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

Last change on this file since 467 was 467, checked in by lmdzadmin, 21 years ago

Modifs sur les seuils (cdrag etc...), inclusion des diagnostics ISCCP par Ionela
LF

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