New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
cpl.F90 in trunk/NEMO/OPA_SRC – NEMO

source: trunk/NEMO/OPA_SRC/cpl.F90 @ 83

Last change on this file since 83 was 83, checked in by opalod, 20 years ago

CT : UPDATE056 : Change the subroutine name cpl_step to cpl_stp

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 29.1 KB
Line 
1MODULE cpl
2   !!======================================================================
3   !!                       ***  MODULE cpl  ***
4   !! Coupled O/A : coupled ocean-atmosphere case using OASIS
5   !!=====================================================================
6#if defined key_coupled
7   !!----------------------------------------------------------------------
8   !!   'key_coupled'                              coupled Ocean/Atmosphere
9   !!----------------------------------------------------------------------
10   !!   cpl_init     : initialization of coupled mode communication
11   !!   cpl_read     : read the coupled namelist
12   !!   cpl_stp      : exchange fields in coupled mode
13   !!----------------------------------------------------------------------
14   !! * Modules used
15   USE oce             ! ocean dynamics and tracers
16   USE dom_oce         ! ocean space and time domain
17   USE in_out_manager  ! I/O manager
18   USE cpl_oce         ! coupled exchange variables (???)
19   USE flx_oce         ! in case of ice
20   USE ocfzpt          ! ocean freezing point
21
22   IMPLICIT NONE
23   PRIVATE
24
25   !! Routine accessibility
26   PUBLIC cpl_init     ! routine called in opa module
27   PUBLIC cpl_stp      ! routine called in step module
28   !!----------------------------------------------------------------------
29   !!   OPA 9.0 , LODYC-IPSL  (2003)
30   !!----------------------------------------------------------------------
31
32CONTAINS
33
34   SUBROUTINE cpl_init( kastp, kexch, kstep )
35      !!---------------------------------------------------------------------
36      !!                  ***  ROUTINE cpl_init  ***
37      !!
38      !! ** Purpose :   Initialize coupled mode communication for ocean
39      !!    exchange process identifiers and timestep information
40      !!    between AGCM, OGCM and COUPLER. (OASIS software)
41      !!
42      !! ** Method  :  3 types :
43      !!      a) Use named pipes(FIFO) to exchange process identifiers
44      !!          between the 3 programs
45      !!      b) USE a messag passing method with PVM language (CLIM)
46      !!      c) USE SVIPC method
47      !!
48      !! ** Input   :   npiat     : agcm process identifier
49      !!                npicp     : coupler process identifier
50      !!                npioc     : ogcm process identifier
51      !!
52      !! Reference  :   see Epicoa 0803 (1992)
53      !!
54      !! History :
55      !!        !  92-09  (L. Terray)  Original code
56      !!        !  96-07  (L. Terray)  OASIS version 2
57      !!        !  96-11  (E. Guilyardi)  run-off + Taux,Tauy x2
58      !!        !  98-04  (M.A Foujols, S. Valcke, M. Imbard)  OASIS2.2
59      !!   8.5  !  02-09  (G. Madec)  F90: Free form and module
60      !!----------------------------------------------------------------------
61      !! * Arguments
62      INTEGER, INTENT(in ) ::   &
63         kastp,      &  ! total number of timesteps in oceanic model
64         kexch,      &  ! frequency of exchange for the fluxes (in time steps)
65         kstep          ! timestep value (in seconds)
66
67      !! * Local declarations
68      INTEGER,DIMENSION(3)  :: iparal
69      INTEGER               :: ifcpl, idt, info, imxtag, istep
70
71      CHARACTER (len=9) ::   clpoolnam 
72      INTEGER           :: ipoolhandle, ipoolsize, index, jf
73      CHARACTER (len=3) ::   cljobnam      ! experiment name
74      INTEGER           :: ierror
75      INTEGER,DIMENSION(4) ::  imess, imesso
76      INTEGER           :: getpid, mknod     ! system functions
77      !!----------------------------------------------------------------------
78     
79      IF(lwp) WRITE(numout,*)
80      IF(lwp) WRITE(numout,*) 'cpl_init : initialization in coupled ocean/atmosphere case'
81      IF(lwp) WRITE(numout,*) '~~~~~~~~'
82      IF(lwp) WRITE(numout,*)
83     
84#if defined key_flx_bulk_monthly || defined key_flx_bulk_daily || defined key_flx_forced_daily
85      IF(lwp)WRITE(numout,cform_err)
86      IF(lwp)WRITE(numout,*) ' key_coupled and key_flx_bulk_... are incompatible'
87      nstop = nstop + 1
88#endif
89 
90      IF(lwp)WRITE(numout,*)'     coupled simulation'
91      IF(lwp)WRITE(numout,*)'        unit ',numlhf,' receive atm fluxes'
92      IF(lwp)WRITE(numout,*)'        unit ',numlws,' receive windstress'
93      IF(lwp)WRITE(numout,*)'        unit ',numlts,' transfer sst'
94      IF(lwp)WRITE(numout,*)'        unit ',numlic,' transfer ice cover'
95
96
97      CALL cpl_read           ! read the coupled mode information in namelist
98
99      CALL flush(numout)
100
101      ! I- PIPE
102      ! --------
103      ! W A R N I N G : PIPE technique is temporary diseable (nov. 2000)
104
105      IF( cchan == 'PIPE' ) THEN
106
107         IF(lwp) WRITE(numout,*)
108         IF(lwp) WRITE(numout,*) 'Making pipes for fields to receive from CPL'
109         IF(lwp) WRITE(numout,*)
110         CALL flush(numout)
111         ierror = 0
112
113         ! loop to define pipes (CPL=atmos to ocean)
114
115         DO jf = 1, nflxc2o 
116            ! CALL PIPE_Model_Define( numout, cpl_readflx(jf), jpread, info )
117            IF( info /= 0 ) ierror = ierror + 1
118         END DO
119         DO jf = 1, ntauc2o
120            ! CALL PIPE_Model_Define( numout, cpl_readtau(jf), jpread, info )
121            IF( info /= 0 ) ierror = ierror + 1
122         END DO
123         
124         IF(lwp) WRITE(numout,*) ' '
125         IF(lwp) WRITE(numout,*) 'Making pipes for fields to send to CPL'
126         IF(lwp) WRITE(numout,*) ' '
127         
128         ! loop to define pipes (ocean to atmos=CPL)
129
130         DO jf = 1, nfldo2c
131            ! CALL PIPE_Model_Define( numout, cpl_writ(jf), jpwrit, info )
132            IF( info /= 0 ) ierror = ierror + 1
133         END DO
134
135         IF( ierror /= 0 ) THEN
136            IF(lwp) WRITE(numout,*)
137            IF(lwp) WRITE(numout,*) 'cpl_init: end of job due to error in pipes definitions'
138            CALL abort
139         END IF
140         
141         IF(lwp) WRITE(numout,*)
142         IF(lwp) WRITE(numout,*) 'All pipes have been made'
143         
144         IF(lwp) WRITE(numout,*)
145         IF(lwp) WRITE(numout,*) 'Communication test between OCE and CPL'
146         CALL flush(numout)
147         
148         ! CALL PIPE_Model_Stepi(numout, imess, nmodcpl, imesso, ierror)
149         
150         IF( ierror /= 0 ) THEN
151            IF(lwp) WRITE(numout,*)
152            IF(lwp) WRITE(numout,*) 'cpl_init: end of job due to error in exchange first informations with Oasis'
153            CALL abort
154         END IF
155         
156         IF(lwp) WRITE(numout,*)
157         IF(lwp) WRITE(numout,*) 'Communication test between OCE and CPL is OK'
158         IF(lwp) WRITE(numout,*) ' total simulation time in oasis = ',imesso(1)
159         IF(lwp) WRITE(numout,*) ' total number of iterations is  = ',imesso(2)
160         IF(lwp) WRITE(numout,*) ' value of oasis timestep  is    = ',imesso(3)
161         IF(lwp) WRITE(numout,*) ' process id for oasis  is       = ',imesso(4)
162         CALL flush(numout)
163         
164         ! II SVIPC
165         ! ---------
166         ! W A R N I N G : SVIPC technique is temporary diseable (nov. 2000)
167         
168         
169      ELSE IF( cchan == 'SIPC' ) THEN
170
171         ! debug for more information
172
173         ! CALL SVIPC_debug(1)
174
175         ! Define the experiment name :
176
177          cljobnam = 'IPC'      ! as $JOBNAM in namcouple
178
179          ! Attach to shared memory pool used to exchange initial infos
180
181          info = 0
182          ! CALL SIPC_Init_Model (cljobnam, cplmodnam, 1, info)
183          IF( info /= 0 ) THEN
184             IF(lwp) WRITE(numout,*)
185             IF(lwp) WRITE(numout,*)'WARNING: Problem with attachement to',info 
186             IF(lwp) WRITE(numout,*)'         initial memory pool(s) in ocean'
187             IF(lwp) WRITE(numout,*)
188             CALL abort('STOP in ocean')
189          ENDIF
190
191          ! Attach to pools used to exchange fields from ocean to coupler
192
193          DO jf = 1, nfldo2c
194             ! Pool name:
195             clpoolnam = 'P'//cpl_writ(jf)
196             ! CALL SIPC_Attach(clpoolnam, ipoolhandle)
197             ! Resulting pool handle:
198             mpoolwrit(jf) = ipoolhandle 
199          END DO
200
201          ! Attach to pools used to exchange fields from coupler to ocean
202         
203          DO jf = 1, nflxc2o
204             ! Pool name:
205             clpoolnam = 'P'//cpl_readflx(jf)
206             ! CALL SIPC_Attach(clpoolnam, ipoolhandle)
207             ! Resulting pool handle:
208             mpoolread(jf) = ipoolhandle 
209          END DO 
210
211          DO jf = 1, ntauc2o
212             ! Pool name:
213             clpoolnam = 'P'//cpl_readtau(jf)
214             ! CALL SIPC_Attach(clpoolnam, ipoolhandle)
215             ! Resulting pool handle:
216             mpoolread(jf+nflxc2o) = ipoolhandle 
217          END DO 
218
219          ! Exchange of initial infos
220
221          ! Write data array isend to pool READ by Oasis
222
223          info = 0
224          ipoolsize = 4*jpbyteint
225          ! CALL SVIPC_write(mpoolinitr, imess, ipoolsize, info)
226
227          ! Find error if any
228
229          IF( info < 0 ) THEN
230             IF(lwp) WRITE(numout,*)
231             IF(lwp) WRITE(numout,*) 'Problem in ocean in writing initial' 
232             IF(lwp) WRITE(numout,*) 'infos to the shared memory segment(s)'
233             IF(lwp) WRITE(numout,*)
234          ELSE
235             IF(lwp) WRITE(numout,*)
236             IF(lwp) WRITE(numout,*) 'Initial infos written in ocean'           
237             IF(lwp) WRITE(numout,*) 'to the shared memory segment(s)'
238             IF(lwp) WRITE(numout,*)
239          ENDIF
240
241          ! Read data array irecv from pool written by Oasis
242
243          info = 0
244          ipoolsize = 4 * jpbyteint
245          CALL svipc_read(mpoolinitw, imesso, ipoolsize, info)
246
247          ! Find error if any
248
249          IF( info < 0 ) THEN
250             IF(lwp) WRITE(numout,*) '   '
251             IF(lwp) WRITE(numout,*) 'Problem in ocean in reading initial' 
252             IF(lwp) WRITE(numout,*) 'infos from the shared memory segment(s)'
253             IF(lwp) WRITE(numout,*) '   '
254          ELSE
255             IF(lwp) WRITE(numout,*) '   '
256             IF(lwp) WRITE(numout,*) 'Initial infos read by ocean'               
257             IF(lwp) WRITE(numout,*) 'from the shared memory segment(s)'
258             IF(lwp) WRITE(numout,*) '   '
259             IF(lwp) WRITE(numout,*) ' ntime, niter, nstep, Oasis pid:'
260             IF(lwp) WRITE(numout,*) imesso(1), imesso(2), imesso(3), imesso(4) 
261          ENDIF
262
263          ! Detach from shared memory segment(s)
264
265          info = 0
266          ! CALL SVIPC_close(mpoolinitw, 0, info)
267         
268          ! Find error if any
269
270          IF( info < 0 ) THEN
271             IF(lwp) WRITE(numout,*) 'Problem in detaching from shared memory segment(s)'
272             IF(lwp) WRITE(numout,*) 'used by ocean to read initial infos' 
273          ENDIF
274
275          ! III CLIM
276          ! --------
277
278      ELSE IF( cchan == 'CLIM' ) THEN
279
280         ! Define the number of processors involved in the coupling for
281         ! Oasis (=1) and each model (as last two INTEGER on $CHATYPE line
282         ! in the namcouple); they will be stored in a COMMON in mpiclim.h
283         ! (used for CLIM/MPI2 only)
284         mpi_nproc(0)=1
285         mpi_nproc(1)=1
286         mpi_nproc(2)=1 
287
288         ! Define the number of processors used by each model as in
289         ! $CHATYPE line of namcouple (used for CLIM/MPI2 only)
290         mpi_totproc(1)=1
291         mpi_totproc(2)=1
292         
293         ! Define names of each model as in $NBMODEL line of namcouple
294         ! (used for CLIM/MPI2 only)
295         cmpi_modnam(1)='lmdz.x'
296         cmpi_modnam(2)=cplmodnam
297         
298         ! 1.1-Define the experiment name :
299         
300         cljobnam = 'CLI'      ! as $JOBNAM in namcouple
301         
302         OPEN ( UNIT = 7, FILE = 'trace', STATUS = 'unknown', FORM = 'formatted')
303         CALL clim_init ( cljobnam, cplmodnam, 3, 7,   &
304                          kastp, kexch, kstep,   &
305                          5, 3600, 3600, info )
306
307         IF( info /= clim_ok ) THEN
308            IF(lwp) WRITE( numout, *) 'cpl_init : pb init clim, error code is = ', info
309            CALL abort( 'STOP in cpl_init' )
310         ELSE
311            IF(lwp) WRITE(numout,*) 'cpl_init : init clim ok '
312         ENDIF
313         
314         iparal ( clim_strategy ) = clim_serial
315         iparal ( clim_length   ) = jpiglo*jpjglo
316         iparal ( clim_offset   ) = 0
317         
318         ! loop to define messages (CPL=atmos to ocean)
319         DO jf = 1, nflxc2o
320            CALL CLIM_Define ( cpl_readflx(jf), clim_in, clim_double, iparal, info ) 
321         END DO
322         DO jf = 1, ntauc2o
323            CALL CLIM_Define ( cpl_readtau(jf), clim_in, clim_double, iparal, info ) 
324         END DO
325         
326         ! loop to define messages (ocean to CPL=atmos)
327         DO jf = 1, nfldo2c
328            CALL CLIM_Define ( cpl_writ(jf), clim_out, clim_double, iparal, info )   
329         END DO
330         
331         IF(lwp) WRITE(numout,*) 'cpl_init : clim_define ok '
332         
333         CALL CLIM_Start( imxtag, info )
334         
335         IF( info /= clim_ok ) THEN
336            IF(lwp) WRITE(numout,*) 'cpl_init : pb start clim, error code is = ', info
337            CALL abort( 'stop in cpl_init' )
338         ELSE
339            IF(lwp) WRITE(numout,*) 'cpl_init : start clim ok '
340         ENDIF
341         
342         CALL CLIM_Stepi ( cploasis, istep, ifcpl, idt, info )
343
344         IF( info /= clim_ok ) THEN
345            IF(lwp) WRITE(numout,*) ' warning : problem in getting step info from oasis '
346            IF(lwp) WRITE(numout,*) ' =======   error code number = ', info
347         ELSE
348            IF(lwp) WRITE(numout,*) ' got step information from oasis '
349         ENDIF
350         IF(lwp) WRITE(numout,*) ' number of tstep in oasis ', istep
351         IF(lwp) WRITE(numout,*) ' exchange frequency in oasis ', ifcpl
352         IF(lwp) WRITE(numout,*) ' length of tstep in oasis ', idt
353      ENDIF
354
355   END SUBROUTINE cpl_init
356
357
358   SUBROUTINE cpl_read
359      !!---------------------------------------------------------------------
360      !!                  ***  ROUTINE cpl_read  ***
361      !!                   
362      !! ** Purpose :   Read and print options for the coupled run (namelist)
363      !!
364      !! ** Method  :   ???
365      !!
366      !! History :
367      !!   8.5  !  02-12  (G. Madec)  F90: Free form and module
368      !!----------------------------------------------------------------------
369      !! * Local declarations
370      INTEGER :: jf
371
372      CHARACTER (len=21) ::   clold, clfor, clseq
373      CHARACTER (len=32) ::   clname
374
375      NAMELIST/namcpl/ nexco, cchan, nmodcpl, cplmodnam, cploasis   &
376          , nfldo2c, nflxc2o, ntauc2o, cpl_f_readflx, cpl_f_readtau   &
377          , cpl_f_writ, cpl_readflx, cpl_readtau, cpl_writ
378      !!----------------------------------------------------------------------
379     
380      IF(lwp) WRITE(numout,*)
381      IF(lwp) WRITE(numout,*) ' cpl_read : read the coupled parameters in namelist'
382      IF(lwp) WRITE(numout,*) ' ~~~~~~~~'
383      IF(lwp) WRITE(numout,*)
384
385      ! Default values
386     
387      nexco = 24
388      cchan='PIPE'              ! echange TYPE
389      nmodcpl = 2
390      cplmodnam = 'opa.xx'      ! model name : as $NBMODEL in namcouple
391      cploasis = 'Oasis'        ! coupler name : as in coupler
392
393      ! -Define symbolic name for fields exchanged from ocean to coupler,
394      ! must be the same as (1) of the field  definition in namcouple:
395      nfldo2c=2
396      cpl_writ(1)='SOSSTSST'
397      cpl_writ(2)='SOICECOV'
398
399      ! -Define files name for fields exchanged from ocean to coupler,
400      ! must be the same as (6) of the field  definition in namcouple:
401      nflxc2o=6
402      cpl_readflx(1)='SONSFLDO' ! non solar heat flux (positif vers l'ocean)
403      cpl_readflx(2)='SOSHFLDO' ! solar flux
404      cpl_readflx(3)='SOTOPRSU' ! precip
405      cpl_readflx(4)='SOTFSHSU' ! evaporation
406      cpl_readflx(5)='SORUNCOA' ! coastal run-off
407      cpl_readflx(6)='SORIVFLU' ! river run-off
408      ntauc2o=2
409      cpl_readtau(1)='SOZOTAUX' ! first zonal wind stress
410      cpl_readtau(2)='SOZOTAU2' ! second zonal wind stress
411      cpl_readtau(3)='SOMETAUY' ! first meridien wind stress
412      cpl_readtau(4)='SOMETAU2' ! second meridien wind stress
413
414      ! -Define files name for fields exchanged from ocean to coupler,
415      ! must be the same as (6) of the field  definition in namcouple:
416      cpl_f_writ(1)='ocesst'
417      cpl_f_writ(2)='oceice'
418
419      ! -Define files name for fields exchanged from coupler to ocean
420      ! must be the same as (7) of the field  definition in namcouple:
421      cpl_f_readflx(1)='oceflx'
422      cpl_f_readflx(2)='oceflx'
423      cpl_f_readflx(3)='oceflx'
424      cpl_f_readflx(4)='oceflx'
425      cpl_f_readflx(5)='oceflx'
426      cpl_f_readflx(6)='oceflx'
427      cpl_f_readtau(1)='ocetau'
428      cpl_f_readtau(2)='ocetau'
429      cpl_f_readtau(3)='ocetau'
430      cpl_f_readtau(4)='ocetau'
431
432      ! Namelist namcpl : coupling mode and frequency
433      REWIND( numnam )
434      READ  ( numnam, namcpl )
435
436      IF(lwp) THEN
437         WRITE(numout,*) 'namcpl'
438         WRITE(numout,*) 
439         WRITE(numout,*) ' Coupling exchange frequency    nexco  = ',nexco
440         WRITE(numout,*) ' Coupling exchange technique    cchan  = ',cchan
441         WRITE(numout,*) ' Mode Coupling technique      nmodcpl  = ',nmodcpl
442         WRITE(numout,*) ' Define the model name      cplmodnam  = ',cplmodnam
443         WRITE(numout,*) ' Define the coupler name      cploasis = ',cploasis
444         WRITE(numout,*) ' Fields number ocean to coupler nfldo2c= ',nfldo2c
445         WRITE(numout,*) ' Flux fields coupler to ocean nflxc2o  = ',nflxc2o
446         WRITE(numout,*) ' Stress fields coupler to ocean ntauc2o= ',ntauc2o
447         IF ( cchan == 'PIPE' .OR.  cchan == 'pipe' ) THEN
448            cchan='PIPE'
449            WRITE(numout,*)'(communication between models made by pipes)'
450         ELSEIF( cchan == 'CLIM' .OR. cchan == 'clim' ) THEN
451            cchan='CLIM'
452            WRITE(numout,*)'(communication between models made by CLIM-PVM)'
453         ELSEIF( cchan == 'SIPC' .OR. cchan == 'sipc' ) THEN
454            cchan='SIPC'
455            WRITE(numout,*)'(communication between models made by the',  &
456               'Share Memory Segment and Semaphore)'
457         ELSE
458            WRITE(numout,*) 'technic not yet implemented ',cchan
459            STOP 'in cpl_read'
460         ENDIF
461         DO jf = 1, nflxc2o
462            WRITE(numout,*) 'file to receive field number = ',jf,'  ',cpl_f_readflx(jf) 
463         END DO
464         DO jf = 1, ntauc2o
465            WRITE(numout,*) 'file to receive field number = ',jf,'  ',cpl_f_readtau(jf) 
466         END DO
467         DO jf = 1, nfldo2c
468            WRITE(numout,*) 'file to send field number = ',jf,'  ',cpl_f_writ(jf)
469         END DO
470         WRITE(numout,*) ' fields received from coupler'
471         DO jf = 1, nflxc2o
472            WRITE(numout,*) 'symbolic name for field number = ',jf,'  ',cpl_readflx(jf) 
473         END DO
474         DO jf = 1, ntauc2o
475            WRITE(numout,*) 'symbolic name for field number = ',jf,'  ',cpl_readtau(jf) 
476         END DO
477         WRITE(numout,*) ' fields send to coupler'
478         DO jf = 1, nfldo2c
479            WRITE(numout,*) 'symbolic name for field number = ',jf,'  ',cpl_writ(jf)
480         END DO
481      ENDIF
482
483   END SUBROUTINE cpl_read
484
485
486   SUBROUTINE cpl_stp( kt )
487      !!---------------------------------------------------------------------
488      !!                  ***  ROUTINE cpl_stp  ***
489      !!                      *****************
490      !!                      * OASIS routine *
491      !!                      *****************
492      !! ** Purpose : - At each coupling time-step,this routine sends fields
493      !!      like sst or ice cover to the coupler.
494      !!              - At each time-step computes time average values
495      !!              - Specific treatment for the last time-step
496      !!
497      !! ** Method  :   3 types available:
498      !!      a) Use named pipes(FIFO) to exchange process identifiers
499      !!         between the 3 programs
500      !!      b) USE a messag passing method with PVM language (CLIM)
501      !!      c) USE SVIPC method
502      !!
503      !! History :
504      !!        !  92-09 (L. Terray)  Original code
505      !!        !  96-07 (L. Terray)  OASIS version 2
506      !!        !  96-11 (E. Guilyardi)  run-off + Taux,Tauy x2
507      !!        !  98-04 (M.A Foujols, S. Valcke, M. Imbard)  OASIS2.2
508      !!   8.5  !  02-06  (G. Madec)  F90: Free form and module
509      !!----------------------------------------------------------------------
510      !! * modules used
511      USE ioipsl
512
513      !! * Arguments
514      INTEGER, INTENT( in ) ::   kt    ! ocean time-step
515
516      !! * Local declarations
517      INTEGER :: ji, jj, jn, jf           ! dummy loop indexes
518      INTEGER :: icstep, info, ierror, isize
519      INTEGER :: iflmax, iunmax
520      INTEGER :: ifile(jpmaxfld), ifield(jpmaxfld)
521      CHARACTER (len=8) ::  clfile(jpmaxfld) 
522      LOGICAL :: llfind
523      REAL(wp), DIMENSION(jpiglo,jpjglo) ::    &
524         zstoc, zieoc, zalboc, zticoc
525     
526      ! netcdf outputs
527       
528      CHARACTER (len=80) ::  clcplsnam
529      INTEGER, SAVE ::  nhoridcs, nidcs, ndexcs(1)
530      LOGICAL, SAVE :: lfirsts = .TRUE.
531      REAL(wp) ::    zjulian
532     
533      ! Additions for SVIPC
534     
535      INTEGER  :: index
536      INTEGER, DIMENSION(3) :: infos
537      CHARACTER (len=3) ::  clmodinf       ! Header or not
538      CHARACTER (len=3) ::  cljobnam      ! experiment name
539      !!----------------------------------------------------------------------
540
541      ! coupled mode Ocean/Atmosphere
542
543      ! 0. Initialization
544      ! -----------------
545
546      isize = jpiglo * jpjglo
547
548      ! First time step: ocean sst and ice sea-ice extend set to zero
549      IF( kt == nit000 ) THEN
550         sstoc(:,:) = 0.e0
551         sieoc(:,:) = 0.e0
552         alboc(:,:) = 0.e0
553         ticoc(:,:) = 0.e0
554
555         ! initialisation for netcdf outputs
556         !
557         ndexcs(:) = 0
558         clcplsnam = "cpl_oce_sst"
559
560         ! Compute julian date from starting date of the run
561         CALL ymds2ju( nyear, nmonth, nday, 0.e0, zjulian )
562         CALL histbeg(clcplsnam, jpiglo, glamt, jpjglo, gphit,   &
563            1, jpiglo, 1, jpjglo, 0,   &
564            zjulian, rdt, nhoridcs, nidcs)
565         ! no vertical axis
566         DO jf = 1, nfldo2c
567            CALL histdef(nidcs, cpl_writ(jf),cpl_writ(jf),"-",jpi,    &
568               jpj, nhoridcs, 1, 1, 1, -99, 32, "inst", rdt, rdt)
569         END DO
570         CALL histend(nidcs)
571      ENDIF
572
573      ! 1. Cumulated sst and sea-ice extend
574      !------------------------------------
575
576      sstoc(:,:) = sstoc(:,:) + ( 1.0 - freeze(:,:) ) * ( tn(:,:,1) + rt0 )
577      sieoc(:,:) = sieoc(:,:) + freeze(:,:)
578
579#if defined key_ice_lim
580      alboc(:,:) = alboc(:,:) + freeze(:,:) * alb_ice(:,:)
581      ticoc(:,:) = ticoc(:,:) + freeze(:,:) * tn_ice(:,:) 
582#else
583      alboc(:,:) = alboc(:,:) + freeze(:,:) * 0.8
584      ticoc(:,:) = ticoc(:,:) + freeze(:,:) * ( -10.e0 + rt0 )
585#endif
586
587
588      ! 2. Send coupling fields to OASIS
589      !---------------------------------
590
591      IF( MOD( kt, nexco ) == 0 ) THEN
592
593         ! 2.1 Average : mean coupling fields
594         zstoc (:,:) = 0.e0
595         zieoc (:,:) = 0.e0
596         zalboc(:,:) = 0.e0
597         zticoc(:,:) = 0.e0
598         DO jj = 1, nlcj
599            DO ji = 1, nlci
600               zstoc (mig(ji),mjg(jj)) = sstoc(ji,jj) / FLOAT( nexco )
601               zieoc (mig(ji),mjg(jj)) = sieoc(ji,jj) / FLOAT( nexco )
602               zalboc(mig(ji),mjg(jj)) = alboc(ji,jj) / FLOAT( nexco )
603               zticoc(mig(ji),mjg(jj)) = ticoc(ji,jj) / FLOAT( nexco )
604            END DO
605         END DO
606         icstep = kt - nit000 + 1
607
608         WRITE(numout,*)
609         WRITE(numout,*) 'STEP: Send fields to CPL with kt= ', kt
610         WRITE(numout,*)
611
612         ! outputs
613
614         CALL histwrite( nidcs, cpl_writ(1), kt, zstoc , jpi*jpj, ndexcs )
615         CALL histwrite( nidcs, cpl_writ(2), kt, zieoc , jpi*jpj, ndexcs )
616         CALL histwrite( nidcs, cpl_writ(3), kt, zalboc, jpi*jpj, ndexcs )
617         CALL histwrite( nidcs, cpl_writ(4), kt, zticoc, jpi*jpj, ndexcs )
618         CALL histsync ( nidcs )
619
620         ! 2.2 Last time step (clim or pipe) or pipe mode
621         !
622         IF( kt == nitend .OR. cchan == 'PIPE' ) THEN 
623
624            ! finalize outputs
625
626            CALL histclo( nidcs )
627
628            ! WRITE fields for coupler with pipe technique or for last time step
629
630            ! initialisation
631
632            iflmax =  1
633            iunmax = 99
634           
635            clfile(iflmax) = cpl_f_writ(iflmax)     ! keeps first file name
636            ifile(iflmax) = iunmax                  ! keeps first file unit
637            iunmax = iunmax - 1                     ! decrements file unit maximum
638            ifield(1) = ifile(iflmax)               ! keeps file unit for field
639
640            ! different files names counter
641            DO jf = 2, nfldo2c
642               llfind = .FALSE.
643               DO jn = 1, iflmax
644                  IF( .NOT. llfind ) THEN
645                     IF( cpl_f_writ(jf) == clfile(jn) ) THEN
646                        ifield(jf) = ifile(jn)      ! keep file unit for field
647                        llfind = .TRUE.
648                     ENDIF
649                  END IF
650               END DO
651               IF( .NOT. llfind) THEN
652                  iflmax = iflmax + 1               ! increment the number of different files
653                  clfile(iflmax) = cpl_f_writ(jf)   ! keep file name
654                  ifile (iflmax) = iunmax           ! keep file unit for file
655                  ifield(jf) = ifile(iflmax)        ! keep file unit for field
656                  iunmax = iunmax-1                 ! decrement unit maximum number from 99 to 98...
657               ENDIF
658            END DO
659            !         
660            DO jn = 1, iflmax 
661               OPEN (ifile(jn), FILE=clfile(jn), FORM='UNFORMATTED')
662            END DO
663            !             
664            DO jf = 1, nfldo2c
665               IF( jf == 1 ) CALL locwrite(cpl_writ(jf),zstoc , isize, ifield(jf), ierror, numout) 
666               IF( jf == 2 ) CALL locwrite(cpl_writ(jf),zieoc , isize, ifield(jf), ierror, numout) 
667               IF( jf == 3 ) CALL locwrite(cpl_writ(jf),zalboc, isize, ifield(jf), ierror, numout) 
668               IF( jf == 4 ) CALL locwrite(cpl_writ(jf),zticoc, isize, ifield(jf), ierror, numout) 
669            END DO
670
671            ! simulate a FLUSH
672
673            DO jn = 1, iflmax 
674               CLOSE( ifile(jn) )
675            END DO
676
677            ! Clim mode
678            IF( cchan == 'CLIM' ) THEN  ! inform PVM daemon, I have finished
679               CALL CLIM_Quit( CLIM_ContPvm, info )
680               IF( info /= CLIM_Ok ) THEN
681                  WRITE (6, *) 'An error occured while leaving CLIM. Error = ',info
682               ENDIF
683            ENDIF
684
685         ENDIF
686
687         ! IF last we have finished if not pass info to the atmosphere
688
689         IF ( kt /= nitend ) THEN
690
691            ! 2.3 normal exchange
692
693            ! PIPE mode     
694            IF( cchan == 'PIPE' ) THEN 
695
696               ! Send message to pipes for CPL=atmosphere
697
698               ! DO jf = 1, nfldo2c
699               !    CALL PIPE_Model_Send(cpl_writ(jf), icstep, numout)
700               ! END DO
701
702               ! SIPC mode
703            ELSE IF( cchan == 'SIPC' ) THEN
704
705               ! Define IF a header must be encapsulated within the field brick :
706               clmodinf = 'NOT'  ! as $MODINFO in namcouple 
707
708               ! IF clmodinf = 'YES', define encapsulated infos to be exchanged
709               !    infos(1) = initial date
710               !    infos(2) = timestep
711               !    infos(3) = actual time
712               !
713               ! Writing of output field SST SOSSTSST
714               !
715               ! Index of SST in total number of fields jpfldo2a:
716               index = 1
717               !
718               ! CALL SIPC_Write_Model(index, isize, clmodinf, cljobnam, infos, zstoc)
719               !
720               ! Writing of output field Sea-Ice SOICECOV
721               !
722               ! Index of sea-ice in total number of fields jpfldo2a:
723               index = 2
724               !
725               ! CALL SIPC_Write_Model(index, isize, clmodinf, cljobnam, infos, zieoc)
726   
727               ! CLIM mode
728            ELSE IF( cchan == 'CLIM' ) THEN
729   
730               DO jn = 1, nfldo2c
731   
732                  IF (jn == 1) CALL CLIM_Export(cpl_writ(jn), icstep, zstoc , info)
733                  IF (jn == 2) CALL CLIM_Export(cpl_writ(jn), icstep, zieoc , info)
734                  IF (jn == 3) CALL CLIM_Export(cpl_writ(jn), icstep, zalboc, info)
735                  IF (jn == 4) CALL CLIM_Export(cpl_writ(jn), icstep, zticoc, info)
736
737                  IF (info /= CLIM_Ok) THEN
738                     WRITE (numout,*) 'STEP : Pb giving', cpl_writ(jn), ':', jn
739                     WRITE (numout,*) ' at timestep = ', icstep, 'kt = ', kt
740                     WRITE (numout,*) 'Clim error code is = ',info
741                     WRITE (numout,*) 'STOP in stpcpl '
742                     CALL abort(' stpcpl ')
743                  ENDIF
744               END DO
745            ENDIF
746
747            ! reset cumulative sst and sea-ice extend to zero
748            sstoc(:,:) = 0.e0
749            sieoc(:,:) = 0.e0
750            alboc(:,:) = 0.e0
751            ticoc(:,:) = 0.e0
752         ENDIF
753      ENDIF
754
755   END SUBROUTINE cpl_stp
756
757#else
758   !!----------------------------------------------------------------------
759   !!   Default case           Dummy module         forced Ocean/Atmosphere
760   !!----------------------------------------------------------------------
761CONTAINS
762   SUBROUTINE cpl_init            ! Dummy routine
763      WRITE(*,*) 'cpl_init: You should have not see this print! error?'
764   END SUBROUTINE cpl_init
765   SUBROUTINE cpl_stp( kt )       ! Dummy routine
766      WRITE(*,*) 'cpl_stp: You should have not see this print! error?', kt
767   END SUBROUTINE cpl_stp
768#endif
769
770   !!======================================================================
771END MODULE cpl
Note: See TracBrowser for help on using the repository browser.