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

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

CL + CT: BUGFIX087: Add missing "USE daymod" and "USE phycst" modules

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