source: LMDZ.3.3/branches/rel-LF/libf/phylmd/oasis.F @ 421

Last change on this file since 421 was 421, checked in by lmdzadmin, 22 years ago

Les appels bidons a clim_ avaient disparu
LF

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