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

Last change on this file since 131 was 131, checked in by lmdzadmin, 24 years ago

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