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.
Changeset 679 for trunk/NEMO – NEMO

Changeset 679 for trunk/NEMO


Ignore:
Timestamp:
2007-06-29T18:29:31+02:00 (17 years ago)
Author:
rblod
Message:

nemo_v2_update_018 : SM : improve IOM
nemo_v2_bugfix_049 : SM : Patch to work when jpni*jpnj /= jpnij
nemo_v2_update_020 : SM : add jpdom_autoglo and jpdom_autodta
nemo_v2_bugfix_053 : SM : make sure everything is ok when kiomid <= 0
nemo_v2_bugfix_054 : RB : correct a bug in mpp with iom and suppress useless dummy arguments

Location:
trunk/NEMO/OPA_SRC/IOM
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r631 r679  
    8484   !!---------------------------------------------------------------------- 
    8585   !!  OPA 9.0 , LOCEAN-IPSL (2005)  
    86    !! $Header$  
     86   !! $Header: /home/opalod/NEMOCVSROOT/NEMO/OPA_SRC/IOM/in_out_manager.F90,v 1.11 2007/03/02 16:37:06 opalod Exp $  
    8787   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    8888   !!---------------------------------------------------------------------- 
  • trunk/NEMO/OPA_SRC/IOM/iom.F90

    r611 r679  
    1919   USE in_out_manager  ! I/O manager 
    2020   USE dom_oce         ! ocean space and time domain 
     21   USE lbclnk          ! lateal boundary condition / mpp exchanges 
    2122   USE iom_def         ! iom variables definitions 
    2223   USE iom_ioipsl      ! NetCDF format with IOIPSL library 
     
    3839   !!---------------------------------------------------------------------- 
    3940   !!  OPA 9.0 , LOCEAN-IPSL (2006) 
    40    !! $Header$ 
     41   !! $Header: /home/opalod/NEMOCVSROOT/NEMO/OPA_SRC/IOM/iom.F90,v 1.10 2007/06/29 14:10:50 opalod Exp $ 
    4142   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    4243   !!---------------------------------------------------------------------- 
     
    4445CONTAINS 
    4546 
    46    SUBROUTINE iom_open( cdname, kiomid, ldwrt, kdom, kiolib ) 
     47   SUBROUTINE iom_open( cdname, kiomid, ldwrt, kdom, kiolib, ldstop ) 
    4748      !!--------------------------------------------------------------------- 
    4849      !!                   ***  SUBROUTINE  iom_open  *** 
     
    5556      INTEGER         , INTENT(in   ), OPTIONAL ::   kdom     ! Type of domain to be written (default = jpdom_local_noovlap) 
    5657      INTEGER         , INTENT(in   ), OPTIONAL ::   kiolib   ! library used to open the file (default = jpnf90)  
     58      LOGICAL         , INTENT(in   ), OPTIONAL ::   ldstop   ! stop if open to read a non-existing file (default = .TRUE.) 
    5759 
    5860      CHARACTER(LEN=100)    ::   clname    ! the name of the file based on cdname [[+clcpu]+clcpu] 
     
    6264      CHARACTER(LEN=100)    ::   clinfo    ! info character 
    6365      LOGICAL               ::   llok      ! check the existence  
    64       LOGICAL               ::   llwrt     !  
     66      LOGICAL               ::   llwrt     ! local definition of ldwrt 
     67      LOGICAL               ::   llstop    ! local definition of ldstop 
    6568      INTEGER               ::   iolib     ! library do we use to open the file 
    6669      INTEGER               ::   icnt      ! counter for digits in clcpu (max = jpmax_digits) 
     
    8992      ELSE                        ;   llwrt = .FALSE. 
    9093      ENDIF 
     94      ! do we call ctl_stop if we try to open a non-existing file in read mode? 
     95      IF( PRESENT(ldstop) ) THEN   ;   llstop = ldstop 
     96      ELSE                         ;   llstop = .TRUE. 
     97      ENDIF 
    9198      ! what library do we use to open the file? 
    9299      IF( PRESENT(kiolib) ) THEN   ;   iolib = kiolib 
     
    110117      iln = LEN_TRIM(clname) 
    111118      ils = LEN_TRIM(clsuffix) 
    112       IF( iln <= ils) clname = clname(1:iln)//TRIM(clsuffix) 
    113       IF( clname(iln-ils+1:iln) /= TRIM(clsuffix) )   clname = clname(1:iln)//TRIM(clsuffix) 
     119      IF( INDEX( TRIM(clname), TRIM(clsuffix), back = .TRUE. ) /= iln - ils + 1 ) clname = TRIM(clname)//TRIM(clsuffix) 
    114120      cltmpn = clname   ! store this name 
    115121      ! try to find if the file to be opened already exist 
     
    118124      IF( .NOT.llok ) THEN 
    119125         ! we try to add the cpu number to the name 
    120          WRITE(clcpu,*) narea-1 
     126         IF( iolib == jprstdimg ) THEN   ;   WRITE(clcpu,*) narea 
     127         ELSE                            ;   WRITE(clcpu,*) narea-1 
     128         ENDIF 
    121129         clcpu  = TRIM(ADJUSTL(clcpu)) 
    122          iln = INDEX(clname,TRIM(clsuffix)) 
     130         iln = INDEX(clname,TRIM(clsuffix), back = .TRUE.) 
    123131         clname = clname(1:iln-1)//'_'//TRIM(clcpu)//TRIM(clsuffix) 
    124132         icnt = 0 
     
    132140         END DO 
    133141      ENDIF 
    134       ! check the domain definition 
    135       idom = jpdom_local_noovlap   ! default definition 
    136       IF( PRESENT(kdom) )   idom = kdom 
    137       ! create the domain informations 
    138       ! ============= 
    139       SELECT CASE (idom) 
    140       CASE (jpdom_local_full) 
    141          idompar(:,1) = (/ jpi             , jpj              /) 
    142          idompar(:,2) = (/ nimpp           , njmpp            /) 
    143          idompar(:,3) = (/ nimpp + jpi - 1 , njmpp + jpj - 1  /) 
    144          idompar(:,4) = (/ nldi - 1        , nldj - 1         /) 
    145          idompar(:,5) = (/ jpi - nlei      , jpj - nlej       /) 
    146       CASE (jpdom_local_noextra) 
    147          idompar(:,1) = (/ nlci            , nlcj             /) 
    148          idompar(:,2) = (/ nimpp           , njmpp            /) 
    149          idompar(:,3) = (/ nimpp + nlci - 1, njmpp + nlcj - 1 /) 
    150          idompar(:,4) = (/ nldi - 1        , nldj - 1         /) 
    151          idompar(:,5) = (/ nlci - nlei     , nlcj - nlej      /) 
    152       CASE (jpdom_local_noovlap) 
    153          idompar(:,1) = (/ nlei - nldi + 1 , nlej - nldj + 1  /) 
    154          idompar(:,2) = (/ nimpp + nldi - 1, njmpp + nldj - 1 /) 
    155          idompar(:,3) = (/ nimpp + nlei - 1, njmpp + nlej - 1 /) 
    156          idompar(:,4) = (/ 0               , 0                /) 
    157          idompar(:,5) = (/ 0               , 0                /) 
    158       CASE DEFAULT 
    159          CALL ctl_stop( TRIM(clinfo), 'wrong value of kdom, only jpdom_local* cases are accepted' ) 
    160       END SELECT 
     142      IF( llwrt ) THEN 
     143         ! check the domain definition 
     144! JMM + SM: ugly patch before getting the new version of lib_mpp) 
     145!         idom = jpdom_local_noovlap   ! default definition 
     146         IF( jpni*jpnj == jpnij ) THEN   ;   idom = jpdom_local_noovlap   ! default definition 
     147         ELSE                            ;   idom = jpdom_local_full      ! default definition 
     148         ENDIF 
     149         IF( PRESENT(kdom) )   idom = kdom 
     150         ! create the domain informations 
     151         ! ============= 
     152         SELECT CASE (idom) 
     153         CASE (jpdom_local_full) 
     154            idompar(:,1) = (/ jpi             , jpj              /) 
     155            idompar(:,2) = (/ nimpp           , njmpp            /) 
     156            idompar(:,3) = (/ nimpp + jpi - 1 , njmpp + jpj - 1  /) 
     157            idompar(:,4) = (/ nldi - 1        , nldj - 1         /) 
     158            idompar(:,5) = (/ jpi - nlei      , jpj - nlej       /) 
     159         CASE (jpdom_local_noextra) 
     160            idompar(:,1) = (/ nlci            , nlcj             /) 
     161            idompar(:,2) = (/ nimpp           , njmpp            /) 
     162            idompar(:,3) = (/ nimpp + nlci - 1, njmpp + nlcj - 1 /) 
     163            idompar(:,4) = (/ nldi - 1        , nldj - 1         /) 
     164            idompar(:,5) = (/ nlci - nlei     , nlcj - nlej      /) 
     165         CASE (jpdom_local_noovlap) 
     166            idompar(:,1) = (/ nlei  - nldi + 1, nlej  - nldj + 1 /) 
     167            idompar(:,2) = (/ nimpp + nldi - 1, njmpp + nldj - 1 /) 
     168            idompar(:,3) = (/ nimpp + nlei - 1, njmpp + nlej - 1 /) 
     169            idompar(:,4) = (/ 0               , 0                /) 
     170            idompar(:,5) = (/ 0               , 0                /) 
     171         CASE DEFAULT 
     172            CALL ctl_stop( TRIM(clinfo), 'wrong value of kdom, only jpdom_local* cases are accepted' ) 
     173         END SELECT 
     174      ENDIF 
    161175      ! Open the NetCDF or RSTDIMG file 
    162176      ! ============= 
    163177      ! do we have some free file identifier? 
    164178      IF( MINVAL(iom_file(:)%nfid) /= 0 )   & 
    165             &   CALL ctl_stop( TRIM(clinfo), 'No more free file identifier', 'increase jpmax_files in iom_def' ) 
     179         &   CALL ctl_stop( TRIM(clinfo), 'No more free file identifier', 'increase jpmax_files in iom_def' ) 
     180      ! if no file was found... 
     181      IF( .NOT. llok ) THEN 
     182         IF( .NOT. llwrt ) THEN   ! we are in read mode  
     183            IF( llstop ) THEN   ;   CALL ctl_stop( TRIM(clinfo), 'File '//TRIM(cltmpn)//'* not found' ) 
     184            ELSE                ;   istop = nstop + 1   ! make sure that istop /= nstop so we don't open the file 
     185            ENDIF 
     186         ELSE                     ! we are in write mode so we  
     187            clname = cltmpn       ! get back the file name without the cpu number 
     188         ENDIF 
     189      ENDIF 
    166190      IF( istop == nstop ) THEN   ! no error within this routine 
    167          IF( .NOT. llok )   clname = cltmpn   ! get back the file name without the cpu number 
    168191         SELECT CASE (iolib) 
    169192         CASE (jpioipsl )   ;   CALL iom_ioipsl_open(  clname, kiomid, llwrt, llok, idompar ) 
     
    212235               END SELECT 
    213236               iom_file(jf)%nfid       = 0   ! free the id  
    214                IF(lwp) WRITE(numout,*) TRIM(clinfo)//' close file: '//TRIM(iom_file(kiomid)%name)//' ok' 
     237               IF(lwp) WRITE(numout,*) TRIM(clinfo)//' close file: '//TRIM(iom_file(jf)%name)//' ok' 
    215238            ELSEIF( PRESENT(kiomid) ) THEN 
    216239               WRITE(ctmp1,*) '--->',  kiomid 
     
    237260      CHARACTER(LEN=100)             ::   clinfo                   ! info character 
    238261      !!----------------------------------------------------------------------- 
    239       clinfo = 'iom_varid, file: '//trim(iom_file(kiomid)%name)//', var: '//trim(cdvar) 
    240262      iom_varid = 0                         ! default definition 
    241263      ! 
    242264      IF( kiomid > 0 ) THEN 
     265         clinfo = 'iom_varid, file: '//trim(iom_file(kiomid)%name)//', var: '//trim(cdvar) 
    243266         IF( iom_file(kiomid)%nfid == 0 ) THEN  
    244267            CALL ctl_stop( trim(clinfo), 'the file is not open' ) 
     
    294317      INTEGER               :: idvar   ! variable id 
    295318      ! 
    296       idvar = iom_varid( kiomid, cdvar ) 
    297       IF( iom_file(kiomid)%nfid > 0 .AND. idvar > 0 ) THEN 
    298          SELECT CASE (iom_file(kiomid)%iolib) 
    299          CASE (jpioipsl )   ;   CALL iom_ioipsl_get(  kiomid, idvar, pvar ) 
    300          CASE (jpnf90   )   ;   CALL iom_nf90_get(    kiomid, idvar, pvar ) 
    301          CASE (jprstdimg)   ;   CALL iom_rstdimg_get( kiomid, idvar, pvar ) 
    302          CASE DEFAULT     
    303             CALL ctl_stop( 'iom_g0d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
    304          END SELECT 
    305       END IF 
     319      IF( kiomid > 0 ) THEN 
     320         idvar = iom_varid( kiomid, cdvar ) 
     321         IF( iom_file(kiomid)%nfid > 0 .AND. idvar > 0 ) THEN 
     322            SELECT CASE (iom_file(kiomid)%iolib) 
     323            CASE (jpioipsl )   ;   CALL iom_ioipsl_get(  kiomid, idvar, pvar ) 
     324            CASE (jpnf90   )   ;   CALL iom_nf90_get(    kiomid, idvar, pvar ) 
     325            CASE (jprstdimg)   ;   CALL iom_rstdimg_get( kiomid, idvar, pvar ) 
     326            CASE DEFAULT     
     327               CALL ctl_stop( 'iom_g0d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     328            END SELECT 
     329         ENDIF 
     330      ENDIF 
    306331   END SUBROUTINE iom_g0d 
    307332 
     
    315340      INTEGER         , INTENT(in   ), DIMENSION(1), OPTIONAL ::   kcount    ! number of points in each axis 
    316341      ! 
    317       IF( iom_file(kiomid)%nfid > 0 ) CALL iom_get_123d( kiomid, kdom       , cdvar        , pv_r1d=pvar,   & 
    318             &                                        ktime=ktime, kstart=kstart, kcount=kcount ) 
     342      IF( kiomid > 0 ) THEN 
     343         IF( iom_file(kiomid)%nfid > 0 ) CALL iom_get_123d( kiomid, kdom       , cdvar        , pv_r1d=pvar,   & 
     344              &                                                     ktime=ktime, kstart=kstart, kcount=kcount ) 
     345      ENDIF 
    319346   END SUBROUTINE iom_g1d 
    320347 
     
    328355      INTEGER         , INTENT(in   ), DIMENSION(2)  , OPTIONAL ::   kcount    ! number of points in each axis 
    329356      ! 
    330       IF( iom_file(kiomid)%nfid > 0 ) CALL iom_get_123d( kiomid, kdom       , cdvar        , pv_r2d=pvar,   & 
    331             &                                        ktime=ktime, kstart=kstart, kcount=kcount ) 
     357      IF( kiomid > 0 ) THEN 
     358         IF( iom_file(kiomid)%nfid > 0 ) CALL iom_get_123d( kiomid, kdom       , cdvar        , pv_r2d=pvar,   & 
     359              &                                                     ktime=ktime, kstart=kstart, kcount=kcount ) 
     360      ENDIF 
    332361   END SUBROUTINE iom_g2d 
    333362 
     
    341370      INTEGER         , INTENT(in   ), DIMENSION(3)    , OPTIONAL ::   kcount    ! number of points in each axis 
    342371      ! 
    343       IF( iom_file(kiomid)%nfid > 0 ) CALL iom_get_123d( kiomid, kdom       , cdvar        , pv_r3d=pvar,   & 
    344             &                                        ktime=ktime, kstart=kstart, kcount=kcount ) 
     372      IF( kiomid > 0 ) THEN 
     373         IF( iom_file(kiomid)%nfid > 0 ) CALL iom_get_123d( kiomid, kdom       , cdvar        , pv_r3d=pvar,   & 
     374              &                                                     ktime=ktime, kstart=kstart, kcount=kcount ) 
     375      ENDIF 
    345376   END SUBROUTINE iom_g3d 
    346377   !!---------------------------------------------------------------------- 
    347378 
    348379   SUBROUTINE iom_get_123d( kiomid, kdom  , cdvar ,   & 
    349          &                   pv_r1d, pv_r2d, pv_r3d,   & 
    350          &                   ktime , kstart, kcount  ) 
     380         &                  pv_r1d, pv_r2d, pv_r3d,   & 
     381         &                  ktime , kstart, kcount  ) 
    351382      !!----------------------------------------------------------------------- 
    352383      !!                  ***  ROUTINE  iom_get_123d  *** 
     
    373404      INTEGER                        ::   itime       ! record number 
    374405      INTEGER                        ::   istop       ! temporary value of nstop 
     406      INTEGER                        ::   ix1, ix2, iy1, iy2   ! subdomain indexes 
     407      INTEGER                        ::   ji, jj      ! loop counters 
     408      INTEGER                        ::   irankpv       !  
     409      INTEGER                        ::   ind1, ind2  ! substring index 
    375410      INTEGER, DIMENSION(jpmax_dims) ::   istart      ! starting point to read for each axis 
    376411      INTEGER, DIMENSION(jpmax_dims) ::   icnt        ! number of value to read along each axis  
    377412      INTEGER, DIMENSION(jpmax_dims) ::   idimsz      ! size of the dimensions of the variable 
     413      INTEGER, DIMENSION(jpmax_dims) ::   ishape      ! size of the dimensions of the variable 
    378414      REAL(wp)                       ::   zscf, zofs  ! sacle_factor and add_offset 
    379415      INTEGER                        ::   itmp        ! temporary integer 
    380416      CHARACTER(LEN=100)             ::   clinfo      ! info character 
     417      CHARACTER(LEN=100)             ::   clname      ! file name 
     418      CHARACTER(LEN=1)               ::   clrankpv, cldmspc      !  
    381419      !--------------------------------------------------------------------- 
    382420      ! 
    383       clinfo = '          iom_get_123d, file: '//trim(iom_file(kiomid)%name)//', var: '//trim(cdvar) 
     421      clname = iom_file(kiomid)%name   !   esier to read 
     422      clinfo = '          iom_get_123d, file: '//trim(clname)//', var: '//trim(cdvar) 
    384423      ! local definition of the domain ? 
    385424      idom = kdom 
    386425      ! check kcount and kstart optionals parameters... 
    387       IF( PRESENT(kcount) .AND. (.NOT. PRESENT(kstart)) )   & 
    388             CALL ctl_stop( trim(clinfo), 'kcount present needs kstart present' ) 
    389       IF( PRESENT(kstart) .AND. (.NOT. PRESENT(kcount)) )   & 
    390             CALL ctl_stop( trim(clinfo), 'kstart present needs kcount present' ) 
    391       IF( PRESENT(kstart) .AND. idom /= jpdom_unknown   )   & 
    392             CALL ctl_stop( trim(clinfo), 'kstart present needs kdom = jpdom_unknown' ) 
     426      IF( PRESENT(kcount) .AND. (.NOT. PRESENT(kstart)) ) CALL ctl_stop(trim(clinfo), 'kcount present needs kstart present') 
     427      IF( PRESENT(kstart) .AND. (.NOT. PRESENT(kcount)) ) CALL ctl_stop(trim(clinfo), 'kstart present needs kcount present') 
     428      IF( PRESENT(kstart) .AND. idom /= jpdom_unknown   ) CALL ctl_stop(trim(clinfo), 'kstart present needs kdom = jpdom_unknown') 
    393429 
    394430      ! Search for the variable in the data base (eventually actualize data) 
     
    402438         idmspc = inbdim                                   ! number of spatial dimensions in the file 
    403439         IF( iom_file(kiomid)%luld(idvar) )   idmspc = inbdim - 1 
    404          IF( idmspc > 3 )   CALL ctl_stop(trim(clinfo),   & 
    405                &                    'the file has more than 3 spatial dimensions this case is not coded...' )  
    406          IF( idom == jpdom_local ) THEN        ! Identify the domain in case of jpdom_local definition 
    407             IF( idimsz(1) == jpi .AND. idimsz(2) == jpj ) THEN  
    408                idom = jpdom_local_full 
    409             ELSEIF( idimsz(1) == nlci .AND. idimsz(2) == nlcj ) THEN  
    410                idom = jpdom_local_noextra 
    411             ELSEIF( idimsz(1) == (nlei - nldi + 1) .AND. idimsz(2) == (nlej - nldj + 1) ) THEN  
    412                idom = jpdom_local_noovlap 
    413             ELSE  
    414                CALL ctl_stop( trim(clinfo), 'impossible to identify the local domain' ) 
    415             ENDIF 
    416          ENDIF 
    417          ! 
    418          ! definition of istart and icnt 
     440         IF( idmspc > 3 )   CALL ctl_stop(trim(clinfo), 'the file has more than 3 spatial dimensions this case is not coded...')  
     441         ! 
     442         ! update idom definition... 
     443         ! Identify the domain in case of jpdom_auto(glo/dta) definition 
     444         IF( idom == jpdom_autoglo .OR. idom == jpdom_autodta ) THEN             
     445            IF( idom == jpdom_autoglo ) THEN   ;   idom = jpdom_global  
     446            ELSE                               ;   idom = jpdom_data 
     447            ENDIF 
     448            ind1 = INDEX( clname, '_', back = .TRUE. ) + 1 
     449            ind2 = INDEX( clname, '.', back = .TRUE. ) - 1 
     450            IF( ind2 > ind1 ) THEN   ;   IF( VERIFY( clname(ind1:ind2), '0123456789' ) == 0 )   idom = jpdom_local   ;   ENDIF 
     451         ENDIF 
     452         ! Identify the domain in case of jpdom_local definition 
     453         IF( idom == jpdom_local ) THEN 
     454            IF(     idimsz(1) == jpi               .AND. idimsz(2) == jpj               ) THEN   ;   idom = jpdom_local_full 
     455            ELSEIF( idimsz(1) == nlci              .AND. idimsz(2) == nlcj              ) THEN   ;   idom = jpdom_local_noextra 
     456            ELSEIF( idimsz(1) == (nlei - nldi + 1) .AND. idimsz(2) == (nlej - nldj + 1) ) THEN   ;   idom = jpdom_local_noovlap 
     457            ELSE   ;   CALL ctl_stop( trim(clinfo), 'impossible to identify the local domain' ) 
     458            ENDIF 
     459         ENDIF 
     460         ! 
     461         ! check the consistency between input array and data rank in the file 
    419462         ! 
    420463         ! initializations 
    421          istart(:) = 1 
    422          icnt  (:) = 1 
    423464         itime = 1 
    424465         IF( PRESENT(ktime) ) itime = ktime 
    425          ! 
    426          IF( PRESENT(pv_r1d) ) THEN 
    427             IF( idmspc == 1 ) THEN  
    428                ! data is 1d array (+ maybe a temporal dimension) 
    429                IF( PRESENT(kstart) ) THEN 
    430                   istart(1:2) = (/ kstart(1), itime /) 
    431                   icnt(1) = kcount(1) 
     466 
     467         irankpv = 1 * COUNT( (/PRESENT(pv_r1d)/) ) + 2 * COUNT( (/PRESENT(pv_r2d)/) ) + 3 * COUNT( (/PRESENT(pv_r3d)/) ) 
     468         WRITE(clrankpv, fmt='(i1)') irankpv 
     469         WRITE(cldmspc , fmt='(i1)') idmspc 
     470         ! 
     471         IF(     idmspc <  irankpv ) THEN  
     472            CALL ctl_stop( TRIM(clinfo), 'The file has only '//cldmspc//' spatial dimension',   & 
     473               &                         'it is impossible to read a '//clrankpv//'D array from this file...' ) 
     474         ELSEIF( idmspc == irankpv ) THEN 
     475            IF( PRESENT(pv_r1d) .AND. idom /= jpdom_unknown )   & 
     476               &   CALL ctl_stop( TRIM(clinfo), 'case not coded...You must use jpdom_unknown' ) 
     477         ELSEIF( idmspc >  irankpv ) THEN 
     478               IF( PRESENT(pv_r2d) .AND. itime == 1 .AND. idimsz(3) == 1 .AND. idmspc == 3 ) THEN 
     479                  CALL ctl_warn( trim(clinfo), '2D array but 3 spatial dimensions for the data...'              ,   & 
     480                        &         'As the size of the z dimension is 1 and as we try to read the first record, ',   & 
     481                        &         'we accept this case, even if there is a possible mix-up between z and time dimension' )    
     482                  idmspc = idmspc - 1 
    432483               ELSE 
    433                   IF( kdom == jpdom_unknown ) THEN 
    434                      istart(2) = itime 
    435                      icnt(1) = idimsz(1) 
    436                   ELSE  
    437                      CALL ctl_stop( trim(clinfo), 'case not coded...You must use jpdom_unknown' ) 
     484                  CALL ctl_stop( TRIM(clinfo), 'To keep iom lisibility, when reading a '//clrankpv//'D array,'         ,   & 
     485                     &                         'we do not accept data with more than '//cldmspc//' spatial dimension',   & 
     486                     &                         'Use ncwa -a to suppress the unnecessary dimensions' ) 
     487               ENDIF 
     488         ENDIF 
     489 
     490         ! 
     491         ! definition of istart and icnt 
     492         ! 
     493         icnt  (:) = 1 
     494         istart(:) = 1 
     495         istart(idmspc+1) = itime 
     496 
     497         IF(              PRESENT(kstart)       ) THEN ; istart(1:idmspc) = kstart(1:idmspc) ; icnt(1:idmspc) = kcount(1:idmspc) 
     498         ELSE 
     499            IF(           idom == jpdom_unknown ) THEN                                       ; icnt(1:idmspc) = idimsz(1:idmspc) 
     500            ELSE  
     501               IF( .NOT. PRESENT(pv_r1d) ) THEN   !   not a 1D array 
     502                  IF(     idom == jpdom_data    ) THEN ; istart(1:2) = (/ mig(1), mjg(1) /)  ! icnt(1:2) done bellow 
     503                  ELSEIF( idom == jpdom_global  ) THEN ; istart(1:2) = (/ nimpp , njmpp  /)  ! icnt(1:2) done bellow 
    438504                  ENDIF 
    439                ENDIF 
    440             ELSE 
    441                CALL ctl_stop( trim(clinfo), 'to keep iom lisibility, when reading a 1D array,', & 
    442                      &         'we do not accept data with more than 1 spatial dimension',     & 
    443                      &         'Use ncwa -a to suppress the unnecessary dimensions') 
    444             ENDIF 
    445          ELSEIF( PRESENT(pv_r2d) ) THEN 
    446             SELECT CASE (idmspc) 
    447             CASE (1) 
    448                CALL ctl_stop( trim(clinfo), 'the file has only 1 spatial dimension',  & 
    449                      &         'it is impossible to read a 2d array from this file...') 
    450             CASE (2) 
    451                ! data is 2d array (+ maybe a temporal dimension) 
    452                IF( PRESENT(kstart) ) THEN 
    453                   istart(1:3) = (/ kstart(1:2), itime /) 
    454                   icnt(1:2) = kcount(1:2) 
    455                ELSE 
    456                   IF( kdom == jpdom_unknown ) THEN 
    457                      istart(3) = itime 
    458                      icnt(1:2) = idimsz(1:2) 
    459                   ELSE  
    460                      IF( idom == jpdom_data ) THEN 
    461                         istart(1:3) = (/ mig(1), mjg(1), itime /) 
    462                      ELSEIF( idom == jpdom_global ) THEN 
    463                         istart(1:3) = (/ nimpp, njmpp, itime /) 
    464                      ENDIF 
    465                      ! we do not read the overlap -> we start to read at nldi, nldj 
    466                      IF( idom /= jpdom_local_noovlap )   istart(1:2) = istart(1:2) + (/ nldi - 1, nldj - 1 /) 
    467                      ! we do not read the overlap and the extra-halos   
    468                      ! -> from nldi to nlei and from nldj to nlej  
    469                      icnt(1:2) = (/ nlei - nldi + 1, nlej - nldj + 1 /) 
     505                  ! we do not read the overlap                     -> we start to read at nldi, nldj 
     506! JMM + SM: ugly patch before getting the new version of lib_mpp) 
     507!                  IF( idom /= jpdom_local_noovlap )   istart(1:2) = istart(1:2) + (/ nldi - 1, nldj - 1 /) 
     508                  IF( jpni*jpnj == jpnij .AND. idom /= jpdom_local_noovlap ) istart(1:2) = istart(1:2) + (/ nldi - 1, nldj - 1 /) 
     509                  ! we do not read the overlap and the extra-halos -> from nldi to nlei and from nldj to nlej  
     510! JMM + SM: ugly patch before getting the new version of lib_mpp) 
     511!                  icnt(1:2) = (/ nlei - nldi + 1, nlej - nldj + 1 /) 
     512                  IF( jpni*jpnj == jpnij ) THEN   ;   icnt(1:2) = (/ nlei - nldi + 1, nlej - nldj + 1 /) 
     513                  ELSE                            ;   icnt(1:2) = (/ nlci           , nlcj            /) 
    470514                  ENDIF 
    471                ENDIF 
    472             CASE DEFAULT 
    473                IF( itime == 1 .AND. idimsz(3) == 1 .AND. idmspc == 3 ) THEN 
    474                   CALL ctl_warn( trim(clinfo), '2D array but 3 spatial dimensions for the data...',                & 
    475                         &         'As the size of the z dimension is 1 and as we try to read the first record, ',   & 
    476                         &         'we accept this case even if there is a possible mix-up between z and time dimension' )            
    477                   IF( PRESENT(kstart) ) THEN 
    478                      istart(1:2) = kstart(1:2) 
    479                      icnt(1:2) = kcount(1:2) 
    480                   ELSE 
    481                      IF( kdom == jpdom_unknown ) THEN 
    482                         icnt(1:2) = idimsz(1:2) 
    483                      ELSE  
    484                         IF( idom == jpdom_data ) THEN 
    485                            istart(1:2) = (/ mig(1), mjg(1) /) 
    486                         ELSEIF( idom == jpdom_global ) THEN 
    487                            istart(1:2) = (/ nimpp, njmpp /) 
    488                         ENDIF 
    489                         ! we do not read the overlap -> we start to read at nldi, nldj 
    490                         IF( idom /= jpdom_local_noovlap )   istart(1:2) = istart(1:2) + (/ nldi - 1, nldj - 1 /) 
    491                         ! we do not read the overlap and the extra-halos   
    492                         ! -> from nldi to nlei and from nldj to nlej  
    493                         icnt(1:2) = (/ nlei - nldi + 1, nlej - nldj + 1 /) 
    494                      ENDIF 
    495                   ENDIF 
    496                ELSE 
    497                   CALL ctl_stop( trim(clinfo), 'to keep iom lisibility, when reading a 2D array,',           & 
    498                         &                       'we do not accept data with more than 2 spatial dimension',   & 
    499                         &                       'Use ncwa -a to suppress the unnecessary dimensions' ) 
    500                ENDIF 
    501             END SELECT 
    502          ELSEIF( PRESENT(pv_r3d) ) THEN 
    503             SELECT CASE (idmspc) 
    504             CASE( 1 ) 
    505                CALL ctl_stop( trim(clinfo), 'the file has only 1 spatial dimension',            & 
    506                      &                       'it is impossible to read a 3d array from this file...' ) 
    507             CASE( 2 ) 
    508                CALL ctl_stop( trim(clinfo), 'the file has only 2 spatial dimension',            & 
    509                      &                       'it is impossible to read a 3d array from this file...' ) 
    510             CASE( 3 ) 
    511                ! data is 3d array (+ maybe a temporal dimension) 
    512                IF( PRESENT(kstart) ) THEN 
    513                   istart(1:4) = (/ kstart(1:3), itime /) 
    514                   icnt(1:3) = kcount(1:3) 
    515                ELSE 
    516                   IF( kdom == jpdom_unknown ) THEN 
    517                      istart(4) = itime 
    518                      icnt(1:3) = idimsz(1:3) 
    519                   ELSE  
    520                      IF( idom == jpdom_data ) THEN 
    521                         istart(1:4) = (/ mig(1), mjg(1), 1, itime /) 
    522                      ELSEIF( idom == jpdom_global ) THEN 
    523                         istart(1:4) = (/ nimpp, njmpp, 1, itime /) 
    524                      ENDIF 
    525                      ! we do not read the overlap -> we start to read at nldi, nldj 
    526                      IF( idom /= jpdom_local_noovlap )   istart(1:2) = istart(1:2) + (/ nldi - 1, nldj - 1 /) 
    527                      ! we do not read the overlap and the extra-halos 
    528                      ! -> from nldi to nlei and from nldj to nlej  
    529                      icnt(1:2) = (/ nlei - nldi + 1, nlej - nldj + 1 /) 
    530                      IF( idom == jpdom_data ) THEN  
    531                         icnt(3) = jpkdta 
    532                      ELSE 
    533                         icnt(3) = jpk 
     515                  IF( PRESENT(pv_r3d) ) THEN 
     516                     IF( idom == jpdom_data ) THEN   ; icnt(3) = jpkdta 
     517                     ELSE                            ; icnt(3) = jpk 
    534518                     ENDIF 
    535519                  ENDIF 
    536520               ENDIF 
    537             CASE DEFAULT 
    538                CALL ctl_stop( trim(clinfo), 'to keep iom lisibility, when reading a 3D array,',   & 
    539                      &         'we do not accept data with more than 3 spatial dimension',         & 
    540                      &         'Use ncwa -a to suppress the unnecessary dimensions' )            
    541             END SELECT 
     521            ENDIF 
    542522         ENDIF 
    543523 
     
    546526         DO jl = 1, jpmax_dims 
    547527            itmp = istart(jl)+icnt(jl)-1 
    548             IF( (itmp) > idimsz(jl) .AND. idimsz(jl) /= 0 ) THEN 
    549                WRITE(ctmp1,*) '(istart(',jl,') + icnt(',jl,') - 1) = ', itmp 
    550                WRITE(ctmp2,*) ' is larger than idimsz(',jl,'): ', idimsz(jl) 
     528            IF( itmp > idimsz(jl) .AND. idimsz(jl) /= 0 ) THEN 
     529               WRITE( ctmp1, FMT="('(istart(', i1, ') + icnt(', i1, ') - 1) = ', i5)" ) jl, jl, itmp 
     530               WRITE( ctmp2, FMT="(' is larger than idimsz(', i1,') = ', i5)"         ) jl, idimsz(jl) 
    551531               CALL ctl_stop( trim(clinfo), 'start and count too big regarding to the size of the data, ', ctmp1, ctmp2 )      
    552532            ENDIF 
     
    555535         ! check that icnt matches the input array 
    556536         !-      
    557          IF( PRESENT(pv_r1d) ) THEN 
    558             itmp = size(pv_r1d) 
    559             WRITE(ctmp1,*) 'size(pv_r1d): ', itmp, ' /= icnt(1): ', icnt(1) 
    560             IF( itmp /= icnt(1) )   CALL ctl_stop( trim(clinfo), ctmp1 ) 
    561          ELSEIF( PRESENT(pv_r2d) ) THEN 
    562             DO jl = 1, 2 
    563                IF( idom == jpdom_unknown ) THEN 
    564                   itmp = size(pv_r2d, jl) 
    565                   WRITE(ctmp1,*) 'size(pv_r2d, ',jl,'): ',itmp,' /= icnt(',jl,'): ',icnt(jl) 
    566                ELSE  
    567                   itmp = size(pv_r2d(nldi:nlei,nldj:nlej), jl) 
    568                   WRITE(ctmp1,*) 'size(pv_r2d(nldi:nlei,nldj:nlej), ',jl,'): ',itmp,' /= icnt(',jl,'): ',icnt(jl) 
     537         IF( idom == jpdom_unknown ) THEN 
     538            IF( irankpv == 1 )        ishape(1:1) = SHAPE(pv_r1d) 
     539            IF( irankpv == 2 )        ishape(1:2) = SHAPE(pv_r2d) 
     540            IF( irankpv == 3 )        ishape(1:3) = SHAPE(pv_r3d) 
     541            ctmp1 = 'd' 
     542         ELSE 
     543            IF( irankpv == 2 ) THEN 
     544! JMM + SM: ugly patch before getting the new version of lib_mpp) 
     545!               ishape(1:2) = SHAPE(pv_r2d(nldi:nlei,nldj:nlej  ))   ;   ctmp1 = 'd(nldi:nlei,nldj:nlej)' 
     546               IF( jpni*jpnj == jpnij ) THEN ; ishape(1:2)=SHAPE(pv_r2d(nldi:nlei,nldj:nlej  )) ; ctmp1='d(nldi:nlei,nldj:nlej)' 
     547               ELSE                          ; ishape(1:2)=SHAPE(pv_r2d(1   :nlci,1   :nlcj  )) ; ctmp1='d(1:nlci,1:nlcj)' 
    569548               ENDIF 
    570                IF( itmp /= icnt(jl) )   CALL ctl_stop( trim(clinfo), ctmp1 ) 
    571             END DO 
    572          ELSEIF( PRESENT(pv_r3d) ) THEN 
    573             DO jl = 1, 3 
    574                IF( idom == jpdom_unknown ) THEN 
    575                   itmp = size(pv_r3d, jl) 
    576                   WRITE(ctmp1,*) 'size(pv_r3d, ',jl,'): ',itmp,' /= icnt(',jl,'):', icnt(jl) 
    577                ELSE  
    578                   itmp = size(pv_r3d(nldi:nlei,nldj:nlej,:), jl) 
    579                   WRITE(ctmp1,*) 'size(pv_r3d(nldi:nlei,nldj:nlej), ',jl,'): ',itmp,' /= icnt(',jl,'): ',icnt(jl) 
     549            ENDIF 
     550            IF( irankpv == 3 ) THEN  
     551! JMM + SM: ugly patch before getting the new version of lib_mpp) 
     552!               ishape(1:3) = SHAPE(pv_r3d(nldi:nlei,nldj:nlej,:))   ;   ctmp1 = 'd(nldi:nlei,nldj:nlej,:)' 
     553               IF( jpni*jpnj == jpnij ) THEN ; ishape(1:3)=SHAPE(pv_r3d(nldi:nlei,nldj:nlej,:)) ; ctmp1='d(nldi:nlei,nldj:nlej,:)' 
     554               ELSE                          ; ishape(1:3)=SHAPE(pv_r3d(1   :nlci,1   :nlcj,:)) ; ctmp1='d(1:nlci,1:nlcj,:)' 
    580555               ENDIF 
    581                IF( itmp /= icnt(jl) )   CALL ctl_stop( trim(clinfo), ctmp1 ) 
    582             END DO 
    583          ENDIF 
     556            ENDIF 
     557         ENDIF 
     558          
     559         DO jl = 1, irankpv 
     560            WRITE( ctmp2, FMT="(', ', i1,'): ', i5,' /= icnt(', i1,'):', i5)" ) jl, ishape(jl), jl, icnt(jl) 
     561            IF( ishape(jl) /= icnt(jl) )   CALL ctl_stop( TRIM(clinfo), 'size(pv_r'//clrankpv//TRIM(ctmp1)//TRIM(ctmp2) ) 
     562         END DO 
     563 
    584564      ENDIF 
    585565 
    586566      ! read the data 
    587567      !-      
    588       IF( istop == nstop) THEN ! no additional errors until this point... 
    589          ! 
     568      IF( idvar > 0 .AND. istop == nstop ) THEN   ! no additional errors until this point... 
     569         ! 
     570         ! find the right index of the array to be read 
     571! JMM + SM: ugly patch before getting the new version of lib_mpp) 
     572!         IF( idom /= jpdom_unknown ) THEN   ;   ix1 = nldi   ;   ix2 = nlei      ;   iy1 = nldj   ;   iy2 = nlej 
     573!         ELSE                               ;   ix1 = 1      ;   ix2 = icnt(1)   ;   iy1 = 1      ;   iy2 = icnt(2) 
     574!         ENDIF 
     575         IF( jpni*jpnj == jpnij ) THEN 
     576            IF( idom /= jpdom_unknown ) THEN   ;   ix1 = nldi   ;   ix2 = nlei      ;   iy1 = nldj   ;   iy2 = nlej 
     577            ELSE                               ;   ix1 = 1      ;   ix2 = icnt(1)   ;   iy1 = 1      ;   iy2 = icnt(2) 
     578            ENDIF 
     579         ELSE 
     580            IF( idom /= jpdom_unknown ) THEN   ;   ix1 = 1      ;   ix2 = nlci      ;   iy1 = 1      ;   iy2 = nlcj 
     581            ELSE                               ;   ix1 = 1      ;   ix2 = icnt(1)   ;   iy1 = 1      ;   iy2 = icnt(2) 
     582            ENDIF 
     583         ENDIF 
     584       
    590585         SELECT CASE (iom_file(kiomid)%iolib) 
    591          CASE (jpioipsl )   ;   CALL iom_ioipsl_get(  kiomid, idom, idvar, inbdim, istart, icnt, pv_r1d, pv_r2d, pv_r3d ) 
    592          CASE (jpnf90   )   ;   CALL iom_nf90_get(    kiomid, idom, idvar, inbdim, istart, icnt, pv_r1d, pv_r2d, pv_r3d ) 
    593          CASE (jprstdimg)   ;   CALL iom_rstdimg_get( kiomid, idom, idvar,         istart, icnt, pv_r1d, pv_r2d, pv_r3d ) 
     586         CASE (jpioipsl )   ;   CALL iom_ioipsl_get(  kiomid, idvar, inbdim, istart, icnt, ix1, ix2, iy1, iy2,   & 
     587            &                                         pv_r1d, pv_r2d, pv_r3d ) 
     588         CASE (jpnf90   )   ;   CALL iom_nf90_get(    kiomid, idvar, inbdim, istart, icnt, ix1, ix2, iy1, iy2,   & 
     589            &                                         pv_r1d, pv_r2d, pv_r3d ) 
     590         CASE (jprstdimg)   ;   CALL iom_rstdimg_get( kiomid, idom, idvar, ix1, ix2, iy1, iy2,   & 
     591            &                                         pv_r1d, pv_r2d, pv_r3d ) 
    594592         CASE DEFAULT     
    595593            CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
    596594         END SELECT 
    597          IF( istop == nstop .AND. lwp )   & 
    598                WRITE(numout,*) '           read '//trim(cdvar)//' in '//trim(iom_file(kiomid)%name)//' ok' 
    599          !--- Apply scale_factor and offset 
    600          zscf = iom_file(kiomid)%scf(idvar)      ! scale factor 
    601          zofs = iom_file(kiomid)%ofs(idvar)      ! offset 
    602          IF( PRESENT(pv_r1d) ) THEN 
    603             IF( zscf /= 1. )   pv_r1d(:) = pv_r1d(:) * zscf  
    604             IF( zofs /= 0. )   pv_r1d(:) = pv_r1d(:) + zofs 
    605          ELSEIF( PRESENT(pv_r2d) ) THEN 
    606 !CDIR COLLAPSE 
    607             IF( zscf /= 1.)   pv_r2d(:,:) = pv_r2d(:,:) * zscf 
    608 !CDIR COLLAPSE 
    609             IF( zofs /= 0.)   pv_r2d(:,:) = pv_r2d(:,:) + zofs 
    610          ELSEIF( PRESENT(pv_r3d) ) THEN 
    611 !CDIR COLLAPSE 
    612             IF( zscf /= 1.)   pv_r3d(:,:,:) = pv_r3d(:,:,:) * zscf 
    613 !CDIR COLLAPSE 
    614             IF( zofs /= 0.)   pv_r3d(:,:,:) = pv_r3d(:,:,:) + zofs 
     595 
     596         IF( istop == nstop ) THEN   ! no additional errors until this point... 
     597            IF(lwp) WRITE(numout,*) '           read '//TRIM(cdvar)//' in '//TRIM(iom_file(kiomid)%name)//' ok' 
     598             
     599            !--- overlap areas and extra hallows (mpp) 
     600            IF(     PRESENT(pv_r2d) .AND. idom /= jpdom_unknown ) THEN 
     601               CALL lbc_lnk( pv_r2d,'Z',-999.,'no0' ) 
     602            ELSEIF( PRESENT(pv_r3d) .AND. idom /= jpdom_unknown ) THEN 
     603               ! this if could be simplified with the new lbc_lnk that works with any size of the 3rd dimension 
     604               IF( icnt(3) == jpk ) THEN 
     605                  CALL lbc_lnk( pv_r3d,'Z',-999.,'no0' ) 
     606               ELSE   ! put some arbitrary value (a call to lbc_lnk will be done later...) 
     607                  DO jj = nlcj+1, jpj   ;   pv_r3d(1:nlci, jj, :) = pv_r3d(1:nlci, nlej, :)   ;   END DO 
     608                  DO ji = nlci+1, jpi   ;   pv_r3d(ji    , : , :) = pv_r3d(nlei  , :   , :)   ;   END DO 
     609               ENDIF 
     610            ENDIF 
     611             
     612            !--- Apply scale_factor and offset 
     613            zscf = iom_file(kiomid)%scf(idvar)      ! scale factor 
     614            zofs = iom_file(kiomid)%ofs(idvar)      ! offset 
     615            IF(     PRESENT(pv_r1d) ) THEN 
     616               IF( zscf /= 1. )   pv_r1d(:) = pv_r1d(:) * zscf  
     617               IF( zofs /= 0. )   pv_r1d(:) = pv_r1d(:) + zofs 
     618            ELSEIF( PRESENT(pv_r2d) ) THEN 
     619               !CDIR COLLAPSE 
     620               IF( zscf /= 1.)   pv_r2d(:,:) = pv_r2d(:,:) * zscf 
     621               !CDIR COLLAPSE 
     622               IF( zofs /= 0.)   pv_r2d(:,:) = pv_r2d(:,:) + zofs 
     623            ELSEIF( PRESENT(pv_r3d) ) THEN 
     624               !CDIR COLLAPSE 
     625               IF( zscf /= 1.)   pv_r3d(:,:,:) = pv_r3d(:,:,:) * zscf 
     626               !CDIR COLLAPSE 
     627               IF( zofs /= 0.)   pv_r3d(:,:,:) = pv_r3d(:,:,:) + zofs 
     628            ENDIF 
     629            ! 
    615630         ENDIF 
    616631         ! 
     
    634649      !--------------------------------------------------------------------- 
    635650      ! 
    636       clinfo = 'iom_gettime, file: '//trim(iom_file(kiomid)%name)//', var: '//trim(cdvar) 
    637       idvar = iom_varid( kiomid, cdvar ) 
    638       ! 
    639       ptime(:) = 0. ! default definition 
    640       IF( idvar > 0 ) THEN 
    641          IF( iom_file(kiomid)%ndims(idvar) == 1 ) THEN 
    642             IF( iom_file(kiomid)%luld(idvar) ) THEN 
    643                IF( iom_file(kiomid)%dimsz(1,idvar) == size(ptime) ) THEN 
    644                   SELECT CASE (iom_file(kiomid)%iolib) 
    645                   CASE (jpioipsl )   ;   CALL iom_ioipsl_gettime( kiomid, idvar, ptime ) 
    646                   CASE (jpnf90   )   ;   CALL iom_nf90_gettime(   kiomid, idvar, ptime ) 
    647                   CASE (jprstdimg)   ;   CALL ctl_stop( TRIM(clinfo)//' case IO library == jprstdimg not coded...' ) 
    648                   CASE DEFAULT     
    649                      CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
    650                   END SELECT 
     651      IF( kiomid > 0 ) THEN 
     652         clinfo = 'iom_gettime, file: '//trim(iom_file(kiomid)%name)//', var: '//trim(cdvar) 
     653         idvar = iom_varid( kiomid, cdvar ) 
     654         ! 
     655         ptime(:) = 0. ! default definition 
     656         IF( idvar > 0 ) THEN 
     657            IF( iom_file(kiomid)%ndims(idvar) == 1 ) THEN 
     658               IF( iom_file(kiomid)%luld(idvar) ) THEN 
     659                  IF( iom_file(kiomid)%dimsz(1,idvar) == size(ptime) ) THEN 
     660                     SELECT CASE (iom_file(kiomid)%iolib) 
     661                     CASE (jpioipsl )   ;   CALL iom_ioipsl_gettime( kiomid, idvar, ptime ) 
     662                     CASE (jpnf90   )   ;   CALL iom_nf90_gettime(   kiomid, idvar, ptime ) 
     663                     CASE (jprstdimg)   ;   CALL ctl_stop( TRIM(clinfo)//' case IO library == jprstdimg not coded...' ) 
     664                     CASE DEFAULT     
     665                        CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     666                     END SELECT 
     667                  ELSE 
     668                     WRITE(ctmp1,*) 'error with the size of ptime ',size(ptime),iom_file(kiomid)%dimsz(1,idvar) 
     669                     CALL ctl_stop( trim(clinfo), trim(ctmp1) ) 
     670                  ENDIF 
    651671               ELSE 
    652                   WRITE(ctmp1,*) 'error with the size of ptime ',size(ptime),iom_file(kiomid)%dimsz(1,idvar) 
    653                   CALL ctl_stop( trim(clinfo), trim(ctmp1) ) 
     672                  CALL ctl_stop( trim(clinfo), 'variable dimension is not unlimited... use iom_get' ) 
    654673               ENDIF 
    655674            ELSE 
    656                CALL ctl_stop( trim(clinfo), 'variable dimension is not unlimited... use iom_get' ) 
     675               CALL ctl_stop( trim(clinfo), 'the variable has more than 1 dimension' ) 
    657676            ENDIF 
    658677         ELSE 
    659             CALL ctl_stop( trim(clinfo), 'the variable has more than 1 dimension' ) 
    660          ENDIF 
    661       ELSE 
    662          CALL ctl_stop( trim(clinfo), 'variable not found in '//iom_file(kiomid)%name ) 
     678            CALL ctl_stop( trim(clinfo), 'variable not found in '//iom_file(kiomid)%name ) 
     679         ENDIF 
    663680      ENDIF 
    664681      ! 
     
    677694      INTEGER         , INTENT(in), OPTIONAL               ::   ktype    ! variable external type 
    678695      INTEGER :: ivid   ! variable id 
    679       IF( iom_file(kiomid)%nfid > 0 ) THEN 
    680          ivid = iom_varid(kiomid, cdvar) 
    681          SELECT CASE (iom_file(kiomid)%iolib) 
    682          CASE (jpioipsl )   ;   CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r0d = pvar ) 
    683          CASE (jpnf90   )   ;   CALL iom_nf90_rstput(   kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r0d = pvar ) 
    684          CASE (jprstdimg)   ;   IF( kt == kwrite )    CALL iom_rstdimg_rstput( kiomid, cdvar, ivid, pvar ) 
    685          CASE DEFAULT      
    686             CALL ctl_stop( 'iom_rp0d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
    687          END SELECT 
    688       END IF 
     696      IF( kiomid > 0 ) THEN 
     697         IF( iom_file(kiomid)%nfid > 0 ) THEN 
     698            ivid = iom_varid(kiomid, cdvar) 
     699            SELECT CASE (iom_file(kiomid)%iolib) 
     700            CASE (jpioipsl )   ;   CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r0d = pvar ) 
     701            CASE (jpnf90   )   ;   CALL iom_nf90_rstput(   kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r0d = pvar ) 
     702            CASE (jprstdimg)   ;   IF( kt == kwrite )    CALL iom_rstdimg_rstput( kiomid, cdvar, ivid, pvar ) 
     703            CASE DEFAULT      
     704               CALL ctl_stop( 'iom_rp0d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     705            END SELECT 
     706         ENDIF 
     707      ENDIF 
    689708   END SUBROUTINE iom_rp0d 
    690709 
     
    697716      INTEGER         , INTENT(in), OPTIONAL               ::   ktype    ! variable external type 
    698717      INTEGER :: ivid   ! variable id 
    699       IF( iom_file(kiomid)%nfid > 0 ) THEN 
    700          ivid = iom_varid(kiomid, cdvar) 
    701          SELECT CASE (iom_file(kiomid)%iolib) 
    702          CASE (jpioipsl )   ;   CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r1d = pvar ) 
    703          CASE (jpnf90   )   ;   CALL iom_nf90_rstput(   kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r1d = pvar ) 
    704          CASE (jprstdimg)   ;   IF( kt == kwrite )    CALL iom_rstdimg_rstput( kiomid, cdvar, ivid, pv_r1d = pvar ) 
    705          CASE DEFAULT      
    706             CALL ctl_stop( 'iom_rp1d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
    707          END SELECT 
    708       END IF 
     718      IF( kiomid > 0 ) THEN 
     719         IF( iom_file(kiomid)%nfid > 0 ) THEN 
     720            ivid = iom_varid(kiomid, cdvar) 
     721            SELECT CASE (iom_file(kiomid)%iolib) 
     722            CASE (jpioipsl )   ;   CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r1d = pvar ) 
     723            CASE (jpnf90   )   ;   CALL iom_nf90_rstput(   kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r1d = pvar ) 
     724            CASE (jprstdimg)   ;   IF( kt == kwrite )    CALL iom_rstdimg_rstput( kiomid, cdvar, ivid, pv_r1d = pvar ) 
     725            CASE DEFAULT      
     726               CALL ctl_stop( 'iom_rp1d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     727            END SELECT 
     728         ENDIF 
     729      ENDIF 
    709730   END SUBROUTINE iom_rp1d 
    710731 
     
    717738      INTEGER         , INTENT(in), OPTIONAL               ::   ktype    ! variable external type 
    718739      INTEGER :: ivid   ! variable id 
    719       IF( iom_file(kiomid)%nfid > 0 ) THEN 
    720          ivid = iom_varid(kiomid, cdvar) 
    721          SELECT CASE (iom_file(kiomid)%iolib) 
    722          CASE (jpioipsl )   ;   CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r2d = pvar ) 
    723          CASE (jpnf90   )   ;   CALL iom_nf90_rstput(   kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r2d = pvar ) 
    724          CASE (jprstdimg)   ;   IF( kt == kwrite )   CALL iom_rstdimg_rstput( kiomid, cdvar, ivid, pv_r2d = pvar )  
    725          CASE DEFAULT      
    726             CALL ctl_stop( 'iom_rp2d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
    727          END SELECT 
    728       END IF 
     740      IF( kiomid > 0 ) THEN 
     741         IF( iom_file(kiomid)%nfid > 0 ) THEN 
     742            ivid = iom_varid(kiomid, cdvar) 
     743            SELECT CASE (iom_file(kiomid)%iolib) 
     744            CASE (jpioipsl )   ;   CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r2d = pvar ) 
     745            CASE (jpnf90   )   ;   CALL iom_nf90_rstput(   kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r2d = pvar ) 
     746            CASE (jprstdimg)   ;   IF( kt == kwrite )   CALL iom_rstdimg_rstput( kiomid, cdvar, ivid, pv_r2d = pvar )  
     747            CASE DEFAULT      
     748               CALL ctl_stop( 'iom_rp2d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     749            END SELECT 
     750         ENDIF 
     751      ENDIF 
    729752   END SUBROUTINE iom_rp2d 
    730753 
     
    737760      INTEGER         , INTENT(in), OPTIONAL               ::   ktype    ! variable external type 
    738761      INTEGER :: ivid   ! variable id 
    739       IF( iom_file(kiomid)%nfid > 0 ) THEN 
    740          ivid = iom_varid(kiomid, cdvar) 
    741          SELECT CASE (iom_file(kiomid)%iolib) 
    742          CASE (jpioipsl )   ;   CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r3d = pvar ) 
    743          CASE (jpnf90   )   ;   CALL iom_nf90_rstput(   kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r3d = pvar ) 
    744          CASE (jprstdimg)   ;   IF( kt == kwrite )   CALL iom_rstdimg_rstput( kiomid, cdvar, ivid, pv_r3d = pvar ) 
    745          CASE DEFAULT      
    746             CALL ctl_stop( 'iom_rp3d: accepted IO library are only jpioipsl and jprstdimg' ) 
    747          END SELECT 
    748       END IF 
     762      IF( kiomid > 0 ) THEN 
     763         IF( iom_file(kiomid)%nfid > 0 ) THEN 
     764            ivid = iom_varid(kiomid, cdvar) 
     765            SELECT CASE (iom_file(kiomid)%iolib) 
     766            CASE (jpioipsl )   ;   CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r3d = pvar ) 
     767            CASE (jpnf90   )   ;   CALL iom_nf90_rstput(   kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r3d = pvar ) 
     768            CASE (jprstdimg)   ;   IF( kt == kwrite )   CALL iom_rstdimg_rstput( kiomid, cdvar, ivid, pv_r3d = pvar ) 
     769            CASE DEFAULT      
     770               CALL ctl_stop( 'iom_rp3d: accepted IO library are only jpioipsl and jprstdimg' ) 
     771            END SELECT 
     772         ENDIF 
     773      ENDIF 
    749774   END SUBROUTINE iom_rp3d 
    750775   !!---------------------------------------------------------------------- 
  • trunk/NEMO/OPA_SRC/IOM/iom_def.F90

    r577 r679  
    88   !!--------------------------------------------------------------------------------- 
    99   !! OPA 9.0 , LOCEAN-IPSL (2006)  
    10    !! $Header$  
     10   !! $Header: /home/opalod/NEMOCVSROOT/NEMO/OPA_SRC/IOM/iom_def.F90,v 1.7 2007/06/05 10:33:38 opalod Exp $  
    1111   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    1212   !!--------------------------------------------------------------------------------- 
     
    2424   INTEGER, PARAMETER, PUBLIC ::   jpdom_local_noovlap = 6   !: (nldi:nlei  ,nldj:nlej  ) 
    2525   INTEGER, PARAMETER, PUBLIC ::   jpdom_unknown       = 7   !: No dimension checking 
     26   INTEGER, PARAMETER, PUBLIC ::   jpdom_autoglo       = 8   !:  
     27   INTEGER, PARAMETER, PUBLIC ::   jpdom_autodta       = 9   !:  
    2628 
    2729   INTEGER, PARAMETER, PUBLIC ::   jpioipsl    = 100      !: Use ioipsl (fliocom only) library 
  • trunk/NEMO/OPA_SRC/IOM/iom_ioipsl.F90

    r588 r679  
    1919   USE in_out_manager  ! I/O manager 
    2020   USE dom_oce         ! ocean space and time domain 
    21    USE lbclnk          ! lateal boundary condition / mpp exchanges 
    2221   USE iom_def         ! iom variables definitions 
    2322   USE ioipsl          ! IOIPSL library 
     
    3635   !!---------------------------------------------------------------------- 
    3736   !!  OPA 9.0 , LOCEAN-IPSL (2006) 
    38    !! $Header$ 
     37   !! $Header: /home/opalod/NEMOCVSROOT/NEMO/OPA_SRC/IOM/iom_ioipsl.F90,v 1.8 2007/06/29 14:10:50 opalod Exp $ 
    3938   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    4039   !!---------------------------------------------------------------------- 
     
    4847      !! ** Purpose :  open an input file with IOIPSL (only fliocom module) 
    4948      !!--------------------------------------------------------------------- 
    50       CHARACTER(len=*)       , INTENT(inout) ::   cdname    ! File name 
    51       INTEGER                , INTENT(  out) ::   kiomid    ! ioipsl identifier of the opened file 
    52       LOGICAL                , INTENT(in   ) ::   ldwrt     ! read or write the file? 
    53       LOGICAL                , INTENT(in   ) ::   ldok      ! check the existence  
    54       INTEGER, DIMENSION(2,5), INTENT(in   ) ::   kdompar   ! domain parameters:  
     49      CHARACTER(len=*)       , INTENT(inout)           ::   cdname    ! File name 
     50      INTEGER                , INTENT(  out)           ::   kiomid    ! ioipsl identifier of the opened file 
     51      LOGICAL                , INTENT(in   )           ::   ldwrt     ! read or write the file? 
     52      LOGICAL                , INTENT(in   )           ::   ldok      ! check the existence  
     53      INTEGER, DIMENSION(2,5), INTENT(in   ), OPTIONAL ::   kdompar   ! domain parameters:  
    5554 
    5655      CHARACTER(LEN=100) ::   clinfo     ! info character 
     
    9392            ENDIF 
    9493         ELSE              ! the file should be open for read mode so it must exist... 
    95             CALL ctl_stop( TRIM(clinfo), 'File '//cdname(1:iln-1)//'* not found' ) 
     94            CALL ctl_stop( TRIM(clinfo), ' should be impossible case...' ) 
    9695         ENDIF 
    9796      ENDIF 
     
    219218 
    220219 
    221    SUBROUTINE iom_ioipsl_g123d( kiomid, kdom, kvid, knbdim, kstart, kcount,    & 
    222          &                          pv_r1d, pv_r2d, pv_r3d) 
     220   SUBROUTINE iom_ioipsl_g123d( kiomid, kvid, knbdim, kstart, kcount, kx1, kx2, ky1, ky2,   & 
     221         &                      pv_r1d, pv_r2d, pv_r3d) 
    223222      !!----------------------------------------------------------------------- 
    224223      !!                  ***  ROUTINE  iom_ioipsl_g123d  *** 
     
    229228      !!----------------------------------------------------------------------- 
    230229      INTEGER                    , INTENT(in   )           ::   kiomid     ! iom identifier of the file 
    231       INTEGER                    , INTENT(in   )           ::   kdom       ! Type of domain to be read 
    232230      INTEGER                    , INTENT(in   )           ::   kvid       ! Name of the variable 
    233231      INTEGER                    , INTENT(in   )           ::   knbdim     ! number of dimensions of the variable 
    234232      INTEGER , DIMENSION(:)     , INTENT(in   )           ::   kstart     ! start position of the reading in each axis  
    235233      INTEGER , DIMENSION(:)     , INTENT(in   )           ::   kcount     ! number of points to be read in each axis 
     234      INTEGER ,                    INTENT(in   )           ::   kx1, kx2, ky1, ky2   ! subdomain indexes 
    236235      REAL(wp), DIMENSION(:)     , INTENT(  out), OPTIONAL ::   pv_r1d     ! read field (1D case) 
    237236      REAL(wp), DIMENSION(:,:)   , INTENT(  out), OPTIONAL ::   pv_r2d     ! read field (2D case) 
     
    241240      CHARACTER(LEN=100)    ::   clvn       ! variable name 
    242241      !--------------------------------------------------------------------- 
    243       clvn = TRIM(iom_file(kiomid)%cn_var(kvid)) 
    244       ioipslid = iom_file(kiomid)%nfid 
     242      clvn = TRIM(iom_file(kiomid)%cn_var(kvid))   ! get back variable name  
     243      ioipslid = iom_file(kiomid)%nfid             ! get back IPIPSL file id 
    245244      ! 
    246245      IF( PRESENT(pv_r1d) ) THEN 
    247          CALL fliogetv( ioipslid, clvn, pv_r1d(:), start=kstart(1:knbdim), count=kcount(1:knbdim) ) 
     246         CALL fliogetv( ioipslid, clvn, pv_r1d(:                ), start = kstart(1:knbdim), count = kcount(1:knbdim) ) 
    248247      ELSEIF( PRESENT(pv_r2d) ) THEN 
    249          IF( kdom /= jpdom_unknown ) THEN 
    250             CALL fliogetv( ioipslid, clvn, pv_r2d(nldi:nlei,nldj:nlej), start=kstart(1:knbdim), count=kcount(1:knbdim) ) 
    251             !--- Fill the overlap areas and extra hallows (mpp) 
    252             CALL lbc_lnk (pv_r2d,'Z',-999.,'no0') 
    253          ELSE 
    254             CALL fliogetv( ioipslid, clvn, pv_r2d(:,:), start=kstart(1:knbdim), count=kcount(1:knbdim) ) 
    255          ENDIF 
     248         CALL fliogetv( ioipslid, clvn, pv_r2d(kx1:kx2,ky1:ky2  ), start = kstart(1:knbdim), count = kcount(1:knbdim) ) 
    256249      ELSEIF( PRESENT(pv_r3d) ) THEN 
    257          IF( kdom /= jpdom_unknown ) THEN 
    258             CALL fliogetv( ioipslid, clvn, pv_r3d(nldi:nlei,nldj:nlej,:), start=kstart(1:knbdim),   & 
    259                   &                                                         count=kcount  (1:knbdim) ) 
    260             !--- Fill the overlap areas and extra hallows (mpp) 
    261             ! this if could be simplified with the new lbc_lnk that works with any size of the 3rd dimension 
    262             IF( kcount(3) == jpk ) THEN 
    263                CALL lbc_lnk( pv_r3d,'Z',-999.,'no0' ) 
    264             ELSE   ! put some arbitrary value (a call to lbc_lnk will be done later...) 
    265                pv_r3d(nlei+1:jpi,      :   ,:) = 1.             
    266                pv_r3d(      :   ,nlej+1:jpj,:) = 1.             
    267             ENDIF 
    268          ELSE 
    269             CALL fliogetv( ioipslid, clvn, pv_r3d(:,:,:), start=kstart(1:knbdim), count=kcount(1:knbdim) ) 
    270          ENDIF 
     250         CALL fliogetv( ioipslid, clvn, pv_r3d(kx1:kx2,ky1:ky2,:), start = kstart(1:knbdim), count = kcount(1:knbdim) ) 
    271251      ENDIF 
    272252      ! 
  • trunk/NEMO/OPA_SRC/IOM/iom_nf90.F90

    r588 r679  
    3636   !!---------------------------------------------------------------------- 
    3737   !!  OPA 9.0 , LOCEAN-IPSL (2006) 
    38    !! $Header$ 
     38   !! $Header: /home/opalod/NEMOCVSROOT/NEMO/OPA_SRC/IOM/iom_nf90.F90,v 1.8 2007/06/29 14:10:50 opalod Exp $ 
    3939   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    4040   !!---------------------------------------------------------------------- 
     
    4848      !! ** Purpose : open an input file with NF90 
    4949      !!--------------------------------------------------------------------- 
    50       CHARACTER(len=*)       , INTENT(inout) ::   cdname    ! File name 
    51       INTEGER                , INTENT(  out) ::   kiomid    ! nf90 identifier of the opened file 
    52       LOGICAL                , INTENT(in   ) ::   ldwrt     ! read or write the file? 
    53       LOGICAL                , INTENT(in   ) ::   ldok      ! check the existence  
    54       INTEGER, DIMENSION(2,5), INTENT(in   ) ::   kdompar   ! domain parameters:  
     50      CHARACTER(len=*)       , INTENT(inout)           ::   cdname    ! File name 
     51      INTEGER                , INTENT(  out)           ::   kiomid    ! nf90 identifier of the opened file 
     52      LOGICAL                , INTENT(in   )           ::   ldwrt     ! read or write the file? 
     53      LOGICAL                , INTENT(in   )           ::   ldok      ! check the existence  
     54      INTEGER, DIMENSION(2,5), INTENT(in   ), OPTIONAL ::   kdompar   ! domain parameters:  
    5555 
    5656      CHARACTER(LEN=100) ::   clinfo   ! info character 
     
    104104            CALL iom_nf90_check(NF90_PUT_ATT( if90id, NF90_GLOBAL, 'DOMAIN_type'           , 'BOX'              ), clinfo) 
    105105         ELSE              ! the file should be open for read mode so it must exist... 
    106             CALL ctl_stop( TRIM(clinfo), 'File '//cdname(1:iln-1)//'* not found' ) 
     106            CALL ctl_stop( TRIM(clinfo), ' should be impossible case...' ) 
    107107         ENDIF 
    108108      ENDIF 
     
    232232 
    233233 
    234    SUBROUTINE iom_nf90_g123d( kiomid, kdom, kvid, knbdim, kstart, kcount,    & 
    235          &                          pv_r1d, pv_r2d, pv_r3d) 
     234   SUBROUTINE iom_nf90_g123d( kiomid, kvid, knbdim, kstart, kcount, kx1, kx2, ky1, ky2,   & 
     235         &                    pv_r1d, pv_r2d, pv_r3d ) 
    236236      !!----------------------------------------------------------------------- 
    237237      !!                  ***  ROUTINE  iom_nf90_g123d  *** 
     
    242242      !!----------------------------------------------------------------------- 
    243243      INTEGER                    , INTENT(in   )           ::   kiomid    ! iom identifier of the file 
    244       INTEGER                    , INTENT(in   )           ::   kdom      ! Type of domain to be read 
    245244      INTEGER                    , INTENT(in   )           ::   kvid      ! Name of the variable 
    246245      INTEGER                    , INTENT(in   )           ::   knbdim    ! number of dimensions of the variable 
    247246      INTEGER , DIMENSION(:)     , INTENT(in   )           ::   kstart    ! start position of the reading in each axis  
    248247      INTEGER , DIMENSION(:)     , INTENT(in   )           ::   kcount    ! number of points to be read in each axis 
     248      INTEGER ,                    INTENT(in   )           ::   kx1, kx2, ky1, ky2   ! subdomain indexes 
    249249      REAL(wp), DIMENSION(:)     , INTENT(  out), OPTIONAL ::   pv_r1d    ! read field (1D case) 
    250250      REAL(wp), DIMENSION(:,:)   , INTENT(  out), OPTIONAL ::   pv_r2d    ! read field (2D case) 
    251251      REAL(wp), DIMENSION(:,:,:) , INTENT(  out), OPTIONAL ::   pv_r3d    ! read field (3D case) 
    252252      ! 
    253       CHARACTER(LEN=100) ::   clinfo   ! info character 
    254       INTEGER            ::   if90id   ! nf90 identifier of the opened file 
    255       INTEGER            ::   ivid     ! nf90 variable id 
     253      CHARACTER(LEN=100) ::   clinfo               ! info character 
     254      INTEGER            ::   if90id               ! nf90 identifier of the opened file 
     255      INTEGER            ::   ivid                 ! nf90 variable id 
    256256      !--------------------------------------------------------------------- 
    257257      clinfo = 'iom_nf90_g123d , file: '//TRIM(iom_file(kiomid)%name)//', var: '//TRIM(iom_file(kiomid)%cn_var(kvid)) 
    258258      if90id = iom_file(kiomid)%nfid         ! get back NetCDF file id 
    259259      ivid   = iom_file(kiomid)%nvid(kvid)   ! get back NetCDF var id 
    260       IF( PRESENT(pv_r1d) ) THEN 
    261          CALL iom_nf90_check(NF90_GET_VAR(if90id, ivid, pv_r1d(:), start=kstart(1:knbdim), count=kcount(1:knbdim)), clinfo ) 
     260      ! 
     261      IF(     PRESENT(pv_r1d) ) THEN 
     262         CALL iom_nf90_check( NF90_GET_VAR(if90id, ivid, pv_r1d(:                ), start = kstart(1:knbdim),   & 
     263            &                                                                       count = kcount(1:knbdim)), clinfo ) 
    262264      ELSEIF( PRESENT(pv_r2d) ) THEN 
    263          IF( kdom /= jpdom_unknown ) THEN 
    264             CALL iom_nf90_check(NF90_GET_VAR(if90id, ivid, pv_r2d(nldi:nlei,nldj:nlej),   & 
    265                   &                           start=kstart(1:knbdim), count=kcount(1:knbdim)), clinfo) 
    266             !--- Fill the overlap areas and extra hallows (mpp) 
    267             CALL lbc_lnk (pv_r2d,'Z',-999.,'no0') 
    268          ELSE 
    269             CALL iom_nf90_check(NF90_GET_VAR(if90id, ivid, pv_r2d(:,:), start=kstart(1:knbdim), count=kcount(1:knbdim)), clinfo) 
    270          ENDIF 
     265         CALL iom_nf90_check( NF90_GET_VAR(if90id, ivid, pv_r2d(kx1:kx2,ky1:ky2  ), start = kstart(1:knbdim),   & 
     266            &                                                                       count = kcount(1:knbdim)), clinfo ) 
    271267      ELSEIF( PRESENT(pv_r3d) ) THEN 
    272          IF( kdom /= jpdom_unknown ) THEN 
    273             CALL iom_nf90_check(NF90_GET_VAR(if90id, ivid, pv_r3d(nldi:nlei,nldj:nlej,:),   & 
    274                   &                           start=kstart(1:knbdim), count=kcount  (1:knbdim)), clinfo) 
    275             !--- Fill the overlap areas and extra hallows (mpp) 
    276             ! this if could be simplified with the new lbc_lnk that works with any size of the 3rd dimension 
    277             IF( kcount(3) == jpk ) THEN 
    278                CALL lbc_lnk( pv_r3d,'Z',-999.,'no0' ) 
    279             ELSE   ! put some arbitrary value (a call to lbc_lnk will be done later...) 
    280                pv_r3d(nlei+1:jpi,      :   ,:) = 1.             
    281                pv_r3d(      :   ,nlej+1:jpj,:) = 1.             
    282             ENDIF 
    283          ELSE 
    284             CALL iom_nf90_check(NF90_GET_VAR(if90id, ivid, pv_r3d(:,:,:),   & 
    285                   &                           start=kstart(1:knbdim), count=kcount  (1:knbdim)), clinfo) 
    286          ENDIF 
     268         CALL iom_nf90_check( NF90_GET_VAR(if90id, ivid, pv_r3d(kx1:kx2,ky1:ky2,:), start = kstart(1:knbdim),   & 
     269            &                                                                       count = kcount(1:knbdim)), clinfo ) 
    287270      ENDIF 
    288271      ! 
  • trunk/NEMO/OPA_SRC/IOM/iom_rstdimg.F90

    r611 r679  
    3636   !!---------------------------------------------------------------------- 
    3737   !!  OPA 9.0 , LOCEAN-IPSL (2006) 
    38    !! $Header$ 
     38   !! $Header: /home/opalod/NEMOCVSROOT/NEMO/OPA_SRC/IOM/iom_rstdimg.F90,v 1.9 2007/06/29 14:10:50 opalod Exp $ 
    3939   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    4040   !!---------------------------------------------------------------------- 
     
    4848      !! ** Purpose :  open an input file read only (return 0 if not found) 
    4949      !!--------------------------------------------------------------------- 
    50       CHARACTER(len=*)       , INTENT(inout) ::   cdname   ! File name 
    51       INTEGER                , INTENT(  out) ::   kiomid   ! iom identifier of the opened file 
    52       LOGICAL                , INTENT(in   ) ::   ldwrt    ! read or write the file? 
    53       LOGICAL                , INTENT(in   ) ::   ldok     ! check the existence  
    54       INTEGER, DIMENSION(2,5), INTENT(in   ) ::   kdompar  ! domain parameters:  
     50      CHARACTER(len=*)       , INTENT(inout)           ::   cdname   ! File name 
     51      INTEGER                , INTENT(  out)           ::   kiomid   ! iom identifier of the opened file 
     52      LOGICAL                , INTENT(in   )           ::   ldwrt    ! read or write the file? 
     53      LOGICAL                , INTENT(in   )           ::   ldok     ! check the existence  
     54      INTEGER, DIMENSION(2,5), INTENT(in   ), OPTIONAL ::   kdompar  ! domain parameters:  
    5555 
    5656      CHARACTER(LEN=100)                      ::   clinfo                     ! info character 
     
    113113               &       , RECL = irecl8, STATUS = 'new', ACTION = 'readwrite', IOSTAT = ios, ERR = 987 ) 
    114114         ELSE              ! the file should be open for read mode so it must exist... 
    115             CALL ctl_stop( TRIM(clinfo), 'File '//cdname(1:iln-1)//'* not found' ) 
     115            CALL ctl_stop( TRIM(clinfo), ' should be impossible case...' ) 
    116116         ENDIF 
    117117      ENDIF 
     
    128128         IF( iiglo /= jpiglo       )   CALL ctl_stop( TRIM(clinfo), 'Mismatch in global domain size in i direction' ) 
    129129         IF( ijglo /= jpjglo       )   CALL ctl_stop( TRIM(clinfo), 'Mismatch in global domain size in j direction' ) 
    130          IF( inx   /= kdompar(1,1) )   CALL ctl_stop( TRIM(clinfo), 'Mismatch in local domain size in i direction' ) 
    131          IF( iny   /= kdompar(2,1) )   CALL ctl_stop( TRIM(clinfo), 'Mismatch in local domain size in j direction' ) 
     130         IF( ldwrt ) THEN 
     131            IF( inx   /= kdompar(1,1) )   CALL ctl_stop( TRIM(clinfo), 'Mismatch in local domain size in i direction' ) 
     132            IF( iny   /= kdompar(2,1) )   CALL ctl_stop( TRIM(clinfo), 'Mismatch in local domain size in j direction' ) 
     133         ENDIF 
    132134         IF( inz   /= jpk          )   CALL ctl_stop( TRIM(clinfo), 'Mismatch in domain size in k direction' ) 
    133135         IF( ipni  /= jpni         )   CALL ctl_stop( TRIM(clinfo), 'Processor splitting changed along I' ) 
     
    347349 
    348350 
    349    SUBROUTINE iom_rstdimg_g123d( kiomid, kdom  , kvid  , kstart, kcount,    & 
    350          &                          pv_r1d, pv_r2d, pv_r3d ) 
     351   SUBROUTINE iom_rstdimg_g123d( kiomid, kdom  , kvid, kx1, kx2, ky1, ky2,   & 
     352         &                       pv_r1d, pv_r2d, pv_r3d ) 
    351353      !!----------------------------------------------------------------------- 
    352354      !!                  ***  ROUTINE  iom_rstdimg_g123d  *** 
     
    359361      INTEGER                    , INTENT(in   )           ::   kdom       ! Type of domain to be read 
    360362      INTEGER                    , INTENT(in   )           ::   kvid       ! variable id 
    361       INTEGER , DIMENSION(:)     , INTENT(in   )           ::   kstart     ! start position of the reading in each axis  
    362       INTEGER , DIMENSION(:)     , INTENT(in   )           ::   kcount     ! number of points to be read in each axis 
     363      INTEGER ,                    INTENT(inout)           ::   kx1, kx2, ky1, ky2   ! subdomain indexes 
    363364      REAL(wp), DIMENSION(:)     , INTENT(  out), OPTIONAL ::   pv_r1d     ! read field (1D case) 
    364365      REAL(wp), DIMENSION(:,:)   , INTENT(  out), OPTIONAL ::   pv_r2d     ! read field (2D case) 
     
    369370      INTEGER            ::   jk                   ! loop counter 
    370371      INTEGER            ::   idrst                ! logical unit of the restart file 
    371       INTEGER            ::   istop                ! temporary storage of nstop 
    372       INTEGER            ::   ix1, ix2, iy1, iy2   ! subdomain indexes 
    373372      !--------------------------------------------------------------------- 
    374373      clinfo = '                    iom_rstdimg_g123d ~~~  ' 
    375374      ! 
    376       istop = nstop                   ! store the actual value of nstop 
    377       idrst = iom_file(kiomid)%nfid   ! get back the logical unit of the restart file 
    378       IF( kdom == jpdom_data .OR. kdom == jpdom_global )   & 
    379             &   CALL ctl_stop( TRIM(clinfo), TRIM(iom_file(kiomid)%cn_var(kvid))//': case not coded for rstdimg files' ) 
    380       ! 
    381       IF( istop == nstop .AND. kvid > 0 ) THEN 
    382          IF( .NOT. PRESENT(pv_r1d) ) THEN 
    383             SELECT CASE (kdom)   ! find the right index of the array to be read 
    384             CASE (jpdom_local_full)      ;   ix1 = nldi   ;   ix2 = nlei   ;   iy1 = nldj   ;   iy2 = nlej 
    385             CASE (jpdom_local_noextra)   ;   ix1 = 1      ;   ix2 = nlci   ;   iy1 = 1      ;   iy2 = nlcj 
    386             CASE (jpdom_local_noovlap)   ;   ix1 = nldi   ;   ix2 = nlei   ;   iy1 = nldj   ;   iy2 = nlej 
    387             CASE DEFAULT                 ;   CALL ctl_stop( clinfo, 'we should not be there...' ) 
    388             END SELECT 
    389          ENDIF 
     375      IF( kdom == jpdom_data .OR. kdom == jpdom_global ) THEN 
     376         CALL ctl_stop( TRIM(clinfo), TRIM(iom_file(kiomid)%cn_var(kvid))//': case not coded for rstdimg files' ) 
     377      ELSE 
     378      ! 
     379         idrst = iom_file(kiomid)%nfid   ! get back the logical unit of the restart file 
     380         ! modify the subdomain indexes because we cannot directly extract the appropriate subdomaine 
     381         IF(     kdom == jpdom_local_full    ) THEN   ;   kx1 = 1   ;   kx2 = jpi    ;   ky1 = 1 
     382         ELSEIF( kdom == jpdom_local_noextra ) THEN   ;   kx1 = 1   ;   kx2 = nlci   ;   ky1 = 1 
     383         ENDIF 
     384         ! 
    390385         IF(     PRESENT(pv_r1d) ) THEN   ! read 1D variables 
    391             READ( idrst, REC = iom_file(kiomid)%nvid(kvid), IOSTAT = ios, ERR = 987 )   pv_r1d(:) 
     386            READ(    idrst, REC = iom_file(kiomid)%nvid(kvid)         , IOSTAT = ios, ERR = 987 )   pv_r1d(:) 
    392387         ELSEIF( PRESENT(pv_r2d) ) THEN   ! read 2D variables 
    393             READ( idrst, REC = iom_file(kiomid)%nvid(kvid), IOSTAT = ios, ERR = 987 )   pv_r2d(ix1:ix2, iy1:iy2 ) 
    394             SELECT CASE (kdom) 
    395             CASE (jpdom_local_noextra)   !--- Fill extra hallows (mpp)        
    396                pv_r2d(nlci+1:jpi,      :   ) = 1.     
    397                pv_r2d(      :   ,nlcj+1:jpj) = 1.             
    398             CASE (jpdom_local_noovlap)   !--- Fill the overlap areas and extra hallows (mpp) 
    399                CALL lbc_lnk (pv_r2d,'Z',-999.,'no0') 
    400             CASE DEFAULT 
    401             END SELECT 
     388            READ(    idrst, REC = iom_file(kiomid)%nvid(kvid)         , IOSTAT = ios, ERR = 987 )   pv_r2d(kx1:kx2, ky1:ky2    ) 
    402389         ELSEIF( PRESENT(pv_r3d) ) THEN   ! read 3D variables 
    403390            DO jk = 1, iom_file(kiomid)%dimsz(3,kvid)   ! do loop on each level 
    404                READ( idrst, REC = iom_file(kiomid)%nvid(kvid) + jk - 1, IOSTAT = ios, ERR = 987 )   & 
    405                      &      pv_r3d( ix1:ix2, iy1:iy2, jk ) 
    406             END DO 
    407             SELECT CASE (kdom) 
    408             CASE (jpdom_local_noextra)   !--- Fill extra hallows (mpp)        
    409                pv_r3d(nlci+1:jpi,      :   ,:) = 1.     
    410                pv_r3d(      :   ,nlcj+1:jpj,:) = 1.             
    411             CASE (jpdom_local_noovlap)   !--- Fill the overlap areas and extra hallows (mpp) 
    412                ! this if could be simplified with the new lbc_lnk that works with any size of the 3rd dimension 
    413                IF( kcount(3) == jpk ) THEN 
    414                   CALL lbc_lnk( pv_r3d,'Z',-999.,'no0' ) 
    415                ELSE 
    416                   pv_r3d(nlei+1:jpi,      :   ,:) = 1.             
    417                   pv_r3d(      :   ,nlej+1:jpj,:) = 1.             
    418                ENDIF 
    419             CASE DEFAULT 
    420             END SELECT 
    421          ENDIF 
    422       ENDIF 
    423 987   CONTINUE 
    424       IF( ios /= 0 ) THEN 
    425          WRITE(ctmp1,*) '           iostat = ', ios 
    426          CALL ctl_stop( TRIM(clinfo), '   IO error with file '//TRIM(iom_file(kiomid)%name), ctmp1 ) 
     391               READ( idrst, REC = iom_file(kiomid)%nvid(kvid) + jk - 1, IOSTAT = ios, ERR = 987 )   pv_r3d(kx1:kx2, ky1:ky2, jk) 
     392            END DO 
     393         ENDIF 
     394987      CONTINUE 
     395         IF( ios /= 0 ) THEN 
     396            WRITE(ctmp1,*) '           iostat = ', ios 
     397            CALL ctl_stop( TRIM(clinfo), '   IO error with file '//TRIM(iom_file(kiomid)%name), ctmp1 ) 
     398         ENDIF 
    427399      ENDIF 
    428400      ! 
Note: See TracChangeset for help on using the changeset viewer.