Changeset 4141 for palm/trunk/UTIL
- Timestamp:
- Aug 5, 2019 12:24:51 PM (5 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/UTIL/binary_to_netcdf.f90
r4123 r4141 49 49 50 50 !-- Set kinds to be used as defaults 51 INTEGER, PARAMETER :: wp = 8 !< default real kind52 INTEGER, PARAMETER :: iwp = 4 !< default integer kind51 INTEGER, PARAMETER :: iwp = 4 !< default integer kind for output-variable values 52 INTEGER, PARAMETER :: wp = 8 !< default real kind for output-variable values 53 53 54 54 INTEGER, PARAMETER :: charlen_internal = 1000 !< length of strings within this program … … 59 59 CHARACTER(LEN=charlen_internal) :: name !< name of attribute 60 60 CHARACTER(LEN=charlen_internal) :: value_char !< character value 61 INTEGER (iwp) :: var_id!< id of variable to which the attribute belongs to61 INTEGER :: variable_id !< id of variable to which the attribute belongs to 62 62 INTEGER(KIND=1) :: value_int8 !< 8bit integer value 63 63 INTEGER(KIND=2) :: value_int16 !< 16bit integer value … … 70 70 CHARACTER(LEN=charlen_internal) :: data_type !< data type of dimension 71 71 CHARACTER(LEN=charlen_internal) :: name !< dimension name 72 INTEGER (iwp):: id !< dimension id within file73 INTEGER (iwp):: length !< length of dimension72 INTEGER :: id !< dimension id within file 73 INTEGER :: length !< length of dimension 74 74 END TYPE dimension_type 75 75 76 76 TYPE variable_type 77 CHARACTER(LEN=charlen_internal) :: data_type!< data type of variable78 CHARACTER(LEN=charlen_internal) :: name!< variable name79 INTEGER (iwp) :: id!< variable id within file80 INTEGER (iwp), DIMENSION(:), ALLOCATABLE :: dimension_ids !< list of dimension ids used by variable77 CHARACTER(LEN=charlen_internal) :: data_type !< data type of variable 78 CHARACTER(LEN=charlen_internal) :: name !< variable name 79 INTEGER :: id !< variable id within file 80 INTEGER, DIMENSION(:), ALLOCATABLE :: dimension_ids !< list of dimension ids used by variable 81 81 END TYPE variable_type 82 82 … … 92 92 config_file_list_name = 'BINARY_CONFIG_LIST' !< file containing list of binary config files of each output group 93 93 94 INTEGER (iwp):: charlen !< length of characters (strings) in binary file95 INTEGER (iwp):: dom_global_id !< global ID within a single file defined by DOM96 INTEGER 97 INTEGER :: dom_nrank!< number of MPI ranks used by DOM98 INTEGER (iwp):: file_index !< loop index to loop over files99 INTEGER 100 INTEGER (iwp):: nc_file_id !< ID of netcdf output file101 INTEGER (iwp):: nfiles !< number of output files defined in config file102 INTEGER :: ngroup!< number of output-file groups103 INTEGER 104 INTEGER 94 INTEGER :: charlen !< length of characters (strings) in binary file 95 INTEGER :: dom_global_id !< global ID within a single file defined by DOM 96 INTEGER :: dom_master_rank !< master MPI rank in DOM (rank which wrote additional information in DOM) 97 INTEGER :: dom_nranks !< number of MPI ranks used by DOM 98 INTEGER :: file_index !< loop index to loop over files 99 INTEGER :: group !< loop index to loop over groups 100 INTEGER :: nc_file_id !< ID of netcdf output file 101 INTEGER :: nfiles !< number of output files defined in config file 102 INTEGER :: ngroups !< number of output-file groups 103 INTEGER :: return_value !< return value 104 INTEGER :: your_return_value !< returned value of called routine 105 105 106 106 INTEGER(KIND=1) :: dummy_int8 !< dummy variable used for reading 107 107 INTEGER(KIND=2) :: dummy_int16 !< dummy variable used for reading 108 108 INTEGER(KIND=4) :: dummy_int32 !< dummy variable used for reading 109 INTEGER (iwp) :: dummy_intwp!< dummy variable used for reading109 INTEGER :: dummy_int !< dummy variable used for reading 110 110 111 111 INTEGER, PARAMETER :: bin_file_unit = 12 !< Fortran unit of binary file … … 113 113 INTEGER, PARAMETER :: config_file_list_unit = 10 !< Fortran unit of file containing config-file list 114 114 115 INTEGER, DIMENSION(:), ALLOCATABLE :: dim _id_netcdf !< mapped dimension id within NetCDF file:116 !> dimension_list(i)%id and dim _id_netcdf(dimension_list(i)%id)115 INTEGER, DIMENSION(:), ALLOCATABLE :: dimension_id_netcdf !< mapped dimension id within NetCDF file: 116 !> dimension_list(i)%id and dimension_id_netcdf(dimension_list(i)%id) 117 117 !> reference the same dimension 118 INTEGER, DIMENSION(:), ALLOCATABLE :: var _id_netcdf !< mapped variable id within NetCDF file:119 !> variable_list(i)%id and var _id_netcdf(variable_list(i)%id)118 INTEGER, DIMENSION(:), ALLOCATABLE :: variable_id_netcdf !< mapped variable id within NetCDF file: 119 !> variable_list(i)%id and variable_id_netcdf(variable_list(i)%id) 120 120 !> reference the same variable 121 121 … … 139 139 140 140 !-- Go through each group of output files (all marked by same file suffix) 141 DO group = 1, ngroup 141 DO group = 1, ngroups 142 142 143 143 CALL internal_message( 'info', 'Start converting ' // TRIM( group_names(group) ) // & … … 160 160 161 161 IF ( your_return_value == 0 ) THEN 162 CALL convert_data_to_netcdf( TRIM( filename_list(file_index) ), your_return_value ) 162 CALL convert_data_to_netcdf( TRIM( filename_list(file_index) ), & 163 your_return_value ) 163 164 ELSE 164 165 return_value = your_return_value … … 228 229 229 230 !-- Count the configuration files 230 ngroup = 0231 ngroups = 0 231 232 DO WHILE ( io_stat == 0 ) 232 233 READ( config_file_list_unit, '(A)', IOSTAT=io_stat ) file_name 233 IF ( io_stat == 0 ) ngroup = ngroup+ 1234 IF ( io_stat == 0 ) ngroups = ngroups + 1 234 235 ENDDO 235 236 REWIND( config_file_list_unit ) 236 237 237 IF ( ngroup /= 0 ) THEN238 239 ALLOCATE( group_names(ngroup ) )238 IF ( ngroups /= 0 ) THEN 239 240 ALLOCATE( group_names(ngroups) ) 240 241 241 242 !-- Extract the group names 242 DO i = 1, ngroup 243 DO i = 1, ngroups 243 244 READ( config_file_list_unit, '(A)', IOSTAT=io_stat ) file_name 244 245 IF ( INDEX( TRIM( file_name ), config_file_name_base ) == 1 ) THEN … … 284 285 CHARACTER(LEN=charlen_internal), DIMENSION(:), ALLOCATABLE :: filename_list_tmp !< temporary list of file names 285 286 286 INTEGER (iwp):: filename_prefix_length !< length of string containing the filname prefix287 INTEGER :: filename_prefix_length !< length of string containing the filname prefix 287 288 INTEGER :: io_stat !< status of Fortran I/O operations 288 289 INTEGER, INTENT(OUT) :: return_value !< return value of routine … … 298 299 IF ( io_stat /= 0 ) THEN 299 300 return_value = 1 300 CALL internal_message( 'error', &301 routine_name //': error while opening configuration file "' // &302 TRIM( config_file_name ) // '"' )301 CALL internal_message( 'error', routine_name // & 302 ': error while opening configuration file "' // & 303 TRIM( config_file_name ) // '"' ) 303 304 ENDIF 304 305 305 306 IF ( return_value == 0 ) THEN 306 307 307 READ( config_file_unit ) dom_nrank 308 309 IF ( dom_nrank > 1000000 ) THEN310 dom_nrank = 1000000308 READ( config_file_unit ) dom_nranks 309 310 IF ( dom_nranks > 1000000 ) THEN 311 dom_nranks = 1000000 311 312 CALL internal_message( 'info', routine_name // & 312 313 ': number of MPI ranks used in PALM is greater than the maximum ' // & … … 357 358 return_value = 1 358 359 CALL internal_message( 'error', routine_name // & 359 360 ': error while reading file names from config' ) 360 361 EXIT 361 362 ENDIF … … 377 378 378 379 CHARACTER(LEN=2*charlen) :: bin_filename !< name of binary file which to read 379 CHARACTER(LEN=* ),INTENT(IN) :: bin_filename_body !< body of binary filename which to read380 CHARACTER(LEN=*), INTENT(IN) :: bin_filename_body !< body of binary filename which to read 380 381 CHARACTER(LEN=charlen ) :: read_string !< string read from file 381 382 … … 387 388 INTEGER :: n_dimensions !< number of dimensions in file 388 389 INTEGER :: n_variables !< number of variables in file 389 INTEGER (iwp) :: var_ndim!< number of dimensions of a variable390 INTEGER :: variable_ndims !< number of dimensions of a variable 390 391 INTEGER, INTENT(OUT) :: return_value !< return value 391 392 … … 408 409 IF ( io_stat == 0 ) THEN 409 410 410 READ( bin_file_unit ) dummy_int wp411 READ( bin_file_unit ) dummy_int wp412 READ( bin_file_unit ) read_string 411 READ( bin_file_unit ) dummy_int ! charlen 412 READ( bin_file_unit ) dummy_int ! file_id 413 READ( bin_file_unit ) read_string ! filename 413 414 414 415 ELSE … … 475 476 READ( bin_file_unit ) read_string 476 477 variable_list(n_variables)%data_type = read_string 477 READ( bin_file_unit ) var_ndim 478 ALLOCATE( variable_list(n_variables)%dimension_ids(1:var_ndim) ) 479 READ( bin_file_unit ) ( variable_list(n_variables)%dimension_ids(i), i = 1, var_ndim ) 478 READ( bin_file_unit ) variable_ndims 479 ALLOCATE( variable_list(n_variables)%dimension_ids(1:variable_ndims) ) 480 READ( bin_file_unit ) & 481 ( variable_list(n_variables)%dimension_ids(i), i = 1, variable_ndims ) 480 482 481 483 CASE ( 'attribute' ) … … 496 498 497 499 !-- Read attribute 498 READ( bin_file_unit ) attribute_list(n_attributes)%var _id500 READ( bin_file_unit ) attribute_list(n_attributes)%variable_id 499 501 READ( bin_file_unit ) read_string 500 502 attribute_list(n_attributes)%name = read_string … … 559 561 CHARACTER(LEN=*), PARAMETER :: routine_name = 'define_netcdf_files' !< routine name 560 562 561 INTEGER :: i !< loop index562 INTEGER :: j !< loop index563 INTEGER :: nc_data_type !< netcdf data type of output variable564 INTEGER :: nc_dim _length !< length of dimension in netcdf file565 INTEGER :: nc_stat !< return value of Netcdf calls566 INTEGER, INTENT(OUT) :: return_value !< return value567 568 INTEGER (iwp), DIMENSION(:), ALLOCATABLE :: var_dim_id!< list of dimension ids of a variable563 INTEGER :: i !< loop index 564 INTEGER :: j !< loop index 565 INTEGER :: nc_data_type !< netcdf data type of output variable 566 INTEGER :: nc_dimension_length !< length of dimension in netcdf file 567 INTEGER :: nc_stat !< return value of Netcdf calls 568 INTEGER, INTENT(OUT) :: return_value !< return value 569 570 INTEGER, DIMENSION(:), ALLOCATABLE :: dimension_ids !< list of dimension ids of a variable 569 571 570 572 … … 581 583 582 584 !-- Define dimensions in NetCDF file 583 ALLOCATE( dim _id_netcdf(1:MAXVAL(dimension_list(:)%id)) )585 ALLOCATE( dimension_id_netcdf(1:MAXVAL(dimension_list(:)%id)) ) 584 586 585 587 DO i = 1, SIZE( dimension_list ) 586 588 587 589 IF ( dimension_list(i)%length < 0 ) THEN 588 nc_dim _length = NF90_UNLIMITED590 nc_dimension_length = NF90_UNLIMITED 589 591 ELSE 590 nc_dim _length = dimension_list(i)%length592 nc_dimension_length = dimension_list(i)%length 591 593 ENDIF 592 594 593 nc_stat = NF90_DEF_DIM( nc_file_id, dimension_list(i)%name, nc_dim _length, &594 dim _id_netcdf(dimension_list(i)%id) )595 nc_stat = NF90_DEF_DIM( nc_file_id, dimension_list(i)%name, nc_dimension_length, & 596 dimension_id_netcdf(dimension_list(i)%id) ) 595 597 596 598 IF ( nc_stat /= NF90_NOERR ) THEN … … 609 611 610 612 !-- Create vector to map variable IDs from binary file to those within netcdf file 611 ALLOCATE( var_id_netcdf(MIN( MINVAL(attribute_list(:)%var_id), & 612 MINVAL(variable_list(:)%id) ) : & 613 MAX( MAXVAL(attribute_list(:)%var_id), & 614 MAXVAL(variable_list(:)%id) ) ) ) 613 ALLOCATE( variable_id_netcdf(MIN( MINVAL( attribute_list(:)%variable_id ), & 614 MINVAL( variable_list(:)%id ) ) & 615 : & 616 MAX( MAXVAL( attribute_list(:)%variable_id ), & 617 MAXVAL( variable_list(:)%id ) ) ) ) 615 618 616 619 !-- Map global id from binary file to that of the netcdf file 617 var _id_netcdf(dom_global_id) = NF90_GLOBAL620 variable_id_netcdf(dom_global_id) = NF90_GLOBAL 618 621 619 622 !-- Define variables in NetCDF file … … 651 654 IF ( return_value == 0 ) THEN 652 655 653 ALLOCATE( var_dim_id(1:SIZE( variable_list(i)%dimension_ids )) )656 ALLOCATE( dimension_ids(1:SIZE( variable_list(i)%dimension_ids )) ) 654 657 655 658 DO j = 1, SIZE( variable_list(i)%dimension_ids ) 656 659 657 var_dim_id(j) = dim_id_netcdf(variable_list(i)%dimension_ids(j))660 dimension_ids(j) = dimension_id_netcdf(variable_list(i)%dimension_ids(j)) 658 661 659 662 ENDDO 660 663 661 664 nc_stat = NF90_DEF_VAR( nc_file_id, variable_list(i)%name, nc_data_type, & 662 var_dim_id, var_id_netcdf(variable_list(i)%id) )665 dimension_ids, variable_id_netcdf(variable_list(i)%id) ) 663 666 IF ( nc_stat /= NF90_NOERR ) THEN 664 667 return_value = 1 … … 668 671 ENDIF 669 672 670 DEALLOCATE( var_dim_id)673 DEALLOCATE( dimension_ids ) 671 674 672 675 ENDIF … … 686 689 687 690 CASE ( 'char' ) 688 nc_stat = NF90_PUT_ATT( nc_file_id, &689 var _id_netcdf(attribute_list(i)%var_id), &690 TRIM(attribute_list(i)%name), &691 nc_stat = NF90_PUT_ATT( nc_file_id, & 692 variable_id_netcdf(attribute_list(i)%variable_id), & 693 TRIM(attribute_list(i)%name), & 691 694 TRIM(attribute_list(i)%value_char) ) 692 695 693 696 CASE ( 'int8' ) 694 nc_stat = NF90_PUT_ATT( nc_file_id, &695 var _id_netcdf(attribute_list(i)%var_id), &696 TRIM(attribute_list(i)%name), &697 nc_stat = NF90_PUT_ATT( nc_file_id, & 698 variable_id_netcdf(attribute_list(i)%variable_id), & 699 TRIM(attribute_list(i)%name), & 697 700 attribute_list(i)%value_int8 ) 698 701 699 702 CASE ( 'int16' ) 700 nc_stat = NF90_PUT_ATT( nc_file_id, &701 var _id_netcdf(attribute_list(i)%var_id), &702 TRIM(attribute_list(i)%name), &703 nc_stat = NF90_PUT_ATT( nc_file_id, & 704 variable_id_netcdf(attribute_list(i)%variable_id), & 705 TRIM(attribute_list(i)%name), & 703 706 attribute_list(i)%value_int16 ) 704 707 705 708 CASE ( 'int32' ) 706 nc_stat = NF90_PUT_ATT( nc_file_id, &707 var _id_netcdf(attribute_list(i)%var_id), &708 TRIM(attribute_list(i)%name), &709 nc_stat = NF90_PUT_ATT( nc_file_id, & 710 variable_id_netcdf(attribute_list(i)%variable_id), & 711 TRIM(attribute_list(i)%name), & 709 712 attribute_list(i)%value_int32 ) 710 713 711 714 CASE ( 'real32' ) 712 nc_stat = NF90_PUT_ATT( nc_file_id, &713 var _id_netcdf(attribute_list(i)%var_id), &714 TRIM(attribute_list(i)%name), &715 nc_stat = NF90_PUT_ATT( nc_file_id, & 716 variable_id_netcdf(attribute_list(i)%variable_id), & 717 TRIM(attribute_list(i)%name), & 715 718 attribute_list(i)%value_real32 ) 716 719 717 720 CASE ( 'real64' ) 718 nc_stat = NF90_PUT_ATT( nc_file_id, &719 var _id_netcdf(attribute_list(i)%var_id), &720 TRIM(attribute_list(i)%name), &721 nc_stat = NF90_PUT_ATT( nc_file_id, & 722 variable_id_netcdf(attribute_list(i)%variable_id), & 723 TRIM(attribute_list(i)%name), & 721 724 attribute_list(i)%value_real64 ) 722 725 723 726 CASE DEFAULT 724 727 return_value = 1 725 CALL internal_message( 'error', routine_name // &728 CALL internal_message( 'error', routine_name // & 726 729 ': data type "' // TRIM( attribute_list(i)%data_type ) // & 727 730 '" of attribute "' // TRIM( attribute_list(i)%name ) // & … … 733 736 IF ( nc_stat /= NF90_NOERR ) THEN 734 737 return_value = 1 735 CALL internal_message( 'error', routine_name // &736 ': attribute "' // TRIM( attribute_list(i)%name ) // 738 CALL internal_message( 'error', routine_name // & 739 ': attribute "' // TRIM( attribute_list(i)%name ) // & 737 740 '": NF90_PUT_ATT error: ' // TRIM( NF90_STRERROR( nc_stat ) ) ) 738 741 EXIT … … 750 753 return_value = 1 751 754 CALL internal_message( 'error', routine_name // & 752 ': NF90_ENDDEF error: ' // TRIM( NF90_STRERROR( nc_stat ) ) )755 ': NF90_ENDDEF error: ' // TRIM( NF90_STRERROR( nc_stat ) ) ) 753 756 ENDIF 754 757 … … 772 775 INTEGER :: i !< loop file_index 773 776 INTEGER :: io_stat !< status of Fortran I/O operations 774 INTEGER :: pe_id !< loop index for loop over PEfiles775 INTEGER :: n_dim 777 INTEGER :: rank !< loop index for loop over rank files 778 INTEGER :: n_dimensions !< number of dimensions of a variable 776 779 INTEGER :: nc_stat !< return value of Netcdf calls 777 780 INTEGER, INTENT(OUT) :: return_value !< return value 778 INTEGER (iwp) :: var_id!< variable id read from binary file779 780 INTEGER (iwp), DIMENSION(:), ALLOCATABLE :: start_positions !< start position of data per dimension781 INTEGER (iwp), DIMENSION(:), ALLOCATABLE :: data_count_per_dimension !< data count of variable per dimension782 INTEGER (iwp), DIMENSION(:), ALLOCATABLE :: bounds_start !< lower bounds of variable783 INTEGER (iwp), DIMENSION(:), ALLOCATABLE :: bounds_origin !< lower bounds of dimensions in output file781 INTEGER :: variable_id !< variable id read from binary file 782 783 INTEGER, DIMENSION(:), ALLOCATABLE :: start_positions !< start position of data per dimension 784 INTEGER, DIMENSION(:), ALLOCATABLE :: data_count_per_dimension !< data count of variable per dimension 785 INTEGER, DIMENSION(:), ALLOCATABLE :: bounds_start !< lower bounds of variable 786 INTEGER, DIMENSION(:), ALLOCATABLE :: bounds_origin !< lower bounds of dimensions in output file 784 787 785 788 INTEGER(KIND=1), DIMENSION(:), ALLOCATABLE :: values_int8 !< variable values … … 797 800 return_value = 0 798 801 799 !-- Open binary files of every possible PE800 DO pe_id = 0, dom_nrank- 1802 !-- Open binary files of every possible MPI rank 803 DO rank = 0, dom_nranks - 1 801 804 802 805 WRITE( bin_filename, '(A, I6.6)' ) & 803 TRIM( filename_prefix ) // TRIM( bin_filename_body ) // '_', pe_id806 TRIM( filename_prefix ) // TRIM( bin_filename_body ) // '_', rank 804 807 805 808 INQUIRE( FILE=bin_filename, EXIST=file_exists ) … … 846 849 DO WHILE ( io_stat == 0 .AND. return_value == 0 ) 847 850 848 READ( bin_file_unit, IOSTAT=io_stat ) var _id851 READ( bin_file_unit, IOSTAT=io_stat ) variable_id 849 852 IF ( io_stat < 0 ) EXIT ! End-of-file 850 853 851 854 DO i = LBOUND( variable_list, DIM=1 ), UBOUND( variable_list, DIM=1 ) 852 IF ( var _id == variable_list(i)%id ) THEN853 n_dim = SIZE( variable_list(i)%dimension_ids )855 IF ( variable_id == variable_list(i)%id ) THEN 856 n_dimensions = SIZE( variable_list(i)%dimension_ids ) 854 857 variable_name = variable_list(i)%name 855 858 856 859 CALL internal_message( 'debug', routine_name // ': read variable "' // & 857 860 TRIM( variable_name ) // '"' ) 858 WRITE( temp_string, * ) n_dim 861 WRITE( temp_string, * ) n_dimensions 859 862 CALL internal_message( 'debug', routine_name // & 860 ': n_dim = ' // TRIM( temp_string ) )863 ': n_dimensions = ' // TRIM( temp_string ) ) 861 864 862 865 EXIT … … 864 867 ENDDO 865 868 866 ALLOCATE( bounds_start(1:n_dim ) )867 ALLOCATE( bounds_origin(1:n_dim ) )868 ALLOCATE( start_positions(1:n_dim ) )869 ALLOCATE( data_count_per_dimension(1:n_dim ) )870 871 READ( bin_file_unit ) ( bounds_start(i), i = 1, n_dim )872 READ( bin_file_unit ) ( data_count_per_dimension(i), i = 1, n_dim )873 READ( bin_file_unit ) ( bounds_origin(i), i = 1, n_dim )869 ALLOCATE( bounds_start(1:n_dimensions) ) 870 ALLOCATE( bounds_origin(1:n_dimensions) ) 871 ALLOCATE( start_positions(1:n_dimensions) ) 872 ALLOCATE( data_count_per_dimension(1:n_dimensions) ) 873 874 READ( bin_file_unit ) ( bounds_start(i), i = 1, n_dimensions ) 875 READ( bin_file_unit ) ( data_count_per_dimension(i), i = 1, n_dimensions ) 876 READ( bin_file_unit ) ( bounds_origin(i), i = 1, n_dimensions ) 874 877 875 878 WRITE( temp_string, * ) bounds_start … … 885 888 data_count = 1 886 889 887 DO i = 1, n_dim 890 DO i = 1, n_dimensions 888 891 data_count = data_count * data_count_per_dimension(i) 889 892 start_positions(i) = bounds_start(i) - bounds_origin(i) + 1 … … 900 903 READ( bin_file_unit ) ( values_int8(i), i = 1, data_count ) 901 904 902 nc_stat = NF90_PUT_VAR( nc_file_id, var_id_netcdf(var_id), values_int8, & 905 nc_stat = NF90_PUT_VAR( nc_file_id, variable_id_netcdf(variable_id), & 906 values_int8, & 903 907 start = start_positions, count = data_count_per_dimension ) 904 908 … … 910 914 READ( bin_file_unit ) ( values_int16(i), i = 1, data_count ) 911 915 912 nc_stat = NF90_PUT_VAR( nc_file_id, var_id_netcdf(var_id), values_int16, & 916 nc_stat = NF90_PUT_VAR( nc_file_id, variable_id_netcdf(variable_id), & 917 values_int16, & 913 918 start = start_positions, count = data_count_per_dimension ) 914 919 … … 920 925 READ( bin_file_unit ) ( values_int32(i), i = 1, data_count ) 921 926 922 nc_stat = NF90_PUT_VAR( nc_file_id, var_id_netcdf(var_id), values_int32, & 927 nc_stat = NF90_PUT_VAR( nc_file_id, variable_id_netcdf(variable_id), & 928 values_int32, & 923 929 start = start_positions, count = data_count_per_dimension ) 924 930 … … 930 936 READ( bin_file_unit ) ( values_intwp(i), i = 1, data_count ) 931 937 932 nc_stat = NF90_PUT_VAR( nc_file_id, var_id_netcdf(var_id), values_intwp, & 938 nc_stat = NF90_PUT_VAR( nc_file_id, variable_id_netcdf(variable_id), & 939 values_intwp, & 933 940 start = start_positions, count = data_count_per_dimension ) 934 941 … … 940 947 READ( bin_file_unit ) ( values_real32(i), i = 1, data_count ) 941 948 942 nc_stat = NF90_PUT_VAR( nc_file_id, var_id_netcdf(var_id), values_real32, & 949 nc_stat = NF90_PUT_VAR( nc_file_id, variable_id_netcdf(variable_id), & 950 values_real32, & 943 951 start = start_positions, count = data_count_per_dimension ) 944 952 … … 950 958 READ( bin_file_unit ) ( values_real64(i), i = 1, data_count ) 951 959 952 nc_stat = NF90_PUT_VAR( nc_file_id, var_id_netcdf(var_id), values_real64, & 960 nc_stat = NF90_PUT_VAR( nc_file_id, variable_id_netcdf(variable_id), & 961 values_real64, & 953 962 start = start_positions, count = data_count_per_dimension ) 954 963 … … 960 969 READ( bin_file_unit ) ( values_realwp(i), i = 1, data_count ) 961 970 962 nc_stat = NF90_PUT_VAR( nc_file_id, var_id_netcdf(var_id), values_realwp, & 971 nc_stat = NF90_PUT_VAR( nc_file_id, variable_id_netcdf(variable_id), & 972 values_realwp, & 963 973 start = start_positions, count = data_count_per_dimension ) 964 974 … … 997 1007 998 1008 !-- Deallocate fields for next file 999 IF ( ALLOCATED( variable_list ) ) DEALLOCATE( variable_list )1000 IF ( ALLOCATED( dim _id_netcdf ) ) DEALLOCATE( dim_id_netcdf )1001 IF ( ALLOCATED( var _id_netcdf ) ) DEALLOCATE( var_id_netcdf )1009 IF ( ALLOCATED( variable_list ) ) DEALLOCATE( variable_list ) 1010 IF ( ALLOCATED( dimension_id_netcdf ) ) DEALLOCATE( dimension_id_netcdf ) 1011 IF ( ALLOCATED( variable_id_netcdf ) ) DEALLOCATE( variable_id_netcdf ) 1002 1012 1003 1013 END SUBROUTINE convert_data_to_netcdf … … 1010 1020 SUBROUTINE internal_message( level, string ) 1011 1021 1012 CHARACTER(LEN=*), INTENT(IN) :: level !< message importance level1013 CHARACTER(LEN=*), INTENT(IN) :: string !< message string1022 CHARACTER(LEN=*), INTENT(IN) :: level !< message importance level 1023 CHARACTER(LEN=*), INTENT(IN) :: string !< message string 1014 1024 1015 1025 IF ( TRIM( level ) == 'error' ) THEN
Note: See TracChangeset
for help on using the changeset viewer.