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 5213 for branches/2015/dev_r5021_UKMO1_CICE_coupling/NEMOGCM/TOOLS/SIREN/src/iom.f90 – NEMO

Ignore:
Timestamp:
2015-04-15T17:03:58+02:00 (9 years ago)
Author:
davestorkey
Message:

Merge in trunk changes up to rev 5107.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5021_UKMO1_CICE_coupling/NEMOGCM/TOOLS/SIREN/src/iom.f90

    r4213 r5213  
    66! 
    77! DESCRIPTION: 
    8 !> @brief Input/Output manager :  Library to read input files<br/> 
     8!> @brief Input/Output manager :  Library to read input files 
    99!> 
    1010!> @details 
     11!>    to open file:<br/> 
     12!> @code 
     13!>    CALL iom_open(td_file) 
     14!> @endcode 
     15!>       - td_file is file structure 
     16!> 
     17!>    to create file:<br/> 
     18!> @code 
     19!>    CALL iom_create(td_file) 
     20!> @endcode 
     21!>       - td_file is file structure 
    1122!>  
    12 !>    to open file:<br/> 
    13 !>    CALL iom_open(td_file) 
    14 !>       - td_file is file structure 
    15 !> 
    1623!>    to write in file:<br/> 
     24!> @code 
    1725!>    CALL  iom_write_file(td_file) 
     26!> @endcode 
    1827!> 
    1928!>    to close file:<br/> 
     29!> @code 
    2030!>    CALL iom_close(tl_file) 
     31!> @endcode 
    2132!> 
    2233!>    to read one dimension in file:<br/> 
    23 !>    tl_dim = iom_read_dim(tl_file, id_dimid)<br/> 
     34!> @code 
     35!>    tl_dim = iom_read_dim(tl_file, id_dimid) 
     36!> @endcode 
    2437!>    or<br/> 
    25 !>    tl_dim = iom_read_dim(tl_file, cd_name)<br/> 
     38!> @code 
     39!>    tl_dim = iom_read_dim(tl_file, cd_name) 
     40!> @endcode 
    2641!>       - id_dimid is dimension id 
    2742!>       - cd_name is dimension name 
    2843!> 
    2944!>    to read variable or global attribute in file:<br/> 
    30 !>    tl_att = iom_read_att(tl_file, id_varid, id_attid)<br/> 
    31 !>    or<br/> 
    32 !>    tl_att = iom_read_att(tl_file, id_varid, cd_attname)<br/> 
    33 !>    or<br/> 
    34 !>    tl_att = iom_read_att(tl_file, cd_varname, cd_attid, [cd_stdname])<br/> 
    35 !>    or<br/> 
    36 !>    tl_att = iom_read_att(tl_file, cd_varname, cd_attname, cd_stdname) 
     45!> @code 
     46!>    tl_att = iom_read_att(tl_file, id_varid, id_attid) 
     47!> @endcode 
     48!>    or 
     49!> @code 
     50!>    tl_att = iom_read_att(tl_file, id_varid, cd_attname) 
     51!> @endcode 
     52!>    or 
     53!> @code 
     54!>    tl_att = iom_read_att(tl_file, cd_varname, id_attid) 
     55!> @endcode 
     56!>    or 
     57!> @code 
     58!>    tl_att = iom_read_att(tl_file, cd_varname, cd_attname) 
     59!> @endcode 
    3760!>       - id_varid is variable id 
    3861!>       - id_attid is attribute id 
    3962!>       - cd_attname is attribute name 
    40 !>       - cd_varname is variable name 
    41 !>       - cd_stdname is variable standard name (optional) 
     63!>       - cd_varname is variable name or standard name 
    4264!>     
    4365!>    to read one variable in file:<br/> 
    44 !>    tl_var = iom_read_var(td_file, id_varid, [id_start, id_count])<br/> 
    45 !>    or<br/> 
    46 !>    tl_var = iom_read_var(td_file, cd_name, [id_start, [id_count,]] [cd_stdname]) 
     66!> @code 
     67!>    tl_var = iom_read_var(td_file, id_varid, [id_start, id_count]) 
     68!> @endcode 
     69!>    or 
     70!> @code 
     71!>    tl_var = iom_read_var(td_file, cd_name, [id_start, [id_count,]]) 
     72!> @endcode 
    4773!>       - id_varid is variabale id 
    48 !>       - cd_name is variabale name 
    49 !>       - id_start is a integer(4) 1D table of index from which the data  
    50 !>          values will be read (optional) 
    51 !>       - id_count is a integer(4) 1D table of the number of indices selected 
    52 !>          along each dimension (optional) 
    53 !>       - cd_stdname is variable standard name (optional) 
     74!>       - cd_name is variabale name or standard name. 
     75!>       - id_start is a integer(4) 1D array of index from which the data  
     76!>          values will be read [optional] 
     77!>       - id_count is a integer(4) 1D array of the number of indices selected 
     78!>          along each dimension [optional] 
    5479!> 
    5580!> @author 
    5681!> J.Paul 
    5782! REVISION HISTORY: 
    58 !> @date Nov, 2013 - Initial Version 
    59 ! 
    60 !> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     83!> @date November, 2013 - Initial Version 
     84!> 
    6185!> @todo 
    6286!> - see lbc_lnk 
    6387!> - see goup netcdf4 
    64 !> - add iom_fill_var_value : complete tl_file avec valeur de la variable 
     88!> 
     89!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    6590!---------------------------------------------------------------------- 
    6691MODULE iom 
    6792   USE netcdf                          ! nf90 library 
     93   USE global                          ! global parameter 
    6894   USE kind                            ! F90 kind parameter 
    6995   USE fct                             ! basic useful function 
    70    USE logger                             ! log file manager 
     96   USE logger                          ! log file manager 
    7197   USE dim                             ! dimension manager 
    7298   USE att                             ! attribute manager 
     
    76102   USE iom_rstdimg                     ! restart dimg I/O manager 
    77103   IMPLICIT NONE 
    78    PRIVATE 
    79104   ! NOTE_avoid_public_variables_if_possible 
    80105 
     
    86111   PUBLIC :: iom_read_att    !< read one attribute in an opened file 
    87112   PUBLIC :: iom_read_var    !< read one variable  in an opened file    
    88    PUBLIC :: iom_fill_var    !< fill variable value 
    89113   PUBLIC :: iom_write_file  !< write file structure contents in an opened file 
    90    ! PUBLIC :: iom_get_mpp     ! get sub domain decomposition  
    91  
    92                                           !< read variable or global attribute in an opened file 
    93    PRIVATE :: iom__read_var_name_att_id   !< given variable name or standard name and attribute id. 
    94    PRIVATE :: iom__read_var_id_att_id     !< given variable id and attribute id. 
    95    PRIVATE :: iom__read_var_name_att_name !< given variable name or standard name, and attribute name. 
    96    PRIVATE :: iom__read_var_id_att_name   !< given variable id and attribute name. 
    97  
    98    PRIVATE :: iom__read_dim_id            !< read one dimension in an opened file, given dimension id. 
    99    PRIVATE :: iom__read_dim_name          !< read one dimension in an opened netcdf file, given dimension name. 
    100    PRIVATE :: iom__read_var_id            !< read variable value in an opened file, given variable id. 
    101    PRIVATE :: iom__read_var_name          !< read variable value in an opened file, given variable name or standard name. 
    102    PRIVATE :: iom__fill_var_id            !< fill variable value in an opened file, given variable id 
    103    PRIVATE :: iom__fill_var_name          !< fill variable value in an opened file, given variable name 
    104    PRIVATE :: iom__fill_var_all           !< fill all variable value in an opened file 
     114 
     115                                          ! read variable or global attribute in an opened file 
     116   PRIVATE :: iom__read_att_varname_id   ! given variable name or standard name and attribute id. 
     117   PRIVATE :: iom__read_att_varid_id     ! given variable id and attribute id. 
     118   PRIVATE :: iom__read_att_varname_name ! given variable name or standard name, and attribute name. 
     119   PRIVATE :: iom__read_att_varid_name   ! given variable id and attribute name. 
     120 
     121   PRIVATE :: iom__read_dim_id            ! read one dimension in an opened file, given dimension id. 
     122   PRIVATE :: iom__read_dim_name          ! read one dimension in an opened netcdf file, given dimension name. 
     123   PRIVATE :: iom__read_var_id            ! read variable value in an opened file, given variable id. 
     124   PRIVATE :: iom__read_var_name          ! read variable value in an opened file, given variable name or standard name. 
    105125 
    106126   INTERFACE iom_read_var 
     
    109129   END INTERFACE iom_read_var 
    110130 
    111    INTERFACE iom_fill_var 
    112       MODULE PROCEDURE iom__fill_var_id 
    113       MODULE PROCEDURE iom__fill_var_name 
    114       MODULE PROCEDURE iom__fill_var_all 
    115    END INTERFACE  
    116  
    117131   INTERFACE iom_read_dim 
    118132      MODULE PROCEDURE iom__read_dim_id 
     
    121135 
    122136   INTERFACE iom_read_att    !< read variable or global attribute in an opened file 
    123       MODULE PROCEDURE iom__read_var_name_att_id   !< given variable name or standard name and attribute id. 
    124       MODULE PROCEDURE iom__read_var_id_att_id     !< given variable id and attribute id. 
    125       MODULE PROCEDURE iom__read_var_name_att_name !< given variable name or standard name, and attribute name. 
    126       MODULE PROCEDURE iom__read_var_id_att_name   !< given variable id and attribute name. 
     137      MODULE PROCEDURE iom__read_att_varname_id   !< given variable name or standard name and attribute id. 
     138      MODULE PROCEDURE iom__read_att_varid_id     !< given variable id and attribute id. 
     139      MODULE PROCEDURE iom__read_att_varname_name !< given variable name or standard name, and attribute name. 
     140      MODULE PROCEDURE iom__read_att_varid_name   !< given variable id and attribute name. 
    127141   END INTERFACE iom_read_att 
    128142 
    129143CONTAINS 
    130144   !------------------------------------------------------------------- 
    131    !> @brief This function open a file in read or write mode<br/> 
     145   !> @brief This function open a file in read or write mode 
     146   !> @details 
    132147   !> If try to open a file in write mode that did not exist, create it.<br/> 
    133148   !>  
    134    !> If file already exist, get information about: 
     149   !> If file exist, get information about: 
    135150   !> - the number of variables 
    136151   !> - the number of dimensions 
     
    141156   !> 
    142157   !> @author J.Paul 
    143    !> - Nov, 2013- Initial Version 
    144    ! 
    145    !> @param[inout] td_file : file structure 
    146    !------------------------------------------------------------------- 
    147    !> @code 
     158   !> - November, 2013- Initial Version 
     159   ! 
     160   !> @param[inout] td_file file structure 
     161   !------------------------------------------------------------------- 
    148162   SUBROUTINE iom_open(td_file) 
    149163      IMPLICIT NONE 
     
    163177            CALL iom_rstdimg_open(td_file) 
    164178         CASE DEFAULT 
    165             CALL logger_error("OPEN: unknow type : "//TRIM(td_file%c_name)) 
     179            CALL logger_error("IOM OPEN: unknow type : "//TRIM(td_file%c_name)) 
    166180 
    167181      END SELECT 
    168182 
    169183   END SUBROUTINE iom_open 
    170    !> @endcode 
    171    !------------------------------------------------------------------- 
    172    !> @brief This function create a file<br/> 
     184   !------------------------------------------------------------------- 
     185   !> @brief This function create a file. 
    173186   !>  
    174187   !> @author J.Paul 
    175    !> - Nov, 2013- Initial Version 
    176    ! 
    177    !> @param[inout] td_file : file structure 
    178    !------------------------------------------------------------------- 
    179    !> @code 
     188   !> - November, 2013- Initial Version 
     189   ! 
     190   !> @param[inout] td_file file structure 
     191   !------------------------------------------------------------------- 
    180192   SUBROUTINE iom_create(td_file) 
    181193      IMPLICIT NONE 
     
    202214            CALL iom_rstdimg_open(td_file) 
    203215         CASE DEFAULT 
    204             CALL logger_error( "CREATE: can't create file "//& 
     216            CALL logger_error( "IOM CREATE: can't create file "//& 
    205217            &               TRIM(td_file%c_name)//": type unknown " ) 
    206218      END SELECT 
    207219 
    208220   END SUBROUTINE iom_create 
    209    !> @endcode 
    210221   !------------------------------------------------------------------- 
    211222   !> @brief This subroutine close file 
    212223   !> 
    213224   !> @author J.Paul 
    214    !> - Nov, 2013- Initial Version 
    215    ! 
    216    !> @param[inout] td_file : file structure 
    217    !------------------------------------------------------------------- 
    218    !> @code 
     225   !> - November, 2013- Initial Version 
     226   ! 
     227   !> @param[inout] td_file file structure 
     228   !------------------------------------------------------------------- 
    219229   SUBROUTINE iom_close(td_file) 
    220230      IMPLICIT NONE 
     
    230240            CALL iom_rstdimg_close(td_file) 
    231241         CASE DEFAULT 
    232             CALL logger_error( " CLOSE: can't close file "//& 
     242            CALL logger_error( "IOM CLOSE: can't close file "//& 
    233243            &               TRIM(td_file%c_name)//": type unknown " ) 
    234244      END SELECT 
    235245 
    236246   END SUBROUTINE iom_close 
    237    !> @endcode 
    238247   !------------------------------------------------------------------- 
    239248   !> @brief This function read attribute (of variable or global) in an opened  
    240249   !> file, given variable name or standard name and attribute id. 
    241    !> to get global attribute use 'GLOBAL' as variable name  
    242    !> 
    243    !> To check only standard name of the variable, put variable name to '' 
    244    ! 
    245    !> @author J.Paul 
    246    !> - Nov, 2013- Initial Version 
    247    ! 
    248    !> @param[in] td_file : file structure 
    249    !> @param[in] cd_varname : variable name. use 'GLOBAL' to read global  
     250   !> @details 
     251   !>  - to get global attribute use 'GLOBAL' as variable name.  
     252   ! 
     253   !> @author J.Paul 
     254   !> - November, 2013- Initial Version 
     255   ! 
     256   !> @param[in] td_file      file structure 
     257   !> @param[in] cd_varname   variable name. use 'GLOBAL' to read global  
    250258   !> attribute in a file 
    251    !> @param[in] id_attid : attribute id 
    252    !> @param[in] cd_stdname : variable standard name 
     259   !> @param[in] id_attid     attribute id 
    253260   !> @return  attribute structure  
    254261   !------------------------------------------------------------------- 
    255    !> @code 
    256    TYPE(TATT) FUNCTION iom__read_var_name_att_id( td_file, cd_varname, & 
    257    &                                              id_attid) 
     262   TYPE(TATT) FUNCTION iom__read_att_varname_id( td_file, cd_varname, & 
     263   &                                             id_attid) 
    258264      IMPLICIT NONE 
    259265      ! Argument 
     
    277283         SELECT CASE(TRIM(td_file%c_type)) 
    278284            CASE('cdf') 
    279                iom__read_var_name_att_id=iom_read_att( td_file, il_varid, & 
     285               iom__read_att_varname_id=iom_read_att( td_file, il_varid, & 
    280286               &                                       id_attid) 
    281287            CASE('dimg') 
    282                CALL logger_warn( " READ ATT: can't read attribute "//& 
     288               CALL logger_warn( " IOM READ ATT: can't read attribute "//& 
    283289               &              "in dimg file : "//TRIM(td_file%c_name) ) 
    284290            CASE DEFAULT 
    285                CALL logger_error( " READ ATT: can't read attribute in file "//& 
    286                &               TRIM(td_file%c_name)//" : type unknown " ) 
     291               CALL logger_error( " IOM READ ATT: can't read attribute "//& 
     292               &    " in file "//TRIM(td_file%c_name)//" : type unknown " ) 
    287293         END SELECT 
    288294      ENDIF 
    289295 
    290    END FUNCTION iom__read_var_name_att_id 
    291    !> @endcode    
     296   END FUNCTION iom__read_att_varname_id 
    292297   !------------------------------------------------------------------- 
    293298   !> @brief This function read attribute (of variable or global) in an opened  
     
    295300   !> 
    296301   !> @author J.Paul 
    297    !> - Nov, 2013- Initial Version 
    298    ! 
    299    !> @param[in] td_file : file structure 
    300    !> @param[in] id_varid : variable id. use NF90_GLOBAL to read global  
     302   !> - November, 2013- Initial Version 
     303   ! 
     304   !> @param[in] td_file   file structure 
     305   !> @param[in] id_varid variable id. use NF90_GLOBAL to read global  
    301306   !> attribute in a file 
    302    !> @param[in] id_attid : attribute id 
     307   !> @param[in] id_attid attribute id 
    303308   !> @return  attribute structure  
    304309   !------------------------------------------------------------------- 
    305    !> @code 
    306    TYPE(TATT) FUNCTION iom__read_var_id_att_id( td_file, id_varid, & 
     310   TYPE(TATT) FUNCTION iom__read_att_varid_id( td_file, id_varid, & 
    307311   &                                            id_attid) 
    308312      IMPLICIT NONE 
     
    316320      SELECT CASE(TRIM(td_file%c_type)) 
    317321         CASE('cdf') 
    318             iom__read_var_id_att_id=iom_cdf_read_att( td_file, id_varid, & 
     322            iom__read_att_varid_id=iom_cdf_read_att( td_file, id_varid, & 
    319323            &                                         id_attid) 
    320324         CASE('dimg') 
    321             CALL logger_warn( " READ ATT: can't read attribute in dimg file "//& 
     325            CALL logger_warn( " IOM READ ATT: can't read attribute in dimg file "//& 
    322326            &              TRIM(td_file%c_name) ) 
    323327         CASE DEFAULT 
    324             CALL logger_error( " READ ATT: can't read attribute in file "//& 
    325             &               TRIM(td_file%c_name)//" : type unknown " ) 
    326       END SELECT 
    327  
    328    END FUNCTION iom__read_var_id_att_id 
    329    !> @endcode 
     328            CALL logger_error( " IOM READ ATT: can't read attribute in file "//& 
     329            &               TRIM(td_file%c_name)//" : type unknown " ) 
     330      END SELECT 
     331 
     332   END FUNCTION iom__read_att_varid_id 
    330333   !------------------------------------------------------------------- 
    331334   !> @brief This function read attribute (of variable or global) in an opened  
    332335   !> file, given variable name or standard name, and attribute name. 
    333    !> to get global attribute use 'GLOBAL' as variable name. 
    334    !> 
    335    !> To check only standard name of the variable, put variable name to '' 
    336    ! 
    337    !> @author J.Paul 
    338    !> - Nov, 2013- Initial Version 
    339    ! 
    340    !> @param[in] td_file : file structure 
    341    !> @param[in] cd_varname : variable name or standard name. use 'GLOBAL' to read global 
     336   !> @details 
     337   !> - to get global attribute use 'GLOBAL' as variable name. 
     338   ! 
     339   !> @author J.Paul 
     340   !> - November, 2013- Initial Version 
     341   ! 
     342   !> @param[in] td_file      file structure 
     343   !> @param[in] cd_varname   variable name or standard name. use 'GLOBAL' to read global 
    342344   !> attribute in a file 
    343    !> @param[in] cd_attname : attribute name 
     345   !> @param[in] cd_attname   attribute name 
    344346   !> @return  attribute structure     
    345347   !------------------------------------------------------------------- 
    346    !> @code 
    347    TYPE(TATT) FUNCTION iom__read_var_name_att_name( td_file, cd_varname, & 
     348   TYPE(TATT) FUNCTION iom__read_att_varname_name( td_file, cd_varname, & 
    348349   &                                                cd_attname) 
    349350      IMPLICIT NONE 
     
    368369         SELECT CASE(TRIM(td_file%c_type)) 
    369370            CASE('cdf') 
    370                iom__read_var_name_att_name=iom_cdf_read_att( td_file, il_varid, & 
     371               iom__read_att_varname_name=iom_cdf_read_att( td_file, il_varid, & 
    371372               &                                             cd_attname) 
    372373            CASE('dimg') 
    373                CALL logger_warn( " READ ATT: can't read attribute "//& 
     374               CALL logger_warn( " IOM READ ATT: can't read attribute "//& 
    374375               &              "in dimg file :"//TRIM(td_file%c_name) ) 
    375376            CASE DEFAULT 
    376                CALL logger_error( " READ ATT: can't read attribute in file "//& 
     377               CALL logger_error( " IOM READ ATT: can't read attribute in file "//& 
    377378               &               TRIM(td_file%c_name)//" : type unknown " ) 
    378379         END SELECT 
    379380      ENDIF 
    380381 
    381    END FUNCTION iom__read_var_name_att_name 
    382    !> @endcode 
     382   END FUNCTION iom__read_att_varname_name 
    383383   !------------------------------------------------------------------- 
    384384   !> @brief This function read attribute (of variable or global) in an opened  
     
    386386   ! 
    387387   !> @author J.Paul 
    388    !> - Nov, 2013- Initial Version 
    389    ! 
    390    !> @param[in] td_file : file structure 
    391    !> @param[in] id_varid : variable id. use NF90_GLOBAL to read global 
     388   !> - November, 2013- Initial Version 
     389   ! 
     390   !> @param[in] td_file     file structure 
     391   !> @param[in] id_varid     variable id. use NF90_GLOBAL to read global 
    392392   !> attribute in a file 
    393    !> @param[in] cd_name : attribute name 
     393   !> @param[in] cd_attname  attribute name 
    394394   !> @return  attribute structure     
    395395   !------------------------------------------------------------------- 
    396    !> @code 
    397    TYPE(TATT) FUNCTION iom__read_var_id_att_name( td_file, id_varid, & 
     396   TYPE(TATT) FUNCTION iom__read_att_varid_name( td_file, id_varid, & 
    398397   &                                              cd_attname) 
    399398      IMPLICIT NONE 
     
    407406      SELECT CASE(TRIM(td_file%c_type)) 
    408407         CASE('cdf') 
    409             iom__read_var_id_att_name=iom_cdf_read_att( td_file, id_varid, & 
     408            iom__read_att_varid_name=iom_cdf_read_att( td_file, id_varid, & 
    410409            &                                           cd_attname) 
    411410         CASE('dimg') 
    412             CALL logger_warn( " READ ATT: can't read attribute in dimg file :"& 
     411            CALL logger_warn( " IOM READ ATT: can't read attribute in dimg file :"& 
    413412            &              //TRIM(td_file%c_name) ) 
    414413         CASE DEFAULT 
    415             CALL logger_error( " READ ATT: can't read attribute in file "//& 
    416             &               TRIM(td_file%c_name)//" : type unknown " ) 
    417       END SELECT 
    418  
    419    END FUNCTION iom__read_var_id_att_name 
    420    !> @endcode 
     414            CALL logger_error( " IOM READ ATT: can't read attribute in file "//& 
     415            &               TRIM(td_file%c_name)//" : type unknown " ) 
     416      END SELECT 
     417 
     418   END FUNCTION iom__read_att_varid_name 
    421419   !------------------------------------------------------------------- 
    422420   !> @brief This function read one dimension in an opened file,  
     
    424422   ! 
    425423   !> @author J.Paul 
    426    !> - Nov, 2013- Initial Version 
    427    ! 
    428    !> @param[in] td_file : file structure 
    429    !> @param[in] id_dimid : dimension id 
     424   !> - November, 2013- Initial Version 
     425   ! 
     426   !> @param[in] td_file   file structure 
     427   !> @param[in] id_dimid dimension id 
    430428   !> @return  dimension structure  
    431429   !------------------------------------------------------------------- 
    432    !> @code 
    433430   TYPE(TDIM) FUNCTION iom__read_dim_id(td_file, id_dimid) 
    434431      IMPLICIT NONE 
     
    445442            iom__read_dim_id=iom_rstdimg_read_dim(td_file, id_dimid) 
    446443         CASE DEFAULT 
    447             CALL logger_error( " READ DIM: can't read dimension in file "//& 
     444            CALL logger_error( " IOM READ DIM: can't read dimension in file "//& 
    448445            &               TRIM(td_file%c_name)//" : type unknown " ) 
    449446      END SELECT       
    450447 
    451448   END FUNCTION iom__read_dim_id 
    452    !> @endcode 
    453449   !------------------------------------------------------------------- 
    454450   !> @brief This function read one dimension in an opened netcdf file,  
     
    456452   ! 
    457453   !> @author J.Paul 
    458    !> - Nov, 2013- Initial Version 
    459    ! 
    460    !> @param[in] td_file : file structure 
    461    !> @param[in] cd_name : dimension name 
     454   !> - November, 2013- Initial Version 
     455   ! 
     456   !> @param[in] td_file   file structure 
     457   !> @param[in] cd_name   dimension name 
    462458   !> @return  dimension structure  
    463459   !------------------------------------------------------------------- 
    464    !> @code 
    465460   TYPE(TDIM) FUNCTION iom__read_dim_name(td_file, cd_name) 
    466461      IMPLICIT NONE 
     
    477472            iom__read_dim_name=iom_rstdimg_read_dim(td_file, cd_name) 
    478473         CASE DEFAULT 
    479             CALL logger_error( " READ DIM: can't read dimension in file "//& 
     474            CALL logger_error( " IOM READ DIM: can't read dimension in file "//& 
    480475            &               TRIM(td_file%c_name)//" : type unknown " ) 
    481476      END SELECT       
    482477 
    483478   END FUNCTION iom__read_dim_name 
    484    !> @endcode 
    485479   !------------------------------------------------------------------- 
    486480   !> @brief This function read variable value in an opened  
    487    !> file, given variable id.</br/> 
     481   !> file, given variable id. 
     482   !> @details 
    488483   !> start indices and number of indices selected along each dimension  
    489    !> could be specify in a 4 dimension table (/'x','y','z','t'/) 
    490    ! 
    491    !> @author J.Paul 
    492    !> - Nov, 2013- Initial Version 
    493    ! 
    494    !> @param[in] td_file : file structure 
    495    !> @param[in] id_varid : variable id 
    496    !> @param[in] id_start : index in the variable from which the data values  
     484   !> could be specify in a 4 dimension array (/'x','y','z','t'/) 
     485   ! 
     486   !> @author J.Paul 
     487   !> - November, 2013- Initial Version 
     488   ! 
     489   !> @param[in] td_file   file structure 
     490   !> @param[in] id_varid variable id 
     491   !> @param[in] id_start index in the variable from which the data values  
    497492   !> will be read 
    498    !> @param[in] id_count : number of indices selected along each dimension 
     493   !> @param[in] id_count number of indices selected along each dimension 
    499494   !> @return  variable structure  
    500495   !------------------------------------------------------------------- 
    501    !> @code 
    502496   TYPE(TVAR) FUNCTION iom__read_var_id( td_file, id_varid,& 
    503497   &                                     id_start, id_count) 
     
    519513            &                                     id_start, id_count) 
    520514         CASE DEFAULT 
    521             CALL logger_error( " READ VAR: can't read variable in file "//& 
     515            CALL logger_error( " IOM READ VAR: can't read variable in file "//& 
    522516            &               TRIM(td_file%c_name)//" : type unknown " ) 
    523517      END SELECT 
    524518 
    525519   END FUNCTION iom__read_var_id 
    526    !> @endcode 
    527520   !------------------------------------------------------------------- 
    528521   !> @brief This function read variable value in an opened  
    529    !> file, given variable name or standard name.</br/> 
     522   !> file, given variable name or standard name. 
     523   !> @details 
    530524   !> start indices and number of indices selected along each dimension  
    531    !> could be specify in a 4 dimension table (/'x','y','z','t'/) 
    532    ! 
    533    !> @details 
     525   !> could be specify in a 4 dimension array (/'x','y','z','t'/) 
     526   !> 
    534527   !> look first for variable name. If it doesn't 
    535528   !> exist in file, look for variable standard name.<br/> 
    536    !> If variable name is not present, check variable standard name.<br/> 
    537    ! 
    538    !> @author J.Paul 
    539    !> - Nov, 2013- Initial Version 
    540    ! 
    541    !> @param[in] td_file  : file structure 
    542    !> @param[in] cd_name  : variable name or standard name 
    543    !> @param[in] id_start : index in the variable from which the data values 
     529   ! 
     530   !> @author J.Paul 
     531   !> - November, 2013- Initial Version 
     532   ! 
     533   !> @param[in] td_file   file structure 
     534   !> @param[in] cd_name   variable name or standard name 
     535   !> @param[in] id_start  index in the variable from which the data values 
    544536   !> will be read 
    545    !> @param[in] id_count : number of indices selected along each dimension 
     537   !> @param[in] id_count number of indices selected along each dimension 
    546538   !> @return  variable structure  
    547539   !------------------------------------------------------------------- 
    548    !> @code 
    549540   TYPE(TVAR) FUNCTION iom__read_var_name(td_file, cd_name,   & 
    550541   &                                      id_start, id_count  ) 
     
    552543      ! Argument       
    553544      TYPE(TFILE)                   , INTENT(IN) :: td_file 
    554       CHARACTER(LEN=*)              , INTENT(IN), OPTIONAL :: cd_name 
     545      CHARACTER(LEN=*)              , INTENT(IN) :: cd_name 
    555546      INTEGER(i4)     , DIMENSION(:), INTENT(IN), OPTIONAL :: id_start 
    556547      INTEGER(i4)     , DIMENSION(:), INTENT(IN), OPTIONAL :: id_count 
    557       !INTEGER(i4),      DIMENSION(ip_maxdim),  INTENT(IN), OPTIONAL :: id_start 
    558       !INTEGER(i4),      DIMENSION(ip_maxdim),  INTENT(IN), OPTIONAL :: id_count 
    559548      !---------------------------------------------------------------- 
    560549       
     
    568557            &                                   id_start, id_count ) 
    569558         CASE DEFAULT 
    570             CALL logger_error( " READ VAR: can't read variable in file "//& 
     559            CALL logger_error( " IOM READ VAR: can't read variable in file "//& 
    571560            &               TRIM(td_file%c_name)//" : type unknown " ) 
    572561      END SELECT 
    573562 
    574563   END FUNCTION iom__read_var_name 
    575    !> @endcode 
    576    !------------------------------------------------------------------- 
    577    !> @brief This subroutine fill all variables value in an opened  
    578    !> file.</br/> 
    579    !> start indices and number of indices selected along each dimension  
    580    !> could be specify in a 4 dimension table (/'x','y','z','t'/) 
    581    ! 
    582    !> @author J.Paul 
    583    !> - Nov, 2013- Initial Version 
    584    ! 
    585    !> @param[inout] td_file : file structure 
    586    !> @param[in] id_start : index in the variable from which the data values  
    587    !> will be read 
    588    !> @param[in] id_count : number of indices selected along each dimension 
    589    !------------------------------------------------------------------- 
    590    !> @code 
    591    SUBROUTINE iom__fill_var_all( td_file, id_start, id_count) 
    592       IMPLICIT NONE 
    593       ! Argument       
    594       TYPE(TFILE),                       INTENT(INOUT) :: td_file 
    595       INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN),   OPTIONAL :: id_start 
    596       INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN),   OPTIONAL :: id_count 
    597       !---------------------------------------------------------------- 
    598  
    599       ! open file 
    600       SELECT CASE(TRIM(td_file%c_type)) 
    601          CASE('cdf') 
    602             CALL iom_cdf_fill_var(td_file, id_start, id_count) 
    603          CASE('dimg') 
    604             CALL iom_rstdimg_fill_var(td_file, id_start, id_count) 
    605          CASE DEFAULT 
    606             CALL logger_error( " FILL VAR: can't read variable in file "//& 
    607             &               TRIM(td_file%c_name)//" : type unknown " ) 
    608       END SELECT 
    609  
    610    END SUBROUTINE iom__fill_var_all 
    611    !> @endcode 
    612    !------------------------------------------------------------------- 
    613    !> @brief This subroutine fill variable value in an opened  
    614    !> file, given variable id.</br/> 
    615    !> start indices and number of indices selected along each dimension  
    616    !> could be specify in a 4 dimension table (/'x','y','z','t'/) 
    617    ! 
    618    !> @author J.Paul 
    619    !> - Nov, 2013- Initial Version 
    620    ! 
    621    !> @param[inout] td_file : file structure 
    622    !> @param[in] id_varid : variable id 
    623    !> @param[in] id_start : index in the variable from which the data values  
    624    !> will be read 
    625    !> @param[in] id_count : number of indices selected along each dimension 
    626    !------------------------------------------------------------------- 
    627    !> @code 
    628    SUBROUTINE iom__fill_var_id( td_file, id_varid, id_start, id_count) 
    629       IMPLICIT NONE 
    630       ! Argument       
    631       TYPE(TFILE),                       INTENT(INOUT) :: td_file 
    632       INTEGER(i4),                       INTENT(IN)    :: id_varid 
    633       INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN),   OPTIONAL :: id_start 
    634       INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN),   OPTIONAL :: id_count 
    635       !---------------------------------------------------------------- 
    636  
    637       ! open file 
    638       SELECT CASE(TRIM(td_file%c_type)) 
    639          CASE('cdf') 
    640             CALL iom_cdf_fill_var(td_file, id_varid, id_start, id_count) 
    641          CASE('dimg') 
    642             CALL iom_rstdimg_fill_var(td_file, id_varid, id_start, id_count) 
    643          CASE DEFAULT 
    644             CALL logger_error( " FILL VAR: can't read variable in file "//& 
    645             &               TRIM(td_file%c_name)//" : type unknown " ) 
    646       END SELECT 
    647  
    648    END SUBROUTINE iom__fill_var_id 
    649    !> @endcode 
    650    !------------------------------------------------------------------- 
    651    !> @brief This subroutine fill variable value in an opened  
    652    !> file, given variable name or standard name.</br/> 
    653    !> start indices and number of indices selected along each dimension  
    654    !> could be specify in a 4 dimension table (/'x','y','z','t'/) 
    655    ! 
    656    !> @details 
    657    !> look first for variable name. If it doesn't 
    658    !> exist in file, look for variable standard name.<br/> 
    659    !> If variable name is not present, check variable standard name.<br/> 
    660    ! 
    661    !> @author J.Paul 
    662    !> - Nov, 2013- Initial Version 
    663    ! 
    664    !> @param[inout] td_file : file structure 
    665    !> @param[in] cd_name  : variable name or standard name 
    666    !> @param[in] id_start : index in the variable from which the data values 
    667    !> will be read 
    668    !> @param[in] id_count : number of indices selected along each dimension 
    669    !------------------------------------------------------------------- 
    670    !> @code 
    671    SUBROUTINE iom__fill_var_name( td_file, cd_name, id_start, id_count ) 
    672       IMPLICIT NONE 
    673       ! Argument       
    674       TYPE(TFILE),                             INTENT(INOUT) :: td_file 
    675       CHARACTER(LEN=*),                        INTENT(IN)    :: cd_name 
    676       INTEGER(i4),      DIMENSION(ip_maxdim),  INTENT(IN),   OPTIONAL :: id_start 
    677       INTEGER(i4),      DIMENSION(ip_maxdim),  INTENT(IN),   OPTIONAL :: id_count 
    678       !---------------------------------------------------------------- 
    679        
    680       ! open file 
    681       SELECT CASE(TRIM(td_file%c_type)) 
    682          CASE('cdf') 
    683             CALL iom_cdf_fill_var(td_file, cd_name, id_start, id_count ) 
    684          CASE('dimg') 
    685             CALL iom_rstdimg_fill_var(td_file, cd_name, id_start, id_count ) 
    686          CASE DEFAULT 
    687             CALL logger_error( " FILL VAR: can't read variable in file "//& 
    688             &               TRIM(td_file%c_name)//" : type unknown " ) 
    689       END SELECT 
    690  
    691    END SUBROUTINE iom__fill_var_name 
    692    !> @endcode 
    693564   !------------------------------------------------------------------- 
    694565   !> @brief This subroutine write file structure in an opened file. 
    695566   ! 
    696    !> @details 
    697    ! 
    698    !> @author J.Paul 
    699    !> - Nov, 2013- Initial Version 
    700    ! 
    701    !> @param[in] td_file : file structure 
    702    !------------------------------------------------------------------- 
    703    !> @code 
     567   !> @author J.Paul 
     568   !> - November, 2013- Initial Version 
     569   ! 
     570   !> @param[in] td_file   file structure 
     571   !------------------------------------------------------------------- 
    704572   SUBROUTINE iom_write_file(td_file) 
    705573      IMPLICIT NONE 
     
    715583            CALL iom_rstdimg_write_file(td_file) 
    716584         CASE DEFAULT 
    717             CALL logger_error( " WRITE: can't write file "//& 
     585            CALL logger_error( " IOM WRITE: can't write file "//& 
    718586            &               TRIM(td_file%c_name)//" : type unknown " ) 
    719587      END SELECT 
    720588 
    721589   END SUBROUTINE iom_write_file 
    722    !> @endcode    
    723 !   !------------------------------------------------------------------- 
    724 !   !> @brief This function get sub domain decomposition. 
    725 !   ! 
    726 !   !> @details 
    727 !   ! 
    728 !   !> @author J.Paul 
    729 !   !> - Nov, 2013- Initial Version 
    730 !   ! 
    731 !   !> @param[in] td_file : file structure 
    732 !   !------------------------------------------------------------------- 
    733 !   !> @code 
    734 !   TYPE(TMPP) FUNCTION iom_get_mpp(td_file) 
    735 !      IMPLICIT NONE 
    736 !      ! Argument       
    737 !      TYPE(TFILE), INTENT(INOUT) :: td_file 
    738 !      !---------------------------------------------------------------- 
    739 ! 
    740 !      ! open file 
    741 !      SELECT CASE(TRIM(td_file%c_type)) 
    742 !         CASE('cdf') 
    743 !            iom_get_mpp = iom_cdf_get_mpp(td_file) 
    744 !         CASE('dimg') 
    745 !            iom_get_mpp = iom_rstdimg_get_mpp(td_file) 
    746 !         CASE DEFAULT 
    747 !            CALL logger_error( " WRITE: can't write file "//& 
    748 !            &               TRIM(td_file%c_name)//" : type unknown " ) 
    749 !      END SELECT 
    750 ! 
    751 !   END FUNCTION iom_get_mpp 
    752 !   !> @endcode 
    753590END MODULE iom 
    754591 
Note: See TracChangeset for help on using the changeset viewer.