Ignore:
Timestamp:
Jan 29, 2019 7:51:41 PM (5 years ago)
Author:
suehring
Message:

Revision of virtual-measurement module and data output enabled. Further, post-processing tool added to merge distributed virtually sampled data and to output it into NetCDF files.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/netcdf_data_input_mod.f90

    r3655 r3704  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Interface for attribute input of 8-bit and 32-bit integer
    2323!
    2424! Former revisions:
     
    777777   
    778778    INTERFACE netcdf_data_input_att
    779        MODULE PROCEDURE netcdf_data_input_att_int
     779       MODULE PROCEDURE netcdf_data_input_att_int8
     780       MODULE PROCEDURE netcdf_data_input_att_int32
    780781       MODULE PROCEDURE netcdf_data_input_att_real
    781782       MODULE PROCEDURE netcdf_data_input_att_string
     
    11741175! Description:
    11751176! ------------
    1176 !> Read a global integer attribute
    1177 !------------------------------------------------------------------------------!
    1178     SUBROUTINE netcdf_data_input_att_int( val, search_string, id_mod,          &
    1179                                           input_file, global, openclose,       &
    1180                                           variable_name )
     1177!> Read a global 8-bit integer attribute
     1178!------------------------------------------------------------------------------!
     1179    SUBROUTINE netcdf_data_input_att_int8( val, search_string, id_mod,         &
     1180                                           input_file, global, openclose,      &
     1181                                           variable_name )
     1182
     1183       IMPLICIT NONE
     1184
     1185       CHARACTER(LEN=*) ::  search_string !< name of the attribue
     1186       
     1187       CHARACTER(LEN=*) ::  input_file    !< name of input file
     1188       CHARACTER(LEN=*) ::  openclose     !< string indicating whether NetCDF needs to be opend or closed
     1189       CHARACTER(LEN=*) ::  variable_name !< string indicating whether NetCDF needs to be opend or closed
     1190       
     1191       INTEGER(iwp) ::  id_mod   !< NetCDF id of input file
     1192       INTEGER(KIND=1) ::  val      !< value of the attribute
     1193       
     1194       LOGICAL ::  global        !< flag indicating a global or a variable's attribute
     1195
     1196#if defined ( __netcdf )
     1197!
     1198!--    Open file in read-only mode
     1199       IF ( openclose == 'open' )  THEN
     1200          CALL open_read_file( TRIM( input_file ) // TRIM( coupling_char ), &
     1201                                  id_mod )
     1202       ENDIF
     1203!
     1204!--    Read global attribute
     1205       IF ( global )  THEN
     1206          CALL get_attribute( id_mod, search_string, val, global )
     1207!
     1208!--    Read variable attribute
     1209       ELSE
     1210          CALL get_attribute( id_mod, search_string, val, global, variable_name )
     1211       ENDIF
     1212!
     1213!--    Finally, close input file
     1214       IF ( openclose == 'close' )  CALL close_input_file( id_mod )
     1215#endif           
     1216
     1217    END SUBROUTINE netcdf_data_input_att_int8
     1218   
     1219!------------------------------------------------------------------------------!
     1220! Description:
     1221! ------------
     1222!> Read a global 32-bit integer attribute
     1223!------------------------------------------------------------------------------!
     1224    SUBROUTINE netcdf_data_input_att_int32( val, search_string, id_mod,        &
     1225                                            input_file, global, openclose,     &
     1226                                            variable_name )
    11811227
    11821228       IMPLICIT NONE
     
    12141260#endif           
    12151261
    1216     END SUBROUTINE netcdf_data_input_att_int
     1262    END SUBROUTINE netcdf_data_input_att_int32
    12171263   
    12181264!------------------------------------------------------------------------------!
Note: See TracChangeset for help on using the changeset viewer.