source: LMDZ.3.3/branches/rel-LF/libf/phylmd/oasis.true @ 179

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

Synchronisation avec version MAFO:

ajout sortie netcdf des champs echanges avec le coupleur
quelques save sur les variables (pb stack/static sur le nec)

LF

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 19.7 KB
Line 
1C $Id: oasis.true 179 2001-03-20 15:14:30Z 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            WRITE(nuout,*) 'inicma : clim define done for ',jf
202     $          ,cl_read(jf)
203          END DO
204c
205c         -Loop on total number of atmosphere-to-coupler fields
206c         (see lib/clim/src/CLIM_Define for the definition of input parameters)
207          DO jf=1, jpflda2o1+jpflda2o2
208            CALL CLIM_Define (cl_writ(jf), clim_out , clim_double,
209     $          iparal, info )   
210            WRITE(nuout,*) 'inicma : clim define done for ',jf
211     $          ,cl_writ(jf)
212          END DO
213c
214          WRITE(nuout,*) 'inicma : clim_define ok '
215c
216c         -Join a pvm group, wait for other programs and broadcast usefull
217c          informations to Oasis and to the ocean (see lib/clim/src/CLIM_Start)
218          CALL CLIM_Start ( imxtag, info )
219          IF (info.ne.clim_ok) THEN
220              WRITE ( nuout, *) 'inicma : pb start clim '
221              WRITE ( nuout, *) ' error code is = ', info
222              CALL halte('stop in inicma')
223            ELSE
224              WRITE ( nuout, *)  'inicma : start clim ok '
225          ENDIF
226c
227c         -Get initial information from Oasis
228c          (see lib/clim/src/CLIM_Stepi)
229          CALL CLIM_Stepi (cloasis, istep, ifcpl, idt, info)
230          IF (info .NE. clim_ok) THEN
231              WRITE ( UNIT = nuout, FMT = *)
232     $            ' warning : problem in getting step info ',
233     $            'from oasis '
234              WRITE (UNIT = nuout, FMT = *)
235     $            ' =======   error code number = ', info
236            ELSE
237              WRITE (UNIT = nuout, FMT = *)
238     $            ' got step information from oasis '
239          ENDIF
240          WRITE ( nuout, *) ' number of tstep in oasis ', istep
241          WRITE ( nuout, *) ' exchange frequency in oasis ', ifcpl
242          WRITE ( nuout, *) ' length of tstep in oasis ', idt
243      ENDIF
244
245      RETURN
246      END
247
248c $Id: oasis.true 179 2001-03-20 15:14:30Z lmdzadmin $
249      SUBROUTINE fromcpl(kt, imjm, sst, gla, tice, albedo)
250c ======================================================================
251c S. Valcke (02/99) adapted From L.Z.X Li: this subroutine reads the SST
252c and Sea-Ice provided by the coupler with the CLIM (PVM exchange messages)
253c technique.
254c======================================================================
255      IMPLICIT none
256      INTEGER imjm, kt
257      REAL sst(imjm)          ! sea-surface-temperature
258      REAL gla(imjm)          ! sea-ice
259      REAL tice(imjm)          ! temp glace
260      REAL albedo(imjm)          ! albedo glace
261c
262      INTEGER nuout             ! listing output unit
263      PARAMETER (nuout=6)
264c
265      INTEGER nuread, ios, iflag, icpliter
266      INTEGER info, jf
267c
268      INCLUDE 'clim.h'
269c
270      INCLUDE 'oasis.h'
271      INCLUDE 'param_cou.h'
272c
273      INCLUDE 'inc_cpl.h'
274c
275c
276      WRITE (nuout,*) ' '
277      WRITE (nuout,*) 'Fromcpl: Reading fields from CPL, kt=',kt
278      WRITE (nuout,*) ' '
279      CALL flush (nuout)
280
281
282      IF (cchan.eq.'CLIM') THEN
283
284c
285c     -Get interpolated oceanic fields from Oasis
286c
287          DO jf=1,jpfldo2a
288            IF (jf.eq.1) CALL CLIM_Import (cl_read(jf) , kt, sst, info)
289            IF (jf.eq.2) CALL CLIM_Import (cl_read(jf) , kt, gla, info)
290            IF (jf.eq.3) CALL CLIM_Import (cl_read(jf), kt,albedo, info)
291            IF (jf.eq.4) CALL CLIM_Import (cl_read(jf) , kt, tice, info)
292            IF ( info .NE. CLIM_Ok) THEN
293                WRITE(nuout,*)'Pb in reading ', cl_read(jf), jf
294                WRITE(nuout,*)'Couplage kt is = ',kt
295                WRITE(nuout,*)'CLIM error code is = ', info
296                CALL halte('STOP in fromcpl.F')
297            ENDIF
298          END DO
299
300      ENDIF
301c
302      RETURN
303      END
304
305c $Id: oasis.true 179 2001-03-20 15:14:30Z lmdzadmin $
306      SUBROUTINE intocpl(kt, imjm, fsolice, fsolwat, fnsolice, fnsolwat,
307     $    fnsicedt, evice, evwat, lpre, spre, dirunoff, rivrunoff,
308     $    tauxx_u, tauyy_u, tauzz_u, tauxx_v, tauyy_v, tauzz_v,last)
309c ======================================================================
310c S. Valcke (02/99) adapted From L.Z.X Li: this subroutine provides the
311c atmospheric coupling fields to the coupler with the CLIM (PVM exchange
312c messages) technique.
313c IF last time step, writes output fields to binary files.
314c ======================================================================
315      IMPLICIT NONE
316      INTEGER kt, imjm
317c
318      REAL fsolice(imjm)
319      REAL fsolwat(imjm)
320      REAL fnsolwat(imjm)
321      REAL fnsolice(imjm)
322      REAL fnsicedt(imjm)
323      REAL evice(imjm)
324      REAL evwat(imjm)
325      REAL lpre(imjm)
326      REAL spre(imjm)
327      REAL dirunoff(imjm)
328      REAL rivrunoff(imjm)
329c$$$      REAL tauxu(imjm)
330c$$$      REAL tauxv(imjm)
331c$$$      REAL tauyu(imjm)
332c$$$      REAL tauyv(imjm)
333      REAL tauxx_u(imjm)
334      REAL tauxx_v(imjm)
335      REAL tauyy_u(imjm)
336      REAL tauyy_v(imjm)
337      REAL tauzz_u(imjm)
338      REAL tauzz_v(imjm)
339      LOGICAL last
340c
341      INTEGER nuout
342      PARAMETER (nuout = 6)
343c
344      INCLUDE 'clim.h'
345      INCLUDE 'param_cou.h'
346      INCLUDE 'inc_cpl.h'
347c
348      CHARACTER*8 file_name(jpmaxfld)
349      INTEGER max_file
350      INTEGER file_unit_max, file_unit(jpmaxfld),
351     $    file_unit_field(jpmaxfld)
352
353      INTEGER icstep, info, jn, jf, ierror
354      LOGICAL trouve
355c
356      INCLUDE 'oasis.h'
357c
358      icstep=kt
359c
360      WRITE(nuout,*) ' '
361      WRITE(nuout,*) 'Intocpl: sending fields to CPL, kt= ', kt
362      WRITE(nuout,*) ' '
363
364      IF (last) THEN
365c
366c     -WRITE fields to binary files for coupler restart at last time step
367c
368c         -initialisation and files opening
369c
370          max_file=1
371          file_unit_max=99
372c         -keeps first file name
373          file_name(max_file)=cl_f_writ(max_file)
374c         -keeps first file unit
375          file_unit(max_file)=file_unit_max
376c         -decrements file unit maximum
377          file_unit_max=file_unit_max-1
378c         -keeps file unit for field
379          file_unit_field(1)=file_unit(max_file)
380c
381c         -different files names counter
382c
383          DO jf= 2, jpflda2o1 + jpflda2o2
384            trouve=.false.
385            DO jn= 1, max_file
386              IF (.not.trouve) THEN
387                  IF (cl_f_writ(jf).EQ.file_name(jn)) THEN
388c                 -keep file unit for field
389                      file_unit_field(jf)=file_unit(jn)
390                      trouve=.true.
391                  END IF
392              END IF
393            END DO
394            IF (.not.trouve) then
395c           -increment the number of different files
396                max_file=max_file+1
397c           -keep file name
398                file_name(max_file)=cl_f_writ(jf)
399c           -keep file unit for file
400                file_unit(max_file)=file_unit_max
401c           -keep file unit for field
402                file_unit_field(jf)=file_unit(max_file)
403c           -decrement unit maximum number from 99 to 98, ...
404                file_unit_max=file_unit_max-1
405            END IF
406          END DO
407c         
408          DO jn=1, max_file
409            OPEN (file_unit(jn), FILE=file_name(jn), FORM='UNFORMATTED')
410          END DO
411c
412c         WRITE fields to files         
413          DO jf=1, jpflda2o1 + jpflda2o2
414            IF (jf.eq.1)
415     $          CALL locwrite(cl_writ(jf),fsolice, imjm,
416     $          file_unit_field(jf), ierror)
417            IF (jf.eq.2)
418     $          CALL locwrite(cl_writ(jf),fsolwat, imjm,
419     $          file_unit_field(jf), ierror)
420            IF (jf.eq.3)
421     $          CALL locwrite(cl_writ(jf),fnsolice, imjm,
422     $          file_unit_field(jf), ierror)
423            IF (jf.eq.4)
424     $          CALL locwrite(cl_writ(jf),fnsolwat, imjm,
425     $          file_unit_field(jf), ierror)
426            IF (jf.eq.5)
427     $          CALL locwrite(cl_writ(jf),fnsicedt, imjm,
428     $          file_unit_field(jf), ierror)
429c            IF (jf.eq.6)
430c     $          CALL locwrite(cl_writ(jf),ictemp, imjm,
431c     $          file_unit_field(jf), ierror)
432            IF (jf.eq.6)
433     $          CALL locwrite(cl_writ(jf),evice, imjm,
434     $          file_unit_field(jf), ierror)
435            IF (jf.eq.7)
436     $          CALL locwrite(cl_writ(jf),evwat, imjm,
437     $          file_unit_field(jf), ierror)
438            IF (jf.eq.8)
439     $          CALL locwrite(cl_writ(jf),lpre, imjm,
440     $          file_unit_field(jf), ierror)
441            IF (jf.eq.9)
442     $          CALL locwrite(cl_writ(jf),spre, imjm,
443     $          file_unit_field(jf), ierror)
444            IF (jf.eq.10)
445     $          CALL locwrite(cl_writ(jf),dirunoff, imjm,
446     $          file_unit_field(jf), ierror)
447            IF (jf.eq.11)
448     $          CALL locwrite(cl_writ(jf),rivrunoff, imjm,
449     $          file_unit_field(jf), ierror)
450c$$$            IF (jf.eq.12)
451c$$$     $          CALL locwrite(cl_writ(jf),tauxu, imjm,
452c$$$     $          file_unit_field(jf),ierror)
453c$$$            IF (jf.eq.13)
454c$$$     $          CALL locwrite(cl_writ(jf),tauxv, imjm,
455c$$$     $          file_unit_field(jf),ierror)
456c$$$            IF (jf.eq.14)
457c$$$     $          CALL locwrite(cl_writ(jf),tauyv, imjm,
458c$$$     $          file_unit_field(jf),ierror)
459c$$$            IF (jf.eq.15)
460c$$$     $          CALL locwrite(cl_writ(jf),tauyu, imjm,
461c$$$     $          file_unit_field(jf), ierror)
462            IF (jf.eq.12)
463     $          CALL locwrite(cl_writ(jf),tauxx_u, imjm,
464     $          file_unit_field(jf),ierror)
465            IF (jf.eq.13)
466     $          CALL locwrite(cl_writ(jf),tauyy_u, imjm,
467     $          file_unit_field(jf),ierror)
468            IF (jf.eq.14)
469     $          CALL locwrite(cl_writ(jf),tauzz_u, imjm,
470     $          file_unit_field(jf),ierror)
471            IF (jf.eq.15)
472     $          CALL locwrite(cl_writ(jf),tauxx_v, imjm,
473     $          file_unit_field(jf),ierror)
474            IF (jf.eq.16)
475     $          CALL locwrite(cl_writ(jf),tauyy_v, imjm,
476     $          file_unit_field(jf),ierror)
477            IF (jf.eq.17)
478     $          CALL locwrite(cl_writ(jf),tauzz_v, imjm,
479     $          file_unit_field(jf),ierror)
480          END DO
481C
482C         -simulate a FLUSH
483C
484          DO jn=1, max_file
485            CLOSE (file_unit(jn))
486          END DO
487C
488C
489          IF(cchan.eq.'CLIM') THEN
490C
491C         -inform PVM daemon that message exchange is finished
492C
493              CALL CLIM_Quit (CLIM_ContPvm, info)
494              IF (info .NE. CLIM_Ok) THEN
495                  WRITE (6, *)
496     $                'An error occured while leaving CLIM. Error = ',
497     $                info
498              ENDIF
499          END IF
500          RETURN   
501      END IF
502C
503      IF(cchan.eq.'CLIM') THEN
504C
505C     -Give atmospheric fields to Oasis
506C
507          DO jn=1, jpflda2o1 + jpflda2o2
508C           
509          IF (jn.eq.1) CALL CLIM_Export(cl_writ(jn), kt, fsolice, info)
510          IF (jn.eq.2) CALL CLIM_Export(cl_writ(jn), kt, fsolwat, info)
511          IF (jn.eq.3) CALL CLIM_Export(cl_writ(jn), kt, fnsolice, info)
512          IF (jn.eq.4) CALL CLIM_Export(cl_writ(jn), kt, fnsolwat, info)
513          IF (jn.eq.5) CALL CLIM_Export(cl_writ(jn), kt, fnsicedt, info)
514c          IF (jn.eq.6) CALL CLIM_Export(cl_writ(jn), kt, ictemp, info)
515          IF (jn.eq.6) CALL CLIM_Export(cl_writ(jn), kt, evice, info)
516          IF (jn.eq.7) CALL CLIM_Export(cl_writ(jn), kt, evwat, info)
517          IF (jn.eq.8) CALL CLIM_Export(cl_writ(jn), kt, lpre, info)
518          IF (jn.eq.9) CALL CLIM_Export(cl_writ(jn), kt, spre, info)
519          IF (jn.eq.10) CALL CLIM_Export(cl_writ(jn),kt,dirunoff, info)
520          IF (jn.eq.11) CALL CLIM_Export(cl_writ(jn),kt,rivrunoff,info)
521c$$$          IF (jn.eq.12) CALL CLIM_Export(cl_writ(jn), kt, tauxu, info)
522c$$$          IF (jn.eq.13) CALL CLIM_Export(cl_writ(jn), kt, tauxv, info)
523c$$$          IF (jn.eq.14) CALL CLIM_Export(cl_writ(jn), kt, tauyv, info)
524c$$$          IF (jn.eq.15) CALL CLIM_Export(cl_writ(jn), kt, tauyu, info)
525          IF (jn.eq.12) CALL CLIM_Export(cl_writ(jn), kt, tauxx_u, info)
526          IF (jn.eq.13) CALL CLIM_Export(cl_writ(jn), kt, tauyy_u, info)
527          IF (jn.eq.14) CALL CLIM_Export(cl_writ(jn), kt, tauzz_u, info)
528          IF (jn.eq.15) CALL CLIM_Export(cl_writ(jn), kt, tauxx_v, info)
529          IF (jn.eq.16) CALL CLIM_Export(cl_writ(jn), kt, tauyy_v, info)
530          IF (jn.eq.17) CALL CLIM_Export(cl_writ(jn), kt, tauzz_v, info)
531         
532            IF (info .NE. CLIM_Ok) THEN
533                WRITE (nuout,*) 'STEP : Pb giving ',cl_writ(jn), ':',jn
534                WRITE (nuout,*) ' at timestep = ', icstep,'kt = ',kt
535                WRITE (nuout,*) 'Clim error code is = ',info
536                CALL halte('STOP in intocpl ')
537            ENDIF
538          END DO
539      ENDIF
540C
541      RETURN
542      END
543
544      SUBROUTINE pipe_model_define
545      print*,'Attention dans oasis.F, pipe_model_define est non defini'
546      RETURN
547      END
548
549      SUBROUTINE pipe_model_stepi
550      print*,'Attention dans oasis.F, pipe_model_stepi est non defini'
551      RETURN
552      END
553
554      SUBROUTINE pipe_model_recv
555      print *, 'Attention dans oasis.F, pipe_model_recv est non defini'
556      RETURN
557      END
558
559      SUBROUTINE pipe_model_send
560      print *, 'Attention dans oasis.F, pipe_model_send est non defini'
561      RETURN
562      END
563
564      SUBROUTINE quitcpl
565      print *, 'Attention dans oasis.F, quitcpl est non defini'
566      RETURN
567      END
568
569      SUBROUTINE sipc_write_model
570      print *, 'Attention dans oasis.F, sipc_write_model est non defini'
571      RETURN
572      END
573
574      SUBROUTINE sipc_attach
575      print *, 'Attention dans oasis.F, sipc_attach est non defini'
576      RETURN
577      END
578
579      SUBROUTINE sipc_init_model
580      print *, 'Attention dans oasis.F, sipc_init_model est non defini'
581      RETURN
582      END
583
584      SUBROUTINE sipc_read_model
585      print *, 'Attention dans oasis.F, sipc_read_model est non defini'
586      RETURN
587      END
Note: See TracBrowser for help on using the repository browser.