mo_control.f90

      MODULE mo_control
      
        ! Control variables for model housekeeping.
        !
   5:   ! U. Schlese, DKRZ, December 1994
        ! A. Rhodin, MPI, January 1999,
        !      Subroutine m_control renamed to alloc_mods and moved from
        !      module mo_control to module m_alloc_mods.
        ! L. Kornblueh, MPI, June 1999,
  10:   !      added nproca and nprocb for driving the parallel decomposition
      
        IMPLICIT NONE
      
        REAL :: dtime             !   time step (in seconds).
  15:   REAL :: twodt             !   2.*dtime.
        REAL :: eps               !   time filtering coefficient.
      
        REAL, ALLOCATABLE :: vct(:)      !   vertical coefficients table.
      
  20: 
        INTEGER :: nproca         !   number of processors in set A
        INTEGER :: nprocb         !   number of processors in set A
        INTEGER :: nm             !   max zonal wave number.
        INTEGER :: nn             !   max meridional wave number for m=0.
  25:   INTEGER :: nk             !   max meridional wave number.
        INTEGER :: ngl            !   number of gaussian latitudes.
        INTEGER :: nlon           !   max number of points on each latitude line.
        INTEGER :: nlev           !   number of vertical levels.
        INTEGER :: nmp1           !   max zonal wave number + 1.
  30:   INTEGER :: nnp1           !   max meridional wave number + 1.
        INTEGER :: nkp1
        INTEGER :: n2mp1          !   2 * (max zonal wave number + 1).
        INTEGER :: n4mp1          !   4 * (max zonal wave number + 1).
        INTEGER :: nlp2           !   max number of points per latitude line + 2.
  35:   INTEGER :: nlevp1         !   *nlev+1.
        INTEGER :: nsp            !   number of spectral coefficients.
        INTEGER :: n2sp           !   2*number of spectral coefficients.
        INTEGER :: nhgl           !   (number of gaussian latitudes)/2.
        INTEGER :: nscan          !   current scan number.
  40:   INTEGER :: nresum         !   time step at which the run started or was
        !                             reumed after interruption.
        INTEGER :: nspace1        !   memory manager space for use of root task
        INTEGER :: nspace2        !   memory manager space for use of subtasks
        INTEGER :: ncbase         !   century date of the initial data.
  45:   INTEGER :: ntbase         !   time of the initial data.
        INTEGER :: ncdata         !   verifying (century) date of the initial data.
        INTEGER :: ntdata         !   verifying time of the initial data.
        INTEGER :: ntimst         !   constant to convert *ntbase* into seconds.
        INTEGER :: nspadd         !   memory manager space increase
  50:   INTEGER :: nwtime         !   rerun write-up interval
        INTEGER :: nptime         !   array of post-processing times required
        INTEGER :: n4ptime
        INTEGER :: nwlag          !   rerun-files saving interval in months
        INTEGER :: nsub           !   number of jobs to be submitted at end of ru
  55:   INTEGER :: nsubint(9)     !   submit-interval in months
        INTEGER :: nstop          !   last time step.
        INTEGER :: nrow(3)        !   current latitude line. (one entry per task).
        INTEGER :: maxrow         !   number of latitude lines.
        INTEGER :: nvclev         !   number of levels with vertical coefficients.
  60:   INTEGER :: nlat(1)        !   current "geographic" latitude line
        !                             from north to south (one entry per task)
        INTEGER :: numfl1         !   number of optional fields read at nstep=0
        INTEGER :: numfl2         !   number of optional fields read at nstep=nresum
      
  65: !! see in extra namelist for nudging
      !!  INTEGER :: ndstart      !   start date of a run
      !!  INTEGER :: ntstart      !   start time of a run
      !!  INTEGER :: ndrer(31)    !   day of month (a rerun files should be prepared)
        INTEGER :: nmend          
  70: !!  INTEGER :: nsstini      !   observed sst every nsstini hours
      
        LOGICAL :: labort
        LOGICAL :: lwtime         !   .TRUE. when history writeup is due
        LOGICAL :: lptime         !   .TRUE. when postprocessing step is due
  75:   LOGICAL :: lrepro         !   .TRUE. for reproducable results in multitsk.
        LOGICAL :: ldebug         !   .TRUE. for mass fixer diagnostics
        LOGICAL :: lwmonth        !   .TRUE. to force history event at end of month
        LOGICAL :: lg4x
        LOGICAL :: l4ptime
  80:   LOGICAL :: lamip          !   .TRUE. for using variable sst
        LOGICAL :: lsub           !   .TRUE. to submit *nsub* jobs
        LOGICAL :: lsstadj        !   .TRUE. for orographic adjustment of sst
        LOGICAL :: lhg3x          !   .TRUE. to use g3x info from history files
        LOGICAL :: lcouple        !   .TRUE. for a coupled run
  85:   LOGICAL :: lnwp           !   .FALSE. for climate mode .true. for NWP mode
        LOGICAL :: lanalysis      !   .FALSE. for climate mode .true. for analysis
        LOGICAL :: lnudge         !   .TRUE. for Nudging mode
        LOGICAL :: lmidatm        !   .TRUE. for middle atmosphere model version
      
  90:   LOGICAL :: lnmi           !   .TRUE. normal mode initialisation
        LOGICAL :: ltdiag         !   .TRUE. run with additional diagnostics of tendency terms
      
        LOGICAL :: lcond5         !   .TRUE. for cond5
      
  95: END MODULE mo_control


Info Section
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.