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 6225 for branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/TOOLS/SIREN/src/iom_cdf.f90 – NEMO

Ignore:
Timestamp:
2016-01-08T10:35:19+01:00 (8 years ago)
Author:
jamesharle
Message:

Update MPP_BDY_UPDATE branch to be consistent with head of trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/TOOLS/SIREN/src/iom_cdf.f90

    r4213 r6225  
    66! 
    77! DESCRIPTION: 
    8 !> @brief 
    9 !> This module is a library to read/write Netcdf file. 
     8!> @brief NETCDF Input/Output manager :  Library to read Netcdf input files 
    109!> 
    1110!> @details 
    12 !> 
    1311!>    to open netcdf file:<br/> 
     12!> @code 
    1413!>    CALL iom_cdf_open(td_file) 
    15 !>       - td_file is file structure (see file.f90) 
     14!> @endcode 
     15!>       - td_file is file structure (see @ref file) 
    1616!> 
    1717!>    to write in netcdf file:<br/> 
     18!> @code 
    1819!>    CALL  iom_cdf_write_file(td_file) 
     20!> @endcode 
    1921!> 
    2022!>    to close netcdf file:<br/> 
     23!> @code 
    2124!>    CALL iom_cdf_close(tl_file) 
     25!> @endcode 
    2226!> 
    2327!>    to read one dimension in netcdf file:<br/> 
    24 !>    tl_dim = iom_cdf_read_dim(tl_file, id_dimid)<br/> 
    25 !>    or<br/> 
     28!> @code 
     29!>    tl_dim = iom_cdf_read_dim(tl_file, id_dimid) 
     30!> @endcode 
     31!>    or 
     32!> @code 
    2633!>    tl_dim = iom_cdf_read_dim(tl_file, cd_name) 
     34!> @endcode 
    2735!>       - id_dimid is dimension id<br/> 
    2836!>       - cd_name is dimension name 
    2937!> 
    30 !>    to read one global attribute in netcdf file:<br/> 
    31 !>    tl_att = iom_cdf_read_att(tl_file, id_varid, id_attid)<br/> 
    32 !>    or<br/> 
     38!>    to read one attribute in netcdf file:<br/> 
     39!> @code 
     40!>    tl_att = iom_cdf_read_att(tl_file, id_varid, id_attid) 
     41!> @endcode 
     42!>    or 
     43!> @code 
    3344!>    tl_att = iom_cdf_read_att(tl_file, id_varid, cd_name) 
     45!> @endcode 
    3446!>       - id_varid is variable id 
    3547!>       - id_attid is attribute id<br/> 
     
    3749!>     
    3850!>    to read one variable in netcdf file:<br/> 
    39 !>    tl_var = iom_cdf_read_var(td_file, id_varid, [id_start, id_count])<br/> 
    40 !>    or<br/> 
    41 !>    tl_var = iom_cdf_read_var(td_file, cd_name, [id_start, [id_count,]] [cd_stdname]) 
     51!> @code 
     52!>    tl_var = iom_cdf_read_var(td_file, id_varid, [id_start, id_count]) 
     53!> @endcode 
     54!>    or 
     55!> @code 
     56!>    tl_var = iom_cdf_read_var(td_file, cd_name, [id_start, [id_count,]]) 
     57!> @endcode 
    4258!>       - id_varid is variabale id 
    4359!>       - 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) 
     60!>       - id_start is a integer(4) 1D array of index from which the data  
     61!>          values will be read [optional] 
     62!>       - id_count is a integer(4) 1D array of the number of indices selected 
     63!>          along each dimension [optional] 
    4964!> 
    5065!> @author 
    5166!> J.Paul 
    5267! REVISION HISTORY: 
    53 !> @date Nov, 2013 - Initial Version 
    54 ! 
    55 !> @param MyModule_type : brief_description 
     68!> @date November, 2013 - Initial Version 
    5669! 
    5770!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    58 ! 
    59 !> @todo  
    60 !> - inform variable pni, pnj, pnij, area, iglo, jglo  
    61 !> - use var_init when read new variable 
    62 !> - use dim_init when read new dimension 
    63 !> - use att_init when read new attribute 
    64 !> - add read td_dom 
    65 !> @todo 
    66 !> - voir si il ne faut pas redefinir (__copy) variable si elle vient de mpp 
    67 !> exemple CALL  mpp_move_var( td_mpp, td_mpp%t_var ) 
    6871!---------------------------------------------------------------------- 
    6972MODULE iom_cdf 
     
    7275   USE kind                            ! F90 kind parameter 
    7376   USE fct                             ! basic useful function 
    74    USE logger                             ! log file manager 
     77   USE logger                          ! log file manager 
    7578   USE att                             ! attribute manage 
    7679   USE dim                             ! dimension manager 
    7780   USE var                             ! variable manager 
    7881   USE file                            ! file manager 
    79    USE dom                             ! domain manager 
    80 !   USE proc                            ! processor manager 
    8182   IMPLICIT NONE 
    82    PRIVATE 
    8383   ! NOTE_avoid_public_variables_if_possible 
    8484 
     
    9191   PUBLIC :: iom_cdf_fill_var    !< fill variable value in an opened netcdf file 
    9292   PUBLIC :: iom_cdf_write_file  !< write file structure contents in an opened netcdf file 
    93    ! PUBLIC :: iom_cdf_get_mpp     ! get sub domain decomposition in a netcdf file 
    94  
    95    PRIVATE :: iom_cdf__check           !< provides a simple interface to netcdf error message 
    96    PRIVATE :: iom_cdf__get_info        !< get global information in an opened netcdf file 
    97    PRIVATE :: iom_cdf__get_file_dim    !< read dimension on an opened netcdf file, and reorder it 
    98    PRIVATE :: iom_cdf__get_file_att    !< read global attribute on an opened netcdf file 
    99    PRIVATE :: iom_cdf__get_file_var    !< read information about variable on an opened netcdf file 
    100    PRIVATE :: iom_cdf__read_dim_id     !< read one dimension in an opened netcdf file, given dimension id. 
    101    PRIVATE :: iom_cdf__read_dim_name   !< read one dimension in an opened netcdf file, given dimension name. 
    102    PRIVATE :: iom_cdf__read_att_name   !< read variable or global attribute in an opened netcdf file, given attribute name.  
    103    PRIVATE :: iom_cdf__read_att_id     !< read variable or global attribute in an opened netcdf file, given attribute id. 
    104    PRIVATE :: iom_cdf__read_var_id     !< read variable value in an opened netcdf file, given variable id. 
    105    PRIVATE :: iom_cdf__read_var_name   !< read variable value in an opened netcdf file, given variable name or standard name. 
    106    PRIVATE :: iom_cdf__read_var_meta   !< read metadata of a variable in an opened netcdf file. 
    107    PRIVATE :: iom_cdf__read_var_dim    !< read variable dimension in an opened netcdf file. 
    108    PRIVATE :: iom_cdf__read_var_att    !< read variable attributes in an opened netcdf file. 
    109    PRIVATE :: iom_cdf__read_var_value  !< read variable value in an opened netcdf file. 
    110    PRIVATE :: iom_cdf__write_dim       !< write one dimension in an opened netcdf file in write mode. 
    111    PRIVATE :: iom_cdf__write_att       !< write a variable attribute in an opened netcdf file. 
    112    PRIVATE :: iom_cdf__write_var       !< write a variable in an opened netcdf file. 
    113    PRIVATE :: iom_cdf__write_var_def   !< define variable in an opened netcdf file. 
    114    PRIVATE :: iom_cdf__write_var_value !< put variable value in an opened netcdf file. 
    115    PRIVATE :: iom_cdf__fill_var_id     !< fill variable value in an opened netcdf file, given variable id 
    116    PRIVATE :: iom_cdf__fill_var_name   !< fill variable value in an opened netcdf file, given variable name 
    117    PRIVATE :: iom_cdf__fill_var_all    !< fill all variable value in an opened netcdf file 
    118    PRIVATE :: iom_cdf__del_var_dim     !< remove variable dimension from an opened netcdf file 
     93 
     94   PRIVATE :: iom_cdf__check           ! provides a simple interface to netcdf error message 
     95   PRIVATE :: iom_cdf__get_info        ! get global information in an opened netcdf file 
     96   PRIVATE :: iom_cdf__get_file_dim    ! read dimension on an opened netcdf file, and reorder it 
     97   PRIVATE :: iom_cdf__get_file_att    ! read global attribute on an opened netcdf file 
     98   PRIVATE :: iom_cdf__get_file_var    ! read information about variable on an opened netcdf file 
     99   PRIVATE :: iom_cdf__read_dim_id     ! read one dimension in an opened netcdf file, given dimension id. 
     100   PRIVATE :: iom_cdf__read_dim_name   ! read one dimension in an opened netcdf file, given dimension name. 
     101   PRIVATE :: iom_cdf__read_att_name   ! read variable or global attribute in an opened netcdf file, given attribute name.  
     102   PRIVATE :: iom_cdf__read_att_id     ! read variable or global attribute in an opened netcdf file, given attribute id. 
     103   PRIVATE :: iom_cdf__read_var_id     ! read variable value in an opened netcdf file, given variable id. 
     104   PRIVATE :: iom_cdf__read_var_name   ! read variable value in an opened netcdf file, given variable name or standard name. 
     105   PRIVATE :: iom_cdf__read_var_meta   ! read metadata of a variable in an opened netcdf file. 
     106   PRIVATE :: iom_cdf__read_var_dim    ! read variable dimension in an opened netcdf file. 
     107   PRIVATE :: iom_cdf__read_var_att    ! read variable attributes in an opened netcdf file. 
     108   PRIVATE :: iom_cdf__read_var_value  ! read variable value in an opened netcdf file. 
     109   PRIVATE :: iom_cdf__write_dim       ! write one dimension in an opened netcdf file in write mode. 
     110   PRIVATE :: iom_cdf__write_att       ! write a variable attribute in an opened netcdf file. 
     111   PRIVATE :: iom_cdf__write_var       ! write a variable in an opened netcdf file. 
     112   PRIVATE :: iom_cdf__write_var_def   ! define variable in an opened netcdf file. 
     113   PRIVATE :: iom_cdf__write_var_value ! put variable value in an opened netcdf file. 
     114   PRIVATE :: iom_cdf__fill_var_id     ! fill variable value in an opened netcdf file, given variable id 
     115   PRIVATE :: iom_cdf__fill_var_name   ! fill variable value in an opened netcdf file, given variable name 
     116   PRIVATE :: iom_cdf__fill_var_all    ! fill all variable value in an opened netcdf file 
     117   PRIVATE :: iom_cdf__del_coord_var   ! remove coordinate variable from an opened netcdf file 
    119118 
    120119   INTERFACE iom_cdf_read_var 
     
    145144   !> 
    146145   !> @author J.Paul 
    147    !> - Nov, 2013- Initial Version 
    148    ! 
    149    !> @param[in] id_status : error status 
    150    !------------------------------------------------------------------- 
    151    !> @code 
    152    SUBROUTINE iom_cdf__check(id_status) 
    153       IMPLICIT NONE 
    154       ! Argument       
    155       INTEGER(i4), INTENT(IN) :: id_status 
    156       !---------------------------------------------------------------- 
     146   !> @date November, 2013 - Initial Version 
     147   !> @date May, 2015 - add optional message to netcdf error message 
     148   !> 
     149   !> @param[in] id_status error status 
     150   !> @param[in] cd_msg    message 
     151   !------------------------------------------------------------------- 
     152   SUBROUTINE iom_cdf__check(id_status, cd_msg) 
     153      IMPLICIT NONE 
     154      ! Argument       
     155      INTEGER(i4)     , INTENT(IN)           :: id_status 
     156      CHARACTER(LEN=*), INTENT(IN), OPTIONAL :: cd_msg 
     157      ! local variable 
     158      CHARACTER(LEN=lc) :: cl_msg 
     159      !---------------------------------------------------------------- 
     160 
     161      cl_msg="" 
     162      IF( PRESENT(cd_msg) ) cl_msg=cd_msg 
    157163 
    158164      IF( id_status /= NF90_NOERR )THEN 
    159          CALL logger_error(TRIM(NF90_STRERROR(id_status))) 
     165         CALL logger_error(TRIM(cl_msg)//TRIM(NF90_STRERROR(id_status))) 
    160166      ENDIF 
    161167 
    162168   END SUBROUTINE iom_cdf__check 
    163    !> @endcode 
    164    !------------------------------------------------------------------- 
    165    !> @brief This subroutine open a netcdf file in read or write mode<br/> 
     169   !------------------------------------------------------------------- 
     170   !> @brief This subroutine open a netcdf file in read or write mode. 
     171   !> @details 
    166172   !> if try to open a file in write mode that did not exist, create it.<br/> 
    167    !> if file already exist, get information about: 
     173   !> if file already exist, get information about0:<br/> 
    168174   !> - the number of variables 
    169175   !> - the number of dimensions 
     
    171177   !> - the ID of the unlimited dimension 
    172178   !> - the file format 
    173    !> and finally read dimensions. 
     179   !> Finally it read dimensions, and 'longitude' variable to compute East-West 
     180   !> overlap. 
    174181   !> 
    175182   !> @author J.Paul 
    176    !> - Nov, 2013- Initial Version 
    177    ! 
    178    !> @param[inout] td_file : file structure 
    179    !------------------------------------------------------------------- 
    180    !> @code 
     183   !> @date November, 2013 - Initial Version 
     184   ! 
     185   !> @param[inout] td_file   file structure 
     186   !------------------------------------------------------------------- 
    181187   SUBROUTINE iom_cdf_open(td_file) 
    182188      IMPLICIT NONE 
     
    189195 
    190196      INTEGER(i4) :: il_status 
    191  
    192       TYPE(TVAR)  :: tl_lon 
    193       ! loop indices 
    194       INTEGER(i4) :: ji 
    195197      !---------------------------------------------------------------- 
    196198 
     
    202204         IF( .NOT. td_file%l_wrt )THEN 
    203205 
    204             CALL logger_fatal( " OPEN: can not open file "//& 
     206            CALL logger_fatal( " IOM CDF OPEN: can not open file "//& 
    205207            &               TRIM(td_file%c_name) ) 
    206             td_file%i_id=-1 
    207           
     208  
    208209         ELSE 
    209210 
    210             CALL logger_info( " CREATE: file "//TRIM(td_file%c_name) ) 
    211  
    212             il_status = NF90_CREATE( TRIM(td_file%c_name),& 
    213             &                        NF90_WRITE,               & 
    214             &                        td_file%i_id) 
    215             CALL iom_cdf__check(il_status) 
     211            CALL logger_info( " IOM CDF CREATE: file "//TRIM(td_file%c_name) ) 
     212 
     213            il_status = NF90_CREATE(TRIM(td_file%c_name),& 
     214            &                       cmode=NF90_64BIT_OFFSET,& 
     215            &                       ncid=td_file%i_id) 
     216         !NF90_WRITE,               & 
     217            CALL iom_cdf__check(il_status," IOM CDF CREATE: ") 
    216218 
    217219            td_file%l_def=.TRUE. 
     
    220222 
    221223      ELSE 
    222  
    223224         IF( td_file%i_id /= 0 )THEN 
    224225 
    225             CALL logger_error( " OPEN: file "//& 
     226            CALL logger_error( " IOM CDF OPEN: file "//& 
    226227            &               TRIM(td_file%c_name)//" already opened") 
    227228 
    228229         ELSE 
    229  
     230  
    230231            IF( .NOT. td_file%l_wrt )THEN 
    231232 
    232                CALL logger_info( " OPEN: file "//& 
     233               CALL logger_info( " IOM CDF OPEN: file "//& 
    233234               &              TRIM(td_file%c_name)//" in read only mode" ) 
    234235 
    235236               il_status = NF90_OPEN( TRIM(td_file%c_name), & 
    236                &                      NF90_NOWRITE,              & 
     237               &                      NF90_NOWRITE,         & 
    237238               &                      td_file%i_id) 
    238                CALL iom_cdf__check(il_status) 
    239  
    240                CALL logger_debug("OPEN "//TRIM(td_file%c_name)//" "//TRIM(fct_str(td_file%i_id))) 
     239               CALL iom_cdf__check(il_status," IOM CDF OPEN: ") 
     240 
     241               CALL logger_trace("IOM CDF OPEN "//TRIM(td_file%c_name)//" "//& 
     242                  &  TRIM(fct_str(td_file%i_id))) 
    241243            ELSE 
    242244 
    243                CALL logger_info( " OPEN: file "//& 
     245               CALL logger_info( "IOM CDF OPEN: file "//& 
    244246               &              TRIM(td_file%c_name)//" in write mode" ) 
    245247 
     
    247249               &                      NF90_WRITE,           & 
    248250               &                      td_file%i_id) 
    249                CALL iom_cdf__check(il_status) 
     251               CALL iom_cdf__check(il_status,"IOM CDF OPEN: ") 
    250252 
    251253            ENDIF 
     
    263265            CALL iom_cdf__get_file_var(td_file) 
    264266 
    265             ! get ew overlap 
    266             tl_lon=iom_cdf_read_var(td_file,'longitude') 
    267             td_file%i_ew=dom_get_ew_overlap(tl_lon) 
    268             CALL logger_debug(" IOM OPEN EW "//TRIM(fct_str(td_file%i_ew)) ) 
    269             WHERE( td_file%t_var(:)%t_dim(1)%l_use ) 
    270                td_file%t_var(:)%i_ew=td_file%i_ew 
    271             END WHERE 
    272             CALL var_clean(tl_lon) 
    273  
    274             DO ji=1,td_file%i_nvar 
    275                CALL logger_debug(TRIM(td_file%t_var(ji)%c_name)//": "//TRIM(fct_str(td_file%t_var(ji)%i_ew)) ) 
    276             ENDDO 
    277   
    278267            ! remove dimension variable from list of variable 
    279             CALL iom_cdf__del_var_dim(td_file) 
     268            CALL iom_cdf__del_coord_var(td_file) 
    280269 
    281270         ENDIF 
     
    284273 
    285274   END SUBROUTINE iom_cdf_open 
    286    !> @endcode 
    287    !------------------------------------------------------------------- 
    288    !> @brief This subroutine close netcdf file 
     275   !------------------------------------------------------------------- 
     276   !> @brief This subroutine close netcdf file. 
    289277   !> 
    290278   !> @author J.Paul 
    291    !> - Nov, 2013- Initial Version 
    292    ! 
    293    !> @param[inout] td_file : file structure 
    294    !------------------------------------------------------------------- 
    295    !> @code 
     279   !> @date November, 2013 - Initial Version 
     280   ! 
     281   !> @param[inout] td_file   file structure 
     282   !------------------------------------------------------------------- 
    296283   SUBROUTINE iom_cdf_close(td_file) 
    297284      IMPLICIT NONE 
     
    307294 
    308295         CALL logger_error( & 
    309          &  " CLOSE: no id associated to file "//TRIM(td_file%c_name)) 
     296         &  " IOM CDF CLOSE: no id associated to file "//TRIM(td_file%c_name)) 
    310297 
    311298      ELSE 
    312299         CALL logger_info( & 
    313          &  " CLOSE: file "//TRIM(td_file%c_name)) 
     300         &  " IOM CDF CLOSE: file "//TRIM(td_file%c_name)) 
    314301 
    315302         il_status = NF90_CLOSE(td_file%i_id) 
    316          CALL iom_cdf__check(il_status) 
     303         CALL iom_cdf__check(il_status,"IOM CDF CLOSE: ") 
    317304 
    318305         td_file%i_id = 0 
     
    321308 
    322309   END SUBROUTINE iom_cdf_close 
    323    !> @endcode 
    324310   !------------------------------------------------------------------- 
    325311   !> @brief This subroutine get global information in an opened netcdf  
    326    !> file.<br/> 
     312   !> file. 
    327313   !> @details 
    328314   !> It gets the number of variables, the number of dimensions,  
     
    331317   !> 
    332318   !> @author J.Paul 
    333    !> - Nov, 2013- Initial Version 
    334    ! 
    335    !> @param[inout] td_file : file structure 
    336    !> @return file structure completed  
    337    !------------------------------------------------------------------- 
    338    !> @code 
     319   !> @date November, 2013 - Initial Version 
     320   ! 
     321   !> @param[inout] td_file   file structure 
     322   !------------------------------------------------------------------- 
    339323   SUBROUTINE iom_cdf__get_info(td_file) 
    340324      IMPLICIT NONE 
     
    348332 
    349333      CALL logger_trace( & 
    350       &  " GET INFO: about netcdf file "//TRIM(td_file%c_name)) 
     334      &  " IOM CDF GET INFO: about netcdf file "//TRIM(td_file%c_name)) 
    351335 
    352336      il_status=NF90_INQUIRE(td_file%i_id, td_file%i_ndim, & 
    353337      &     td_file%i_nvar, td_file%i_natt, td_file%i_uldid, il_fmt) 
    354       CALL iom_cdf__check(il_status) 
     338      CALL iom_cdf__check(il_status,"IOM CDF GET INFO: ") 
    355339 
    356340      SELECT CASE(il_fmt) 
     
    365349 
    366350   END SUBROUTINE iom_cdf__get_info 
    367    !> @endcode 
    368351   !------------------------------------------------------------------- 
    369352   !> @brief This subroutine read dimension on an opened netcdf file, and 
    370    !> reorder dimension to ('x', 'y', 'z', 't').<br/> 
     353   !> reorder dimension to ('x', 'y', 'z', 't'). 
    371354   !> The dimension structure inside file structure is then completed. 
    372355   ! 
    373356   !> @author J.Paul 
    374    !> - Nov, 2013- Initial Version 
    375    ! 
    376    !> @param[inout] td_file : file structure 
    377    !> @return file structure completed  
    378    !------------------------------------------------------------------- 
    379    !> @code 
     357   !> @date November, 2013 - Initial Version 
     358   ! 
     359   !> @param[inout] td_file   file structure 
     360   !------------------------------------------------------------------- 
    380361   SUBROUTINE iom_cdf__get_file_dim(td_file) 
    381362      IMPLICIT NONE 
     
    401382         IF( td_file%i_uldid == -1 )THEN 
    402383            CALL logger_warn( & 
    403             &  " GET FILE DIM: there is no unlimited dimension in file "//& 
     384            &  " IOM CDF GET FILE DIM: there is no unlimited dimension in file "//& 
    404385            &  TRIM(td_file%c_name)) 
    405386         ELSE 
     
    410391 
    411392         CALL logger_warn( & 
    412          &  " GET FILE DIM: there is no dimension in file "//& 
     393         &  " IOM CDF GET FILE DIM: there is no dimension in file "//& 
    413394         &  TRIM(td_file%c_name)) 
    414395 
     
    419400 
    420401   END SUBROUTINE iom_cdf__get_file_dim 
    421    !> @endcode 
    422402   !------------------------------------------------------------------- 
    423403   !> @brief This subroutine read global attribute on an opened netcdf  
    424    !> file.<br/> 
     404   !> file. 
    425405   !> The attribute structure inside file structure is then completed. 
    426406   ! 
    427407   !> @author J.Paul 
    428    !> - Nov, 2013- Initial Version 
    429    ! 
    430    !> @param[inout] td_file : file structure 
    431    !> @return file structure completed  
    432    !------------------------------------------------------------------- 
    433    !> @code 
     408   !> @date November, 2013 - Initial Version 
     409   !> @date September, 2014 
     410   !> - use attribute periodicity read from the file if present. 
     411   ! 
     412   !> @param[inout] td_file   file structure 
     413   !------------------------------------------------------------------- 
    434414   SUBROUTINE iom_cdf__get_file_att(td_file) 
    435415      IMPLICIT NONE 
     
    437417      TYPE(TFILE), INTENT(INOUT) :: td_file 
    438418 
     419      ! local variable 
    439420      ! loop indices 
    440421      INTEGER(i4) :: ji 
     
    443424      IF( td_file%i_natt > 0 )THEN 
    444425         IF(ASSOCIATED(td_file%t_att))THEN 
     426            CALL att_clean(td_file%t_att(:)) 
    445427            DEALLOCATE(td_file%t_att) 
    446428         ENDIF 
     
    451433            td_file%t_att(ji)=iom_cdf_read_att( td_file, NF90_GLOBAL, ji) 
    452434             
    453             SELECT CASE(TRIM(td_file%t_att(ji)%c_name)) 
    454                CASE('periodicity') 
    455                   td_file%i_perio=INT(td_file%t_att(ji)%d_value(1),i4) 
    456                CASE('pivot_point') 
    457                   td_file%i_pivot=INT(td_file%t_att(ji)%d_value(1),i4) 
    458                CASE('ew_overlap') 
    459                   td_file%i_ew=INT(td_file%t_att(ji)%d_value(1),i4) 
    460             END SELECT 
    461  
    462435         ENDDO 
    463436 
    464437      ELSE 
    465438         CALL logger_debug( & 
    466          &  " GET FILE ATT: there is no global attribute in file "//& 
     439         &  " IOM CDF GET FILE ATT: there is no global attribute in file "//& 
    467440         &  TRIM(td_file%c_name)) 
    468441      ENDIF 
    469442 
    470443   END SUBROUTINE iom_cdf__get_file_att 
    471    !> @endcode    
    472444   !------------------------------------------------------------------- 
    473445   !> @brief This subroutine read information about variable of an  
    474    !> opened netcdf file.<br/> 
     446   !> opened netcdf file. 
    475447   !> The variable structure inside file structure is then completed. 
    476448   !> @note variable value are not read ! 
    477449   ! 
    478450   !> @author J.Paul 
    479    !> - Nov, 2013- Initial Version 
    480    ! 
    481    !> @param[inout] td_file : file structure 
    482    !> @return file structure completed  
    483    !------------------------------------------------------------------- 
    484    !> @code 
     451   !> @date November, 2013 - Initial Version 
     452   ! 
     453   !> @param[inout] td_file   file structure 
     454   !------------------------------------------------------------------- 
    485455   SUBROUTINE iom_cdf__get_file_var(td_file) 
    486456      IMPLICIT NONE 
     
    497467      IF( td_file%i_nvar > 0 )THEN 
    498468         IF(ASSOCIATED(td_file%t_var))THEN 
     469            CALL var_clean(td_file%t_var(:)) 
    499470            DEALLOCATE(td_file%t_var) 
    500471         ENDIF 
     
    504475            ! read dimension information 
    505476            td_file%t_var(ji)=iom_cdf__read_var_meta( td_file, ji) 
    506  
    507477            SELECT CASE(td_file%t_var(ji)%i_ndim) 
    508478               CASE(0) 
     
    520490 
    521491            ! look for depth id 
    522             IF( INDEX(TRIM(td_file%t_var(ji)%c_name),'depth') /= 0 )THEN 
     492            IF( INDEX(TRIM(fct_lower(td_file%t_var(ji)%c_name)),'depth')/=0 )THEN 
    523493               IF( td_file%i_depthid == 0 )THEN 
    524494                  td_file%i_depthid=ji 
    525495               ELSE 
    526                   CALL logger_error("IOM OPEN: find more than one "//& 
    527                   &                 "depth variable in file "//& 
    528                   &                 TRIM(td_file%c_name) ) 
     496                  IF( td_file%i_depthid /= ji )THEN 
     497                     CALL logger_error("IOM CDF GET FILE VAR: find more"//& 
     498                        &  " than one depth variable in file "//& 
     499                        &  TRIM(td_file%c_name) ) 
     500                  ENDIF 
    529501               ENDIF 
    530502            ENDIF 
    531503 
    532504            ! look for time id 
    533             IF( INDEX(TRIM(td_file%t_var(ji)%c_name),'time') /= 0 )THEN 
     505            IF( INDEX(TRIM(fct_lower(td_file%t_var(ji)%c_name)),'time')/=0 )THEN 
    534506               IF( td_file%i_timeid == 0 )THEN 
    535507                  td_file%i_timeid=ji 
     
    542514                     td_file%i_timeid=ji 
    543515                  !ELSE 
    544                   !   print *,'error' 
    545                   !   CALL logger_error("IOM OPEN: find more than one "//& 
    546                   !   &                 "time variable in file "//& 
     516                  !   CALL logger_error("IOM CDF GET FILE VAR: find more "//& 
     517                  !   &                 "than one time variable in file "//& 
    547518                  !   &                 TRIM(td_file%c_name) ) 
    548519                  ENDIF 
     
    554525      ELSE 
    555526         CALL logger_debug( & 
    556          &  " GET FILE VAR: there is no variable in file "//& 
     527         &  " IOM CDF GET FILE VAR: there is no variable in file "//& 
    557528         &  TRIM(td_file%c_name)) 
    558529      ENDIF 
    559530 
    560531   END SUBROUTINE iom_cdf__get_file_var 
    561    !> @endcode 
    562    !------------------------------------------------------------------- 
    563    !> @brief This subroutine delete variable dimension from an  
    564    !> opened netcdf file.<br/> 
    565    ! 
    566    !> @author J.Paul 
    567    !> - 2013- Initial Version 
    568    ! 
    569    !> @param[inout] td_file : file structure 
    570    !------------------------------------------------------------------- 
    571    !> @code 
    572    SUBROUTINE iom_cdf__del_var_dim(td_file) 
     532   !------------------------------------------------------------------- 
     533   !> @brief This subroutine delete coordinate variable from an  
     534   !> opened netcdf file if present. 
     535   ! 
     536   !> @author J.Paul 
     537   !> @date November, 2013 - Initial Version 
     538   ! 
     539   !> @param[inout] td_file   file structure 
     540   !------------------------------------------------------------------- 
     541   SUBROUTINE iom_cdf__del_coord_var(td_file) 
    573542      IMPLICIT NONE 
    574543      ! Argument       
     
    598567      ELSE 
    599568         CALL logger_debug( & 
    600          &  " DEL VAR DIM: there is no variable in file "//& 
     569         &  " IOM CDF DEL VAR DIM: there is no variable in file "//& 
    601570         &  TRIM(td_file%c_name)) 
    602571      ENDIF 
    603    END SUBROUTINE iom_cdf__del_var_dim 
    604    !> @endcode 
    605 !   !------------------------------------------------------------------- 
    606 !   !> @brief This subroutine get variable time from an  
    607 !   !> opened netcdf file.<br/> 
    608 !   ! 
    609 !   !> @author J.Paul 
    610 !   !> - 2013- Initial Version 
    611 !   ! 
    612 !   !> @param[inout] td_file : file structure 
    613 !   !------------------------------------------------------------------- 
    614 !   !> @code 
    615 !   SUBROUTINE iom_cdf__get_var_time(td_file) 
    616 !      IMPLICIT NONE 
    617 !      ! Argument       
    618 !      TYPE(TFILE), INTENT(INOUT) :: td_file 
    619 ! 
    620 !      ! local variable 
    621 !      CHARACTER(LEN=lc) :: cl_name 
    622 ! 
    623 !      ! loop indices 
    624 !      INTEGER(i4) :: ji 
    625 !      !---------------------------------------------------------------- 
    626 !      IF( td_file%i_nvar > 0 )THEN 
    627 !         DO ji=1,td_file%i_nvar 
    628 !            cl_name=TRIM(td_file%t_var(ji)%c_name) 
    629 !            IF( INDEX(cl_name,'time') /= 0 )THEN 
    630 !               ! read time variable 
    631 !               td_file%t_time=iom_cdf_read_var(td_file,ji) 
    632 !               ! remove time variable from variable list 
    633 !               CALL file_del_ver(td_file,TRIM(cl_name)) 
    634 !               EXIT 
    635 !            ENDIF 
    636 !         ENDDO 
    637 !      ELSE 
    638 !         CALL logger_debug( & 
    639 !         &  " GET VAR TIME: there is no variable in file "//& 
    640 !         &  TRIM(td_file%c_name)) 
    641 !      ENDIF 
    642 !   END SUBROUTINE iom_cdf__get_var_time 
    643 !   !> @endcode 
    644 !   !------------------------------------------------------------------- 
    645 !   !> @brief This subroutine get variable depth from an  
    646 !   !> opened netcdf file.<br/> 
    647 !   ! 
    648 !   !> @author J.Paul 
    649 !   !> - 2013- Initial Version 
    650 !   ! 
    651 !   !> @param[inout] td_file : file structure 
    652 !   !------------------------------------------------------------------- 
    653 !   !> @code 
    654 !   SUBROUTINE iom_cdf__get_var_depth(td_file) 
    655 !      IMPLICIT NONE 
    656 !      ! Argument       
    657 !      TYPE(TFILE), INTENT(INOUT) :: td_file 
    658 ! 
    659 !      ! local variable 
    660 !      CHARACTER(LEN=lc) :: cl_name 
    661 ! 
    662 !      ! loop indices 
    663 !      INTEGER(i4) :: ji 
    664 !      !---------------------------------------------------------------- 
    665 !      IF( td_file%i_nvar > 0 )THEN 
    666 !         DO ji=1,td_file%i_nvar 
    667 !            cl_name=TRIM(td_file%t_var(ji)%c_name) 
    668 !            IF( INDEX(cl_name,'depth') /= 0 )THEN 
    669 !               ! read depth variable 
    670 !               td_file%t_depth=iom_cdf_read_var(td_file,ji) 
    671 !               ! remove depth variable from variable list 
    672 !               CALL file_del_ver(td_file,TRIM(cl_name)) 
    673 !               EXIT 
    674 !            ENDIF 
    675 !         ENDDO 
    676 !      ELSE 
    677 !         CALL logger_debug( & 
    678 !         &  " GET VAR TIME: there is no variable in file "//& 
    679 !         &  TRIM(td_file%c_name)) 
    680 !      ENDIF 
    681 !   END SUBROUTINE iom_cdf__get_var_depth 
    682 !   !> @endcode 
     572   END SUBROUTINE iom_cdf__del_coord_var 
    683573   !------------------------------------------------------------------- 
    684574   !> @brief This function read one dimension in an opened netcdf file,  
     
    686576   ! 
    687577   !> @author J.Paul 
    688    !> - Nov, 2013- Initial Version 
    689    ! 
    690    !> @param[in] td_file : file structure 
    691    !> @param[in] id_dimid : dimension id 
     578   !> @date November, 2013 - Initial Version 
     579   !> @date February, 2015 - create unused dimension, when reading dimension 
     580   !> of length less or equal to zero 
     581   ! 
     582   !> @param[in] td_file   file structure 
     583   !> @param[in] id_dimid  dimension id 
    692584   !> @return  dimension structure  
    693585   !------------------------------------------------------------------- 
    694    !> @code 
    695586   TYPE(TDIM) FUNCTION iom_cdf__read_dim_id(td_file, id_dimid) 
    696587      IMPLICIT NONE 
     
    703594      INTEGER(i4)       :: il_len 
    704595      CHARACTER(LEN=lc) :: cl_name 
     596      LOGICAL           :: ll_use 
    705597      !---------------------------------------------------------------- 
    706598 
     
    709601 
    710602         CALL logger_error( & 
    711          &  " READ DIM: no id associated to file "//TRIM(td_file%c_name)) 
     603         &  " IOM CDF READ DIM: no id associated to file "//TRIM(td_file%c_name)) 
    712604 
    713605      ELSE       
     
    715607         iom_cdf__read_dim_id%i_id=id_dimid 
    716608 
    717          CALL logger_debug( & 
    718          &  " READ DIM: dimension "//TRIM(fct_str(id_dimid))//& 
     609         CALL logger_trace( & 
     610         &  " IOM CDF READ DIM: dimension "//TRIM(fct_str(id_dimid))//& 
    719611         &  " in file "//TRIM(td_file%c_name)) 
    720612 
    721613         il_status=NF90_INQUIRE_DIMENSION(td_file%i_id, id_dimid, & 
    722614         &                                cl_name, il_len ) 
    723          CALL iom_cdf__check(il_status) 
    724  
    725          iom_cdf__read_dim_id=dim_init(cl_name, il_len) 
     615         CALL iom_cdf__check(il_status,"IOM CDF READ DIM: ") 
     616 
     617         ll_use=.TRUE. 
     618         IF( il_len <= 0 )THEN 
     619            CALL logger_warn( & 
     620         &  " IOM CDF READ DIM: dimension "//TRIM(fct_str(id_dimid))//& 
     621         &  " in file "//TRIM(td_file%c_name)//" is less or equel to zero") 
     622            il_len=1 
     623            ll_use=.FALSE. 
     624         ENDIF 
     625         iom_cdf__read_dim_id=dim_init(cl_name, il_len, ld_use=ll_use) 
    726626 
    727627      ENDIF 
    728628 
    729629   END FUNCTION iom_cdf__read_dim_id 
    730    !> @endcode 
    731630   !------------------------------------------------------------------- 
    732631   !> @brief This function read one dimension in an opened netcdf file,  
     
    734633   ! 
    735634   !> @author J.Paul 
    736    !> - Nov, 2013- Initial Version 
    737    ! 
    738    !> @param[in] td_file : file structure 
    739    !> @param[in] cd_name : dimension name 
     635   !> @date November, 2013 - Initial Version 
     636   ! 
     637   !> @param[in] td_file   file structure 
     638   !> @param[in] cd_name   dimension name 
    740639   !> @return  dimension structure  
    741640   !------------------------------------------------------------------- 
    742    !> @code 
    743641   TYPE(TDIM) FUNCTION iom_cdf__read_dim_name(td_file, cd_name) 
    744642      IMPLICIT NONE 
     
    756654 
    757655         CALL logger_error( & 
    758          &  " READ DIM: no id associated to file "//TRIM(td_file%c_name)) 
     656         &  " IOM CDF READ DIM: no id associated to file "//& 
     657         &  TRIM(td_file%c_name)) 
    759658 
    760659      ELSE       
     
    762661         il_status=NF90_INQ_DIMID( td_file%i_id, TRIM(ADJUSTL(cd_name)), & 
    763662         &                         il_dimid) 
    764          CALL iom_cdf__check(il_status) 
     663         CALL iom_cdf__check(il_status,"IOM CDF READ DIM: ") 
    765664 
    766665         iom_cdf__read_dim_name=iom_cdf_read_dim(td_file, il_dimid) 
     
    769668 
    770669   END FUNCTION iom_cdf__read_dim_name 
    771    !> @endcode    
    772670   !------------------------------------------------------------------- 
    773671   !> @brief This function read variable or global attribute in an opened  
     
    775673   ! 
    776674   !> @author J.Paul 
    777    !> - Nov, 2013- Initial Version 
    778    ! 
    779    !> @param[in] td_file : file structure 
    780    !> @param[in] id_varid : variable id. use NF90_GLOBAL to read global 
     675   !> @date November, 2013 - Initial Version 
     676   ! 
     677   !> @param[in] td_file   file structure 
     678   !> @param[in] id_varid variable id. use NF90_GLOBAL to read global 
    781679   !> attribute in a file 
    782    !> @param[in] cd_name : attribute name 
     680   !> @param[in] cd_name   attribute name 
    783681   !> @return  attribute structure  
    784682   !------------------------------------------------------------------- 
    785    !> @code 
    786683   TYPE(TATT) FUNCTION iom_cdf__read_att_name(td_file, id_varid, cd_name) 
    787684      IMPLICIT NONE 
     
    800697 
    801698      CHARACTER(LEN=lc) :: cl_value 
     699       
    802700      INTEGER(i1), DIMENSION(:), ALLOCATABLE :: bl_value 
    803701      INTEGER(i2), DIMENSION(:), ALLOCATABLE :: sl_value 
     
    810708 
    811709         CALL logger_error( & 
    812          &  " READ ATT: no id associated to file "//TRIM(td_file%c_name)) 
     710         &  " IOM CDF READ ATT: no id associated to file "//TRIM(td_file%c_name)) 
    813711 
    814712      ELSE       
     
    819717         IF( id_varid == NF90_GLOBAL )THEN 
    820718 
    821             CALL logger_debug( & 
    822             &  " READ ATT: inquire global attribute "//& 
     719            CALL logger_trace( & 
     720            &  " IOM CDF READ ATT: inquire global attribute "//& 
    823721            &  " in file "//TRIM(td_file%c_name)) 
    824722 
    825723         ELSE 
    826724 
    827             CALL logger_debug( & 
    828             &  " READ ATT: inquire attribute "//& 
     725            CALL logger_trace( & 
     726            &  " IOM CDF READ ATT: inquire attribute "//& 
    829727            &  " of variable "//TRIM(fct_str(id_varid))//& 
    830728            &  " in file "//TRIM(td_file%c_name)) 
     
    837735         &                                il_len, & 
    838736         &                                il_attid ) 
    839          CALL iom_cdf__check(il_status) 
     737         CALL iom_cdf__check(il_status,"IOM CDF READ ATT: ") 
    840738 
    841739         !! get attribute value 
    842          CALL logger_debug( " READ ATT: get attribute "//TRIM(cl_name)//& 
    843          &               " in file "//TRIM(td_file%c_name)) 
     740         CALL logger_debug( " IOM CDF READ ATT: get attribute "//& 
     741            &            TRIM(cl_name)//" in file "//TRIM(td_file%c_name)) 
    844742 
    845743         SELECT CASE( il_type ) 
     
    851749 
    852750                  CALL logger_error( & 
    853                   &  " READ ATT: not enough space to put attribute "//& 
    854                   &  TRIM(cl_name) ) 
     751                  &  " IOM CDF READ ATT: not enough space to put "//& 
     752                  &  "attribute "//TRIM(cl_name) ) 
    855753 
    856754               ELSE 
     
    860758                  &                      cl_name, & 
    861759                  &                      cl_value ) 
    862                   CALL iom_cdf__check(il_status) 
     760                  CALL iom_cdf__check(il_status,"IOM CDF READ ATT: ") 
    863761 
    864762                  iom_cdf__read_att_name=att_init(cl_name, cl_value) 
     
    872770               IF(il_status /= 0 )THEN 
    873771 
    874                   CALL logger_error( & 
    875                   &  " READ ATT: not enough space to put attribute "//& 
    876                   &  TRIM(cl_name) ) 
     772                  CALL logger_error( "IOM CDF READ ATT: "//& 
     773                  &  "not enough space to put attribute "//TRIM(cl_name) ) 
    877774 
    878775               ELSE 
     
    882779                  &                      cl_name, & 
    883780                  &                      bl_value(:)) 
    884                   CALL iom_cdf__check(il_status)    
     781                  CALL iom_cdf__check(il_status,"IOM CDF READ ATT: ")    
    885782 
    886783                  iom_cdf__read_att_name=att_init(cl_name, bl_value(:)) 
     
    897794 
    898795                  CALL logger_error( & 
    899                   &  " READ ATT: not enough space to put attribute "//& 
    900                   &  TRIM(cl_name) ) 
     796                  &  " IOM CDF READ ATT: not enough space to put "//& 
     797                  &  "attribute "//TRIM(cl_name) ) 
    901798 
    902799               ELSE 
     
    906803                  &                      cl_name, & 
    907804                  &                      sl_value(:)) 
    908                   CALL iom_cdf__check(il_status)    
     805                  CALL iom_cdf__check(il_status,"IOM CDF READ ATT: ")    
    909806 
    910807                  iom_cdf__read_att_name=att_init(cl_name, sl_value(:)) 
     
    921818 
    922819                  CALL logger_error( & 
    923                   &  " READ ATT: not enough space to put attribute "//& 
    924                   &  TRIM(cl_name) ) 
     820                  &  " IOM CDF READ ATT: not enough space to put "//& 
     821                  &  "attribute "//TRIM(cl_name) ) 
    925822 
    926823               ELSE 
     
    930827                  &                      cl_name, & 
    931828                  &                      il_value(:)) 
    932                   CALL iom_cdf__check(il_status)    
     829                  CALL iom_cdf__check(il_status,"IOM CDF READ ATT: ")    
    933830 
    934831                  iom_cdf__read_att_name=att_init(cl_name, il_value(:)) 
     
    944841 
    945842                  CALL logger_error( & 
    946                   &  " READ ATT: not enough space to put attribute "//& 
    947                   &  TRIM(cl_name) ) 
     843                  &  " IOM CDF READ ATT: not enough space to put "//& 
     844                  &  "attribute "//TRIM(cl_name) ) 
    948845 
    949846               ELSE 
     
    953850                  &                      cl_name, & 
    954851                  &                      fl_value(:)) 
    955                   CALL iom_cdf__check(il_status)    
     852                  CALL iom_cdf__check(il_status,"IOM CDF READ ATT: ")    
    956853 
    957854                  iom_cdf__read_att_name=att_init(cl_name, fl_value(:)) 
     
    968865 
    969866                  CALL logger_error( & 
    970                   &  " READ ATT: not enough space to put attribute "//& 
    971                   &  TRIM(cl_name) ) 
     867                  &  " IOM CDF READ ATT: not enough space to put "//& 
     868                  &  "attribute "//TRIM(cl_name) ) 
    972869 
    973870               ELSE 
     
    977874                  &                      cl_name, & 
    978875                  &                      dl_value(:)) 
    979                   CALL iom_cdf__check(il_status)    
     876                  CALL iom_cdf__check(il_status,"IOM CDF READ ATT: ")    
    980877 
    981878                  iom_cdf__read_att_name=att_init(cl_name, dl_value(:)) 
     
    992889 
    993890   END FUNCTION iom_cdf__read_att_name 
    994    !> @endcode    
    995891   !------------------------------------------------------------------- 
    996892   !> @brief This function read variable or global attribute in an opened  
     
    998894   ! 
    999895   !> @author J.Paul 
    1000    !> - Nov, 2013- Initial Version 
    1001    ! 
    1002    !> @param[in] td_file : file structure 
    1003    !> @param[in] id_varid : variable id. use NF90_GLOBAL to read global  
     896   !> @date November, 2013 - Initial Version 
     897   ! 
     898   !> @param[in] td_file   file structure 
     899   !> @param[in] id_varid variable id. use NF90_GLOBAL to read global  
    1004900   !> attribute in a file 
    1005    !> @param[in] id_attid : attribute id 
     901   !> @param[in] id_attid attribute id 
    1006902   !> @return  attribute structure  
    1007903   !------------------------------------------------------------------- 
    1008    !> @code 
    1009904   TYPE(TATT) FUNCTION iom_cdf__read_att_id(td_file, id_varid, id_attid) 
    1010905      IMPLICIT NONE 
     
    1022917 
    1023918         CALL logger_error( & 
    1024          &  " READ ATT: no id associated to file "//TRIM(td_file%c_name)) 
    1025  
    1026       ELSE       
     919         &  "IOM CDF READ ATT: no id associated to file "//TRIM(td_file%c_name)) 
     920 
     921      ELSE 
    1027922 
    1028923         ! get attribute name 
    1029924         il_status=NF90_INQ_ATTNAME(td_file%i_id, id_varid, id_attid, cl_name) 
    1030          CALL iom_cdf__check(il_status) 
     925         CALL iom_cdf__check(il_status,"IOM CDF READ ATT: ") 
    1031926 
    1032927         ! read attribute 
     
    1036931 
    1037932   END FUNCTION iom_cdf__read_att_id 
    1038    !> @endcode    
    1039933   !------------------------------------------------------------------- 
    1040934   !> @brief This function read variable value in an opened  
    1041    !> netcdf file, given variable id.</br/> 
    1042    !> start indices and number of indices selected along each dimension  
    1043    !> could be specify in a 4 dimension table (/'x','y','z','t'/) 
    1044    ! 
    1045    !> @author J.Paul 
    1046    !> - Nov, 2013- Initial Version 
    1047    ! 
    1048    !> @param[in] td_file : file structure 
    1049    !> @param[in] id_varid : variable id 
    1050    !> @param[in] id_start : index in the variable from which the data values  
     935   !> netcdf file, given variable id. 
     936   !> @details 
     937   !> Optionaly, start indices and number of indices selected along each dimension  
     938   !> could be specify in a 4 dimension array (/'x','y','z','t'/) 
     939   ! 
     940   !> @author J.Paul 
     941   !> @date November, 2013 - Initial Version 
     942   ! 
     943   !> @param[in] td_file   file structure 
     944   !> @param[in] id_varid  variable id 
     945   !> @param[in] id_start  index in the variable from which the data values  
    1051946   !> will be read 
    1052    !> @param[in] id_count : number of indices selected along each dimension 
     947   !> @param[in] id_count number of indices selected along each dimension 
    1053948   !> @return  variable structure  
    1054949   !------------------------------------------------------------------- 
    1055    !> @code 
    1056950   TYPE(TVAR) FUNCTION iom_cdf__read_var_id(td_file, id_varid,& 
    1057951   &                                        id_start, id_count) 
     
    1070964 
    1071965         CALL logger_error( & 
    1072          &  " IOM READ VAR: no id associated to file "//TRIM(td_file%c_name)) 
     966         &  " IOM CDF READ VAR: no id associated to file "//TRIM(td_file%c_name)) 
    1073967 
    1074968      ELSE 
    1075969 
    1076          ! look for variable id 
     970         ! look for variable index 
    1077971         il_ind(:)=MINLOC(td_file%t_var(:)%i_id,mask=(td_file%t_var(:)%i_id==id_varid)) 
    1078972         IF( il_ind(1) /= 0 )THEN 
    1079973 
    1080             iom_cdf__read_var_id=td_file%t_var(il_ind(1)) 
    1081  
    1082             print *,"iom_cdf__read_var_id ",trim(iom_cdf__read_var_id%c_name)," ",iom_cdf__read_var_id%i_ew 
     974            iom_cdf__read_var_id=var_copy(td_file%t_var(il_ind(1))) 
     975 
    1083976            !!! read variable value 
    1084977            CALL iom_cdf__read_var_value(td_file, iom_cdf__read_var_id, & 
     
    1086979 
    1087980         ELSE 
    1088             print *,"iom_cdf__read_var_id " 
    1089981            CALL logger_error( & 
    1090             &  " IOM READ VAR: there is no variable with id "//& 
     982            &  " IOM CDF READ VAR: there is no variable with id "//& 
    1091983            &  TRIM(fct_str(id_varid))//" in file "//TRIM(td_file%c_name)) 
    1092984         ENDIF 
     
    1094986      ENDIF 
    1095987   END FUNCTION iom_cdf__read_var_id 
    1096    !> @endcode    
    1097988   !------------------------------------------------------------------- 
    1098989   !> @brief This function read variable value in an opened  
    1099    !> netcdf file, given variable name or standard name.</br/> 
    1100    !> start indices and number of indices selected along each dimension  
    1101    !> could be specify in a 4 dimension table (/'x','y','z','t'/) 
    1102    ! 
     990   !> netcdf file, given variable name or standard name. 
    1103991   !> @details 
     992   !> Optionaly, start indices and number of indices selected along each dimension  
     993   !> could be specify in a 4 dimension array (/'x','y','z','t'/) 
     994   !> 
    1104995   !> look first for variable name. If it doesn't 
    1105996   !> exist in file, look for variable standard name.<br/> 
    1106    !> If variable name is not present, check variable standard name.<br/> 
    1107    ! 
    1108    !> @author J.Paul 
    1109    !> - Nov, 2013- Initial Version 
    1110    ! 
    1111    !> @param[in] td_file : file structure 
    1112    !> @param[in] cd_name  : variable name 
    1113    !> @param[in] id_start : index in the variable from which the data values will be read 
    1114    !> @param[in] id_count : number of indices selected along each dimension 
    1115    !> @param[in] cd_stdname : variable standard name 
     997   ! 
     998   !> @author J.Paul 
     999   !> @date November, 2013 - Initial Version 
     1000   ! 
     1001   !> @param[in] td_file   file structure 
     1002   !> @param[in] cd_name   variable name or standard name. 
     1003   !> @param[in] id_start  index in the variable from which the data values will be read 
     1004   !> @param[in] id_count  number of indices selected along each dimension 
    11161005   !> @return  variable structure  
    11171006   !------------------------------------------------------------------- 
    1118    !> @code 
    11191007   TYPE(TVAR) FUNCTION iom_cdf__read_var_name(td_file, cd_name,  & 
    11201008   &                                          id_start, id_count ) 
     
    11271015 
    11281016      ! local variable 
    1129       INTEGER(i4)       :: il_ind 
     1017      INTEGER(i4)       :: il_varid 
    11301018      !---------------------------------------------------------------- 
    11311019      ! check if file opened 
     
    11331021 
    11341022         CALL logger_error( & 
    1135          &  " IOM READ VAR: no id associated to file "//TRIM(td_file%c_name)) 
     1023         &  " IOM CDF READ VAR: no id associated to file "//TRIM(td_file%c_name)) 
    11361024 
    11371025      ELSE 
     
    11401028 
    11411029            CALL logger_error( & 
    1142             &  " IOM READ VAR: you must specify a variable to read "//& 
     1030            &  " IOM CDF READ VAR: you must specify a variable to read "//& 
    11431031            &  " in file "//TRIM(td_file%c_name)) 
    11441032 
    11451033         ELSE 
    11461034 
    1147             il_ind=var_get_id(td_file%t_var(:), cd_name) 
    1148             IF( il_ind /= 0 )THEN 
    1149  
    1150                iom_cdf__read_var_name=td_file%t_var(il_ind) 
     1035            il_varid=var_get_index(td_file%t_var(:), cd_name) 
     1036            IF( il_varid /= 0 )THEN 
     1037 
     1038               iom_cdf__read_var_name=var_copy(td_file%t_var(il_varid)) 
    11511039 
    11521040               !!! read variable value 
     
    11581046 
    11591047               CALL logger_error( & 
    1160                &  " IOM READ VAR: there is no variable with "//& 
     1048               &  " IOM CDF READ VAR: there is no variable with "//& 
    11611049               &  " name or standard name "//TRIM(cd_name)//& 
    11621050               &  " in file "//TRIM(td_file%c_name) ) 
     
    11681056       
    11691057   END FUNCTION iom_cdf__read_var_name 
    1170    !> @endcode 
    1171    !------------------------------------------------------------------- 
    1172    !> @brief This subroutine fill variable value in an opened  
    1173    !> netcdf file, given variable id.</br/> 
    1174    !> start indices and number of indices selected along each dimension  
    1175    !> could be specify in a 4 dimension table (/'x','y','z','t'/) 
    1176    ! 
    1177    !> @note ne peut pas marcher qd on fait boucle sur les variable d'un 
    1178    !> fichier. puisque change id. 
    1179  
    1180    !> @author J.Paul 
    1181    !> - Nov, 2013- Initial Version 
    1182    ! 
    1183    !> @param[inout] td_file : file structure 
    1184    !> @param[in] id_start : index in the variable from which the data values  
     1058   !------------------------------------------------------------------- 
     1059   !> @brief This subroutine fill all variable value from an opened  
     1060   !> netcdf file. 
     1061   !> @details 
     1062   !> Optionaly, start indices and number of indices selected along each dimension  
     1063   !> could be specify in a 4 dimension array (/'x','y','z','t'/) 
     1064   ! 
     1065   !> @author J.Paul 
     1066   !> @date November, 2013 - Initial Version 
     1067   ! 
     1068   !> @param[inout] td_file   file structure 
     1069   !> @param[in] id_start     index in the variable from which the data values  
    11851070   !> will be read 
    1186    !> @param[in] id_count : number of indices selected along each dimension 
    1187    !------------------------------------------------------------------- 
    1188    !> @code 
     1071   !> @param[in] id_count     number of indices selected along each dimension 
     1072   !------------------------------------------------------------------- 
    11891073   SUBROUTINE iom_cdf__fill_var_all(td_file, id_start, id_count) 
    11901074      IMPLICIT NONE 
     
    12031087 
    12041088         CALL logger_error( & 
    1205          &  " FILL VAR: no id associated to file "//TRIM(td_file%c_name)) 
     1089         &  " IOM CDF FILL VAR: no id associated to file "//TRIM(td_file%c_name)) 
    12061090 
    12071091      ELSE 
    12081092 
    12091093         DO ji=1,td_file%i_nvar 
    1210             CALL iom_cdf_fill_var(td_file, ji, id_start, id_count) 
     1094            CALL iom_cdf_fill_var(td_file, td_file%t_var(ji)%i_id, & 
     1095            &                     id_start, id_count) 
    12111096         ENDDO 
    12121097 
    12131098      ENDIF 
    12141099   END SUBROUTINE iom_cdf__fill_var_all 
    1215    !> @endcode 
    12161100   !------------------------------------------------------------------- 
    12171101   !> @brief This subroutine fill variable value in an opened  
    1218    !> netcdf file, given variable id.</br/> 
    1219    !> start indices and number of indices selected along each dimension  
    1220    !> could be specify in a 4 dimension table (/'x','y','z','t'/) 
    1221    ! 
    1222    !> @note ne peut pas marcher qd on fait boucle sur les variable d'un 
    1223    !> fichier. puisque change id. 
    1224  
    1225    !> @author J.Paul 
    1226    !> - Nov, 2013- Initial Version 
    1227    ! 
    1228    !> @param[inout] td_file : file structure 
    1229    !> @param[in] id_varid : variable id 
    1230    !> @param[in] id_start : index in the variable from which the data values  
     1102   !> netcdf file, given variable id. 
     1103   !> @details 
     1104   !> Optionaly, start indices and number of indices selected along each dimension  
     1105   !> could be specify in a 4 dimension array (/'x','y','z','t'/) 
     1106   ! 
     1107   !> @author J.Paul 
     1108   !> @date November, 2013 - Initial Version 
     1109   ! 
     1110   !> @param[inout] td_file   file structure 
     1111   !> @param[in] id_varid     variable id 
     1112   !> @param[in] id_start     index in the variable from which the data values  
    12311113   !> will be read 
    1232    !> @param[in] id_count : number of indices selected along each dimension 
    1233    !------------------------------------------------------------------- 
    1234    !> @code 
     1114   !> @param[in] id_count     number of indices selected along each dimension 
     1115   !------------------------------------------------------------------- 
    12351116   SUBROUTINE iom_cdf__fill_var_id(td_file, id_varid, id_start, id_count) 
    12361117      IMPLICIT NONE 
     
    12421123 
    12431124      ! local variable 
    1244       INTEGER(i4), DIMENSION(1) :: il_ind 
     1125      INTEGER(i4), DIMENSION(1) :: il_varid 
    12451126 
    12461127      ! loop indices 
     
    12511132 
    12521133         CALL logger_error( & 
    1253          &  " FILL VAR: no id associated to file "//TRIM(td_file%c_name)) 
     1134         &  "IOM CDF FILL VAR: no id associated to file "//TRIM(td_file%c_name)) 
    12541135 
    12551136      ELSE 
    12561137 
    12571138         ! look for variable id 
    1258          il_ind(:)=MINLOC( td_file%t_var(:)%i_id, & 
     1139         il_varid(:)=MINLOC( td_file%t_var(:)%i_id, & 
    12591140         &                 mask=(td_file%t_var(:)%i_id==id_varid)) 
    1260          IF( il_ind(1) /= 0 )THEN 
     1141         IF( il_varid(1) /= 0 )THEN 
    12611142 
    12621143            !!! read variable value 
    1263             CALL iom_cdf__read_var_value(td_file, td_file%t_var(il_ind(1)), & 
     1144            CALL iom_cdf__read_var_value(td_file, td_file%t_var(il_varid(1)), & 
    12641145            &                            id_start, id_count) 
    12651146 
    12661147            DO ji=1,td_file%i_nvar 
    1267                CALL logger_debug(" var id "//TRIM(td_file%t_var(ji)%c_name)//" "//TRIM(fct_str(td_file%t_var(ji)%i_id)) ) 
     1148               CALL logger_debug(" IOM CDF FILL VAR: var id "//& 
     1149               &     TRIM(td_file%t_var(ji)%c_name)//" "//& 
     1150               &     TRIM(fct_str(td_file%t_var(ji)%i_id)) ) 
    12681151            ENDDO 
    12691152         ELSE 
    12701153            CALL logger_error( & 
    1271             &  " FILL VAR: there is no variable with id "//& 
     1154            &  " IOM CDF FILL VAR: there is no variable with id "//& 
    12721155            &  TRIM(fct_str(id_varid))//" in file "//TRIM(td_file%c_name)) 
    12731156         ENDIF 
     
    12751158      ENDIF 
    12761159   END SUBROUTINE iom_cdf__fill_var_id 
    1277    !> @endcode 
    12781160   !------------------------------------------------------------------- 
    12791161   !> @brief This subroutine fill variable value in an opened  
    1280    !> netcdf file, given variable name or standard name.</br/> 
    1281    !> start indices and number of indices selected along each dimension  
    1282    !> could be specify in a 4 dimension table (/'x','y','z','t'/) 
    1283    ! 
     1162   !> netcdf file, given variable name or standard name. 
    12841163   !> @details 
     1164   !> Optionaly, start indices and number of indices selected along each dimension  
     1165   !> could be specify in a 4 dimension array (/'x','y','z','t'/) 
     1166   !> 
    12851167   !> look first for variable name. If it doesn't 
    12861168   !> exist in file, look for variable standard name.<br/> 
    1287    !> If variable name is not present, check variable standard name.<br/> 
    1288    ! 
    1289    !> @author J.Paul 
    1290    !> - Nov, 2013- Initial Version 
    1291    ! 
    1292    !> @param[inout] td_file : file structure 
    1293    !> @param[in] cd_name  : variable name or standard name 
    1294    !> @param[in] id_start : index in the variable from which the data values will be read 
    1295    !> @param[in] id_count : number of indices selected along each dimension 
    1296    !------------------------------------------------------------------- 
    1297    !> @code 
     1169   ! 
     1170   !> @author J.Paul 
     1171   !> @date November, 2013 - Initial Version 
     1172   ! 
     1173   !> @param[inout] td_file   file structure 
     1174   !> @param[in] cd_name      variable name or standard name 
     1175   !> @param[in] id_start     index in the variable from which the data values will be read 
     1176   !> @param[in] id_count     number of indices selected along each dimension 
     1177   !------------------------------------------------------------------- 
    12981178   SUBROUTINE iom_cdf__fill_var_name(td_file, cd_name, id_start, id_count ) 
    12991179      IMPLICIT NONE 
     
    13051185 
    13061186      ! local variable 
    1307       INTEGER(i4)       :: il_ind 
     1187      INTEGER(i4)       :: il_varid 
    13081188      !---------------------------------------------------------------- 
    13091189      ! check if file opened 
     
    13111191 
    13121192         CALL logger_error( & 
    1313          &  " FILL VAR: no id associated to file "//TRIM(td_file%c_name)) 
     1193         &  "IOM CDF FILL VAR: no id associated to file "//TRIM(td_file%c_name)) 
    13141194 
    13151195      ELSE 
    13161196 
    1317             il_ind=var_get_id(td_file%t_var(:), cd_name) 
    1318             IF( il_ind /= 0 )THEN 
     1197            il_varid=var_get_index(td_file%t_var(:), cd_name) 
     1198            IF( il_varid /= 0 )THEN 
    13191199 
    13201200               !!! read variable value 
    1321                CALL iom_cdf__read_var_value(td_file, td_file%t_var(il_ind), & 
     1201               CALL iom_cdf__read_var_value(td_file, td_file%t_var(il_varid), & 
    13221202               &                            id_start, id_count) 
    13231203 
     
    13251205 
    13261206               CALL logger_error( & 
    1327                &  " FILL VAR: there is no variable with "//& 
     1207               &  "IOM CDF FILL VAR: there is no variable with "//& 
    13281208               &  "name or standard name"//TRIM(cd_name)//& 
    13291209               &  " in file "//TRIM(td_file%c_name)) 
     
    13331213       
    13341214   END SUBROUTINE iom_cdf__fill_var_name 
    1335    !> @endcode 
    13361215   !------------------------------------------------------------------- 
    13371216   !> @brief This function read metadata of a variable in an opened  
    1338    !> netcdf file.</br/> 
     1217   !> netcdf file. 
    13391218   ! 
    13401219   !> @note variable value are not read 
    13411220   ! 
    13421221   !> @author J.Paul 
    1343    !> - Nov, 2013- Initial Version 
    1344    ! 
    1345    !> @param[in] id_fileid : file id 
    1346    !> @param[in] id_varid : variable id 
     1222   !> @date November, 2013 - Initial Version 
     1223   !> @date September, 2014 
     1224   !> - force to use FillValue=1.e20 if no FillValue for coordinate variable. 
     1225   ! 
     1226   !> @param[in] td_file   file structure 
     1227   !> @param[in] id_varid  variable id 
    13471228   !> @return  variable structure  
    13481229   !------------------------------------------------------------------- 
    1349    !> @code 
    13501230   TYPE(TVAR) FUNCTION iom_cdf__read_var_meta(td_file, id_varid) 
    13511231      IMPLICIT NONE 
     
    13751255 
    13761256         CALL logger_error( & 
    1377          &  " READ ATT: no id associated to file "//TRIM(td_file%c_name)) 
     1257         &  " IOM CDF READ VAR META: no id associated to file "//& 
     1258         &   TRIM(td_file%c_name)) 
    13781259 
    13791260      ELSE 
    13801261 
    13811262         ! inquire variable 
    1382          CALL logger_trace( & 
    1383          &  " READ VAR: inquire variable "//TRIM(fct_str(id_varid))//& 
     1263         CALL logger_debug( & 
     1264         &  " IOM CDF READ VAR META: inquire variable "//& 
     1265         &  TRIM(fct_str(id_varid))//& 
    13841266         &  " in file "//TRIM(td_file%c_name)) 
    13851267          
     
    13921274         &                                il_dimid(:),& 
    13931275         &                                il_natt ) 
    1394          CALL iom_cdf__check(il_status) 
    1395  
     1276         CALL iom_cdf__check(il_status,"IOM CDF READ VAR META: ") 
    13961277         !!! fill variable dimension structure 
    13971278         tl_dim(:)=iom_cdf__read_var_dim( td_file, il_ndim, il_dimid(:) ) 
     
    14051286            il_attid=att_get_id(tl_att(:),'_FillValue') 
    14061287            IF( il_attid == 0 )THEN 
    1407                CALL logger_warn("IOM READ VAR: no _FillValue for variable "//& 
     1288               CALL logger_info("IOM CDF READ VAR META: no _FillValue for variable "//& 
    14081289               &  TRIM(cl_name)//" in file "//TRIM(td_file%c_name) ) 
    14091290 
     
    14111292               IF( il_attid /= 0 )THEN 
    14121293                  ! create attribute _FillValue 
    1413                   CALL logger_warn("IOM READ VAR: assume _FillValue is equal to "//& 
     1294                  CALL logger_info("IOM CDF READ VAR META: assume _FillValue is equal to "//& 
    14141295                  &                "missing_value for variable "//TRIM(cl_name) ) 
    1415                   tl_fill=att_init('_FillValue',tl_att(il_attid)%d_value(:)) 
     1296                  tl_fill=att_init('_FillValue',tl_att(il_attid)%d_value(:), & 
     1297                  &                 id_type=tl_att(il_attid)%i_type) 
    14161298               ELSE 
    14171299                  ! create attribute _FillValue 
    1418                   CALL logger_warn("IOM READ VAR: assume _FillValue is equal to "//& 
    1419                   &                "zero for variable "//TRIM(cl_name) ) 
    1420                   tl_fill=att_init('_FillValue',0.) 
    1421                   !tl_fill=att_init('_FillValue',1.e20) 
     1300                  SELECT CASE(TRIM(fct_lower(cl_name))) 
     1301                     CASE DEFAULT 
     1302                        CALL logger_info("IOM CDF READ VAR META: assume _FillValue is equal to "//& 
     1303                        &                "zero for variable "//TRIM(cl_name) ) 
     1304                        tl_fill=att_init('_FillValue',0.) 
     1305                     CASE('nav_lon','nav_lat', 'nav_lev', & 
     1306                        &  'glamt','glamu','glamv','glamf', & 
     1307                        &  'gphit','gphiu','gphiv','gphif') 
     1308                        CALL logger_info("IOM CDF READ VAR META: assume _FillValue is equal to "//& 
     1309                        &                "dummy fillValue (1.e20) for variable "//TRIM(cl_name) ) 
     1310                        tl_fill=att_init('_FillValue',1.e20) 
     1311                  END SELECT 
    14221312               ENDIF 
    14231313 
    14241314               ALLOCATE( tl_tmp(il_natt) ) 
    14251315               ! save read attribut 
    1426                tl_tmp(:)=tl_att(:) 
    1427                ! change number of attribute in table 
     1316               tl_tmp(:)=att_copy(tl_att(:)) 
     1317               ! change number of attribute in array 
     1318               CALL att_clean(tl_att(:)) 
    14281319               DEALLOCATE( tl_att ) 
    14291320               ALLOCATE( tl_att(il_natt+1) ) 
    14301321               ! copy read attribut 
    1431                tl_att(1:il_natt)=tl_tmp(:) 
     1322               tl_att(1:il_natt)=att_copy(tl_tmp(:)) 
     1323               ! clean 
     1324               CALL att_clean(tl_tmp(:)) 
    14321325               DEALLOCATE( tl_tmp ) 
    14331326 
    14341327               ! create attribute _FillValue 
    1435                tl_att(il_natt+1)=tl_fill 
     1328               tl_att(il_natt+1)=att_copy(tl_fill) 
    14361329 
    14371330            ENDIF 
     
    14401333            ALLOCATE(tl_att(il_natt+1) ) 
    14411334            ! create attribute _FillValue 
    1442             CALL logger_warn("IOM READ VAR: assume _FillValue is equal to "//& 
    1443             &                "zero for variable "//TRIM(cl_name) ) 
    1444             tl_fill=att_init('_FillValue',0.) 
     1335            SELECT CASE(TRIM(fct_lower(cl_name))) 
     1336               CASE DEFAULT 
     1337                  CALL logger_info("IOM CDF READ VAR META: assume _FillValue is equal to "//& 
     1338                  &                "zero for variable "//TRIM(cl_name) ) 
     1339                  tl_fill=att_init('_FillValue',0.) 
     1340               CASE('nav_lon','nav_lat', & 
     1341                  &  'glamt','glamu','glamv','glamf', & 
     1342                  &  'gphit','gphiu','gphiv','gphif') 
     1343                  CALL logger_info("IOM CDF READ VAR META: assume _FillValue is equal to "//& 
     1344                  &                "dummy fillValue (1.e20) for variable "//TRIM(cl_name) ) 
     1345                  tl_fill=att_init('_FillValue',1.e20) 
     1346            END SELECT             
    14451347            ! create attribute _FillValue 
    1446             tl_att(il_natt+1)=tl_fill 
     1348            tl_att(il_natt+1)=att_copy(tl_fill) 
    14471349         ENDIF 
    14481350 
     
    14511353         &                                tl_att(:), id_id=id_varid ) 
    14521354 
     1355         ! clean 
     1356         CALL dim_clean(tl_dim(:)) 
     1357         CALL att_clean(tl_fill) 
     1358         CALL att_clean(tl_att(:)) 
    14531359         DEALLOCATE( tl_att ) 
    14541360 
     
    14561362 
    14571363   END FUNCTION iom_cdf__read_var_meta 
    1458    !> @endcode 
    14591364   !------------------------------------------------------------------- 
    14601365   !> @brief This subroutine read variable dimension 
    14611366   !> in an opened netcdf file. 
    1462    ! 
     1367   !> 
    14631368   !> @details 
    14641369   !> the number of dimension can't exceed 4,  
    14651370   !> and should be 'x', 'y', 'z', 't' (whatever their order).<br/> 
    1466    !> If the number of dimension read is less than 4, the table of dimension 
     1371   !> If the number of dimension read is less than 4, the array of dimension 
    14671372   !> strucure is filled with unused dimension.<br/> 
    1468    !> So the table of dimension structure of a variable is always compose of 4 
     1373   !> So the array of dimension structure of a variable is always compose of 4 
    14691374   !> dimension (use or not).  
    14701375   ! 
    14711376   !> @author J.Paul 
    1472    !> - Nov, 2013- Initial Version 
    1473    ! 
    1474    !> @param[inout] td_file : file structure 
    1475    !> @return file structure completed  
    1476    !------------------------------------------------------------------- 
    1477    !> @code 
     1377   !> @date November, 2013 - Initial Version 
     1378   !> @date July, 2015  
     1379   !> - Bug fix: use order to disorder table (see dim_init) 
     1380   !> 
     1381   !> @param[in] td_file   file structure 
     1382   !> @param[in] id_ndim   number of dimension 
     1383   !> @param[in] id_dimid  array of dimension id 
     1384   !> @return array dimension structure  
     1385   !------------------------------------------------------------------- 
    14781386   FUNCTION iom_cdf__read_var_dim(td_file, id_ndim, id_dimid) 
    14791387      IMPLICIT NONE 
     
    14871395 
    14881396      ! local variable 
    1489       INTEGER(i4), DIMENSION(ip_maxdim) :: il_2xyzt 
     1397      INTEGER(i4), DIMENSION(ip_maxdim) :: il_xyzt2 
    14901398 
    14911399      TYPE(TDIM) , DIMENSION(ip_maxdim) :: tl_dim 
     
    15021410         CALL dim_reorder(tl_dim(:)) 
    15031411 
    1504          iom_cdf__read_var_dim(:)=tl_dim(:) 
     1412         iom_cdf__read_var_dim(:)=dim_copy(tl_dim(:)) 
     1413 
     1414         ! clean 
     1415         CALL dim_clean(tl_dim(:)) 
    15051416 
    15061417      ELSE IF( id_ndim > 0 .AND. id_ndim <= 4 )THEN 
     
    15081419 
    15091420         DO ji = 1, id_ndim 
    1510             CALL logger_debug( " READ VAR DIM: get variable dimension "//& 
    1511             &               TRIM(fct_str(ji)) ) 
    1512  
    1513             il_2xyzt(ji)=td_file%t_dim(id_dimid(ji))%i_2xyzt 
     1421            CALL logger_debug( " IOM CDF READ VAR DIM: get variable "//& 
     1422               &  "dimension "//TRIM(fct_str(ji)) ) 
     1423 
     1424            il_xyzt2(ji)=td_file%t_dim(id_dimid(ji))%i_xyzt2 
    15141425 
    15151426            ! read dimension information 
    1516             tl_dim(ji) = dim_init( td_file%t_dim(il_2xyzt(ji))%c_name, & 
    1517             &                      td_file%t_dim(il_2xyzt(ji))%i_len ) 
     1427            tl_dim(ji) = dim_init( td_file%t_dim(il_xyzt2(ji))%c_name, & 
     1428            &                      td_file%t_dim(il_xyzt2(ji))%i_len ) 
    15181429         ENDDO 
    15191430 
    15201431         ! reorder dimension to ('x','y','z','t') 
    15211432         CALL dim_reorder(tl_dim(:)) 
    1522        
    1523          iom_cdf__read_var_dim(:)=tl_dim(:) 
     1433  
     1434         iom_cdf__read_var_dim(:)=dim_copy(tl_dim(:)) 
     1435 
     1436         ! clean 
     1437         CALL dim_clean(tl_dim(:)) 
    15241438 
    15251439      ELSE 
    15261440 
    1527          CALL logger_error(" READ VAR DIM: can't manage "//& 
     1441         CALL logger_error(" IOM CDF READ VAR DIM: can't manage "//& 
    15281442         &              TRIM(fct_str(id_ndim))//" dimension(s)" ) 
    15291443 
     
    15311445 
    15321446   END FUNCTION iom_cdf__read_var_dim 
    1533    !> @endcode    
    15341447   !------------------------------------------------------------------- 
    15351448   !> @brief This subroutine read variable attributes 
     
    15371450   ! 
    15381451   !> @author J.Paul 
    1539    !> - Nov, 2013- Initial Version 
    1540    ! 
    1541    !> @param[in] td_file : file structure 
    1542    !> @param[inout] td_var : variable structure 
    1543    !> @return filled variable attribute structure  
    1544    !------------------------------------------------------------------- 
    1545    !> @code 
     1452   !> @date November, 2013 - Initial Version 
     1453   ! 
     1454   !> @param[in] td_file   file structure 
     1455   !> @param[in] id_varid  variable id 
     1456   !> @param[in] id_natt   number of attributes 
     1457   !> @return array of attribute structure 
     1458   !------------------------------------------------------------------- 
    15461459   FUNCTION iom_cdf__read_var_att(td_file, id_varid, id_natt) 
    15471460      IMPLICIT NONE 
     
    15551468 
    15561469      ! local variable 
    1557       TYPE(TATT), DIMENSION(id_natt) :: tl_att 
    15581470 
    15591471      ! loop indices 
     
    15621474 
    15631475      IF( id_natt > 0 )THEN 
    1564  
     1476       
    15651477         ! read attributes 
    15661478         DO ji = 1, id_natt 
    1567             CALL logger_debug( " READ VAR ATT: get attribute "//& 
     1479            CALL logger_trace( " IOM CDF READ VAR ATT: get attribute "//& 
    15681480            &               TRIM(fct_str(ji)) ) 
    15691481 
    1570             tl_att(ji)=iom_cdf_read_att(td_file, id_varid, ji) 
     1482            iom_cdf__read_var_att(ji)=iom_cdf_read_att(td_file, id_varid, ji) 
    15711483 
    15721484         ENDDO 
    15731485 
    1574          iom_cdf__read_var_att(:)=tl_att(:) 
    1575  
    15761486      ELSE 
    15771487 
    1578          CALL logger_debug( " READ VAR ATT: no attribute for variable " ) 
     1488         CALL logger_debug( " IOM CDF READ VAR ATT: no attribute for variable " ) 
    15791489 
    15801490      ENDIF 
    15811491 
    15821492   END FUNCTION iom_cdf__read_var_att 
    1583    !> @endcode    
    15841493   !------------------------------------------------------------------- 
    15851494   !> @brief This subroutine read variable value 
    15861495   !> in an opened netcdf file. 
    1587    ! 
    1588    !> @author J.Paul 
    1589    !> - Nov, 2013- Initial Version 
    1590    ! 
    1591    !> @param[in] td_file : file structure 
    1592    !> @param[inout] td_var : variable structure 
    1593    !> @param[in] id_start : index in the variable from which the data values will be read 
    1594    !> @param[in] id_count : number of indices selected along each dimension 
     1496   !> @details 
     1497   !> Optionaly, start indices and number of indices selected along each dimension  
     1498   !> could be specify in a 4 dimension array (/'x','y','z','t'/) 
     1499   ! 
     1500   !> @author J.Paul 
     1501   !> @date November, 2013 - Initial Version 
     1502   !> @date June, 2015  
     1503   !> - use scale factor and offset, as soon as read variable value 
     1504   ! 
     1505   !> @param[in] td_file   file structure 
     1506   !> @param[inout] td_var variable structure 
     1507   !> @param[in] id_start  index in the variable from which the data values will be read 
     1508   !> @param[in] id_count  number of indices selected along each dimension 
    15951509   !> @return variable structure completed  
    1596    ! 
    1597    !> @todo 
    1598    !> - warning do not change fill value when use scale factor.. 
    1599    !------------------------------------------------------------------- 
    1600    !> @code 
     1510   !------------------------------------------------------------------- 
    16011511   SUBROUTINE iom_cdf__read_var_value(td_file, td_var, & 
    16021512   &                                  id_start, id_count ) 
     
    16091519 
    16101520      ! local variable 
    1611       INTEGER(i4)                       :: il_status 
    1612       INTEGER(i4)                       :: il_tmp1, il_tmp2, il_varid 
    1613       INTEGER(i4), DIMENSION(ip_maxdim) :: il_start 
    1614       INTEGER(i4), DIMENSION(ip_maxdim) :: il_count 
    1615       INTEGER(i4), DIMENSION(ip_maxdim) :: il_start_ord 
    1616       INTEGER(i4), DIMENSION(ip_maxdim) :: il_count_ord 
    1617       REAL(dp)   , DIMENSION(:,:,:,:), ALLOCATABLE :: dl_value 
    1618  
    1619       TYPE(TDIM),  DIMENSION(ip_maxdim) :: tl_dim 
     1521      INTEGER(i4)                                    :: il_status 
     1522      INTEGER(i4)                                    :: il_tmp1 
     1523      INTEGER(i4)                                    :: il_tmp2 
     1524      INTEGER(i4)                                    :: il_varid 
     1525      INTEGER(i4), DIMENSION(ip_maxdim)              :: il_start 
     1526      INTEGER(i4), DIMENSION(ip_maxdim)              :: il_count 
     1527      INTEGER(i4), DIMENSION(ip_maxdim)              :: il_start_ord 
     1528      INTEGER(i4), DIMENSION(ip_maxdim)              :: il_count_ord 
     1529 
     1530      REAL(dp)   , DIMENSION(:,:,:,:)  , ALLOCATABLE :: dl_value 
     1531      REAL(dp)   , DIMENSION(:,:,:,:)  , ALLOCATABLE :: dl_tmp 
     1532 
    16201533      ! loop indices 
    16211534      INTEGER(i4) :: ji 
    16221535      !---------------------------------------------------------------- 
    16231536 
    1624       ! check id_count and id_start optionals parameters... 
    1625       IF( (       PRESENT(id_start)  .AND. (.NOT. PRESENT(id_count))) .OR. & 
    1626           ((.NOT. PRESENT(id_start)) .AND.        PRESENT(id_count) ) )THEN 
    1627          CALL logger_warn( & 
    1628          &  " READ VAR VALUE: id_start and id_count should be both specify") 
    1629       ENDIF 
    1630  
    1631       IF( PRESENT(id_start).AND.PRESENT(id_count) )THEN 
    1632  
    1633          IF( SIZE(id_start(:)) /= ip_maxdim .OR. & 
    1634          &   SIZE(id_count(:)) /= ip_maxdim )THEN 
    1635             CALL logger_error("READ VAR: dimension of table start or count "//& 
    1636             &      " are invalid to read variable "//TRIM(td_var%c_name)//& 
    1637             &      " in file "//TRIM(td_file%c_name) ) 
    1638          ENDIF 
    1639  
    1640          ! change dimension order from ('x','y','z','t') 
    1641          il_start(:)=dim_reorder_xyzt2(td_var%t_dim, id_start(:)) 
    1642          il_count(:)=dim_reorder_xyzt2(td_var%t_dim, id_count(:)) 
    1643  
    1644          ! keep ordered table ('x','y','z','t') 
    1645          il_start_ord(:)=il_start(:) 
    1646          il_count_ord(:)=il_count(:) 
    1647  
     1537      ! check if variable in file structure 
     1538      il_varid=var_get_id(td_file%t_var(:),TRIM(td_var%c_name)) 
     1539      IF( il_varid /= 0 )THEN 
     1540 
     1541         ! check id_count and id_start optionals parameters... 
     1542         IF( (       PRESENT(id_start)  .AND. (.NOT. PRESENT(id_count))) .OR. & 
     1543             ((.NOT. PRESENT(id_start)) .AND.        PRESENT(id_count) ) )THEN 
     1544            CALL logger_warn( "IOM CDF READ VAR VALUE: id_start and id_count"//& 
     1545               & " should be both specify") 
     1546         ENDIF 
     1547         IF( PRESENT(id_start).AND.PRESENT(id_count) )THEN 
     1548 
     1549            IF( SIZE(id_start(:)) /= ip_maxdim .OR. & 
     1550            &   SIZE(id_count(:)) /= ip_maxdim )THEN 
     1551               CALL logger_error("IOM CDF READ VAR: dimension of array start"//& 
     1552                  &  " or count are invalid to read variable "//& 
     1553                  &  TRIM(td_var%c_name)//" in file "//TRIM(td_file%c_name) ) 
     1554            ENDIF 
     1555 
     1556            ! change dimension order from ('x','y','z','t') 
     1557            il_start(:)=dim_reorder_xyzt2(td_var%t_dim, id_start(:)) 
     1558            il_count(:)=dim_reorder_xyzt2(td_var%t_dim, id_count(:)) 
     1559 
     1560            ! keep ordered array ('x','y','z','t') 
     1561            il_start_ord(:)=id_start(:) 
     1562            il_count_ord(:)=id_count(:) 
     1563 
     1564         ELSE 
     1565 
     1566            ! change dimension order from ('x','y','z','t') 
     1567            il_start(:)=(/1,1,1,1/) 
     1568            il_count(:)=dim_reorder_xyzt2(td_var%t_dim(:),td_var%t_dim(:)%i_len) 
     1569 
     1570            ! keep ordered array ('x','y','z','t') 
     1571            il_start_ord(:)=(/1,1,1,1/) 
     1572            il_count_ord(:)=td_var%t_dim(:)%i_len 
     1573 
     1574         ENDIF 
     1575 
     1576         ! check dimension 
     1577         IF( .NOT. ALL(il_start_ord(:)>=(/1,1,1,1/)) )THEN 
     1578 
     1579            CALL logger_error( "IOM CDF READ VAR VALUE: start indices should"//& 
     1580            &  " be greater than or equal to 1") 
     1581 
     1582         ENDIF 
     1583 
     1584         IF(.NOT.ALL(il_start_ord(:)+il_count_ord(:)-1 <= & 
     1585            &  (/td_var%t_dim( 1 )%i_len,& 
     1586            &    td_var%t_dim( 2 )%i_len,& 
     1587            &    td_var%t_dim( 3 )%i_len,& 
     1588            &    td_var%t_dim( 4 )%i_len & 
     1589            &                                            /)) )THEN 
     1590 
     1591            DO ji = 1, ip_maxdim 
     1592               il_tmp1=il_start_ord(ji)+il_count_ord(ji)-1 
     1593               il_tmp2=td_var%t_dim(ji)%i_len 
     1594               CALL logger_debug( "IOM CDF READ VAR VALUE: start + count -1:"//& 
     1595               &  TRIM(fct_str(il_tmp1))//" variable dimension"//& 
     1596               &  TRIM(fct_str(il_tmp2))) 
     1597            ENDDO 
     1598            CALL logger_error( "IOM CDF READ VAR VALUE: start + count exceed "//& 
     1599            &  "variable dimension for "//TRIM(td_var%c_name) ) 
     1600 
     1601         ELSE 
     1602 
     1603            ! Allocate space to hold variable value (disorder) 
     1604            ALLOCATE(dl_value( il_count(1), & 
     1605               &               il_count(2), & 
     1606               &               il_count(3), & 
     1607               &               il_count(4)),& 
     1608               &               stat=il_status) 
     1609            IF( il_status /= 0 )THEN 
     1610 
     1611              CALL logger_error( & 
     1612               &  "IOM CDF READ VAR VALUE: not enough space to put variable "//& 
     1613               &  TRIM(td_var%c_name)) 
     1614 
     1615            ENDIF 
     1616 
     1617            ! read values 
     1618            CALL logger_debug( & 
     1619            &  "IOM CDF READ VAR VALUE: get variable "//TRIM(td_var%c_name)//& 
     1620            &  " in file "//TRIM(td_file%c_name)) 
     1621 
     1622            il_status = NF90_GET_VAR( td_file%i_id, il_varid,           & 
     1623            &                                       dl_value(:,:,:,:),  & 
     1624            &                                       start = il_start(:),& 
     1625            &                                       count = il_count(:) ) 
     1626            CALL iom_cdf__check(il_status,"IOM CDF READ VAR VALUE: ") 
     1627 
     1628            ! Allocate space to hold variable value in structure 
     1629            IF( ASSOCIATED(td_var%d_value) )THEN 
     1630               DEALLOCATE(td_var%d_value)    
     1631            ENDIF 
     1632   
     1633            ! new dimension length 
     1634            td_var%t_dim(:)%i_len=il_count_ord(:) 
     1635 
     1636!>   dummy patch for pgf95 
     1637            ALLOCATE( dl_tmp( td_var%t_dim(1)%i_len, & 
     1638            &                 td_var%t_dim(2)%i_len, & 
     1639            &                 td_var%t_dim(3)%i_len, & 
     1640            &                 td_var%t_dim(4)%i_len),& 
     1641            &        stat=il_status) 
     1642            IF(il_status /= 0 )THEN 
     1643 
     1644               CALL logger_error( & 
     1645               &  "IOM CDF READ VAR VALUE: not enough space to put variable "//& 
     1646               &  TRIM(td_var%c_name)//& 
     1647               &  " in variable structure") 
     1648            ENDIF 
     1649            dl_tmp(:,:,:,:)=td_var%d_fill 
     1650 
     1651            ! reshape values to be ordered as ('x','y','z','t') 
     1652            dl_tmp(:,:,:,:)=dim_reshape_2xyzt(td_var%t_dim(:), & 
     1653            &                                 dl_value(:,:,:,:)) 
     1654 
     1655            DEALLOCATE(dl_value) 
     1656 
     1657            ALLOCATE(td_var%d_value( td_var%t_dim(1)%i_len, & 
     1658            &                        td_var%t_dim(2)%i_len, & 
     1659            &                        td_var%t_dim(3)%i_len, & 
     1660            &                        td_var%t_dim(4)%i_len),& 
     1661            &        stat=il_status) 
     1662            IF(il_status /= 0 )THEN 
     1663 
     1664               CALL logger_error( & 
     1665               &  "IOM CDF READ VAR VALUE: not enough space to put variable "//& 
     1666               &  TRIM(td_var%c_name)//& 
     1667               &  " in variable structure") 
     1668 
     1669            ENDIF 
     1670!            ! FillValue by default 
     1671!            td_var%d_value(:,:,:,:)=td_var%d_fill 
     1672! 
     1673!            ! reshape values to be ordered as ('x','y','z','t') 
     1674!            td_var%d_value(:,:,:,:)=dim_reshape_2xyzt(td_var%t_dim(:), & 
     1675!            &                                         dl_value(:,:,:,:)) 
     1676! 
     1677!            DEALLOCATE(dl_value) 
     1678 
     1679            td_var%d_value(:,:,:,:)=dl_tmp(:,:,:,:) 
     1680            DEALLOCATE(dl_tmp) 
     1681!<   dummy patch for pgf95 
     1682 
     1683            ! force to change _FillValue to avoid mistake  
     1684            ! with dummy zero _FillValue 
     1685            IF( td_var%d_fill == 0._dp )THEN 
     1686               CALL var_chg_FillValue(td_var) 
     1687            ENDIF 
     1688 
     1689            ! use scale factor and offset 
     1690            WHERE( td_var%d_value(:,:,:,:) /= td_var%d_fill ) 
     1691               td_var%d_value(:,:,:,:) = & 
     1692               &  td_var%d_value(:,:,:,:)*td_var%d_scf + td_var%d_ofs 
     1693            END WHERE 
     1694 
     1695         ENDIF 
    16481696      ELSE 
    1649  
    1650          ! change dimension order from ('x','y','z','t') 
    1651          il_start(:)=(/1,1,1,1/) 
    1652          il_count(:)=dim_reorder_xyzt2(td_var%t_dim(:),td_var%t_dim(:)%i_len) 
    1653  
    1654          ! keep ordered table ('x','y','z','t') 
    1655          il_start_ord(:)=(/1,1,1,1/) 
    1656          il_count_ord(:)=td_var%t_dim(:)%i_len 
    1657  
    1658       ENDIF 
    1659  
    1660       ! check dimension 
    1661       IF( .NOT. ALL(il_start_ord(:)>=(/1,1,1,1/)) )THEN 
    1662  
    16631697         CALL logger_error( & 
    1664          &" READ VAR VALUE: start indices should be greater than or equal to 1") 
    1665  
    1666       ENDIF 
    1667  
    1668       IF(.NOT.ALL(il_start_ord(:)+il_count_ord(:)-1<=(/td_var%t_dim(1)%i_len,& 
    1669          &                                             td_var%t_dim(2)%i_len,& 
    1670          &                                             td_var%t_dim(3)%i_len,& 
    1671          &                                             td_var%t_dim(4)%i_len & 
    1672          &                                            /)) )THEN 
    1673  
    1674          CALL logger_error( & 
    1675          &  " READ VAR VALUE: start + count exceed variable dimension" ) 
    1676  
    1677          DO ji = 1, ip_maxdim 
    1678             il_tmp1=il_start_ord(ji)+il_count_ord(ji) 
    1679             il_tmp2=td_var%t_dim(ji)%i_len 
    1680             CALL logger_debug( & 
    1681             &  " READ VAR VALUE: start + count -1 "//TRIM(fct_str(il_tmp1))//& 
    1682             &  " variable dimension"//TRIM(fct_str(il_tmp2))) 
    1683          ENDDO 
    1684  
    1685       ELSE 
    1686  
    1687          ! Allocate space to hold variable value (unorder) 
    1688          ALLOCATE(dl_value( il_count(1), & 
    1689             &               il_count(2), & 
    1690             &               il_count(3), & 
    1691             &               il_count(4)),& 
    1692             &               stat=il_status) 
    1693          IF( il_status /= 0 )THEN 
    1694  
    1695            CALL logger_error( & 
    1696             &  " READ VAR VALUE: not enough space to put variable "//& 
    1697             &  TRIM(td_var%c_name)) 
    1698  
    1699          ENDIF 
    1700  
    1701          ! read values 
    1702          CALL logger_debug( & 
    1703          &  " READ VAR VALUE: get variable "//TRIM(td_var%c_name)//& 
    1704          &  " in file "//TRIM(td_file%c_name)) 
    1705          CALL logger_debug("start "//TRIM(fct_str(il_start(1)))//','//& 
    1706          &                           TRIM(fct_str(il_start(2)))//','//& 
    1707          &                           TRIM(fct_str(il_start(3)))//','//& 
    1708          &                           TRIM(fct_str(il_start(4)))//')'  ) 
    1709          CALL logger_debug("count "//TRIM(fct_str(il_count(1)))//','//& 
    1710          &                           TRIM(fct_str(il_count(2)))//','//& 
    1711          &                           TRIM(fct_str(il_count(3)))//','//& 
    1712          &                           TRIM(fct_str(il_count(4)))//')'  ) 
    1713          CALL logger_debug("dim "//TRIM(fct_str(td_file%t_dim(1)%i_len))//','//& 
    1714          &                         TRIM(fct_str(td_file%t_dim(2)%i_len))//','//& 
    1715          &                         TRIM(fct_str(td_file%t_dim(3)%i_len))//','//& 
    1716          &                         TRIM(fct_str(td_file%t_dim(4)%i_len))//')'  ) 
    1717          CALL logger_debug("shape "//TRIM(fct_str(SIZE(dl_value,DIM=1)))//","//& 
    1718          &                           TRIM(fct_str(SIZE(dl_value,DIM=2)))//","//& 
    1719          &                           TRIM(fct_str(SIZE(dl_value,DIM=3)))//","//& 
    1720          &                           TRIM(fct_str(SIZE(dl_value,DIM=4)))//")" ) 
    1721          CALL logger_debug("var "//TRIM(td_var%c_name)) 
    1722          il_varid=var_get_id(td_file%t_var(:),TRIM(td_var%c_name)) 
    1723          CALL logger_debug("var id "//TRIM(fct_str(il_varid))//' '//TRIM(fct_str(td_var%i_id))) 
    1724          CALL logger_debug("file id "//TRIM(fct_str(td_file%i_id))) 
    1725          il_status = NF90_GET_VAR( td_file%i_id, td_var%i_id,        & 
    1726          &                                       dl_value(:,:,:,:),  & 
    1727          &                                       start = il_start(:),& 
    1728          &                                       count = il_count(:) ) 
    1729          CALL iom_cdf__check(il_status) 
    1730  
    1731          ! Allocate space to hold variable value in structure 
    1732          IF( ASSOCIATED(td_var%d_value) )THEN 
    1733             DEALLOCATE(td_var%d_value)    
    1734          ENDIF 
    1735    
    1736          ! new dimension length 
    1737          td_var%t_dim(:)%i_len=il_count_ord(:) 
    1738  
    1739          ALLOCATE(td_var%d_value( il_count_ord(1), & 
    1740          &                        il_count_ord(2), & 
    1741          &                        il_count_ord(3), & 
    1742          &                        il_count_ord(4)),& 
    1743          &        stat=il_status) 
    1744          IF(il_status /= 0 )THEN 
    1745  
    1746             CALL logger_error( & 
    1747             &  " READ VAR VALUE: not enough space to put variable "//& 
    1748             &  TRIM(td_var%c_name)//& 
    1749             &  " in variable structure") 
    1750  
    1751          ENDIF 
    1752          ! FillValue by default 
    1753          td_var%d_value(:,:,:,:)=td_var%d_fill 
    1754  
    1755          ! reshape values to be ordered as ('x','y','z','t') 
    1756          tl_dim(:)=td_var%t_dim(:) 
    1757          td_var%d_value(:,:,:,:)=dim_reshape_2xyzt(tl_dim,dl_value(:,:,:,:)) 
    1758  
    1759          DEALLOCATE(dl_value) 
    1760  
    1761          ! force to change _FillValue to avoid mistake  
    1762          ! with dummy zero _FillValue 
    1763          IF( td_var%d_fill == 0._dp )THEN 
    1764             CALL var_chg_FillValue(td_var) 
    1765          ENDIF 
     1698         &  "IOM CDF READ VAR VALUE: no variable "//TRIM(td_var%c_name)//& 
     1699         &  " in file structure "//TRIM(td_file%c_name)) 
    17661700      ENDIF 
    17671701 
    17681702   END SUBROUTINE iom_cdf__read_var_value 
    1769    !> @endcode    
    17701703   !------------------------------------------------------------------- 
    17711704   !> @brief This subroutine write file structure in an opened netcdf file. 
    1772    ! 
     1705   !> 
    17731706   !> @details 
    1774    ! 
    1775    !> @author J.Paul 
    1776    !> - Nov, 2013- Initial Version 
    1777    ! 
    1778    !> @param[in] td_file : file structure 
    1779    !------------------------------------------------------------------- 
    1780    !> @code 
    1781    SUBROUTINE iom_cdf_write_file(td_file) 
    1782       IMPLICIT NONE 
    1783       ! Argument       
    1784       TYPE(TFILE), INTENT(INOUT) :: td_file 
     1707   !> optionally, you could specify dimension order (default 'xyzt') 
     1708   !> 
     1709   !> @author J.Paul 
     1710   !> @date November, 2013 - Initial Version 
     1711   !> @date July, 2015  
     1712   !> - add dimension order option  
     1713   ! 
     1714   !> @param[inout] td_file   file structure 
     1715   !------------------------------------------------------------------- 
     1716   SUBROUTINE iom_cdf_write_file(td_file, cd_dimorder) 
     1717      IMPLICIT NONE 
     1718      ! Argument       
     1719      TYPE(TFILE)     , INTENT(INOUT) :: td_file 
     1720      CHARACTER(LEN=*), INTENT(IN   ), OPTIONAL :: cd_dimorder 
    17851721 
    17861722      ! local variable 
    17871723      INTEGER(i4), DIMENSION(:), ALLOCATABLE :: il_value 
     1724 
     1725      CHARACTER(LEN=lc)                      :: cl_dimorder 
    17881726 
    17891727      TYPE(TVAR)                             :: tl_var 
     
    17941732      INTEGER(i4) :: ji 
    17951733      INTEGER(i4) :: jj 
    1796       !---------------------------------------------------------------- 
     1734      INTEGER(i4) :: jvar 
     1735      !---------------------------------------------------------------- 
     1736 
     1737      cl_dimorder='xyzt' 
     1738      IF( PRESENT(cd_dimorder) ) cl_dimorder=TRIM(cd_dimorder) 
    17971739 
    17981740      ! check if file opened 
     
    18001742 
    18011743         CALL logger_error( & 
    1802          &  " WRITE FILE: no id associated to file "//TRIM(td_file%c_name)) 
     1744         &  " IOM CDF WRITE FILE: no id associated to file "//TRIM(td_file%c_name)) 
    18031745 
    18041746      ELSE 
    18051747         IF( td_file%l_wrt )THEN 
    18061748 
    1807             ! delete dummy variable 
    1808             CALL file_del_var( td_file, 'no0d' ) 
    1809             CALL file_del_var( td_file, 'no1d' ) 
    1810             CALL file_del_var( td_file, 'no2d' ) 
    1811             CALL file_del_var( td_file, 'no3d' ) 
     1749            ! remove dummy variable 
     1750            CALL file_del_var(td_file,'no0d') 
     1751            CALL file_del_var(td_file,'no1d') 
     1752            CALL file_del_var(td_file,'no2d') 
     1753            CALL file_del_var(td_file,'no3d') 
    18121754 
    18131755            DO ji = 1, td_file%i_nvar 
     
    18161758 
    18171759            ! save usefull dimension 
    1818             tl_dim(:)=var_max_dim(td_file%t_var(:)) 
    1819  
    1820             DO ji=1,ip_maxdim 
    1821                IF( tl_dim(ji)%l_use ) CALL file_move_dim(td_file, tl_dim(ji)) 
    1822             ENDDO 
     1760            IF( ASSOCIATED(td_file%t_var) )THEN 
     1761               tl_dim(:)=var_max_dim(td_file%t_var(:)) 
     1762 
     1763               DO ji=1,ip_maxdim 
     1764                  IF( tl_dim(ji)%l_use ) CALL file_move_dim(td_file, tl_dim(ji)) 
     1765               ENDDO 
     1766               ! clean 
     1767               CALL dim_clean(tl_dim(:)) 
     1768            ENDIF 
     1769 
     1770            ! change dimension order 
     1771            IF( TRIM(cl_dimorder) /= 'xyzt' )THEN 
     1772               CALL dim_reorder(td_file%t_dim(:),TRIM(cl_dimorder)) 
     1773               DO jvar=1,td_file%i_nvar 
     1774                  CALL logger_debug("VAR REORDER: "//TRIM(td_file%t_var(jvar)%c_name)) 
     1775                  CALL var_reorder(td_file%t_var(jvar),TRIM(cl_dimorder)) 
     1776               ENDDO 
     1777            ENDIF 
    18231778 
    18241779            ! write dimension in file 
     
    18361791 
    18371792                  DEALLOCATE(il_value) 
     1793 
     1794                  ! do not use FillValue for dimension variable 
     1795                  CALL var_del_att(tl_var, "_FillValue") 
    18381796                    
    18391797                  CALL iom_cdf__write_var(td_file,tl_var) 
     1798                  ! clean 
    18401799                  CALL var_clean(tl_var) 
    18411800 
     
    18561815 
    18571816            CALL logger_error( & 
    1858             &  " WRITE FILE: try to write in file "//TRIM(td_file%c_name)//& 
     1817            &  "IOM CDF WRITE FILE: try to write in file "//TRIM(td_file%c_name)//& 
    18591818            &  ", not opened in write mode") 
    18601819 
     
    18631822 
    18641823   END SUBROUTINE iom_cdf_write_file 
    1865    !> @endcode 
    18661824   !------------------------------------------------------------------- 
    18671825   !> @brief This subroutine write one dimension in an opened netcdf  
     
    18691827   ! 
    18701828   !> @author J.Paul 
    1871    !> - Nov, 2013- Initial Version 
    1872    ! 
    1873    !> @param[inout] td_file : file structure 
    1874    !> @param[inout] td_dim : dimension structure 
    1875    !------------------------------------------------------------------- 
    1876    !> @code 
     1829   !> @date November, 2013 - Initial Version 
     1830   ! 
     1831   !> @param[inout] td_file   file structure 
     1832   !> @param[inout] td_dim    dimension structure 
     1833   !------------------------------------------------------------------- 
    18771834   SUBROUTINE iom_cdf__write_dim(td_file, td_dim) 
    18781835      IMPLICIT NONE 
     
    18871844      IF( .NOT. td_file%l_def )THEN 
    18881845 
    1889          CALL logger_debug( & 
    1890          &  " WRITE FILE DIM: Enter define mode, file "//TRIM(td_file%c_name)) 
     1846         CALL logger_trace( & 
     1847         &  " IOM CDF WRITE FILE DIM: Enter define mode, file "//TRIM(td_file%c_name)) 
    18911848 
    18921849         ! Enter define mode 
    18931850         il_status=NF90_REDEF(td_file%i_id) 
    1894          CALL iom_cdf__check(il_status) 
     1851         CALL iom_cdf__check(il_status,"IOM CDF WRITE FILE DIM: ") 
    18951852 
    18961853         td_file%l_def=.TRUE. 
     
    19011858         IF( td_dim%l_uld )THEN 
    19021859            ! write unlimited dimension 
    1903             CALL logger_debug( & 
    1904             &  " WRITE FILE DIM: write unlimited dimension "//& 
     1860            CALL logger_trace( & 
     1861            &  "IOM CDF WRITE FILE DIM: write unlimited dimension "//& 
    19051862            &  TRIM(td_dim%c_name)//" in file "//TRIM(td_file%c_name)) 
    19061863 
    19071864            il_status=NF90_DEF_DIM(td_file%i_id, fct_upper(td_dim%c_sname), & 
    19081865            &                      NF90_UNLIMITED, td_dim%i_id) 
    1909             CALL iom_cdf__check(il_status) 
     1866            CALL iom_cdf__check(il_status,"IOM CDF WRITE FILE DIM: ") 
    19101867 
    19111868         ELSE 
    19121869            ! write not unlimited dimension 
    19131870            CALL logger_debug( & 
    1914             &  " WRITE FILE DIM: write dimension "//TRIM(td_dim%c_name)//& 
     1871            &  "IOM CDF WRITE FILE DIM: write dimension "//TRIM(td_dim%c_name)//& 
    19151872            &  " in file "//TRIM(td_file%c_name)) 
    19161873             
    19171874            il_status=NF90_DEF_DIM(td_file%i_id, fct_upper(td_dim%c_sname), & 
    19181875            &                      td_dim%i_len, td_dim%i_id) 
    1919             CALL iom_cdf__check(il_status) 
     1876            CALL iom_cdf__check(il_status,"IOM CDF WRITE FILE DIM: ") 
    19201877 
    19211878         ENDIF 
     
    19231880 
    19241881   END SUBROUTINE iom_cdf__write_dim 
    1925    !> @endcode    
    19261882   !------------------------------------------------------------------- 
    19271883   !> @brief This subroutine write a variable attribute in 
     
    19291885   ! 
    19301886   !> @author J.Paul 
    1931    !> - Nov, 2013- Initial Version 
    1932    ! 
    1933    !> @param[inout] td_file : file structure 
    1934    !> @param[in] id_varid : variable id. use NF90_GLOBAL to write global attribute 
    1935    !> in a file 
    1936    !> @param[in] td_att : attribute structure 
    1937    !------------------------------------------------------------------- 
    1938    !> @code 
     1887   !> @date November, 2013 - Initial Version 
     1888   ! 
     1889   !> @param[inout] td_file   file structure 
     1890   !> @param[in] id_varid     variable id. use NF90_GLOBAL to write  
     1891   !> global attribute in a file 
     1892   !> @param[in] td_att       attribute structure 
     1893   !------------------------------------------------------------------- 
    19391894   SUBROUTINE iom_cdf__write_att(td_file, id_varid, td_att) 
    19401895      IMPLICIT NONE 
     
    19501905      IF( .NOT. td_file%l_def )THEN 
    19511906 
    1952          CALL logger_debug( & 
    1953          &  " WRITE FILE ATT: Enter define mode, file "//TRIM(td_file%c_name)) 
     1907         CALL logger_trace( & 
     1908         &  "IOM CDF WRITE FILE ATT: Enter define mode, file "//TRIM(td_file%c_name)) 
    19541909 
    19551910         ! Enter define mode 
    19561911         il_status=NF90_REDEF(td_file%i_id) 
    1957          CALL iom_cdf__check(il_status) 
     1912         CALL iom_cdf__check(il_status,"IOM CDF WRITE FILE ATT: ") 
    19581913 
    19591914         td_file%l_def=.TRUE. 
     
    19621917 
    19631918      !! put attribute value 
    1964       CALL logger_debug( & 
    1965       &  " WRITE FILE ATT: write attribute "//TRIM(td_att%c_name)//& 
     1919      CALL logger_trace( & 
     1920      &  "IOM CDF WRITE FILE ATT: write attribute "//TRIM(td_att%c_name)//& 
    19661921      &  " of variable "//TRIM(fct_str(id_varid))//& 
    19671922      &  " in file "//TRIM(td_file%c_name)) 
     
    19721927            il_status = NF90_PUT_ATT(td_file%i_id, id_varid, & 
    19731928            &  td_att%c_name, td_att%c_value ) 
    1974             CALL iom_cdf__check(il_status) 
     1929            CALL iom_cdf__check(il_status,"IOM CDF WRITE FILE ATT: ") 
    19751930 
    19761931         CASE(NF90_BYTE, NF90_SHORT, NF90_INT, NF90_FLOAT, NF90_DOUBLE) 
     
    19781933            il_status = NF90_PUT_ATT(td_file%i_id, id_varid, & 
    19791934            &  td_att%c_name, td_att%d_value ) 
    1980             CALL iom_cdf__check(il_status) 
     1935            CALL iom_cdf__check(il_status,"IOM CDF WRITE FILE ATT: ") 
    19811936 
    19821937      END SELECT 
    19831938 
    19841939   END SUBROUTINE iom_cdf__write_att 
    1985    !> @endcode    
    1986    !------------------------------------------------------------------- 
    1987    !> @brief This subroutine write a variable in an opened netcdf file.</br/> 
    1988    ! 
    1989    !> @author J.Paul 
    1990    !> - Nov, 2013- Initial Version 
    1991    ! 
    1992    !> @param[inout] td_file : file structure 
    1993    !> @param[inout] td_var : variable structure 
    1994    !------------------------------------------------------------------- 
    1995    !> @code 
     1940   !------------------------------------------------------------------- 
     1941   !> @brief This subroutine write a variable in an opened netcdf file. 
     1942   ! 
     1943   !> @author J.Paul 
     1944   !> @date November, 2013 - Initial Version 
     1945   ! 
     1946   !> @param[inout] td_file   file structure 
     1947   !> @param[inout] td_var    variable structure 
     1948   !------------------------------------------------------------------- 
    19961949   SUBROUTINE iom_cdf__write_var(td_file, td_var) 
    19971950      IMPLICIT NONE 
     
    20021955      ! local variable 
    20031956      INTEGER(i4) :: il_status 
     1957      LOGICAL     :: ll_chg 
     1958      ! loop indices 
     1959      INTEGER(i4) :: ji 
    20041960      !---------------------------------------------------------------- 
    20051961 
    20061962      IF( .NOT. td_file%l_def )THEN 
    20071963 
    2008          CALL logger_debug( & 
    2009          &  " WRITE FILE VAR: Enter define mode, file "//TRIM(td_file%c_name)) 
     1964         CALL logger_trace( & 
     1965         &  " IOM CDF WRITE VAR: Enter define mode, file "//& 
     1966         &  TRIM(td_file%c_name)) 
    20101967 
    20111968         ! Enter define mode 
    20121969         il_status=NF90_REDEF(td_file%i_id) 
    2013          CALL iom_cdf__check(il_status) 
     1970         CALL iom_cdf__check(il_status,"IOM CDF WRITE VAR: ") 
    20141971 
    20151972         td_file%l_def=.TRUE. 
    20161973 
    20171974      ENDIF 
    2018        
     1975  
    20191976      ! check if file and variable dimension conform 
    20201977      IF( file_check_var_dim(td_file, td_var) )THEN 
     
    20231980         CALL var_check_dim(td_var) 
    20241981 
    2025          ! change fill value to NETCDF standard 
    2026          CALL var_chg_FillValue(td_var) 
     1982         ll_chg=.TRUE. 
     1983         DO ji=1,ip_maxdim 
     1984            IF( TRIM(fct_lower(cp_dimorder(ji:ji))) == & 
     1985            &   TRIM(fct_lower(td_var%c_name)) )THEN 
     1986               ll_chg=.FALSE. 
     1987               CALL logger_trace(TRIM(fct_lower(td_var%c_name))//' is var dimension') 
     1988               EXIT 
     1989            ENDIF 
     1990         ENDDO 
     1991         ! ugly patch until NEMO do not force to use 0. as FillValue  
     1992         IF( ll_chg )THEN 
     1993            ! not a dimension variable 
     1994            ! change FillValue 
     1995            SELECT CASE( TRIM(fct_lower(td_var%c_name)) ) 
     1996               CASE DEFAULT 
     1997                  CALL var_chg_FillValue(td_var,0._dp) 
     1998               CASE('nav_lon','nav_lat', & 
     1999                  & 'glamt','glamu','glamv','glamf', & 
     2000                  & 'gphit','gphiu','gphiv','gphif') 
     2001            END SELECT 
     2002         ENDIF 
    20272003 
    20282004         ! define variable in file 
     
    20312007         IF( td_file%l_def )THEN 
    20322008 
    2033             CALL logger_debug( & 
    2034             &  " WRITE FILE VAR: Leave define mode, file "//TRIM(td_file%c_name)) 
     2009            CALL logger_trace( & 
     2010            &  " IOM CDF WRITE VAR: Leave define mode, file "//& 
     2011            &  TRIM(td_file%c_name)) 
    20352012 
    20362013            ! Leave define mode 
    20372014            il_status=NF90_ENDDEF(td_file%i_id) 
    2038             CALL iom_cdf__check(il_status) 
     2015            CALL iom_cdf__check(il_status,"IOM CDF WRITE VAR: ") 
    20392016 
    20402017            td_file%l_def=.FALSE. 
     
    20502027 
    20512028   END SUBROUTINE iom_cdf__write_var 
    2052    !> @endcode    
    20532029   !------------------------------------------------------------------- 
    20542030   !> @brief This function define variable in an opened netcdf file. 
    20552031   ! 
    20562032   !> @author J.Paul 
    2057    !> - Nov, 2013- Initial Version 
    2058    ! 
    2059    !> @param[in] td_file : file structure 
    2060    !> @param[in] td_var : variable structure 
     2033   !> @date November, 2013 - Initial Version 
     2034   ! 
     2035   !> @param[in] td_file   file structure 
     2036   !> @param[in] td_var   variable structure 
    20612037   !> @return  variable id 
    20622038   !------------------------------------------------------------------- 
    2063    !> @code 
    20642039   INTEGER(i4) FUNCTION iom_cdf__write_var_def(td_file, td_var) 
    20652040      IMPLICIT NONE 
     
    20702045      ! local variable 
    20712046      INTEGER(i4)                       :: il_status 
     2047      INTEGER(i4)                       :: il_ind 
    20722048      INTEGER(i4), DIMENSION(ip_maxdim) :: il_dimid 
     2049 
     2050      TYPE(TVAR)                        :: tl_var 
    20732051 
    20742052      ! loop indices 
     
    20772055      !---------------------------------------------------------------- 
    20782056 
    2079       CALL logger_debug( & 
    2080       &  " WRITE FILE VAR DEF: get dimension to be used for variable "//& 
    2081       &  TRIM(td_var%c_name)//" in file "//TRIM(td_file%c_name)) 
    2082  
    2083       IF( ALL( .NOT. td_var%t_dim(:)%l_use ) )THEN 
     2057      ! copy structure 
     2058      tl_var=var_copy(td_var) 
     2059 
     2060      ! forced to use float type 
     2061      IF( tl_var%d_unf /= 1. .AND. tl_var%i_type==NF90_SHORT )THEN 
     2062         tl_var%i_type=NF90_FLOAT 
     2063      ENDIF 
     2064 
     2065      IF( ALL( .NOT. tl_var%t_dim(:)%l_use ) )THEN 
     2066         CALL logger_debug( & 
     2067         &  "IOM CDF WRITE VAR DEF scalar: define variable "//& 
     2068         &  TRIM(tl_var%c_name)//" in file "//TRIM(td_file%c_name)) 
    20842069         ! scalar value 
    2085          il_status = NF90_DEF_VAR(td_file%i_id, TRIM(td_var%c_name), & 
    2086          &                        td_var%i_type, varid=iom_cdf__write_var_def)  
    2087          CALL iom_cdf__check(il_status) 
     2070         il_status = NF90_DEF_VAR(td_file%i_id, TRIM(tl_var%c_name), & 
     2071         &                        tl_var%i_type, varid=iom_cdf__write_var_def)  
     2072         CALL iom_cdf__check(il_status,"IOM CDF WRITE VAR DEF: ") 
    20882073      ELSE 
    20892074 
     
    20932078         ! reorder dimension, so unused dimension won't be written 
    20942079         DO ji = 1,  ip_maxdim 
    2095             IF( td_var%t_dim(ji)%l_use )THEN 
     2080            IF( tl_var%t_dim(ji)%l_use )THEN 
    20962081               jj=jj+1 
    2097                CALL logger_debug(" get dim id for dimension "//TRIM(td_var%t_dim(ji)%c_name)) 
    2098                il_dimid(jj)=dim_get_id(td_file%t_dim(:),td_var%t_dim(ji)%c_name) 
     2082               il_dimid(jj)=dim_get_id(td_file%t_dim(:),tl_var%t_dim(ji)%c_name) 
    20992083            ENDIF 
    21002084         ENDDO 
    21012085 
    21022086         CALL logger_debug( & 
    2103          &  " WRITE FILE VAR DEF: define dimension to be used for variable "//& 
    2104          &  TRIM(td_var%c_name)//" in file "//TRIM(td_file%c_name)) 
     2087         &  "IOM CDF WRITE VAR DEF: define dimension to be used for variable "//& 
     2088         &  TRIM(tl_var%c_name)//" in file "//TRIM(td_file%c_name)) 
    21052089 
    21062090         DO ji=1,jj 
    2107             CALL logger_debug(" WRITE FILE VAR DEF: dimid "//TRIM(fct_str(il_dimid(ji))) ) 
     2091            CALL logger_debug("IOM CDF WRITE VAR DEF: dimid "//TRIM(fct_str(il_dimid(ji))) ) 
    21082092         ENDDO 
    2109          il_status = NF90_DEF_VAR(td_file%i_id, TRIM(td_var%c_name),     & 
    2110          &                        td_var%i_type,                         & 
     2093 
     2094         il_status = NF90_DEF_VAR(td_file%i_id, TRIM(tl_var%c_name),     & 
     2095         &                        tl_var%i_type,                         & 
    21112096         &                        il_dimid(1:jj),                        & 
    21122097         &                        varid=iom_cdf__write_var_def           ) 
    2113          CALL iom_cdf__check(il_status) 
    2114       ENDIF 
    2115  
    2116       DO ji = 1, td_var%i_natt 
     2098         CALL iom_cdf__check(il_status,"IOM CDF WRITE VAR DEF: ") 
     2099      ENDIF 
     2100 
     2101      ! remove unuseful attribute 
     2102      il_ind=att_get_index( tl_var%t_att(:), "ew_overlap" ) 
     2103      IF( il_ind /= 0 )THEN 
     2104         IF( tl_var%t_att(il_ind)%d_value(1) == -1 )THEN 
     2105            CALL var_del_att(tl_var, tl_var%t_att(il_ind)) 
     2106         ENDIF 
     2107      ENDIF 
     2108 
     2109      DO ji = 1, tl_var%i_natt 
    21172110         CALL logger_debug( & 
    2118          &  " WRITE FILE VAR DEF: put attribute "//TRIM(td_var%t_att(ji)%c_name)//& 
    2119          &  " for variable "//TRIM(td_var%c_name)//& 
     2111         &  " IOM CDF WRITE VAR DEF: put attribute "//TRIM(tl_var%t_att(ji)%c_name)//& 
     2112         &  " for variable "//TRIM(tl_var%c_name)//& 
    21202113         &  " in file "//TRIM(td_file%c_name) ) 
    21212114 
    2122          IF( td_var%t_att(ji)%i_type == NF90_CHAR )THEN 
    2123             !IF( TRIM(td_var%t_att(ji)%c_value) /= 'unknown' )THEN 
    2124             IF( TRIM(td_var%t_att(ji)%c_value) /= '' )THEN 
     2115         ! forced FillValue to have same type than variable 
     2116         IF( TRIM(tl_var%t_att(ji)%c_name) == '_FillValue' )THEN 
     2117            tl_var%t_att(ji)%i_type=tl_var%i_type 
     2118         ENDIF 
     2119 
     2120         IF( tl_var%t_att(ji)%i_type == NF90_CHAR )THEN 
     2121            IF( TRIM(tl_var%t_att(ji)%c_value) /= '' )THEN 
    21252122               il_status = NF90_PUT_ATT(td_file%i_id, iom_cdf__write_var_def, & 
    2126                &                        TRIM(td_var%t_att(ji)%c_name),        & 
    2127                &                        TRIM(td_var%t_att(ji)%c_value)        ) 
    2128                CALL iom_cdf__check(il_status) 
     2123               &                        TRIM(tl_var%t_att(ji)%c_name),        & 
     2124               &                        TRIM(tl_var%t_att(ji)%c_value)        ) 
     2125               CALL iom_cdf__check(il_status,"IOM CDF WRITE VAR DEF: ") 
    21292126            ENDIF 
    21302127         ELSE 
    2131             SELECT CASE(td_var%t_att(ji)%i_type) 
     2128            SELECT CASE(tl_var%t_att(ji)%i_type) 
    21322129               CASE(NF90_BYTE) 
    21332130                  il_status = NF90_PUT_ATT(td_file%i_id,                   & 
    21342131                  &                        iom_cdf__write_var_def,         & 
    2135                   &                        TRIM(td_var%t_att(ji)%c_name),  & 
    2136                   &                        INT(td_var%t_att(ji)%d_value(:),i1)) 
     2132                  &                        TRIM(tl_var%t_att(ji)%c_name),  & 
     2133                  &                        INT(tl_var%t_att(ji)%d_value(:),i1)) 
    21372134               CASE(NF90_SHORT) 
    21382135                  il_status = NF90_PUT_ATT(td_file%i_id,                   & 
    21392136                  &                        iom_cdf__write_var_def,         & 
    2140                   &                        TRIM(td_var%t_att(ji)%c_name),  & 
    2141                   &                        INT(td_var%t_att(ji)%d_value(:),i2)) 
     2137                  &                        TRIM(tl_var%t_att(ji)%c_name),  & 
     2138                  &                        INT(tl_var%t_att(ji)%d_value(:),i2)) 
    21422139               CASE(NF90_INT) 
    21432140                  il_status = NF90_PUT_ATT(td_file%i_id,                   & 
    21442141                  &                        iom_cdf__write_var_def,         & 
    2145                   &                        TRIM(td_var%t_att(ji)%c_name),  & 
    2146                   &                        INT(td_var%t_att(ji)%d_value(:),i4)) 
     2142                  &                        TRIM(tl_var%t_att(ji)%c_name),  & 
     2143                  &                        INT(tl_var%t_att(ji)%d_value(:),i4)) 
    21472144               CASE(NF90_FLOAT) 
    21482145                  il_status = NF90_PUT_ATT(td_file%i_id,                   & 
    21492146                  &                        iom_cdf__write_var_def,         & 
    2150                   &                        TRIM(td_var%t_att(ji)%c_name),  & 
    2151                   &                        REAL(td_var%t_att(ji)%d_value(:),sp)) 
     2147                  &                        TRIM(tl_var%t_att(ji)%c_name),  & 
     2148                  &                        REAL(tl_var%t_att(ji)%d_value(:),sp)) 
    21522149               CASE(NF90_DOUBLE) 
    21532150                  il_status = NF90_PUT_ATT(td_file%i_id,                   & 
    21542151                  &                        iom_cdf__write_var_def,         & 
    2155                   &                        TRIM(td_var%t_att(ji)%c_name),  & 
    2156                   &                        REAL(td_var%t_att(ji)%d_value(:),dp)) 
    2157                END SELECT 
    2158             CALL iom_cdf__check(il_status) 
     2152                  &                        TRIM(tl_var%t_att(ji)%c_name),  & 
     2153                  &                        REAL(tl_var%t_att(ji)%d_value(:),dp)) 
     2154            END SELECT 
     2155            CALL iom_cdf__check(il_status,"IOM CDF WRITE VAR DEF: ") 
    21592156         ENDIF 
    21602157      ENDDO 
    21612158 
    21622159   END FUNCTION iom_cdf__write_var_def 
    2163    !> @endcode 
    21642160   !------------------------------------------------------------------- 
    21652161   !> @brief This subroutine put variable value in an opened netcdf file. 
     
    21672163   !> @details 
    21682164   !> The variable is written in the type define in variable structure. 
    2169    !> Only dimension used are printed, and fillValue in table are 
     2165   !> Only dimension used are printed, and fillValue in array are 
    21702166   !> replaced by default fill values defined in module netcdf for each type.  
    21712167   ! 
    21722168   !> @author J.Paul 
    2173    !> - Nov, 2013- Initial Version 
    2174    ! 
    2175    !> @param[in] td_file : file structure 
    2176    !> @param[in] td_var : variable structure 
    2177    !------------------------------------------------------------------- 
    2178    !> @code 
     2169   !> @date November, 2013 - Initial Version 
     2170   !> @date June, 2015 
     2171   !> - reuse scale factor and offset, before writing variable 
     2172   ! 
     2173   !> @param[in] td_file   file structure 
     2174   !> @param[in] td_var    variable structure 
     2175   !------------------------------------------------------------------- 
    21792176   SUBROUTINE iom_cdf__write_var_value(td_file, td_var) 
    21802177      IMPLICIT NONE 
     
    21942191 
    21952192      ! check which dimension use 
    2196       CALL logger_debug( & 
    2197       &  " WRITE FILE VAR VALUE: get dimension to be used for variable "//& 
     2193      CALL logger_trace( & 
     2194      &  "IOM CDF WRITE VAR VALUE: get dimension to be used for variable "//& 
    21982195      &  TRIM(td_var%c_name)//" in file "//TRIM(td_file%c_name)) 
    2199  
     2196    
     2197      ! use scale factor and offset 
     2198      WHERE( td_var%d_value(:,:,:,:) /= td_var%d_fill ) 
     2199         td_var%d_value(:,:,:,:) = & 
     2200         &  (td_var%d_value(:,:,:,:)-td_var%d_ofs)/td_var%d_scf 
     2201      END WHERE 
     2202       
    22002203      jj=0 
    22012204      DO ji = 1, ip_maxdim 
    22022205         IF( td_var%t_dim(ji)%l_use )THEN 
    22032206            jj=jj+1 
    2204             !il_order(ji)=jj 
    2205             !il_shape(ji)=td_var%t_dim(jj)%i_len 
    22062207            il_order(jj)=ji 
    22072208            il_shape(jj)=td_var%t_dim(ji)%i_len 
     
    22122213         IF( .NOT. td_var%t_dim(ji)%l_use )THEN 
    22132214            jj=jj+1 
    2214             !il_order(ji)=jj 
    2215             !il_shape(ji)=td_var%t_dim(jj)%i_len 
    22162215            il_order(jj)=ji 
    22172216            il_shape(jj)=td_var%t_dim(ji)%i_len 
     
    22212220      ALLOCATE( dl_value( il_shape(1),il_shape(2),il_shape(3),il_shape(4) ) ) 
    22222221 
    2223       ! reshape table, so unused dimension won't be written 
     2222      ! reshape array, so unused dimension won't be written 
    22242223      dl_value(:,:,:,:)=RESHAPE(source=td_var%d_value(:,:,:,:),& 
    22252224      &                         SHAPE = il_shape(:), & 
     
    22272226 
    22282227      ! put value 
    2229       CALL logger_debug( & 
    2230       &  " WRITE FILE VAR VALUE: put "//TRIM(td_var%c_name)//" value "//& 
     2228      CALL logger_trace( & 
     2229      &  "IOM CDF WRITE VAR VALUE: put "//TRIM(td_var%c_name)//" value "//& 
    22312230      &  "in file "//TRIM(td_file%c_name)) 
    22322231 
    22332232      il_status = NF90_PUT_VAR( td_file%i_id, td_var%i_id, dl_value(:,:,:,:)) 
    2234       CALL iom_cdf__check(il_status) 
     2233      CALL iom_cdf__check(il_status,"IOM CDF WRITE VAR VALUE: ") 
    22352234 
    22362235      DEALLOCATE( dl_value ) 
    22372236 
    22382237   END SUBROUTINE iom_cdf__write_var_value 
    2239    !> @endcode 
    22402238END MODULE iom_cdf 
Note: See TracChangeset for help on using the changeset viewer.