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

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

CT : BUGFIX001 : Compilation error is solved

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 10.0 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.h'
60! -- clim.h   18-08-95   Version 2.0   Author: Laurent Terray
61!    ******
62!             26-10-99   Version 2.4   Jean Latour (F.S.E.) MPI-2 support
63!!
64!!  Contents : variables related to the CLIM library
65!!  --------
66!! For complete definition, see the CLIM manual
67!!
68      INTEGER*4 CLIM_MaxMod,    CLIM_MaxPort,  CLIM_MaxSegments,
69     *          CLIM_MaxTag,
70     *          CLIM_MaxLink,
71     *          CLIM_ParSize,
72     *          CLIM_Clength,
73     *          CLIM_MaxCodes
74
75      INTEGER*4 CLIM_Void
76
77      INTEGER*4 CLIM_In,        CLIM_Out,       CLIM_InOut
78
79      INTEGER*4 CLIM_Strategy,  CLIM_Segments, 
80     *          CLIM_Serial,    CLIM_Length,    CLIM_Orange,
81     *          CLIM_Apple,     CLIM_Offset,
82     *          CLIM_Box,       CLIM_SizeX,     CLIM_SizeY,
83     *          CLIM_LdX
84
85      INTEGER*4 CLIM_Integer,   CLIM_Real,      CLIM_Double
86
87      INTEGER*4 CLIM_StopPvm,   CLIM_ContPvm
88
89      INTEGER*4 CLIM_Ok
90      INTEGER*4 CLIM_FastExit,  CLIM_BadName,   CLIM_BadPort,
91     *          CLIM_BadType,   CLIM_DoubleDef, CLIM_NotStep,
92     *          CLIM_IncStep,   CLIM_IncSize,   CLIM_NotClim,
93     *          CLIM_TimeOut,
94     *          CLIM_Pvm,       CLIM_FirstCall, CLIM_PbRoute,
95     *          CLIM_Group,     CLIM_BadTaskId, CLIM_NoTask,
96     *          CLIM_InitBuff,  CLIM_Pack,      CLIM_Unpack,
97     *          CLIM_Down,      CLIM_PvmExit
98
99      INTEGER*4 CLIM_jpmax,     CLIM_jpmx8,     CLIM_Mpi
100
101!-----Parameter sizes
102
103      PARAMETER ( CLIM_Void    = 0  )
104      PARAMETER ( CLIM_MaxMod  = 8 )
105      PARAMETER ( CLIM_MaxPort = 50 )
106      PARAMETER ( CLIM_MaxSegments = 50 )
107      PARAMETER ( CLIM_MaxLink = CLIM_MaxMod * CLIM_MaxPort )
108      PARAMETER ( CLIM_ParSize = 2*CLIM_MaxSegments+2 )
109      PARAMETER ( CLIM_MaxTag  = 16777215 )
110      PARAMETER ( CLIM_Clength = 32 )
111
112!-----Dimension of buffer for packing / unpacking messages with MPI
113!     (must be equal to jpmax of Oasis)
114
115      PARAMETER ( CLIM_jpmax = 400000 )
116      PARAMETER ( CLIM_jpmx8 = CLIM_jpmax*8 )
117
118!-----Ports status
119
120      PARAMETER ( CLIM_In      = 1 )
121      PARAMETER ( CLIM_Out     = 0 )
122      PARAMETER ( CLIM_InOut   = 2 )
123
124!-----Parallel distribution
125
126      PARAMETER ( CLIM_Strategy = 1 )
127      PARAMETER ( CLIM_Segments = 2 )
128      PARAMETER ( CLIM_Serial   = 0 )
129      PARAMETER ( CLIM_Apple    = 1 )
130      PARAMETER ( CLIM_Box      = 2 )
131      PARAMETER ( CLIM_Orange   = 3 )
132      PARAMETER ( CLIM_Offset   = 2 )
133      PARAMETER ( CLIM_Length   = 3 )
134      PARAMETER ( CLIM_SizeX    = 3 )
135      PARAMETER ( CLIM_SizeY    = 4 )
136      PARAMETER ( CLIM_LdX      = 5 )
137
138!-----Datatypes
139
140      PARAMETER ( CLIM_Integer = 1 )
141      PARAMETER ( CLIM_Real    = 4 ) 
142      PARAMETER ( CLIM_Double  = 8 )
143
144!-----Quit parameters
145
146      PARAMETER ( CLIM_ContPvm = 0 )
147      PARAMETER ( CLIM_StopPvm = 1 )
148
149!-----Error Codes
150
151      PARAMETER ( CLIM_MaxCodes  = -22 )
152
153      PARAMETER ( CLIM_Ok        = 0 )
154      PARAMETER ( CLIM_FastExit  = -1 )
155      PARAMETER ( CLIM_BadName   = -2 )
156      PARAMETER ( CLIM_BadPort   = -3 )
157      PARAMETER ( CLIM_BadType   = -4 )
158      PARAMETER ( CLIM_DoubleDef = -5 )
159      PARAMETER ( CLIM_NotStep   = -6 )
160      PARAMETER ( CLIM_IncStep   = -7 )
161      PARAMETER ( CLIM_IncSize   = -8 )
162      PARAMETER ( CLIM_NotClim   = -9 )
163      PARAMETER ( CLIM_TimeOut   = -10 )
164      PARAMETER ( CLIM_Pvm       = -11 )
165      PARAMETER ( CLIM_FirstCall = -12 )
166      PARAMETER ( CLIM_PbRoute   = -13 )
167      PARAMETER ( CLIM_Group     = -14 )
168      PARAMETER ( CLIM_BadTaskId = -15 )
169      PARAMETER ( CLIM_NoTask    = -16 )
170      PARAMETER ( CLIM_InitBuff  = -17 )
171      PARAMETER ( CLIM_Pack      = -18 )
172      PARAMETER ( CLIM_Unpack    = -19 )
173      PARAMETER ( CLIM_Down      = -20 )
174      PARAMETER ( CLIM_PvmExit   = -21 )
175      PARAMETER ( CLIM_Mpi       = -22 )
176
177!     --- end of clim.h
178!!!END-----------------------------------------------------------------
179
180!!!INCLUDE '../../CPL/include/mpiclim.h'
181!!-- mpiclim.h  26-10-99   Version 2.4   Author: Jean Latour (F.S.E.)
182!!   *********
183!!
184!!  Contents : variables related to MPI-2 message passing
185!!  --------
186!!
187!! -- mpi_totproc: number of processors on which to launch each model
188!!
189!! -- mpi_nproc: number of processors involved in the coupling for
190!!               each model
191!! -- cmpi_modnam: models name
192!     -----------------------------------------------------------------
193
194      INTEGER*4 mpi_totproc(1:CLIM_MaxMod-1),mpi_nproc(0:CLIM_MaxMod-1)
195
196      CHARACTER*6 cmpi_modnam(1:CLIM_MaxMod-1)
197
198!!!END-----------------------------------------------------------------
199
200
201   !!----------------------------------------------------------------------
202   !!  Atmosphere/Ice/Ocean Coupling
203   !!---------------------------------
204
205   REAL(wp), DIMENSION(jpi,jpj) ::   &   !: data from an atmospheric model
206      qc  ,       &  !: total surf. total heat flux (wm-2)
207      ec  ,       &  !: surface water flux (kg m-2s-1)
208      qsrc           !: solar radiation (w m-2)
209
210#  if defined key_ice_lim
211   REAL(wp), DIMENSION(jpi,jpj) ::   &  !:
212      watm        ,    &  !:
213      tatm        ,    &  !:
214      hatm        ,    &  !:
215      vatm        ,    &  !:
216      catm                !:
217#  endif
218
219   !! Coupling
220
221   INTEGER ::          &  !:
222      npioc       ,    &  !: process-id of ocean PROGRAM
223      nexco       ,    &  !: exchange frequency for fluxes
224      nmodcpl     ,    &  !: coupling mode
225      nflxc2o     ,    &  !: fluxes field number coupler to ocean
226      ntauc2o     ,    &  !: stress field number coupler to ocean
227      nfldo2c             !: surface field number ocean to coupler
228
229   CHARACTER(len=4) ::   cchan       !: type of message passing (pipe or clim)
230   CHARACTER(len=6) ::   cplmodnam   !: model name
231   CHARACTER(len=5) ::   cploasis    !: coupler name
232
233   CHARACTER(len=8), DIMENSION(jpmaxfld) ::   &  !:
234      cpl_f_readflx,   &  !: coupler to ocean file name for flx.coupled
235      cpl_f_readtau,   &  !: coupler to ocean file name for tau.coupled
236      cpl_f_writ   ,   &  !: ocean to coupler file name for stp_cmo
237      cpl_readflx  ,   &  !: coupler to ocean field name for flx.coupled
238      cpl_readtau  ,   &  !: coupler to ocean field name for tau.coupled
239      cpl_writ            !: ocean to coupler field name for stp_cmo
240
241  REAL(wp), DIMENSION(jpi,jpj) ::   &  !:
242      sstoc,     &  !: work array to average sst
243      sieoc,     &  !: work array to average Ice index
244      alboc,     &  !: work array to average Ice Albedo
245      ticoc         !: work array to average Ice temperature
246
247
248   !! -- inc_sipc.h   97-08-11   Version 2.0   Author: S&A
249   !!    **********
250   !! variables describing pools formed of shared memory segments
251
252   INTEGER ::   &  !:
253      mpoolinitr,  &  !: handles associated to model pools for passing
254      mpoolinitw      !: initial info (r=read, w=write)
255
256   INTEGER, DIMENSION(jpmaxfld) ::   &  !:
257      mpoolwrit,   &  !: handles associated to pools used to pass fields
258      !               !  exchanged from model to coupler
259      !               !  (see libsipc/SIPC_Write_Model.f)
260      mpoolread       !: handles associated to pools used to pass fields
261      !               !  exchanged from model to coupler
262      !               !  (see libsipc/SIPC_Read_Model.f)
263
264#else
265   !!----------------------------------------------------------------------
266   !!   Default case                                Forced Ocean/Atmosphere
267   !!----------------------------------------------------------------------
268   !!   Empty module
269   LOGICAL, PUBLIC, PARAMETER :: lk_cpl = .FALSE.   !: coupled flag
270#endif
271
272   !!----------------------------------------------------------------------
273END MODULE cpl_oce
Note: See TracBrowser for help on using the repository browser.