mo_start_dataset.f90

      MODULE mo_start_dataset
      
        IMPLICIT NONE
      
   5:   ! U. Schlese, DKRZ, December 1994, original source
      
        INTEGER :: nstart   !  time step for start/restart.
        INTEGER :: nstep    !  current time step.
        INTEGER :: ntwodt   !  2 * time step interval (milliseconds).
  10:   INTEGER :: neps     !  1000 * time filter coefficient.
        INTEGER :: nf1a     !  `
        INTEGER :: nf3a     !   > indices for fourier buffers.
        INTEGER :: nf4a     !  '
        INTEGER :: ng1a     !  `
  15:   INTEGER :: ng2a     !   > indices for grid point buffers.
        INTEGER :: ng3a     !  
        INTEGER :: ng4a     !  '
        INTEGER :: ngl1a    !  index for grid point slt buffer.
        INTEGER :: ndiafi   !  length of a run in days
  20:   INTEGER :: ndiahdf  !  logical unit for hdiff diagnostics.
        INTEGER :: nemi     !  logical unit for surface emission file
        INTEGER :: nini     !  logical unit for tracer initial file
        INTEGER :: nisp     !  logical unit  for initial spectral fields.
        INTEGER :: nigp     !  logical unit  for initial grid point fields.
  25:   INTEGER :: nfl1     !  logical unit for optional file read at nstep=0
        INTEGER :: nfl2     !  logical unit for optional file read at nresum
        INTEGER :: nist     !  logical unit for surf.temp. file
        INTEGER :: nhf1     !  `
        INTEGER :: nhf3     !   > logical units for fourier history files.
  30:   INTEGER :: nhf4     !  '
        INTEGER :: nhg1     !  `
        INTEGER :: nhg2     !   >logical units for grid point history files.
        INTEGER :: nhg3     !  
        INTEGER :: nhg4     !  '
  35:   INTEGER :: nl1a     !  index for legendre coefficients buffer
        INTEGER :: nhgl1    !  logical unit for grid point slt work file
        INTEGER :: ngribs   !  logical unit for spectral grib file
        INTEGER :: ngribg   !  logical unit for gridpoint grib file
        INTEGER :: ngribx   !  logical unit for g4x grib file
  40:   INTEGER :: njin     !  logical unit for "jobn" input file
        INTEGER :: njout    !  logical unit for "subjobn" output file
      
        LOGICAL :: lres     !  .TRUE. if forecast is restarted.
        LOGICAL :: ldebugio !  .TRUE. to debug IO
  45:   LOGICAL :: ldebugmem!  .TRUE. to debug memory
        LOGICAL :: ly365    !  .TRUE. use 365 days
      
      CONTAINS
      
  50:   SUBROUTINE initsd
      
          ! Description:
          !
          ! Sets unit numbers and buffer indices.
  55:     !
          ! Method:
          !
          ! Variables are assigned preset values which may be modified
          ! by namelist *sdsctl*.
  60:     !
          ! Authors:
          !
          ! U. Schlese, DKRZ, December 1994, original source
          ! L. Kornblueh, MPI, May 1998, f90 rewrite
  65:     ! U. Schulzweida, MPI, May 1998, f90 rewrite
          ! L. Kornblueh, MPI, June 1999, parallel version (MPI based)
          ! 
          ! for more details see file AUTHORS
          !
  70: 
          USE mo_mpi
          USE mo_doctor
      
          INCLUDE 'sdsctl.inc'
  75: 
          !  Executable statements 
      
          !-- 1. Pre-set values
      
  80:     !-- 1.1 Basic constants
      
          nstart = 0
          nstep  = 0
          ntwodt = 0
  85:     neps   = 0
      
          ! Length of a run in days
      
          ndiafi = 30
  90: 
          !-- 1.2 Logical units for files and buffer indices
      
          ! Subjob files "jobn" and "subjobn"
      
  95:     njin  = 30
          njout = 39
      
          ! *Fourier work file and buffers.
      
 100:     nf1a = 26
          nf3a = 43
          nf4a = 44
      
          ! Grid point work file and buffers.
 105: 
          ng1a = 27
          ng2a = 62
          ng3a = 63
          ng4a = 64
 110: 
          ! Gridpoint buffer index for slt-variables
      
          ngl1a = 28
      
 115:     ! Spectral and grid point initial files.
      
          nisp = 23
          nigp = 24
      
 120:     ! Legendre polynomial coefficients buffer index
      
          nl1a = 25
      
          ! Surface temperature annual cycle file
 125: 
          nist = 20
      
          ! File for surface emissions
      
 130:     nemi = 15
      
          ! Optional files
      
          nini = 12
 135:     nfl1 = 13
          nfl2 = 14
      
          ! Grib output files
      
 140:     ngribs = 29
          ngribg = ngribs
          ngribx = 16
      
          ! History files.
 145: 
          nhf1 = 31
          nhf3 = 33
          nhf4 = 34
      
 150:     nhgl1 = 32
      
          nhg1 = 35
          nhg2 = 36
          nhg3 = 37
 155:     nhg4 = 38
      
          ! File for diagnostics of horizontal diffusion
      
          ndiahdf = 11
 160: 
          !-- 1.3 Initial values for logical flags
      
          lres = .TRUE.
      
 165:     !-- 1.4 Optional variables for user defined purposes
      
          ldebugio  = .FALSE.
          ldebugmem = .FALSE.
      
 170:     ! climate mode is 360 days per year (30 day months)
          ly365 = .FALSE.
      
          !-- 2. Read namelist sdsctl
      
 175:     IF (p_parallel) THEN
             IF (p_parallel_io) THEN
                READ (nin,sdsctl)
             ENDIF
             CALL p_bcast (nstart, p_io)
 180:        CALL p_bcast (nstep, p_io)
             CALL p_bcast (nf1a, p_io)
             CALL p_bcast (ng1a, p_io)
             CALL p_bcast (ngl1a, p_io)
             CALL p_bcast (nl1a, p_io)
 185:        CALL p_bcast (nisp, p_io)
             CALL p_bcast (nigp, p_io)
             CALL p_bcast (ndiafi, p_io)
             CALL p_bcast (ndiahdf, p_io)
             CALL p_bcast (nemi, p_io)
 190:        CALL p_bcast (nist, p_io)
             CALL p_bcast (nhf1, p_io)
             CALL p_bcast (nhf3, p_io)
             CALL p_bcast (nhf4, p_io)
             CALL p_bcast (nhg1, p_io)
 195:        CALL p_bcast (nhg2, p_io)
             CALL p_bcast (nhg3, p_io)
             CALL p_bcast (nhg4, p_io)
             CALL p_bcast (nhgl1, p_io)
             CALL p_bcast (nfl1, p_io)
 200:        CALL p_bcast (nfl2, p_io)
             CALL p_bcast (nini, p_io)
             CALL p_bcast (ngribs, p_io)
             CALL p_bcast (ngribg, p_io)
             CALL p_bcast (ngribx, p_io)
 205:        CALL p_bcast (njin, p_io)
             CALL p_bcast (njout, p_io)
             CALL p_bcast (lres, p_io)
             CALL p_bcast (ldebugio, p_io)
             CALL p_bcast (ldebugmem, p_io)
 210:        CALL p_bcast (ly365, p_io)
          ELSE
             READ (nin,sdsctl)
          ENDIF
      
 215:   END SUBROUTINE initsd
      
      
      
      END MODULE mo_start_dataset


Info Section
uses: mo_doctor, mo_mpi includes: sdsctl.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.