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/CMIP5_IPSL/NEMO/OFF_SRC/IOM – NEMO

source: branches/CMIP5_IPSL/NEMO/OFF_SRC/IOM/iom.F90 @ 1830

Last change on this file since 1830 was 1830, checked in by cetlod, 14 years ago

Computation of additional diagnostics for PISCES model ( under CPP key key_diaar5 )

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