mo_tracer.f90

      MODULE mo_tracer
      
        USE mo_parameters
      
   5:   IMPLICIT NONE
      
        ! J. Feichter, MI, September 1990, original source
      
        INTEGER :: ntrac
  10:   INTEGER :: ntraca
        INTEGER :: nhtrac
        INTEGER :: ntcode(jptrac)
        INTEGER :: nfix(jps)
        INTEGER :: nfixt(jptrac)
  15:   INTEGER :: ifileini
        INTEGER :: ifileemi
      
        LOGICAL :: lppxt(jptrac)
        LOGICAL :: lhtrac
  20:   LOGICAL :: lslt(jptrac)
        LOGICAL :: lxtvdiff
        LOGICAL :: lxtconv
        LOGICAL :: lwetdep(jptrac)
        LOGICAL :: lemis
  25: 
        REAL    :: sxtini(jptrac)
        REAL    :: sxtemi(jptrac)
        REAL    :: vdrydep(jptrac)
        REAL    :: sxtsink(jptrac)
  30: 
      CONTAINS
      
        SUBROUTINE initrac
      
  35:     ! Description:
          !
          ! Preset constants in tractl.
          !
          ! Method:
  40:     !
          ! Preset and read the namelist *tractl*.
          !
          ! *inictl* is called from *initialise*.
          !
  45:     ! Authors:
          !
          ! J. Feichter, MI, September 1990, original source
          ! U. Hansson, MI, July 1991, changed
          ! L. Kornblueh, MPI, May 1998, f90 rewrite
  50:     ! U. Schulzweida, MPI, May 1998, f90 rewrite
          ! L. Kornblueh, MPI, June 1999, parallel version (MPI based)
          ! 
          ! for more details see file AUTHORS
          !
  55: 
          USE mo_parameters
          USE mo_mpi
          USE mo_doctor
          USE mo_start_dataset
  60: 
          IMPLICIT NONE
      
          !  Local scalars: 
          INTEGER :: icode, itraca, j, jt
  65: 
          INCLUDE 'tractl.inc'
      
          !  Executable statements 
      
  70:     !-- 1. Preset namelist variables
      
          ntrac = 0
          lhtrac = .FALSE.
          icode = 234
  75: 
          DO j = 1, jps
             nfix(j) = 1
          END DO
          DO jt = 1, jptrac
  80:        lppxt(jt) = .FALSE.
             lslt(jt) = .TRUE.
             nfixt(jt) = 1
             icode = icode + 1
             ntcode(jt) = icode
  85:        sxtini(jt) = 0.
             sxtemi(jt) = 0.
             vdrydep(jt) = 0.
             sxtsink(jt) = 0.
          END DO
  90: 
          lxtvdiff = .TRUE.
          lxtconv = .TRUE.
      
          !-- 2. Read namelist tractl
  95: 
          IF (p_parallel) THEN
             IF (p_parallel_io) THEN
                READ (nin,tractl)
             ENDIF
 100:        CALL p_bcast (ntrac, p_io)
             CALL p_bcast (lslt, p_io)
             CALL p_bcast (lppxt, p_io)
             CALL p_bcast (lhtrac, p_io)
             CALL p_bcast (ntcode, p_io)
 105:        CALL p_bcast (nfix, p_io)
             CALL p_bcast (nfixt, p_io)
             CALL p_bcast (lxtvdiff, p_io)
             CALL p_bcast (lxtconv, p_io)
             CALL p_bcast (lwetdep, p_io)
 110:        CALL p_bcast (sxtini, p_io)
             CALL p_bcast (sxtemi, p_io)
             CALL p_bcast (vdrydep, p_io)
             CALL p_bcast (sxtsink, p_io)
          ELSE
 115:        READ (nin,tractl)
          ENDIF
      
          ! Choose number of tracers in case of rerun
      
 120:     itraca = 0
          DO jt = 1, ntrac
             IF (lslt(jt)) itraca = itraca + 1
             IF ( .NOT. lslt(jt)) nfixt(jt) = 0
          END DO
 125:     ntraca = itraca
      
          IF (ntrac==0) THEN
             lxtvdiff = .FALSE.
             lxtconv = .FALSE.
 130:     END IF
      
        END SUBROUTINE initrac
      
      END MODULE mo_tracer


Info Section
uses: mo_doctor, mo_mpi, mo_parameters, mo_start_dataset includes: tractl.inc calls: p_bcast
back to top
ECHAM 4 vf90 (C) 1998 Max-Planck-Institut für Meteorologie, Hamburg
Wed Nov 24 01:25:21 CST 1999

HTML derived from FORTRAN source by f2html.pl v0.3 (C) 1997,98 Beroud Jean-Marc.