timestep


ここでは,一回のタイムステップで行う計算を操っている. DoループはSubroutine MODEL で行われる.


C##############################################################
      SUBROUTINE TIMESTEP(A,B)
      DIMENSION A(*),B(*)
      include 'rcommons.h'
C
     
C--------------------------------------------------------------------
C
      elseif (itmdiff.eq.3) then
c     +-------------------------------------------------------------+
c     |   timestep driver for the hybrid non-hydrostatic time-split |
c     |      model.                                                 |
c     +-------------------------------------------------------------+
c         IF ((TIME.LE.0.1).and.(NGRID.EQ.1)) 
c         IF (NGRID.EQ.2) 
c         CALL OUTKAN(nzp,nxp,nyp,a(ISHEAT),a(ISRFHH),a(ISRFLE),
c     +         a(ISRFRN),a(ISRFGG),
c     +         a(IUP),a(IVP),a(IWP),a(IRV),a(ITHP))  
c         CALL CNGFRQANL
c
         call tend0(a)                     !  zero out all tendency arrays
c
         CALL pert(nzp,nxp,nyp,a(isclt(1)),a(ISHEAT),a(IPCTLND))
c
         if(icloud(1).lt.0) call thermo('PAST','MICRO',A)
         call radiate(a)                   !  radiation
         if(nqparm.eq.1) call cuparm(a)    !  cumulus parameterization 
         call sfclyr(a)                    !  surface layer, soil and veggie
c
c  START USING BOUNDARY VELOCITIES AND SCALARS NOW
c
         call diffuse(a)                   !  subgrid diffusion
         call corlos(a)                    !  coriolis terms
         if(initial.eq.2) call datassim(a) !  nudging boundary condition
         call fadvect(a,'T')               !  advection terms for scalars
         call rayft(a)                     !  rayleigh friction for theta
         if(ngrid.ne.1) call nstbdriv(a,b) !  nesting boundary conditions
         call predtr(a)                    !  update scalars
         if(icloud(1).ge.0) then
            call negadj1(a) !  moisture variables pos. def.
            call micro(a)
         endif                  !  microphysics
         call trsets(a)                    !  apply scalar b.c.'s
C     ---------------------------------------------------------------
c        CALL REPLACE_RT(nzp,nxp,nyp,a(IPP),a(IPI0),a(ITHETA)
c     +   ,a(irtp),a(ivgtyp),ZMN)
c         call INOVG
C     ---------------------------------------------------------------
c  SEND SCALARS TO MASTER NOW, AND HAVE MASTER SEND THEM BACK
c
         call ladvect(a,'V')               !  advection terms for velocities
         call latbnd(a)                    !  lateral boundaries - radiative
         call filter(a)                    !  smoothing routines
         call hadvance(1,a)                !  first stage asselin filter
         if(time.lt.timscl) call windin(a) !  spinup wind field if desired.
         call thermo('PAST','NOMICRO',a)     !  theta/vapor/cloud diagnosis
C     ---------------------------------------------------------------
C         IF (TIME.GT.0)
c        CALL RSUT_INO(nzp,nxp,nyp,a(IPP),a(IPI0),a(ITHETA)
c     +   ,a(IRV),a(irtp),a(ivgtyp))
C     ---------------------------------------------------------------
         if(nonhyd.eq.0) then              !  small timestep drivers
            call hydsdt(a)
         elseif(nonhyd.eq.1) then
            call buoyancy(a)
            call acoustc(a)
         endif


         call hadvance(2,a)                !  last stage of asselin filter
         call vpsets(a)                    !  velocity/pressure boundary conds


c
c  SEND VELOCITIES AND PRESSURE TO MASTER NOW, AND HAVE MASTER SEND THEM BACK
c
      endif
      if(mod(istp,5).eq.0) call cfl(a)
c
      return
      end
C

C
C     ******************************************************************
C