source: LMDZ4/branches/IPSL-CM4_IPCC_patches/libf/phylmd/oasis.dummy @ 589

Last change on this file since 589 was 589, checked in by Laurent Fairhead, 19 years ago

Modifications pour le couplage carbone LOOP, PC
LF

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