!---------------------------------------------------------------------- ! NEMO system team, System and Interface for oceanic RElocable Nesting !---------------------------------------------------------------------- ! ! MODULE: iom ! ! DESCRIPTION: !> @brief Input/Output manager : Library to read input files
!> !> @details !> !> to open file:
!> CALL iom_open(td_file) !> - td_file is file structure !> !> to write in file:
!> CALL iom_write_file(td_file) !> !> to close file:
!> CALL iom_close(tl_file) !> !> to read one dimension in file:
!> tl_dim = iom_read_dim(tl_file, id_dimid)
!> or
!> tl_dim = iom_read_dim(tl_file, cd_name)
!> - id_dimid is dimension id !> - cd_name is dimension name !> !> to read variable or global attribute in file:
!> tl_att = iom_read_att(tl_file, id_varid, id_attid)
!> or
!> tl_att = iom_read_att(tl_file, id_varid, cd_attname)
!> or
!> tl_att = iom_read_att(tl_file, cd_varname, cd_attid, [cd_stdname])
!> or
!> tl_att = iom_read_att(tl_file, cd_varname, cd_attname, cd_stdname) !> - id_varid is variable id !> - id_attid is attribute id !> - cd_attname is attribute name !> - cd_varname is variable name !> - cd_stdname is variable standard name (optional) !> !> to read one variable in file:
!> tl_var = iom_read_var(td_file, id_varid, [id_start, id_count])
!> or
!> tl_var = iom_read_var(td_file, cd_name, [id_start, [id_count,]] [cd_stdname]) !> - id_varid is variabale id !> - cd_name is variabale name !> - id_start is a integer(4) 1D table of index from which the data !> values will be read (optional) !> - id_count is a integer(4) 1D table of the number of indices selected !> along each dimension (optional) !> - cd_stdname is variable standard name (optional) !> !> @author !> J.Paul ! REVISION HISTORY: !> @date Nov, 2013 - Initial Version ! !> @note Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) !> @todo !> - see lbc_lnk !> - see goup netcdf4 !> - add iom_fill_var_value : complete tl_file avec valeur de la variable !---------------------------------------------------------------------- MODULE iom USE netcdf ! nf90 library USE kind ! F90 kind parameter USE fct ! basic useful function USE logger ! log file manager USE dim ! dimension manager USE att ! attribute manager USE var ! variable manager USE file ! file manager USE iom_cdf ! netcdf I/O manager USE iom_rstdimg ! restart dimg I/O manager IMPLICIT NONE PRIVATE ! NOTE_avoid_public_variables_if_possible ! function and subroutine PUBLIC :: iom_open !< open or create file, fill file structure PUBLIC :: iom_create !< create file, fill file structure PUBLIC :: iom_close !< close file PUBLIC :: iom_read_dim !< read one dimension in an opened file PUBLIC :: iom_read_att !< read one attribute in an opened file PUBLIC :: iom_read_var !< read one variable in an opened file PUBLIC :: iom_fill_var !< fill variable value PUBLIC :: iom_write_file !< write file structure contents in an opened file ! PUBLIC :: iom_get_mpp ! get sub domain decomposition !< read variable or global attribute in an opened file PRIVATE :: iom__read_var_name_att_id !< given variable name or standard name and attribute id. PRIVATE :: iom__read_var_id_att_id !< given variable id and attribute id. PRIVATE :: iom__read_var_name_att_name !< given variable name or standard name, and attribute name. PRIVATE :: iom__read_var_id_att_name !< given variable id and attribute name. PRIVATE :: iom__read_dim_id !< read one dimension in an opened file, given dimension id. PRIVATE :: iom__read_dim_name !< read one dimension in an opened netcdf file, given dimension name. PRIVATE :: iom__read_var_id !< read variable value in an opened file, given variable id. PRIVATE :: iom__read_var_name !< read variable value in an opened file, given variable name or standard name. PRIVATE :: iom__fill_var_id !< fill variable value in an opened file, given variable id PRIVATE :: iom__fill_var_name !< fill variable value in an opened file, given variable name PRIVATE :: iom__fill_var_all !< fill all variable value in an opened file INTERFACE iom_read_var MODULE PROCEDURE iom__read_var_id MODULE PROCEDURE iom__read_var_name END INTERFACE iom_read_var INTERFACE iom_fill_var MODULE PROCEDURE iom__fill_var_id MODULE PROCEDURE iom__fill_var_name MODULE PROCEDURE iom__fill_var_all END INTERFACE INTERFACE iom_read_dim MODULE PROCEDURE iom__read_dim_id MODULE PROCEDURE iom__read_dim_name END INTERFACE iom_read_dim INTERFACE iom_read_att !< read variable or global attribute in an opened file MODULE PROCEDURE iom__read_var_name_att_id !< given variable name or standard name and attribute id. MODULE PROCEDURE iom__read_var_id_att_id !< given variable id and attribute id. MODULE PROCEDURE iom__read_var_name_att_name !< given variable name or standard name, and attribute name. MODULE PROCEDURE iom__read_var_id_att_name !< given variable id and attribute name. END INTERFACE iom_read_att CONTAINS !------------------------------------------------------------------- !> @brief This function open a file in read or write mode
!> If try to open a file in write mode that did not exist, create it.
!> !> If file already exist, get information about: !> - the number of variables !> - the number of dimensions !> - the number of global attributes !> - the ID of the unlimited dimension !> - the file format !> and finally read dimensions. !> !> @author J.Paul !> - Nov, 2013- Initial Version ! !> @param[inout] td_file : file structure !------------------------------------------------------------------- !> @code SUBROUTINE iom_open(td_file) IMPLICIT NONE ! Argument TYPE(TFILE), INTENT(INOUT) :: td_file !---------------------------------------------------------------- ! add suffix to file name td_file%c_name = file_add_suffix( TRIM(td_file%c_name), & & TRIM(td_file%c_type) ) ! check type SELECT CASE(TRIM(ADJUSTL(fct_lower(td_file%c_type)))) CASE('cdf') CALL iom_cdf_open(td_file) CASE('dimg') CALL iom_rstdimg_open(td_file) CASE DEFAULT CALL logger_error("OPEN: unknow type : "//TRIM(td_file%c_name)) END SELECT END SUBROUTINE iom_open !> @endcode !------------------------------------------------------------------- !> @brief This function create a file
!> !> @author J.Paul !> - Nov, 2013- Initial Version ! !> @param[inout] td_file : file structure !------------------------------------------------------------------- !> @code SUBROUTINE iom_create(td_file) IMPLICIT NONE ! Argument TYPE(TFILE), INTENT(INOUT) :: td_file ! local variable LOGICAL :: ll_exist !---------------------------------------------------------------- INQUIRE(FILE=TRIM(td_file%c_name), EXIST=ll_exist ) IF( ll_exist )THEN CALL logger_fatal("IOM CREATE: can not create file "//& & TRIM(td_file%c_name)//". file exist already.") ENDIF ! forced to open in write mode td_file%l_wrt=.TRUE. ! check type SELECT CASE(TRIM(td_file%c_type)) CASE('cdf') CALL iom_cdf_open(td_file) CASE('dimg') CALL iom_rstdimg_open(td_file) CASE DEFAULT CALL logger_error( "CREATE: can't create file "//& & TRIM(td_file%c_name)//": type unknown " ) END SELECT END SUBROUTINE iom_create !> @endcode !------------------------------------------------------------------- !> @brief This subroutine close file !> !> @author J.Paul !> - Nov, 2013- Initial Version ! !> @param[inout] td_file : file structure !------------------------------------------------------------------- !> @code SUBROUTINE iom_close(td_file) IMPLICIT NONE ! Argument TYPE(TFILE), INTENT(INOUT) :: td_file !---------------------------------------------------------------- ! open file SELECT CASE(TRIM(td_file%c_type)) CASE('cdf') CALL iom_cdf_close(td_file) CASE('dimg') CALL iom_rstdimg_close(td_file) CASE DEFAULT CALL logger_error( " CLOSE: can't close file "//& & TRIM(td_file%c_name)//": type unknown " ) END SELECT END SUBROUTINE iom_close !> @endcode !------------------------------------------------------------------- !> @brief This function read attribute (of variable or global) in an opened !> file, given variable name or standard name and attribute id. !> to get global attribute use 'GLOBAL' as variable name !> !> To check only standard name of the variable, put variable name to '' ! !> @author J.Paul !> - Nov, 2013- Initial Version ! !> @param[in] td_file : file structure !> @param[in] cd_varname : variable name. use 'GLOBAL' to read global !> attribute in a file !> @param[in] id_attid : attribute id !> @param[in] cd_stdname : variable standard name !> @return attribute structure !------------------------------------------------------------------- !> @code TYPE(TATT) FUNCTION iom__read_var_name_att_id( td_file, cd_varname, & & id_attid) IMPLICIT NONE ! Argument TYPE(TFILE), INTENT(IN) :: td_file CHARACTER(LEN=lc), INTENT(IN) :: cd_varname INTEGER(i4), INTENT(IN) :: id_attid ! local variable INTEGER(i4) :: il_varid !---------------------------------------------------------------- ! get variable id IF( TRIM(fct_upper(cd_varname)) == 'GLOBAL' )THEN il_varid=NF90_GLOBAL ELSE il_varid=var_get_id(td_file%t_var(:), cd_varname) ENDIF IF( il_varid /= 0 .OR. TRIM(fct_upper(cd_varname)) == 'GLOBAL' )THEN ! open file SELECT CASE(TRIM(td_file%c_type)) CASE('cdf') iom__read_var_name_att_id=iom_read_att( td_file, il_varid, & & id_attid) CASE('dimg') CALL logger_warn( " READ ATT: can't read attribute "//& & "in dimg file : "//TRIM(td_file%c_name) ) CASE DEFAULT CALL logger_error( " READ ATT: can't read attribute in file "//& & TRIM(td_file%c_name)//" : type unknown " ) END SELECT ENDIF END FUNCTION iom__read_var_name_att_id !> @endcode !------------------------------------------------------------------- !> @brief This function read attribute (of variable or global) in an opened !> file, given variable id and attribute id. !> !> @author J.Paul !> - Nov, 2013- Initial Version ! !> @param[in] td_file : file structure !> @param[in] id_varid : variable id. use NF90_GLOBAL to read global !> attribute in a file !> @param[in] id_attid : attribute id !> @return attribute structure !------------------------------------------------------------------- !> @code TYPE(TATT) FUNCTION iom__read_var_id_att_id( td_file, id_varid, & & id_attid) IMPLICIT NONE ! Argument TYPE(TFILE), INTENT(IN) :: td_file INTEGER(i4), INTENT(IN) :: id_varid INTEGER(i4), INTENT(IN) :: id_attid !---------------------------------------------------------------- ! open file SELECT CASE(TRIM(td_file%c_type)) CASE('cdf') iom__read_var_id_att_id=iom_cdf_read_att( td_file, id_varid, & & id_attid) CASE('dimg') CALL logger_warn( " READ ATT: can't read attribute in dimg file "//& & TRIM(td_file%c_name) ) CASE DEFAULT CALL logger_error( " READ ATT: can't read attribute in file "//& & TRIM(td_file%c_name)//" : type unknown " ) END SELECT END FUNCTION iom__read_var_id_att_id !> @endcode !------------------------------------------------------------------- !> @brief This function read attribute (of variable or global) in an opened !> file, given variable name or standard name, and attribute name. !> to get global attribute use 'GLOBAL' as variable name. !> !> To check only standard name of the variable, put variable name to '' ! !> @author J.Paul !> - Nov, 2013- Initial Version ! !> @param[in] td_file : file structure !> @param[in] cd_varname : variable name or standard name. use 'GLOBAL' to read global !> attribute in a file !> @param[in] cd_attname : attribute name !> @return attribute structure !------------------------------------------------------------------- !> @code TYPE(TATT) FUNCTION iom__read_var_name_att_name( td_file, cd_varname, & & cd_attname) IMPLICIT NONE ! Argument TYPE(TFILE), INTENT(IN) :: td_file CHARACTER(LEN=*), INTENT(IN) :: cd_varname CHARACTER(LEN=*), INTENT(IN) :: cd_attname ! local variable INTEGER(i4) :: il_varid !---------------------------------------------------------------- ! get variable id IF( TRIM(fct_upper(cd_varname)) == 'GLOBAL' )THEN il_varid=NF90_GLOBAL ELSE il_varid=var_get_id(td_file%t_var(:), cd_varname) ENDIF IF( il_varid /= 0 .OR. TRIM(fct_upper(cd_varname)) == 'GLOBAL' )THEN ! open file SELECT CASE(TRIM(td_file%c_type)) CASE('cdf') iom__read_var_name_att_name=iom_cdf_read_att( td_file, il_varid, & & cd_attname) CASE('dimg') CALL logger_warn( " READ ATT: can't read attribute "//& & "in dimg file :"//TRIM(td_file%c_name) ) CASE DEFAULT CALL logger_error( " READ ATT: can't read attribute in file "//& & TRIM(td_file%c_name)//" : type unknown " ) END SELECT ENDIF END FUNCTION iom__read_var_name_att_name !> @endcode !------------------------------------------------------------------- !> @brief This function read attribute (of variable or global) in an opened !> file, given variable id and attribute name. ! !> @author J.Paul !> - Nov, 2013- Initial Version ! !> @param[in] td_file : file structure !> @param[in] id_varid : variable id. use NF90_GLOBAL to read global !> attribute in a file !> @param[in] cd_name : attribute name !> @return attribute structure !------------------------------------------------------------------- !> @code TYPE(TATT) FUNCTION iom__read_var_id_att_name( td_file, id_varid, & & cd_attname) IMPLICIT NONE ! Argument TYPE(TFILE), INTENT(IN) :: td_file INTEGER(i4), INTENT(IN) :: id_varid CHARACTER(LEN=*), INTENT(IN) :: cd_attname !---------------------------------------------------------------- ! open file SELECT CASE(TRIM(td_file%c_type)) CASE('cdf') iom__read_var_id_att_name=iom_cdf_read_att( td_file, id_varid, & & cd_attname) CASE('dimg') CALL logger_warn( " READ ATT: can't read attribute in dimg file :"& & //TRIM(td_file%c_name) ) CASE DEFAULT CALL logger_error( " READ ATT: can't read attribute in file "//& & TRIM(td_file%c_name)//" : type unknown " ) END SELECT END FUNCTION iom__read_var_id_att_name !> @endcode !------------------------------------------------------------------- !> @brief This function read one dimension in an opened file, !> given dimension id. ! !> @author J.Paul !> - Nov, 2013- Initial Version ! !> @param[in] td_file : file structure !> @param[in] id_dimid : dimension id !> @return dimension structure !------------------------------------------------------------------- !> @code TYPE(TDIM) FUNCTION iom__read_dim_id(td_file, id_dimid) IMPLICIT NONE ! Argument TYPE(TFILE), INTENT(IN) :: td_file INTEGER(i4), INTENT(IN) :: id_dimid !---------------------------------------------------------------- ! open file SELECT CASE(TRIM(td_file%c_type)) CASE('cdf') iom__read_dim_id=iom_cdf_read_dim(td_file, id_dimid) CASE('dimg') iom__read_dim_id=iom_rstdimg_read_dim(td_file, id_dimid) CASE DEFAULT CALL logger_error( " READ DIM: can't read dimension in file "//& & TRIM(td_file%c_name)//" : type unknown " ) END SELECT END FUNCTION iom__read_dim_id !> @endcode !------------------------------------------------------------------- !> @brief This function read one dimension in an opened netcdf file, !> given dimension name. ! !> @author J.Paul !> - Nov, 2013- Initial Version ! !> @param[in] td_file : file structure !> @param[in] cd_name : dimension name !> @return dimension structure !------------------------------------------------------------------- !> @code TYPE(TDIM) FUNCTION iom__read_dim_name(td_file, cd_name) IMPLICIT NONE ! Argument TYPE(TFILE), INTENT(IN) :: td_file CHARACTER(LEN=*), INTENT(IN) :: cd_name !---------------------------------------------------------------- ! open file SELECT CASE(TRIM(td_file%c_type)) CASE('cdf') iom__read_dim_name=iom_cdf_read_dim(td_file, cd_name) CASE('dimg') iom__read_dim_name=iom_rstdimg_read_dim(td_file, cd_name) CASE DEFAULT CALL logger_error( " READ DIM: can't read dimension in file "//& & TRIM(td_file%c_name)//" : type unknown " ) END SELECT END FUNCTION iom__read_dim_name !> @endcode !------------------------------------------------------------------- !> @brief This function read variable value in an opened !> file, given variable id.
!> start indices and number of indices selected along each dimension !> could be specify in a 4 dimension table (/'x','y','z','t'/) ! !> @author J.Paul !> - Nov, 2013- Initial Version ! !> @param[in] td_file : file structure !> @param[in] id_varid : variable id !> @param[in] id_start : index in the variable from which the data values !> will be read !> @param[in] id_count : number of indices selected along each dimension !> @return variable structure !------------------------------------------------------------------- !> @code TYPE(TVAR) FUNCTION iom__read_var_id( td_file, id_varid,& & id_start, id_count) IMPLICIT NONE ! Argument TYPE(TFILE), INTENT(IN) :: td_file INTEGER(i4), INTENT(IN) :: id_varid INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN), OPTIONAL :: id_start INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN), OPTIONAL :: id_count !---------------------------------------------------------------- ! open file SELECT CASE(TRIM(td_file%c_type)) CASE('cdf') iom__read_var_id=iom_cdf_read_var(td_file, id_varid, & & id_start, id_count) CASE('dimg') iom__read_var_id=iom_rstdimg_read_var(td_file, id_varid, & & id_start, id_count) CASE DEFAULT CALL logger_error( " READ VAR: can't read variable in file "//& & TRIM(td_file%c_name)//" : type unknown " ) END SELECT END FUNCTION iom__read_var_id !> @endcode !------------------------------------------------------------------- !> @brief This function read variable value in an opened !> file, given variable name or standard name.
!> start indices and number of indices selected along each dimension !> could be specify in a 4 dimension table (/'x','y','z','t'/) ! !> @details !> look first for variable name. If it doesn't !> exist in file, look for variable standard name.
!> If variable name is not present, check variable standard name.
! !> @author J.Paul !> - Nov, 2013- Initial Version ! !> @param[in] td_file : file structure !> @param[in] cd_name : variable name or standard name !> @param[in] id_start : index in the variable from which the data values !> will be read !> @param[in] id_count : number of indices selected along each dimension !> @return variable structure !------------------------------------------------------------------- !> @code TYPE(TVAR) FUNCTION iom__read_var_name(td_file, cd_name, & & id_start, id_count ) IMPLICIT NONE ! Argument TYPE(TFILE) , INTENT(IN) :: td_file CHARACTER(LEN=*) , INTENT(IN), OPTIONAL :: cd_name INTEGER(i4) , DIMENSION(:), INTENT(IN), OPTIONAL :: id_start INTEGER(i4) , DIMENSION(:), INTENT(IN), OPTIONAL :: id_count !INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN), OPTIONAL :: id_start !INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN), OPTIONAL :: id_count !---------------------------------------------------------------- ! open file SELECT CASE(TRIM(td_file%c_type)) CASE('cdf') iom__read_var_name=iom_cdf_read_var(td_file, cd_name, & & id_start, id_count ) CASE('dimg') iom__read_var_name=iom_rstdimg_read_var(td_file, cd_name, & & id_start, id_count ) CASE DEFAULT CALL logger_error( " READ VAR: can't read variable in file "//& & TRIM(td_file%c_name)//" : type unknown " ) END SELECT END FUNCTION iom__read_var_name !> @endcode !------------------------------------------------------------------- !> @brief This subroutine fill all variables value in an opened !> file.
!> start indices and number of indices selected along each dimension !> could be specify in a 4 dimension table (/'x','y','z','t'/) ! !> @author J.Paul !> - Nov, 2013- Initial Version ! !> @param[inout] td_file : file structure !> @param[in] id_start : index in the variable from which the data values !> will be read !> @param[in] id_count : number of indices selected along each dimension !------------------------------------------------------------------- !> @code SUBROUTINE iom__fill_var_all( td_file, id_start, id_count) IMPLICIT NONE ! Argument TYPE(TFILE), INTENT(INOUT) :: td_file INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN), OPTIONAL :: id_start INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN), OPTIONAL :: id_count !---------------------------------------------------------------- ! open file SELECT CASE(TRIM(td_file%c_type)) CASE('cdf') CALL iom_cdf_fill_var(td_file, id_start, id_count) CASE('dimg') CALL iom_rstdimg_fill_var(td_file, id_start, id_count) CASE DEFAULT CALL logger_error( " FILL VAR: can't read variable in file "//& & TRIM(td_file%c_name)//" : type unknown " ) END SELECT END SUBROUTINE iom__fill_var_all !> @endcode !------------------------------------------------------------------- !> @brief This subroutine fill variable value in an opened !> file, given variable id.
!> start indices and number of indices selected along each dimension !> could be specify in a 4 dimension table (/'x','y','z','t'/) ! !> @author J.Paul !> - Nov, 2013- Initial Version ! !> @param[inout] td_file : file structure !> @param[in] id_varid : variable id !> @param[in] id_start : index in the variable from which the data values !> will be read !> @param[in] id_count : number of indices selected along each dimension !------------------------------------------------------------------- !> @code SUBROUTINE iom__fill_var_id( td_file, id_varid, id_start, id_count) IMPLICIT NONE ! Argument TYPE(TFILE), INTENT(INOUT) :: td_file INTEGER(i4), INTENT(IN) :: id_varid INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN), OPTIONAL :: id_start INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN), OPTIONAL :: id_count !---------------------------------------------------------------- ! open file SELECT CASE(TRIM(td_file%c_type)) CASE('cdf') CALL iom_cdf_fill_var(td_file, id_varid, id_start, id_count) CASE('dimg') CALL iom_rstdimg_fill_var(td_file, id_varid, id_start, id_count) CASE DEFAULT CALL logger_error( " FILL VAR: can't read variable in file "//& & TRIM(td_file%c_name)//" : type unknown " ) END SELECT END SUBROUTINE iom__fill_var_id !> @endcode !------------------------------------------------------------------- !> @brief This subroutine fill variable value in an opened !> file, given variable name or standard name.
!> start indices and number of indices selected along each dimension !> could be specify in a 4 dimension table (/'x','y','z','t'/) ! !> @details !> look first for variable name. If it doesn't !> exist in file, look for variable standard name.
!> If variable name is not present, check variable standard name.
! !> @author J.Paul !> - Nov, 2013- Initial Version ! !> @param[inout] td_file : file structure !> @param[in] cd_name : variable name or standard name !> @param[in] id_start : index in the variable from which the data values !> will be read !> @param[in] id_count : number of indices selected along each dimension !------------------------------------------------------------------- !> @code SUBROUTINE iom__fill_var_name( td_file, cd_name, id_start, id_count ) IMPLICIT NONE ! Argument TYPE(TFILE), INTENT(INOUT) :: td_file CHARACTER(LEN=*), INTENT(IN) :: cd_name INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN), OPTIONAL :: id_start INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN), OPTIONAL :: id_count !---------------------------------------------------------------- ! open file SELECT CASE(TRIM(td_file%c_type)) CASE('cdf') CALL iom_cdf_fill_var(td_file, cd_name, id_start, id_count ) CASE('dimg') CALL iom_rstdimg_fill_var(td_file, cd_name, id_start, id_count ) CASE DEFAULT CALL logger_error( " FILL VAR: can't read variable in file "//& & TRIM(td_file%c_name)//" : type unknown " ) END SELECT END SUBROUTINE iom__fill_var_name !> @endcode !------------------------------------------------------------------- !> @brief This subroutine write file structure in an opened file. ! !> @details ! !> @author J.Paul !> - Nov, 2013- Initial Version ! !> @param[in] td_file : file structure !------------------------------------------------------------------- !> @code SUBROUTINE iom_write_file(td_file) IMPLICIT NONE ! Argument TYPE(TFILE), INTENT(INOUT) :: td_file !---------------------------------------------------------------- ! open file SELECT CASE(TRIM(td_file%c_type)) CASE('cdf') CALL iom_cdf_write_file(td_file) CASE('dimg') CALL iom_rstdimg_write_file(td_file) CASE DEFAULT CALL logger_error( " WRITE: can't write file "//& & TRIM(td_file%c_name)//" : type unknown " ) END SELECT END SUBROUTINE iom_write_file !> @endcode ! !------------------------------------------------------------------- ! !> @brief This function get sub domain decomposition. ! ! ! !> @details ! ! ! !> @author J.Paul ! !> - Nov, 2013- Initial Version ! ! ! !> @param[in] td_file : file structure ! !------------------------------------------------------------------- ! !> @code ! TYPE(TMPP) FUNCTION iom_get_mpp(td_file) ! IMPLICIT NONE ! ! Argument ! TYPE(TFILE), INTENT(INOUT) :: td_file ! !---------------------------------------------------------------- ! ! ! open file ! SELECT CASE(TRIM(td_file%c_type)) ! CASE('cdf') ! iom_get_mpp = iom_cdf_get_mpp(td_file) ! CASE('dimg') ! iom_get_mpp = iom_rstdimg_get_mpp(td_file) ! CASE DEFAULT ! CALL logger_error( " WRITE: can't write file "//& ! & TRIM(td_file%c_name)//" : type unknown " ) ! END SELECT ! ! END FUNCTION iom_get_mpp ! !> @endcode END MODULE iom