source: LMDZ6/trunk/libf/phylmd/oasis.F90 @ 5687

Last change on this file since 5687 was 5687, checked in by acozic, 5 weeks ago

Add new flag to coupled N deposition between atm and ocean
coupling initialized in lmdz but send is in inca code
can be use only with inca chemistry

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 23.0 KB
Line 
1!
2MODULE oasis
3!
4! This module contains subroutines for initialization, sending and receiving
5! towards the coupler OASIS3. It also contains some parameters for the coupling.
6!
7! This module should always be compiled. With the coupler OASIS3 available the cpp key
8! CPP_COUPLE should be set and the entier of this file will then be compiled.
9! In a forced mode CPP_COUPLE should not be defined and the compilation ends before
10! the CONTAINS, without compiling the subroutines.
11!
12  USE dimphy
13  USE mod_phys_lmdz_para
14  USE write_field_phy
15
16#ifdef CPP_COUPLE
17! Use of Oasis-MCT coupler
18#if defined CPP_OMCT
19  USE mod_prism
20! Use of Oasis3 coupler
21#else
22  USE mod_prism_proto
23  USE mod_prism_def_partition_proto
24  USE mod_prism_get_proto
25  USE mod_prism_put_proto
26#endif
27#endif
28 
29  IMPLICIT NONE
30 
31  ! Id for fields sent to ocean
32  INTEGER, PARAMETER :: ids_tauxxu = 1
33  INTEGER, PARAMETER :: ids_tauyyu = 2
34  INTEGER, PARAMETER :: ids_tauzzu = 3
35  INTEGER, PARAMETER :: ids_tauxxv = 4
36  INTEGER, PARAMETER :: ids_tauyyv = 5
37  INTEGER, PARAMETER :: ids_tauzzv = 6
38  INTEGER, PARAMETER :: ids_windsp = 7
39  INTEGER, PARAMETER :: ids_shfice = 8
40  INTEGER, PARAMETER :: ids_shfoce = 9
41  INTEGER, PARAMETER :: ids_shftot = 10
42  INTEGER, PARAMETER :: ids_nsfice = 11
43  INTEGER, PARAMETER :: ids_nsfoce = 12
44  INTEGER, PARAMETER :: ids_nsftot = 13
45  INTEGER, PARAMETER :: ids_dflxdt = 14
46  INTEGER, PARAMETER :: ids_totrai = 15
47  INTEGER, PARAMETER :: ids_totsno = 16
48  INTEGER, PARAMETER :: ids_toteva = 17
49  INTEGER, PARAMETER :: ids_icevap = 18
50  INTEGER, PARAMETER :: ids_ocevap = 19
51  INTEGER, PARAMETER :: ids_calvin = 20
52  INTEGER, PARAMETER :: ids_liqrun = 21
53  INTEGER, PARAMETER :: ids_runcoa = 22
54  INTEGER, PARAMETER :: ids_rivflu = 23
55  INTEGER, PARAMETER :: ids_atmco2 = 24
56  INTEGER, PARAMETER :: ids_taumod = 25
57  INTEGER, PARAMETER :: ids_qraioc = 26
58  INTEGER, PARAMETER :: ids_qsnooc = 27
59  INTEGER, PARAMETER :: ids_qraiic = 28
60  INTEGER, PARAMETER :: ids_qsnoic = 29
61  INTEGER, PARAMETER :: ids_delta_sst = 30, ids_delta_sal = 31, ids_dter = 32, &
62       ids_dser = 33, ids_dt_ds = 34
63  INTEGER, PARAMETER :: ids_atmn2o = 35
64  INTEGER, PARAMETER :: ids_atmndp = 36
65 
66  INTEGER, PARAMETER :: maxsend    = 36  ! Maximum number of fields to send
67  INTEGER, PARAMETER :: maxsend_phys = 34 ! Maximum number of fields to send in LMDZ phys - the last one will be send by Inca
68
69  ! Id for fields received from ocean
70
71  INTEGER, PARAMETER :: idr_sisutw = 1
72  INTEGER, PARAMETER :: idr_icecov = 2
73  INTEGER, PARAMETER :: idr_icealw = 3
74  INTEGER, PARAMETER :: idr_icetem = 4
75  INTEGER, PARAMETER :: idr_curenx = 5
76  INTEGER, PARAMETER :: idr_cureny = 6
77  INTEGER, PARAMETER :: idr_curenz = 7
78  INTEGER, PARAMETER :: idr_oceco2 = 8
79  ! bulk salinity of the surface layer of the ocean, in ppt
80  INTEGER, PARAMETER :: idr_sss = 9
81  INTEGER, PARAMETER :: idr_ocedms = 10
82  INTEGER, PARAMETER :: idr_ocen2o = 11
83
84  INTEGER, PARAMETER :: maxrecv      = 11     ! Maximum number of fields to receive
85  INTEGER, PARAMETER :: maxrecv_phys = 9      ! Maximum number of fields to receive in physiq (without fields received in INCA model )
86                                              ! will be changed in next version - INCA fields will be received in LMDZ (like for ORCHIDEE fields)
87                                              ! and then send by routine in INCA model
88 
89
90  TYPE, PUBLIC ::   FLD_CPL            ! Type for coupling field information
91     CHARACTER(len = 8) ::   name      ! Name of the coupling field   
92     LOGICAL            ::   action    ! To be exchanged or not
93     INTEGER            ::   nid       ! Id of the field
94  END TYPE FLD_CPL
95
96  TYPE(FLD_CPL), DIMENSION(maxsend), SAVE, PUBLIC :: infosend   ! Information for sending coupling fields
97!$OMP THREADPRIVATE(infosend)
98  TYPE(FLD_CPL), DIMENSION(maxrecv), SAVE, PUBLIC :: inforecv   ! Information for receiving coupling fields
99!$OMP THREADPRIVATE(inforecv)
100 
101  LOGICAL,SAVE :: cpl_current
102!$OMP THREADPRIVATE(cpl_current)
103
104#ifdef CPP_COUPLE
105
106CONTAINS
107
108  SUBROUTINE inicma
109!************************************************************************************
110!**** *INICMA*  - Initialize coupled mode communication for atmosphere
111!                 and exchange some initial information with Oasis
112!
113!     Rewrite to take the PRISM/psmile library into account
114!     LF 09/2003
115!
116    USE IOIPSL
117    USE surface_data, ONLY : version_ocean
118    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl
119    use wxios_mod, ONLY : wxios_context_init
120    USE chemistry_cycle_mod, ONLY : dms_cycle_cpl, n2o_cycle_cpl, ndp_cycle_cpl
121    USE lmdz_xios 
122    USE print_control_mod, ONLY: lunout
123    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, grid_type, unstructured, regular_lonlat
124    USE geometry_mod, ONLY: ind_cell_glo                   
125    USE mod_phys_lmdz_mpi_data, ONLY: klon_mpi_para_nb
126    use config_ocean_skin_m, only: activate_ocean_skin
127    USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_INCA
128
129! Local variables
130!************************************************************************************
131    INTEGER                            :: comp_id
132    INTEGER                            :: ierror, il_commlocal
133    INTEGER                            :: il_part_id
134    INTEGER, ALLOCATABLE               :: ig_paral(:)
135    INTEGER, DIMENSION(2)              :: il_var_nodims
136    INTEGER, DIMENSION(4)              :: il_var_actual_shape
137    INTEGER                            :: il_var_type
138    INTEGER                            :: jf
139    CHARACTER (len = 6)                :: clmodnam
140    CHARACTER (len = 20)               :: modname = 'inicma'
141    CHARACTER (len = 80)               :: abort_message
142    !! WARNING: cpl_current_omp should NOT be put in a THREADPRIVATE statement, it is shared between tasks
143    LOGICAL, SAVE                      :: cpl_current_omp
144    INTEGER, DIMENSION(klon_mpi)       :: ind_cell_glo_mpi
145
146
147!*    1. Initializations
148!        ---------------
149!************************************************************************************
150    WRITE(lunout,*) ' '
151    WRITE(lunout,*) ' '
152    WRITE(lunout,*) ' ROUTINE INICMA'
153    WRITE(lunout,*) ' **************'
154    WRITE(lunout,*) ' '
155    WRITE(lunout,*) ' '
156
157!
158! Define the model name
159!
160    IF (grid_type==unstructured) THEN
161        clmodnam = 'icosa'                 ! as in $NBMODEL in Cpl/Nam/namcouple.tmp
162    ELSE IF (grid_type==regular_lonlat) THEN
163        clmodnam = 'LMDZ'                  ! as in $NBMODEL in Cpl/Nam/namcouple.tmp
164    ELSE
165        abort_message='Pb : type of grid unknown'
166        CALL abort_physic(modname,abort_message,1)
167    ENDIF
168
169
170!************************************************************************************
171! Define if coupling ocean currents or not
172!************************************************************************************
173!$OMP MASTER
174    cpl_current_omp = .FALSE.
175    CALL getin('cpl_current', cpl_current_omp)
176!$OMP END MASTER
177!$OMP BARRIER
178    cpl_current = cpl_current_omp
179    WRITE(lunout,*) 'Couple ocean currents, cpl_current = ',cpl_current
180
181!************************************************************************************
182! Gather global index to be used for oasis decomposition
183!************************************************************************************
184    CALL gather_omp(ind_cell_glo,ind_cell_glo_mpi)
185
186!************************************************************************************
187! Define coupling variables
188!************************************************************************************
189
190! Atmospheric variables to send
191
192!$OMP MASTER
193    infosend(:)%action = .FALSE.
194
195    infosend(ids_tauxxu)%action = .TRUE. ; infosend(ids_tauxxu)%name = 'COTAUXXU'
196    infosend(ids_tauyyu)%action = .TRUE. ; infosend(ids_tauyyu)%name = 'COTAUYYU'
197    infosend(ids_tauzzu)%action = .TRUE. ; infosend(ids_tauzzu)%name = 'COTAUZZU'
198    infosend(ids_tauxxv)%action = .TRUE. ; infosend(ids_tauxxv)%name = 'COTAUXXV'
199    infosend(ids_tauyyv)%action = .TRUE. ; infosend(ids_tauyyv)%name = 'COTAUYYV'
200    infosend(ids_tauzzv)%action = .TRUE. ; infosend(ids_tauzzv)%name = 'COTAUZZV'
201    infosend(ids_windsp)%action = .TRUE. ; infosend(ids_windsp)%name = 'COWINDSP'
202    infosend(ids_shfice)%action = .TRUE. ; infosend(ids_shfice)%name = 'COSHFICE'
203    infosend(ids_nsfice)%action = .TRUE. ; infosend(ids_nsfice)%name = 'CONSFICE'
204    infosend(ids_dflxdt)%action = .TRUE. ; infosend(ids_dflxdt)%name = 'CODFLXDT'
205    infosend(ids_calvin)%action = .TRUE. ; infosend(ids_calvin)%name = 'COCALVIN'
206   
207    if (activate_ocean_skin == 2) then
208       infosend(ids_delta_sst)%action = .TRUE.
209       infosend(ids_delta_sst)%name = 'CODELSST'
210       infosend(ids_delta_sal)%action = .TRUE.
211       infosend(ids_delta_sal)%name = 'CODELSSS'
212       infosend(ids_dter)%action = .TRUE.
213       infosend(ids_dter)%name = 'CODELTER'
214       infosend(ids_dser)%action = .TRUE.
215       infosend(ids_dser)%name = 'CODELSER'
216       infosend(ids_dt_ds)%action = .TRUE.
217       infosend(ids_dt_ds)%name = 'CODTDS'
218    end if
219           
220    IF (version_ocean=='nemo') THEN
221        infosend(ids_shftot)%action = .TRUE. ; infosend(ids_shftot)%name = 'COQSRMIX'
222        infosend(ids_nsftot)%action = .TRUE. ; infosend(ids_nsftot)%name = 'COQNSMIX'
223        infosend(ids_totrai)%action = .TRUE. ; infosend(ids_totrai)%name = 'COTOTRAI'
224        infosend(ids_totsno)%action = .TRUE. ; infosend(ids_totsno)%name = 'COTOTSNO'
225        infosend(ids_toteva)%action = .TRUE. ; infosend(ids_toteva)%name = 'COTOTEVA'
226        infosend(ids_icevap)%action = .TRUE. ; infosend(ids_icevap)%name = 'COICEVAP'
227        infosend(ids_liqrun)%action = .TRUE. ; infosend(ids_liqrun)%name = 'COLIQRUN'
228        infosend(ids_taumod)%action = .TRUE. ; infosend(ids_taumod)%name = 'COTAUMOD'
229        IF (carbon_cycle_cpl) THEN
230            infosend(ids_atmco2)%action = .TRUE. ; infosend(ids_atmco2)%name = 'COATMCO2'
231        ENDIF
232        IF (n2o_cycle_cpl) THEN
233            infosend(ids_atmn2o)%action = .TRUE. ; infosend(ids_atmn2o)%name = 'COATMN2O'
234        ENDIF
235        IF (ndp_cycle_cpl) THEN
236            infosend(ids_atmndp)%action = .TRUE. ; infosend(ids_atmndp)%name = 'COATMNDP'
237        ENDIF
238        infosend(ids_qraioc)%action = .TRUE. ; infosend(ids_qraioc)%name = 'COQRAIOC'
239        infosend(ids_qsnooc)%action = .TRUE. ; infosend(ids_qsnooc)%name = 'COQSNOOC'
240        infosend(ids_qraiic)%action = .TRUE. ; infosend(ids_qraiic)%name = 'COQRAIIC'
241        infosend(ids_qsnoic)%action = .TRUE. ; infosend(ids_qsnoic)%name = 'COQSNOIC'
242       
243    ELSE IF (version_ocean=='opa8') THEN
244        infosend(ids_shfoce)%action = .TRUE. ; infosend(ids_shfoce)%name = 'COSHFOCE'
245        infosend(ids_nsfoce)%action = .TRUE. ; infosend(ids_nsfoce)%name = 'CONSFOCE'
246        infosend(ids_icevap)%action = .TRUE. ; infosend(ids_icevap)%name = 'COTFSICE'
247        infosend(ids_ocevap)%action = .TRUE. ; infosend(ids_ocevap)%name = 'COTFSOCE'
248        infosend(ids_totrai)%action = .TRUE. ; infosend(ids_totrai)%name = 'COTOLPSU'
249        infosend(ids_totsno)%action = .TRUE. ; infosend(ids_totsno)%name = 'COTOSPSU'
250        infosend(ids_runcoa)%action = .TRUE. ; infosend(ids_runcoa)%name = 'CORUNCOA'
251        infosend(ids_rivflu)%action = .TRUE. ; infosend(ids_rivflu)%name = 'CORIVFLU'
252   ENDIF
253       
254! Oceanic variables to receive
255
256   inforecv(:)%action = .FALSE.
257
258   inforecv(idr_sisutw)%action = .TRUE. ; inforecv(idr_sisutw)%name = 'SISUTESW'
259   inforecv(idr_icecov)%action = .TRUE. ; inforecv(idr_icecov)%name = 'SIICECOV'
260   inforecv(idr_icealw)%action = .TRUE. ; inforecv(idr_icealw)%name = 'SIICEALW'
261   inforecv(idr_icetem)%action = .TRUE. ; inforecv(idr_icetem)%name = 'SIICTEMW'
262
263   if (activate_ocean_skin >= 1) then
264      inforecv(idr_sss)%action = .TRUE.
265      inforecv(idr_sss)%name = 'SISUSALW'
266   end if
267   
268   IF (cpl_current ) THEN
269       inforecv(idr_curenx)%action = .TRUE. ; inforecv(idr_curenx)%name = 'CURRENTX'
270       inforecv(idr_cureny)%action = .TRUE. ; inforecv(idr_cureny)%name = 'CURRENTY'
271       inforecv(idr_curenz)%action = .TRUE. ; inforecv(idr_curenz)%name = 'CURRENTZ'
272   ENDIF
273
274   IF (carbon_cycle_cpl ) THEN
275       inforecv(idr_oceco2)%action = .TRUE. ; inforecv(idr_oceco2)%name = 'SICO2FLX'
276   ENDIF
277   IF (dms_cycle_cpl) THEN
278      inforecv(idr_ocedms)%action = .TRUE. ; inforecv(idr_ocedms)%name = 'SIDMSFLX'
279   ENDIF
280   IF (n2o_cycle_cpl) THEN
281      inforecv(idr_ocen2o)%action = .TRUE. ; inforecv(idr_ocen2o)%name = 'SIN2OFLX'
282   ENDIF
283 
284
285!************************************************************************************
286! Here we go: psmile initialisation
287!************************************************************************************
288    IF (is_sequential) THEN
289       CALL prism_init_comp_proto (comp_id, clmodnam, ierror)
290       
291       IF (ierror .NE. PRISM_Ok) THEN
292          abort_message=' Probleme init dans prism_init_comp '
293          CALL abort_physic(modname,abort_message,1)
294       ELSE
295          WRITE(lunout,*) 'inicma : init psmile ok '
296       ENDIF
297    ENDIF
298
299    CALL prism_get_localcomm_proto (il_commlocal, ierror)
300!************************************************************************************
301! Domain decomposition
302!************************************************************************************
303    IF (grid_type==unstructured) THEN
304
305      ALLOCATE( ig_paral(klon_mpi_para_nb(mpi_rank) + 2) )
306
307      ig_paral(1) = 4                                      ! points partition for //
308      ig_paral(2) = klon_mpi_para_nb(mpi_rank)             ! nb of local cells
309
310      DO jf=1, klon_mpi_para_nb(mpi_rank)
311        ig_paral(2+jf) = ind_cell_glo_mpi(jf)
312      ENDDO
313
314    ELSE IF (grid_type==regular_lonlat) THEN
315
316      ALLOCATE( ig_paral(3) )
317
318      ig_paral(1) = 1                            ! apple partition for //
319      ig_paral(2) = (jj_begin-1)*nbp_lon+ii_begin-1  ! offset
320      ig_paral(3) = (jj_end*nbp_lon+ii_end) - (jj_begin*nbp_lon+ii_begin) + 1
321
322      IF (mpi_rank==mpi_size-1) ig_paral(3)=ig_paral(3)+nbp_lon-1
323    ELSE
324      abort_message='Pb : type of grid unknown'
325      CALL abort_physic(modname,abort_message,1)
326    ENDIF
327
328
329    WRITE(lunout,*) mpi_rank,'ig_paral--->',ig_paral(2),ig_paral(3)
330   
331    ierror=PRISM_Ok
332    CALL prism_def_partition_proto (il_part_id, ig_paral, ierror)
333
334    IF (ierror .NE. PRISM_Ok) THEN
335       abort_message=' Probleme dans prism_def_partition '
336       CALL abort_physic(modname,abort_message,1)
337    ELSE
338       WRITE(lunout,*) 'inicma : decomposition domaine psmile ok '
339    ENDIF
340
341    il_var_nodims(1) = 2                        ! rank of field array (1d or 2d)
342    il_var_nodims(2) = 1                        ! always 1 in current oasis version" doc oasis3mct p18
343
344    il_var_actual_shape(1) = 1                  ! min of 1st dimension (always 1)
345    il_var_actual_shape(2) = nbp_lon            ! max of 1st dimension
346    il_var_actual_shape(3) = 1                  ! min of 2nd dimension (always 1)
347    il_var_actual_shape(4) = nbp_lat            ! max of 2nd dimension
348   
349    il_var_type = PRISM_Real
350
351!************************************************************************************
352! Oceanic Fields to receive
353! Loop over all possible variables
354!************************************************************************************
355    DO jf=1, maxrecv
356       IF (inforecv(jf)%action) THEN
357          CALL prism_def_var_proto(inforecv(jf)%nid, inforecv(jf)%name, il_part_id, &
358               il_var_nodims, PRISM_In, il_var_actual_shape, il_var_type, &
359               ierror)
360          IF (ierror .NE. PRISM_Ok) THEN
361             WRITE(lunout,*) 'inicma : Problem with prism_def_var_proto for field : ',&
362                  inforecv(jf)%name
363             abort_message=' Problem in call to prism_def_var_proto for fields to receive'
364             CALL abort_physic(modname,abort_message,1)
365          ENDIF
366       ENDIF
367    END DO
368
369 
370!************************************************************************************
371! Atmospheric Fields to send
372! Loop over all possible variables
373!************************************************************************************
374    DO jf=1,maxsend
375       IF (infosend(jf)%action) THEN
376          CALL prism_def_var_proto(infosend(jf)%nid, infosend(jf)%name, il_part_id, &
377               il_var_nodims, PRISM_Out, il_var_actual_shape, il_var_type, &
378               ierror)
379          IF (ierror .NE. PRISM_Ok) THEN
380             WRITE(lunout,*) 'inicma : Problem with prism_def_var_proto for field : ',&
381                  infosend(jf)%name
382             abort_message=' Problem in call to prism_def_var_proto for fields to send'
383             CALL abort_physic(modname,abort_message,1)
384          ENDIF
385       ENDIF
386    END DO
387   
388!************************************************************************************
389! End definition
390!************************************************************************************
391
392    IF (using_xios) CALL xios_oasis_enddef()
393
394    CALL prism_enddef_proto(ierror)
395    IF (ierror .NE. PRISM_Ok) THEN
396       abort_message=' Problem in call to prism_endef_proto'
397       CALL abort_physic(modname,abort_message,1)
398    ELSE
399       WRITE(lunout,*) 'inicma : endef psmile ok '
400    ENDIF
401
402
403IF (CPPKEY_INCA) THEN
404    IF (dms_cycle_cpl .OR. n2o_cycle_cpl .OR. ndp_cycle_cpl) THEN
405       CALL init_inca_oasis(inforecv(idr_ocedms:idr_ocen2o),infosend(ids_atmn2o:ids_atmndp))
406    ENDIF
407END IF
408
409!$OMP END MASTER
410   
411  END SUBROUTINE inicma
412
413!
414!************************************************************************************
415!
416
417  SUBROUTINE fromcpl(ktime, tab_get)
418! ======================================================================
419! L. Fairhead (09/2003) adapted From L.Z.X Li: this subroutine reads the SST
420! and Sea-Ice provided by the coupler. Adaptation to psmile library
421!======================================================================
422!
423    USE print_control_mod, ONLY: lunout
424    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat
425! Input arguments
426!************************************************************************************
427    INTEGER, INTENT(IN)                               ::  ktime
428
429! Output arguments
430!************************************************************************************
431    REAL, DIMENSION(nbp_lon, jj_nb,maxrecv_phys), INTENT(OUT) :: tab_get
432
433! Local variables
434!************************************************************************************
435    INTEGER                       :: ierror, i
436    INTEGER                       :: istart,iend
437    CHARACTER (len = 20)          :: modname = 'fromcpl'
438    CHARACTER (len = 80)          :: abort_message
439    REAL, DIMENSION(nbp_lon*jj_nb)    :: field
440
441!************************************************************************************
442    WRITE (lunout,*) ' '
443    WRITE (lunout,*) 'Fromcpl: Reading fields from CPL, ktime=',ktime
444    WRITE (lunout,*) ' '
445   
446    istart=ii_begin
447    IF (is_south_pole_dyn) THEN
448       iend=(jj_end-jj_begin)*nbp_lon+nbp_lon
449    ELSE
450       iend=(jj_end-jj_begin)*nbp_lon+ii_end
451    ENDIF
452   
453    DO i = 1, maxrecv_phys
454      IF (inforecv(i)%action .AND. inforecv(i)%nid .NE. -1) THEN
455          field(:) = -99999.
456          CALL prism_get_proto(inforecv(i)%nid, ktime, field(istart:iend), ierror)
457          tab_get(:,:,i) = RESHAPE(field(:),(/nbp_lon,jj_nb/))
458       
459          IF (ierror .NE. PRISM_Ok .AND. ierror.NE.PRISM_Recvd .AND. &
460             ierror.NE.PRISM_FromRest &
461             .AND. ierror.NE.PRISM_Input .AND. ierror.NE.PRISM_RecvOut &
462             .AND. ierror.NE.PRISM_FromRestOut) THEN
463              WRITE (lunout,*)  'Error with receiving field: ', inforecv(i)%name, ktime   
464              abort_message=' Problem in prism_get_proto '
465              CALL abort_physic(modname,abort_message,1)
466          ENDIF
467      ENDIF
468    END DO
469   
470   
471  END SUBROUTINE fromcpl
472
473!
474!************************************************************************************
475!
476
477  SUBROUTINE intocpl(ktime, last, tab_put)
478! ======================================================================
479! L. Fairhead (09/2003) adapted From L.Z.X Li: this subroutine provides the
480! atmospheric coupling fields to the coupler with the psmile library.
481! IF last time step, writes output fields to binary files.
482! ======================================================================
483!
484!
485    USE print_control_mod, ONLY: lunout
486    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat
487! Input arguments
488!************************************************************************************
489    INTEGER, INTENT(IN)                              :: ktime
490    LOGICAL, INTENT(IN)                              :: last
491    REAL, DIMENSION(nbp_lon, jj_nb, maxsend_phys), INTENT(IN) :: tab_put
492
493! Local variables
494!************************************************************************************
495    LOGICAL                          :: checkout
496    INTEGER                          :: istart,iend
497    INTEGER                          :: wstart,wend
498    INTEGER                          :: ierror, i
499    REAL, DIMENSION(nbp_lon*jj_nb)       :: field
500    CHARACTER (len = 20),PARAMETER   :: modname = 'intocpl'
501    CHARACTER (len = 80)             :: abort_message
502
503!************************************************************************************
504    checkout=.FALSE.
505
506    WRITE(lunout,*) ' '
507    WRITE(lunout,*) 'Intocpl: sending fields to CPL, ktime= ', ktime
508    WRITE(lunout,*) 'last = ', last
509    WRITE(lunout,*)
510
511
512    istart=ii_begin
513    IF (is_south_pole_dyn) THEN
514       iend=(jj_end-jj_begin)*nbp_lon+nbp_lon
515    ELSE
516       iend=(jj_end-jj_begin)*nbp_lon+ii_end
517    ENDIF
518   
519    IF (checkout) THEN   
520       wstart=istart
521       wend=iend
522       IF (is_north_pole_dyn) wstart=istart+nbp_lon-1
523       IF (is_south_pole_dyn) wend=iend-nbp_lon+1
524       
525       DO i = 1, maxsend_phys
526          IF (infosend(i)%action) THEN
527             field = RESHAPE(tab_put(:,:,i),(/nbp_lon*jj_nb/))
528             CALL writefield_phy(infosend(i)%name,field(wstart:wend),1)
529          END IF
530       END DO
531    END IF
532
533!************************************************************************************
534! PRISM_PUT
535!************************************************************************************
536
537    DO i = 1, maxsend_phys
538      IF (infosend(i)%action .AND. infosend(i)%nid .NE. -1 ) THEN
539          field = RESHAPE(tab_put(:,:,i),(/nbp_lon*jj_nb/))
540          CALL prism_put_proto(infosend(i)%nid, ktime, field(istart:iend), ierror)
541         
542          IF (ierror .NE. PRISM_Ok .AND. ierror.NE.PRISM_Sent .AND. ierror.NE.PRISM_ToRest &
543             .AND. ierror.NE.PRISM_LocTrans .AND. ierror.NE.PRISM_Output .AND. &
544             ierror.NE.PRISM_SentOut .AND. ierror.NE.PRISM_ToRestOut) THEN
545              WRITE (lunout,*) 'Error with sending field :', infosend(i)%name, ktime   
546              abort_message=' Problem in prism_put_proto '
547              CALL abort_physic(modname,abort_message,1)
548          ENDIF
549      ENDIF
550    END DO
551   
552!************************************************************************************
553! Finalize PSMILE for the case is_sequential, if parallel finalization is done
554! from Finalize_parallel in dyn3dpar/parallel.F90
555!************************************************************************************
556
557    IF (last) THEN
558       IF (is_sequential) THEN
559          CALL prism_terminate_proto(ierror)
560          IF (ierror .NE. PRISM_Ok) THEN
561             abort_message=' Problem in prism_terminate_proto '
562             CALL abort_physic(modname,abort_message,1)
563          ENDIF
564       ENDIF
565    ENDIF
566   
567   
568  END SUBROUTINE intocpl
569
570#endif
571 
572END MODULE oasis
Note: See TracBrowser for help on using the repository browser.