MODULE iom !!===================================================================== !! *** MODULE iom *** !! !! Input/Output manager : Library to read input files !! !! Ongoing work : This code is here to help discussions about I/O !! library in the NEMO system !!==================================================================== !!-------------------------------------------------------------------- !! iom_open : open a file read only !! iom_close : close a file or all files opened by iom !! iom_get : read a field : interface to several routines !! iom_varid : get the id of a variable in a file !! iom_get_gblatt : ??? !!-------------------------------------------------------------------- !! History : 9.0 ! 05 12 (J. Belier) Original code !! 9.0 ! 06 02 (S. Masson) Adaptation to NEMO !!-------------------------------------------------------------------- !! * Modules used USE in_out_manager ! I/O manager USE dom_oce ! ocean space and time domain USE lbclnk ! ??? USE ioipsl ! ??? IMPLICIT NONE PRIVATE PUBLIC :: iom_open, iom_close, iom_get, iom_varid, iom_get_gblatt !! * Interfaces INTERFACE iom_get MODULE PROCEDURE iom_get_r_1d, iom_get_r_2d, iom_get_r_3d END INTERFACE !! * Share module variables INTEGER, PARAMETER, PUBLIC :: & !: jpdom_data = 1, & !: ( 1 :jpidta, 1 :jpjdta) jpdom_global = 2, & !: ( 1 :jpiglo, 1 :jpjglo) jpdom_local = 3, & !: One of the 3 following cases jpdom_local_full = 4, & !: ( 1 :jpi , 1 :jpi ) jpdom_local_noextra = 5, & !: ( 1 :nlci , 1 :nlcj ) jpdom_local_noovlap = 6, & !: (nldi:nlei ,nldj:nlej ) jpdom_unknown = 7 !: No dimension checking !! * Module variables INTEGER, PARAMETER :: & jpmax_vars = 75, & ! maximum number of variables in one file jpmax_dims = 5, & ! maximum number of dimensions for one variable jpmax_digits = 5 ! maximum number of digits in the file name to reference the cpu number !$AGRIF_DO_NOT_TREAT INTEGER :: iom_init = 0 TYPE :: flio_file CHARACTER(LEN=240) :: name ! name of the file INTEGER :: iopen ! 1/0 is the file is open/not open INTEGER :: nvars ! number of identified varibles in the file INTEGER :: iduld ! id of the unlimited dimension CHARACTER(LEN=16), DIMENSION(jpmax_vars) :: cn_var ! names of the variables INTEGER, DIMENSION(jpmax_vars) :: ndims ! number of dimensions of the variables LOGICAL, DIMENSION(jpmax_vars) :: luld ! variable including unlimited dimension INTEGER, DIMENSION(jpmax_dims,jpmax_vars) :: dimsz ! size of the dimensions of the variables REAL(kind=wp), DIMENSION(jpmax_vars) :: scf ! scale_factor of the variables REAL(kind=wp), DIMENSION(jpmax_vars) :: ofs ! add_offset of the variables END TYPE flio_file TYPE(flio_file), DIMENSION(flio_max_files) :: iom_file ! array containing the info for all opened files !$AGRIF_END_DO_NOT_TREAT !!---------------------------------------------------------------------- !! OPA 9.0 , LOCEAN-IPSL (2006) !! $Header$ !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE iom_open( cdname, knumfl, ldimg ) !!--------------------------------------------------------------------- !! *** SUBROUTINE iom_open *** !! !! ** Purpose : open an input file read only (return 0 if not found) !! !! ** Method : !! !!--------------------------------------------------------------------- CHARACTER(len=*), INTENT(in ) :: cdname ! File name INTEGER, INTENT(out) :: knumfl ! Identifier of the opened file LOGICAL, INTENT(in ), OPTIONAL :: ldimg ! flg to specify that we use dimg format CHARACTER(LEN=100) :: clname ! the name of the file based on cdname [[+clcpu]+clcpu] CHARACTER(LEN=10) :: clsuffix ! ".nc" or ".dimg" CHARACTER(LEN=10) :: clcpu ! the cpu number (max jpmax_digits digits) LOGICAL :: llok ! check the existence INTEGER :: icnt ! counter for digits in clcpu (max = jpmax_digits) !--------------------------------------------------------------------- ! find the file ! ============= clname = trim(cdname) #if defined key_agrif if ( .NOT. Agrif_Root() ) clname = TRIM(Agrif_CFixed())//'_'//TRIM(clname) #endif clsuffix = ".nc" IF( PRESENT(ldimg) ) THEN IF ( ldimg ) clsuffix = ".dimg" ENDIF ! INQUIRE( FILE = clname, EXIST = llok ) IF( .NOT.llok ) THEN ! try to complete the name with the suffix only clname = TRIM(cdname)//TRIM(clsuffix) #if defined key_agrif if ( .NOT. Agrif_Root() ) clname = TRIM(Agrif_CFixed())//'_'//TRIM(clname) #endif INQUIRE( FILE = clname, EXIST = llok ) IF( .NOT.llok ) THEN ! try to complete the name with both cpu number and suffix WRITE(clcpu,*) narea-1 clcpu = trim(adjustl(clcpu)) clname = trim(cdname)//"_" #if defined key_agrif if ( .NOT. Agrif_Root() ) clname = TRIM(Agrif_CFixed())//'_'//TRIM(clname) #endif icnt = 0 INQUIRE( FILE = trim(clname)//trim(clcpu)//trim(clsuffix), EXIST = llok ) DO WHILE( .NOT.llok .AND. icnt < jpmax_digits ) ! we try fifferent formats for the cpu number by adding 0 clname = trim(clname)//"0" INQUIRE( FILE = trim(clname)//trim(clcpu)//trim(clsuffix), EXIST = llok ) icnt = icnt + 1 END DO IF( .NOT.llok ) THEN ! no way to find the files... CALL ctl_stop( 'iom_open: file '//trim(clname)//'... not found' ) ENDIF clname = trim(clname)//trim(clcpu)//trim(clsuffix) ENDIF ENDIF ! Open the file ! ============= IF( llok ) THEN IF (lwp) WRITE(numout,*) 'iom_open ~~~ open file: '//trim(clname) CALL flioopfd( trim(clname), knumfl ) IF( iom_init == 0 ) THEN iom_file(:)%iopen = 0 iom_init = 1 ENDIF iom_file(knumfl)%iopen = 1 iom_file(knumfl)%name = TRIM(clname) iom_file(knumfl)%nvars = 0 iom_file(knumfl)%ndims(:) = 0 iom_file(knumfl)%luld(:) = .FALSE. iom_file(knumfl)%dimsz(:,:) = 0 ! does the file contain time axis (that must be unlimitted) ? CALL flioinqf( knumfl, id_uld = iom_file(knumfl)%iduld ) ELSE knumfl = 0 ENDIF END SUBROUTINE iom_open SUBROUTINE iom_close( knumfl ) !!-------------------------------------------------------------------- !! *** SUBROUTINE iom_close *** !! !! ** Purpose : close an input file, or all files opened by iom !! !! ** Method : !! !!-------------------------------------------------------------------- INTEGER,INTENT(in), OPTIONAL :: knumfl ! Identifier of the file to be closed ! ! If this argument is not present, ! ! all the files opened by iom are closed. INTEGER :: jf ! dummy loop indices INTEGER :: i_s, i_e ! temporary integer !--------------------------------------------------------------------- IF( PRESENT(knumfl) ) THEN i_s = knumfl i_e = knumfl ELSE i_s = 1 i_e = flio_max_files ENDIF IF ( i_s > 0 ) THEN DO jf = i_s, i_e IF( iom_file(jf)%iopen > 0 ) THEN CALL flioclo( jf ) iom_file(jf)%iopen = 0 iom_file(jf)%name = 'NONE' iom_file(jf)%nvars = 0 iom_file(jf)%iduld = 0 iom_file(jf)%ndims(:) = 0 iom_file(jf)%luld(:) = .FALSE. iom_file(jf)%dimsz(:,:) = 0 ELSEIF( PRESENT(knumfl) ) THEN WRITE(ctmp1,*) '--->', knumfl CALL ctl_stop( 'iom_close: Invalid file identifier', ctmp1 ) ENDIF END DO ENDIF END SUBROUTINE iom_close !!---------------------------------------------------------------------- !! INTERFACE iom_u_getv !!---------------------------------------------------------------------- SUBROUTINE iom_get_r_1d( knumfl, kdom , cdvar , pvar , & & ktime, kstart, kcount ) INTEGER , INTENT(in ) :: knumfl ! 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) :: pvar ! read field 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 ! CHARACTER(LEN=100) :: clinfo ! info character ! clinfo = 'iom_get_r_1d, file: '//trim(iom_file(knumfl)%name)//', var: '//trim(cdvar) IF( PRESENT(kstart) ) THEN IF ( SIZE(kstart) /= 1 ) CALL ctl_stop( trim(clinfo), 'kstart must be a 1 element vector' ) ENDIF IF( PRESENT(kcount) ) THEN IF ( SIZE(kcount) /= 1 ) CALL ctl_stop( trim(clinfo), 'kcount must be a 1 element vector' ) ENDIF IF ( knumfl > 0 ) CALL iom_u_getv( knumfl, kdom , cdvar , pv_r1d=pvar, & & ktime=ktime, kstart=kstart, kcount=kcount ) END SUBROUTINE iom_get_r_1d SUBROUTINE iom_get_r_2d( knumfl, kdom , cdvar , pvar , & & ktime, kstart, kcount ) INTEGER,INTENT(in) :: knumfl INTEGER,INTENT(in) :: kdom CHARACTER(len=*),INTENT(in) :: cdvar REAL(wp),INTENT(out),DIMENSION(:,:) :: pvar INTEGER,INTENT(in),OPTIONAL :: ktime INTEGER,DIMENSION(:),INTENT(in),OPTIONAL :: kstart INTEGER,DIMENSION(:),INTENT(in),OPTIONAL :: kcount ! CHARACTER(LEN=100) :: clinfo ! info character ! clinfo = 'iom_get_r_2d, file: '//trim(iom_file(knumfl)%name)//', var: '//trim(cdvar) IF( PRESENT(kstart) ) THEN IF ( size(kstart) /= 2 ) CALL ctl_stop(trim(clinfo), 'kstart must be a 2 element vector') ENDIF IF( PRESENT(kcount) ) THEN IF ( size(kcount) /= 2 ) CALL ctl_stop(trim(clinfo), 'kcount must be a 2 element vector') ENDIF IF ( knumfl > 0 ) CALL iom_u_getv( knumfl, kdom , cdvar , pv_r2d=pvar, & & ktime=ktime, kstart=kstart, kcount=kcount ) END SUBROUTINE iom_get_r_2d SUBROUTINE iom_get_r_3d( knumfl, kdom , cdvar , pvar , & & ktime, kstart, kcount ) INTEGER,INTENT(in) :: knumfl INTEGER,INTENT(in) :: kdom CHARACTER(len=*),INTENT(in) :: cdvar REAL(wp),INTENT(out),DIMENSION(:,:,:) :: pvar INTEGER,INTENT(in),OPTIONAL :: ktime INTEGER,DIMENSION(:),INTENT(in),OPTIONAL :: kstart INTEGER,DIMENSION(:),INTENT(in),OPTIONAL :: kcount ! CHARACTER(LEN=100) :: clinfo ! info character ! clinfo = 'iom_get_r_3d, file: '//trim(iom_file(knumfl)%name)//', var: '//trim(cdvar) IF ( PRESENT(kstart) ) THEN IF ( size(kstart) /= 3 ) CALL ctl_stop(trim(clinfo), 'kstart must be a 3 element vector') ENDIF IF ( PRESENT(kcount) ) THEN IF ( size(kcount) /= 3 ) CALL ctl_stop(trim(clinfo), 'kcount must be a 3 element vector') ENDIF IF ( knumfl > 0 ) CALL iom_u_getv( knumfl, kdom , cdvar , pv_r3d=pvar, & & ktime=ktime, kstart=kstart, kcount=kcount ) END SUBROUTINE iom_get_r_3d !!---------------------------------------------------------------------- SUBROUTINE iom_u_getv( knumfl, kdom , cdvar , & & pv_r1d, pv_r2d, pv_r3d, & & ktime , kstart, kcount ) !!----------------------------------------------------------------------- !! *** ROUTINE iom_u_getv *** !! !! ** Purpose : read a 1D/2D/3D variable !! !! ** Method : read ONE time step at each CALL !! !!----------------------------------------------------------------------- INTEGER, INTENT(in ) :: knumfl ! 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 & idvar, & ! id of the variable & inbdim, & ! number of dimensions of the variable & idmspc, & ! number of spatial dimensions & itime, & ! record number & istop ! temporary value of nstop INTEGER, DIMENSION(jpmax_dims) :: istart, & ! starting point to read for each axis & icnt, & ! number of value to read along each axis & 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_u_getv, file: '//trim(iom_file(knumfl)%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( knumfl, cdvar ) ! IF ( idvar > 0 ) THEN ! to write iom_file(knumfl)%dimsz in a shorter way ! idimsz(:) = iom_file(knumfl)%dimsz(:, idvar) inbdim = iom_file(knumfl)%ndims(idvar)! number of dimensions in the file idmspc = inbdim ! number of spatial dimensions in the file IF( iom_file(knumfl)%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...') ! Identify the domain in case of jpdom_local definition !- IF( idom == jpdom_local ) THEN 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 reacord, ', & & '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 istart and icnt match 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... ! istop = nstop ! zscf = iom_file(knumfl)%scf(idvar) ! scale factor zofs = iom_file(knumfl)%ofs(idvar) ! offset ! IF( PRESENT(pv_r1d) ) THEN CALL fliogetv( knumfl, cdvar, pv_r1d(:), start=istart(1:inbdim), count=icnt(1:inbdim) ) !--- Apply scale_factor and offset IF( zscf /= 1. ) pv_r1d(:) = pv_r1d(:) * zscf IF( zofs /= 0. ) pv_r1d(:) = pv_r1d(:) + zofs ELSEIF( PRESENT(pv_r2d) ) THEN IF( idom /= jpdom_unknown ) THEN CALL fliogetv( knumfl, cdvar, pv_r2d(nldi:nlei,nldj:nlej), start=istart(1:inbdim), count=icnt(1:inbdim) ) !--- Apply scale_factor and offset IF (zscf /= 1.) pv_r2d(nldi:nlei, nldj:nlej) = pv_r2d(nldi:nlei,nldj:nlej) * zscf IF (zofs /= 0.) pv_r2d(nldi:nlei, nldj:nlej) = pv_r2d(nldi:nlei,nldj:nlej) + zofs !--- Fill the overlap areas and extra hallows (mpp) CALL lbc_lnk (pv_r2d,'Z',-999.,'no0') ELSE CALL fliogetv( knumfl, cdvar, pv_r2d(:,:), start=istart(1:inbdim), count=icnt(1:inbdim) ) !--- Apply scale_factor and offset IF (zscf /= 1.) pv_r2d(:,:) = pv_r2d(:,:) * zscf IF (zofs /= 0.) pv_r2d(:,:) = pv_r2d(:,:) + zofs ENDIF ELSEIF( PRESENT(pv_r3d) ) THEN IF( idom /= jpdom_unknown ) THEN CALL fliogetv( knumfl, cdvar, pv_r3d(nldi:nlei,nldj:nlej,:), start=istart(1:inbdim), count=icnt(1:inbdim) ) !--- Apply scale_factor and offset IF( zscf /= 1. ) pv_r3d(nldi:nlei,nldj:nlej,:) = pv_r3d(nldi:nlei,nldj:nlej,:) * zscf IF( zofs /= 0. ) pv_r3d(nldi:nlei,nldj:nlej,:) = pv_r3d(nldi:nlei,nldj:nlej,:) + zofs !--- Fill the overlap areas and extra hallows (mpp) IF( icnt(3) == jpk ) CALL lbc_lnk( pv_r3d,'Z',-999.,'no0' ) ! this if could be removed with the new lbc_lnk ... ELSE CALL fliogetv( knumfl, cdvar, pv_r3d(:,:,:), start=istart(1:inbdim), count=icnt(1:inbdim) ) !--- Apply scale_factor and offset IF (zscf /= 1.) pv_r3d(:,:,:) = pv_r3d(:,:,:) * zscf IF (zofs /= 0.) pv_r3d(:,:,:) = pv_r3d(:,:,:) + zofs ENDIF ENDIF ! IF( istop == nstop .AND. lwp ) & & WRITE(numout,*) ' read '//trim(cdvar)//' in '//trim(iom_file(knumfl)%name)//' ok' ENDIF ! END SUBROUTINE iom_u_getv SUBROUTINE iom_gettime( knumfl, cdvar, ptime ) !!-------------------------------------------------------------------- !! *** SUBROUTINE iom_close *** !! !! ** Purpose : read the time axis cdvar in the file !! !! ** Method : !! !!-------------------------------------------------------------------- INTEGER , INTENT(in) :: knumfl ! Identifier of the file to be closed 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(knumfl)%name)//', var: '//trim(cdvar) idvar = iom_varid( knumfl, cdvar ) ! ptime(:) = 0. ! default definition IF ( idvar > 0 ) THEN IF ( iom_file(knumfl)%ndims(idvar) == 1 ) THEN IF ( iom_file(knumfl)%luld(idvar) ) THEN IF ( iom_file(knumfl)%dimsz(1,idvar) == size(ptime) ) THEN CALL fliogetv( knumfl, cdvar, ptime(:), start=(/ 1 /), & & count=(/ iom_file(knumfl)%dimsz(1,idvar) /) ) ELSE WRITE(ctmp1,*) 'error with the size of ptime ',size(ptime),iom_file(knumfl)%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(knumfl)%name ) ENDIF END SUBROUTINE iom_gettime FUNCTION iom_varid ( knumfl, cdvar, kdimsz ) !!----------------------------------------------------------------------- !! *** FUNCTION iom_varid *** !! !! ** Purpose : get the id of a variable in a file (return 0 if not found) !! !! ** Method : ??? !! !!----------------------------------------------------------------------- INTEGER , INTENT(in) :: knumfl ! file Identifier CHARACTER(len=*) , INTENT(in) :: cdvar ! name of the variable INTEGER, DIMENSION(:), INTENT(out), OPTIONAL :: kdimsz ! size of the dimensions ! INTEGER :: iom_varid, idvar, i_nvd, ji INTEGER, DIMENSION(jpmax_dims) :: idimid LOGICAL :: ll_fnd CHARACTER(LEN=100) :: clinfo ! info character !!----------------------------------------------------------------------- clinfo = 'iom_varid, file: '//trim(iom_file(knumfl)%name)//', var: '//trim(cdvar) iom_varid = 0 ! default definition IF ( PRESENT(kdimsz) ) kdimsz(:) = 0 ! default definition ! IF ( knumfl > 0 ) THEN IF( iom_file(knumfl)%iopen == 0 ) THEN CALL ctl_stop( trim(clinfo), 'the file is not open' ) ELSE ! ll_fnd = .FALSE. idvar = 0 ! DO WHILE ( .NOT.ll_fnd .AND. idvar < iom_file(knumfl)%nvars ) idvar = idvar + 1 ll_fnd = ( TRIM(cdvar) == TRIM(iom_file(knumfl)%cn_var(idvar)) ) END DO ! IF( .NOT.ll_fnd ) THEN idvar = idvar + 1 IF( idvar <= jpmax_vars ) THEN CALL flioinqv( knumfl, cdvar, ll_fnd, nb_dims = i_nvd ) IF( ll_fnd ) THEN IF( i_nvd <= jpmax_dims ) THEN iom_file(knumfl)%nvars = idvar iom_file(knumfl)%cn_var(idvar) = trim(cdvar) iom_file(knumfl)%ndims(idvar) = i_nvd CALL flioinqv( knumfl, cdvar, ll_fnd, & & len_dims = iom_file(knumfl)%dimsz(1:i_nvd,idvar), & & id_dims = idimid(1:i_nvd) ) DO ji = 1, i_nvd IF ( idimid(ji) == iom_file(knumfl)%iduld ) iom_file(knumfl)%luld(idvar) = .TRUE. END DO !---------- !---------- Deal with scale_factor and offset CALL flioinqa( knumfl, cdvar, 'scale_factor', ll_fnd ) IF (ll_fnd) THEN CALL fliogeta( knumfl, cdvar, 'scale_factor', iom_file(knumfl)%scf(idvar) ) ELSE iom_file(knumfl)%scf(idvar) = 1. END IF CALL flioinqa( knumfl, cdvar, 'offset', ll_fnd ) IF( ll_fnd ) THEN CALL fliogeta( knumfl, cdvar, 'offset', iom_file(knumfl)%ofs(idvar) ) ELSE iom_file(knumfl)%ofs(idvar) = 0. END IF ! iom_varid = idvar IF ( PRESENT(kdimsz) ) THEN IF ( i_nvd == size(kdimsz) ) THEN kdimsz(:) = iom_file(knumfl)%dimsz(1:i_nvd,idvar) ELSE WRITE(ctmp1,*) i_nvd, size(kdimsz) CALL ctl_stop( trim(clinfo), 'error in kdimsz size'//trim(ctmp1) ) ENDIF ENDIF ELSE CALL ctl_stop( trim(clinfo), 'Too many dimensions in the file '//iom_file(knumfl)%name, & & 'increase the parameter jpmax_vars') ENDIF ELSE CALL ctl_warn( trim(clinfo), 'Variable '//trim(cdvar)// & & ' is not found in the file '//trim(iom_file(knumfl)%name) ) ENDIF ELSE CALL ctl_stop( trim(clinfo), 'Too many variables in the file '//iom_file(knumfl)%name, & & 'increase the parameter jpmax_vars') ENDIF ELSE iom_varid = idvar IF ( PRESENT(kdimsz) ) THEN i_nvd = iom_file(knumfl)%ndims(idvar) IF ( i_nvd == size(kdimsz) ) THEN kdimsz(:) = iom_file(knumfl)%dimsz(1:i_nvd,idvar) 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 FUNCTION iom_get_gblatt( knumfl, kinfonum ) !!----------------------------------------------------------------------- !! *** FUNCTION iom_get_gblatt *** !! !! ** Purpose : ??? !! !! ** Method : ??? !! !!----------------------------------------------------------------------- INTEGER,INTENT(in) :: knumfl INTEGER, intent(in) :: kinfonum ! CHARACTER(LEN=10) :: clinfo REAL(wp) :: iom_get_gblatt !!----------------------------------------------------------------------- WRITE(clinfo,*) kinfonum clinfo = 'info'//trim(adjustl(clinfo)) CALL fliogeta (knumfl, "?", clinfo, iom_get_gblatt) END FUNCTION iom_get_gblatt !!====================================================================== END MODULE iom