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 @ 3

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

Initial revision

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