source: LMDZ4/trunk/libf/phylmd/oasis.dummy @ 524

Last change on this file since 524 was 524, checked in by lmdzadmin, 20 years ago

Initial revision

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 21.6 KB
Line 
1!
2! $Header$
3!
4C $Id: oasis.dummy 524 2004-05-19 12:53:04Z lmdzadmin $
5C****
6C
7C**** *INICMA*  - Initialize coupled mode communication for atmosphere
8C                 and exchange some initial information with Oasis
9C
10C     Input:
11C     -----
12C       KASTP  : total number of timesteps in atmospheric model
13C       KEXCH  : frequency of exchange (in time steps)
14C       KSTEP  : length of timestep (in seconds)
15C
16C     -----------------------------------------------------------
17C
18      SUBROUTINE inicma(kastp,kexch,kstep,imjm)
19c
20c     INCLUDE "param.h"
21c
22      INTEGER kastp, kexch, kstep,imjm
23      INTEGER iparal(3)
24      INTEGER ifcpl, idt, info, imxtag, istep, jf
25c
26#include "param_cou.h"
27#include "inc_cpl.h"
28      CHARACTER*3 cljobnam      ! experiment name
29      CHARACTER*6 clmodnam      ! model name
30c     EM: not used by Oasis2.4
31CEM      CHARACTER*6 clbid(2)      ! for CLIM_Init call (not used)
32CEM                                ! must be dimensioned by the number of models
33CEM      INTEGER nbid(2)           ! for CLIM_Init call (not used)
34CEM                                ! must be dimensioned by the number of models
35      CHARACTER*5 cloasis       ! coupler name (Oasis)
36      INTEGER imess(4)
37      INTEGER getpid            ! system functions
38      INTEGER nuout
39CEM      LOGICAL llmodel
40      PARAMETER (nuout = 6)
41c
42#include "clim.h"
43#include "mpiclim.h"
44c
45#include "oasis.h"     
46                        ! contains the name of communication technique. Here
47                        ! cchan=CLIM only is possible.
48c                       ! ctype=MPI2
49c
50C     -----------------------------------------------------------
51C
52C*    1. Initializations
53C        ---------------
54C
55      WRITE(nuout,*) ' '
56      WRITE(nuout,*) ' '
57      WRITE(nuout,*) ' ROUTINE INICMA'
58      WRITE(nuout,*) ' **************'
59      WRITE(nuout,*) ' '
60      WRITE(nuout,*) ' '
61c
62c     Define the model name
63c
64      clmodnam = 'lmdz.x'       ! as in $NBMODEL in Cpl/Nam/namcouple.tmp
65c
66c     Define the coupler name
67c
68      cloasis = 'Oasis'        !  always 'Oasis' as in the coupler
69c
70c
71c     Define symbolic name for fields exchanged from atmos to coupler,
72c         must be the same as (1) of the field  definition in namcouple:
73c
74      cl_writ(1)='COSHFICE'
75      cl_writ(2)='COSHFOCE'
76      cl_writ(3)='CONSFICE'
77      cl_writ(4)='CONSFOCE'
78      cl_writ(5)='CODFLXDT'
79c      cl_writ(6)='COICTEMP'
80      cl_writ(6)='COTFSICE'
81      cl_writ(7)='COTFSOCE'
82      cl_writ(8)='COTOLPSU'
83      cl_writ(9)='COTOSPSU'
84      cl_writ(10)='CORUNCOA'
85      cl_writ(11)='CORIVFLU'
86      cl_writ(12)='COCALVIN'
87c$$$      cl_writ(13)='COZOTAUX'
88c$$$      cl_writ(14)='COZOTAUV'
89c$$$      cl_writ(15)='COMETAUY'
90c$$$      cl_writ(16)='COMETAUU'
91      cl_writ(13)='COTAUXXU'
92      cl_writ(14)='COTAUYYU'
93      cl_writ(15)='COTAUZZU'
94      cl_writ(16)='COTAUXXV'
95      cl_writ(17)='COTAUYYV'
96      cl_writ(18)='COTAUZZV'
97c
98c     Define files name for fields exchanged from atmos to coupler,
99c         must be the same as (6) of the field  definition in namcouple:
100c
101      cl_f_writ(1)='flxatmos'
102      cl_f_writ(2)='flxatmos'
103      cl_f_writ(3)='flxatmos'
104      cl_f_writ(4)='flxatmos'
105      cl_f_writ(5)='flxatmos'
106      cl_f_writ(6)='flxatmos'
107      cl_f_writ(7)='flxatmos'
108      cl_f_writ(8)='flxatmos'
109      cl_f_writ(9)='flxatmos'
110      cl_f_writ(10)='flxatmos'
111      cl_f_writ(11)='flxatmos'
112      cl_f_writ(12)='flxatmos'
113      cl_f_writ(13)='flxatmos'
114      cl_f_writ(14)='flxatmos'
115      cl_f_writ(15)='flxatmos'
116      cl_f_writ(16)='flxatmos'
117      cl_f_writ(17)='flxatmos'
118      cl_f_writ(18)='flxatmos'
119
120c
121c
122c     Define symbolic name for fields exchanged from coupler to atmosphere,
123c         must be the same as (2) of the field  definition in namcouple:
124c
125      cl_read(1)='SISUTESW'
126      cl_read(2)='SIICECOV'
127      cl_read(3)='SIICEALW'
128      cl_read(4)='SIICTEMW'
129c
130c     Define files names for fields exchanged from coupler to atmosphere,
131c         must be the same as (7) of the field  definition in namcouple:
132c
133      cl_f_read(1)='sstatmos'
134      cl_f_read(2)='sstatmos'
135      cl_f_read(3)='sstatmos'
136      cl_f_read(4)='sstatmos'
137c
138c
139c     Define the number of processors involved in the coupling for
140c     Oasis (=1) and each model (as last two INTEGER on $CHATYPE line
141c     in the namcouple); they will be stored in a COMMON in mpiclim.h
142c     (used for CLIM/MPI2 only)
143      mpi_nproc(0)=1
144      mpi_nproc(1)=1
145      mpi_nproc(2)=1
146c
147c     Define infos to be sent initially to oasis
148c
149      imess(1) = kastp      ! total number of timesteps in atmospheric model
150      imess(2) = kexch      ! period of exchange (in time steps)
151      imess(3) = kstep      ! length of atmospheric timestep (in seconds)
152      imess(4) = getpid()   ! PID of atmospheric model
153c
154c     Initialization and exchange of initial info in the CLIM technique
155c
156      IF (cchan.eq.'CLIM') THEN
157c
158c     Define the experiment name :
159c
160          cljobnam = 'CLI'      ! as $JOBNAM in namcouple
161c
162c         Start the coupling
163c         (see lib/clim/src/CLIM_Init for the definition of input parameters)
164c
165cEM          clbid(1)='      '
166cEM          clbid(2)='      '
167cEM          nbid(1)=0
168cEM          nbid(2)=0
169CEM          llmodel=.true.
170c
171c         Define the number of processors used by each model as in
172c         $CHATYPE line of namcouple (used for CLIM/MPI2 only)
173          mpi_totproc(1)=1
174          mpi_totproc(2)=1
175c
176c         Define names of each model as in $NBMODEL line of namcouple
177c         (used for CLIM/MPI2 only)       
178          cmpi_modnam(1)='lmdz.x'
179          cmpi_modnam(2)='opa.xx'
180c         Start the coupling
181c
182          CALL CLIM_Init ( cljobnam, clmodnam, 3, 7,
183     *                 kastp, kexch, kstep,
184     *                 5, 3600, 3600, info )
185c
186          IF (info.ne.CLIM_Ok) THEN
187              WRITE ( nuout, *) ' inicma : pb init clim '
188              WRITE ( nuout, *) ' error code is = ', info
189              CALL halte('STOP in inicma')
190            ELSE
191              WRITE(nuout,*) 'inicma : init clim ok '
192          ENDIF
193c
194c         For each coupling field, association of a port to its symbolic name
195c
196c         -Define the parallel decomposition associated to the port of each
197c          field; here no decomposition for all ports.
198          iparal ( clim_strategy ) = clim_serial
199          iparal ( clim_length   ) = imjm
200          iparal ( clim_offset   ) = 0
201c
202c         -Loop on total number of coupler-to-atmosphere fields
203c         (see lib/clim/src/CLIM_Define for the definition of input parameters)
204          DO jf=1, jpfldo2a
205            CALL CLIM_Define (cl_read(jf), clim_in , clim_double, iparal
206     $          , info ) 
207            WRITE(nuout,*) 'inicma : clim define done for ',jf
208     $          ,cl_read(jf)
209          END DO
210c
211c         -Loop on total number of atmosphere-to-coupler fields
212c         (see lib/clim/src/CLIM_Define for the definition of input parameters)
213          DO jf=1, jpflda2o1+jpflda2o2
214            CALL CLIM_Define (cl_writ(jf), clim_out , clim_double,
215     $          iparal, info )   
216            WRITE(nuout,*) 'inicma : clim define done for ',jf
217     $          ,cl_writ(jf)
218          END DO
219c
220          WRITE(nuout,*) 'inicma : clim_define ok '
221c
222c         -Join a pvm group, wait for other programs and broadcast usefull
223c          informations to Oasis and to the ocean (see lib/clim/src/CLIM_Start)
224          CALL CLIM_Start ( imxtag, info )
225          IF (info.ne.clim_ok) THEN
226              WRITE ( nuout, *) 'inicma : pb start clim '
227              WRITE ( nuout, *) ' error code is = ', info
228              CALL halte('stop in inicma')
229            ELSE
230              WRITE ( nuout, *)  'inicma : start clim ok '
231          ENDIF
232c
233c         -Get initial information from Oasis
234c          (see lib/clim/src/CLIM_Stepi)
235          CALL CLIM_Stepi (cloasis, istep, ifcpl, idt, info)
236          IF (info .NE. clim_ok) THEN
237              WRITE ( UNIT = nuout, FMT = *)
238     $            ' warning : problem in getting step info ',
239     $            'from oasis '
240              WRITE (UNIT = nuout, FMT = *)
241     $            ' =======   error code number = ', info
242            ELSE
243              WRITE (UNIT = nuout, FMT = *)
244     $            ' got step information from oasis '
245          ENDIF
246          WRITE ( nuout, *) ' number of tstep in oasis ', istep
247          WRITE ( nuout, *) ' exchange frequency in oasis ', ifcpl
248          WRITE ( nuout, *) ' length of tstep in oasis ', idt
249      ENDIF
250
251      RETURN
252      END
253
254c $Id: oasis.dummy 524 2004-05-19 12:53:04Z lmdzadmin $
255      SUBROUTINE fromcpl(kt, imjm, sst, gla, tice, albedo)
256c ======================================================================
257c S. Valcke (02/99) adapted From L.Z.X Li: this subroutine reads the SST
258c and Sea-Ice provided by the coupler with the CLIM (PVM exchange messages)
259c technique.
260c======================================================================
261      IMPLICIT none
262      INTEGER imjm, kt
263      REAL sst(imjm)          ! sea-surface-temperature
264      REAL gla(imjm)          ! sea-ice
265      REAL tice(imjm)          ! temp glace
266      REAL albedo(imjm)          ! albedo glace
267c
268      INTEGER nuout             ! listing output unit
269      PARAMETER (nuout=6)
270c
271      INTEGER nuread, ios, iflag, icpliter
272      INTEGER info, jf
273c
274#include "clim.h"
275c
276#include "oasis.h"
277#include "param_cou.h"
278c
279#include "inc_cpl.h"
280c
281c
282      WRITE (nuout,*) ' '
283      WRITE (nuout,*) 'Fromcpl: Reading fields from CPL, kt=',kt
284      WRITE (nuout,*) ' '
285      CALL flush (nuout)
286
287
288      IF (cchan.eq.'CLIM') THEN
289
290c
291c     -Get interpolated oceanic fields from Oasis
292c
293          DO jf=1,jpfldo2a
294            IF (jf.eq.1) CALL CLIM_Import (cl_read(jf) , kt, sst, info)
295            IF (jf.eq.2) CALL CLIM_Import (cl_read(jf) , kt, gla, info)
296            IF (jf.eq.3) CALL CLIM_Import (cl_read(jf), kt,albedo, info)
297            IF (jf.eq.4) CALL CLIM_Import (cl_read(jf) , kt, tice, info)
298            IF ( info .NE. CLIM_Ok) THEN
299                WRITE(nuout,*)'Pb in reading ', cl_read(jf), jf
300                WRITE(nuout,*)'Couplage kt is = ',kt
301                WRITE(nuout,*)'CLIM error code is = ', info
302                CALL halte('STOP in fromcpl.F')
303            ENDIF
304          END DO
305
306      ENDIF
307c
308      RETURN
309      END
310
311c $Id: oasis.dummy 524 2004-05-19 12:53:04Z lmdzadmin $
312      SUBROUTINE intocpl(kt, imjm, fsolice, fsolwat, fnsolice, fnsolwat,
313     $    fnsicedt, evice, evwat, lpre, spre, dirunoff, rivrunoff,
314     $    calving, tauxx_u, tauyy_u, tauzz_u, tauxx_v, tauyy_v, tauzz_v
315     $    , last)
316c ======================================================================
317c S. Valcke (02/99) adapted From L.Z.X Li: this subroutine provides the
318c atmospheric coupling fields to the coupler with the CLIM (PVM exchange
319c messages) technique.
320c IF last time step, writes output fields to binary files.
321c ======================================================================
322      IMPLICIT NONE
323      INTEGER kt, imjm
324c
325      REAL fsolice(imjm)
326      REAL fsolwat(imjm)
327      REAL fnsolwat(imjm)
328      REAL fnsolice(imjm)
329      REAL fnsicedt(imjm)
330      REAL evice(imjm)
331      REAL evwat(imjm)
332      REAL lpre(imjm)
333      REAL spre(imjm)
334      REAL dirunoff(imjm)
335      REAL rivrunoff(imjm)
336      REAL calving(imjm)
337c$$$      REAL tauxu(imjm)
338c$$$      REAL tauxv(imjm)
339c$$$      REAL tauyu(imjm)
340c$$$      REAL tauyv(imjm)
341      REAL tauxx_u(imjm)
342      REAL tauxx_v(imjm)
343      REAL tauyy_u(imjm)
344      REAL tauyy_v(imjm)
345      REAL tauzz_u(imjm)
346      REAL tauzz_v(imjm)
347      LOGICAL last
348c
349      INTEGER nuout
350      PARAMETER (nuout = 6)
351c
352#include "clim.h"
353#include "param_cou.h"
354#include "inc_cpl.h"
355c
356      CHARACTER*8 file_name(jpmaxfld)
357      INTEGER max_file
358      INTEGER file_unit_max, file_unit(jpmaxfld),
359     $    file_unit_field(jpmaxfld)
360
361      INTEGER icstep, info, jn, jf, ierror
362      LOGICAL trouve
363c
364#include "oasis.h"
365c
366      icstep=kt
367c
368      WRITE(nuout,*) ' '
369      WRITE(nuout,*) 'Intocpl: sending fields to CPL, kt= ', kt
370      WRITE(nuout,*) 'last  ', last
371      WRITE(nuout,*)
372
373      IF (last) THEN
374c
375c     -WRITE fields to binary files for coupler restart at last time step
376c
377c         -initialisation and files opening
378c
379          max_file=1
380          file_unit_max=99
381c         -keeps first file name
382          file_name(max_file)=cl_f_writ(max_file)
383c         -keeps first file unit
384          file_unit(max_file)=file_unit_max
385c         -decrements file unit maximum
386          file_unit_max=file_unit_max-1
387c         -keeps file unit for field
388          file_unit_field(1)=file_unit(max_file)
389c
390c         -different files names counter
391c
392          DO jf= 2, jpflda2o1 + jpflda2o2
393            trouve=.false.
394            DO jn= 1, max_file
395              IF (.not.trouve) THEN
396                  IF (cl_f_writ(jf).EQ.file_name(jn)) THEN
397c                 -keep file unit for field
398                      file_unit_field(jf)=file_unit(jn)
399                      trouve=.true.
400                  END IF
401              END IF
402            END DO
403            IF (.not.trouve) then
404c           -increment the number of different files
405                max_file=max_file+1
406c           -keep file name
407                file_name(max_file)=cl_f_writ(jf)
408c           -keep file unit for file
409                file_unit(max_file)=file_unit_max
410c           -keep file unit for field
411                file_unit_field(jf)=file_unit(max_file)
412c           -decrement unit maximum number from 99 to 98, ...
413                file_unit_max=file_unit_max-1
414            END IF
415          END DO
416c         
417          DO jn=1, max_file
418            OPEN (file_unit(jn), FILE=file_name(jn), FORM='UNFORMATTED')
419            WRITE(*,*) 'Opening FILE ', file_unit(jn), ' '
420     $          , file_name(jn)
421            REWIND(file_unit(jn))
422          END DO
423c
424c         WRITE fields to files         
425          DO jf=1, jpflda2o1 + jpflda2o2
426            IF (jf.eq.1)
427     $          CALL locwrite(cl_writ(jf),fsolice, imjm,
428     $          file_unit_field(jf), ierror)
429            IF (jf.eq.2)
430     $          CALL locwrite(cl_writ(jf),fsolwat, imjm,
431     $          file_unit_field(jf), ierror)
432            IF (jf.eq.3)
433     $          CALL locwrite(cl_writ(jf),fnsolice, imjm,
434     $          file_unit_field(jf), ierror)
435            IF (jf.eq.4)
436     $          CALL locwrite(cl_writ(jf),fnsolwat, imjm,
437     $          file_unit_field(jf), ierror)
438            IF (jf.eq.5)
439     $          CALL locwrite(cl_writ(jf),fnsicedt, imjm,
440     $          file_unit_field(jf), ierror)
441c            IF (jf.eq.6)
442c     $          CALL locwrite(cl_writ(jf),ictemp, imjm,
443c     $          file_unit_field(jf), ierror)
444            IF (jf.eq.6)
445     $          CALL locwrite(cl_writ(jf),evice, imjm,
446     $          file_unit_field(jf), ierror)
447            IF (jf.eq.7)
448     $          CALL locwrite(cl_writ(jf),evwat, imjm,
449     $          file_unit_field(jf), ierror)
450            IF (jf.eq.8)
451     $          CALL locwrite(cl_writ(jf),lpre, imjm,
452     $          file_unit_field(jf), ierror)
453            IF (jf.eq.9)
454     $          CALL locwrite(cl_writ(jf),spre, imjm,
455     $          file_unit_field(jf), ierror)
456            IF (jf.eq.10)
457     $          CALL locwrite(cl_writ(jf),dirunoff, imjm,
458     $          file_unit_field(jf), ierror)
459            IF (jf.eq.11)
460     $          CALL locwrite(cl_writ(jf),rivrunoff, imjm,
461     $          file_unit_field(jf), ierror)
462            IF (jf.eq.12)
463     $          CALL locwrite(cl_writ(jf),calving, imjm,
464     $          file_unit_field(jf), ierror)
465c$$$            IF (jf.eq.13)
466c$$$     $          CALL locwrite(cl_writ(jf),tauxu, imjm,
467c$$$     $          file_unit_field(jf),ierror)
468c$$$            IF (jf.eq.1')
469c$$$     $          CALL locwrite(cl_writ(jf),tauxv, imjm,
470c$$$     $          file_unit_field(jf),ierror)
471c$$$            IF (jf.eq.15)
472c$$$     $          CALL locwrite(cl_writ(jf),tauyv, imjm,
473c$$$     $          file_unit_field(jf),ierror)
474c$$$            IF (jf.eq.16)
475c$$$     $          CALL locwrite(cl_writ(jf),tauyu, imjm,
476c$$$     $          file_unit_field(jf), ierror)
477            IF (jf.eq.13)
478     $          CALL locwrite(cl_writ(jf),tauxx_u, imjm,
479     $          file_unit_field(jf),ierror)
480            IF (jf.eq.14)
481     $          CALL locwrite(cl_writ(jf),tauyy_u, imjm,
482     $          file_unit_field(jf),ierror)
483            IF (jf.eq.15)
484     $          CALL locwrite(cl_writ(jf),tauzz_u, imjm,
485     $          file_unit_field(jf),ierror)
486            IF (jf.eq.16)
487     $          CALL locwrite(cl_writ(jf),tauxx_v, imjm,
488     $          file_unit_field(jf),ierror)
489            IF (jf.eq.17)
490     $          CALL locwrite(cl_writ(jf),tauyy_v, imjm,
491     $          file_unit_field(jf),ierror)
492            IF (jf.eq.18)
493     $          CALL locwrite(cl_writ(jf),tauzz_v, imjm,
494     $          file_unit_field(jf),ierror)
495          END DO
496C
497C         -simulate a FLUSH
498C
499          DO jn=1, max_file
500            CLOSE (file_unit(jn))
501          END DO
502C
503C
504          IF(cchan.eq.'CLIM') THEN
505C
506C         -inform PVM daemon that message exchange is finished
507C
508              CALL CLIM_Quit (CLIM_ContPvm, info)
509              IF (info .NE. CLIM_Ok) THEN
510                  WRITE (6, *)
511     $                'An error occured while leaving CLIM. Error = ',
512     $                info
513              ENDIF
514          END IF
515          RETURN   
516      END IF
517C
518      IF(cchan.eq.'CLIM') THEN
519C
520C     -Give atmospheric fields to Oasis
521C
522          DO jn=1, jpflda2o1 + jpflda2o2
523C           
524          IF (jn.eq.1) CALL CLIM_Export(cl_writ(jn), kt, fsolice, info)
525          IF (jn.eq.2) CALL CLIM_Export(cl_writ(jn), kt, fsolwat, info)
526          IF (jn.eq.3) CALL CLIM_Export(cl_writ(jn), kt, fnsolice, info)
527          IF (jn.eq.4) CALL CLIM_Export(cl_writ(jn), kt, fnsolwat, info)
528          IF (jn.eq.5) CALL CLIM_Export(cl_writ(jn), kt, fnsicedt, info)
529c          IF (jn.eq.6) CALL CLIM_Export(cl_writ(jn), kt, ictemp, info)
530          IF (jn.eq.6) CALL CLIM_Export(cl_writ(jn), kt, evice, info)
531          IF (jn.eq.7) CALL CLIM_Export(cl_writ(jn), kt, evwat, info)
532          IF (jn.eq.8) CALL CLIM_Export(cl_writ(jn), kt, lpre, info)
533          IF (jn.eq.9) CALL CLIM_Export(cl_writ(jn), kt, spre, info)
534          IF (jn.eq.10) CALL CLIM_Export(cl_writ(jn),kt,dirunoff, info)
535          IF (jn.eq.11) CALL CLIM_Export(cl_writ(jn),kt,rivrunoff,info)
536          IF (jn.eq.12) CALL CLIM_Export(cl_writ(jn),kt,calving,info)
537c$$$          IF (jn.eq.13) CALL CLIM_Export(cl_writ(jn), kt, tauxu, info)
538c$$$          IF (jn.eq.14) CALL CLIM_Export(cl_writ(jn), kt, tauxv, info)
539c$$$          IF (jn.eq.15) CALL CLIM_Export(cl_writ(jn), kt, tauyv, info)
540c$$$          IF (jn.eq.16) CALL CLIM_Export(cl_writ(jn), kt, tauyu, info)
541          IF (jn.eq.13) CALL CLIM_Export(cl_writ(jn), kt, tauxx_u, info)
542          IF (jn.eq.14) CALL CLIM_Export(cl_writ(jn), kt, tauyy_u, info)
543          IF (jn.eq.15) CALL CLIM_Export(cl_writ(jn), kt, tauzz_u, info)
544          IF (jn.eq.16) CALL CLIM_Export(cl_writ(jn), kt, tauxx_v, info)
545          IF (jn.eq.17) CALL CLIM_Export(cl_writ(jn), kt, tauyy_v, info)
546          IF (jn.eq.18) CALL CLIM_Export(cl_writ(jn), kt, tauzz_v, info)
547         
548            IF (info .NE. CLIM_Ok) THEN
549                WRITE (nuout,*) 'STEP : Pb giving ',cl_writ(jn), ':',jn
550                WRITE (nuout,*) ' at timestep = ', icstep,'kt = ',kt
551                WRITE (nuout,*) 'Clim error code is = ',info
552                CALL halte('STOP in intocpl ')
553            ENDIF
554          END DO
555      ENDIF
556C
557      RETURN
558      END
559
560      SUBROUTINE halte
561      print *, 'Attention dans oasis.F, halte est non defini'
562      RETURN
563      END
564
565      SUBROUTINE locread
566      print *, 'Attention dans oasis.F, locread est non defini'
567      RETURN
568      END
569
570      SUBROUTINE locwrite
571      print *, 'Attention dans oasis.F, locwrite est non defini'
572      RETURN
573      END
574
575      SUBROUTINE pipe_model_define
576      print*,'Attention dans oasis.F, pipe_model_define est non defini'
577      RETURN
578      END
579
580      SUBROUTINE pipe_model_stepi
581      print*,'Attention dans oasis.F, pipe_model_stepi est non defini'
582      RETURN
583      END
584
585      SUBROUTINE pipe_model_recv
586      print *, 'Attention dans oasis.F, pipe_model_recv est non defini'
587      RETURN
588      END
589
590      SUBROUTINE pipe_model_send
591      print *, 'Attention dans oasis.F, pipe_model_send est non defini'
592      RETURN
593      END
594
595      SUBROUTINE clim_stepi
596      print *, 'Attention dans oasis.F, clim_stepi est non defini'
597      RETURN
598      END
599
600      SUBROUTINE clim_start
601      print *, 'Attention dans oasis.F, clim_start est non defini'
602      RETURN
603      END
604
605      SUBROUTINE clim_import
606      print *, 'Attention dans oasis.F, clim_import est non defini'
607      RETURN
608      END
609
610      SUBROUTINE clim_export
611      print *, 'Attention dans oasis.F, clim_export est non defini'
612      RETURN
613      END
614
615      SUBROUTINE clim_init
616      print *, 'Attention dans oasis.F, clim_init est non defini'
617      RETURN
618      END
619
620      SUBROUTINE clim_define
621      print *, 'Attention dans oasis.F, clim_define est non defini'
622      RETURN
623      END
624
625      SUBROUTINE clim_quit
626      print *, 'Attention dans oasis.F, clim_quit est non defini'
627      RETURN
628      END
629
630      SUBROUTINE svipc_write
631      print *, 'Attention dans oasis.F, svipc_write est non defini'
632      RETURN
633      END
634
635      SUBROUTINE svipc_close
636      print *, 'Attention dans oasis.F, svipc_close est non defini'
637      RETURN
638      END
639
640      SUBROUTINE svipc_read
641      print *, 'Attention dans oasis.F, svipc_read est non defini'
642      RETURN
643      END
644
645      SUBROUTINE quitcpl
646      print *, 'Attention dans oasis.F, quitcpl est non defini'
647      RETURN
648      END
649
650      SUBROUTINE sipc_write_model
651      print *, 'Attention dans oasis.F, sipc_write_model est non defini'
652      RETURN
653      END
654
655      SUBROUTINE sipc_attach
656      print *, 'Attention dans oasis.F, sipc_attach est non defini'
657      RETURN
658      END
659
660      SUBROUTINE sipc_init_model
661      print *, 'Attention dans oasis.F, sipc_init_model est non defini'
662      RETURN
663      END
664
665      SUBROUTINE sipc_read_model
666      print *, 'Attention dans oasis.F, sipc_read_model est non defini'
667      RETURN
668      END
Note: See TracBrowser for help on using the repository browser.