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

Last change on this file since 177 was 177, checked in by lmdzadmin, 23 years ago

Lots of stuff, plus particulierement:

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