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

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

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

revision 1.6 by cnh, Fri Apr 24 03:45:12 1998 UTC revision 1.28 by adcroft, Mon May 24 15:42:23 1999 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2    
3  #include "CPP_EEOPTIONS.h"  #include "CPP_OPTIONS.h"
4    
5        SUBROUTINE THE_MODEL_MAIN(myThid)        SUBROUTINE THE_MODEL_MAIN(myThid)
6  C     /==========================================================\  C     /==========================================================\
# Line 22  C     | ===== Line 22  C     | =====
22  C     | C*P* comments indicating place holders for which code is |  C     | C*P* comments indicating place holders for which code is |
23  C     |      presently being developed.                          |  C     |      presently being developed.                          |
24  C     \==========================================================/  C     \==========================================================/
25          IMPLICIT NONE
26    C
27    C     Call Tree
28    C     =========
29    C    
30    C      main ( eesupp )
31    C       |
32    C       .
33    C       .
34    C       . Generic environment initialisation ( see eesupp/src and
35    C       .                                      eesupp/inc )      
36    C       . multiple threads and/or processes are created in here
37    C       .
38    C       .
39    C       .
40    C       |
41    C       |-THE_MODEL_MAIN - Begin specific model. One instance
42    C       |  |               of this codes exists for each thread
43    C       |  |               and/or instance. Each instance manages
44    C       |  |               a specifc set of tiles.              
45    C       |  |
46    C       |  |--INITIALISE
47    C       |  |   o Set initial conditions and model configuration
48    C       |  |     Topography, hydrography, timestep, grid, etc..
49    C       |  |
50    C  ==>  |  | ** Time stepping loop starts here **
51    C  |    |  |
52    C /|\   |  |
53    C  |    |  |--LOAD_EXTERNAL_DATA
54    C /|\   |  |   o Load and/or set time dependent forcing fields
55    C  |    |  |
56    C /|\   |  |--DYNAMICS
57    C  |    |  |   o Evaluate "forward" terms
58    C /|\   |  |
59    C  |    |  |--DO_THE_MODEL_IO
60    C /|\   |  |   o Write model state
61    C  |    |  |
62    C /|\   |  |--SOLVE_FOR_PRESSURE
63    C  |    |  |   o Find pressure field to keep flow non-divergent
64    C /|\   |  |
65    C  |    |  |--DO_GTERM_BLOCKING_EXCHANGES
66    C /|\   |  |   o Update overlap regions
67    C  |    |  |
68    C /|\   |  |--WRITE_CHECKPOINT
69    C  |    |  |   o Write restart file(s)
70    C /|\   |  |
71    C  |    |  |
72    C  |<== |  | ** Time stepping loop finishes here **
73    C       |  |
74    C       |  |--WRITE_STATE
75    C       |  |--WRITE_CHECKPOINT
76    C       |
77    C       .
78    C       .
79    C       . Generic environment termination ( see eesupp/src and
80    C       .                                      eesupp/inc )      
81    C       .
82    C       .
83    
84  C     == Global variables ===  C     == Global variables ===
85  #include "SIZE.h"  #include "SIZE.h"
86  #include "EEPARAMS.h"  #include "EEPARAMS.h"
87  #include "PARAMS.h"  #include "PARAMS.h"
 #include "CG2D.h"  
88  #include "DYNVARS.h"  #include "DYNVARS.h"
89    #include "CG2D.h"
90    #ifdef ALLOW_NONHYDROSTATIC
91    #include "CG3D.h"
92    #endif
93    
94  C     == Routine arguments ==  C     == Routine arguments ==
95  C     myThid - Thread number for this instance of the routine.  C     myThid - Thread number for this instance of the routine.
96        INTEGER myThid          INTEGER myThid  
97    
98  C     == Local variables ==  C     == Local variables ==
99  C     Note: Under the multi-threaded model myCurrentIter and myCurrentTime  C     Note: Under the multi-threaded model myCurrentIter and
100  C           are local variables passed around as routine arguments. Although  C           myCurrentTime are local variables passed around as routine
101  C           this is fiddly it saves the need to impose additional synchronisation  C           arguments. Although this is fiddly it saves the need to
102  C           points when they are updated.  C           impose additional synchronisation points when they are
103    C           updated.
104  C     myCurrentIter - Iteration counter for this thread  C     myCurrentIter - Iteration counter for this thread
105  C     myCurrentTime - Time counter for this thread  C     myCurrentTime - Time counter for this thread
106  C     I             - Loop counter  C     I             - Loop counter
107        INTEGER I, myCurrentIter        INTEGER I, myCurrentIter
108        REAL    myCurrentTime        REAL    myCurrentTime
109          CHARACTER*(30) suff
110    
111    C--   This timer encompasses the whole code
112          CALL TIMER_START('ALL',myThid)
113    
114          CALL TIMER_START('SPIN-UP',myThid)
115    
116  C--   Set model initial conditions  C--   Set model initial conditions
117          CALL TIMER_START('INITIALISE          [SPIN-UP]',myThid)
118        CALL INITIALISE( myThid )        CALL INITIALISE( myThid )
119        myCurrentTime = startTime        myCurrentTime = startTime
120        myCurrentIter = nIter0        myCurrentIter = nIter0
121          CALL TIMER_STOP ('INITIALISE          [SPIN-UP]',myThid)
122    
123    C--   Dump for start state
124          CALL TIMER_START('I/O (WRITE)         [SPIN-UP]',myThid)
125          CALL WRITE_STATE( .TRUE., myCurrentTime, myCurrentIter, myThid )
126          CALL TIMER_STOP ('I/O (WRITE)         [SPIN-UP]',myThid)
127    
128          CALL TIMER_STOP ('SPIN-UP',myThid)
129    
130  C--   Begin time stepping loop  C--   Begin time stepping loop
131          CALL TIMER_START('MAIN LOOP',myThid)
132        DO I=1, nTimeSteps        DO I=1, nTimeSteps
133    
134  C--    Do IO if needed.  C--    Load forcing/external data fields
135         CALL DO_THE_MODEL_IO( myCurrentIter, myThid )         CALL TIMER_START('I/O (READ)         [MAIN LOOP]',myThid)
136           CALL LOAD_EXTERNAL_FIELDS( myCurrentTime, myCurrentIter, myThid )
137  C--    Load offline tracer fields         CALL TIMER_STOP ('I/O (READ)         [MAIN LOOP]',myThid)
138         IF ( MOD(myCurrentIter,numStepsPerPickup) .EQ. 1 ) THEN  
139  C       I/O  #ifdef INCLUDE_SHAPIRO_FILTER_CODE
140  C       o Writes to arrays are performed by their own thread (to ensure  C--    Step forward all tiles, filter and exchange.
141  C         physical memory allocation will pair with thread).         CALL TIMER_START('SHAP_FILT          [MAIN LOOP]',myThid)
142  C       o Thread 1 reads into a buffer.         CALL SHAP_FILT( myCurrentTime, myCurrentIter, myThid )
143  C       CALL LOAD_OFFLINE_FIELDS( myCurrentTime, myCurrentIter, myThid )         CALL TIMER_STOP ('SHAP_FILT          [MAIN LOOP]',myThid)
144    #endif
145    
146    #ifdef ALLOW_OBCS
147    C--    Set Open Boundaries Values
148           IF (openBoundaries) THEN
149            CALL TIMER_START('OBCS               [MAIN LOOP]',myThid)
150            CALL SET_OBCS( myCurrentTime, myThid )
151            CALL TIMER_STOP ('OBCS               [MAIN LOOP]',myThid)
152         ENDIF         ENDIF
153    #endif
154    
155  C--    Step forward fields and calculate time tendency terms  C--    Step forward fields and calculate time tendency terms
156         CALL DYNAMICS( myThid )         CALL TIMER_START('DYNAMICS           [MAIN LOOP]',myThid)
157           CALL DYNAMICS( myCurrentTime, myCurrentIter, myThid )
158           CALL TIMER_STOP ('DYNAMICS           [MAIN LOOP]',myThid)
159    
160    #ifdef ALLOW_NONHYDROSTATIC
161    C--    Step forward W field in N-H algorithm
162           IF ( nonHydrostatic ) THEN
163            CALL TIMER_START('CALC_GW            [MAIN LOOP]',myThid)
164            CALL CALC_GW( myThid)
165            CALL TIMER_STOP ('CALC_GW            [MAIN LOOP]',myThid)
166           ENDIF
167    #endif
168    
169    C--    Do time averages
170    #ifdef INCLUDE_DIAGNOSTICS_INTERFACE_CODE
171           CALL TIMER_START('I/O (WRITE)        [MAIN LOOP]',myThid)
172           IF (taveFreq.GT.0.) THEN
173            CALL WRITE_TIME_AVERAGES( myCurrentTime, myCurrentIter, myThid )
174           ENDIF
175           CALL TIMER_STOP ('I/O (WRITE)        [MAIN LOOP]',myThid)
176    #endif
177    
178    C--    Do IO if needed.
179    C      Note:
180    C      =====
181    C      At this point model arrays hold U,V,T,S  at "time-level" N
182    C      and cg2d_x at "time-level" N-1/2 where N = I+timeLevBase-1.
183    C      By convention this is taken to be the model "state".
184           CALL TIMER_START('I/O (WRITE)        [MAIN LOOP]',myThid)
185           CALL DO_THE_MODEL_IO( myCurrentTime, myCurrentIter, myThid )
186           CALL TIMER_STOP ('I/O (WRITE)        [MAIN LOOP]',myThid)
187    
188  C--    Solve elliptic equation(s).  C--    Solve elliptic equation(s).
189  C      Two-dimensional only for conventional hydrostatic or three-dimensional  C      Two-dimensional only for conventional hydrostatic or
190  C      for non-hydrostatic and/or IGW scheme.  C      three-dimensional for non-hydrostatic and/or IGW scheme.
191           CALL TIMER_START('SOLVE_FOR_PRESSURE [MAIN LOOP]',myThid)
192         CALL SOLVE_FOR_PRESSURE( myThid )         CALL SOLVE_FOR_PRESSURE( myThid )
193           CALL TIMER_STOP ('SOLVE_FOR_PRESSURE [MAIN LOOP]',myThid)
194    
195  C--    Do "blocking" sends and receives for tendency "overlap" terms  C--    Do "blocking" sends and receives for tendency "overlap" terms
196           CALL TIMER_START('BLOCKING_EXCHANGES [MAIN LOOP]',myThid)
197         CALL DO_GTERM_BLOCKING_EXCHANGES( myThid )         CALL DO_GTERM_BLOCKING_EXCHANGES( myThid )
198           CALL TIMER_STOP ('BLOCKING_EXCHANGES [MAIN LOOP]',myThid)
199    
200         myCurrentIter = myCurrentIter + 1         myCurrentIter = myCurrentIter + 1
201         myCurrentTime = myCurrentTime  + deltaTtracer         myCurrentTime = myCurrentTime + deltaTClock
202    
203  C--    Save state for restarts  C--    Save state for restarts
204  C*P*   CALL CHECKPOINT( myThid )  C      Note:
205    C      =====
206    C      Because of the ordering of the timestepping code and
207    C      tendency term code at end of loop model arrays hold
208    C      U,V,T,S  at "time-level" N but gu, gv, gs, gt, guNM1,...
209    C      at "time-level" N+1/2 (guNM1 at "time-level" N+1/2 is
210    C      gu at "time-level" N-1/2) and cg2d_x at "time-level" N+1/2.
211    C       where N = I+timeLevBase-1
212    C      Thus a checkpoint contains U.0000000000, GU.0000000001 and
213    C      cg2d_x.0000000001 in the indexing scheme used for the model
214    C      "state" files. This example is referred to as a checkpoint
215    C      at time level 1
216           CALL TIMER_START('I/O (WRITE)        [MAIN LOOP]',myThid)
217           CALL
218         & WRITE_CHECKPOINT( .FALSE., myCurrentTime, myCurrentIter, myThid )
219           CALL TIMER_STOP ('I/O (WRITE)        [MAIN LOOP]',myThid)
220    
221        ENDDO        ENDDO
222          CALL TIMER_STOP ('MAIN LOOP',myThid)
223          CALL TIMER_START('SPIN-DOWN',myThid)
224    
225    C--   Final checkpoint (incase the in-loop checkpoint was missed)
226          CALL TIMER_START('I/O (WRITE)         [SPIN-DOWN]',myThid)
227          CALL
228         & WRITE_CHECKPOINT( .TRUE., myCurrentTime, myCurrentIter, myThid )
229          CALL TIMER_STOP ('I/O (WRITE)         [SPIN-DOWN]',myThid)
230    
231    #ifdef ALLOW_OBCS
232    C--   Set Open Boundaries Values
233          IF (openBoundaries) THEN
234           CALL TIMER_START('OBCS               [SPIN_DOWN]',myThid)
235           CALL SET_OBCS( myCurrentTime, myThid )
236           CALL TIMER_STOP ('OBCS               [SPIN_DOWN]',myThid)
237          ENDIF
238    #endif
239    
240    C--   Step-forward U/V/Theta/Salt for purposes of final I/O dump
241          CALL TIMER_START('DYNAMICS            [SPIN-DOWN]',myThid)
242          CALL DYNAMICS( myCurrentTime, myCurrentIter, myThid )
243          CALL TIMER_STOP ('DYNAMICS            [SPIN-DOWN]',myThid)
244    
245    #ifdef ALLOW_NONHYDROSTATIC
246          IF ( nonHydrostatic ) THEN
247    C--    Step forward W field in N-H algorithm
248           CALL TIMER_START('CALC_GW            [SPIN-DOWN]',myThid)
249           CALL CALC_GW( myThid)
250           CALL TIMER_STOP ('CALC_GW            [SPIN-DOWN]',myThid)
251          ENDIF
252    #endif
253    
254    C--   Do time averages
255    #ifdef ALLOW_DIAGNOSTICS
256          IF (taveFreq.GT.0.) THEN
257           CALL TIMER_START('I/O (WRITE)        [SPIN-DOWN]',myThid)
258           CALL WRITE_TIME_AVERAGES( myCurrentTime, myCurrentIter, myThid )
259           CALL TIMER_STOP ('I/O (WRITE)        [SPIN-DOWN]',myThid)
260          ENDIF
261    #endif
262    
263    C--   Dump for end state
264          CALL TIMER_START('I/O (WRITE)         [SPIN-DOWN]',myThid)
265          CALL WRITE_STATE( .FALSE., myCurrentTime, myCurrentIter, myThid )
266          CALL TIMER_STOP ('I/O (WRITE)         [SPIN-DOWN]',myThid)
267    
268          CALL TIMER_STOP ('SPIN-DOWN',myThid)
269          CALL TIMER_STOP ('ALL',myThid)
270    
271    C--   Write timer statistics
272          IF ( myThid .EQ. 1 ) THEN
273           CALL TIMER_PRINTALL( myThid )
274           CALL COMM_STATS
275          ENDIF
276    
277        RETURN        RETURN
278        END        END

Legend:
Removed from v.1.6  
changed lines
  Added in v.1.28

  ViewVC Help
Powered by ViewVC 1.1.22