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

source: trunk/NEMO/OPA_SRC/cpl_oce.F90 @ 143

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

CL + CT: BUGFIX088: Replace include clim.h and mpiclim.h by clim.h90 and mpiclim.h90

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 10.3 KB
Line 
1MODULE cpl_oce
2   !!======================================================================
3   !!                   ***  MODULE  cpl_oce  ***
4   !! Ocean coupling:  ocean-atmosphere-sea ice coupled exchanges
5   !!=====================================================================
6#if defined key_coupled
7   !!----------------------------------------------------------------------
8   !!   'key_coupled'                              Coupled Ocean/Atmosphere
9   !!----------------------------------------------------------------------
10   !! ** Purpose :   Atmosphere/Ice/Ocean Coupling
11   !!      GASTON TEAM (CERFACS, Meteo-France, LMD, LSCE, IPSL, LODYC)
12   !!
13   !! history :
14   !!  8.0   ! 08-98  (M.A. Foujols, M. Imbard)  Original code
15   !!  8.5   ! 06/02  (G. Madec)  modules
16   !!----------------------------------------------------------------------
17   !!   OPA 9.0 , LODYC-IPSL (2003)
18   !!----------------------------------------------------------------------
19   !! * Modules used
20   USE par_oce          ! ocean parameters
21
22   IMPLICIT NONE
23
24   !! ---------------------------------------------------------------------
25   !! Ocean/Ice/Atmosphere Coupling
26   !! -----------------------------
27   LOGICAL, PUBLIC, PARAMETER :: lk_cpl = .TRUE.   !: coupled flag
28
29   INTEGER, PARAMETER ::   &  !: 
30      jpmaxfld = 40           !: Number of maximum fields exchange betwwen
31      !                       ! the ocean and the coupler
32
33   !!---------------------------------------------------------------------
34   !! SIPC Method   (L. Terray, S. Valcke, CERFACS)
35   !! -----------
36
37   INTEGER, PARAMETER ::   &  !:
38      jpbyteint = 4,       &  !: number of bytes per integer
39      jpbyterea = 8,       &  !: number of bytes per real
40      jpbytecha = 1           !: number of bytes per character 
41
42   INTEGER, PARAMETER ::   &  !:
43      jptest = 100            !: The models will test during 2*jptest
44      !                       ! seconds if the file DUMMY_SIPC has been
45      !                       ! created by OASIS, signaling that the
46      !                       ! SHM pools are opened. After, it aborts.
47
48   !!---------------------------------------------------------------------
49   !! PIPE Method   (L. Terray, CERFACS)
50   !! -----------
51
52   INTEGER, PARAMETER ::   &  !:
53      jpread = 0,          &  !:
54      jpwrit = 1              !:
55
56   !!---------------------------------------------------------------------
57   !! Messag Passing Method (CLIM)
58   !! ----------------------------
59!!!INCLUDE '../../CPL/include/clim.h90'
60!!
61!! -- clim.h   18-08-95   Version 2.0   Author: Laurent Terray
62!!    ******
63!!             26-10-99   Version 2.4   Jean Latour (F.S.E.) MPI-2 support
64!!
65!!   clim.h90  13-08-04  Change to F90 C. Levy
66!!@
67!!@  Contents : variables related to the CLIM library
68!!@  --------
69!!@ For complete definition, see the CLIM manual
70!!@
71      INTEGER (kind=4)  CLIM_MaxMod,    CLIM_MaxPort,  CLIM_MaxSegments, &
72               CLIM_MaxTag, &
73               CLIM_MaxLink, &
74               CLIM_ParSize, & 
75               CLIM_Clength, &
76               CLIM_MaxCodes
77!!
78      INTEGER (kind=4) CLIM_Void
79!!
80      INTEGER (kind=4) CLIM_In,  CLIM_Out,   CLIM_InOut
81!!
82      INTEGER (kind=4) CLIM_Strategy,  CLIM_Segments,  &
83               CLIM_Serial,    CLIM_Length,    CLIM_Orange, &
84               CLIM_Apple,     CLIM_Offset, &
85               CLIM_Box,   CLIM_SizeX, CLIM_SizeY, &
86               CLIM_LdX
87!!
88      INTEGER  (kind=4)CLIM_Integer,   CLIM_Real,  CLIM_Double
89!!
90      INTEGER  (kind=4)CLIM_StopPvm,   CLIM_ContPvm
91!!
92      INTEGER (kind=4)  CLIM_Ok
93      INTEGER (kind=4) CLIM_FastExit,  CLIM_BadName,  CLIM_BadPort, &
94               CLIM_BadType,  CLIM_DoubleDef, CLIM_NotStep, &
95               CLIM_IncStep,  CLIM_IncSize,  CLIM_NotClim, &
96               CLIM_TimeOut, &
97               CLIM_Pvm,   CLIM_FirstCall, CLIM_PbRoute, &
98               CLIM_Group,    CLIM_BadTaskId, CLIM_NoTask, &
99               CLIM_InitBuff,    CLIM_Pack,  CLIM_Unpack, &
100               CLIM_Down,  CLIM_PvmExit
101!!
102      INTEGER (kind=4) CLIM_jpmax,  CLIM_jpmx8,    CLIM_Mpi
103!!
104!!-----Parameter sizes
105!!
106      PARAMETER ( CLIM_Void    = 0  )
107      PARAMETER ( CLIM_MaxMod  = 8 )
108      PARAMETER ( CLIM_MaxPort = 50 )
109      PARAMETER ( CLIM_MaxSegments = 50 )
110      PARAMETER ( CLIM_MaxLink = CLIM_MaxMod * CLIM_MaxPort )
111      PARAMETER ( CLIM_ParSize = 2*CLIM_MaxSegments+2 )
112      PARAMETER ( CLIM_MaxTag  = 16777215 )
113      PARAMETER ( CLIM_Clength = 32 )
114!!
115!!-----Dimension of buffer for packing / unpacking messages with MPI
116!!     (must be equal to jpmax of Oasis)
117!!
118      PARAMETER ( CLIM_jpmax = 400000 )
119      PARAMETER ( CLIM_jpmx8 = CLIM_jpmax*8 )
120!!
121!!-----Ports status
122!!
123      PARAMETER ( CLIM_In      = 1 )
124      PARAMETER ( CLIM_Out     = 0 )
125      PARAMETER ( CLIM_InOut   = 2 )
126!!
127!!-----Parallel distribution
128!!
129      PARAMETER ( CLIM_Strategy = 1 )
130      PARAMETER ( CLIM_Segments = 2 )
131      PARAMETER ( CLIM_Serial   = 0 )
132      PARAMETER ( CLIM_Apple    = 1 )
133      PARAMETER ( CLIM_Box      = 2 )
134      PARAMETER ( CLIM_Orange   = 3 )
135      PARAMETER ( CLIM_Offset   = 2 )
136      PARAMETER ( CLIM_Length   = 3 )
137      PARAMETER ( CLIM_SizeX    = 3 )
138      PARAMETER ( CLIM_SizeY    = 4 )
139      PARAMETER ( CLIM_LdX      = 5 )
140!!
141!!-----Datatypes
142!!
143      PARAMETER ( CLIM_Integer = 1 )
144      PARAMETER ( CLIM_Real    = 4 ) 
145      PARAMETER ( CLIM_Double  = 8 )
146!!
147!!-----Quit parameters
148!!
149      PARAMETER ( CLIM_ContPvm = 0 )
150      PARAMETER ( CLIM_StopPvm = 1 )
151!!
152!!-----Error Codes
153!!
154      PARAMETER ( CLIM_MaxCodes  = -22 )
155!!
156      PARAMETER ( CLIM_Ok   = 0 )
157      PARAMETER ( CLIM_FastExit  = -1 )
158      PARAMETER ( CLIM_BadName   = -2 )
159      PARAMETER ( CLIM_BadPort   = -3 )
160      PARAMETER ( CLIM_BadType   = -4 )
161      PARAMETER ( CLIM_DoubleDef = -5 )
162      PARAMETER ( CLIM_NotStep   = -6 )
163      PARAMETER ( CLIM_IncStep   = -7 )
164      PARAMETER ( CLIM_IncSize   = -8 )
165      PARAMETER ( CLIM_NotClim   = -9 )
166      PARAMETER ( CLIM_TimeOut   = -10 )
167      PARAMETER ( CLIM_Pvm       = -11 )
168      PARAMETER ( CLIM_FirstCall = -12 )
169      PARAMETER ( CLIM_PbRoute   = -13 )
170      PARAMETER   ( CLIM_Group     = -14 )
171      PARAMETER ( CLIM_BadTaskId = -15 )
172      PARAMETER ( CLIM_NoTask    = -16 )
173      PARAMETER ( CLIM_InitBuff  = -17 )
174      PARAMETER ( CLIM_Pack      = -18 )
175      PARAMETER ( CLIM_Unpack    = -19 )
176      PARAMETER ( CLIM_Down      = -20 )
177      PARAMETER ( CLIM_PvmExit   = -21 )
178      PARAMETER ( CLIM_Mpi       = -22 )
179
180!!
181!     --- end of clim.h90
182!!!END-----------------------------------------------------------------
183
184!!!INCLUDE '../../CPL/include/mpiclim.h90'
185!!
186!! -- mpiclim.h  26-10-99   Version 2.4   Author: Jean Latour (F.S.E.)
187!!    *********
188!!    mpiclim.h90 13-08-04 change to F90 C. Levy
189!!@
190!!@  Contents : variables related to MPI-2 message passing
191!!@  --------
192!!@
193!!@ -- mpi_totproc: number of processors on which to launch each model
194!!@
195!!@ -- mpi_nproc: number of processors involved in the coupling for
196!!@               each model
197!!@ -- cmpi_modnam: models name
198!!     -----------------------------------------------------------------
199!!
200      INTEGER (kind=4) mpi_totproc(1:CLIM_MaxMod-1),mpi_nproc(0:CLIM_MaxMod-1)
201!!
202      CHARACTER (len=6) cmpi_modnam(1:CLIM_MaxMod-1)
203!!
204      common/CLIM_mpiclim/mpi_totproc, mpi_nproc, cmpi_modnam 
205!!
206!!!END-----------------------------------------------------------------
207
208
209   !!----------------------------------------------------------------------
210   !!  Atmosphere/Ice/Ocean Coupling
211   !!---------------------------------
212
213   REAL(wp), DIMENSION(jpi,jpj) ::   &   !: data from an atmospheric model
214      qc  ,       &  !: total surf. total heat flux (wm-2)
215      ec  ,       &  !: surface water flux (kg m-2s-1)
216      qsrc           !: solar radiation (w m-2)
217
218#  if defined key_ice_lim
219   REAL(wp), DIMENSION(jpi,jpj) ::   &  !:
220      watm        ,    &  !:
221      tatm        ,    &  !:
222      hatm        ,    &  !:
223      vatm        ,    &  !:
224      catm                !:
225#  endif
226
227   !! Coupling
228
229   INTEGER ::          &  !:
230      npioc       ,    &  !: process-id of ocean PROGRAM
231      nexco       ,    &  !: exchange frequency for fluxes
232      nmodcpl     ,    &  !: coupling mode
233      nflxc2o     ,    &  !: fluxes field number coupler to ocean
234      ntauc2o     ,    &  !: stress field number coupler to ocean
235      nfldo2c             !: surface field number ocean to coupler
236
237   CHARACTER(len=4) ::   cchan       !: type of message passing (pipe or clim)
238   CHARACTER(len=6) ::   cplmodnam   !: model name
239   CHARACTER(len=5) ::   cploasis    !: coupler name
240
241   CHARACTER(len=8), DIMENSION(jpmaxfld) ::   &  !:
242      cpl_f_readflx,   &  !: coupler to ocean file name for flx.coupled
243      cpl_f_readtau,   &  !: coupler to ocean file name for tau.coupled
244      cpl_f_writ   ,   &  !: ocean to coupler file name for cpl_stp
245      cpl_readflx  ,   &  !: coupler to ocean field name for flx.coupled
246      cpl_readtau  ,   &  !: coupler to ocean field name for tau.coupled
247      cpl_writ            !: ocean to coupler field name for cpl_stp
248
249  REAL(wp), DIMENSION(jpi,jpj) ::   &  !:
250      sstoc,     &  !: work array to average sst
251      sieoc,     &  !: work array to average Ice index
252      alboc,     &  !: work array to average Ice Albedo
253      ticoc         !: work array to average Ice temperature
254
255
256   !! -- inc_sipc.h   97-08-11   Version 2.0   Author: S&A
257   !!    **********
258   !! variables describing pools formed of shared memory segments
259
260   INTEGER ::   &  !:
261      mpoolinitr,  &  !: handles associated to model pools for passing
262      mpoolinitw      !: initial info (r=read, w=write)
263
264   INTEGER, DIMENSION(jpmaxfld) ::   &  !:
265      mpoolwrit,   &  !: handles associated to pools used to pass fields
266      !               !  exchanged from model to coupler
267      !               !  (see libsipc/SIPC_Write_Model.f)
268      mpoolread       !: handles associated to pools used to pass fields
269      !               !  exchanged from model to coupler
270      !               !  (see libsipc/SIPC_Read_Model.f)
271
272#else
273   !!----------------------------------------------------------------------
274   !!   Default case                                Forced Ocean/Atmosphere
275   !!----------------------------------------------------------------------
276   !!   Empty module
277   LOGICAL, PUBLIC, PARAMETER :: lk_cpl = .FALSE.   !: coupled flag
278#endif
279
280   !!----------------------------------------------------------------------
281END MODULE cpl_oce
Note: See TracBrowser for help on using the repository browser.