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

Last change on this file since 699 was 699, checked in by smasson, 17 years ago

insert revision Id

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