/[MITgcm]/MITgcm/model/src/do_statevars_diags.F
ViewVC logotype

Diff of /MITgcm/model/src/do_statevars_diags.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph | View Patch Patch

revision 1.4 by jmc, Tue Jan 4 02:42:31 2005 UTC revision 1.14 by jahn, Fri Jun 26 23:10:09 2009 UTC
# Line 8  C $Name$ Line 8  C $Name$
8  CBOP  CBOP
9  C     !ROUTINE: DO_STATEVARS_DIAGS  C     !ROUTINE: DO_STATEVARS_DIAGS
10  C     !INTERFACE:  C     !INTERFACE:
11        SUBROUTINE DO_STATEVARS_DIAGS( myTime, myIter, myThid )        SUBROUTINE DO_STATEVARS_DIAGS( myTime, seqFlag, myIter, myThid )
12  C     !DESCRIPTION: \bv  C     !DESCRIPTION: \bv
13  C     *==========================================================*  C     *==========================================================*
14  C     | SUBROUTINE DO_STATEVARS_DIAGS                                  C     | SUBROUTINE DO_STATEVARS_DIAGS
15  C     | o Controlling routine for state variables diagnostics  C     | o Controlling routine for state variables diagnostics
16  C     *==========================================================*  C     *==========================================================*
17  C     | Computing statistics of the model state (state-variables)  C     | Computing diagnostics of the model state (state-variables)
18  C     | is done at this level (after updating the halo region),  C     | is done at this level ;
19  C     | as opposed to other diagnostic calls (fluxes, tendencies)  C     | by contrast, other diagnostics (fluxes, tendencies)
20  C     | that remain within the computation sequence.    C     | remain within the computation sequence.
 C     | Note: IO are not supposed to be done at this level  
 C     |       but later (in DO_THE_MODEL_IO)  
21  C     *==========================================================*  C     *==========================================================*
22  C     \ev  C     \ev
23    
# Line 32  C     == Global variables === Line 30  C     == Global variables ===
30    
31  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
32  C     == Routine arguments ==  C     == Routine arguments ==
33  C     myTime - Current time of simulation ( s )  C     myTime  :: Current time of simulation ( s )
34  C     myIter - Iteration number  C     seqFlag :: flag that indicate where this S/R is called from:
35  C     myThid - Thread number for this instance of the routine.  C             :: =0 called from the beginning of forward_step
36    C             :: =1 called from the middle of forward_step
37    C             :: =2 called from the end of forward_step
38    C     myIter  :: Iteration number
39    C     myThid  :: Thread number for this instance of the routine.
40        _RL     myTime        _RL     myTime
41          INTEGER seqFlag
42        INTEGER myIter        INTEGER myIter
43        INTEGER myThid        INTEGER myThid
   
44  CEOP  CEOP
45    
46    #ifdef ALLOW_DIAGNOSTICS
47  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
48  C     == Local variables  C     == Local variables ==
49        INTEGER bi,bj  C     selectVars :: select which group of dianostics variables to fill-in
50    C            = 1 :: fill-in diagnostics for tracer   variables only
51    C            = 2 :: fill-in diagnostics for momentum variables only
52    C            = 3 :: fill-in diagnostics for momentum & tracer variables
53    C            = 4 :: fill-in state variable tendency diagnostics the second time
54    C     bi,bj      :: tile indices
55          INTEGER selectVars
56    #if defined(ALLOW_THSICE) || defined(ALLOW_LAND)
57          INTEGER bi, bj
58    #endif
59    
60  #ifdef ALLOW_TIMEAVE  C--   Fill-in Diagnostics pkg storage array (for state-variables)
61  C--   Fill-in TimeAve pkg diagnostics (for state-variables)        IF ( usediagnostics ) THEN
62    
63        DO bj=myByLo(myThid),myByHi(myThid)  C-    select which group of state-var diagnostics to fill-in,
64         DO bi=myBxLo(myThid),myBxHi(myThid)  C      depending on: where this S/R is called from (seqFlag)
65    C                    and stagger/synchronous TimeStep
66            selectVars = 0
67            IF ( staggerTimeStep ) THEN
68              IF ( seqFlag.EQ.0 ) selectVars = 2
69              IF ( seqFlag.EQ.1 ) selectVars = 1
70            ELSE
71              IF ( seqFlag.EQ.0 ) selectVars = 3
72            ENDIF
73            IF ( seqFlag.EQ.2 ) selectVars = 4
74            CALL DIAGNOSTICS_FILL_STATE(selectVars, myThid)
75    
76          IF ( taveFreq.GT.0. ) THEN  #ifdef ALLOW_GENERIC_ADVDIFF
77            CALL TIMEAVE_STATVARS(myTime, myIter, bi, bj, myThid)          IF ( seqFlag.EQ.0 .AND. useGAD ) THEN
78  # ifdef ALLOW_PTRACERS            CALL GAD_DIAGNOSTICS_STATE( myTime, myIter, myThid )
           IF ( usePTRACERS ) THEN        
            CALL PTRACERS_STATVARS(myTime, myIter, bi, bj, myThid)  
           ENDIF  
 # endif /* ALLOW_PTRACERS */  
79          ENDIF          ENDIF
80    #endif /* ALLOW_GENERIC_ADVDIFF */
81    
82  C--    End of bi,bj loop  #ifdef ALLOW_PTRACERS
83         ENDDO          IF ( (selectVars.EQ.1 .OR. selectVars.EQ.3)
84        ENDDO       &      .AND. usePTRACERS ) THEN
85  #endif /* ALLOW_TIMEAVE */            CALL PTRACERS_DIAGNOSTICS_STATE( myTime, myIter, myThid )
86            ENDIF
87    #endif
88    
89  #ifdef ALLOW_DIAGNOSTICS  #ifdef ALLOW_SEAICE
90  C--   Fill-in Diagnostics pkg storage array (for state-variables)         IF ( seqFlag.EQ.0 .AND. useSEAICE ) THEN
91            CALL SEAICE_DIAGNOSTICS_STATE( myTime, myIter, myThid )
92           ENDIF
93    #endif /* ALLOW_SEAICE */
94    
95        IF ( usediagnostics ) THEN  #ifdef ALLOW_THSICE
96          CALL DIAGNOSTICS_FILL_STATE(myThid)         IF ( seqFlag.EQ.0 .AND. useThSIce ) THEN
97  # ifdef ALLOW_PTRACERS          DO bj=myByLo(myThid),myByHi(myThid)
98         IF (usePTRACERS) THEN           DO bi=myBxLo(myThid),myBxHi(myThid)
99          CALL PTRACERS_DIAGNOSTICS_FILL(myThid)            CALL THSICE_DIAGNOSTICS_STATE( myTime,myIter,bi,bj,myThid )
100             ENDDO
101            ENDDO
102         ENDIF         ENDIF
103  # endif  #endif /* ALLOW_THSICE */
104        ENDIf  
105    #ifdef ALLOW_LAND
106           IF ( seqFlag.EQ.0 .AND. useLand ) THEN
107            DO bj=myByLo(myThid),myByHi(myThid)
108             DO bi=myBxLo(myThid),myBxHi(myThid)
109              CALL LAND_DIAGNOSTICS_STATE( myTime,myIter, bi,bj, myThid )
110             ENDDO
111            ENDDO
112           ENDIF
113    #endif /* ALLOW_LAND */
114    
115    #ifdef ALLOW_MYPACKAGE
116           IF ( seqFlag.EQ.0 .AND. useMYPACKAGE ) THEN
117             CALL MYPACKAGE_DIAGNOSTICS_STATE( myTime, myIter, myThid )
118           ENDIF
119    #endif /* ALLOW_MYPACKAGE */
120    
121          ENDIf
122  #endif /* ALLOW_DIAGNOSTICS */  #endif /* ALLOW_DIAGNOSTICS */
123    
124        RETURN        RETURN

Legend:
Removed from v.1.4  
changed lines
  Added in v.1.14

  ViewVC Help
Powered by ViewVC 1.1.22