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

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

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

revision 1.12 by heimbach, Fri Jul 13 20:14:08 2001 UTC revision 1.32 by heimbach, Thu May 30 02:32:14 2002 UTC
# Line 1  Line 1 
1    C $Header$
2    C $Name$
3    
4  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
5    
6        subroutine forward_step( iloop, mytime, myiter, mythid )  CBOP
7    C     !ROUTINE: FORWARD_STEP
8  c     ==================================================================  C     !INTERFACE:
9  c     SUBROUTINE forward_step        SUBROUTINE FORWARD_STEP( iloop, myTime, myIter, myThid )
10  c     ==================================================================  
11  c  C     !DESCRIPTION: \bv
12  c     o Run the ocean model and evaluate the specified cost function.  C     *==================================================================
13  c  C     | SUBROUTINE forward_step
14  c     *the_main_loop* is the toplevel routine for the Tangent Linear and  C     | o Run the ocean model and, optionally, evaluate a cost function.
15  c     Adjoint Model Compiler (TAMC). For this purpose the initialization  C     *==================================================================
16  c     of the model was split into two parts. Those parameters that do  C     |
17  c     not depend on a specific model run are set in *initialise_fixed*,  C     | THE_MAIN_LOOP is the toplevel routine for the Tangent Linear and
18  c     whereas those that do depend on the specific realization are  C     | Adjoint Model Compiler (TAMC). For this purpose the initialization
19  c     initialized in *initialise_varia*.  C     | of the model was split into two parts. Those parameters that do
20  c     This routine is to be used in conjuction with the MITgcmuv  C     | not depend on a specific model run are set in INITIALISE_FIXED,  
21  c     checkpoint 37.  C     | whereas those that do depend on the specific realization are
22  c  C     | initialized in INITIALISE_VARIA.  
23  c     ==================================================================  C     |
24  c     SUBROUTINE forward_step  C     *==================================================================
25  c     ==================================================================  C     \ev
26    
27        implicit none  C     !USES:
28          IMPLICIT NONE
29  c     == global variables ==  C     == Global variables ==
   
30  #include "SIZE.h"  #include "SIZE.h"
31  #include "EEPARAMS.h"  #include "EEPARAMS.h"
32  #include "PARAMS.h"  #include "PARAMS.h"
33  #include "DYNVARS.h"  #include "DYNVARS.h"
34  #include "FFIELDS.h"  #include "FFIELDS.h"
 #include "TR1.h"  
35    
36  #ifdef ALLOW_NONHYDROSTATIC  #ifdef ALLOW_NONHYDROSTATIC
37  #include "CG3D.h"  #include "CG3D.h"
38  #endif  #endif
39    
40    #ifdef ALLOW_SHAP_FILT
41    #include "SHAP_FILT.h"
42    #endif
43    #ifdef ALLOW_ZONAL_FILT
44    #include "ZONAL_FILT.h"
45    #endif
46    
47  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
48  #include "tamc.h"  # include "tamc.h"
49  #include "ctrl.h"  # include "ctrl.h"
50  #include "ctrl_dummy.h"  # include "ctrl_dummy.h"
51  #include "cost.h"  # include "cost.h"
52    # ifdef INCLUDE_EXTERNAL_FORCING_PACKAGE
53    #  include "exf_fields.h"
54    #  ifdef ALLOW_BULKFORMULAE
55    #   include "exf_constants.h"
56    #  endif
57    # endif
58    # ifdef ALLOW_OBCS
59    #  include "OBCS.h"
60    # endif
61  #endif  #endif
62    
63  c     == routine arguments ==  C     !LOCAL VARIABLES:
64  c     note: under the multi-threaded model myiter and  C     == Routine arguments ==
65  c           mytime are local variables passed around as routine  C     note: under the multi-threaded model myiter and
66  c           arguments. Although this is fiddly it saves the need to  C           mytime are local variables passed around as routine
67  c           impose additional synchronisation points when they are  C           arguments. Although this is fiddly it saves the need to
68  c           updated.  C           impose additional synchronisation points when they are
69  c     myiter - iteration counter for this thread  C           updated.
70  c     mytime - time counter for this thread  C     myiter - iteration counter for this thread
71  c     mythid - thread number for this instance of the routine.  C     mytime - time counter for this thread
72    C     mythid - thread number for this instance of the routine.
73        integer iloop        integer iloop
74        integer mythid        integer mythid
75        integer myiter        integer myiter
76        _RL     mytime        _RL     mytime
77          INTEGER bi,bj
78    
79  c     == local variables ==  CEOP
80    
 c--   == end of interface ==  
   
 c--     >>> Loop body start <<<  
81    
82  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
83  c--     Set the model iteration counter and the model time.  C--     Reset the model iteration counter and the model time.
84          myiter = nIter0 + (iloop-1)          myiter = nIter0 + (iloop-1)
85          mytime = startTime + float(iloop-1)*deltaTclock          mytime = startTime + float(iloop-1)*deltaTclock
86    #endif
87    
88  c       Include call to a dummy routine. Its adjoint will be  #if (defined (ALLOW_AUTODIFF_TAMC) && defined (ALLOW_AUTODIFF_MONITOR))
89  c       called at the proper place in the adjoint code.  C       Include call to a dummy routine. Its adjoint will be
90  c       The adjoint routine will print out adjoint values  C       called at the proper place in the adjoint code.
91  c       if requested. The location of the call is important,  C       The adjoint routine will print out adjoint values
92  c       it has to be after the adjoint of the exchanges  C       if requested. The location of the call is important,
93  c       (DO_GTERM_BLOCKING_EXCHANGES).  C       it has to be after the adjoint of the exchanges
94          call dummy_in_stepping( myTime, myIter, myThid )  C       (DO_GTERM_BLOCKING_EXCHANGES).
95            CALL DUMMY_IN_STEPPING( myTime, myIter, myThid )
96            CALL DO_FIELDS_BLOCKING_EXCHANGES( myThid )
97  #endif  #endif
98    
99  c--     Load forcing/external data fields.  #ifdef EXACT_CONSERV
100          IF (exactConserv) THEN
101    C--   Update etaH(n+1) :
102            DO bj=myByLo(myThid),myByHi(myThid)
103             DO bi=myBxLo(myThid),myBxHi(myThid)
104               CALL CALC_EXACT_ETA( .FALSE., bi,bj, uVel,vVel,
105         I                          myTime, myIter, myThid )
106             ENDDO
107            ENDDO
108            IF (implicDiv2Dflow .NE. 1. _d 0 .OR. useOBCS )
109         &     _EXCH_XY_R8(etaH, myThid )
110          ENDIF
111    #endif /* EXACT_CONSERV */
112    
113    #ifdef NONLIN_FRSURF
114    C--   compute the future surface level thickness
115    C      according to etaH(n+1)
116            IF ( nonlinFreeSurf.GT.0) THEN
117              CALL CALC_SURF_DR(etaH, myTime, myIter, myThid )
118            ENDIF
119    #endif /* NONLIN_FRSURF */
120    
121    C--     Load forcing/external data fields.
122  #ifdef INCLUDE_EXTERNAL_FORCING_PACKAGE  #ifdef INCLUDE_EXTERNAL_FORCING_PACKAGE
123  c       NOTE, that although the exf package is part of the  C       NOTE, that although the exf package is part of the
124  c       distribution, it is not currently maintained, i.e.  C       distribution, it is not currently maintained, i.e.
125  c       exf is disabled by default in genmake.  C       exf is disabled by default in genmake.
126    #ifdef ALLOW_AUTODIFF_TAMC
127    c**************************************
128    #include "checkpoint_lev1_directives.h"
129    c**************************************
130    #endif
131          CALL EXF_GETFORCING( mytime, myiter, mythid )          CALL EXF_GETFORCING( mytime, myiter, mythid )
132  #else  #else
133          CALL TIMER_START('EXTERNAL_FIELDS_LOAD[THE_MAIN_LOOP]',mythid)          CALL TIMER_START('EXTERNAL_FIELDS_LOAD[THE_MAIN_LOOP]',mythid)
# Line 90  c       exf is disabled by default in ge Line 135  c       exf is disabled by default in ge
135          CALL TIMER_STOP ('EXTERNAL_FIELDS_LOAD[THE_MAIN_LOOP]',mythid)          CALL TIMER_STOP ('EXTERNAL_FIELDS_LOAD[THE_MAIN_LOOP]',mythid)
136  #endif  #endif
137    
138  c--     Step forward fields and calculate time tendency terms.  C--     Step forward fields and calculate time tendency terms.
139            CALL TIMER_START('THERMODYNAMICS      [THE_MAIN_LOOP]',mythid)
140            CALL THERMODYNAMICS( myTime, myIter, myThid )
141            CALL TIMER_STOP ('THERMODYNAMICS      [THE_MAIN_LOOP]',mythid)
142    
143    #ifdef ALLOW_SHAP_FILT
144           IF (useSHAP_FILT .AND.
145         &     staggerTimeStep .AND. shap_filt_TrStagg ) THEN
146            CALL TIMER_START('SHAP_FILT           [THE_MAIN_LOOP]',myThid)
147            CALL SHAP_FILT_APPLY_TS( gT, gS, myTime, myIter, myThid )
148            CALL TIMER_STOP ('SHAP_FILT           [THE_MAIN_LOOP]',myThid)
149           ENDIF
150    #endif
151    #ifdef ALLOW_ZONAL_FILT
152           IF (useZONAL_FILT .AND.
153         &     staggerTimeStep .AND. zonal_filt_TrStagg ) THEN
154            CALL TIMER_START('ZONAL_FILT_APPLY    [THE_MAIN_LOOP]',myThid)
155            CALL ZONAL_FILT_APPLY_TS( gT, gS, myThid )
156            CALL TIMER_STOP ('ZONAL_FILT_APPLY    [THE_MAIN_LOOP]',myThid)
157          ENDIF
158    #endif  
159    
160    C--     Step forward fields and calculate time tendency terms.
161            IF ( momStepping ) THEN
162          CALL TIMER_START('DYNAMICS            [THE_MAIN_LOOP]',mythid)          CALL TIMER_START('DYNAMICS            [THE_MAIN_LOOP]',mythid)
163          CALL DYNAMICS( myTime, myIter, myThid )          CALL DYNAMICS( myTime, myIter, myThid )
164          CALL TIMER_STOP ('DYNAMICS            [THE_MAIN_LOOP]',mythid)          CALL TIMER_STOP ('DYNAMICS            [THE_MAIN_LOOP]',mythid)
165            ENDIF
 #ifndef ALLOW_AUTODIFF_TAMC  
166    
167  #ifdef ALLOW_NONHYDROSTATIC  #ifdef ALLOW_NONHYDROSTATIC
168  C--   Step forward W field in N-H algorithm  C--   Step forward W field in N-H algorithm
169          IF ( nonHydrostatic ) THEN          IF ( momStepping .AND. nonHydrostatic ) THEN
170            CALL TIMER_START('CALC_GW          [THE_MAIN_LOOP]',myThid)            CALL TIMER_START('CALC_GW          [THE_MAIN_LOOP]',myThid)
171            CALL CALC_GW(myThid)            CALL CALC_GW(myThid)
172            CALL TIMER_STOP ('CALC_GW          [THE_MAIN_LOOP]',myThid)            CALL TIMER_STOP ('CALC_GW          [THE_MAIN_LOOP]',myThid)
173          ENDIF          ENDIF
174  #endif  #endif
175    
176    #ifdef NONLIN_FRSURF
177    C--   update hfacC,W,S and recip_hFac according to etaH(n+1) :
178          IF ( momStepping ) THEN
179          IF ( nonlinFreeSurf.GT.0) THEN
180            CALL UPDATE_SURF_DR( myTime, myIter, myThid )
181          ENDIF
182    C-    update also CG2D matrix (and preconditioner)
183          IF ( nonlinFreeSurf.GT.2) THEN
184            CALL UPDATE_CG2D( myTime, myIter, myThid )
185          ENDIF
186          ENDIF
187    #endif
188    
189    C--   Apply Filters to u*,v* before SOLVE_FOR_PRESSURE
190  #ifdef ALLOW_SHAP_FILT  #ifdef ALLOW_SHAP_FILT
191  C--   Step forward all tiles, filter and exchange.        IF (useSHAP_FILT .AND. shap_filt_uvStar) THEN
192        CALL TIMER_START('SHAP_FILT           [THE_MAIN_LOOP]',myThid)          CALL TIMER_START('SHAP_FILT           [THE_MAIN_LOOP]',myThid)
193        CALL SHAP_FILT_APPLY(          CALL SHAP_FILT_APPLY_UV( gUnm1,gVnm1, myTime,myIter,myThid )
194       I                     gUnm1, gVnm1, gTnm1, gSnm1,          IF (implicDiv2Dflow.LT.1.) THEN
      I                     myTime, myIter, myThid )  
       IF (implicDiv2Dflow.LT.1.) THEN  
195  C--   Explicit+Implicit part of the Barotropic Flow Divergence  C--   Explicit+Implicit part of the Barotropic Flow Divergence
196  C      => Filtering of uVel,vVel is necessary  C      => Filtering of uVel,vVel is necessary
197           CALL SHAP_FILT_UV( uVel, vVel, myTime, myThid )            CALL SHAP_FILT_APPLY_UV( uVel,vVel, myTime,myIter,myThid )
198            ENDIF
199            CALL TIMER_STOP ('SHAP_FILT           [THE_MAIN_LOOP]',myThid)
200        ENDIF        ENDIF
       CALL TIMER_STOP ('SHAP_FILT           [THE_MAIN_LOOP]',myThid)  
201  #endif  #endif
   
202  #ifdef ALLOW_ZONAL_FILT  #ifdef ALLOW_ZONAL_FILT
203        IF (zonal_filt_lat.LT.90.) THEN        IF (useZONAL_FILT .AND. zonal_filt_uvStar) THEN
204          CALL TIMER_START('ZONAL_FILT_APPLY    [THE_MAIN_LOOP]',myThid)          CALL TIMER_START('ZONAL_FILT_APPLY    [THE_MAIN_LOOP]',myThid)
205          CALL ZONAL_FILT_APPLY(          CALL ZONAL_FILT_APPLY_UV( gUnm1, gVnm1, myThid )
206       U           gUnm1, gVnm1, gTnm1, gSnm1,          IF (implicDiv2Dflow.LT.1.) THEN
207       I           myThid )  C--   Explicit+Implicit part of the Barotropic Flow Divergence
208    C      => Filtering of uVel,vVel is necessary
209              CALL ZONAL_FILT_APPLY_UV( uVel, vVel, myThid )
210            ENDIF
211          CALL TIMER_STOP ('ZONAL_FILT_APPLY    [THE_MAIN_LOOP]',myThid)          CALL TIMER_STOP ('ZONAL_FILT_APPLY    [THE_MAIN_LOOP]',myThid)
212        ENDIF        ENDIF
213  #endif  #endif  
   
 #endif /* ALLOW_AUTODIFF_TAMC */  
214    
215  C--   Solve elliptic equation(s).  C--   Solve elliptic equation(s).
216  C     Two-dimensional only for conventional hydrostatic or  C     Two-dimensional only for conventional hydrostatic or
217  C     three-dimensional for non-hydrostatic and/or IGW scheme.  C     three-dimensional for non-hydrostatic and/or IGW scheme.
218          IF ( momStepping ) THEN
219        CALL TIMER_START('SOLVE_FOR_PRESSURE  [THE_MAIN_LOOP]',myThid)        CALL TIMER_START('SOLVE_FOR_PRESSURE  [THE_MAIN_LOOP]',myThid)
220        CALL SOLVE_FOR_PRESSURE( myThid )        CALL SOLVE_FOR_PRESSURE(myTime, myIter, myThid)
221        CALL TIMER_STOP ('SOLVE_FOR_PRESSURE  [THE_MAIN_LOOP]',myThid)        CALL TIMER_STOP ('SOLVE_FOR_PRESSURE  [THE_MAIN_LOOP]',myThid)
222          ENDIF
223    
224  C--   Correct divergence in flow field and cycle time-stepping  C--   Correct divergence in flow field and cycle time-stepping
225  C     arrays (for all fields) ; update time-counter  C     arrays (for all fields) ; update time-counter
# Line 157  C--   Do "blocking" sends and receives f Line 239  C--   Do "blocking" sends and receives f
239        CALL DO_FIELDS_BLOCKING_EXCHANGES( myThid )        CALL DO_FIELDS_BLOCKING_EXCHANGES( myThid )
240        CALL TIMER_STOP ('BLOCKING_EXCHANGES  [THE_MAIN_LOOP]',myThid)        CALL TIMER_STOP ('BLOCKING_EXCHANGES  [THE_MAIN_LOOP]',myThid)
241    
242    #ifdef ALLOW_FLT
243    C--   Calculate float trajectories
244          IF (useFLT) THEN
245            CALL TIMER_START('FLOATS            [THE_MAIN_LOOP]',myThid)
246            CALL FLT_MAIN(myIter,myTime, myThid)
247            CALL TIMER_STOP ('FLOATS            [THE_MAIN_LOOP]',myThid)
248          ENDIF
249    #endif
250    
251  #ifndef EXCLUDE_MONITOR  #ifndef EXCLUDE_MONITOR
252  C--   Check status of solution (statistics, cfl, etc...)  C--   Check status of solution (statistics, cfl, etc...)
253        CALL MONITOR( myIter, myTime, myThid )        CALL MONITOR( myIter, myTime, myThid )
# Line 188  C     at time level 1 Line 279  C     at time level 1
279    
280  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
281    
 c--           >>> Loop body end <<<  
   
282        END        END

Legend:
Removed from v.1.12  
changed lines
  Added in v.1.32

  ViewVC Help
Powered by ViewVC 1.1.22