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_oasis4.F90 in trunk/NEMO/OPA_SRC/SBC – NEMO

source: trunk/NEMO/OPA_SRC/SBC/cpl_oasis4.F90 @ 1146

Last change on this file since 1146 was 1146, checked in by rblod, 16 years ago

Add svn Id (first try), see ticket #210

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 45.2 KB
Line 
1MODULE cpl_oasis4
2   !!======================================================================
3   !!                    ***  MODULE cpl_oasis4  ***
4   !! Coupled O/A : coupled ocean-atmosphere case using OASIS4
5   !!               special case: OPA/LIM coupled to ECHAM5
6   !!=====================================================================
7   !! History :   
8   !!   9.0  !  04-06  (R. Redler, NEC CCRLE, Germany) Original code
9   !!   " "  !  04-11  (R. Redler, N. Keenlyside) revision
10   !!   " "  !  04-11  (V. Gayler, MPI M&D) Grid writing
11   !!   " "  !  05-08  (R. Redler, W. Park) frld initialization, paral(2) revision
12   !!   " "  !  05-09  (R. Redler) extended to allow for communication over root only
13   !!   " "  !  05-09  (R. Redler) extended to allow for communication over root only
14   !!   " "  !  05-12  (R. Hill, Met. Office) Tweaks and hacks to get NEMO/O4 working
15   !!   " "  !  06-02  (R. Redler, W. Park) Bug fixes and updates according to the OASIS3 interface
16   !!   " "  !  06-02  (R. Redler) app/grid/grid_name from namelist
17   !!----------------------------------------------------------------------
18#if defined key_oasis4
19   !!----------------------------------------------------------------------
20   !!   'key_oasis4'                    coupled Ocean/Atmosphere via OASIS4
21   !!----------------------------------------------------------------------
22   !!   cpl_prism_init     : initialization of coupled mode communication
23   !!   cpl_prism_define   : definition of grid and fields
24   !!   cpl_prism_send     : send out fields in coupled mode
25   !!   cpl_prism_recv     : receive fields in coupled mode
26   !!   cpl_prism_finalize : finalize the coupled mode communication
27   !!----------------------------------------------------------------------
28   !! * Modules used
29!##################### WARNING coupled mode ###############################
30!##################### WARNING coupled mode ###############################
31!   Following line must be enabled if coupling with OASIS
32!   USE prism                        ! prism module
33!##################### WARNING coupled mode ###############################
34!##################### WARNING coupled mode ###############################
35#if defined key_mpp_mpi
36   USE lib_mpp, only : mppsize, mpprank   ! message passing
37   USE lib_mpp, only : mppsend            ! message passing
38   USE lib_mpp, only : mpprecv            ! message passing
39#endif
40   USE daymod                       ! date and time info
41   USE dom_oce                      ! ocean space and time domain
42   USE in_out_manager               ! I/O manager
43   USE par_oce                      !
44   USE phycst, only : rt0           ! freezing point of sea water
45   USE oasis4_date                  ! OASIS4 date declarations in
46                                    ! PRISM compatible format
47   IMPLICIT NONE
48!
49! Exchange parameters for coupling ORCA-LIM with ECHAM5
50!
51#if defined key_cpl_ocevel
52   INTEGER, PARAMETER         :: nsend =  6
53#else
54   INTEGER, PARAMETER         :: nsend =  4
55#endif
56
57#if defined key_cpl_discharge
58   INTEGER, PARAMETER         :: nrecv = 20
59#else
60   INTEGER, PARAMETER         :: nrecv = 17
61#endif
62
63   INTEGER, DIMENSION(nsend)  :: send_id
64   INTEGER, DIMENSION(nrecv)  :: recv_id
65
66   CHARACTER(len=32)          :: cpl_send (nsend)
67   CHARACTER(len=32)          :: cpl_recv (nrecv)
68
69   CHARACTER(len=16)          :: app_name       ! application name for OASIS use
70   CHARACTER(len=16)          :: comp_name      ! name of this PRISM component
71   CHARACTER(len=16)          :: grid_name      ! name of the grid
72   CHARACTER(len=1)           :: c_mpi_send
73
74! The following now come in via new module oasis4_date
75!   TYPE(PRISM_Time_struct), PUBLIC    :: dates          ! date info for send operation
76!   TYPE(PRISM_Time_struct), PUBLIC    :: dates_bound(2) ! date info for send operation
77!   TYPE(PRISM_Time_struct), PUBLIC    :: dater          ! date info for receive operation
78!   TYPE(PRISM_Time_struct), PUBLIC    :: dater_bound(2) ! date info for receive operation
79!   TYPE(PRISM_Time_struct), PUBLIC    :: tmpdate
80
81   PRIVATE
82
83   INTEGER, PARAMETER         :: localRoot  = 0
84
85   INTEGER                    :: localRank      ! local MPI rank
86   INTEGER                    :: localSize      ! local MPI size
87   INTEGER                    :: localComm      ! local MPI size
88   LOGICAL                    :: commRank       ! true for ranks doing OASIS communication
89   INTEGER                    :: comp_id        ! id returned by prism_init_comp
90
91   INTEGER                    :: range(5)
92
93   LOGICAL, SAVE              :: prism_was_initialized
94   LOGICAL, SAVE              :: prism_was_terminated
95   INTEGER, SAVE              :: write_grid
96
97   INTEGER                    :: ierror         ! return error code
98
99#ifdef key_cpl_rootexchg
100   LOGICAL                               :: rootexchg =.true.     ! logical switch
101#else
102   LOGICAL                               :: rootexchg =.false.    ! logical switch
103#endif
104
105   REAL(wp), DIMENSION(:,:), ALLOCATABLE :: exfld  ! Temporary buffer for exchange
106   REAL(wp), DIMENSION(:),   ALLOCATABLE :: buffer ! Temporary buffer for exchange
107   INTEGER, DIMENSION(:,:),  ALLOCATABLE :: ranges ! Temporary buffer for exchange
108
109   DOUBLE PRECISION           :: date_incr
110
111   !! Routine accessibility
112   PUBLIC cpl_prism_init
113   PUBLIC cpl_prism_define
114   PUBLIC cpl_prism_send
115   PUBLIC cpl_prism_recv
116   PUBLIC cpl_prism_finalize
117
118   PUBLIC send_id, recv_id
119
120   !!----------------------------------------------------------------------
121   !!   OPA 9.0 , LOCEAN-IPSL (2006)
122   !! $ Id: $
123   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
124   !!----------------------------------------------------------------------
125
126CONTAINS
127
128   SUBROUTINE cpl_prism_init( localCommunicator )
129
130      IMPLICIT NONE
131
132      !!-------------------------------------------------------------------
133      !!             ***  ROUTINE cpl_prism_init  ***
134      !!
135      !! ** Purpose :   Initialize coupled mode communication for ocean
136      !!    exchange between AGCM, OGCM and COUPLER. (OASIS4 software)
137      !!
138      !! ** Method  :   OASIS4 MPI communication
139      !!--------------------------------------------------------------------
140      !! * Arguments
141      !!
142      INTEGER, INTENT(OUT)       :: localCommunicator
143      !!
144      !! * Local declarations
145      !!
146
147      NAMELIST/nam_mpp/ app_name, comp_name, c_mpi_send, grid_name
148
149      !!
150      !!--------------------------------------------------------------------
151      !!
152      IF(lwp) WRITE(numout,*)
153      IF(lwp) WRITE(numout,*) 'cpl_prism_init : initialization in coupled ocean/atmosphere case'
154      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~~~'
155      IF(lwp) WRITE(numout,*)
156     
157#if defined key_flx_bulk_monthly || defined key_flx_bulk_daily || defined key_flx_forced_daily
158
159#if !defined key_oasis4
160! The following is not necessarily a valid peice of checking
161
162      IF(lwp) WRITE(numout,cform_err)
163      IF(lwp) WRITE(numout,*) ' key_coupled and key_flx_bulk_* key_flx_forced_daily are incompatible'
164      nstop = nstop + 1
165
166#endif
167
168#endif
169
170      REWIND( numnam )
171      READ  ( numnam, nam_mpp )
172      REWIND( numnam )
173
174      !------------------------------------------------------------------
175      ! 1st Initialize the PRISM system for the application
176      !------------------------------------------------------------------
177
178      CALL prism_initialized (prism_was_initialized, ierror)
179      IF ( ierror /= PRISM_Success ) &
180         CALL prism_abort( comp_id, 'OPA9.0', 'cpl_prism_init: Failure in prism_initialized' )
181
182      IF ( .NOT. prism_was_initialized ) THEN
183         CALL prism_init( app_name, ierror )
184         IF ( ierror /= PRISM_Success ) &
185            CALL prism_abort(comp_id, 'OPA9.0', 'cpl_prism_init: Failure in prism_init')
186         prism_was_initialized = .true.
187      ELSE
188         call prism_abort(comp_id, 'OPA9.0', 'cpl_prism_init: Do not initialize prism twice!')
189      ENDIF
190      !
191      ! Obtain the actual dates and date bounds
192      !
193      ! date is determined by adding days since beginning of
194      !   the run to the corresponding initial date. Note that
195      !   OPA internal info about the start date of the experiment
196      !   is bypassed. Instead we rely sololy on the info provided
197      !   by the SCC.xml file.
198      !
199      dates   = PRISM_Jobstart_date
200
201      WRITE(6,*) "PRISM JOB START DATE IS", dates
202
203      !
204      ! upper bound is determined by adding half a time step
205      !
206      tmpdate = dates
207      date_incr = rdttra(1)/2.0
208      CALL PRISM_calc_newdate ( tmpdate, date_incr, ierror )
209      dates_bound(2) = tmpdate
210      !
211      ! lower bound is determined by half distance to date from previous run
212      !
213      tmpdate   = dates
214      date_incr = ( adatrj - adatrj0 ) * 43200.0
215      CALL PRISM_calc_newdate ( tmpdate, date_incr, ierror )
216      dates_bound(1) = tmpdate
217
218      dater = dates
219      dater_bound(1) = dates_bound(1) 
220      dater_bound(2) = dates_bound(2) 
221
222      WRITE(6,*) "DATE send and rec BOUNDS",dater_bound
223      WRITE(6,*) "OTHER BITS FOR DATE",rdttra(1)
224      WRITE(6,*) "adatrj/0",adatrj,adatrj0,date_incr
225
226      !------------------------------------------------------------------
227      ! 2nd Initialize the PRISM system for the component
228      !------------------------------------------------------------------
229
230      CALL prism_init_comp ( comp_id, comp_name, ierror )
231      IF ( ierror /= PRISM_Success ) &
232         CALL prism_abort (comp_id, 'OPA9.0', 'cpl_prism_init: Failure in prism_init_comp')
233
234      WRITE(6,*) "COMPLETED INIT_COMP",comp_name,comp_id
235
236      !------------------------------------------------------------------
237      ! 3rd Get an MPI communicator for OPA local communication
238      !------------------------------------------------------------------
239
240      CALL prism_get_localcomm ( comp_id, localComm, ierror )
241      IF ( ierror /= PRISM_Success ) &
242         CALL prism_abort (comp_id, 'OPA9.0', 'cpl_prism_init: Failure in prism_get_localcomm' )
243
244      localCommunicator = localComm
245
246       WRITE(6,*) "COMPLETED GET_LOCALCOMM",comp_name,comp_id
247
248
249   END SUBROUTINE cpl_prism_init
250
251
252   SUBROUTINE cpl_prism_define ()
253
254      IMPLICIT NONE
255
256      !!-------------------------------------------------------------------
257      !!             ***  ROUTINE cpl_prism_define  ***
258      !!
259      !! ** Purpose :   Define grid and field information for ocean
260      !!    exchange between AGCM, OGCM and COUPLER. (OASIS4 software)
261      !!
262      !! ** Method  :   OASIS4 MPI communication
263      !!--------------------------------------------------------------------
264      !! * Arguments
265      !!
266      !! * Local declarations
267
268      INTEGER                    :: grid_id(2)     ! id returned by prism_def_grid
269
270      INTEGER                    :: upoint_id(2), &
271                                    vpoint_id(2), &
272                                    tpoint_id(2), &
273                                    fpoint_id(2)   ! ids returned by prism_set_points
274
275      INTEGER                    :: umask_id(2), &
276                                    vmask_id(2), &
277                                    tmask_id(2), &
278                                    fmask_id(2)    ! ids returned by prism_set_mask
279
280      INTEGER                    :: grid_type      ! PRISM grid type
281
282      INTEGER                    :: shape(2,3)     ! shape of arrays passed to PSMILe
283      INTEGER                    :: nodim(2)
284      INTEGER                    :: data_type      ! data type of transients
285
286      INTEGER                    :: nbr_corners
287
288      LOGICAL                    :: new_points
289      LOGICAL                    :: new_mask
290      LOGICAL                    :: mask(jpi,jpj,jpk)
291
292      INTEGER                    :: ji, jj, jk     ! local loop indicees
293
294      CHARACTER(len=32)          :: cpl_send (nsend)
295      CHARACTER(len=32)          :: cpl_recv (nrecv)
296
297      CHARACTER(len=32)          :: grid_name      ! name of the grid
298      CHARACTER(len=32)          :: point_name     ! name of the grid points
299
300      REAL(kind=wp), ALLOCATABLE :: rclon(:,:,:)
301      REAL(kind=wp), ALLOCATABLE :: rclat(:,:,:)
302      REAL(kind=wp), ALLOCATABLE :: rcz  (:,:)
303
304      !!--------------------------------------------------------------------
305     
306      IF(lwp) WRITE(numout,*)
307      IF(lwp) WRITE(numout,*) 'cpl_prism_define : initialization in coupled ocean/atmosphere case'
308      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~~~~'
309      IF(lwp) WRITE(numout,*)
310     
311#if defined key_flx_bulk_monthly || defined key_flx_bulk_daily || defined key_flx_forced_daily
312
313#if !defined key_oasis4
314! The problem with the following is that it ASSUMES we're only ever coupling to an atmosphere
315! which is not necessarily the case. Prevent this test temporarily for NEMOGAM development.
316
317      IF(lwp) WRITE(numout,cform_err)
318      IF(lwp) WRITE(numout,*) ' key_coupled and key_flx_bulk_... are incompatible'
319      nstop = nstop + 1
320
321#endif
322
323#endif
324
325      ! -----------------------------------------------------------------
326      ! ... Some initialisation
327      ! -----------------------------------------------------------------
328
329      send_id = 0
330      recv_id = 0
331
332#if defined key_mpp_mpi
333
334      ! -----------------------------------------------------------------
335      ! ... Some MPI stuff relevant for optional exchange via root only
336      ! -----------------------------------------------------------------
337
338      commRank = .false.
339
340      localRank = mpprank ! from lib_mpp
341      localSize = mppsize ! from lib_mpp
342
343      IF(lwp) WRITE(numout,*) "CALLING DEFINE"
344
345      IF ( rootexchg ) THEN
346         IF ( localRank == localRoot ) commRank = .true.
347      ELSE
348         commRank = .true.
349      ENDIF
350
351#else
352      !
353      ! For non-parallel configurations the one and only process ("localRoot")
354      ! takes part in the communication
355      !
356      localRank = localRoot
357      commRank = .true.
358
359#endif
360
361      ! -----------------------------------------------------------------
362      ! ... Allocate memory for data exchange
363      ! -----------------------------------------------------------------
364
365
366      IF(lwp) WRITE(numout,*) "Abbout to allocate exfld",jpi,jpj
367
368      ALLOCATE(exfld(1:jpi,1:jpj), stat = ierror)
369      IF (ierror > 0) THEN
370         CALL prism_abort ( comp_id, 'OPA9.0', 'cpl_prism_define: Failure in allocating Reals')
371         RETURN
372      ENDIF
373
374      IF ( rootexchg .and. localRank == localRoot ) THEN
375         ALLOCATE(ranges(5,0:localSize-1), stat = ierror)
376         IF (ierror > 0) THEN
377            CALL prism_abort ( comp_id, 'OPA9.0', 'cpl_prism_define: Failure in allocating Integer')
378            RETURN
379         ENDIF
380      ENDIF
381
382      !------------------------------------------------------------------
383      ! 1st Declare the local grid (ORCA tripolar) characteristics for
384      !     surface coupling. The halo regions must be excluded. For
385      !     surface coupling it is sufficient to specify only one
386      !     vertical z-level.
387      !------------------------------------------------------------------
388
389      grid_type = PRISM_irrlonlat_regvrt
390
391      IF(lwp) WRITE(numout,*) "Set grid type"
392
393
394      ! -----------------------------------------------------------------
395      ! ... Define the shape of the valid region without the halo.
396      !     For serial configuration (key_mpp_mpi not being active)
397      !     nl* is set to the global values 1 and jp*glo.
398      ! -----------------------------------------------------------------
399
400      IF ( rootexchg ) THEN
401         shape(1,1) = 1+jpreci
402         shape(2,1) = jpiglo-jpreci
403         shape(1,2) = 1+jpreci
404         shape(2,2) = jpjglo-jpreci
405         shape(1,3) = 1
406         shape(2,3) = 1
407      ELSE
408         shape(1,1) = 1+jpreci
409         shape(2,1) = jpi-jpreci
410         shape(1,2) = 1+jpreci
411         shape(2,2) = jpj-jpreci
412         shape(1,3) = 1
413         shape(2,3) = 1
414      ENDIF
415
416      IF(lwp) WRITE(numout,*) "commrank is", commRank
417
418      IF ( commRank ) THEN
419
420         IF(lwp) WRITE(numout,*) "CALLING DEF_GRID"
421
422         IF(lwp) WRITE(numout,*) "grid name",grid_name
423         IF(lwp) WRITE(numout,*) " shape",shape
424         IF(lwp) WRITE(numout,*) "grid type",grid_type
425
426         CALL prism_def_grid ( grid_id(1), grid_name, comp_id, shape, &
427              grid_type, ierror )
428         IF ( ierror /= PRISM_Success ) THEN
429            PRINT *, 'OPA cpl_prism_define: Failure in prism_def_grid'
430            CALL prism_abort (comp_id, 'OPA9.0', 'cpl_prism_define: Failure in prism_def_grid')
431         ENDIF
432
433         !------------------------------------------------------------------
434         ! 2nd Declare the geometic information for this grid.
435         !------------------------------------------------------------------
436
437         ! -----------------------------------------------------------------
438         ! ... Redefine shape which may now include the halo region as well.
439         ! -----------------------------------------------------------------
440
441         shape(1,1) = 1
442         shape(2,1) = jpi
443         shape(1,2) = 1
444         shape(2,2) = jpj
445         shape(1,3) = 1
446         shape(2,3) = 1
447
448         IF(lwp) WRITE(numout,*) "redefined shape",shape
449
450         ! -----------------------------------------------------------------
451         ! ... Define the elements, i.e. specify the corner points for each
452         !     volume element. In case OPA runs on level coordinates (regular
453         !     in the vertical) we only need to give the 4 horizontal corners
454         !     for a volume element plus the vertical position of the upper
455         !     and lower face. Nevertheless the volume element has 8 corners.
456         ! -----------------------------------------------------------------
457
458         !
459         ! ... Treat corners in the horizontal plane
460         !
461         ALLOCATE(rclon(shape(1,1):shape(2,1),shape(1,2):shape(2,2),4), &
462              STAT=ierror)
463         IF ( ierror /= 0 ) &
464              CALL prism_abort ( comp_id, 'OPA9.0', 'cpl_prism_define: error in allocate for rclon')
465
466         ALLOCATE(rclat(shape(1,1):shape(2,1),shape(1,2):shape(2,2),4), &
467              STAT=ierror)
468         IF ( ierror /= 0 ) &
469              CALL prism_abort ( comp_id, 'OPA9.0', 'cpl_prism_define: error in allocate for rclon')
470
471         nbr_corners = 8
472         !
473         ! ... Set right longitudes and upper latitudes
474         !
475         DO jj = shape(1,2), shape(2,2)
476            DO ji = shape(1,1), shape(2,1)
477               rclon(ji,jj,1) = glamu(ji,jj)
478               rclon(ji,jj,2) = glamu(ji,jj)
479               rclat(ji,jj,2) = gphiv(ji,jj)
480               rclat(ji,jj,3) = gphiv(ji,jj)
481            ENDDO
482         ENDDO
483         !
484         ! ... Set the lower latitudes
485         !
486         DO jj = shape(1,2)+1, shape(2,2)
487            DO ji = shape(1,1), shape(2,1)
488               rclat(ji,jj-1,1) = rclat(ji,jj,2)
489               rclat(ji,jj-1,4) = rclat(ji,jj,3)
490            ENDDO
491         ENDDO
492         !
493         ! ... Set the left longitudes
494         !
495         DO jj = shape(1,2), shape(2,2)
496            DO ji = shape(1,1)+1, shape(2,1)
497               rclon(ji-1,jj,3) = rclon(ji,jj,2)
498               rclon(ji-1,jj,4) = rclon(ji,jj,1)
499            ENDDO
500         ENDDO
501         !
502         ! ... Set the lowermost latitudes
503         !
504         DO jj = shape(1,2), shape(1,2)
505            DO ji = shape(1,1), shape(2,1)
506               rclat(ji,jj,1) = 2.0*gphit(ji,jj)-rclat(ji,jj,2)
507               rclat(ji,jj,4) = 2.0*gphit(ji,jj)-rclat(ji,jj,4)
508            ENDDO
509         ENDDO
510         !
511         ! ... Set the rightmost latitudes
512         !
513         DO jj = shape(1,2), shape(2,2)
514            DO ji = shape(1,2), shape(1,2)
515               rclon(ji,jj,3) = 2.0*glamt(ji,jj)-rclon(ji,jj,2)
516               rclon(ji,jj,4) = 2.0*glamt(ji,jj)-rclon(ji,jj,1)
517
518               WRITE(76,*) "rclon", ji, jj, rclon(ji,jj,1), &
519                                            rclon(ji,jj,2), &
520                                            rclon(ji,jj,3), &
521                                            rclon(ji,jj,4)
522
523               WRITE(76,*) "rclat", ji, jj, rclat(ji,jj,1), &
524                                            rclat(ji,jj,2), &
525                                            rclat(ji,jj,3), &
526                                            rclat(ji,jj,4)
527
528            ENDDO
529         ENDDO
530
531         !
532         ! ... Treat corners along the vertical axis
533         !
534         ALLOCATE(rcz(shape(1,3):shape(2,3),2), STAT=ierror)
535         IF ( ierror /= 0 ) &
536              CALL prism_abort ( comp_id, 'OPA9.0', 'cpl_prism_define: error in allocate for rcz')
537
538         DO jk = shape(1,3), shape(2,3)
539            rcz(jk,1) = gdepw(jk)
540            rcz(jk,2) = gdepw(jk+1)
541         ENDDO
542
543         IF(lwp) WRITE(numout,*) "ABOUT TO CALL SET CORNERS",shape
544
545         CALL prism_set_corners ( grid_id(1), nbr_corners, shape, rclon, rclat, &
546              rcz, ierror)
547         IF ( ierror /= PRISM_Success ) &
548              CALL prism_abort ( comp_id, 'OPA9.0', 'cpl_prism_define: Failure in prism_set_corners')
549
550         DEALLOCATE(rclon, rclat, rcz)
551
552         ! -----------------------------------------------------------------
553         ! ... Define the gridpoints 
554         ! -----------------------------------------------------------------
555
556         new_points = .TRUE.
557
558         IF(lwp) WRITE(numout,*) "CALLING SET_POINTS"
559
560         !
561         ! ... the u-points
562         !
563         point_name = 'u-points'
564         CALL prism_set_points ( upoint_id(1), point_name, grid_id(1), shape,      &
565              glamu, gphiu, gdept(shape(1,3):shape(2,3)), new_points, ierror )
566         IF ( ierror /= PRISM_Success ) &
567              CALL prism_abort ( comp_id, 'OPA9.0', 'cpl_prism_define: Failure in prism_set_points upoint_id')
568         !
569         ! ... the v-points
570         !
571
572         IF(lwp) WRITE(numout,*) "CALLING SET_POINTS done u doing v"
573
574         point_name = 'v-points'
575         CALL prism_set_points ( vpoint_id(1), point_name, grid_id(1), shape,      &
576              glamv, gphiv, gdept(shape(1,3):shape(2,3)), new_points, ierror )     
577         IF ( ierror /= PRISM_Success ) &
578              CALL prism_abort ( comp_id, 'OPA9.0', 'cpl_prism_define: Failure in prism_set_points vpoint_id')
579         !
580         ! ... the t-points
581         !
582         ! WRITE(76,*) 'CALLING T POINTS', shape
583         ! WRITE(77,*) 'glamt', glamt
584         ! WRITE(78,*) 'gphit', gphit
585         !
586         point_name = 't-points'
587         CALL prism_set_points ( tpoint_id(1), point_name, grid_id(1), shape,   &
588              glamt, gphit, gdept(shape(1,3):shape(2,3)), new_points, ierror )
589         IF ( ierror /= PRISM_Success ) &
590              CALL prism_abort ( comp_id, 'OPA9.0', 'cpl_prism_define: Failure in prism_set_points tpoint_id')
591         !
592         ! ... the f-points
593         !
594         point_name = 'f-points'
595         CALL prism_set_points ( fpoint_id(1), point_name, grid_id(1), shape,   &
596              glamf, gphif, gdept(shape(1,3):shape(2,3)), new_points, ierror )
597         IF ( ierror /= PRISM_Success ) &
598              CALL prism_abort ( comp_id, 'OPA9.0', 'cpl_prism_define: Failure in prism_set_points fpoint_id')
599
600
601         IF(lwp) WRITE(numout,*) "CALLING SET_POINTS done f"
602
603         ! -----------------------------------------------------------------
604         ! ... Convert OPA masks to logicals and define the masks
605         ! -----------------------------------------------------------------
606
607         new_mask = .true.
608
609         mask = (umask == 1)
610         CALL prism_set_mask (umask_id(1), grid_id(1), shape, &
611                 mask(shape(1,1):shape(2,1),                  &
612                      shape(1,2):shape(2,2),                  &
613                      shape(1,3):shape(2,3)),                 &
614              new_mask, ierror )
615         IF ( ierror /= PRISM_Success ) &
616              CALL prism_abort ( comp_id, 'OPA9.0', 'cpl_prism_define: Failure in prism_set_mask umask_id')
617
618         mask = (vmask == 1)
619         CALL prism_set_mask (vmask_id(1), grid_id(1), shape, &
620                 mask(shape(1,1):shape(2,1),                  &
621                      shape(1,2):shape(2,2),                  &
622                      shape(1,3):shape(2,3)),                 &
623              new_mask, ierror )
624         IF ( ierror /= PRISM_Success ) &
625              CALL prism_abort ( comp_id, 'OPA9.0', 'cpl_prism_define: Failure in prism_set_mask umask_id')
626
627         mask = (tmask == 1)
628         CALL prism_set_mask (tmask_id(1), grid_id(1), shape, &
629                 mask(shape(1,1):shape(2,1),                  &
630                      shape(1,2):shape(2,2),                  &
631                      shape(1,3):shape(2,3)),                 &
632              new_mask, ierror )
633         IF ( ierror /= PRISM_Success ) &
634              CALL prism_abort ( comp_id, 'OPA9.0', 'cpl_prism_define: Failure in prism_set_mask umask_id')
635
636         mask = (fmask == 1)
637         CALL prism_set_mask (fmask_id(1), grid_id(1), shape, &
638                 mask(shape(1,1):shape(2,1),                  &
639                      shape(1,2):shape(2,2),                  &
640                      shape(1,3):shape(2,3)),                 &
641              new_mask, ierror )
642         IF ( ierror /= PRISM_Success ) &
643              CALL prism_abort ( comp_id, 'OPA9.0', 'cpl_prism_define: Failure in prism_set_mask umask_id')
644
645         IF(lwp) WRITE(numout,*) "DONE ALL THE SET MASKS"
646
647         ! -----------------------------------------------------------------
648         ! ... Define the angles
649         !   This is needed if zonal tau is not oriented E-W and meridional
650         !   tau is not oriented along N-S but rather along local coordinate
651         !   axis. Please check!!!!
652         ! -----------------------------------------------------------------
653
654!rr      cal prism_set_angles ( ..., ierror ) ! not yet supported by OASIS4
655
656         ! -----------------------------------------------------------------
657         ! ... Define the partition
658         ! -----------------------------------------------------------------
659         
660         IF ( rootexchg ) THEN
661
662            range(1) = nimpp-1+nldi   ! global start in i
663            range(2) = nlei-nldi+1    ! local size in i of valid region
664            range(3) = njmpp-1+nldj   ! global start in j
665            range(4) = nlej-nldj+1    ! local size in j of valid region
666            range(5) = range(2) &
667                     * range(4)       ! local horizontal size
668            !
669            ! Collect ranges from all NEMO procs on the local root process
670            !
671            CALL mpi_gather(range,  5, MPI_INTEGER, &
672                            ranges, 5, MPI_INTEGER, localRoot, localComm, ierror)
673
674            IF ( localRank == localRoot ) THEN
675
676               maxlen = maxval(ranges(5,:))
677
678               ALLOCATE(buffer(1:maxlen), stat = ierror)
679               IF (ierror > 0) THEN
680                  CALL prism_abort ( comp_id, 'OPA9.0', 'cpl_prism_define: Failure in allocating buffer')
681                  RETURN
682               ENDIF
683
684            ENDIF
685
686         ENDIF
687
688         ! -----------------------------------------------------------------
689         ! ... Define the scalefactors
690         ! -----------------------------------------------------------------
691
692!rr      WRITE(numout,*) "CALLING SCALEFACTOR"
693!rr      call prism_set_scalefactor ( grid_id(1), shape, e1t, e2t, e3t, ierror )  ! not yet supported by OASIS4
694!rr      WRITE(numout,*) "ABOUT TO DEFINE THE TRANSIENTS"
695
696         !------------------------------------------------------------------
697         ! 3rd Declare the transient variables
698         !------------------------------------------------------------------
699         !
700         ! ... Define symbolic names for the transient fields send by the ocean
701         !     These must be identical to the names specified in the SMIOC file.
702         !
703         cpl_send( 1)='SOSSTSST' ! sea surface temperature              -> sst_io
704         cpl_send( 2)='SITOCEAN' ! sea ice thickness                    -> hicif (only 1 layer available!)
705#if defined key_cpl_albedo
706         cpl_send( 3)='STIOCEAN' ! surface temperature over sea ice     -> tn_ice
707         cpl_send( 4)='SAIOCEAN' ! albedo over sea ice                  -> alb_ice
708#else
709         cpl_send( 3)='SITOCEAN' ! sea ice thickness                    -> hicif (only 1 layer available!)
710         cpl_send( 4)='SNTOCEAN' ! surface snow thickness over sea ice  -> hsnif
711#endif
712#if defined key_cpl_ocevel
713         cpl_send( 5)='SUNOCEAN' ! U-velocity                           -> un
714         cpl_send( 6)='SVNOCEAN' ! V-velocity                           -> vn
715#endif
716         !
717         ! ...  Define symbolic names for transient fields received by the ocean.
718         !      These must be identical to the names specified in the SMIOC file.
719         !
720         ! ...  a) U-Grid fields
721         !
722         cpl_recv( 1)='TXWOCEWU' ! weighted surface downward eastward stress
723         cpl_recv( 2)='TYWOCEWU' ! weighted surface downward northward stress
724         cpl_recv( 3)='TXIOCEWU' ! weighted surface downward eastward stress over ice
725         cpl_recv( 4)='TYIOCEWU' ! weighted surface downward northward stress over ice
726         !
727         ! ...  a) V-Grid fields
728         !
729         cpl_recv( 5)='TXWOCEWV' ! weighted surface downward eastward stress
730         cpl_recv( 6)='TYWOCEWV' ! weighted surface downward northward stress
731         cpl_recv( 7)='TXIOCEWV' ! weighted surface downward eastward stress over ice
732         cpl_recv( 8)='TYIOCEWV' ! weighted surface downward northward stress over ice
733         !
734         ! ...  a) T-Grid fields
735         !
736         cpl_recv( 9)='FRWOCEPE' ! P-E over water                               -> zpew
737         cpl_recv(10)='FRIOCEPE' ! P-E over ice                                 -> zpei
738         cpl_recv(11)='FRROCESN' ! surface downward snow fall                   -> zpsol
739         cpl_recv(12)='FRIOCEEV' ! surface upward snow flux where sea ice       -> zevice
740
741         cpl_recv(13)='QSWOCESR' ! surface net downward shortwave flux          -> qsr_oce
742         cpl_recv(14)='QSWOCENS' ! surface downward non-solar heat flux in air  -> qnsr_oce
743         cpl_recv(15)='QSIOCESR' ! solar heat flux on sea ice                   -> qsr_ice
744         cpl_recv(16)='QSIOCENS' ! non-solar heat flux on sea ice               -> qnsr_ice
745         cpl_recv(17)='QSIOCEDQ' ! non-solar heat flux derivative               -> dqns_ice
746
747#ifdef key_cpl_discharge
748         cpl_recv(18)='FRWOCEIS' ! ice discharge into ocean                     -> calving
749         cpl_recv(19)='FRWOCERD' ! river discharge into ocean                   -> zrunriv
750         cpl_recv(20)='FRWOCECD' ! continental discharge into ocean             -> zruncot
751#endif
752         IF ( wp == 4 ) data_type = PRISM_REAL
753         IF ( wp == 8 ) data_type = PRISM_DOUBLE_PRECISION
754
755         nodim(1) = 3 ! check
756         nodim(2) = 0
757         !
758         ! ... Announce send variables, all on T points.
759         !
760         DO ji = 1, nsend
761            ! if ( ji == 2 ) ; then ; nodim(2) = 2 ; else ; nodim(2) = 0 ; endif
762            CALL prism_def_var (send_id(ji), cpl_send(ji), grid_id(1), &
763                 tpoint_id(1), tmask_id(1), nodim, shape, data_type, ierror)
764            IF ( ierror /= PRISM_Success ) THEN
765               PRINT *, 'Failed to define transient ', ji, TRIM(cpl_send(ji))
766               CALL prism_abort ( comp_id, 'OPA9.0', 'cpl_prism_define: Failure in prism_def_var')
767            ENDIF
768         ENDDO
769         !
770         nodim(1) = 3 ! check
771         nodim(2) = 0
772         !
773         ! ... Announce recv variables.
774         !
775         ! ... a) on U points
776         !
777         DO ji = 1, 4
778            CALL prism_def_var (recv_id(ji), cpl_recv(ji), grid_id(1), &
779                 upoint_id(1), umask_id(1), nodim, shape, data_type, ierror)
780            IF ( ierror /= PRISM_Success ) THEN
781               PRINT *, 'Failed to define transient ', ji, TRIM(cpl_recv(ji))
782               CALL prism_abort ( comp_id, 'OPA9.0', 'cpl_prism_define: Failure in prism_def_var')
783            ENDIF
784         ENDDO
785         !
786         ! ... b) on V points
787         !
788         DO ji = 5, 8 
789            CALL prism_def_var (recv_id(ji), cpl_recv(ji), grid_id(1), &
790                 vpoint_id(1), vmask_id(1), nodim, shape, data_type, ierror)
791            IF ( ierror /= PRISM_Success ) THEN
792               PRINT *, 'Failed to define transient ', TRIM(cpl_recv(ji))
793               CALL prism_abort ( comp_id, 'OPA9.0', 'cpl_prism_define: Failure in prism_def_var')
794            ENDIF
795         ENDDO
796         !
797         ! ... c) on T points
798         !
799         DO ji = 9, nrecv
800            CALL prism_def_var (recv_id(ji), "SORUNOFF", grid_id(1), &
801                 tpoint_id(1), tmask_id(1), nodim, shape, data_type, ierror)
802            IF ( ierror /= PRISM_Success ) THEN
803               PRINT *, 'Failed to define transient ', TRIM(cpl_recv(ji))
804               CALL prism_abort ( comp_id, 'OPA9.0', 'OPA cpl_prism_define: Failure in prism_def_var')
805            ENDIF
806         ENDDO
807
808      ENDIF ! commRank
809
810      !------------------------------------------------------------------
811      ! 4th End of definition phase
812      !------------------------------------------------------------------
813
814      IF(lwp) WRITE(numout,*) "ABOUT TO CALL PRISM_ENDDEF" 
815
816      CALL prism_enddef(ierror)
817
818      IF(lwp) WRITE(numout,*) "DONE ENDDEF",ierror
819
820      IF ( ierror /= PRISM_Success ) &
821         CALL prism_abort ( comp_id, 'OPA9.0', 'cpl_prism_define: Failure in prism_enddef')
822       
823      IF(lwp) WRITE(numout,*) "ALL DONE, EXITING PRISM SET UP PHASE"
824 
825   END SUBROUTINE cpl_prism_define
826
827
828
829   SUBROUTINE cpl_prism_send( var_id, date, data_array, info )
830
831      IMPLICIT NONE
832
833      !!---------------------------------------------------------------------
834      !!              ***  ROUTINE cpl_prism_send  ***
835      !!
836      !! ** Purpose : - At each coupling time-step,this routine sends fields
837      !!      like sst or ice cover to the coupler or remote application.
838      !!
839      !! ** Method  : OASIS4
840      !!----------------------------------------------------------------------
841      !! * Arguments
842      !!
843      INTEGER, INTENT( IN )  :: var_id    ! variable Id
844      INTEGER, INTENT( OUT ) :: info      ! variable Id
845      INTEGER, INTENT( IN )  :: date      ! ocean time-step in seconds
846      REAL(wp)               :: data_array(:,:)
847      !!
848      !! * Local declarations
849      !!
850#if defined key_mpp_mpi
851      REAL(wp)               :: global_array(jpiglo,jpjglo)
852      !
853!mpi  INTEGER                :: status(MPI_STATUS_SIZE)
854!mpi  INTEGER                :: type       ! MPI data type
855      INTEGER                :: request    ! MPI isend request
856      INTEGER                :: ji, jj, jn ! local loop indicees
857#else
858      INTEGER                :: ji
859#endif
860      !!
861      INTEGER, SAVE          :: ncount = 0
862      !!
863      !!--------------------------------------------------------------------
864      !!
865      ncount = ncount + 1
866
867#if defined key_mpp_mpi
868
869      request = 0
870
871      IF ( rootexchg ) THEN
872         !
873!mpi     IF ( wp == 4 ) type = MPI_REAL
874!mpi     IF ( wp == 8 ) type = MPI_DOUBLE_PRECISION
875         !
876         ! collect data on the local root process
877         !
878         IF ( localRank /= localRoot ) THEN
879
880            DO jj = nldj, nlej
881               DO ji = nldi, nlei
882                  exfld(ji-nldi+1,jj-nldj+1)=data_array(ji,jj)
883               ENDDO
884            ENDDO
885
886!mpi        CALL mpi_send(exfld, range(5), type, localRoot, localRank, localComm, ierror)
887            CALL mppsend (localRank, exfld, range(5), localRoot, request)
888         ENDIF
889
890         IF ( localRank == localRoot ) THEN
891
892            DO jj = ranges(3,localRoot), ranges(3,localRoot)+ranges(4,localRoot)-1
893               DO ji = ranges(1,localRoot), ranges(1,localRoot)+ranges(2,localRoot)-1
894                  global_array(ji,jj) = data_array(ji,jj) ! workaround
895               ENDDO
896            ENDDO
897
898            DO jn = 1, localSize-1
899
900!mpi           CALL mpi_recv(buffer, ranges(5,jn), type, localRoot, jn, localComm, status, ierror)
901               CALL mpprecv(jn, buffer, ranges(5,jn))
902
903               DO jj = ranges(3,jn), ranges(3,jn)+ranges(4,jn)-1
904                  DO ji = ranges(1,jn), ranges(1,jn)+ranges(2,jn)-1
905                     global_array(ji,jj) = buffer( (jj-ranges(3,jn))*ranges(2,jn) + ji-ranges(1,jn)+1 )
906                  ENDDO
907               ENDDO
908
909            ENDDO
910
911         ENDIF
912         !
913         ! send data from local root to OASIS4
914         !
915         CALL prism_put ( var_id, dates, dates_bound, global_array, info, ierror )     
916
917      ELSE
918         !
919         ! send local data from every process to OASIS4
920         !
921         CALL prism_put ( var_id, dates, dates_bound, data_array, info, ierror )     
922
923      ENDIF !rootexchg
924
925#else
926
927      !
928      ! send local data from every process to OASIS4
929      !
930      IF ( commRank ) &
931      CALL prism_put ( var_id, dates, dates_bound, data_array, info, ierror )     
932
933#endif
934
935      IF ( commRank ) THEN
936
937         IF (l_ctl) THEN
938
939            IF ( info==PRISM_Cpl ) THEN
940               WRITE(numout,*) '****************'
941               DO ji = 1, nsend
942                  IF (var_id == send_id(ji) ) THEN
943                     WRITE(numout,*) 'prism_put_proto: Outgoing ', cpl_send(ji)
944                     EXIT
945                  ENDIF
946               ENDDO
947               WRITE(numout,*) 'prism_put: var_id       ', var_id
948               WRITE(numout,*) 'prism_put:   date       ', date
949               WRITE(numout,*) 'prism_put:   info       ', info
950               WRITE(numout,*) '     - Minimum value is ', MINVAL(data_array)
951               WRITE(numout,*) '     - Maximum value is ', MAXVAL(data_array)
952               WRITE(numout,*) '     -     Sum value is ', SUM(data_array)
953               WRITE(numout,*) '****************'
954            ENDIF
955
956         ENDIF
957
958         IF ( ncount == nrecv ) THEN
959            !
960            !  3. Update dates and dates_bound for next step. We assume that cpl_prism_send
961            !  is called for all send fields at each time step. Therefore we update
962            !  the date argument to prism_put only every nsend call to cpl_prism_send.
963            !
964            dates_bound(1) = dates_bound(2)
965
966            tmpdate    = dates_bound(2)
967            date_incr  = rdCplttra(1)/2.0
968
969            CALL PRISM_calc_newdate ( tmpdate, date_incr, ierror )
970            dates = tmpdate
971            CALL PRISM_calc_newdate ( tmpdate, date_incr, ierror )
972            dates_bound(2) = tmpdate
973
974            ncount = 0
975
976         ENDIF
977
978      ENDIF ! commRank
979
980   END SUBROUTINE cpl_prism_send
981
982
983
984   SUBROUTINE cpl_prism_recv(  var_id, date, data_array, info )
985
986      IMPLICIT NONE
987
988      !!---------------------------------------------------------------------
989      !!              ***  ROUTINE cpl_prism_recv  ***
990      !!
991      !! ** Purpose : - At each coupling time-step,this routine receives fields
992      !!      like stresses and fluxes from the coupler or remote application.
993      !!
994      !! ** Method  : OASIS4
995      !!----------------------------------------------------------------------
996      !! * Arguments
997      !!
998      INTEGER, INTENT( IN )  :: var_id    ! variable Id
999      INTEGER, INTENT( OUT ) :: info      ! variable Id
1000      INTEGER, INTENT( IN )  :: date      ! ocean time-step in seconds
1001      REAL(wp),INTENT( OUT ) :: data_array(:,:)
1002      !!
1003      !! * Local declarations
1004      !!
1005#if defined key_mpp_mpi
1006      REAL(wp)               :: global_array(jpiglo,jpjglo)
1007      !
1008      LOGICAL                :: action = .false.
1009!mpi  INTEGER                :: status(MPI_STATUS_SIZE)
1010!mpi  INTEGER                :: type       ! MPI data type
1011      INTEGER                :: request    ! MPI isend request
1012      INTEGER                :: ji, jj, jn ! local loop indicees
1013#else
1014      INTEGER                :: ji
1015#endif
1016
1017      INTEGER, SAVE          :: ncount = 0
1018      !!
1019      !!--------------------------------------------------------------------
1020      !!
1021      ncount  = ncount + 1
1022
1023#ifdef key_mpp_mpi
1024
1025      request = 0
1026
1027      IF ( rootexchg ) THEN
1028         !
1029         ! receive data from OASIS4 on local root
1030         !
1031         IF ( commRank ) &
1032         CALL prism_get (var_id, dater, dater_bound, global_array, info, ierror)
1033         CALL MPI_BCAST ( info, 1, MPI_INTEGER, localRoot, localComm, ierror )
1034
1035      ELSE
1036         !
1037         ! receive local data from OASIS4 on every process
1038         !
1039         CALL prism_get (var_id, dater, dater_bound, exfld, info, ierror)
1040
1041      ENDIF
1042
1043      action = (info==PRISM_CplIO)
1044
1045      IF ( rootexchg .and. action ) THEN
1046         !
1047!mpi     IF ( wp == 4 ) type = MPI_REAL
1048!mpi     IF ( wp == 8 ) type = MPI_DOUBLE_PRECISION
1049         !
1050         ! distribute data to processes
1051         !
1052         IF ( localRank == localRoot ) THEN
1053
1054            DO jj = ranges(3,localRoot), ranges(3,localRoot)+ranges(4,localRoot)-1
1055               DO ji = ranges(1,localRoot), ranges(1,localRoot)+ranges(2,localRoot)-1
1056                  exfld(ji,jj) = global_array(ji,jj)
1057               ENDDO
1058            ENDDO
1059
1060            DO jn = 1, localSize-1
1061
1062               DO jj = ranges(3,jn), ranges(3,jn)+ranges(4,jn)-1
1063                  DO ji = ranges(1,jn), ranges(1,jn)+ranges(2,jn)-1
1064                     buffer( (jj-ranges(3,jn))*ranges(2,jn) + ji-ranges(1,jn)+1 ) = global_array(ji,jj)
1065                  ENDDO
1066               ENDDO
1067
1068!mpi           CALL mpi_send(buffer, ranges(5,jn), type, jn, jn, localComm, ierror)
1069               CALL mppsend (jn, buffer, ranges(5,jn), jn, request) 
1070
1071            ENDDO
1072
1073         ENDIF
1074
1075         IF ( localRank /= localRoot ) &
1076!mpi         CALL mpi_recv(exfld, range(5), type, localRoot, localRank, localComm, status, ierror)
1077             CALL mpprecv(localRank, exfld, range(5))
1078      ENDIF
1079
1080      IF ( action ) THEN
1081
1082         data_array = 0.0
1083
1084         DO jj = nldj, nlej
1085            DO ji = nldi, nlei
1086               data_array(ji,jj)=exfld(ji-nldi+1,jj-nldj+1)
1087            ENDDO
1088         ENDDO
1089
1090         IF (l_ctl) THEN       
1091            WRITE(numout,*) '****************'
1092            DO ji = 1, nrecv
1093               IF (var_id == recv_id(ji) ) THEN
1094                  WRITE(numout,*) 'prism_get: Incoming ', cpl_recv(ji)
1095                  EXIT
1096               ENDIF
1097            ENDDO
1098            WRITE(numout,*) 'prism_get: var_id       ', var_id
1099            WRITE(numout,*) 'prism_get:   date       ', date
1100            WRITE(numout,*) 'prism_get:   info       ', info
1101            WRITE(numout,*) '     - Minimum value is ', MINVAL(data_array)
1102            WRITE(numout,*) '     - Maximum value is ', MAXVAL(data_array)
1103            WRITE(numout,*) '     -     Sum value is ', SUM(data_array)
1104            WRITE(numout,*) '****************'
1105         ENDIF
1106
1107      ENDIF
1108#else
1109
1110      CALL prism_get (var_id, dater, dater_bound, exfld, info, ierror)
1111
1112      IF ( info==PRISM_CplIO ) THEN
1113               data_array=exfld
1114
1115         IF (l_ctl) THEN       
1116            WRITE(numout,*) '****************'
1117            DO ji = 1, nrecv
1118               IF (var_id == recv_id(ji) ) THEN
1119                  WRITE(numout,*) 'prism_get: Incoming ', cpl_recv(ji)
1120                  EXIT
1121               ENDIF
1122            ENDDO
1123            WRITE(numout,*) 'prism_get: var_id       ', var_id
1124            WRITE(numout,*) 'prism_get:   date       ', date
1125            WRITE(numout,*) 'prism_get:   info       ', info
1126            WRITE(numout,*) '     - Minimum value is ', MINVAL(data_array)
1127            WRITE(numout,*) '     - Maximum value is ', MAXVAL(data_array)
1128            WRITE(numout,*) '     -     Sum value is ', SUM(data_array)
1129            WRITE(numout,*) '****************'
1130         ENDIF
1131
1132      ENDIF
1133
1134#endif
1135
1136      IF ( ncount == nrecv ) THEN
1137         !
1138         !  3. Update dater and dater_bound for next step. We assume that cpl_prism_recv
1139         !  is called for all recv fields at each time step. Therefore we update
1140         !  the date argument to prism_get only every nrecv call to cpl_prism_recv.
1141         !
1142         dater_bound(1) = dater_bound(2)
1143
1144         tmpdate    = dater_bound(2)
1145         date_incr  = rdttra(1)/2.0
1146
1147         CALL PRISM_calc_newdate ( tmpdate, date_incr, ierror )
1148         dater = tmpdate
1149         CALL PRISM_calc_newdate ( tmpdate, date_incr, ierror )
1150         dater_bound(2) = tmpdate
1151
1152         ncount = 0
1153
1154      ENDIF
1155
1156   END SUBROUTINE cpl_prism_recv
1157
1158
1159
1160   SUBROUTINE cpl_prism_finalize
1161
1162      IMPLICIT NONE
1163
1164      !!---------------------------------------------------------------------
1165      !!              ***  ROUTINE cpl_prism_finalize  ***
1166      !!
1167      !! ** Purpose : - Finalizes the coupling. If MPI_init has not been
1168      !!      called explicitly before cpl_prism_init it will also close
1169      !!      MPI communication.
1170      !!
1171      !! ** Method  : OASIS4
1172      !!----------------------------------------------------------------------
1173
1174      DEALLOCATE(exfld)
1175
1176      if ( prism_was_initialized ) then
1177
1178         call prism_terminated ( prism_was_terminated, ierror )
1179         
1180         if ( prism_was_terminated ) then
1181            print *, 'prism has already been terminated.'
1182         else
1183            call prism_terminate ( ierror )
1184            prism_was_terminated = .true.
1185         endif
1186
1187      else
1188
1189         print *, 'Initialize prism before terminating it.'
1190
1191      endif
1192
1193
1194   END SUBROUTINE cpl_prism_finalize
1195
1196#else
1197
1198   !!----------------------------------------------------------------------
1199   !!   Default case           Dummy module         forced Ocean/Atmosphere
1200   !!----------------------------------------------------------------------
1201CONTAINS
1202   SUBROUTINE cpl_prism_init             ! Dummy routine
1203   END SUBROUTINE cpl_prism_init
1204   SUBROUTINE cpl_prism_define           ! Dummy routine
1205   END SUBROUTINE cpl_prism_define
1206   SUBROUTINE cpl_prism_send             ! Dummy routine
1207   END SUBROUTINE cpl_prism_send
1208   SUBROUTINE cpl_prism_recv             ! Dummy routine
1209   END SUBROUTINE cpl_prism_recv
1210   SUBROUTINE cpl_prism_finalize         ! Dummy routine
1211   END SUBROUTINE cpl_prism_finalize
1212
1213#endif
1214
1215END MODULE cpl_oasis4
Note: See TracBrowser for help on using the repository browser.