source: CPL/oasis3/trunk/src/mod/oasis3/src/driver.f @ 1677

Last change on this file since 1677 was 1677, checked in by aclsce, 12 years ago

Imported oasis3 (tag ipslcm5a) from cvs server to svn server (igcmg project).

File size: 6.9 KB
Line 
1      SUBROUTINE driver
2C****
3C               *****************************
4C               * OASIS ROUTINE  -  LEVEL C *
5C               * -------------     ------- *
6C               *****************************
7C
8C**** *driver* - Main OASIS routine
9C
10C
11C     Purpose:
12C     -------
13C     Drive and control the simulation between GCMs and coupler.
14C     Contain the time loop. A coupled simulation with OASIS 2.0
15C     starts with the interpolation of the boundary conditions
16C     from their original grid to the target grid in contrast with
17C     the previous versions. Consequently, the GCMs pause initially
18C     until the coupling variables have been interpolated.
19C
20C     N.B: Note that the time loop goes from 0 to niter-1 in contrast
21C          with previous versions. The iteration 0 of oasis DOES NOT
22C          increment the simulation time.
23C
24C**   Interface:
25C     ---------
26C       *CALL*  *driver*
27C
28C     Input:
29C     -----
30C     None
31C
32C     Output:
33C     ------
34C     None
35C
36C     Workspace:
37C     ---------
38C               iindex : index array for field identificators
39C
40C     Externals:
41C     ---------
42C                        Initialization
43C                        **************
44C     inipar, inilun, iniiof, inidya, initim, inicmc, chkpar, inigrd,
45C
46C                        Temporal loop
47C                        ************* 
48C     getfld, preproc, interp, cookart, postpro, givfld, reset, updtim
49C
50C                        Synchronization
51C                        ***************
52C     modsgc, waitpc
53C
54C     Reference:
55C     ---------
56C     See OASIS manual (1995)
57C
58C     History:
59C     -------
60C       Version   Programmer     Date      Description
61C       -------   ----------     ----      ----------- 
62C       1.0       L. Terray      94/01/01  created
63C       2.0beta   L. Terray      95/07/24  modified: new structure
64C       2.0       L. Terray      96/02/01  modified: change in time loop
65C       2.1       O. Marti, L.T  96/09/25  added: extra time step
66C       2.2       S. Valcke, L.T 97/11/13  added: SIPC call to modsgc
67C                                                 mode no message passing
68C       2.3       L. Terray      99/09/15  added: GMEM branch
69C
70C %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
71C
72C* -----------------Include files and USE of modules---------------------------
73C
74      USE mod_kinds_oasis
75      USE mod_string
76      USE mod_analysis
77      USE mod_memory
78      USE mod_parameter
79      USE mod_experiment
80      USE mod_timestep
81      USE mod_unit
82      USE mod_hardware
83C
84C* ---------------------------- Local declarations ----------------------
85C
86      INTEGER (kind=ip_intwp_p), DIMENSION(:), ALLOCATABLE :: iindex
87      LOGICAL lltime, llseqn, llend
88      INTEGER (kind=ip_intwp_p) :: il_flag
89C
90C* ---------------------------- Poema verses ----------------------------
91C
92C %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
93C
94C*    1. Initialization
95C        --------------
96C
97C* - Initialize main run parameters
98C
99      CALL inipar_alloc
100C
101C* - "iindex" allocation
102C
103      IF (lg_oasis_field) THEN
104         ALLOCATE(iindex(ig_nfield))
105         iindex(:)=0
106      ENDIF
107C
108C* - Allocate arrays (first round)
109C
110      il_flag=1
111      CALL alloc(il_flag)
112C
113C* - Initialize other run parameters
114C
115      CALL inipar 
116C
117C* - Initialize logical unit numbers
118C
119      CALL inilun
120cvg C
121cvg C* - Open necessary files
122cvg C
123cvg       CALL iniiof
124
125C
126C* - Initialize time information
127C
128      CALL initim
129C
130C* - Initialize communication between processes
131C
132      CALL inicmc
133C
134C* - Allocate arrays (second round)
135C
136      il_flag=2
137      CALL alloc(il_flag)
138C
139cvg>>>
140C
141C* - Set up dynamic allocation for all grid-related fields
142C
143      CALL inidya
144C
145C* - Open necessary files
146C
147      CALL iniiof
148cvg<<<
149
150C
151C* - Check run parameters compatibility between GCM's and coupler
152C
153      CALL chkpar
154C
155C* - Initialize GCM's grids
156C
157      CALL inigrd
158C
159C* - We will go through the next time loop only if one field (at least) goes
160C    through Oasis
161
162      IF (lg_oasis_field) THEN
163C
164C*    2. Time loop
165C        ---------
166C
167C* Loop on number of iterations
168C* First iteration takes place at ndate (INIDATE in namcouple) and
169C* last iteration at one timestep before the end of the simulation
170C* (INIDATE + RUNTIME in namcouple), 
171C
172         DO 210 jt = 0, nitfn
173C
174C* Assign local variable for iteration number
175C
176            iter = jt
177C
178C* Get time counter. 
179C
180            icount = iter * nstep
181C
182C* Update calendar date
183C
184            CALL updtim (iter)
185C
186C* Loop on number of sequential models
187C
188            DO 220 jm = 1, nmseq
189C
190C* Loop on number of fields to find active fields for current iteration
191C
192               ifield = 0
193               DO 230 jf = 1, ig_total_nfield
194C
195C* Treat the field only IF it has to go through Oasis
196C
197                  IF (lg_state(jf)) THEN
198C     
199C* Get conditional logical flags for doing analysis set
200C
201C
202C* Treat the field only if time smaller than end of simulation
203                     llend  = icount .LT. ntime
204C
205C* Treat the field only if iteration corresponds to one 
206C* of its coupling timesteps
207                     ifnow = nfexch(ig_number_field(jf))
208                     lltime = mod(icount,ifnow) .EQ. 0
209C
210C* If sequential order, treat the field only if it is consumed
211C* in present loop
212                     llseqn = nseqn(ig_number_field(jf)) .EQ. jm
213C
214C* Conditional test to fill up iindex array
215C
216                     IF (llseqn .AND. lltime .AND. llend) 
217     $                    THEN
218                        ifield = ifield + 1
219C
220C* Fill up iindex array with active fields at iteration jt
221C
222                        iindex(ifield) = ig_number_field(jf)
223                     ENDIF
224                  ENDIF
225 230           CONTINUE
226C
227C* There are ifield fields to be exchanged for iteration jt
228C
229               IF (ifield .GT. 0) THEN
230C
231C* Get fields
232C
233                  CALL getfld (iindex, ifield, iter)
234C
235C* Do preprocessing
236C
237                  CALL preproc (iindex, ifield)
238C
239C* Do the interpolation
240C
241                  CALL interp (iindex, ifield)
242C
243C* Do the nitty gritty stuff
244
245C
246                  CALL cookart (iindex, ifield)
247C
248C* Do postprocessing
249C
250                  CALL postpro (iindex, ifield)
251C
252C* If last iteration in PIPE or SIPC case, switch sigcld handler
253                  IF (iter .EQ. nitfn) THEN
254                     IF (cchan .EQ. 'PIPE' .OR. cchan .EQ. 'SIPC')
255     $                    CALL modsgc
256                  ENDIF
257C
258C* Give back fields
259C     
260                  CALL givfld (iindex, ifield, iter)
261               ENDIF
262C
263C* End of loop over the sequential models
264C
265 220        CONTINUE
266C
267C* Reset macro arrays
268C
269        CALL reset
270C
271C* End of iterative loop
272C
273 210  CONTINUE
274      ENDIF
275C
276C*    3. Wait until end of child processes
277C        ---------------------------------
278C
279      CALL waitpc
280C
281C
282C*    4. End of routine
283C        --------------
284C
285C* "iindex" deallocation
286C
287      IF (lg_oasis_field) DEALLOCATE(iindex)
288C
289C* Deallocation of arrays allocated in "inialloc" routine     
290C
291      CALL dealloc
292C
293      RETURN
294      END
Note: See TracBrowser for help on using the repository browser.