MODULE iom !!===================================================================== !! *** MODULE iom *** !! Input/Output manager : Library to read input files !!==================================================================== !! History : 9.0 ! 05 12 (J. Belier) Original code !! 9.0 ! 06 02 (S. Masson) Adaptation to NEMO !!-------------------------------------------------------------------- !!gm caution add !DIR nec: improved performance to be checked as well as no result changes !!-------------------------------------------------------------------- !! iom_open : open a file read only !! iom_close : close a file or all files opened by iom !! iom_get : read a field (interfaced to several routines) !! iom_gettime : read the time axis cdvar in the file !! iom_varid : get the id of a variable in a file !! iom_rstput : write a field in a restart file (interfaced to several routines) !!-------------------------------------------------------------------- USE in_out_manager ! I/O manager USE dom_oce ! ocean space and time domain USE iom_def ! iom variables definitions USE iom_ioipsl ! NetCDF format with IOIPSL library USE iom_nf90 ! NetCDF format with native NetCDF library USE iom_rstdimg ! restarts access direct format "dimg" style... IMPLICIT NONE PUBLIC ! must be public to be able to access iom_def through iom PUBLIC iom_open, iom_close, iom_varid, iom_get, iom_gettime, iom_rstput INTERFACE iom_get MODULE PROCEDURE iom_g0d, iom_g1d, iom_g2d, iom_g3d END INTERFACE INTERFACE iom_rstput MODULE PROCEDURE iom_rp0d, iom_rp1d, iom_rp2d, iom_rp3d END INTERFACE !!---------------------------------------------------------------------- !! OPA 9.0 , LOCEAN-IPSL (2006) !! $Id$ !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE iom_open( cdname, kiomid, ldwrt, kdom, kiolib ) !!--------------------------------------------------------------------- !! *** SUBROUTINE iom_open *** !! !! ** Purpose : open an input file (return 0 if not found) !!--------------------------------------------------------------------- CHARACTER(len=*), INTENT(in ) :: cdname ! File name INTEGER , INTENT( out) :: kiomid ! iom identifier of the opened file LOGICAL , INTENT(in ), OPTIONAL :: ldwrt ! open in write modeb (default = .FALSE.) INTEGER , INTENT(in ), OPTIONAL :: kdom ! Type of domain to be written (default = jpdom_local_noovlap) INTEGER , INTENT(in ), OPTIONAL :: kiolib ! library used to open the file (default = jpnf90) CHARACTER(LEN=100) :: clname ! the name of the file based on cdname [[+clcpu]+clcpu] CHARACTER(LEN=100) :: cltmpn ! tempory name to store clname (in writting mode) CHARACTER(LEN=10) :: clsuffix ! ".nc" or ".dimg" CHARACTER(LEN=15) :: clcpu ! the cpu number (max jpmax_digits digits) CHARACTER(LEN=100) :: clinfo ! info character LOGICAL :: llok ! check the existence LOGICAL :: llwrt ! INTEGER :: iolib ! library do we use to open the file INTEGER :: icnt ! counter for digits in clcpu (max = jpmax_digits) INTEGER :: iln, ils ! lengths of character INTEGER :: idom ! type of domain INTEGER :: istop ! INTEGER, DIMENSION(2,5) :: idompar ! domain parameters: ! local number of points for x,y dimensions ! position of first local point for x,y dimensions ! position of last local point for x,y dimensions ! start halo size for x,y dimensions ! end halo size for x,y dimensions !--------------------------------------------------------------------- ! Initializations and control ! ============= clinfo = ' iom_open ~~~ ' istop = nstop ! if iom_open is called for the first time: initialize iom_file(:)%nfid to 0 ! (could be done when defining iom_file in f95 but not in f90) IF( iom_init == 0 ) THEN iom_file(:)%nfid = 0 iom_init = 1 ENDIF ! do we read or write the file? IF( PRESENT(ldwrt) ) THEN ; llwrt = ldwrt ELSE ; llwrt = .FALSE. ENDIF ! what library do we use to open the file? IF( PRESENT(kiolib) ) THEN ; iolib = kiolib ELSE ; iolib = jpnf90 ENDIF ! create the file name by added, if needed, TRIM(Agrif_CFixed()) and TRIM(clsuffix) ! ============= clname = trim(cdname) #if defined key_agrif if ( .NOT. Agrif_Root() ) clname = TRIM(Agrif_CFixed())//'_'//TRIM(clname) #endif ! which suffix should we use? SELECT CASE (iolib) CASE (jpioipsl ) ; clsuffix = '.nc' CASE (jpnf90 ) ; clsuffix = '.nc' CASE (jprstdimg) ; clsuffix = '.dimg' CASE DEFAULT ; clsuffix = '' CALL ctl_stop( TRIM(clinfo), 'accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) END SELECT ! Add the suffix if needed iln = LEN_TRIM(clname) ils = LEN_TRIM(clsuffix) IF( iln <= ils) clname = clname(1:iln)//TRIM(clsuffix) IF( clname(iln-ils+1:iln) /= TRIM(clsuffix) ) clname = clname(1:iln)//TRIM(clsuffix) cltmpn = clname ! store this name ! try to find if the file to be opened already exist ! ============= INQUIRE( FILE = clname, EXIST = llok ) IF( .NOT.llok ) THEN ! we try to add the cpu number to the name WRITE(clcpu,*) narea-1 clcpu = TRIM(ADJUSTL(clcpu)) iln = INDEX(clname,TRIM(clsuffix)) clname = clname(1:iln-1)//'_'//TRIM(clcpu)//TRIM(clsuffix) icnt = 0 INQUIRE( FILE = clname, EXIST = llok ) ! we try different formats for the cpu number by adding 0 DO WHILE( .NOT.llok .AND. icnt < jpmax_digits ) clcpu = "0"//trim(clcpu) clname = clname(1:iln-1)//'_'//TRIM(clcpu)//TRIM(clsuffix) INQUIRE( FILE = clname, EXIST = llok ) icnt = icnt + 1 END DO ENDIF ! check the domain definition idom = jpdom_local_noovlap ! default definition IF( PRESENT(kdom) ) idom = kdom ! create the domain informations ! ============= SELECT CASE (idom) CASE (jpdom_local_full) idompar(:,1) = (/ jpi , jpj /) idompar(:,2) = (/ nimpp , njmpp /) idompar(:,3) = (/ nimpp + jpi - 1 , njmpp + jpj - 1 /) idompar(:,4) = (/ nldi - 1 , nldj - 1 /) idompar(:,5) = (/ jpi - nlei , jpj - nlej /) CASE (jpdom_local_noextra) idompar(:,1) = (/ nlci , nlcj /) idompar(:,2) = (/ nimpp , njmpp /) idompar(:,3) = (/ nimpp + nlci - 1, njmpp + nlcj - 1 /) idompar(:,4) = (/ nldi - 1 , nldj - 1 /) idompar(:,5) = (/ nlci - nlei , nlcj - nlej /) CASE (jpdom_local_noovlap) idompar(:,1) = (/ nlei - nldi + 1 , nlej - nldj + 1 /) idompar(:,2) = (/ nimpp + nldi - 1, njmpp + nldj - 1 /) idompar(:,3) = (/ nimpp + nlei - 1, njmpp + nlej - 1 /) idompar(:,4) = (/ 0 , 0 /) idompar(:,5) = (/ 0 , 0 /) CASE DEFAULT CALL ctl_stop( TRIM(clinfo), 'wrong value of kdom, only jpdom_local* cases are accepted' ) END SELECT ! Open the NetCDF or RSTDIMG file ! ============= ! do we have some free file identifier? IF( MINVAL(iom_file(:)%nfid) /= 0 ) & & CALL ctl_stop( TRIM(clinfo), 'No more free file identifier', 'increase jpmax_files in iom_def' ) IF( istop == nstop ) THEN ! no error within this routine IF( .NOT. llok ) clname = cltmpn ! get back the file name without the cpu number SELECT CASE (iolib) CASE (jpioipsl ) ; CALL iom_ioipsl_open( clname, kiomid, llwrt, llok, idompar ) CASE (jpnf90 ) ; CALL iom_nf90_open( clname, kiomid, llwrt, llok, idompar ) CASE (jprstdimg) ; CALL iom_rstdimg_open( clname, kiomid, llwrt, llok, idompar ) CASE DEFAULT CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) END SELECT ENDIF ! END SUBROUTINE iom_open SUBROUTINE iom_close( kiomid ) !!-------------------------------------------------------------------- !! *** SUBROUTINE iom_close *** !! !! ** Purpose : close an input file, or all files opened by iom !!-------------------------------------------------------------------- INTEGER, INTENT(in), OPTIONAL :: kiomid ! iom identifier of the file to be closed ! ! No argument : all the files opened by iom are closed INTEGER :: jf ! dummy loop indices INTEGER :: i_s, i_e ! temporary integer CHARACTER(LEN=100) :: clinfo ! info character !--------------------------------------------------------------------- ! clinfo = ' iom_close ~~~ ' IF( PRESENT(kiomid) ) THEN i_s = kiomid i_e = kiomid ELSE i_s = 1 i_e = jpmax_files ENDIF IF( i_s > 0 ) THEN DO jf = i_s, i_e IF( iom_file(jf)%nfid > 0 ) THEN SELECT CASE (iom_file(jf)%iolib) CASE (jpioipsl ) ; CALL iom_ioipsl_close( jf ) CASE (jpnf90 ) ; CALL iom_nf90_close( jf ) CASE (jprstdimg) ; CALL iom_rstdimg_close( jf ) CASE DEFAULT CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) END SELECT iom_file(jf)%nfid = 0 ! free the id IF(lwp) WRITE(numout,*) TRIM(clinfo)//' close file: '//TRIM(iom_file(kiomid)%name)//' ok' ELSEIF( PRESENT(kiomid) ) THEN WRITE(ctmp1,*) '--->', kiomid CALL ctl_stop( TRIM(clinfo)//' Invalid file identifier', ctmp1 ) ENDIF END DO ENDIF ! END SUBROUTINE iom_close FUNCTION iom_varid ( kiomid, cdvar, kdimsz ) !!----------------------------------------------------------------------- !! *** FUNCTION iom_varid *** !! !! ** Purpose : get the id of a variable in a file (return 0 if not found) !!----------------------------------------------------------------------- INTEGER , INTENT(in ) :: kiomid ! file Identifier CHARACTER(len=*) , INTENT(in ) :: cdvar ! name of the variable INTEGER, DIMENSION(:), INTENT( out), OPTIONAL :: kdimsz ! size of the dimensions ! INTEGER :: iom_varid, iiv, i_nvd LOGICAL :: ll_fnd CHARACTER(LEN=100) :: clinfo ! info character !!----------------------------------------------------------------------- clinfo = 'iom_varid, file: '//trim(iom_file(kiomid)%name)//', var: '//trim(cdvar) iom_varid = 0 ! default definition ! IF( kiomid > 0 ) THEN IF( iom_file(kiomid)%nfid == 0 ) THEN CALL ctl_stop( trim(clinfo), 'the file is not open' ) ELSE ll_fnd = .FALSE. iiv = 0 ! DO WHILE ( .NOT.ll_fnd .AND. iiv < iom_file(kiomid)%nvars ) iiv = iiv + 1 ll_fnd = ( TRIM(cdvar) == TRIM(iom_file(kiomid)%cn_var(iiv)) ) END DO ! IF( .NOT.ll_fnd ) THEN iiv = iiv + 1 IF( iiv <= jpmax_vars ) THEN SELECT CASE (iom_file(kiomid)%iolib) CASE (jpioipsl ) ; iom_varid = iom_ioipsl_varid( kiomid, cdvar, iiv, kdimsz ) CASE (jpnf90 ) ; iom_varid = iom_nf90_varid( kiomid, cdvar, iiv, kdimsz ) CASE (jprstdimg) ; iom_varid = 0 ! all variables are listed in iom_file CASE DEFAULT CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) END SELECT ELSE CALL ctl_stop( trim(clinfo), 'Too many variables in the file '//iom_file(kiomid)%name, & & 'increase the parameter jpmax_vars') ENDIF ELSE iom_varid = iiv IF( PRESENT(kdimsz) ) THEN i_nvd = iom_file(kiomid)%ndims(iiv) IF( i_nvd == size(kdimsz) ) THEN kdimsz(:) = iom_file(kiomid)%dimsz(1:i_nvd,iiv) ELSE WRITE(ctmp1,*) i_nvd, size(kdimsz) CALL ctl_stop( trim(clinfo), 'error in kdimsz size'//trim(ctmp1) ) ENDIF ENDIF ENDIF ENDIF ENDIF ! END FUNCTION iom_varid !!---------------------------------------------------------------------- !! INTERFACE iom_get !!---------------------------------------------------------------------- SUBROUTINE iom_g0d( kiomid, cdvar, pvar ) INTEGER , INTENT(in ) :: kiomid ! Identifier of the file CHARACTER(len=*), INTENT(in ) :: cdvar ! Name of the variable REAL(wp) , INTENT( out) :: pvar ! read field ! INTEGER :: idvar ! variable id ! idvar = iom_varid( kiomid, cdvar ) IF( iom_file(kiomid)%nfid > 0 .AND. idvar > 0 ) THEN SELECT CASE (iom_file(kiomid)%iolib) CASE (jpioipsl ) ; CALL iom_ioipsl_get( kiomid, idvar, pvar ) CASE (jpnf90 ) ; CALL iom_nf90_get( kiomid, idvar, pvar ) CASE (jprstdimg) ; CALL iom_rstdimg_get( kiomid, idvar, pvar ) CASE DEFAULT CALL ctl_stop( 'iom_g0d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) END SELECT END IF END SUBROUTINE iom_g0d SUBROUTINE iom_g1d( kiomid, kdom, cdvar, pvar, ktime, kstart, kcount ) INTEGER , INTENT(in ) :: kiomid ! Identifier of the file INTEGER , INTENT(in ) :: kdom ! Type of domain to be read CHARACTER(len=*), INTENT(in ) :: cdvar ! Name of the variable REAL(wp) , INTENT( out), DIMENSION(:) :: pvar ! read field INTEGER , INTENT(in ) , OPTIONAL :: ktime ! record number INTEGER , INTENT(in ), DIMENSION(1), OPTIONAL :: kstart ! start axis position of the reading INTEGER , INTENT(in ), DIMENSION(1), OPTIONAL :: kcount ! number of points in each axis ! IF( iom_file(kiomid)%nfid > 0 ) CALL iom_get_123d( kiomid, kdom , cdvar , pv_r1d=pvar, & & ktime=ktime, kstart=kstart, kcount=kcount ) END SUBROUTINE iom_g1d SUBROUTINE iom_g2d( kiomid, kdom, cdvar, pvar, ktime, kstart, kcount ) INTEGER , INTENT(in ) :: kiomid ! Identifier of the file INTEGER , INTENT(in ) :: kdom ! Type of domain to be read CHARACTER(len=*), INTENT(in ) :: cdvar ! Name of the variable REAL(wp) , INTENT( out), DIMENSION(:,:) :: pvar ! read field INTEGER , INTENT(in ) , OPTIONAL :: ktime ! record number INTEGER , INTENT(in ), DIMENSION(2) , OPTIONAL :: kstart ! start axis position of the reading INTEGER , INTENT(in ), DIMENSION(2) , OPTIONAL :: kcount ! number of points in each axis ! IF( iom_file(kiomid)%nfid > 0 ) CALL iom_get_123d( kiomid, kdom , cdvar , pv_r2d=pvar, & & ktime=ktime, kstart=kstart, kcount=kcount ) END SUBROUTINE iom_g2d SUBROUTINE iom_g3d( kiomid, kdom, cdvar, pvar, ktime, kstart, kcount ) INTEGER , INTENT(in ) :: kiomid ! Identifier of the file INTEGER , INTENT(in ) :: kdom ! Type of domain to be read CHARACTER(len=*), INTENT(in ) :: cdvar ! Name of the variable REAL(wp) , INTENT( out), DIMENSION(:,:,:) :: pvar ! read field INTEGER , INTENT(in ) , OPTIONAL :: ktime ! record number INTEGER , INTENT(in ), DIMENSION(3) , OPTIONAL :: kstart ! start axis position of the reading INTEGER , INTENT(in ), DIMENSION(3) , OPTIONAL :: kcount ! number of points in each axis ! IF( iom_file(kiomid)%nfid > 0 ) CALL iom_get_123d( kiomid, kdom , cdvar , pv_r3d=pvar, & & ktime=ktime, kstart=kstart, kcount=kcount ) END SUBROUTINE iom_g3d !!---------------------------------------------------------------------- SUBROUTINE iom_get_123d( kiomid, kdom , cdvar , & & pv_r1d, pv_r2d, pv_r3d, & & ktime , kstart, kcount ) !!----------------------------------------------------------------------- !! *** ROUTINE iom_get_123d *** !! !! ** Purpose : read a 1D/2D/3D variable !! !! ** Method : read ONE record at each CALL !!----------------------------------------------------------------------- INTEGER , INTENT(in ) :: kiomid ! Identifier of the file INTEGER , INTENT(in ) :: kdom ! Type of domain to be read CHARACTER(len=*) , INTENT(in ) :: cdvar ! Name of the variable REAL(wp), DIMENSION(:) , INTENT( out), OPTIONAL :: pv_r1d ! read field (1D case) REAL(wp), DIMENSION(:,:) , INTENT( out), OPTIONAL :: pv_r2d ! read field (2D case) REAL(wp), DIMENSION(:,:,:) , INTENT( out), OPTIONAL :: pv_r3d ! read field (3D case) INTEGER , INTENT(in ), OPTIONAL :: ktime ! record number INTEGER , DIMENSION(:) , INTENT(in ), OPTIONAL :: kstart ! start position of the reading in each axis INTEGER , DIMENSION(:) , INTENT(in ), OPTIONAL :: kcount ! number of points to be read in each axis ! INTEGER :: jl ! loop on number of dimension INTEGER :: idom ! type of domain INTEGER :: idvar ! id of the variable INTEGER :: inbdim ! number of dimensions of the variable INTEGER :: idmspc ! number of spatial dimensions INTEGER :: itime ! record number INTEGER :: istop ! temporary value of nstop INTEGER, DIMENSION(jpmax_dims) :: istart ! starting point to read for each axis INTEGER, DIMENSION(jpmax_dims) :: icnt ! number of value to read along each axis INTEGER, DIMENSION(jpmax_dims) :: idimsz ! size of the dimensions of the variable REAL(wp) :: zscf, zofs ! sacle_factor and add_offset INTEGER :: itmp ! temporary integer CHARACTER(LEN=100) :: clinfo ! info character !--------------------------------------------------------------------- ! clinfo = ' iom_get_123d, file: '//trim(iom_file(kiomid)%name)//', var: '//trim(cdvar) ! local definition of the domain ? idom = kdom ! check kcount and kstart optionals parameters... IF( PRESENT(kcount) .AND. (.NOT. PRESENT(kstart)) ) & CALL ctl_stop( trim(clinfo), 'kcount present needs kstart present' ) IF( PRESENT(kstart) .AND. (.NOT. PRESENT(kcount)) ) & CALL ctl_stop( trim(clinfo), 'kstart present needs kcount present' ) IF( PRESENT(kstart) .AND. idom /= jpdom_unknown ) & CALL ctl_stop( trim(clinfo), 'kstart present needs kdom = jpdom_unknown' ) ! Search for the variable in the data base (eventually actualize data) istop = nstop idvar = iom_varid( kiomid, cdvar ) ! IF( idvar > 0 ) THEN ! to write iom_file(kiomid)%dimsz in a shorter way ! idimsz(:) = iom_file(kiomid)%dimsz(:, idvar) inbdim = iom_file(kiomid)%ndims(idvar) ! number of dimensions in the file idmspc = inbdim ! number of spatial dimensions in the file IF( iom_file(kiomid)%luld(idvar) ) idmspc = inbdim - 1 IF( idmspc > 3 ) CALL ctl_stop(trim(clinfo), & & 'the file has more than 3 spatial dimensions this case is not coded...' ) IF( idom == jpdom_local ) THEN ! Identify the domain in case of jpdom_local definition IF( idimsz(1) == jpi .AND. idimsz(2) == jpj ) THEN idom = jpdom_local_full ELSEIF( idimsz(1) == nlci .AND. idimsz(2) == nlcj ) THEN idom = jpdom_local_noextra ELSEIF( idimsz(1) == (nlei - nldi + 1) .AND. idimsz(2) == (nlej - nldj + 1) ) THEN idom = jpdom_local_noovlap ELSE CALL ctl_stop( trim(clinfo), 'impossible to identify the local domain' ) ENDIF ENDIF ! ! definition of istart and icnt ! ! initializations istart(:) = 1 icnt (:) = 1 itime = 1 IF( PRESENT(ktime) ) itime = ktime ! IF( PRESENT(pv_r1d) ) THEN IF( idmspc == 1 ) THEN ! data is 1d array (+ maybe a temporal dimension) IF( PRESENT(kstart) ) THEN istart(1:2) = (/ kstart(1), itime /) icnt(1) = kcount(1) ELSE IF( kdom == jpdom_unknown ) THEN istart(2) = itime icnt(1) = idimsz(1) ELSE CALL ctl_stop( trim(clinfo), 'case not coded...You must use jpdom_unknown' ) ENDIF ENDIF ELSE CALL ctl_stop( trim(clinfo), 'to keep iom lisibility, when reading a 1D array,', & & 'we do not accept data with more than 1 spatial dimension', & & 'Use ncwa -a to suppress the unnecessary dimensions') ENDIF ELSEIF( PRESENT(pv_r2d) ) THEN SELECT CASE (idmspc) CASE (1) CALL ctl_stop( trim(clinfo), 'the file has only 1 spatial dimension', & & 'it is impossible to read a 2d array from this file...') CASE (2) ! data is 2d array (+ maybe a temporal dimension) IF( PRESENT(kstart) ) THEN istart(1:3) = (/ kstart(1:2), itime /) icnt(1:2) = kcount(1:2) ELSE IF( kdom == jpdom_unknown ) THEN istart(3) = itime icnt(1:2) = idimsz(1:2) ELSE IF( idom == jpdom_data ) THEN istart(1:3) = (/ mig(1), mjg(1), itime /) ELSEIF( idom == jpdom_global ) THEN istart(1:3) = (/ nimpp, njmpp, itime /) ENDIF ! we do not read the overlap -> we start to read at nldi, nldj IF( idom /= jpdom_local_noovlap ) istart(1:2) = istart(1:2) + (/ nldi - 1, nldj - 1 /) ! we do not read the overlap and the extra-halos ! -> from nldi to nlei and from nldj to nlej icnt(1:2) = (/ nlei - nldi + 1, nlej - nldj + 1 /) ENDIF ENDIF CASE DEFAULT IF( itime == 1 .AND. idimsz(3) == 1 .AND. idmspc == 3 ) THEN CALL ctl_warn( trim(clinfo), '2D array but 3 spatial dimensions for the data...', & & 'As the size of the z dimension is 1 and as we try to read the first record, ', & & 'we accept this case even if there is a possible mix-up between z and time dimension' ) IF( PRESENT(kstart) ) THEN istart(1:2) = kstart(1:2) icnt(1:2) = kcount(1:2) ELSE IF( kdom == jpdom_unknown ) THEN icnt(1:2) = idimsz(1:2) ELSE IF( idom == jpdom_data ) THEN istart(1:2) = (/ mig(1), mjg(1) /) ELSEIF( idom == jpdom_global ) THEN istart(1:2) = (/ nimpp, njmpp /) ENDIF ! we do not read the overlap -> we start to read at nldi, nldj IF( idom /= jpdom_local_noovlap ) istart(1:2) = istart(1:2) + (/ nldi - 1, nldj - 1 /) ! we do not read the overlap and the extra-halos ! -> from nldi to nlei and from nldj to nlej icnt(1:2) = (/ nlei - nldi + 1, nlej - nldj + 1 /) ENDIF ENDIF ELSE CALL ctl_stop( trim(clinfo), 'to keep iom lisibility, when reading a 2D array,', & & 'we do not accept data with more than 2 spatial dimension', & & 'Use ncwa -a to suppress the unnecessary dimensions' ) ENDIF END SELECT ELSEIF( PRESENT(pv_r3d) ) THEN SELECT CASE (idmspc) CASE( 1 ) CALL ctl_stop( trim(clinfo), 'the file has only 1 spatial dimension', & & 'it is impossible to read a 3d array from this file...' ) CASE( 2 ) CALL ctl_stop( trim(clinfo), 'the file has only 2 spatial dimension', & & 'it is impossible to read a 3d array from this file...' ) CASE( 3 ) ! data is 3d array (+ maybe a temporal dimension) IF( PRESENT(kstart) ) THEN istart(1:4) = (/ kstart(1:3), itime /) icnt(1:3) = kcount(1:3) ELSE IF( kdom == jpdom_unknown ) THEN istart(4) = itime icnt(1:3) = idimsz(1:3) ELSE IF( idom == jpdom_data ) THEN istart(1:4) = (/ mig(1), mjg(1), 1, itime /) ELSEIF( idom == jpdom_global ) THEN istart(1:4) = (/ nimpp, njmpp, 1, itime /) ENDIF ! we do not read the overlap -> we start to read at nldi, nldj IF( idom /= jpdom_local_noovlap ) istart(1:2) = istart(1:2) + (/ nldi - 1, nldj - 1 /) ! we do not read the overlap and the extra-halos ! -> from nldi to nlei and from nldj to nlej icnt(1:2) = (/ nlei - nldi + 1, nlej - nldj + 1 /) IF( idom == jpdom_data ) THEN icnt(3) = jpkdta ELSE icnt(3) = jpk ENDIF ENDIF ENDIF CASE DEFAULT CALL ctl_stop( trim(clinfo), 'to keep iom lisibility, when reading a 3D array,', & & 'we do not accept data with more than 3 spatial dimension', & & 'Use ncwa -a to suppress the unnecessary dimensions' ) END SELECT ENDIF ! check that istart and icnt can be used with this file !- DO jl = 1, jpmax_dims itmp = istart(jl)+icnt(jl)-1 IF( (itmp) > idimsz(jl) .AND. idimsz(jl) /= 0 ) THEN WRITE(ctmp1,*) '(istart(',jl,') + icnt(',jl,') - 1) = ', itmp WRITE(ctmp2,*) ' is larger than idimsz(',jl,'): ', idimsz(jl) CALL ctl_stop( trim(clinfo), 'start and count too big regarding to the size of the data, ', ctmp1, ctmp2 ) ENDIF END DO ! check that icnt matches the input array !- IF( PRESENT(pv_r1d) ) THEN itmp = size(pv_r1d) WRITE(ctmp1,*) 'size(pv_r1d): ', itmp, ' /= icnt(1): ', icnt(1) IF( itmp /= icnt(1) ) CALL ctl_stop( trim(clinfo), ctmp1 ) ELSEIF( PRESENT(pv_r2d) ) THEN DO jl = 1, 2 IF( idom == jpdom_unknown ) THEN itmp = size(pv_r2d, jl) WRITE(ctmp1,*) 'size(pv_r2d, ',jl,'): ',itmp,' /= icnt(',jl,'): ',icnt(jl) ELSE itmp = size(pv_r2d(nldi:nlei,nldj:nlej), jl) WRITE(ctmp1,*) 'size(pv_r2d(nldi:nlei,nldj:nlej), ',jl,'): ',itmp,' /= icnt(',jl,'): ',icnt(jl) ENDIF IF( itmp /= icnt(jl) ) CALL ctl_stop( trim(clinfo), ctmp1 ) END DO ELSEIF( PRESENT(pv_r3d) ) THEN DO jl = 1, 3 IF( idom == jpdom_unknown ) THEN itmp = size(pv_r3d, jl) WRITE(ctmp1,*) 'size(pv_r3d, ',jl,'): ',itmp,' /= icnt(',jl,'):', icnt(jl) ELSE itmp = size(pv_r3d(nldi:nlei,nldj:nlej,:), jl) WRITE(ctmp1,*) 'size(pv_r3d(nldi:nlei,nldj:nlej), ',jl,'): ',itmp,' /= icnt(',jl,'): ',icnt(jl) ENDIF IF( itmp /= icnt(jl) ) CALL ctl_stop( trim(clinfo), ctmp1 ) END DO ENDIF ENDIF ! read the data !- IF( istop == nstop) THEN ! no additional errors until this point... ! SELECT CASE (iom_file(kiomid)%iolib) CASE (jpioipsl ) ; CALL iom_ioipsl_get( kiomid, idom, idvar, inbdim, istart, icnt, pv_r1d, pv_r2d, pv_r3d ) CASE (jpnf90 ) ; CALL iom_nf90_get( kiomid, idom, idvar, inbdim, istart, icnt, pv_r1d, pv_r2d, pv_r3d ) CASE (jprstdimg) ; CALL iom_rstdimg_get( kiomid, idom, idvar, istart, icnt, pv_r1d, pv_r2d, pv_r3d ) CASE DEFAULT CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) END SELECT IF( istop == nstop .AND. lwp ) & WRITE(numout,*) ' read '//trim(cdvar)//' in '//trim(iom_file(kiomid)%name)//' ok' !--- Apply scale_factor and offset zscf = iom_file(kiomid)%scf(idvar) ! scale factor zofs = iom_file(kiomid)%ofs(idvar) ! offset IF( PRESENT(pv_r1d) ) THEN IF( zscf /= 1. ) pv_r1d(:) = pv_r1d(:) * zscf IF( zofs /= 0. ) pv_r1d(:) = pv_r1d(:) + zofs ELSEIF( PRESENT(pv_r2d) ) THEN !CDIR COLLAPSE IF( zscf /= 1.) pv_r2d(:,:) = pv_r2d(:,:) * zscf !CDIR COLLAPSE IF( zofs /= 0.) pv_r2d(:,:) = pv_r2d(:,:) + zofs ELSEIF( PRESENT(pv_r3d) ) THEN !CDIR COLLAPSE IF( zscf /= 1.) pv_r3d(:,:,:) = pv_r3d(:,:,:) * zscf !CDIR COLLAPSE IF( zofs /= 0.) pv_r3d(:,:,:) = pv_r3d(:,:,:) + zofs ENDIF ! ENDIF ! END SUBROUTINE iom_get_123d SUBROUTINE iom_gettime( kiomid, cdvar, ptime ) !!-------------------------------------------------------------------- !! *** SUBROUTINE iom_gettime *** !! !! ** Purpose : read the time axis cdvar in the file !!-------------------------------------------------------------------- INTEGER , INTENT(in ) :: kiomid ! file Identifier CHARACTER(len=*) , INTENT(in ) :: cdvar ! time axis name REAL(wp), DIMENSION(:), INTENT( out) :: ptime ! the time axis ! INTEGER :: idvar ! id of the variable CHARACTER(LEN=100) :: clinfo ! info character !--------------------------------------------------------------------- ! clinfo = 'iom_gettime, file: '//trim(iom_file(kiomid)%name)//', var: '//trim(cdvar) idvar = iom_varid( kiomid, cdvar ) ! ptime(:) = 0. ! default definition IF( idvar > 0 ) THEN IF( iom_file(kiomid)%ndims(idvar) == 1 ) THEN IF( iom_file(kiomid)%luld(idvar) ) THEN IF( iom_file(kiomid)%dimsz(1,idvar) == size(ptime) ) THEN SELECT CASE (iom_file(kiomid)%iolib) CASE (jpioipsl ) ; CALL iom_ioipsl_gettime( kiomid, idvar, ptime ) CASE (jpnf90 ) ; CALL iom_nf90_gettime( kiomid, idvar, ptime ) CASE (jprstdimg) ; CALL ctl_stop( TRIM(clinfo)//' case IO library == jprstdimg not coded...' ) CASE DEFAULT CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) END SELECT ELSE WRITE(ctmp1,*) 'error with the size of ptime ',size(ptime),iom_file(kiomid)%dimsz(1,idvar) CALL ctl_stop( trim(clinfo), trim(ctmp1) ) ENDIF ELSE CALL ctl_stop( trim(clinfo), 'variable dimension is not unlimited... use iom_get' ) ENDIF ELSE CALL ctl_stop( trim(clinfo), 'the variable has more than 1 dimension' ) ENDIF ELSE CALL ctl_stop( trim(clinfo), 'variable not found in '//iom_file(kiomid)%name ) ENDIF ! END SUBROUTINE iom_gettime !!---------------------------------------------------------------------- !! INTERFACE iom_rstput !!---------------------------------------------------------------------- SUBROUTINE iom_rp0d( kt, kwrite, kiomid, cdvar, pvar, ktype ) INTEGER , INTENT(in) :: kt ! ocean time-step INTEGER , INTENT(in) :: kwrite ! writing time-step INTEGER , INTENT(in) :: kiomid ! Identifier of the file CHARACTER(len=*), INTENT(in) :: cdvar ! time axis name REAL(wp) , INTENT(in) :: pvar ! written field INTEGER , INTENT(in), OPTIONAL :: ktype ! variable external type INTEGER :: ivid ! variable id IF( iom_file(kiomid)%nfid > 0 ) THEN ivid = iom_varid(kiomid, cdvar) SELECT CASE (iom_file(kiomid)%iolib) CASE (jpioipsl ) ; CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r0d = pvar ) CASE (jpnf90 ) ; CALL iom_nf90_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r0d = pvar ) CASE (jprstdimg) ; IF( kt == kwrite ) CALL iom_rstdimg_rstput( kiomid, cdvar, pvar ) CASE DEFAULT CALL ctl_stop( 'iom_rp0d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) END SELECT END IF END SUBROUTINE iom_rp0d SUBROUTINE iom_rp1d( kt, kwrite, kiomid, cdvar, pvar, ktype ) INTEGER , INTENT(in) :: kt ! ocean time-step INTEGER , INTENT(in) :: kwrite ! writing time-step INTEGER , INTENT(in) :: kiomid ! Identifier of the file CHARACTER(len=*), INTENT(in) :: cdvar ! time axis name REAL(wp) , INTENT(in), DIMENSION( jpk) :: pvar ! written field INTEGER , INTENT(in), OPTIONAL :: ktype ! variable external type INTEGER :: ivid ! variable id IF( iom_file(kiomid)%nfid > 0 ) THEN ivid = iom_varid(kiomid, cdvar) SELECT CASE (iom_file(kiomid)%iolib) CASE (jpioipsl ) ; CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r1d = pvar ) CASE (jpnf90 ) ; CALL iom_nf90_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r1d = pvar ) CASE (jprstdimg) ; IF( kt == kwrite ) CALL iom_rstdimg_rstput( kiomid, cdvar, pv_r1d = pvar ) CASE DEFAULT CALL ctl_stop( 'iom_rp1d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) END SELECT END IF END SUBROUTINE iom_rp1d SUBROUTINE iom_rp2d( kt, kwrite, kiomid, cdvar, pvar, ktype ) INTEGER , INTENT(in) :: kt ! ocean time-step INTEGER , INTENT(in) :: kwrite ! writing time-step INTEGER , INTENT(in) :: kiomid ! Identifier of the file CHARACTER(len=*), INTENT(in) :: cdvar ! time axis name REAL(wp) , INTENT(in), DIMENSION(jpi,jpj ) :: pvar ! written field INTEGER , INTENT(in), OPTIONAL :: ktype ! variable external type INTEGER :: ivid ! variable id IF( iom_file(kiomid)%nfid > 0 ) THEN ivid = iom_varid(kiomid, cdvar) SELECT CASE (iom_file(kiomid)%iolib) CASE (jpioipsl ) ; CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r2d = pvar ) CASE (jpnf90 ) ; CALL iom_nf90_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r2d = pvar ) CASE (jprstdimg) ; IF( kt == kwrite ) CALL iom_rstdimg_rstput( kiomid, cdvar, pv_r2d = pvar ) CASE DEFAULT CALL ctl_stop( 'iom_rp2d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) END SELECT END IF END SUBROUTINE iom_rp2d SUBROUTINE iom_rp3d( kt, kwrite, kiomid, cdvar, pvar, ktype ) INTEGER , INTENT(in) :: kt ! ocean time-step INTEGER , INTENT(in) :: kwrite ! writing time-step INTEGER , INTENT(in) :: kiomid ! Identifier of the file CHARACTER(len=*), INTENT(in) :: cdvar ! time axis name REAL(wp) , INTENT(in), DIMENSION(jpi,jpj,jpk) :: pvar ! written field INTEGER , INTENT(in), OPTIONAL :: ktype ! variable external type INTEGER :: ivid ! variable id IF( iom_file(kiomid)%nfid > 0 ) THEN ivid = iom_varid(kiomid, cdvar) SELECT CASE (iom_file(kiomid)%iolib) CASE (jpioipsl ) ; CALL iom_ioipsl_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r3d = pvar ) CASE (jpnf90 ) ; CALL iom_nf90_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r3d = pvar ) CASE (jprstdimg) ; IF( kt == kwrite ) CALL iom_rstdimg_rstput( kiomid, cdvar, pv_r3d = pvar ) CASE DEFAULT CALL ctl_stop( 'iom_rp3d: accepted IO library are only jpioipsl and jprstdimg' ) END SELECT END IF END SUBROUTINE iom_rp3d !!---------------------------------------------------------------------- !!====================================================================== END MODULE iom