New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
iom.F90 in branches/2011/dev_r2802_MERCATOR9_floats/NEMOGCM/NEMO/OPA_SRC/IOM – NEMO

source: branches/2011/dev_r2802_MERCATOR9_floats/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90 @ 2839

Last change on this file since 2839 was 2839, checked in by cbricaud, 13 years ago

modified routine for netcdf output

  • Property svn:keywords set to Id
File size: 62.8 KB
RevLine 
[544]1MODULE iom
2   !!=====================================================================
3   !!                    ***  MODULE  iom ***
4   !! Input/Output manager :  Library to read input files
5   !!====================================================================
6   !! History :  9.0  ! 05 12  (J. Belier) Original code
7   !!            9.0  ! 06 02  (S. Masson) Adaptation to NEMO
[911]8   !!             "   ! 07 07  (D. Storkey) Changes to iom_gettime
[544]9   !!--------------------------------------------------------------------
10   !!gm  caution add !DIR nec: improved performance to be checked as well as no result changes
11
12   !!--------------------------------------------------------------------
13   !!   iom_open       : open a file read only
14   !!   iom_close      : close a file or all files opened by iom
15   !!   iom_get        : read a field (interfaced to several routines)
[550]16   !!   iom_gettime    : read the time axis cdvar in the file
[544]17   !!   iom_varid      : get the id of a variable in a file
18   !!   iom_rstput     : write a field in a restart file (interfaced to several routines)
19   !!--------------------------------------------------------------------
20   USE dom_oce         ! ocean space and time domain
[2839]21   USE flo_oce         ! floats module declarations
[679]22   USE lbclnk          ! lateal boundary condition / mpp exchanges
[544]23   USE iom_def         ! iom variables definitions
24   USE iom_ioipsl      ! NetCDF format with IOIPSL library
25   USE iom_nf90        ! NetCDF format with native NetCDF library
26   USE iom_rstdimg     ! restarts access direct format "dimg" style...
[2715]27   USE in_out_manager  ! I/O manager
28   USE lib_mpp           ! MPP library
[1412]29#if defined key_iomput
[1725]30   USE sbc_oce, ONLY :   nn_fsbc         ! ocean space and time domain
31   USE domngb          ! ocean space and time domain
32   USE phycst          ! physical constants
33   USE dianam          ! build name of file
[1359]34   USE mod_event_client
[1725]35   USE mod_attribut
[1359]36# endif
37
[544]38   IMPLICIT NONE
[556]39   PUBLIC   !   must be public to be able to access iom_def through iom
[550]40   
[1457]41#if defined key_iomput
[1725]42   LOGICAL, PUBLIC, PARAMETER ::   lk_iomput = .TRUE.        !: iom_put flag
[1457]43#else
44   LOGICAL, PUBLIC, PARAMETER ::   lk_iomput = .FALSE.       !: iom_put flag
45#endif
[1793]46   PUBLIC iom_init, iom_swap, iom_open, iom_close, iom_setkt, iom_varid, iom_get, iom_gettime, iom_rstput, iom_put
[2528]47   PUBLIC iom_getatt
[544]48
[752]49   PRIVATE iom_rp0d, iom_rp1d, iom_rp2d, iom_rp3d
50   PRIVATE iom_g0d, iom_g1d, iom_g2d, iom_g3d, iom_get_123d
[2839]51   PRIVATE iom_p1d, iom_p2d, iom_p3d
[1412]52#if defined key_iomput
[1359]53   PRIVATE set_grid
54# endif
[752]55
[544]56   INTERFACE iom_get
[550]57      MODULE PROCEDURE iom_g0d, iom_g1d, iom_g2d, iom_g3d
[544]58   END INTERFACE
[2528]59   INTERFACE iom_getatt
60      MODULE PROCEDURE iom_g0d_intatt
61   END INTERFACE
[544]62   INTERFACE iom_rstput
[550]63      MODULE PROCEDURE iom_rp0d, iom_rp1d, iom_rp2d, iom_rp3d
[544]64   END INTERFACE
[1359]65  INTERFACE iom_put
[2839]66     MODULE PROCEDURE iom_p0d, iom_p1d, iom_p2d, iom_p3d
[1359]67  END INTERFACE
[1412]68#if defined key_iomput
[1359]69   INTERFACE iom_setkt
70      MODULE PROCEDURE event__set_timestep
71   END INTERFACE
72# endif
[544]73
74   !!----------------------------------------------------------------------
[2528]75   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
[1152]76   !! $Id$
[2528]77   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[544]78   !!----------------------------------------------------------------------
79
80CONTAINS
81
[1725]82   SUBROUTINE iom_init
[1359]83      !!----------------------------------------------------------------------
84      !!                     ***  ROUTINE   ***
85      !!
86      !! ** Purpose :   
87      !!
88      !!----------------------------------------------------------------------
[1412]89#if defined key_iomput
[1730]90      REAL(wp) ::   ztmp
[1359]91      !!----------------------------------------------------------------------
92      ! read the xml file
[1793]93      IF( Agrif_Root() ) CALL event__parse_xml_file( 'iodef.xml' )   ! <- to get from the nameliste (namrun)...
94      CALL iom_swap
[1359]95
96      ! calendar parameters
[1725]97      SELECT CASE ( nleapy )        ! Choose calendar for IOIPSL
98      CASE ( 1)   ;   CALL event__set_calendar('gregorian')
99      CASE ( 0)   ;   CALL event__set_calendar('noleap'   )
100      CASE (30)   ;   CALL event__set_calendar('360d'     )
101      END SELECT
[1730]102      ztmp = fjulday - adatrj
103      IF( ABS(ztmp  - REAL(NINT(ztmp),wp)) < 0.1 / rday )   ztmp = REAL(NINT(ztmp),wp)   ! avoid truncation error
104      CALL event__set_time_parameters( nit000 - 1, ztmp, rdt )
[1359]105
106      ! horizontal grid definition
[1738]107      CALL set_scalar
[1359]108      CALL set_grid( "grid_T", glamt, gphit )
109      CALL set_grid( "grid_U", glamu, gphiu )
110      CALL set_grid( "grid_V", glamv, gphiv )
111      CALL set_grid( "grid_W", glamt, gphit )
112
113      ! vertical grid definition
114      CALL event__set_vert_axis( "deptht", gdept_0 )
115      CALL event__set_vert_axis( "depthu", gdept_0 )
116      CALL event__set_vert_axis( "depthv", gdept_0 )
117      CALL event__set_vert_axis( "depthw", gdepw_0 )
[2839]118#if defined key_floats
119      CALL event__set_vert_axis( "nfloat", REAL(nfloat,wp)  )
120#endif
[1725]121     
122      ! automatic definitions of some of the xml attributs
123      CALL set_xmlatt
[1359]124
125      ! end file definition
126      CALL event__close_io_definition
127#endif
128
129   END SUBROUTINE iom_init
130
131
[1793]132   SUBROUTINE iom_swap
133      !!---------------------------------------------------------------------
134      !!                   ***  SUBROUTINE  iom_swap  ***
135      !!
136      !! ** Purpose :  swap context between different agrif grid for xmlio_server
137      !!---------------------------------------------------------------------
138#if defined key_iomput
139
140     IF( TRIM(Agrif_CFixed()) == '0' ) THEN
141        CALL event__swap_context("nemo")
142     ELSE
143        CALL event__swap_context(TRIM(Agrif_CFixed())//"_nemo")
144     ENDIF
145
146#endif
147   END SUBROUTINE iom_swap
148
149
[1319]150   SUBROUTINE iom_open( cdname, kiomid, ldwrt, kdom, kiolib, ldstop, ldiof )
[544]151      !!---------------------------------------------------------------------
152      !!                   ***  SUBROUTINE  iom_open  ***
153      !!
154      !! ** Purpose :  open an input file (return 0 if not found)
155      !!---------------------------------------------------------------------
156      CHARACTER(len=*), INTENT(in   )           ::   cdname   ! File name
157      INTEGER         , INTENT(  out)           ::   kiomid   ! iom identifier of the opened file
158      LOGICAL         , INTENT(in   ), OPTIONAL ::   ldwrt    ! open in write modeb          (default = .FALSE.)
159      INTEGER         , INTENT(in   ), OPTIONAL ::   kdom     ! Type of domain to be written (default = jpdom_local_noovlap)
[547]160      INTEGER         , INTENT(in   ), OPTIONAL ::   kiolib   ! library used to open the file (default = jpnf90)
[679]161      LOGICAL         , INTENT(in   ), OPTIONAL ::   ldstop   ! stop if open to read a non-existing file (default = .TRUE.)
[1319]162      LOGICAL         , INTENT(in   ), OPTIONAL ::   ldiof    ! Interp On the Fly, needed for AGRIF (default = .FALSE.)
[544]163
164      CHARACTER(LEN=100)    ::   clname    ! the name of the file based on cdname [[+clcpu]+clcpu]
165      CHARACTER(LEN=100)    ::   cltmpn    ! tempory name to store clname (in writting mode)
166      CHARACTER(LEN=10)     ::   clsuffix  ! ".nc" or ".dimg"
[550]167      CHARACTER(LEN=15)     ::   clcpu     ! the cpu number (max jpmax_digits digits)
[544]168      CHARACTER(LEN=100)    ::   clinfo    ! info character
169      LOGICAL               ::   llok      ! check the existence
[679]170      LOGICAL               ::   llwrt     ! local definition of ldwrt
[1200]171      LOGICAL               ::   llnoov    ! local definition to read overlap
[679]172      LOGICAL               ::   llstop    ! local definition of ldstop
[1319]173      LOGICAL               ::   lliof     ! local definition of ldiof
[544]174      INTEGER               ::   iolib     ! library do we use to open the file
175      INTEGER               ::   icnt      ! counter for digits in clcpu (max = jpmax_digits)
176      INTEGER               ::   iln, ils  ! lengths of character
177      INTEGER               ::   idom      ! type of domain
178      INTEGER               ::   istop     !
179      INTEGER, DIMENSION(2,5) ::   idompar ! domain parameters:
180      ! local number of points for x,y dimensions
181      ! position of first local point for x,y dimensions
182      ! position of last local point for x,y dimensions
183      ! start halo size for x,y dimensions
184      ! end halo size for x,y dimensions
185      !---------------------------------------------------------------------
186      ! Initializations and control
187      ! =============
[1341]188      kiomid = -1
[544]189      clinfo = '                    iom_open ~~~  '
190      istop = nstop
191      ! if iom_open is called for the first time: initialize iom_file(:)%nfid to 0
192      ! (could be done when defining iom_file in f95 but not in f90)
[1441]193      IF( Agrif_Root() ) THEN
194         IF( iom_open_init == 0 ) THEN
195            iom_file(:)%nfid = 0
196            iom_open_init = 1
197         ENDIF
[1409]198      ENDIF
[544]199      ! do we read or write the file?
200      IF( PRESENT(ldwrt) ) THEN   ;   llwrt = ldwrt
201      ELSE                        ;   llwrt = .FALSE.
202      ENDIF
[679]203      ! do we call ctl_stop if we try to open a non-existing file in read mode?
204      IF( PRESENT(ldstop) ) THEN   ;   llstop = ldstop
205      ELSE                         ;   llstop = .TRUE.
206      ENDIF
[544]207      ! what library do we use to open the file?
208      IF( PRESENT(kiolib) ) THEN   ;   iolib = kiolib
[547]209      ELSE                         ;   iolib = jpnf90
[544]210      ENDIF
[1319]211      ! are we using interpolation on the fly?
212      IF( PRESENT(ldiof) ) THEN   ;   lliof = ldiof
213      ELSE                        ;   lliof = .FALSE.
214      ENDIF
[1200]215      ! do we read the overlap
216      ! ugly patch SM+JMM+RB to overwrite global definition in some cases
[1202]217      llnoov = (jpni * jpnj ) == jpnij .AND. .NOT. lk_agrif 
[544]218      ! create the file name by added, if needed, TRIM(Agrif_CFixed()) and TRIM(clsuffix)
219      ! =============
220      clname   = trim(cdname)
[1319]221      IF ( .NOT. Agrif_Root() .AND. .NOT. lliof ) THEN
[1200]222         iln    = INDEX(clname,'/') 
223         cltmpn = clname(1:iln)
224         clname = clname(iln+1:LEN_TRIM(clname))
225         clname=TRIM(cltmpn)//TRIM(Agrif_CFixed())//'_'//TRIM(clname)
226      ENDIF
[544]227      ! which suffix should we use?
228      SELECT CASE (iolib)
229      CASE (jpioipsl ) ;   clsuffix = '.nc'
230      CASE (jpnf90   ) ;   clsuffix = '.nc'
231      CASE (jprstdimg) ;   clsuffix = '.dimg'
232      CASE DEFAULT     ;   clsuffix = ''
233         CALL ctl_stop( TRIM(clinfo), 'accepted IO library are only jpioipsl, jpnf90 and jprstdimg' )
234      END SELECT
235      ! Add the suffix if needed
236      iln = LEN_TRIM(clname)
237      ils = LEN_TRIM(clsuffix)
[742]238      IF( iln <= ils .OR. INDEX( TRIM(clname), TRIM(clsuffix), back = .TRUE. ) /= iln - ils + 1 )   &
239         &   clname = TRIM(clname)//TRIM(clsuffix)
[544]240      cltmpn = clname   ! store this name
241      ! try to find if the file to be opened already exist
242      ! =============
243      INQUIRE( FILE = clname, EXIST = llok )
244      IF( .NOT.llok ) THEN
245         ! we try to add the cpu number to the name
[679]246         IF( iolib == jprstdimg ) THEN   ;   WRITE(clcpu,*) narea
247         ELSE                            ;   WRITE(clcpu,*) narea-1
248         ENDIF
[544]249         clcpu  = TRIM(ADJUSTL(clcpu))
[679]250         iln = INDEX(clname,TRIM(clsuffix), back = .TRUE.)
[544]251         clname = clname(1:iln-1)//'_'//TRIM(clcpu)//TRIM(clsuffix)
252         icnt = 0
253         INQUIRE( FILE = clname, EXIST = llok ) 
254         ! we try different formats for the cpu number by adding 0
255         DO WHILE( .NOT.llok .AND. icnt < jpmax_digits )
256            clcpu  = "0"//trim(clcpu)
257            clname = clname(1:iln-1)//'_'//TRIM(clcpu)//TRIM(clsuffix)
258            INQUIRE( FILE = clname, EXIST = llok )
259            icnt = icnt + 1
260         END DO
261      ENDIF
[679]262      IF( llwrt ) THEN
263         ! check the domain definition
264! JMM + SM: ugly patch before getting the new version of lib_mpp)
265!         idom = jpdom_local_noovlap   ! default definition
[1200]266         IF( llnoov ) THEN   ;   idom = jpdom_local_noovlap   ! default definition
267         ELSE                ;   idom = jpdom_local_full      ! default definition
[679]268         ENDIF
269         IF( PRESENT(kdom) )   idom = kdom
270         ! create the domain informations
271         ! =============
272         SELECT CASE (idom)
273         CASE (jpdom_local_full)
274            idompar(:,1) = (/ jpi             , jpj              /)
275            idompar(:,2) = (/ nimpp           , njmpp            /)
276            idompar(:,3) = (/ nimpp + jpi - 1 , njmpp + jpj - 1  /)
277            idompar(:,4) = (/ nldi - 1        , nldj - 1         /)
278            idompar(:,5) = (/ jpi - nlei      , jpj - nlej       /)
279         CASE (jpdom_local_noextra)
280            idompar(:,1) = (/ nlci            , nlcj             /)
281            idompar(:,2) = (/ nimpp           , njmpp            /)
282            idompar(:,3) = (/ nimpp + nlci - 1, njmpp + nlcj - 1 /)
283            idompar(:,4) = (/ nldi - 1        , nldj - 1         /)
284            idompar(:,5) = (/ nlci - nlei     , nlcj - nlej      /)
285         CASE (jpdom_local_noovlap)
286            idompar(:,1) = (/ nlei  - nldi + 1, nlej  - nldj + 1 /)
287            idompar(:,2) = (/ nimpp + nldi - 1, njmpp + nldj - 1 /)
288            idompar(:,3) = (/ nimpp + nlei - 1, njmpp + nlej - 1 /)
289            idompar(:,4) = (/ 0               , 0                /)
290            idompar(:,5) = (/ 0               , 0                /)
291         CASE DEFAULT
292            CALL ctl_stop( TRIM(clinfo), 'wrong value of kdom, only jpdom_local* cases are accepted' )
293         END SELECT
294      ENDIF
[544]295      ! Open the NetCDF or RSTDIMG file
296      ! =============
297      ! do we have some free file identifier?
298      IF( MINVAL(iom_file(:)%nfid) /= 0 )   &
[679]299         &   CALL ctl_stop( TRIM(clinfo), 'No more free file identifier', 'increase jpmax_files in iom_def' )
300      ! if no file was found...
301      IF( .NOT. llok ) THEN
302         IF( .NOT. llwrt ) THEN   ! we are in read mode
303            IF( llstop ) THEN   ;   CALL ctl_stop( TRIM(clinfo), 'File '//TRIM(cltmpn)//'* not found' )
304            ELSE                ;   istop = nstop + 1   ! make sure that istop /= nstop so we don't open the file
305            ENDIF
306         ELSE                     ! we are in write mode so we
307            clname = cltmpn       ! get back the file name without the cpu number
308         ENDIF
[2586]309      ELSE
310         IF( llwrt .AND. .NOT. ln_clobber ) THEN   ! we stop as we want to write in a new file
311            CALL ctl_stop( TRIM(clinfo), 'We want to write in a new file but '//TRIM(clname)//' already exists...' )
312            istop = nstop + 1                      ! make sure that istop /= nstop so we don't open the file
313         ENDIF
[679]314      ENDIF
[544]315      IF( istop == nstop ) THEN   ! no error within this routine
316         SELECT CASE (iolib)
317         CASE (jpioipsl )   ;   CALL iom_ioipsl_open(  clname, kiomid, llwrt, llok, idompar )
318         CASE (jpnf90   )   ;   CALL iom_nf90_open(    clname, kiomid, llwrt, llok, idompar )
319         CASE (jprstdimg)   ;   CALL iom_rstdimg_open( clname, kiomid, llwrt, llok, idompar )
320         CASE DEFAULT
321            CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' )
322         END SELECT
323      ENDIF
324      !
325   END SUBROUTINE iom_open
326
327
328   SUBROUTINE iom_close( kiomid )
329      !!--------------------------------------------------------------------
330      !!                   ***  SUBROUTINE  iom_close  ***
331      !!
332      !! ** Purpose : close an input file, or all files opened by iom
333      !!--------------------------------------------------------------------
[1131]334      INTEGER, INTENT(inout), OPTIONAL ::   kiomid   ! iom identifier of the file to be closed
335      !                                              ! return 0 when file is properly closed
336      !                                              ! No argument: all files opened by iom are closed
[544]337
338      INTEGER ::   jf         ! dummy loop indices
339      INTEGER ::   i_s, i_e   ! temporary integer
340      CHARACTER(LEN=100)    ::   clinfo    ! info character
341      !---------------------------------------------------------------------
342      !
343      clinfo = '                    iom_close ~~~  '
344      IF( PRESENT(kiomid) ) THEN
345         i_s = kiomid
346         i_e = kiomid
347      ELSE
348         i_s = 1
349         i_e = jpmax_files
[1412]350#if defined key_iomput
[1359]351         CALL event__stop_ioserver
352#endif
[544]353      ENDIF
354
355      IF( i_s > 0 ) THEN
356         DO jf = i_s, i_e
357            IF( iom_file(jf)%nfid > 0 ) THEN
358               SELECT CASE (iom_file(jf)%iolib)
359               CASE (jpioipsl )   ;   CALL iom_ioipsl_close(  jf )
360               CASE (jpnf90   )   ;   CALL iom_nf90_close(    jf )
361               CASE (jprstdimg)   ;   CALL iom_rstdimg_close( jf )
362               CASE DEFAULT
363                  CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' )
364               END SELECT
[1131]365               iom_file(jf)%nfid       = 0          ! free the id
366               IF( PRESENT(kiomid) )   kiomid = 0   ! return 0 as id to specify that the file was closed
[679]367               IF(lwp) WRITE(numout,*) TRIM(clinfo)//' close file: '//TRIM(iom_file(jf)%name)//' ok'
[544]368            ELSEIF( PRESENT(kiomid) ) THEN
369               WRITE(ctmp1,*) '--->',  kiomid
370               CALL ctl_stop( TRIM(clinfo)//' Invalid file identifier', ctmp1 )
371            ENDIF
372         END DO
373      ENDIF
374      !   
375   END SUBROUTINE iom_close
376
377
[745]378   FUNCTION iom_varid ( kiomid, cdvar, kdimsz, ldstop ) 
[544]379      !!-----------------------------------------------------------------------
380      !!                  ***  FUNCTION  iom_varid  ***
381      !!
382      !! ** Purpose : get the id of a variable in a file (return 0 if not found)
383      !!-----------------------------------------------------------------------
384      INTEGER              , INTENT(in   )           ::   kiomid   ! file Identifier
385      CHARACTER(len=*)     , INTENT(in   )           ::   cdvar    ! name of the variable
386      INTEGER, DIMENSION(:), INTENT(  out), OPTIONAL ::   kdimsz   ! size of the dimensions
[745]387      LOGICAL              , INTENT(in   ), OPTIONAL ::   ldstop   ! stop if looking for non-existing variable (default = .TRUE.)
[544]388      !
389      INTEGER                        ::   iom_varid, iiv, i_nvd
390      LOGICAL                        ::   ll_fnd
391      CHARACTER(LEN=100)             ::   clinfo                   ! info character
[745]392      LOGICAL                        ::   llstop                   ! local definition of ldstop
[544]393      !!-----------------------------------------------------------------------
394      iom_varid = 0                         ! default definition
[745]395      ! do we call ctl_stop if we look for non-existing variable?
396      IF( PRESENT(ldstop) ) THEN   ;   llstop = ldstop
397      ELSE                         ;   llstop = .TRUE.
398      ENDIF
[544]399      !
400      IF( kiomid > 0 ) THEN
[679]401         clinfo = 'iom_varid, file: '//trim(iom_file(kiomid)%name)//', var: '//trim(cdvar)
[544]402         IF( iom_file(kiomid)%nfid == 0 ) THEN
403            CALL ctl_stop( trim(clinfo), 'the file is not open' )
404         ELSE
405            ll_fnd  = .FALSE.
406            iiv = 0
407            !
408            DO WHILE ( .NOT.ll_fnd .AND. iiv < iom_file(kiomid)%nvars )
409               iiv = iiv + 1
410               ll_fnd  = ( TRIM(cdvar) == TRIM(iom_file(kiomid)%cn_var(iiv)) )
411            END DO
412            !
413            IF( .NOT.ll_fnd ) THEN
414               iiv = iiv + 1
415               IF( iiv <= jpmax_vars ) THEN
416                  SELECT CASE (iom_file(kiomid)%iolib)
417                  CASE (jpioipsl )   ;   iom_varid = iom_ioipsl_varid( kiomid, cdvar, iiv, kdimsz )
[745]418                  CASE (jpnf90   )   ;   iom_varid = iom_nf90_varid  ( kiomid, cdvar, iiv, kdimsz )
419                  CASE (jprstdimg)   ;   iom_varid = -1   ! all variables are listed in iom_file
[544]420                  CASE DEFAULT   
421                     CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' )
422                  END SELECT
423               ELSE
424                  CALL ctl_stop( trim(clinfo), 'Too many variables in the file '//iom_file(kiomid)%name,   &
425                        &                         'increase the parameter jpmax_vars')
426               ENDIF
[745]427               IF( llstop .AND. iom_varid == -1 )   CALL ctl_stop( TRIM(clinfo)//' not found' ) 
[544]428            ELSE
429               iom_varid = iiv
430               IF( PRESENT(kdimsz) ) THEN
431                  i_nvd = iom_file(kiomid)%ndims(iiv)
432                  IF( i_nvd == size(kdimsz) ) THEN
433                     kdimsz(:) = iom_file(kiomid)%dimsz(1:i_nvd,iiv)
434                  ELSE
435                     WRITE(ctmp1,*) i_nvd, size(kdimsz)
436                     CALL ctl_stop( trim(clinfo), 'error in kdimsz size'//trim(ctmp1) )
437                  ENDIF
438               ENDIF
439            ENDIF
440         ENDIF
441      ENDIF
442      !
443   END FUNCTION iom_varid
444
445
446   !!----------------------------------------------------------------------
447   !!                   INTERFACE iom_get
448   !!----------------------------------------------------------------------
[550]449   SUBROUTINE iom_g0d( kiomid, cdvar, pvar )
[544]450      INTEGER         , INTENT(in   )                 ::   kiomid    ! Identifier of the file
451      CHARACTER(len=*), INTENT(in   )                 ::   cdvar     ! Name of the variable
452      REAL(wp)        , INTENT(  out)                 ::   pvar      ! read field
453      !
454      INTEGER               :: idvar   ! variable id
455      !
[679]456      IF( kiomid > 0 ) THEN
457         idvar = iom_varid( kiomid, cdvar )
458         IF( iom_file(kiomid)%nfid > 0 .AND. idvar > 0 ) THEN
459            SELECT CASE (iom_file(kiomid)%iolib)
460            CASE (jpioipsl )   ;   CALL iom_ioipsl_get(  kiomid, idvar, pvar )
461            CASE (jpnf90   )   ;   CALL iom_nf90_get(    kiomid, idvar, pvar )
462            CASE (jprstdimg)   ;   CALL iom_rstdimg_get( kiomid, idvar, pvar )
463            CASE DEFAULT   
464               CALL ctl_stop( 'iom_g0d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' )
465            END SELECT
466         ENDIF
467      ENDIF
[550]468   END SUBROUTINE iom_g0d
[544]469
[550]470   SUBROUTINE iom_g1d( kiomid, kdom, cdvar, pvar, ktime, kstart, kcount )
[544]471      INTEGER         , INTENT(in   )                         ::   kiomid    ! Identifier of the file
472      INTEGER         , INTENT(in   )                         ::   kdom      ! Type of domain to be read
473      CHARACTER(len=*), INTENT(in   )                         ::   cdvar     ! Name of the variable
474      REAL(wp)        , INTENT(  out), DIMENSION(:)           ::   pvar      ! read field
475      INTEGER         , INTENT(in   )              , OPTIONAL ::   ktime     ! record number
476      INTEGER         , INTENT(in   ), DIMENSION(1), OPTIONAL ::   kstart    ! start axis position of the reading
477      INTEGER         , INTENT(in   ), DIMENSION(1), OPTIONAL ::   kcount    ! number of points in each axis
478      !
[679]479      IF( kiomid > 0 ) THEN
480         IF( iom_file(kiomid)%nfid > 0 ) CALL iom_get_123d( kiomid, kdom       , cdvar        , pv_r1d=pvar,   &
481              &                                                     ktime=ktime, kstart=kstart, kcount=kcount )
482      ENDIF
[550]483   END SUBROUTINE iom_g1d
[544]484
[550]485   SUBROUTINE iom_g2d( kiomid, kdom, cdvar, pvar, ktime, kstart, kcount )
[544]486      INTEGER         , INTENT(in   )                           ::   kiomid    ! Identifier of the file
487      INTEGER         , INTENT(in   )                           ::   kdom      ! Type of domain to be read
488      CHARACTER(len=*), INTENT(in   )                           ::   cdvar     ! Name of the variable
489      REAL(wp)        , INTENT(  out), DIMENSION(:,:)           ::   pvar      ! read field
490      INTEGER         , INTENT(in   )                , OPTIONAL ::   ktime     ! record number
491      INTEGER         , INTENT(in   ), DIMENSION(2)  , OPTIONAL ::   kstart    ! start axis position of the reading
492      INTEGER         , INTENT(in   ), DIMENSION(2)  , OPTIONAL ::   kcount    ! number of points in each axis
493      !
[679]494      IF( kiomid > 0 ) THEN
495         IF( iom_file(kiomid)%nfid > 0 ) CALL iom_get_123d( kiomid, kdom       , cdvar        , pv_r2d=pvar,   &
496              &                                                     ktime=ktime, kstart=kstart, kcount=kcount )
497      ENDIF
[550]498   END SUBROUTINE iom_g2d
[544]499
[550]500   SUBROUTINE iom_g3d( kiomid, kdom, cdvar, pvar, ktime, kstart, kcount )
[544]501      INTEGER         , INTENT(in   )                             ::   kiomid    ! Identifier of the file
502      INTEGER         , INTENT(in   )                             ::   kdom      ! Type of domain to be read
503      CHARACTER(len=*), INTENT(in   )                             ::   cdvar     ! Name of the variable
504      REAL(wp)        , INTENT(  out), DIMENSION(:,:,:)           ::   pvar      ! read field
505      INTEGER         , INTENT(in   )                  , OPTIONAL ::   ktime     ! record number
506      INTEGER         , INTENT(in   ), DIMENSION(3)    , OPTIONAL ::   kstart    ! start axis position of the reading
507      INTEGER         , INTENT(in   ), DIMENSION(3)    , OPTIONAL ::   kcount    ! number of points in each axis
508      !
[679]509      IF( kiomid > 0 ) THEN
510         IF( iom_file(kiomid)%nfid > 0 ) CALL iom_get_123d( kiomid, kdom       , cdvar        , pv_r3d=pvar,   &
511              &                                                     ktime=ktime, kstart=kstart, kcount=kcount )
512      ENDIF
[550]513   END SUBROUTINE iom_g3d
[544]514   !!----------------------------------------------------------------------
515
516   SUBROUTINE iom_get_123d( kiomid, kdom  , cdvar ,   &
[679]517         &                  pv_r1d, pv_r2d, pv_r3d,   &
518         &                  ktime , kstart, kcount  )
[544]519      !!-----------------------------------------------------------------------
520      !!                  ***  ROUTINE  iom_get_123d  ***
521      !!
522      !! ** Purpose : read a 1D/2D/3D variable
523      !!
524      !! ** Method : read ONE record at each CALL
525      !!-----------------------------------------------------------------------
526      INTEGER                    , INTENT(in   )           ::   kiomid     ! Identifier of the file
527      INTEGER                    , INTENT(in   )           ::   kdom       ! Type of domain to be read
528      CHARACTER(len=*)           , INTENT(in   )           ::   cdvar      ! Name of the variable
529      REAL(wp), DIMENSION(:)     , INTENT(  out), OPTIONAL ::   pv_r1d     ! read field (1D case)
530      REAL(wp), DIMENSION(:,:)   , INTENT(  out), OPTIONAL ::   pv_r2d     ! read field (2D case)
531      REAL(wp), DIMENSION(:,:,:) , INTENT(  out), OPTIONAL ::   pv_r3d     ! read field (3D case)
532      INTEGER                    , INTENT(in   ), OPTIONAL ::   ktime      ! record number
533      INTEGER , DIMENSION(:)     , INTENT(in   ), OPTIONAL ::   kstart     ! start position of the reading in each axis
534      INTEGER , DIMENSION(:)     , INTENT(in   ), OPTIONAL ::   kcount     ! number of points to be read in each axis
535      !
[1200]536      LOGICAL                        ::   llnoov      ! local definition to read overlap
[544]537      INTEGER                        ::   jl          ! loop on number of dimension
538      INTEGER                        ::   idom        ! type of domain
539      INTEGER                        ::   idvar       ! id of the variable
540      INTEGER                        ::   inbdim      ! number of dimensions of the variable
541      INTEGER                        ::   idmspc      ! number of spatial dimensions
542      INTEGER                        ::   itime       ! record number
543      INTEGER                        ::   istop       ! temporary value of nstop
[679]544      INTEGER                        ::   ix1, ix2, iy1, iy2   ! subdomain indexes
545      INTEGER                        ::   ji, jj      ! loop counters
546      INTEGER                        ::   irankpv       !
547      INTEGER                        ::   ind1, ind2  ! substring index
[544]548      INTEGER, DIMENSION(jpmax_dims) ::   istart      ! starting point to read for each axis
549      INTEGER, DIMENSION(jpmax_dims) ::   icnt        ! number of value to read along each axis
550      INTEGER, DIMENSION(jpmax_dims) ::   idimsz      ! size of the dimensions of the variable
[679]551      INTEGER, DIMENSION(jpmax_dims) ::   ishape      ! size of the dimensions of the variable
[544]552      REAL(wp)                       ::   zscf, zofs  ! sacle_factor and add_offset
553      INTEGER                        ::   itmp        ! temporary integer
554      CHARACTER(LEN=100)             ::   clinfo      ! info character
[679]555      CHARACTER(LEN=100)             ::   clname      ! file name
556      CHARACTER(LEN=1)               ::   clrankpv, cldmspc      !
[544]557      !---------------------------------------------------------------------
558      !
[679]559      clname = iom_file(kiomid)%name   !   esier to read
560      clinfo = '          iom_get_123d, file: '//trim(clname)//', var: '//trim(cdvar)
[544]561      ! local definition of the domain ?
562      idom = kdom
[1200]563      ! do we read the overlap
564      ! ugly patch SM+JMM+RB to overwrite global definition in some cases
[1202]565      llnoov = (jpni * jpnj ) == jpnij .AND. .NOT. lk_agrif 
[544]566      ! check kcount and kstart optionals parameters...
[679]567      IF( PRESENT(kcount) .AND. (.NOT. PRESENT(kstart)) ) CALL ctl_stop(trim(clinfo), 'kcount present needs kstart present')
568      IF( PRESENT(kstart) .AND. (.NOT. PRESENT(kcount)) ) CALL ctl_stop(trim(clinfo), 'kstart present needs kcount present')
569      IF( PRESENT(kstart) .AND. idom /= jpdom_unknown   ) CALL ctl_stop(trim(clinfo), 'kstart present needs kdom = jpdom_unknown')
[544]570
571      ! Search for the variable in the data base (eventually actualize data)
572      istop = nstop
573      idvar = iom_varid( kiomid, cdvar )
574      !
575      IF( idvar > 0 ) THEN
576         ! to write iom_file(kiomid)%dimsz in a shorter way !
577         idimsz(:) = iom_file(kiomid)%dimsz(:, idvar) 
578         inbdim = iom_file(kiomid)%ndims(idvar)            ! number of dimensions in the file
579         idmspc = inbdim                                   ! number of spatial dimensions in the file
580         IF( iom_file(kiomid)%luld(idvar) )   idmspc = inbdim - 1
[679]581         IF( idmspc > 3 )   CALL ctl_stop(trim(clinfo), 'the file has more than 3 spatial dimensions this case is not coded...') 
582         !
583         ! update idom definition...
584         ! Identify the domain in case of jpdom_auto(glo/dta) definition
585         IF( idom == jpdom_autoglo .OR. idom == jpdom_autodta ) THEN           
586            IF( idom == jpdom_autoglo ) THEN   ;   idom = jpdom_global 
587            ELSE                               ;   idom = jpdom_data
[544]588            ENDIF
[679]589            ind1 = INDEX( clname, '_', back = .TRUE. ) + 1
590            ind2 = INDEX( clname, '.', back = .TRUE. ) - 1
591            IF( ind2 > ind1 ) THEN   ;   IF( VERIFY( clname(ind1:ind2), '0123456789' ) == 0 )   idom = jpdom_local   ;   ENDIF
[544]592         ENDIF
[679]593         ! Identify the domain in case of jpdom_local definition
594         IF( idom == jpdom_local ) THEN
595            IF(     idimsz(1) == jpi               .AND. idimsz(2) == jpj               ) THEN   ;   idom = jpdom_local_full
596            ELSEIF( idimsz(1) == nlci              .AND. idimsz(2) == nlcj              ) THEN   ;   idom = jpdom_local_noextra
597            ELSEIF( idimsz(1) == (nlei - nldi + 1) .AND. idimsz(2) == (nlej - nldj + 1) ) THEN   ;   idom = jpdom_local_noovlap
598            ELSE   ;   CALL ctl_stop( trim(clinfo), 'impossible to identify the local domain' )
599            ENDIF
600         ENDIF
[544]601         !
[679]602         ! check the consistency between input array and data rank in the file
[544]603         !
604         ! initializations
605         itime = 1
606         IF( PRESENT(ktime) ) itime = ktime
[679]607
608         irankpv = 1 * COUNT( (/PRESENT(pv_r1d)/) ) + 2 * COUNT( (/PRESENT(pv_r2d)/) ) + 3 * COUNT( (/PRESENT(pv_r3d)/) )
609         WRITE(clrankpv, fmt='(i1)') irankpv
610         WRITE(cldmspc , fmt='(i1)') idmspc
[544]611         !
[679]612         IF(     idmspc <  irankpv ) THEN
613            CALL ctl_stop( TRIM(clinfo), 'The file has only '//cldmspc//' spatial dimension',   &
614               &                         'it is impossible to read a '//clrankpv//'D array from this file...' )
615         ELSEIF( idmspc == irankpv ) THEN
616            IF( PRESENT(pv_r1d) .AND. idom /= jpdom_unknown )   &
617               &   CALL ctl_stop( TRIM(clinfo), 'case not coded...You must use jpdom_unknown' )
618         ELSEIF( idmspc >  irankpv ) THEN
619               IF( PRESENT(pv_r2d) .AND. itime == 1 .AND. idimsz(3) == 1 .AND. idmspc == 3 ) THEN
620                  CALL ctl_warn( trim(clinfo), '2D array but 3 spatial dimensions for the data...'              ,   &
621                        &         'As the size of the z dimension is 1 and as we try to read the first record, ',   &
622                        &         'we accept this case, even if there is a possible mix-up between z and time dimension' )   
623                  idmspc = idmspc - 1
[544]624               ELSE
[679]625                  CALL ctl_stop( TRIM(clinfo), 'To keep iom lisibility, when reading a '//clrankpv//'D array,'         ,   &
626                     &                         'we do not accept data with more than '//cldmspc//' spatial dimension',   &
627                     &                         'Use ncwa -a to suppress the unnecessary dimensions' )
[544]628               ENDIF
[679]629         ENDIF
630
631         !
632         ! definition of istart and icnt
633         !
634         icnt  (:) = 1
635         istart(:) = 1
636         istart(idmspc+1) = itime
637
638         IF(              PRESENT(kstart)       ) THEN ; istart(1:idmspc) = kstart(1:idmspc) ; icnt(1:idmspc) = kcount(1:idmspc)
639         ELSE
640            IF(           idom == jpdom_unknown ) THEN                                       ; icnt(1:idmspc) = idimsz(1:idmspc)
641            ELSE
642               IF( .NOT. PRESENT(pv_r1d) ) THEN   !   not a 1D array
643                  IF(     idom == jpdom_data    ) THEN ; istart(1:2) = (/ mig(1), mjg(1) /)  ! icnt(1:2) done bellow
644                  ELSEIF( idom == jpdom_global  ) THEN ; istart(1:2) = (/ nimpp , njmpp  /)  ! icnt(1:2) done bellow
[544]645                  ENDIF
[679]646                  ! we do not read the overlap                     -> we start to read at nldi, nldj
647! JMM + SM: ugly patch before getting the new version of lib_mpp)
648!                  IF( idom /= jpdom_local_noovlap )   istart(1:2) = istart(1:2) + (/ nldi - 1, nldj - 1 /)
[1200]649                  IF( llnoov .AND. idom /= jpdom_local_noovlap ) istart(1:2) = istart(1:2) + (/ nldi - 1, nldj - 1 /)
[679]650                  ! we do not read the overlap and the extra-halos -> from nldi to nlei and from nldj to nlej
651! JMM + SM: ugly patch before getting the new version of lib_mpp)
652!                  icnt(1:2) = (/ nlei - nldi + 1, nlej - nldj + 1 /)
[1200]653                  IF( llnoov ) THEN   ;   icnt(1:2) = (/ nlei - nldi + 1, nlej - nldj + 1 /)
654                  ELSE                ;   icnt(1:2) = (/ nlci           , nlcj            /)
[544]655                  ENDIF
[679]656                  IF( PRESENT(pv_r3d) ) THEN
657                     IF( idom == jpdom_data ) THEN   ; icnt(3) = jpkdta
658                     ELSE                            ; icnt(3) = jpk
[544]659                     ENDIF
660                  ENDIF
661               ENDIF
[679]662            ENDIF
[544]663         ENDIF
664
665         ! check that istart and icnt can be used with this file
666         !-
667         DO jl = 1, jpmax_dims
668            itmp = istart(jl)+icnt(jl)-1
[679]669            IF( itmp > idimsz(jl) .AND. idimsz(jl) /= 0 ) THEN
670               WRITE( ctmp1, FMT="('(istart(', i1, ') + icnt(', i1, ') - 1) = ', i5)" ) jl, jl, itmp
671               WRITE( ctmp2, FMT="(' is larger than idimsz(', i1,') = ', i5)"         ) jl, idimsz(jl)
[544]672               CALL ctl_stop( trim(clinfo), 'start and count too big regarding to the size of the data, ', ctmp1, ctmp2 )     
673            ENDIF
674         END DO
675
676         ! check that icnt matches the input array
677         !-     
[679]678         IF( idom == jpdom_unknown ) THEN
679            IF( irankpv == 1 )        ishape(1:1) = SHAPE(pv_r1d)
680            IF( irankpv == 2 )        ishape(1:2) = SHAPE(pv_r2d)
681            IF( irankpv == 3 )        ishape(1:3) = SHAPE(pv_r3d)
682            ctmp1 = 'd'
683         ELSE
684            IF( irankpv == 2 ) THEN
685! JMM + SM: ugly patch before getting the new version of lib_mpp)
686!               ishape(1:2) = SHAPE(pv_r2d(nldi:nlei,nldj:nlej  ))   ;   ctmp1 = 'd(nldi:nlei,nldj:nlej)'
[1200]687               IF( llnoov ) THEN ; ishape(1:2)=SHAPE(pv_r2d(nldi:nlei,nldj:nlej  )) ; ctmp1='d(nldi:nlei,nldj:nlej)'
688               ELSE              ; ishape(1:2)=SHAPE(pv_r2d(1   :nlci,1   :nlcj  )) ; ctmp1='d(1:nlci,1:nlcj)'
[544]689               ENDIF
[679]690            ENDIF
691            IF( irankpv == 3 ) THEN 
692! JMM + SM: ugly patch before getting the new version of lib_mpp)
693!               ishape(1:3) = SHAPE(pv_r3d(nldi:nlei,nldj:nlej,:))   ;   ctmp1 = 'd(nldi:nlei,nldj:nlej,:)'
[1200]694               IF( llnoov ) THEN ; ishape(1:3)=SHAPE(pv_r3d(nldi:nlei,nldj:nlej,:)) ; ctmp1='d(nldi:nlei,nldj:nlej,:)'
695               ELSE              ; ishape(1:3)=SHAPE(pv_r3d(1   :nlci,1   :nlcj,:)) ; ctmp1='d(1:nlci,1:nlcj,:)'
[544]696               ENDIF
[679]697            ENDIF
[544]698         ENDIF
[679]699         
700         DO jl = 1, irankpv
701            WRITE( ctmp2, FMT="(', ', i1,'): ', i5,' /= icnt(', i1,'):', i5)" ) jl, ishape(jl), jl, icnt(jl)
702            IF( ishape(jl) /= icnt(jl) )   CALL ctl_stop( TRIM(clinfo), 'size(pv_r'//clrankpv//TRIM(ctmp1)//TRIM(ctmp2) )
703         END DO
704
[544]705      ENDIF
706
707      ! read the data
708      !-     
[679]709      IF( idvar > 0 .AND. istop == nstop ) THEN   ! no additional errors until this point...
[544]710         !
[679]711         ! find the right index of the array to be read
712! JMM + SM: ugly patch before getting the new version of lib_mpp)
713!         IF( idom /= jpdom_unknown ) THEN   ;   ix1 = nldi   ;   ix2 = nlei      ;   iy1 = nldj   ;   iy2 = nlej
714!         ELSE                               ;   ix1 = 1      ;   ix2 = icnt(1)   ;   iy1 = 1      ;   iy2 = icnt(2)
715!         ENDIF
[1200]716         IF( llnoov ) THEN
[679]717            IF( idom /= jpdom_unknown ) THEN   ;   ix1 = nldi   ;   ix2 = nlei      ;   iy1 = nldj   ;   iy2 = nlej
718            ELSE                               ;   ix1 = 1      ;   ix2 = icnt(1)   ;   iy1 = 1      ;   iy2 = icnt(2)
719            ENDIF
720         ELSE
721            IF( idom /= jpdom_unknown ) THEN   ;   ix1 = 1      ;   ix2 = nlci      ;   iy1 = 1      ;   iy2 = nlcj
722            ELSE                               ;   ix1 = 1      ;   ix2 = icnt(1)   ;   iy1 = 1      ;   iy2 = icnt(2)
723            ENDIF
724         ENDIF
725     
[544]726         SELECT CASE (iom_file(kiomid)%iolib)
[679]727         CASE (jpioipsl )   ;   CALL iom_ioipsl_get(  kiomid, idvar, inbdim, istart, icnt, ix1, ix2, iy1, iy2,   &
728            &                                         pv_r1d, pv_r2d, pv_r3d )
729         CASE (jpnf90   )   ;   CALL iom_nf90_get(    kiomid, idvar, inbdim, istart, icnt, ix1, ix2, iy1, iy2,   &
730            &                                         pv_r1d, pv_r2d, pv_r3d )
731         CASE (jprstdimg)   ;   CALL iom_rstdimg_get( kiomid, idom, idvar, ix1, ix2, iy1, iy2,   &
732            &                                         pv_r1d, pv_r2d, pv_r3d )
[544]733         CASE DEFAULT   
734            CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' )
735         END SELECT
[679]736
737         IF( istop == nstop ) THEN   ! no additional errors until this point...
[1191]738            IF(lwp) WRITE(numout,"(10x,' read ',a,' (rec: ',i4,') in ',a,' ok')") TRIM(cdvar), itime, TRIM(iom_file(kiomid)%name)
739         
[679]740            !--- overlap areas and extra hallows (mpp)
741            IF(     PRESENT(pv_r2d) .AND. idom /= jpdom_unknown ) THEN
742               CALL lbc_lnk( pv_r2d,'Z',-999.,'no0' )
743            ELSEIF( PRESENT(pv_r3d) .AND. idom /= jpdom_unknown ) THEN
744               ! this if could be simplified with the new lbc_lnk that works with any size of the 3rd dimension
745               IF( icnt(3) == jpk ) THEN
746                  CALL lbc_lnk( pv_r3d,'Z',-999.,'no0' )
747               ELSE   ! put some arbitrary value (a call to lbc_lnk will be done later...)
748                  DO jj = nlcj+1, jpj   ;   pv_r3d(1:nlci, jj, :) = pv_r3d(1:nlci, nlej, :)   ;   END DO
749                  DO ji = nlci+1, jpi   ;   pv_r3d(ji    , : , :) = pv_r3d(nlei  , :   , :)   ;   END DO
750               ENDIF
751            ENDIF
752           
753            !--- Apply scale_factor and offset
754            zscf = iom_file(kiomid)%scf(idvar)      ! scale factor
755            zofs = iom_file(kiomid)%ofs(idvar)      ! offset
756            IF(     PRESENT(pv_r1d) ) THEN
757               IF( zscf /= 1. )   pv_r1d(:) = pv_r1d(:) * zscf 
758               IF( zofs /= 0. )   pv_r1d(:) = pv_r1d(:) + zofs
759            ELSEIF( PRESENT(pv_r2d) ) THEN
[1697]760!CDIR COLLAPSE
[679]761               IF( zscf /= 1.)   pv_r2d(:,:) = pv_r2d(:,:) * zscf
[1697]762!CDIR COLLAPSE
[679]763               IF( zofs /= 0.)   pv_r2d(:,:) = pv_r2d(:,:) + zofs
764            ELSEIF( PRESENT(pv_r3d) ) THEN
[1697]765!CDIR COLLAPSE
[679]766               IF( zscf /= 1.)   pv_r3d(:,:,:) = pv_r3d(:,:,:) * zscf
[1697]767!CDIR COLLAPSE
[679]768               IF( zofs /= 0.)   pv_r3d(:,:,:) = pv_r3d(:,:,:) + zofs
769            ENDIF
770            !
[544]771         ENDIF
772         !
773      ENDIF
774      !
775   END SUBROUTINE iom_get_123d
776
777
[911]778   SUBROUTINE iom_gettime( kiomid, ptime, cdvar, kntime, cdunits, cdcalendar )
[544]779      !!--------------------------------------------------------------------
780      !!                   ***  SUBROUTINE iom_gettime  ***
781      !!
782      !! ** Purpose : read the time axis cdvar in the file
783      !!--------------------------------------------------------------------
[911]784      INTEGER                    , INTENT(in   ) ::   kiomid     ! file Identifier
785      REAL(wp), DIMENSION(:)     , INTENT(  out) ::   ptime      ! the time axis
786      CHARACTER(len=*), OPTIONAL , INTENT(in   ) ::   cdvar      ! time axis name
787      INTEGER         , OPTIONAL , INTENT(  out) ::   kntime     ! number of times in file
788      CHARACTER(len=*), OPTIONAL , INTENT(  out) ::   cdunits    ! units attribute of time coordinate
789      CHARACTER(len=*), OPTIONAL , INTENT(  out) ::   cdcalendar ! calendar attribute of
[544]790      !
[911]791      INTEGER, DIMENSION(1) :: kdimsz
[544]792      INTEGER            ::   idvar    ! id of the variable
[911]793      CHARACTER(LEN=32)  ::   tname    ! local name of time coordinate
[544]794      CHARACTER(LEN=100) ::   clinfo   ! info character
795      !---------------------------------------------------------------------
796      !
[911]797      IF ( PRESENT(cdvar) ) THEN
798         tname = cdvar
799      ELSE
800         tname = iom_file(kiomid)%uldname
801      ENDIF
[679]802      IF( kiomid > 0 ) THEN
[911]803         clinfo = 'iom_gettime, file: '//trim(iom_file(kiomid)%name)//', var: '//trim(tname)
804         IF ( PRESENT(kntime) ) THEN
805            idvar  = iom_varid( kiomid, tname, kdimsz = kdimsz )
806            kntime = kdimsz(1)
807         ELSE
808            idvar = iom_varid( kiomid, tname )
809         ENDIF
[679]810         !
811         ptime(:) = 0. ! default definition
812         IF( idvar > 0 ) THEN
813            IF( iom_file(kiomid)%ndims(idvar) == 1 ) THEN
814               IF( iom_file(kiomid)%luld(idvar) ) THEN
[2499]815                  IF( iom_file(kiomid)%dimsz(1,idvar) <= size(ptime) ) THEN
[679]816                     SELECT CASE (iom_file(kiomid)%iolib)
[911]817                     CASE (jpioipsl )   ;   CALL iom_ioipsl_gettime( kiomid, idvar, ptime, cdunits, cdcalendar )
818                     CASE (jpnf90   )   ;   CALL iom_nf90_gettime(   kiomid, idvar, ptime, cdunits, cdcalendar )
[679]819                     CASE (jprstdimg)   ;   CALL ctl_stop( TRIM(clinfo)//' case IO library == jprstdimg not coded...' )
820                     CASE DEFAULT   
821                        CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' )
822                     END SELECT
823                  ELSE
824                     WRITE(ctmp1,*) 'error with the size of ptime ',size(ptime),iom_file(kiomid)%dimsz(1,idvar)
825                     CALL ctl_stop( trim(clinfo), trim(ctmp1) )
826                  ENDIF
[544]827               ELSE
[679]828                  CALL ctl_stop( trim(clinfo), 'variable dimension is not unlimited... use iom_get' )
[544]829               ENDIF
830            ELSE
[679]831               CALL ctl_stop( trim(clinfo), 'the variable has more than 1 dimension' )
[544]832            ENDIF
833         ELSE
[679]834            CALL ctl_stop( trim(clinfo), 'variable not found in '//iom_file(kiomid)%name )
[544]835         ENDIF
836      ENDIF
837      !
838   END SUBROUTINE iom_gettime
839
840
841   !!----------------------------------------------------------------------
[2528]842   !!                   INTERFACE iom_getatt
843   !!----------------------------------------------------------------------
844   SUBROUTINE iom_g0d_intatt( kiomid, cdatt, pvar )
845      INTEGER         , INTENT(in   )                 ::   kiomid    ! Identifier of the file
846      CHARACTER(len=*), INTENT(in   )                 ::   cdatt     ! Name of the attribute
847      INTEGER         , INTENT(  out)                 ::   pvar      ! read field
848      !
849      IF( kiomid > 0 ) THEN
850         IF( iom_file(kiomid)%nfid > 0 ) THEN
851            SELECT CASE (iom_file(kiomid)%iolib)
852            CASE (jpioipsl )   ;   CALL ctl_stop('iom_getatt: only nf90 available')
853            CASE (jpnf90   )   ;   CALL iom_nf90_getatt( kiomid, cdatt, pvar )
854            CASE (jprstdimg)   ;   CALL ctl_stop('iom_getatt: only nf90 available')
855            CASE DEFAULT   
856               CALL ctl_stop( 'iom_g0d_att: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' )
857            END SELECT
858         ENDIF
859      ENDIF
860   END SUBROUTINE iom_g0d_intatt
861
862
863   !!----------------------------------------------------------------------
[544]864   !!                   INTERFACE iom_rstput
865   !!----------------------------------------------------------------------
[550]866   SUBROUTINE iom_rp0d( kt, kwrite, kiomid, cdvar, pvar, ktype )
[544]867      INTEGER         , INTENT(in)                         ::   kt       ! ocean time-step
868      INTEGER         , INTENT(in)                         ::   kwrite   ! writing time-step
869      INTEGER         , INTENT(in)                         ::   kiomid   ! Identifier of the file
870      CHARACTER(len=*), INTENT(in)                         ::   cdvar    ! time axis name
[556]871      REAL(wp)        , INTENT(in)                         ::   pvar     ! written field
[544]872      INTEGER         , INTENT(in), OPTIONAL               ::   ktype    ! variable external type
873      INTEGER :: ivid   ! variable id
[679]874      IF( kiomid > 0 ) THEN
875         IF( iom_file(kiomid)%nfid > 0 ) THEN
[745]876            ivid = iom_varid( kiomid, cdvar, ldstop = .FALSE. )
[679]877            SELECT CASE (iom_file(kiomid)%iolib)
878            CASE (jpioipsl )   ;   CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r0d = pvar )
879            CASE (jpnf90   )   ;   CALL iom_nf90_rstput(   kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r0d = pvar )
880            CASE (jprstdimg)   ;   IF( kt == kwrite )    CALL iom_rstdimg_rstput( kiomid, cdvar, ivid, pvar )
881            CASE DEFAULT     
882               CALL ctl_stop( 'iom_rp0d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' )
883            END SELECT
884         ENDIF
885      ENDIF
[550]886   END SUBROUTINE iom_rp0d
[544]887
[550]888   SUBROUTINE iom_rp1d( kt, kwrite, kiomid, cdvar, pvar, ktype )
[544]889      INTEGER         , INTENT(in)                         ::   kt       ! ocean time-step
890      INTEGER         , INTENT(in)                         ::   kwrite   ! writing time-step
891      INTEGER         , INTENT(in)                         ::   kiomid   ! Identifier of the file
892      CHARACTER(len=*), INTENT(in)                         ::   cdvar    ! time axis name
[2715]893      REAL(wp)        , INTENT(in), DIMENSION(          :) ::   pvar     ! written field
[544]894      INTEGER         , INTENT(in), OPTIONAL               ::   ktype    ! variable external type
895      INTEGER :: ivid   ! variable id
[679]896      IF( kiomid > 0 ) THEN
897         IF( iom_file(kiomid)%nfid > 0 ) THEN
[745]898            ivid = iom_varid( kiomid, cdvar, ldstop = .FALSE. )
[679]899            SELECT CASE (iom_file(kiomid)%iolib)
900            CASE (jpioipsl )   ;   CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r1d = pvar )
901            CASE (jpnf90   )   ;   CALL iom_nf90_rstput(   kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r1d = pvar )
902            CASE (jprstdimg)   ;   IF( kt == kwrite )    CALL iom_rstdimg_rstput( kiomid, cdvar, ivid, pv_r1d = pvar )
903            CASE DEFAULT     
904               CALL ctl_stop( 'iom_rp1d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' )
905            END SELECT
906         ENDIF
907      ENDIF
[550]908   END SUBROUTINE iom_rp1d
[544]909
[550]910   SUBROUTINE iom_rp2d( kt, kwrite, kiomid, cdvar, pvar, ktype )
[544]911      INTEGER         , INTENT(in)                         ::   kt       ! ocean time-step
912      INTEGER         , INTENT(in)                         ::   kwrite   ! writing time-step
913      INTEGER         , INTENT(in)                         ::   kiomid   ! Identifier of the file
914      CHARACTER(len=*), INTENT(in)                         ::   cdvar    ! time axis name
[2715]915      REAL(wp)        , INTENT(in), DIMENSION(:,    :    ) ::   pvar     ! written field
[544]916      INTEGER         , INTENT(in), OPTIONAL               ::   ktype    ! variable external type
917      INTEGER :: ivid   ! variable id
[679]918      IF( kiomid > 0 ) THEN
919         IF( iom_file(kiomid)%nfid > 0 ) THEN
[745]920            ivid = iom_varid( kiomid, cdvar, ldstop = .FALSE. )
[679]921            SELECT CASE (iom_file(kiomid)%iolib)
922            CASE (jpioipsl )   ;   CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r2d = pvar )
923            CASE (jpnf90   )   ;   CALL iom_nf90_rstput(   kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r2d = pvar )
924            CASE (jprstdimg)   ;   IF( kt == kwrite )   CALL iom_rstdimg_rstput( kiomid, cdvar, ivid, pv_r2d = pvar ) 
925            CASE DEFAULT     
926               CALL ctl_stop( 'iom_rp2d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' )
927            END SELECT
928         ENDIF
929      ENDIF
[550]930   END SUBROUTINE iom_rp2d
[544]931
[550]932   SUBROUTINE iom_rp3d( kt, kwrite, kiomid, cdvar, pvar, ktype )
[544]933      INTEGER         , INTENT(in)                         ::   kt       ! ocean time-step
934      INTEGER         , INTENT(in)                         ::   kwrite   ! writing time-step
935      INTEGER         , INTENT(in)                         ::   kiomid   ! Identifier of the file
936      CHARACTER(len=*), INTENT(in)                         ::   cdvar    ! time axis name
[2715]937      REAL(wp)        , INTENT(in),       DIMENSION(:,:,:) ::   pvar     ! written field
[544]938      INTEGER         , INTENT(in), OPTIONAL               ::   ktype    ! variable external type
939      INTEGER :: ivid   ! variable id
[679]940      IF( kiomid > 0 ) THEN
941         IF( iom_file(kiomid)%nfid > 0 ) THEN
[745]942            ivid = iom_varid( kiomid, cdvar, ldstop = .FALSE. )
[679]943            SELECT CASE (iom_file(kiomid)%iolib)
944            CASE (jpioipsl )   ;   CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r3d = pvar )
945            CASE (jpnf90   )   ;   CALL iom_nf90_rstput(   kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r3d = pvar )
946            CASE (jprstdimg)   ;   IF( kt == kwrite )   CALL iom_rstdimg_rstput( kiomid, cdvar, ivid, pv_r3d = pvar )
947            CASE DEFAULT     
948               CALL ctl_stop( 'iom_rp3d: accepted IO library are only jpioipsl and jprstdimg' )
949            END SELECT
950         ENDIF
951      ENDIF
[550]952   END SUBROUTINE iom_rp3d
[1359]953
954
[544]955   !!----------------------------------------------------------------------
[1457]956   !!                   INTERFACE iom_put
[1359]957   !!----------------------------------------------------------------------
[1738]958   SUBROUTINE iom_p0d( cdname, pfield0d )
959      CHARACTER(LEN=*), INTENT(in) ::   cdname
960      REAL(wp)        , INTENT(in) ::   pfield0d
961#if defined key_iomput
962      CALL event__write_field2D( cdname, RESHAPE( (/pfield0d/), (/1,1/) ) )
963#else
964      IF( .FALSE. )   WRITE(numout,*) cdname, pfield0d   ! useless test to avoid compilation warnings
965#endif
966   END SUBROUTINE iom_p0d
967
[2839]968   SUBROUTINE iom_p1d( cdname, pfield1d )
969      CHARACTER(LEN=*)          , INTENT(in) ::   cdname
970      REAL(wp),     DIMENSION(:), INTENT(in) ::   pfield1d
971      INTEGER :: jpn
972#if defined key_iomput
973      CALL event__write_field3D( cdname, RESHAPE( (/pfield1d/), (/1,1,jpn/) ) )
974#else
975      IF( .FALSE. )   WRITE(numout,*) cdname, pfield1d   ! useless test to avoid compilation warnings
976#endif
977   END SUBROUTINE iom_p1d
978
[1359]979   SUBROUTINE iom_p2d( cdname, pfield2d )
980      CHARACTER(LEN=*)            , INTENT(in) ::   cdname
[2715]981      REAL(wp),     DIMENSION(:,:), INTENT(in) ::   pfield2d
[1412]982#if defined key_iomput
[1359]983      CALL event__write_field2D( cdname, pfield2d(nldi:nlei, nldj:nlej) )
[1520]984#else
985      IF( .FALSE. )   WRITE(numout,*) cdname, pfield2d   ! useless test to avoid compilation warnings
[1359]986#endif
987   END SUBROUTINE iom_p2d
[544]988
[1359]989   SUBROUTINE iom_p3d( cdname, pfield3d )
990      CHARACTER(LEN=*)                , INTENT(in) ::   cdname
[2715]991      REAL(wp),       DIMENSION(:,:,:), INTENT(in) ::   pfield3d
[1412]992#if defined key_iomput
[1359]993      CALL event__write_field3D( cdname, pfield3d(nldi:nlei, nldj:nlej, :) )
[1520]994#else
995      IF( .FALSE. )   WRITE(numout,*) cdname, pfield3d   ! useless test to avoid compilation warnings
[1359]996#endif
997   END SUBROUTINE iom_p3d
998   !!----------------------------------------------------------------------
[544]999
[1359]1000
[1412]1001#if defined key_iomput
[1359]1002
1003   SUBROUTINE set_grid( cdname, plon, plat )
1004      !!----------------------------------------------------------------------
1005      !!                     ***  ROUTINE   ***
1006      !!
[1725]1007      !! ** Purpose :   define horizontal grids
[1359]1008      !!
1009      !!----------------------------------------------------------------------
1010      CHARACTER(LEN=*)            , INTENT(in) ::   cdname
1011      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) ::   plon
1012      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) ::   plat
1013
1014      CALL event__set_grid_dimension( cdname, jpiglo, jpjglo)
1015      CALL event__set_grid_domain( cdname, nlei-nldi+1, nlej-nldj+1, nimpp+nldi-1, njmpp+nldj-1, &
1016         &                         plon(nldi:nlei, nldj:nlej), plat(nldi:nlei, nldj:nlej) )
1017      CALL event__set_grid_type_nemo( cdname )
1018
1019   END SUBROUTINE set_grid
1020
[1725]1021
[1738]1022   SUBROUTINE set_scalar
1023      !!----------------------------------------------------------------------
1024      !!                     ***  ROUTINE   ***
1025      !!
1026      !! ** Purpose :   define fake grids for scalar point
1027      !!
1028      !!----------------------------------------------------------------------
1029      REAL(wp), DIMENSION(1,1) ::   zz = 1.
1030      !!----------------------------------------------------------------------
1031      CALL event__set_grid_dimension( 'scalarpoint', jpnij, 1)
1032      CALL event__set_grid_domain   ( 'scalarpoint', 1, 1, narea, 1, zz, zz )
1033      CALL event__set_grid_type_nemo( 'scalarpoint' )
1034
1035   END SUBROUTINE set_scalar
1036
1037
[1725]1038   SUBROUTINE set_xmlatt
1039      !!----------------------------------------------------------------------
1040      !!                     ***  ROUTINE   ***
1041      !!
1042      !! ** Purpose :   automatic definitions of some of the xml attributs...
1043      !!
1044      !!----------------------------------------------------------------------
[1743]1045      CHARACTER(len=6),DIMENSION( 8) ::   clsuff                   ! suffix name
[1725]1046      CHARACTER(len=1),DIMENSION( 3) ::   clgrd                    ! suffix name
1047      CHARACTER(len=50)              ::   clname                   ! file name
1048      CHARACTER(len=1)               ::   cl1                      ! 1 character
1049      CHARACTER(len=2)               ::   cl2                      ! 1 character
1050      INTEGER                        ::   idt                      ! time-step in seconds
[1731]1051      INTEGER                        ::   iddss, ihhss             ! number of seconds in 1 day, 1 hour and 1 year
1052      INTEGER                        ::   iyymo                    ! number of months in 1 year
1053      INTEGER                        ::   jg, jh, jd, jm, jy       ! loop counters
[1725]1054      INTEGER                        ::   ix, iy                   ! i-,j- index
1055      REAL(wp)        ,DIMENSION(11) ::   zlontao                  ! longitudes of tao    moorings
1056      REAL(wp)        ,DIMENSION( 7) ::   zlattao                  ! latitudes  of tao    moorings
1057      REAL(wp)        ,DIMENSION( 4) ::   zlonrama                 ! longitudes of rama   moorings
1058      REAL(wp)        ,DIMENSION(11) ::   zlatrama                 ! latitudes  of rama   moorings
1059      REAL(wp)        ,DIMENSION( 3) ::   zlonpira                 ! longitudes of pirata moorings
1060      REAL(wp)        ,DIMENSION( 9) ::   zlatpira                 ! latitudes  of pirata moorings
1061      !!----------------------------------------------------------------------
1062      !
1063      idt   = NINT( rdttra(1)     )
1064      iddss = NINT( rday          )                                         ! number of seconds in 1 day
1065      ihhss = NINT( rmmss * rhhmm )                                         ! number of seconds in 1 hour
[1731]1066      iyymo = NINT( raamo         )                                         ! number of months in 1 year
[1725]1067
1068      ! frequency of the call of iom_put (attribut: freq_op)
1069      CALL event__set_attribut( 'field_definition', attr( field__freq_op, idt           ) )    ! model time-step
1070      CALL event__set_attribut( 'SBC'             , attr( field__freq_op, idt * nn_fsbc ) )    ! SBC time-step
1071     
1072      ! output file names (attribut: name)
[1743]1073      clsuff(:) = (/ 'grid_T', 'grid_U', 'grid_V', 'grid_W', 'icemod', 'ptrc_T', 'diad_T', 'scalar' /)     
[1725]1074      DO jg = 1, SIZE(clsuff)                                                                  ! grid type
1075         DO jh = 1, 12                                                                         ! 1, 2, 3, 4, 6, 12 hours
1076            IF( MOD(12,jh) == 0 ) THEN
1077               WRITE(cl2,'(i2)') jh 
1078               CALL dia_nam( clname, jh * ihhss, clsuff(jg), ldfsec = .TRUE. )
1079               CALL event__set_attribut( TRIM(ADJUSTL(cl2))//'h_'//clsuff(jg), attr( file__name, TRIM(clname) ) )
1080            ENDIF
1081         END DO
1082         DO jd = 1, 5, 2                                                                       ! 1, 3, 5 days
1083            WRITE(cl1,'(i1)') jd 
1084            CALL dia_nam( clname, jd * iddss, clsuff(jg), ldfsec = .TRUE. )
1085            CALL event__set_attribut( cl1//'d_'//clsuff(jg), attr( file__name, TRIM(clname) ) )
1086         END DO
[1731]1087         DO jm = 1, 6                                                                          ! 1, 2, 3, 4, 6 months
1088            IF( MOD(6,jm) == 0 ) THEN
1089               WRITE(cl1,'(i1)') jm 
1090               CALL dia_nam( clname, -jm, clsuff(jg) )
1091               CALL event__set_attribut( cl1//'m_'//clsuff(jg), attr( file__name, TRIM(clname) ) )
1092            ENDIF
1093         END DO
[1725]1094         DO jy = 1, 10                                                                         ! 1, 2, 5, 10 years 
1095            IF( MOD(10,jy) == 0 ) THEN
1096               WRITE(cl2,'(i2)') jy 
[1731]1097               CALL dia_nam( clname, -jy * iyymo, clsuff(jg) )
[1725]1098               CALL event__set_attribut( TRIM(ADJUSTL(cl2))//'y_'//clsuff(jg), attr( file__name, TRIM(clname) ) )
1099            ENDIF
1100         END DO
1101      END DO
1102
1103      ! Zooms...
1104      clgrd = (/ 'T', 'U', 'W' /) 
1105      DO jg = 1, SIZE(clgrd)                                                                   ! grid type
1106         cl1 = clgrd(jg)
1107         ! Equatorial section (attributs: jbegin, ni, name_suffix)
1108         CALL dom_ngb( 0., 0., ix, iy, cl1 )
1109         CALL event__set_attribut( 'Eq'//cl1, attr( zoom__jbegin     , iy     ) )
1110         CALL event__set_attribut( 'Eq'//cl1, attr( zoom__ni         , jpiglo ) )
1111         CALL event__set_attribut( 'Eq'//cl1, attr( file__name_suffix, '_Eq'  ) )
1112      END DO
1113      ! TAO moorings (attributs: ibegin, jbegin, name_suffix)
1114      zlontao = (/ 137.0, 147.0, 156.0, 165.0, -180.0, -170.0, -155.0, -140.0, -125.0, -110.0, -95.0 /)
1115      zlattao = (/  -8.0,  -5.0,  -2.0,   0.0,    2.0,    5.0,    8.0 /)
1116      CALL set_mooring( zlontao, zlattao )
1117      ! RAMA moorings (attributs: ibegin, jbegin, name_suffix)
1118      zlonrama = (/  55.0,  67.0, 80.5, 90.0 /)
1119      zlatrama = (/ -16.0, -12.0, -8.0, -4.0, -1.5, 0.0, 1.5, 4.0, 8.0, 12.0, 15.0 /)
1120      CALL set_mooring( zlonrama, zlatrama )
1121      ! PIRATA moorings (attributs: ibegin, jbegin, name_suffix)
1122      zlonpira = (/ -38.0, -23.0, -10.0 /)
1123      zlatpira = (/ -19.0, -14.0,  -8.0, 0.0, 4.0, 8.0, 12.0, 15.0, 20.0 /)
1124      CALL set_mooring( zlonpira, zlatpira )
1125     
1126   END SUBROUTINE set_xmlatt
1127
1128
1129   SUBROUTINE set_mooring( plon, plat)
1130      !!----------------------------------------------------------------------
1131      !!                     ***  ROUTINE   ***
1132      !!
1133      !! ** Purpose :   automatic definitions of moorings xml attributs...
1134      !!
1135      !!----------------------------------------------------------------------
1136      REAL(wp), DIMENSION(:), INTENT(in) ::  plon, plat           ! longitudes/latitudes oft the mooring
1137      !
1138!!$      CHARACTER(len=1),DIMENSION(4) ::   clgrd = (/ 'T', 'U', 'V', 'W' /)   ! suffix name
1139      CHARACTER(len=1),DIMENSION(1) ::   clgrd = (/ 'T' /)        ! suffix name
1140      CHARACTER(len=50)             ::   clname                   ! file name
1141      CHARACTER(len=1)              ::   cl1                      ! 1 character
1142      CHARACTER(len=6)              ::   clon,clat                ! name of longitude, latitude
1143      INTEGER                       ::   ji, jj, jg               ! loop counters
1144      INTEGER                       ::   ix, iy                   ! i-,j- index
1145      REAL(wp)                      ::   zlon, zlat
1146      !!----------------------------------------------------------------------
1147      DO jg = 1, SIZE(clgrd)
1148         cl1 = clgrd(jg)
1149         DO ji = 1, SIZE(plon)
1150            DO jj = 1, SIZE(plat)
1151               zlon = plon(ji)
1152               zlat = plat(jj)
1153               ! modifications for RAMA moorings
1154               IF( zlon ==  67. .AND. zlat ==  15. )   zlon =  65.
1155               IF( zlon ==  90. .AND. zlat <=  -4. )   zlon =  95.
1156               IF( zlon ==  95. .AND. zlat ==  -4. )   zlat =  -5.
1157               ! modifications for PIRATA moorings
1158               IF( zlon == -38. .AND. zlat == -19. )   zlon = -34.
1159               IF( zlon == -38. .AND. zlat == -14. )   zlon = -32.
1160               IF( zlon == -38. .AND. zlat ==  -8. )   zlon = -30.
1161               IF( zlon == -38. .AND. zlat ==   0. )   zlon = -35.
1162               IF( zlon == -23. .AND. zlat ==  20. )   zlat =  21.
1163               IF( zlon == -10. .AND. zlat == -14. )   zlat = -10.
1164               IF( zlon == -10. .AND. zlat ==  -8. )   zlat =  -6.
1165               IF( zlon == -10. .AND. zlat ==   4. ) THEN   ;   zlon = 0.   ;   zlat = 0.   ;   ENDIF
1166               CALL dom_ngb( zlon, zlat, ix, iy, cl1 )
1167               IF( zlon >= 0. ) THEN 
1168                  IF( zlon == REAL(NINT(zlon), wp) ) THEN   ;   WRITE(clon, '(i3,  a)') NINT( zlon), 'e'
1169                  ELSE                                      ;   WRITE(clon, '(f5.1,a)')       zlon , 'e'
1170                  ENDIF
1171               ELSE             
1172                  IF( zlon == REAL(NINT(zlon), wp) ) THEN   ;   WRITE(clon, '(i3,  a)') NINT(-zlon), 'w'
1173                  ELSE                                      ;   WRITE(clon, '(f5.1,a)')      -zlon , 'w'
1174                  ENDIF
1175               ENDIF
1176               IF( zlat >= 0. ) THEN 
1177                  IF( zlat == REAL(NINT(zlat), wp) ) THEN   ;   WRITE(clat, '(i2,  a)') NINT( zlat), 'n'
1178                  ELSE                                      ;   WRITE(clat, '(f4.1,a)')       zlat , 'n'
1179                  ENDIF
1180               ELSE             
1181                  IF( zlat == REAL(NINT(zlat), wp) ) THEN   ;   WRITE(clat, '(i2,  a)') NINT(-zlat), 's'
1182                  ELSE                                      ;   WRITE(clat, '(f4.1,a)')      -zlat , 's'
1183                  ENDIF
1184               ENDIF
1185               clname = TRIM(ADJUSTL(clat))//TRIM(ADJUSTL(clon))
1186               CALL event__set_attribut( TRIM(clname)//cl1, attr( zoom__ibegin     , ix                ) )
1187               CALL event__set_attribut( TRIM(clname)//cl1, attr( zoom__jbegin     , iy                ) )
1188               CALL event__set_attribut( TRIM(clname)//cl1, attr( file__name_suffix, '_'//TRIM(clname) ) )     
1189            END DO
1190         END DO
1191      END DO
1192     
1193   END SUBROUTINE set_mooring
1194
[1359]1195#else
1196
1197   SUBROUTINE iom_setkt( kt )
1198      INTEGER, INTENT(in   )::   kt 
[1520]1199      IF( .FALSE. )   WRITE(numout,*) kt   ! useless test to avoid compilation warnings
[1359]1200   END SUBROUTINE iom_setkt
1201
1202#endif
1203
1204
[544]1205   !!======================================================================
1206END MODULE iom
Note: See TracBrowser for help on using the repository browser.