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 5086 for branches/2014/dev_r4650_UKMO3_masked_damping/NEMOGCM/TOOLS/SIREN/src/iom_rstdimg.f90 – NEMO

Ignore:
Timestamp:
2015-02-17T10:06:39+01:00 (9 years ago)
Author:
timgraham
Message:

Merged head of trunk into branch in preparation for putting code back onto the trunk
In working copy ran the command:
svn merge svn+sshtimgraham@…/ipsl/forge/projets/nemo/svn/trunk

Also recompiled NEMO_book.pdf with merged input files

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4650_UKMO3_masked_damping/NEMOGCM/TOOLS/SIREN/src/iom_rstdimg.f90

    r4213 r5086  
    1010!> 
    1111!> @details 
    12 !> 
    1312!>    to open dimg file (create file structure):<br/> 
     13!> @code 
    1414!>    CALL iom_rstdimg_open(td_file) 
     15!> @endcode 
    1516!>       - td_file is file structure (see file.f90) 
    1617!> 
    1718!>    to write in dimg file:<br/> 
     19!> @code 
    1820!>    CALL  iom_rstdimg_write_file(td_file) 
     21!> @endcode 
    1922!> 
    2023!>    to close dimg file:<br/> 
     24!> @code 
    2125!>    CALL iom_rstdimg_close(tl_file) 
     26!> @endcode 
    2227!> 
    2328!>    to read one dimension in dimg file:<br/> 
    24 !>    tl_dim = iom_rstdimg_read_dim(tl_file, id_dimid)<br/> 
    25 !>    or<br/> 
     29!> @code 
     30!>    tl_dim = iom_rstdimg_read_dim(tl_file, id_dimid) 
     31!> @endcode 
     32!>    or 
     33!> @code 
    2634!>    tl_dim = iom_rstdimg_read_dim(tl_file, cd_name) 
     35!> @endcode 
    2736!>       - id_dimid is dimension id<br/> 
    2837!>       - cd_name is dimension name 
    2938!> 
    30 !>    to read one global attribute in dimg file:<br/> 
    31 !>    tl_att = iom_rstdimg_read_att(tl_file, id_varid, id_attid)<br/> 
    32 !>    or<br/> 
    33 !>    tl_att = iom_rstdimg_read_att(tl_file, id_varid, cd_name) 
    34 !>       - id_varid is variable id 
    35 !>       - id_attid is attribute id<br/> 
    36 !>       - cd_name is attribute name 
    37 !>   
    3839!>    to read one variable in dimg file:<br/> 
    39 !>    tl_var = iom_rstdimg_read_var(td_file, id_varid, [id_start, id_count])<br/> 
    40 !>    or<br/> 
    41 !>    tl_var = iom_rstdimg_read_var(td_file, cd_name, [id_start, [id_count,]] [cd_stdname]) 
     40!> @code 
     41!>    tl_var = iom_rstdimg_read_var(td_file, id_varid, [id_start, id_count]) 
     42!> @endcode 
     43!>    or 
     44!> @code 
     45!>    tl_var = iom_rstdimg_read_var(td_file, cd_name, [id_start, [id_count]]) 
     46!> @endcode 
    4247!>       - id_varid is variabale id 
    43 !>       - cd_name is variabale name 
    44 !>       - id_start is a integer(4) 1D table of index from which the data  
    45 !>          values will be read (optional) 
    46 !>       - id_count is a integer(4) 1D table of the number of indices selected 
    47 !>          along each dimension (optional) 
    48 !>       - cd_stdname is variable standard name (optional) 
     48!>       - cd_name is variabale name or standard name 
     49!>       - id_start is a integer(4) 1D array of index from which the data  
     50!>          values will be read [optional] 
     51!>       - id_count is a integer(4) 1D array of the number of indices selected 
     52!>          along each dimension [optional] 
     53!> 
     54!>    to get sub domain decomppistion in a dimg file:<br/> 
     55!> @code 
     56!>    CALL iom_rstdimg_get_mpp(td_file) 
     57!> @endcode 
    4958!> 
    5059!> @author 
    5160!> J.Paul 
    5261! REVISION HISTORY: 
    53 !> @date Nov, 2013 - Initial Version 
    54 ! 
    55 !> @param MyModule_type : brief_description 
     62!> @date November, 2013 - Initial Version 
    5663! 
    5764!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    58 ! 
    59 !> @todo 
    6065!---------------------------------------------------------------------- 
    6166MODULE iom_rstdimg 
    6267   USE netcdf                          ! nf90 library 
     68   USE global                          ! global parameter 
    6369   USE kind                            ! F90 kind parameter 
    6470   USE fct                             ! basic useful function 
    65    USE logger                             ! log file manager 
     71   USE logger                          ! log file manager 
    6672   USE att                             ! attribute manager 
    6773   USE dim                             ! dimension manager 
    6874   USE var                             ! variable manager 
    6975   USE file                            ! file manager 
    70    USE dom                             ! domain manager 
    7176   IMPLICIT NONE 
    72    PRIVATE 
    7377   ! NOTE_avoid_public_variables_if_possible 
     78 
     79   ! type and variable 
     80   PRIVATE ::  im_vnl !< variable name length  
    7481 
    7582   ! function and subroutine 
     
    7885   PUBLIC :: iom_rstdimg_read_dim    !< read one dimension in an opened dimg file, return variable structure 
    7986   PUBLIC :: iom_rstdimg_read_var    !< read one variable  in an opened dimg file, return dimension structure 
    80    PUBLIC :: iom_rstdimg_fill_var    !< fill variable value in an opened dimg file 
    8187   PUBLIC :: iom_rstdimg_write_file  !< write file structure contents in an opened dimg file 
    8288   PUBLIC :: iom_rstdimg_get_mpp     !< get sub domain decomppistion in a dimg file 
    8389 
    84    PRIVATE :: iom_rstdimg__get_info       !< get global information in an opened dimg file 
    85    PRIVATE :: iom_rstdimg__get_file_var   !< read information about variable on an opened dimg file. 
    86    PRIVATE :: iom_rstdimg__get_file_var_0d !< put information about scalar variable in file structure 
    87    PRIVATE :: iom_rstdimg__get_file_var_1d !< put information about variable 1D in file structure 
    88    PRIVATE :: iom_rstdimg__get_file_var_2d !< put information about variable 2D in file structure 
    89    PRIVATE :: iom_rstdimg__get_file_var_3d !< put information about variable 3D in file structure 
    90    PRIVATE :: iom_rstdimg__read_dim_id    !< read dimension structure in an opened dimg file, given variable id. 
    91    PRIVATE :: iom_rstdimg__read_dim_name  !< read dimension structure in an opened dimg file, given variable name or standard name. 
    92    PRIVATE :: iom_rstdimg__read_var_id    !< read variable value in an opened dimg file, given variable id. 
    93    PRIVATE :: iom_rstdimg__read_var_name  !< read variable value in an opened dimg file, given variable name or standard name. 
    94    PRIVATE :: iom_rstdimg__read_var_value !< read variable value in an opened dimg file, for variable 1,2,3d 
    95    PRIVATE :: iom_rstdimg__write_header   !< write header in an opened dimg file 
    96    PRIVATE :: iom_rstdimg__write_var      !< write variables in an opened dimg file  
    97    PRIVATE :: iom_rstdimg__fill_var_id    !< fill variable value in an opened dimg file, given variable id 
    98    PRIVATE :: iom_rstdimg__fill_var_name  !< fill variable value in an opened dimg file, given variable name 
    99    PRIVATE :: iom_rstdimg__fill_var_all   !< fill all variable value in an opened dimg file 
     90   PRIVATE :: iom_rstdimg__get_info        ! get global information in an opened dimg file 
     91   PRIVATE :: iom_rstdimg__get_file_var    ! read information about variable on an opened dimg file. 
     92   PRIVATE :: iom_rstdimg__get_file_var_0d ! put information about scalar variable in file structure 
     93   PRIVATE :: iom_rstdimg__get_file_var_1d ! put information about variable 1D in file structure 
     94   PRIVATE :: iom_rstdimg__get_file_var_2d ! put information about variable 2D in file structure 
     95   PRIVATE :: iom_rstdimg__get_file_var_3d ! put information about variable 3D in file structure 
     96   PRIVATE :: iom_rstdimg__read_dim_id     ! read dimension structure in an opened dimg file, given variable id. 
     97   PRIVATE :: iom_rstdimg__read_dim_name   ! read dimension structure in an opened dimg file, given variable name or standard name. 
     98   PRIVATE :: iom_rstdimg__read_var_id     ! read variable value in an opened dimg file, given variable id. 
     99   PRIVATE :: iom_rstdimg__read_var_name   ! read variable value in an opened dimg file, given variable name or standard name. 
     100   PRIVATE :: iom_rstdimg__read_var_value  ! read variable value in an opened dimg file, for variable 1,2,3d 
     101   PRIVATE :: iom_rstdimg__get_rec         ! compute record number before writing file 
     102   PRIVATE :: iom_rstdimg__write_header    ! write header in an opened dimg file 
     103   PRIVATE :: iom_rstdimg__write_var       ! write variables in an opened dimg file  
    100104 
    101105   ! module variable 
    102    INTEGER(i4), PARAMETER :: ip_vnl = 32 ! variable name length 
     106   INTEGER(i4), PARAMETER :: im_vnl = 32 ! variable name length 
    103107 
    104108   INTERFACE iom_rstdimg_read_dim 
     
    112116   END INTERFACE iom_rstdimg_read_var 
    113117 
    114    INTERFACE iom_rstdimg_fill_var 
    115       MODULE PROCEDURE iom_rstdimg__fill_var_id 
    116       MODULE PROCEDURE iom_rstdimg__fill_var_name 
    117       MODULE PROCEDURE iom_rstdimg__fill_var_all 
    118    END INTERFACE iom_rstdimg_fill_var    
    119  
    120118CONTAINS 
    121119   !------------------------------------------------------------------- 
    122    !> @brief This subroutine open a dimg file in read or write mode<br/> 
     120   !> @brief This subroutine open a dimg file in read or write mode. 
     121   !> @details 
    123122   !> if try to open a file in write mode that did not exist, create it.<br/> 
    124123   !> if file already exist, get information about: 
     
    128127   !> - the ID of the unlimited dimension 
    129128   !> - the file format 
    130    !> and finally read dimensions. 
     129   !> Finally it read dimensions, and 'longitude' variable to compute East-West 
     130   !> overlap. 
    131131   !> 
    132132   !> @author J.Paul 
    133    !> - Nov, 2013- Initial Version 
    134    ! 
    135    !> @param[inout] td_file : file structure 
    136    !------------------------------------------------------------------- 
    137    !> @code 
     133   !> - November, 2013- Initial Version 
     134   ! 
     135   !> @param[inout] td_file   file structure 
     136   !------------------------------------------------------------------- 
    138137   SUBROUTINE iom_rstdimg_open(td_file) 
    139138      IMPLICIT NONE 
     
    146145 
    147146      INTEGER(i4)       :: il_status 
    148        
    149       TYPE(TVAR)        :: tl_lon 
    150147      !---------------------------------------------------------------- 
    151148 
     
    180177            ENDIF 
    181178 
    182  
    183179         ENDIF 
    184180 
     
    224220            ENDIF 
    225221 
    226  
    227222            IF( .NOT. td_file%l_wrt )THEN 
    228223 
     
    240235               CALL fct_err(il_status) 
    241236               IF( il_status /= 0 )THEN 
    242                   CALL logger_error("OPEN: file "//TRIM(td_file%c_name)& 
     237                  CALL logger_debug("IOM RSTDIMG OPEN: open staus "//& 
     238                  &  TRIM(fct_str(il_status))) 
     239                  CALL logger_fatal("IOM RSTDIMG OPEN: file "//& 
     240                  &  TRIM(td_file%c_name)& 
    243241                  &  //" with record length "//TRIM(fct_str(td_file%i_recl))) 
    244242               ENDIF                
     
    260258               CALL fct_err(il_status) 
    261259               IF( il_status /= 0 )THEN 
    262                   CALL logger_error("OPEN: file "//TRIM(td_file%c_name)) 
     260                  CALL logger_debug("IOM RSTDIMG OPEN: open staus "//& 
     261                  &  TRIM(fct_str(il_status))) 
     262                  CALL logger_error("IOM RSTDIMG  OPEN: file "//& 
     263                  & TRIM(td_file%c_name)) 
    263264               ENDIF         
    264265 
     
    274275            CALL iom_rstdimg__get_file_var(td_file) 
    275276 
    276             ! get ew overlap 
    277             tl_lon=iom_rstdimg_read_var(td_file,'longitude') 
    278             td_file%i_ew=dom_get_ew_overlap(tl_lon) 
    279             WHERE( td_file%t_var(:)%t_dim(1)%l_use ) 
    280                td_file%t_var(:)%i_ew=td_file%i_ew 
    281             ENDWHERE 
    282             CALL var_clean(tl_lon)  
    283  
    284277         ENDIF 
    285278 
     
    287280 
    288281   END SUBROUTINE iom_rstdimg_open 
    289    !> @endcode 
    290    !------------------------------------------------------------------- 
    291    !> @brief This subroutine close dimg file 
     282   !------------------------------------------------------------------- 
     283   !> @brief This subroutine close dimg file. 
    292284   !> 
    293285   !> @author J.Paul 
    294    !> - Nov, 2013- Initial Version 
    295    ! 
    296    !> @param[in] td_file : file structure 
    297    !------------------------------------------------------------------- 
    298    !> @code 
     286   !> - November, 2013- Initial Version 
     287   ! 
     288   !> @param[inout] td_file   file structure 
     289   !------------------------------------------------------------------- 
    299290   SUBROUTINE iom_rstdimg_close(td_file) 
    300291      IMPLICIT NONE 
     
    327318 
    328319   END SUBROUTINE iom_rstdimg_close 
    329    !> @endcode 
    330320   !------------------------------------------------------------------- 
    331321   !> @brief This subroutine get global information in an opened dimg  
    332    !> file.<br/> 
     322   !> file. 
    333323   !> @details 
    334324   !> It gets the number of variables, the  domain decompistion,  
    335    !> the record of the header infos.<br/> 
     325   !> the record of the header.<br/> 
    336326   !> It read dimensions, and add it to dimension structure inside  
    337327   !> file structure. 
    338328   !> 
    339329   !> @author J.Paul 
    340    !> - Nov, 2013- Initial Version 
    341    ! 
    342    !> @param[inout] td_file : file structure 
    343    !> @return file structure completed  
    344    !------------------------------------------------------------------- 
    345    !> @code 
     330   !> - November, 2013- Initial Version 
     331   ! 
     332   !> @param[inout] td_file   file structure 
     333   !------------------------------------------------------------------- 
    346334   SUBROUTINE iom_rstdimg__get_info(td_file) 
    347335      IMPLICIT NONE 
     
    360348 
    361349      CALL logger_debug( & 
    362       &  " GET INFO: about dimg file "//TRIM(td_file%c_name)) 
     350      &  " IOM RSTDIMG GET INFO: about dimg file "//TRIM(td_file%c_name)) 
    363351 
    364352      ! read first record  
     
    370358      CALL fct_err(il_status) 
    371359      IF( il_status /= 0 )THEN 
    372          CALL logger_error("GET INFO: read first line of "//TRIM(td_file%c_name)) 
    373       ENDIF 
    374  
    375       CALL logger_trace( & 
    376       &  " GET INFO: about dimg file "//TRIM(td_file%c_name)) 
     360         CALL logger_debug(" READ status: "//TRIM(fct_str(il_status))) 
     361         CALL logger_fatal("IOM RSTDIMG GET INFO: read first line of "//& 
     362         &  TRIM(td_file%c_name)) 
     363      ENDIF 
    377364 
    378365      td_file%c_type='dimg' 
     
    380367      ! add dimension to file structure 
    381368      tl_dim=dim_init('X', il_nx) 
    382       CALL file_add_dim(td_file, tl_dim) 
     369      CALL file_move_dim(td_file, tl_dim) 
    383370      tl_dim=dim_init('Y', il_ny) 
    384       CALL file_add_dim(td_file, tl_dim) 
     371      CALL file_move_dim(td_file, tl_dim) 
    385372      tl_dim=dim_init('Z', il_nz) 
    386       CALL file_add_dim(td_file, tl_dim) 
     373      CALL file_move_dim(td_file, tl_dim) 
    387374 
    388375      ! reorder dimension to ('x','y','z','t') 
     
    401388 
    402389   END SUBROUTINE iom_rstdimg__get_info 
    403    !> @endcode 
    404    !------------------------------------------------------------------- 
    405    !> @brief This subroutine get sub domain decomposition in a dimg file.<br/> 
     390   !------------------------------------------------------------------- 
     391   !> @brief This subroutine get sub domain decomposition in a dimg file. 
    406392   !> @details 
    407393   !> domain decomposition informations are saved in attributes. 
    408394   !> 
    409395   !> @author J.Paul 
    410    !> - Nov, 2013- Initial Version 
    411    ! 
    412    !> @param[inout] td_file : file structure 
    413    !> @return mpp structure  
    414    !------------------------------------------------------------------- 
    415    !> @code 
     396   !> - November, 2013- Initial Version 
     397   ! 
     398   !> @param[inout] td_file   file structure 
     399   !------------------------------------------------------------------- 
    416400   SUBROUTINE iom_rstdimg_get_mpp(td_file) 
    417401      IMPLICIT NONE 
     
    440424      !---------------------------------------------------------------- 
    441425 
    442       CALL logger_trace( " GET MPP: dimg file "//TRIM(td_file%c_name)) 
     426      CALL logger_debug( " IOM RSTDIMG GET MPP: dimg file "//& 
     427      &  TRIM(td_file%c_name)) 
    443428 
    444429      ! read first record  
     
    453438      CALL fct_err(il_status) 
    454439      IF( il_status /= 0 )THEN 
    455          CALL logger_error("GET MPP: read first line of "//TRIM(td_file%c_name)) 
     440         CALL logger_debug(" IOM RSTDIMG GET MPP: read status: "//& 
     441         &  TRIM(fct_str(il_status))) 
     442         CALL logger_error(" IOM RSTDIMG GET MPP: read first line of "//& 
     443         &  TRIM(td_file%c_name)) 
    456444      ENDIF 
    457445 
    458446      ! create attributes to save mpp value 
    459447      tl_att=att_init( "DOMAIN_number_total", il_nproc) 
    460       CALL file_add_att(td_file, tl_att) 
     448      CALL file_move_att(td_file, tl_att) 
    461449 
    462450      tl_att=att_init( "DOMAIN_I_number_total", il_niproc) 
    463       CALL file_add_att(td_file, tl_att) 
     451      CALL file_move_att(td_file, tl_att) 
    464452 
    465453      tl_att=att_init( "DOMAIN_J_number_total", il_njproc) 
    466       CALL file_add_att(td_file, tl_att) 
     454      CALL file_move_att(td_file, tl_att) 
    467455 
    468456      tl_att=att_init( "DOMAIN_number", il_area) 
    469       CALL file_add_att(td_file, tl_att) 
     457      CALL file_move_att(td_file, tl_att) 
    470458 
    471459      tl_att=att_init( "DOMAIN_size_global", (/il_iglo, il_jglo/)) 
    472       CALL file_add_att(td_file, tl_att) 
     460      CALL file_move_att(td_file, tl_att) 
    473461 
    474462      ! allocate local variable 
     
    480468      IF(il_status /= 0 )THEN 
    481469 
    482          CALL logger_error( " GET MPP: not enough space to put domain & 
    483          &  decomposition in file "//TRIM(td_file%c_name) ) 
     470         CALL logger_error( " IOM RSTDIMG GET MPP: not enough space to put "//& 
     471         &  "domain decomposition in file "//TRIM(td_file%c_name) ) 
    484472 
    485473      ENDIF 
     
    500488      CALL fct_err(il_status) 
    501489      IF( il_status /= 0 )THEN 
    502          CALL logger_error("GET INFO: read domain decomposition on first & 
    503          &              line of "//TRIM(td_file%c_name)) 
     490         CALL logger_debug(" IOM RSTDIMG GET MPP: read status: "//& 
     491         &  TRIM(fct_str(il_status))) 
     492         CALL logger_fatal("IOM RSTDIMG GET MPP: read domain decomposition "//& 
     493         &           "on first line of "//TRIM(td_file%c_name)) 
    504494      ENDIF 
    505495 
    506496      tl_att=att_init( "DOMAIN_position_first", (/il_impp(il_area), il_jmpp(il_area)/)) 
    507       CALL file_add_att(td_file, tl_att) 
     497      CALL file_move_att(td_file, tl_att) 
    508498 
    509499      tl_att=att_init( "DOMAIN_position_last", (/il_lci(il_area), il_lcj(il_area)/)) 
    510       CALL file_add_att(td_file, tl_att) 
     500      CALL file_move_att(td_file, tl_att) 
    511501 
    512502      tl_att=att_init( "DOMAIN_halo_size_start", (/il_ldi(il_area), il_ldj(il_area)/)) 
    513       CALL file_add_att(td_file, tl_att) 
     503      CALL file_move_att(td_file, tl_att) 
    514504 
    515505      tl_att=att_init( "DOMAIN_halo_size_end", (/il_lei(il_area), il_lej(il_area)/)) 
    516       CALL file_add_att(td_file, tl_att) 
     506      CALL file_move_att(td_file, tl_att) 
    517507 
    518508      tl_att=att_init( "DOMAIN_I_position_first", il_impp(:) ) 
    519       CALL file_add_att(td_file, tl_att) 
     509      CALL file_move_att(td_file, tl_att) 
    520510      tl_att=att_init( "DOMAIN_J_position_first", il_jmpp(:) ) 
    521       CALL file_add_att(td_file, tl_att) 
     511      CALL file_move_att(td_file, tl_att) 
    522512 
    523513      tl_att=att_init( "DOMAIN_I_position_last", il_lci(:) ) 
    524       CALL file_add_att(td_file, tl_att) 
     514      CALL file_move_att(td_file, tl_att) 
    525515      tl_att=att_init( "DOMAIN_J_position_last", il_lcj(:) ) 
    526       CALL file_add_att(td_file, tl_att) 
     516      CALL file_move_att(td_file, tl_att) 
    527517 
    528518      tl_att=att_init( "DOMAIN_I_halo_size_start", il_ldi(:) ) 
    529       CALL file_add_att(td_file, tl_att) 
     519      CALL file_move_att(td_file, tl_att) 
    530520      tl_att=att_init( "DOMAIN_J_halo_size_start", il_ldj(:) ) 
    531       CALL file_add_att(td_file, tl_att) 
     521      CALL file_move_att(td_file, tl_att) 
    532522 
    533523      tl_att=att_init( "DOMAIN_I_halo_size_end", il_lei(:) ) 
    534       CALL file_add_att(td_file, tl_att) 
     524      CALL file_move_att(td_file, tl_att) 
    535525      tl_att=att_init( "DOMAIN_J_halo_size_end", il_lej(:) ) 
    536       CALL file_add_att(td_file, tl_att) 
     526      CALL file_move_att(td_file, tl_att) 
     527 
     528      ! clean 
     529      CALL att_clean(tl_att) 
    537530 
    538531      DEALLOCATE( il_impp, il_jmpp,& 
     
    542535 
    543536   END SUBROUTINE iom_rstdimg_get_mpp 
    544    !> @endcode 
    545537   !------------------------------------------------------------------- 
    546538   !> @brief This subroutine read information about variable on an  
    547    !> opened dimg file.<br/> 
    548    !> The variable structure inside file structure is then completed. 
     539   !> opened dimg file. 
     540   !> @details 
     541   !> The variables structures inside file structure are then completed. 
     542   !> Variables no0d, no1d, no2d, no3d are deleted from file strucutre. 
    549543   !> @note variable value are read only for scalar variable (0d). 
    550544   ! 
    551545   !> @author J.Paul 
    552    !> - Nov, 2013- Initial Version 
    553    ! 
    554    !> @param[inout] td_file : file structure 
    555    !> @return file structure completed  
    556    !------------------------------------------------------------------- 
    557    !> @code 
     546   !> - November, 2013- Initial Version 
     547   ! 
     548   !> @param[inout] td_file   file structure 
     549   !------------------------------------------------------------------- 
    558550   SUBROUTINE iom_rstdimg__get_file_var(td_file) 
    559551      IMPLICIT NONE 
     
    562554 
    563555      ! local variable 
    564       CHARACTER(LEN=ip_vnl), DIMENSION(:), ALLOCATABLE :: cl_name 
     556      CHARACTER(LEN=im_vnl), DIMENSION(:), ALLOCATABLE :: cl_name 
    565557 
    566558      REAL(dp)             , DIMENSION(:), ALLOCATABLE :: dl_value 
     
    605597 
    606598         IF(ASSOCIATED(td_file%t_var))THEN 
     599            CALL var_clean(td_file%t_var(:)) 
    607600            DEALLOCATE(td_file%t_var) 
    608601         ENDIF 
     
    638631 
    639632   END SUBROUTINE iom_rstdimg__get_file_var 
    640    !> @endcode 
    641    !------------------------------------------------------------------- 
    642    !> @brief This subroutine put information about scalar variable  
     633   !------------------------------------------------------------------- 
     634   !> @brief This subroutine put informations about scalar variable  
    643635   !> inside file structure. 
    644636   ! 
    645637   !> @author J.Paul 
    646    !> - Nov, 2013- Initial Version 
    647    ! 
    648    !> @param[inout] td_file : file structure 
    649    !> @param[in] cd_name : table of variable name 
    650    !> @param[in] dd_value : table of variable value 
    651    !> @return file structure completed  
    652    !------------------------------------------------------------------- 
    653    !> @code 
     638   !> - November, 2013- Initial Version 
     639   ! 
     640   !> @param[inout] td_file   file structure 
     641   !> @param[in] cd_name      array of variable name 
     642   !> @param[in] dd_value     array of variable value 
     643   !------------------------------------------------------------------- 
    654644   SUBROUTINE iom_rstdimg__get_file_var_0d(td_file, cd_name, dd_value) 
    655645      IMPLICIT NONE 
    656646      ! Argument       
    657647      TYPE(TFILE),                         INTENT(INOUT) :: td_file 
    658       CHARACTER(LEN=ip_vnl), DIMENSION(:), INTENT(IN)    :: cd_name 
     648      CHARACTER(LEN=im_vnl), DIMENSION(:), INTENT(IN)    :: cd_name 
    659649      REAL(dp),              DIMENSION(:), INTENT(IN)    :: dd_value 
    660650 
     
    667657 
    668658      ! define same dimension as in file 
    669       tl_dim(:)=td_file%t_dim(:) 
     659      tl_dim(:)=dim_copy(td_file%t_dim(:)) 
    670660      ! do not use any dimension 
    671661      tl_dim(:)%l_use=.FALSE. 
     
    676666    
    677667         td_file%t_var(ji)=var_init( TRIM(cd_name(ji)), NF90_DOUBLE, & 
    678          &                           tl_dim(:), id_id=ji, id_rec=1 ) 
     668         &                           tl_dim(:), dd_fill=0._dp,       & 
     669         &                           id_id=ji, id_rec=1 ) 
    679670 
    680671         ! get value of scalar 
     
    688679      ENDDO 
    689680 
     681      ! clean 
     682      CALL dim_clean(tl_dim(:)) 
     683 
    690684   END SUBROUTINE iom_rstdimg__get_file_var_0d 
    691    !> @endcode    
    692    !------------------------------------------------------------------- 
    693    !> @brief This subroutine put information about variable 1D  
     685   !------------------------------------------------------------------- 
     686   !> @brief This subroutine put informations about variable 1D  
    694687   !> inside file structure. 
    695688   ! 
    696689   !> @author J.Paul 
    697    !> - Nov, 2013- Initial Version 
    698    ! 
    699    !> @param[inout] td_file : file structure 
    700    !> @param[in] cd_name : table of variable name 
    701    !> @param[in] dd_value : table of variable record 
    702    !> @return file structure completed  
    703    !------------------------------------------------------------------- 
    704    !> @code 
     690   !> - November, 2013- Initial Version 
     691   ! 
     692   !> @param[inout] td_file   file structure 
     693   !> @param[in] cd_name      array of variable name 
     694   !> @param[in] dd_value     array of variable record 
     695   !------------------------------------------------------------------- 
    705696   SUBROUTINE iom_rstdimg__get_file_var_1d(td_file, cd_name, dd_value) 
    706697      IMPLICIT NONE 
    707698      ! Argument       
    708699      TYPE(TFILE),                         INTENT(INOUT) :: td_file 
    709       CHARACTER(LEN=ip_vnl), DIMENSION(:), INTENT(IN)    :: cd_name 
     700      CHARACTER(LEN=im_vnl), DIMENSION(:), INTENT(IN)    :: cd_name 
    710701      REAL(dp),              DIMENSION(:), INTENT(IN)    :: dd_value 
    711702 
     
    722713 
    723714         ! define same dimension as in file 
    724          tl_dim(:)=td_file%t_dim(:) 
     715         tl_dim(:)=dim_copy(td_file%t_dim(:)) 
    725716         ! do not use X and Y dimension 
    726717         td_file%t_var(ji)%t_dim(1:2)%l_use=.FALSE. 
     
    728719       
    729720         td_file%t_var(ji)=var_init( TRIM(cd_name(ji)), NF90_DOUBLE, & 
    730          &                           tl_dim(:), id_id=ji,            & 
    731          &                           id_rec=INT(dd_value(ji),i4) ) 
     721         &                           tl_dim(:), dd_fill=0._dp,       & 
     722         &                           id_id=ji, id_rec=INT(dd_value(ji),i4) ) 
     723 
     724         ! clean 
     725         CALL dim_clean(tl_dim(:)) 
    732726 
    733727      ENDDO 
    734728 
    735729   END SUBROUTINE iom_rstdimg__get_file_var_1d 
    736    !> @endcode 
    737    !------------------------------------------------------------------- 
    738    !> @brief This subroutine put information about variable 2D  
     730   !------------------------------------------------------------------- 
     731   !> @brief This subroutine put informations about variable 2D  
    739732   !> inside file structure. 
    740733   ! 
    741734   !> @author J.Paul 
    742    !> - Nov, 2013- Initial Version 
    743    ! 
    744    !> @param[inout] td_file : file structure 
    745    !> @param[in] cd_name : table of variable name 
    746    !> @param[in] dd_value : table of variable record 
    747    !> @return file structure completed  
    748    !------------------------------------------------------------------- 
    749    !> @code 
     735   !> - November, 2013- Initial Version 
     736   ! 
     737   !> @param[inout] td_file   file structure 
     738   !> @param[in] cd_name      array of variable name 
     739   !> @param[in] dd_value     array of variable record 
     740   !------------------------------------------------------------------- 
    750741   SUBROUTINE iom_rstdimg__get_file_var_2d(td_file, cd_name, dd_value) 
    751742      IMPLICIT NONE 
    752743      ! Argument       
    753744      TYPE(TFILE),                         INTENT(INOUT) :: td_file 
    754       CHARACTER(LEN=ip_vnl), DIMENSION(:), INTENT(IN)    :: cd_name 
     745      CHARACTER(LEN=im_vnl), DIMENSION(:), INTENT(IN)    :: cd_name 
    755746      REAL(dp),              DIMENSION(:), INTENT(IN)    :: dd_value 
    756747 
     
    767758 
    768759         ! define same dimension as in file 
    769          tl_dim(:)=td_file%t_dim(:) 
     760         tl_dim(:)=dim_copy(td_file%t_dim(:)) 
    770761         ! do not use Z dimension 
    771762         tl_dim(3)%l_use=.FALSE. 
     
    773764 
    774765         td_file%t_var(ji)=var_init( TRIM(cd_name(ji)), NF90_DOUBLE, & 
    775          &                           tl_dim(:), id_id=ji,            & 
    776          &                           id_rec=INT(dd_value(ji),i4) ) 
     766         &                           tl_dim(:), dd_fill=0._dp,       & 
     767         &                           id_id=ji, id_rec=INT(dd_value(ji),i4) ) 
     768 
     769         ! clean 
     770         CALL dim_clean(tl_dim(:)) 
    777771 
    778772      ENDDO 
    779773 
    780774   END SUBROUTINE iom_rstdimg__get_file_var_2d 
    781    !> @endcode 
    782    !------------------------------------------------------------------- 
    783    !> @brief This subroutine put information about variable 3D  
     775   !------------------------------------------------------------------- 
     776   !> @brief This subroutine put informations about variable 3D  
    784777   !> inside file structure. 
    785778   ! 
    786779   !> @author J.Paul 
    787    !> - Nov, 2013- Initial Version 
    788    ! 
    789    !> @param[inout] td_file : file structure 
    790    !> @param[in] cd_name : table of variable name 
    791    !> @param[in] dd_value : table of variable record 
    792    !> @return file structure completed  
    793    !------------------------------------------------------------------- 
    794    !> @code 
     780   !> - November, 2013- Initial Version 
     781   ! 
     782   !> @param[inout] td_file   file structure 
     783   !> @param[in] cd_name      array of variable name 
     784   !> @param[in] dd_value     array of variable record 
     785   !------------------------------------------------------------------- 
    795786   SUBROUTINE iom_rstdimg__get_file_var_3d(td_file, cd_name, dd_value) 
    796787      IMPLICIT NONE 
    797788      ! Argument       
    798789      TYPE(TFILE),                         INTENT(INOUT) :: td_file 
    799       CHARACTER(LEN=ip_vnl), DIMENSION(:), INTENT(IN)    :: cd_name 
     790      CHARACTER(LEN=im_vnl), DIMENSION(:), INTENT(IN)    :: cd_name 
    800791      REAL(dp),              DIMENSION(:), INTENT(IN)    :: dd_value 
    801792 
     
    812803 
    813804         ! define same dimension as in file 
    814          tl_dim(:)=td_file%t_dim(:)  
     805         tl_dim(:)=dim_copy(td_file%t_dim(:))  
    815806 
    816807         td_file%t_var(ji)=var_init( TRIM(cd_name(ji)), NF90_DOUBLE, & 
    817          &                           tl_dim(:), id_id=ji,            & 
    818          &                           id_rec=INT(dd_value(ji),i4) ) 
     808         &                           tl_dim(:), dd_fill=0._dp,       & 
     809         &                           id_id=ji, id_rec=INT(dd_value(ji),i4) ) 
     810 
     811         ! clean 
     812         CALL dim_clean(tl_dim(:)) 
    819813 
    820814      ENDDO 
    821815 
    822816   END SUBROUTINE iom_rstdimg__get_file_var_3d 
    823    !> @endcode 
    824817   !------------------------------------------------------------------- 
    825818   !> @brief This function read one dimension in an opened netcdf file,  
     
    829822   !> - Nov, 2013- Initial Version 
    830823   ! 
    831    !> @param[in] td_file : file structure 
    832    !> @param[in] id_dimid : dimension id 
     824   !> @param[in] td_file   file structure 
     825   !> @param[in] id_dimid dimension id 
    833826   !> @return  dimension structure  
    834827   !------------------------------------------------------------------- 
    835    !> @code 
    836828   TYPE(TDIM) FUNCTION iom_rstdimg__read_dim_id(td_file, id_dimid) 
    837829      IMPLICIT NONE 
     
    866858 
    867859   END FUNCTION iom_rstdimg__read_dim_id 
    868    !> @endcode 
    869860   !------------------------------------------------------------------- 
    870861   !> @brief This function read one dimension in an opened netcdf file,  
     
    874865   !> - Nov, 2013- Initial Version 
    875866   ! 
    876    !> @param[in] td_file : file structure 
    877    !> @param[in] cd_name : dimension name 
     867   !> @param[in] td_file   file structure 
     868   !> @param[in] cd_name   dimension name 
    878869   !> @return  dimension structure  
    879870   !------------------------------------------------------------------- 
    880    !> @code 
    881871   TYPE(TDIM) FUNCTION iom_rstdimg__read_dim_name(td_file, cd_name) 
    882872      IMPLICIT NONE 
     
    909899 
    910900   END FUNCTION iom_rstdimg__read_dim_name 
    911    !> @endcode 
    912901   !------------------------------------------------------------------- 
    913902   !> @brief This function read variable value in an opened  
    914    !> dimg file, given variable id.</br/> 
    915    !> start indices and number of indices selected along each dimension  
    916    !> could be specify in a 4 dimension table (/'x','y','z','t'/) 
     903   !> dimg file, given variable id. 
     904   !> @details 
     905   !> Optionaly, start indices and number of indices selected along each dimension  
     906   !> could be specify in a 4 dimension array (/'x','y','z','t'/) 
    917907   ! 
    918908   !> @author J.Paul 
    919    !> - Nov, 2013- Initial Version 
    920    ! 
    921    !> @param[in] td_file : file structure 
    922    !> @param[in] id_varid : variable id 
    923    !> @param[in] id_start : index in the variable from which the data values  
     909   !> - November, 2013- Initial Version 
     910   ! 
     911   !> @param[in] td_file   file structure 
     912   !> @param[in] id_varid variable id 
     913   !> @param[in] id_start index in the variable from which the data values  
    924914   !> will be read 
    925    !> @param[in] id_count : number of indices selected along each dimension 
     915   !> @param[in] id_count number of indices selected along each dimension 
    926916   !> @return  variable structure  
    927917   !------------------------------------------------------------------- 
    928    !> @code 
    929918   TYPE(TVAR) FUNCTION iom_rstdimg__read_var_id(td_file, id_varid,& 
    930919   &                                            id_start, id_count) 
     
    935924      INTEGER(i4), DIMENSION(:), INTENT(IN), OPTIONAL :: id_start 
    936925      INTEGER(i4), DIMENSION(:), INTENT(IN), OPTIONAL :: id_count 
    937       !INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN), OPTIONAL :: id_start 
    938       !INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN), OPTIONAL :: id_count 
    939926 
    940927      ! local variable 
    941       INTEGER(i4), DIMENSION(1) :: il_ind 
     928      INTEGER(i4), DIMENSION(1) :: il_varid 
    942929      !---------------------------------------------------------------- 
    943930      ! check if file opened 
     
    950937 
    951938         ! look for variable id 
    952          il_ind(:)=MINLOC(td_file%t_var(:)%i_id,mask=(td_file%t_var(:)%i_id==id_varid)) 
    953          IF( il_ind(1) /= 0 )THEN 
    954  
    955             iom_rstdimg__read_var_id=td_file%t_var(il_ind(1)) 
     939         il_varid(:)=MINLOC(td_file%t_var(:)%i_id,mask=(td_file%t_var(:)%i_id==id_varid)) 
     940         IF( il_varid(1) /= 0 )THEN 
     941 
     942            iom_rstdimg__read_var_id=var_copy(td_file%t_var(il_varid(1))) 
    956943 
    957944            IF( iom_rstdimg__read_var_id%i_ndim /= 0 )THEN 
     
    962949            ELSE 
    963950               CALL logger_debug( " READ VAR: variable 0d "//& 
    964                &               TRIM(td_file%t_var(il_ind(1))%c_name)//& 
     951               &               TRIM(td_file%t_var(il_varid(1))%c_name)//& 
    965952               &               " should be already read ") 
    966953            ENDIF             
     
    974961      ENDIF 
    975962   END FUNCTION iom_rstdimg__read_var_id 
    976    !> @endcode    
    977963   !------------------------------------------------------------------- 
    978964   !> @brief This function read variable value in an opened  
    979    !> dimg file, given variable name or standard name.</br/> 
    980    !> start indices and number of indices selected along each dimension  
    981    !> could be specify in a 4 dimension table (/'x','y','z','t'/) 
    982    ! 
     965   !> dimg file, given variable name or standard name. 
    983966   !> @details 
     967   !> Optionaly, start indices and number of indices selected along each dimension  
     968   !> could be specify in a 4 dimension array (/'x','y','z','t'/) 
     969   ! 
    984970   !> look first for variable name. If it doesn't 
    985971   !> exist in file, look for variable standard name.<br/> 
    986    !> If variable name is not present, check variable standard name.<br/> 
    987972   ! 
    988973   !> @author J.Paul 
    989    !> - Nov, 2013- Initial Version 
    990    ! 
    991    !> @param[in] td_file : file structure 
    992    !> @param[in] cd_name  : variable name or standard name  
    993    !> @param[in] id_start : index in the variable from which the data values  
     974   !> - November, 2013- Initial Version 
     975   ! 
     976   !> @param[in] td_file   file structure 
     977   !> @param[in] cd_name  variable name or standard name  
     978   !> @param[in] id_start index in the variable from which the data values  
    994979   !> will be read 
    995    !> @param[in] id_count : number of indices selected along each dimension 
     980   !> @param[in] id_count number of indices selected along each dimension 
    996981   !> @return  variable structure  
    997982   !------------------------------------------------------------------- 
    998    !> @code 
    999983   TYPE(TVAR) FUNCTION iom_rstdimg__read_var_name(td_file, cd_name,   & 
    1000984   &                                              id_start, id_count  ) 
     
    1005989      INTEGER(i4),      DIMENSION(:),  INTENT(IN), OPTIONAL :: id_start 
    1006990      INTEGER(i4),      DIMENSION(:),  INTENT(IN), OPTIONAL :: id_count 
    1007       !INTEGER(i4),      DIMENSION(ip_maxdim),  INTENT(IN), OPTIONAL :: id_start 
    1008       !INTEGER(i4),      DIMENSION(ip_maxdim),  INTENT(IN), OPTIONAL :: id_count 
    1009991 
    1010992      ! local variable 
    1011       INTEGER(i4)       :: il_ind 
     993      INTEGER(i4)       :: il_varid 
    1012994      !---------------------------------------------------------------- 
    1013995      ! check if file opened 
     
    10191001      ELSE 
    10201002 
    1021          il_ind=var_get_id(td_file%t_var(:), cd_name) 
    1022          IF( il_ind /= 0 )THEN 
    1023  
    1024             iom_rstdimg__read_var_name=td_file%t_var(il_ind) 
    1025  
    1026             IF( td_file%t_var(il_ind)%i_ndim /= 0 )THEN 
     1003         il_varid=var_get_index(td_file%t_var(:), cd_name) 
     1004         IF( il_varid /= 0 )THEN 
     1005 
     1006            iom_rstdimg__read_var_name=var_copy(td_file%t_var(il_varid)) 
     1007 
     1008            IF( td_file%t_var(il_varid)%i_ndim /= 0 )THEN 
    10271009               !!! read variable value 
    10281010               CALL iom_rstdimg__read_var_value( td_file, & 
     
    10311013            ELSE 
    10321014               CALL logger_debug( " READ VAR: variable 0d "//& 
    1033                &               TRIM(td_file%t_var(il_ind)%c_name)//& 
     1015               &               TRIM(td_file%t_var(il_varid)%c_name)//& 
    10341016               &               " should have been already read ") 
    10351017            ENDIF 
     
    10471029       
    10481030   END FUNCTION iom_rstdimg__read_var_name 
    1049    !> @endcode 
    1050    !------------------------------------------------------------------- 
    1051    !> @brief This subroutine fill all variable value in an opened  
    1052    !> dimg file.</br/> 
    1053    !> start indices and number of indices selected along each dimension  
    1054    !> could be specify in a 4 dimension table (/'x','y','z','t'/) 
    1055    ! 
    1056    !> @author J.Paul 
    1057    !> - Nov, 2013- Initial Version 
    1058    ! 
    1059    !> @param[inout] td_file : file structure 
    1060    !> @param[in] id_start : index in the variable from which the data values  
    1061    !> will be read 
    1062    !> @param[in] id_count : number of indices selected along each dimension 
    1063    !------------------------------------------------------------------- 
    1064    !> @code 
    1065    SUBROUTINE iom_rstdimg__fill_var_all(td_file, id_start, id_count) 
    1066       IMPLICIT NONE 
    1067       ! Argument       
    1068       TYPE(TFILE),               INTENT(INOUT) :: td_file 
    1069       INTEGER(i4), DIMENSION(:), INTENT(IN),   OPTIONAL :: id_start 
    1070       INTEGER(i4), DIMENSION(:), INTENT(IN),   OPTIONAL :: id_count 
    1071       !INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN),   OPTIONAL :: id_start 
    1072       !INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN),   OPTIONAL :: id_count 
    1073  
    1074       ! local variable 
    1075  
    1076       ! loop indices 
    1077       INTEGER(i4) :: ji 
    1078       !---------------------------------------------------------------- 
    1079       ! check if file opened 
    1080       IF( td_file%i_id == 0 )THEN 
    1081  
    1082          CALL logger_error( & 
    1083          &  " FILL VAR: no id associated to file "//TRIM(td_file%c_name)) 
    1084  
    1085       ELSE 
    1086  
    1087          DO ji=1,td_file%i_nvar 
    1088             CALL iom_rstdimg_fill_var(td_file, ji, id_start, id_count) 
    1089          ENDDO 
    1090  
    1091       ENDIF 
    1092    END SUBROUTINE iom_rstdimg__fill_var_all 
    1093    !> @endcode 
    1094    !------------------------------------------------------------------- 
    1095    !> @brief This subroutine fill variable value in an opened  
    1096    !> dimg file, given variable id.</br/> 
    1097    !> start indices and number of indices selected along each dimension  
    1098    !> could be specify in a 4 dimension table (/'x','y','z','t'/) 
    1099    ! 
    1100    !> @author J.Paul 
    1101    !> - Nov, 2013- Initial Version 
    1102    ! 
    1103    !> @param[inout] td_file : file structure 
    1104    !> @param[in] id_varid : variable id 
    1105    !> @param[in] id_start : index in the variable from which the data values  
    1106    !> will be read 
    1107    !> @param[in] id_count : number of indices selected along each dimension 
    1108    !------------------------------------------------------------------- 
    1109    !> @code 
    1110    SUBROUTINE iom_rstdimg__fill_var_id(td_file, id_varid, id_start, id_count) 
    1111       IMPLICIT NONE 
    1112       ! Argument       
    1113       TYPE(TFILE),               INTENT(INOUT) :: td_file 
    1114       INTEGER(i4),               INTENT(IN)    :: id_varid 
    1115       INTEGER(i4), DIMENSION(:), INTENT(IN),   OPTIONAL :: id_start 
    1116       INTEGER(i4), DIMENSION(:), INTENT(IN),   OPTIONAL :: id_count 
    1117       !INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN),   OPTIONAL :: id_start 
    1118       !INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN),   OPTIONAL :: id_count 
    1119  
    1120       ! local variable 
    1121       INTEGER(i4), DIMENSION(1) :: il_ind 
    1122       TYPE(TVAR)                :: tl_var 
    1123       !---------------------------------------------------------------- 
    1124       ! check if file opened 
    1125       IF( td_file%i_id == 0 )THEN 
    1126  
    1127          CALL logger_error( & 
    1128          &  " FILL VAR: no id associated to file "//TRIM(td_file%c_name)) 
    1129  
    1130       ELSE 
    1131  
    1132          ! look for variable id 
    1133          il_ind(:) = MINLOC( td_file%t_var(:)%i_id, & 
    1134          &                   mask=(td_file%t_var(:)%i_id==id_varid)) 
    1135          IF( il_ind(1) /= 0 )THEN 
    1136  
    1137             IF( tl_var%i_ndim /= 0 )THEN 
    1138                !!! read variable value 
    1139                CALL iom_rstdimg__read_var_value(td_file, td_file%t_var(il_ind(1)), & 
    1140                &                                id_start, id_count) 
    1141  
    1142             ELSE 
    1143                CALL logger_debug( " FILL VAR: variable 0d "//& 
    1144                &               TRIM(td_file%t_var(il_ind(1))%c_name)//& 
    1145                &               " should be already read ") 
    1146             ENDIF             
    1147  
    1148          ELSE 
    1149             CALL logger_error( & 
    1150             &  " FILL VAR: there is no variable with id "//& 
    1151             &  TRIM(fct_str(id_varid))//" in file "//TRIM(td_file%c_name)) 
    1152          ENDIF 
    1153  
    1154       ENDIF 
    1155    END SUBROUTINE iom_rstdimg__fill_var_id 
    1156    !> @endcode 
    1157    !------------------------------------------------------------------- 
    1158    !> @brief This subroutine fill variable value in an opened  
    1159    !> dimg file, given variable name or standard name.</br/> 
    1160    !> start indices and number of indices selected along each dimension  
    1161    !> could be specify in a 4 dimension table (/'x','y','z','t'/) 
    1162    ! 
    1163    !> @details 
    1164    !> look first for variable name. If it doesn't 
    1165    !> exist in file, look for variable standard name.<br/> 
    1166    !> If variable name is not present, check variable standard name.<br/> 
    1167    ! 
    1168    !> @author J.Paul 
    1169    !> - Nov, 2013- Initial Version 
    1170    ! 
    1171    !> @param[inout] td_file : file structure 
    1172    !> @param[in] cd_name  : variable name or standard name 
    1173    !> @param[in] id_start : index in the variable from which the data values  
    1174    !> will be read 
    1175    !> @param[in] id_count : number of indices selected along each dimension 
    1176    !> @return  variable structure  
    1177    !------------------------------------------------------------------- 
    1178    !> @code 
    1179    SUBROUTINE iom_rstdimg__fill_var_name(td_file, cd_name, id_start, id_count ) 
    1180       IMPLICIT NONE 
    1181       ! Argument  
    1182       TYPE(TFILE),                    INTENT(INOUT) :: td_file 
    1183       CHARACTER(LEN=*),               INTENT(IN)    :: cd_name 
    1184       INTEGER(i4),      DIMENSION(:), INTENT(IN), OPTIONAL :: id_start 
    1185       INTEGER(i4),      DIMENSION(:), INTENT(IN), OPTIONAL :: id_count 
    1186       !INTEGER(i4),      DIMENSION(ip_maxdim), INTENT(IN), OPTIONAL :: id_start 
    1187       !INTEGER(i4),      DIMENSION(ip_maxdim), INTENT(IN), OPTIONAL :: id_count 
    1188       !CHARACTER(LEN=*),                       INTENT(IN), OPTIONAL :: cd_stdname 
    1189  
    1190       ! local variable 
    1191       INTEGER(i4)       :: il_ind 
    1192       !---------------------------------------------------------------- 
    1193       ! check if file opened 
    1194       IF( td_file%i_id == 0 )THEN 
    1195  
    1196          CALL logger_error( & 
    1197          &  " FILL VAR: no id associated to file "//TRIM(td_file%c_name)) 
    1198  
    1199       ELSE 
    1200  
    1201          il_ind=var_get_id(td_file%t_var, cd_name) 
    1202          IF( il_ind /= 0 )THEN 
    1203  
    1204             IF( td_file%t_var(il_ind)%i_ndim /= 0 )THEN 
    1205                !!! read variable value 
    1206                CALL iom_rstdimg__read_var_value( td_file, td_file%t_var(il_ind), & 
    1207                &                                 id_start, id_count) 
    1208  
    1209             ELSE 
    1210                CALL logger_debug( " FILL VAR: variable 0d "//& 
    1211                &               TRIM(td_file%t_var(il_ind)%c_name)//& 
    1212                &               " should have been already read ") 
    1213             ENDIF 
    1214  
    1215          ELSE 
    1216  
    1217             CALL logger_error( & 
    1218             &  " FILL VAR: there is no variable with "//& 
    1219             &  " name or standard name "//TRIM(cd_name)//& 
    1220             &  " in file "//TRIM(td_file%c_name)) 
    1221  
    1222          ENDIF 
    1223  
    1224       ENDIF 
    1225        
    1226    END SUBROUTINE iom_rstdimg__fill_var_name 
    1227    !> @endcode 
    12281031   !------------------------------------------------------------------- 
    12291032   !> @brief This subroutine read variable value in an opened dimg file, for 
    12301033   !> variable 1,2,3d. 
    1231    ! 
     1034   !> @details 
     1035   !> Optionaly,start indices and number of indices selected along each dimension  
     1036   !> could be specify in a 4 dimension array (/'x','y','z','t'/) 
     1037   !> 
    12321038   !> @author J.Paul 
    1233    !> - Nov, 2013- Initial Version 
    1234    ! 
    1235    !> @param[in] td_file : file structure 
    1236    !> @param[inout] td_var : variable structure 
    1237    !> @param[in] id_start : index in the variable from which the data values will be read 
    1238    !> @param[in] id_count : number of indices selected along each dimension 
    1239    !> @return variable structure completed  
    1240    !------------------------------------------------------------------- 
    1241    !> @code 
     1039   !> - November, 2013- Initial Version 
     1040   ! 
     1041   !> @param[in] td_file   file structure 
     1042   !> @param[inout] td_var variable structure 
     1043   !> @param[in] id_start  index in the variable from which the data values will be read 
     1044   !> @param[in] id_count  number of indices selected along each dimension 
     1045   !------------------------------------------------------------------- 
    12421046   SUBROUTINE iom_rstdimg__read_var_value(td_file, td_var, & 
    12431047   &                                      id_start, id_count ) 
     
    12481052      INTEGER(i4), DIMENSION(:), INTENT(IN),  OPTIONAL :: id_start 
    12491053      INTEGER(i4), DIMENSION(:), INTENT(IN),  OPTIONAL :: id_count 
    1250       !INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN),  OPTIONAL :: id_start 
    1251       !INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN),  OPTIONAL :: id_count 
    12521054 
    12531055      ! local variable 
     
    12731075         IF( SIZE(id_start(:)) /= ip_maxdim .OR. & 
    12741076         &   SIZE(id_count(:)) /= ip_maxdim )THEN 
    1275             CALL logger_error("READ VAR: dimension of table start or count "//& 
     1077            CALL logger_error("READ VAR: dimension of array start or count "//& 
    12761078            &      " are invalid to read variable "//TRIM(td_var%c_name)//& 
    12771079            &      " in file "//TRIM(td_file%c_name) ) 
     
    13281130            &  " READ VAR VALUE: not enough space to put variable "//& 
    13291131            &  TRIM(td_var%c_name)//& 
    1330             &  " in temporary table") 
     1132            &  " in temporary array") 
    13311133 
    13321134         ENDIF 
     
    13581160            ENDIF 
    13591161         ELSEIF( td_var%t_dim(3)%l_use )THEN 
    1360             ! 1d variable (Z) 
     1162            ! 1D variable (Z) 
    13611163            READ(td_file%i_id, IOSTAT=il_status, REC=td_var%i_rec ) & 
    13621164            &  dl_value(:,:,:,:) 
     
    14031205 
    14041206   END SUBROUTINE iom_rstdimg__read_var_value 
    1405    !> @endcode 
    1406    !------------------------------------------------------------------- 
    1407    !> @brief This subroutine write file structure in an opened dimg file. 
     1207   !------------------------------------------------------------------- 
     1208   !> @brief This subroutine write dimg file from file structure. 
    14081209   ! 
    14091210   !> @details 
    1410    ! 
     1211   !> dimg file have to be already opened in write mode. 
     1212   !> 
    14111213   !> @author J.Paul 
    1412    !> - Nov, 2013- Initial Version 
    1413    ! 
    1414    !> @param[in] td_file : file structure 
    1415    !------------------------------------------------------------------- 
    1416    !> @code 
     1214   !> - November, 2013- Initial Version 
     1215   !> @date September, 2014 
     1216   !> - use iom_rstdimg__get_rec 
     1217   ! 
     1218   !> @param[inout] td_file   file structure 
     1219   !------------------------------------------------------------------- 
    14171220   SUBROUTINE iom_rstdimg_write_file(td_file) 
    14181221      IMPLICIT NONE 
     
    14211224 
    14221225      ! local variable 
    1423       INTEGER(i4) :: il_status 
    1424       INTEGER(i4) :: il_attid 
     1226      INTEGER(i4)           :: il_status 
     1227      INTEGER(i4)           :: il_ind 
    14251228      !---------------------------------------------------------------- 
    14261229      ! check if file opened 
     
    14331236         IF( td_file%l_wrt )THEN 
    14341237 
     1238            ! check dimension 
     1239            IF( td_file%t_dim(jp_L)%l_use .AND. & 
     1240            &   td_file%t_dim(jp_L)%i_len /= 1 )THEN 
     1241               CALL logger_fatal("WRITE FILE: can not write dimg file with "//& 
     1242               &  " several time step.") 
     1243            ENDIF 
     1244 
    14351245            ! close and open file with right record length 
    14361246            CALL iom_rstdimg_close(td_file) 
    14371247 
     1248            ! compute record number to be used  
     1249            ! and add variable no0d, no1d,.. if need be 
     1250            CALL iom_rstdimg__get_rec(td_file) 
     1251 
    14381252            ! compute record length 
    1439             il_attid=att_get_id(td_file%t_att(:),"DOMAIN_number_total") 
    1440             IF( il_attid /= 0 )THEN 
     1253            il_ind=att_get_index(td_file%t_att(:),"DOMAIN_number_total") 
     1254            IF( il_ind /= 0 )THEN 
    14411255               td_file%i_recl = MAX( & 
    14421256               &     td_file%t_dim(1)%i_len * td_file%t_dim(2)%i_len * 8, & 
    1443                &     ( 8 * INT(td_file%t_att(il_attid)%d_value(1)) + 15 ) * 4 ) 
     1257               &     ( 8 * INT(td_file%t_att(il_ind)%d_value(1)) + 15 ) * 4 ) 
    14441258            ELSE 
    14451259               td_file%i_recl = td_file%t_dim(1)%i_len * & 
    14461260               &                td_file%t_dim(2)%i_len * 8 
    14471261            ENDIF 
     1262            ! check record length 
     1263            IF( td_file%i_nvar*(im_vnl+dp) > td_file%i_recl )THEN 
     1264               CALL logger_fatal("WRITE FILE: record length is too small. "//& 
     1265               &  " Try to reduce the output number of processor.") 
     1266            ENDIF 
     1267 
     1268            ! get free unit 
     1269            td_file%i_id=fct_getunit() 
    14481270 
    14491271            OPEN( td_file%i_id, FILE=TRIM(td_file%c_name),& 
     
    14561278            CALL fct_err(il_status) 
    14571279            IF( il_status /= 0 )THEN 
    1458                CALL logger_error("REPLACE: file "//TRIM(td_file%c_name)//& 
     1280               CALL logger_error("WRITE FILE: REPLACE file "//TRIM(td_file%c_name)//& 
    14591281               &  " with record length "//TRIM(fct_str(td_file%i_recl))) 
    14601282            ELSE 
    1461                CALL logger_debug("REPLACE: file "//TRIM(td_file%c_name)//& 
     1283               CALL logger_debug("WRITE FILE: REPLACE file "//TRIM(td_file%c_name)//& 
    14621284               &  " with record length "//TRIM(fct_str(td_file%i_recl))) 
    14631285            ENDIF 
     
    14791301 
    14801302   END SUBROUTINE iom_rstdimg_write_file 
    1481    !> @endcode 
     1303   !------------------------------------------------------------------- 
     1304   !> @brief This subroutine compute record number to be used. 
     1305   !> 
     1306   !> @details 
     1307   !> Moreover it adds variable no0d, no1d, no2d and no3d if need be. 
     1308   !> 
     1309   !> @author J.Paul 
     1310   !> - September, 2014- Initial Version 
     1311   ! 
     1312   !> @param[inout] td_file   file structure 
     1313   !------------------------------------------------------------------- 
     1314   SUBROUTINE iom_rstdimg__get_rec(td_file) 
     1315      IMPLICIT NONE 
     1316      ! Argument       
     1317      TYPE(TFILE), INTENT(INOUT) :: td_file 
     1318 
     1319      ! local variable 
     1320      INTEGER(i4) :: il_rec 
     1321      TYPE(TVAR)  :: tl_var 
     1322 
     1323      INTEGER(i4), DIMENSION(:)    , ALLOCATABLE :: il_tmp1d 
     1324      INTEGER(i4), DIMENSION(:,:)  , ALLOCATABLE :: il_tmp2d 
     1325      INTEGER(i4), DIMENSION(:,:,:), ALLOCATABLE :: il_tmp3d 
     1326 
     1327      ! loop indices 
     1328      INTEGER(i4) :: ji 
     1329      !---------------------------------------------------------------- 
     1330 
     1331      ! add dummy variable if necessary 
     1332      IF( td_file%i_n0d == 0 )THEN 
     1333         ! create var 
     1334         tl_var=var_init('no0d') 
     1335 
     1336         CALL file_add_var( td_file, tl_var ) 
     1337      ENDIF 
     1338 
     1339      IF( td_file%i_n1d == 0 )THEN 
     1340         ! create var 
     1341         ALLOCATE( il_tmp1d( td_file%t_dim(3)%i_len ) ) 
     1342         il_tmp1d(:)=-1 
     1343 
     1344         tl_var=var_init( 'no1d', il_tmp1d(:))  
     1345 
     1346         DEALLOCATE( il_tmp1d ) 
     1347 
     1348         CALL file_add_var( td_file, tl_var )  
     1349      ENDIF 
     1350  
     1351      IF( td_file%i_n2d == 0 )THEN 
     1352         ! create var 
     1353         ALLOCATE( il_tmp2d( td_file%t_dim(1)%i_len, & 
     1354         &                   td_file%t_dim(2)%i_len ) ) 
     1355         il_tmp2d(:,:)=-1 
     1356 
     1357         tl_var=var_init('no2d', il_tmp2d(:,:) ) 
     1358 
     1359         DEALLOCATE( il_tmp2d ) 
     1360 
     1361         CALL file_add_var( td_file, tl_var )  
     1362 
     1363      ENDIF 
     1364  
     1365      IF( td_file%i_n3d == 0 )THEN 
     1366         ! create var 
     1367         ALLOCATE( il_tmp3d( td_file%t_dim(1)%i_len, & 
     1368         &                   td_file%t_dim(2)%i_len, & 
     1369         &                   td_file%t_dim(3)%i_len ) ) 
     1370         il_tmp3d(:,:,:)=-1 
     1371 
     1372         tl_var=var_init('no3d', il_tmp3d(:,:,:) ) 
     1373 
     1374         DEALLOCATE( il_tmp3d ) 
     1375 
     1376         CALL file_add_var( td_file, tl_var )  
     1377      ENDIF 
     1378 
     1379      ! clean 
     1380      CALL var_clean(tl_var) 
     1381 
     1382      il_rec=2 
     1383      DO ji=1,td_file%i_nvar 
     1384         SELECT CASE(td_file%t_var(ji)%i_ndim) 
     1385            CASE(0) 
     1386               IF( INDEX(td_file%t_var(ji)%c_name, 'no0d' ) == 0 )THEN 
     1387                  td_file%t_var(ji)%i_rec=il_rec 
     1388                  il_rec = il_rec  + 0 
     1389               ENDIF 
     1390            CASE(1) 
     1391               IF( INDEX(td_file%t_var(ji)%c_name, 'no1d' ) == 0 )THEN 
     1392                  td_file%t_var(ji)%i_rec=il_rec 
     1393                  il_rec = il_rec  + 1 
     1394               ENDIF 
     1395            CASE(2) 
     1396               IF( INDEX(td_file%t_var(ji)%c_name, 'no2d' ) == 0 )THEN 
     1397                  td_file%t_var(ji)%i_rec=il_rec 
     1398                  il_rec = il_rec  + 1 
     1399               ENDIF 
     1400            CASE(3) 
     1401               IF( INDEX(td_file%t_var(ji)%c_name, 'no3d' ) == 0 )THEN 
     1402                  td_file%t_var(ji)%i_rec=il_rec 
     1403                  il_rec = il_rec  + td_file%t_dim(3)%i_len 
     1404               ENDIF 
     1405         END SELECT 
     1406      ENDDO 
     1407      td_file%i_rhd  = il_rec 
     1408 
     1409      END SUBROUTINE iom_rstdimg__get_rec 
    14821410   !------------------------------------------------------------------- 
    14831411   !> @brief This subroutine write header in an opened dimg  
     
    14851413   ! 
    14861414   !> @author J.Paul 
    1487    !> - Nov, 2013- Initial Version 
    1488    ! 
    1489    !> @param[in] td_file : file structure 
    1490    !> @param[in] td_dim : dimension structure 
    1491    !> @return  dimension id  
    1492    !------------------------------------------------------------------- 
    1493    !> @code 
     1415   !> - November, 2013- Initial Version 
     1416   ! 
     1417   !> @param[inout] td_file   file structure 
     1418   !------------------------------------------------------------------- 
    14941419   SUBROUTINE iom_rstdimg__write_header(td_file) 
    14951420      IMPLICIT NONE 
     
    14991424      ! local variable 
    15001425      INTEGER(i4) :: il_status 
    1501       INTEGER(i4) :: il_attid 
     1426      INTEGER(i4) :: il_ind 
    15021427      INTEGER(i4) :: il_nproc 
    15031428      INTEGER(i4) :: il_niproc 
     
    15371462 
    15381463      ! get domain decomposition 
    1539       il_attid=att_get_id( td_file%t_att, "DOMAIN_number_total" ) 
     1464      il_ind=att_get_index( td_file%t_att, "DOMAIN_number_total" ) 
    15401465      il_nproc = 1 
    1541       IF( il_attid /= 0 )THEN 
    1542          il_nproc = INT(td_file%t_att(il_attid)%d_value(1)) 
    1543       ENDIF 
    1544  
    1545       il_attid=att_get_id( td_file%t_att, "DOMAIN_I_number_total" ) 
     1466      IF( il_ind /= 0 )THEN 
     1467         il_nproc = INT(td_file%t_att(il_ind)%d_value(1)) 
     1468      ENDIF 
     1469 
     1470      il_ind=att_get_index( td_file%t_att, "DOMAIN_I_number_total" ) 
    15461471      il_niproc = 0 
    1547       IF( il_attid /= 0 )THEN 
    1548          il_niproc = INT(td_file%t_att(il_attid)%d_value(1)) 
    1549       ENDIF 
    1550  
    1551       il_attid=att_get_id( td_file%t_att, "DOMAIN_J_number_total" ) 
     1472      IF( il_ind /= 0 )THEN 
     1473         il_niproc = INT(td_file%t_att(il_ind)%d_value(1)) 
     1474      ENDIF 
     1475 
     1476      il_ind=att_get_index( td_file%t_att, "DOMAIN_J_number_total" ) 
    15521477      il_njproc = 0 
    1553       IF( il_attid /= 0 )THEN 
    1554          il_njproc = INT(td_file%t_att(il_attid)%d_value(1)) 
     1478      IF( il_ind /= 0 )THEN 
     1479         il_njproc = INT(td_file%t_att(il_ind)%d_value(1)) 
    15551480      ENDIF 
    15561481 
     
    15701495       
    15711496      ! get domain number 
    1572       il_attid=att_get_id( td_file%t_att, "DOMAIN_number" ) 
     1497      il_ind=att_get_index( td_file%t_att, "DOMAIN_number" ) 
    15731498      il_area = 0 
    1574       IF( il_attid /= 0 )THEN 
    1575          il_area = INT(td_file%t_att(il_attid)%d_value(1)) 
     1499      IF( il_ind /= 0 )THEN 
     1500         il_area = INT(td_file%t_att(il_ind)%d_value(1)) 
    15761501      ENDIF 
    15771502 
    15781503      ! get domain global size 
    1579       il_attid=att_get_id( td_file%t_att, "DOMAIN_size_global" ) 
     1504      il_ind=att_get_index( td_file%t_att, "DOMAIN_size_global" ) 
    15801505      il_iglo = 0 
    15811506      il_jglo = 0 
    1582       IF( il_attid /= 0 )THEN 
    1583          il_iglo = INT(td_file%t_att(il_attid)%d_value(1)) 
    1584          il_jglo = INT(td_file%t_att(il_attid)%d_value(2)) 
     1507      IF( il_ind /= 0 )THEN 
     1508         il_iglo = INT(td_file%t_att(il_ind)%d_value(1)) 
     1509         il_jglo = INT(td_file%t_att(il_ind)%d_value(2)) 
    15851510      ENDIF 
    15861511 
     
    16001525      ! allocate local variable 
    16011526      ALLOCATE( il_impp(il_nproc), il_jmpp(il_nproc),& 
    1602       &         il_lci(il_niproc),  il_lcj(il_njproc), & 
    1603       &         il_ldi(il_niproc),  il_ldj(il_njproc), & 
    1604       &         il_lei(il_niproc),  il_lej(il_njproc) ) 
     1527      &         il_lci(il_nproc),  il_lcj(il_nproc), & 
     1528      &         il_ldi(il_nproc),  il_ldj(il_nproc), & 
     1529      &         il_lei(il_nproc),  il_lej(il_nproc) ) 
    16051530 
    16061531      ! get domain first poistion 
    1607       il_attid=att_get_id( td_file%t_att, "DOMAIN_I_position_first" ) 
     1532      il_ind=att_get_index( td_file%t_att, "DOMAIN_I_position_first" ) 
    16081533      il_impp(:) = 0 
    1609       IF( il_attid /= 0 )THEN 
    1610          il_impp(:) = INT(td_file%t_att(il_attid)%d_value(:)) 
    1611       ENDIF 
    1612  
    1613       il_attid=att_get_id( td_file%t_att, "DOMAIN_J_position_first" ) 
     1534      IF( il_ind /= 0 )THEN 
     1535         il_impp(:) = INT(td_file%t_att(il_ind)%d_value(:)) 
     1536      ENDIF 
     1537 
     1538      il_ind=att_get_index( td_file%t_att, "DOMAIN_J_position_first" ) 
    16141539      il_jmpp(:) = 0 
    1615       IF( il_attid /= 0 )THEN 
    1616          il_jmpp(:) = INT(td_file%t_att(il_attid)%d_value(:)) 
     1540      IF( il_ind /= 0 )THEN 
     1541         il_jmpp(:) = INT(td_file%t_att(il_ind)%d_value(:)) 
    16171542      ENDIF 
    16181543       
     
    16231548 
    16241549      ! get domain last poistion 
    1625       il_attid=att_get_id( td_file%t_att, "DOMAIN_I_position_last" ) 
     1550      il_ind=att_get_index( td_file%t_att, "DOMAIN_I_position_last" ) 
    16261551      il_lci(:) = 0 
    1627       IF( il_attid /= 0 )THEN 
    1628          il_lci(:) = INT(td_file%t_att(il_attid)%d_value(:)) 
    1629       ENDIF 
    1630  
    1631       il_attid=att_get_id( td_file%t_att, "DOMAIN_J_position_last" ) 
     1552      IF( il_ind /= 0 )THEN 
     1553         il_lci(:) = INT(td_file%t_att(il_ind)%d_value(:)) 
     1554      ENDIF 
     1555 
     1556      il_ind=att_get_index( td_file%t_att, "DOMAIN_J_position_last" ) 
    16321557      il_lcj(:) = 0 
    1633       IF( il_attid /= 0 )THEN 
    1634          il_lcj(:) = INT(td_file%t_att(il_attid)%d_value(:)) 
     1558      IF( il_ind /= 0 )THEN 
     1559         il_lcj(:) = INT(td_file%t_att(il_ind)%d_value(:)) 
    16351560      ENDIF 
    16361561 
     
    16411566 
    16421567      ! get halo size start 
    1643       il_attid=att_get_id( td_file%t_att, "DOMAIN_I_halo_size_start" ) 
     1568      il_ind=att_get_index( td_file%t_att, "DOMAIN_I_halo_size_start" ) 
    16441569      il_ldi(:) = 0 
    1645       IF( il_attid /= 0 )THEN 
    1646          il_ldi(:) = INT(td_file%t_att(il_attid)%d_value(:)) 
    1647       ENDIF 
    1648  
    1649       il_attid=att_get_id( td_file%t_att, "DOMAIN_J_halo_size_start" ) 
     1570      IF( il_ind /= 0 )THEN 
     1571         il_ldi(:) = INT(td_file%t_att(il_ind)%d_value(:)) 
     1572      ENDIF 
     1573 
     1574      il_ind=att_get_index( td_file%t_att, "DOMAIN_J_halo_size_start" ) 
    16501575      il_ldj(:) = 0 
    1651       IF( il_attid /= 0 )THEN 
    1652          il_ldj(:) = INT(td_file%t_att(il_attid)%d_value(:)) 
     1576      IF( il_ind /= 0 )THEN 
     1577         il_ldj(:) = INT(td_file%t_att(il_ind)%d_value(:)) 
    16531578      ENDIF 
    16541579       
     
    16591584 
    16601585      ! get halo size end 
    1661       il_attid=att_get_id( td_file%t_att, "DOMAIN_I_halo_size_end" ) 
     1586      il_ind=att_get_index( td_file%t_att, "DOMAIN_I_halo_size_end" ) 
    16621587      il_lei(:) = 0 
    1663       IF( il_attid /= 0 )THEN 
    1664          il_lei(:) = INT(td_file%t_att(il_attid)%d_value(:)) 
    1665       ENDIF 
    1666  
    1667       il_attid=att_get_id( td_file%t_att, "DOMAIN_J_halo_size_end" ) 
     1588      IF( il_ind /= 0 )THEN 
     1589         il_lei(:) = INT(td_file%t_att(il_ind)%d_value(:)) 
     1590      ENDIF 
     1591 
     1592      il_ind=att_get_index( td_file%t_att, "DOMAIN_J_halo_size_end" ) 
    16681593      il_lej(:) = 0 
    1669       IF( il_attid /= 0 )THEN 
    1670          il_lej(:) = INT(td_file%t_att(il_attid)%d_value(:)) 
     1594      IF( il_ind /= 0 )THEN 
     1595         il_lej(:) = INT(td_file%t_att(il_ind)%d_value(:)) 
    16711596      ENDIF 
    16721597 
     
    16901615      &  il_area,                & 
    16911616      &  il_iglo, il_jglo,       & 
    1692       &  il_impp(:), il_jmpp(:), & 
    16931617      &  il_lci(:), il_lcj(:),   & 
    16941618      &  il_ldi(:), il_ldj(:),   & 
    1695       &  il_lei(:), il_lej(:) 
     1619      &  il_lei(:), il_lej(:),   & 
     1620      &  il_impp(:), il_jmpp(:) 
    16961621 
    16971622      DEALLOCATE( il_impp, il_jmpp,& 
     
    17011626 
    17021627      END SUBROUTINE iom_rstdimg__write_header 
    1703    !> @endcode    
    1704    !------------------------------------------------------------------- 
    1705    !> @brief This subroutine write variables in an opened dimg file.</br/> 
    1706    ! 
     1628   !------------------------------------------------------------------- 
     1629   !> @brief This subroutine write variables in an opened dimg file. 
     1630   !> 
    17071631   !> @author J.Paul 
    1708    !> - Nov, 2013- Initial Version 
    1709    ! 
    1710    !> @param[in] id_fileid : file id 
    1711    !------------------------------------------------------------------- 
    1712    !> @code 
     1632   !> - November, 2013- Initial Version 
     1633   !> 
     1634   !> @param[in] id_fileid file id 
     1635   !------------------------------------------------------------------- 
    17131636   SUBROUTINE iom_rstdimg__write_var(td_file) 
    17141637      IMPLICIT NONE 
     
    17181641      ! local variable 
    17191642      INTEGER(i4) :: il_status 
    1720       TYPE(TVAR)  :: tl_var 
     1643      INTEGER(i4) :: il_rec 
    17211644 
    17221645      INTEGER(i4),            DIMENSION(:), ALLOCATABLE :: il_start 
    17231646      INTEGER(i4),            DIMENSION(:), ALLOCATABLE :: il_count 
    1724       CHARACTER(LEN=ip_vnl),  DIMENSION(:), ALLOCATABLE :: cl_name 
     1647      CHARACTER(LEN=im_vnl),  DIMENSION(:), ALLOCATABLE :: cl_name 
    17251648      REAL(dp),               DIMENSION(:), ALLOCATABLE :: dl_value 
    1726  
    1727       INTEGER(i4),            DIMENSION(:,:,:,:), ALLOCATABLE :: il_tmp 
    17281649 
    17291650      ! loop indices 
    17301651      INTEGER(i4) :: ji 
     1652      INTEGER(i4) :: jk 
    17311653      !---------------------------------------------------------------- 
    1732  
    1733       ! add dummy variable if necessary 
    1734       IF( td_file%i_n0d == 0 )THEN 
    1735          ! create var 
    1736          tl_var=var_init('no0d') 
    1737          ! add value 
    1738          ALLOCATE( il_tmp(1,1,1,1) ) 
    1739          il_tmp(:,:,:,:)=-1 
    1740          CALL var_add_value(tl_var, il_tmp) 
    1741          DEALLOCATE( il_tmp ) 
    1742  
    1743          CALL file_add_var( td_file, tl_var ) 
    1744       ENDIF 
    1745  
    1746       IF( td_file%i_n1d == 0 )THEN 
    1747          ! create var 
    1748          tl_var=var_init('no1d') 
    1749          ! add dimension 
    1750          CALL var_add_dim(tl_var, td_file%t_dim(3)) 
    1751          ! add value 
    1752          ALLOCATE( il_tmp(1,1,td_file%t_dim(3)%i_len, 1) ) 
    1753          il_tmp(:,:,:,:)=-1 
    1754          CALL var_add_value(tl_var, il_tmp) 
    1755          DEALLOCATE( il_tmp ) 
    1756  
    1757          CALL file_add_var( td_file, tl_var )  
    1758       ENDIF 
    1759   
    1760       IF( td_file%i_n2d == 0 )THEN 
    1761          ! create var 
    1762          tl_var=var_init('no2d' ) 
    1763          ! add dimension 
    1764          CALL var_add_dim(tl_var, td_file%t_dim(1)) 
    1765          CALL var_add_dim(tl_var, td_file%t_dim(2)) 
    1766          ! add value 
    1767          ALLOCATE( il_tmp( td_file%t_dim(1)%i_len, & 
    1768          &                 td_file%t_dim(2)%i_len, & 
    1769          &                            1,             & 
    1770          &                            1            ) ) 
    1771          il_tmp(:,:,:,:)=-1 
    1772          CALL var_add_value(tl_var, il_tmp) 
    1773          DEALLOCATE( il_tmp ) 
    1774  
    1775          CALL file_add_var( td_file, tl_var )  
    1776       ENDIF 
    1777   
    1778       IF( td_file%i_n3d == 0 )THEN 
    1779          ! create var 
    1780          tl_var=var_init('no3d' ) 
    1781          ! add dimension 
    1782          CALL var_add_dim(tl_var, td_file%t_dim(1)) 
    1783          CALL var_add_dim(tl_var, td_file%t_dim(2)) 
    1784          CALL var_add_dim(tl_var, td_file%t_dim(3)) 
    1785          ! add value 
    1786          ALLOCATE( il_tmp( td_file%t_dim(1)%i_len, & 
    1787          &                 td_file%t_dim(2)%i_len, & 
    1788          &                 td_file%t_dim(3)%i_len, & 
    1789          &                            1            ) ) 
    1790          il_tmp(:,:,:,:)=-1 
    1791          CALL var_add_value(tl_var, il_tmp) 
    1792          DEALLOCATE( il_tmp ) 
    1793  
    1794          CALL file_add_var( td_file, tl_var )  
    1795       ENDIF 
    17961654 
    17971655      ! reform name and record 
    17981656      ALLOCATE( cl_name(td_file%i_nvar), dl_value(td_file%i_nvar) ) 
     1657 
    17991658      DO ji=1,td_file%i_nvar 
     1659 
     1660         ! change FillValue to 0. 
     1661         CALL var_chg_FillValue(td_file%t_var(ji),0._dp) 
     1662 
    18001663         cl_name(ji)  = TRIM(td_file%t_var(ji)%c_name) 
    18011664         dl_value(ji) = REAL(td_file%t_var(ji)%i_rec,dp) 
    1802       ENDDO 
    1803  
    1804       ! special case for 0d 
    1805       DO ji=1,td_file%i_n0d 
    1806          dl_value(ji)=td_file%t_var(ji)%d_value(1,1,1,1) 
     1665          
     1666         SELECT CASE (TRIM(td_file%t_var(ji)%c_name)) 
     1667            CASE('no0d','no1d','no2d','no3d') 
     1668            CASE DEFAULT 
     1669               DO jk=1,td_file%t_var(ji)%t_dim(3)%i_len 
     1670                  SELECT CASE (td_file%t_var(ji)%i_ndim) 
     1671                     CASE(0) 
     1672                        ! special case for 0d, value save in rec 
     1673                        dl_value(ji)=td_file%t_var(ji)%d_value(1,1,1,1) 
     1674                        il_rec = td_file%t_var(ji)%i_rec 
     1675                     CASE(1,2) 
     1676                        il_rec = td_file%t_var(ji)%i_rec 
     1677                     CASE(3) 
     1678                        il_rec = td_file%t_var(ji)%i_rec + jk -1 
     1679                  END SELECT  
     1680                  WRITE( td_file%i_id, IOSTAT=il_status, REC=il_rec ) & 
     1681                  &  td_file%t_var(ji)%d_value(:,:,jk,1) 
     1682                  CALL fct_err(il_status) 
     1683                  IF( il_status /= 0 )THEN 
     1684                     CALL logger_error("IOM RSTDIMG WRITE VAR: can not "//& 
     1685                     &  "write variable "//TRIM(td_file%t_var(ji)%c_name)//& 
     1686                     &  " in record "//TRIM(fct_str(il_rec))) 
     1687                  ENDIF 
     1688               ENDDO 
     1689            END SELECT 
     1690 
    18071691      ENDDO 
    18081692 
     
    18201704      il_start(4) = 1 + il_count(3) 
    18211705      il_count(4) = il_start(4) - 1 + td_file%i_n3d 
    1822   
    18231706 
    18241707      WRITE(td_file%i_id, IOSTAT=il_status, REC=td_file%i_rhd )& 
     
    18271710      &  cl_name(il_start(3):il_count(3)), dl_value(il_start(3):il_count(3)),& 
    18281711      &  cl_name(il_start(4):il_count(4)), dl_value(il_start(4):il_count(4)) 
    1829  
     1712      CALL fct_err(il_status) 
     1713      IF( il_status /= 0 )THEN 
     1714         CALL logger_error("IOM RSTDIMG WRITE VAR: can not "//& 
     1715         &  "write restart header in record "//TRIM(fct_str(td_file%i_rhd))) 
     1716      ENDIF 
     1717 
     1718      ! clean 
     1719      DEALLOCATE( cl_name, dl_value ) 
    18301720      DEALLOCATE( il_start, il_count ) 
    18311721 
    18321722   END SUBROUTINE iom_rstdimg__write_var 
    1833    !> @endcode    
    18341723END MODULE iom_rstdimg 
Note: See TracChangeset for help on using the changeset viewer.