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