/[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.13 by adcroft, Fri Jul 20 15:53:10 2001 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 )        SUBROUTINE FORWARD_STEP( iloop, myTime, myIter, myThid )
7          IMPLICIT NONE
8    
9  c     ==================================================================  c     ==================================================================
10  c     SUBROUTINE forward_step  c     SUBROUTINE forward_step
# Line 15  c     of the model was split into two pa Line 18  c     of the model was split into two pa
18  c     not depend on a specific model run are set in *initialise_fixed*,  c     not depend on a specific model run are set in *initialise_fixed*,
19  c     whereas those that do depend on the specific realization are  c     whereas those that do depend on the specific realization are
20  c     initialized in *initialise_varia*.  c     initialized in *initialise_varia*.
 c     This routine is to be used in conjuction with the MITgcmuv  
 c     checkpoint 37.  
 c  
 c     ==================================================================  
 c     SUBROUTINE forward_step  
 c     ==================================================================  
   
       implicit none  
   
 c     == global variables ==  
21    
22    C     == global variables ==
23  #include "SIZE.h"  #include "SIZE.h"
24  #include "EEPARAMS.h"  #include "EEPARAMS.h"
25  #include "PARAMS.h"  #include "PARAMS.h"
# Line 44  c     == global variables == Line 38  c     == global variables ==
38  #include "cost.h"  #include "cost.h"
39  #endif  #endif
40    
41  c     == routine arguments ==  C     == routine arguments ==
42  c     note: under the multi-threaded model myiter and  C     note: under the multi-threaded model myiter and
43  c           mytime are local variables passed around as routine  C           mytime are local variables passed around as routine
44  c           arguments. Although this is fiddly it saves the need to  C           arguments. Although this is fiddly it saves the need to
45  c           impose additional synchronisation points when they are  C           impose additional synchronisation points when they are
46  c           updated.  C           updated.
47  c     myiter - iteration counter for this thread  C     myiter - iteration counter for this thread
48  c     mytime - time counter for this thread  C     mytime - time counter for this thread
49  c     mythid - thread number for this instance of the routine.  C     mythid - thread number for this instance of the routine.
50        integer iloop        integer iloop
51        integer mythid        integer mythid
52        integer myiter        integer myiter
53        _RL     mytime        _RL     mytime
54    
55  c     == local variables ==  C     == local variables ==
56    
 c--   == end of interface ==  
   
 c--     >>> Loop body start <<<  
57    
58  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
59  c--     Set the model iteration counter and the model time.  C--     Set the model iteration counter and the model time.
60          myiter = nIter0 + (iloop-1)          myiter = nIter0 + (iloop-1)
61          mytime = startTime + float(iloop-1)*deltaTclock          mytime = startTime + float(iloop-1)*deltaTclock
62    
63  c       Include call to a dummy routine. Its adjoint will be  C       Include call to a dummy routine. Its adjoint will be
64  c       called at the proper place in the adjoint code.  C       called at the proper place in the adjoint code.
65  c       The adjoint routine will print out adjoint values  C       The adjoint routine will print out adjoint values
66  c       if requested. The location of the call is important,  C       if requested. The location of the call is important,
67  c       it has to be after the adjoint of the exchanges  C       it has to be after the adjoint of the exchanges
68  c       (DO_GTERM_BLOCKING_EXCHANGES).  C       (DO_GTERM_BLOCKING_EXCHANGES).
69          call dummy_in_stepping( myTime, myIter, myThid )          CALL DUMMY_IN_STEPPING( myTime, myIter, myThid )
70  #endif  #endif
71    
72  c--     Load forcing/external data fields.  C--     Load forcing/external data fields.
73  #ifdef INCLUDE_EXTERNAL_FORCING_PACKAGE  #ifdef INCLUDE_EXTERNAL_FORCING_PACKAGE
74  c       NOTE, that although the exf package is part of the  C       NOTE, that although the exf package is part of the
75  c       distribution, it is not currently maintained, i.e.  C       distribution, it is not currently maintained, i.e.
76  c       exf is disabled by default in genmake.  C       exf is disabled by default in genmake.
77          CALL EXF_GETFORCING( mytime, myiter, mythid )          CALL EXF_GETFORCING( mytime, myiter, mythid )
78  #else  #else
79          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 81  c       exf is disabled by default in ge
81          CALL TIMER_STOP ('EXTERNAL_FIELDS_LOAD[THE_MAIN_LOOP]',mythid)          CALL TIMER_STOP ('EXTERNAL_FIELDS_LOAD[THE_MAIN_LOOP]',mythid)
82  #endif  #endif
83    
84  c--     Step forward fields and calculate time tendency terms.  C--     Step forward fields and calculate time tendency terms.
85          CALL TIMER_START('DYNAMICS            [THE_MAIN_LOOP]',mythid)          CALL TIMER_START('DYNAMICS            [THE_MAIN_LOOP]',mythid)
86          CALL DYNAMICS( myTime, myIter, myThid )          CALL DYNAMICS( myTime, myIter, myThid )
87          CALL TIMER_STOP ('DYNAMICS            [THE_MAIN_LOOP]',mythid)          CALL TIMER_STOP ('DYNAMICS            [THE_MAIN_LOOP]',mythid)
88    
89  #ifndef ALLOW_AUTODIFF_TAMC  #ifndef ALLOW_AUTODIFF_TAMC
   
90  #ifdef ALLOW_NONHYDROSTATIC  #ifdef ALLOW_NONHYDROSTATIC
91  C--   Step forward W field in N-H algorithm  C--   Step forward W field in N-H algorithm
92          IF ( nonHydrostatic ) THEN          IF ( nonHydrostatic ) THEN
# Line 105  C--   Step forward W field in N-H algori Line 95  C--   Step forward W field in N-H algori
95            CALL TIMER_STOP ('CALC_GW          [THE_MAIN_LOOP]',myThid)            CALL TIMER_STOP ('CALC_GW          [THE_MAIN_LOOP]',myThid)
96          ENDIF          ENDIF
97  #endif  #endif
   
 #ifdef ALLOW_SHAP_FILT  
 C--   Step forward all tiles, filter and exchange.  
       CALL TIMER_START('SHAP_FILT           [THE_MAIN_LOOP]',myThid)  
       CALL SHAP_FILT_APPLY(  
      I                     gUnm1, gVnm1, gTnm1, gSnm1,  
      I                     myTime, myIter, myThid )  
       IF (implicDiv2Dflow.LT.1.) THEN  
 C--   Explicit+Implicit part of the Barotropic Flow Divergence  
 C      => Filtering of uVel,vVel is necessary  
          CALL SHAP_FILT_UV( uVel, vVel, myTime, myThid )  
       ENDIF  
       CALL TIMER_STOP ('SHAP_FILT           [THE_MAIN_LOOP]',myThid)  
 #endif  
   
 #ifdef ALLOW_ZONAL_FILT  
       IF (zonal_filt_lat.LT.90.) THEN  
         CALL TIMER_START('ZONAL_FILT_APPLY    [THE_MAIN_LOOP]',myThid)  
         CALL ZONAL_FILT_APPLY(  
      U           gUnm1, gVnm1, gTnm1, gSnm1,  
      I           myThid )  
         CALL TIMER_STOP ('ZONAL_FILT_APPLY    [THE_MAIN_LOOP]',myThid)  
       ENDIF  
 #endif  
   
98  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
99    
100    C-- This block has been moved to the_correction_step(). We have
101    C   left this code here to indicate where the filters used to be
102    C   in the algorithm before JMC moved them to after the pressure
103    C   solver.
104    C
105    C#ifdef ALLOW_SHAP_FILT
106    CC--   Step forward all tiles, filter and exchange.
107    C      CALL TIMER_START('SHAP_FILT           [THE_MAIN_LOOP]',myThid)
108    C      CALL SHAP_FILT_APPLY(
109    C     I                     gUnm1, gVnm1, gTnm1, gSnm1,
110    C     I                     myTime, myIter, myThid )
111    C      IF (implicDiv2Dflow.LT.1.) THEN
112    CC--   Explicit+Implicit part of the Barotropic Flow Divergence
113    CC      => Filtering of uVel,vVel is necessary
114    C         CALL SHAP_FILT_UV( uVel, vVel, myTime, myThid )
115    C      ENDIF
116    C      CALL TIMER_STOP ('SHAP_FILT           [THE_MAIN_LOOP]',myThid)
117    C#endif
118    C
119    C#ifdef ALLOW_ZONAL_FILT
120    C      IF (zonal_filt_lat.LT.90.) THEN
121    C        CALL TIMER_START('ZONAL_FILT_APPLY    [THE_MAIN_LOOP]',myThid)
122    C        CALL ZONAL_FILT_APPLY(
123    C     U           gUnm1, gVnm1, gTnm1, gSnm1,
124    C     I           myThid )
125    C        CALL TIMER_STOP ('ZONAL_FILT_APPLY    [THE_MAIN_LOOP]',myThid)
126    C      ENDIF
127    C#endif
128    
129  C--   Solve elliptic equation(s).  C--   Solve elliptic equation(s).
130  C     Two-dimensional only for conventional hydrostatic or  C     Two-dimensional only for conventional hydrostatic or
131  C     three-dimensional for non-hydrostatic and/or IGW scheme.  C     three-dimensional for non-hydrostatic and/or IGW scheme.
# Line 188  C     at time level 1 Line 182  C     at time level 1
182    
183  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
184    
 c--           >>> Loop body end <<<  
   
185        END        END

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

  ViewVC Help
Powered by ViewVC 1.1.22