diff options
author | M. Scot Breitenfeld <brtnfld@hdfgroup.org> | 2016-09-22 17:02:02 (GMT) |
---|---|---|
committer | M. Scot Breitenfeld <brtnfld@hdfgroup.org> | 2016-09-22 17:02:02 (GMT) |
commit | 392b8ce3c98ac4e52d53f33e591ed6bf14155925 (patch) | |
tree | e6f86dcc045566b3eda5dea255466efa314dd1fd /fortran/test/tH5T_F03.F90 | |
parent | 052efd9bde06ea2427beffd3ea493cbc53a17608 (diff) | |
download | hdf5-392b8ce3c98ac4e52d53f33e591ed6bf14155925.zip hdf5-392b8ce3c98ac4e52d53f33e591ed6bf14155925.tar.gz hdf5-392b8ce3c98ac4e52d53f33e591ed6bf14155925.tar.bz2 |
HDFFV-9973 Fortran library fails to compile and fails tests with NAG compiler
Fixes issues with KIND = BYTE assumptions.
Diffstat (limited to 'fortran/test/tH5T_F03.F90')
-rw-r--r-- | fortran/test/tH5T_F03.F90 | 42 |
1 files changed, 16 insertions, 26 deletions
diff --git a/fortran/test/tH5T_F03.F90 b/fortran/test/tH5T_F03.F90 index 6ddded4..a9148a7 100644 --- a/fortran/test/tH5T_F03.F90 +++ b/fortran/test/tH5T_F03.F90 @@ -1144,33 +1144,33 @@ END SUBROUTINE test_array_compound_atomic ! ! Read data back into an integer size that is larger then the original size used for ! writing the data - f_ptr = C_LOC(data_out_i1) + f_ptr = C_LOC(data_out_i1(1)) CALL h5dread_f(dset_id1, h5kind_to_type(int_kind_1,H5_INTEGER_KIND), f_ptr, error) CALL check("h5dread_f",error, total_error) - f_ptr = C_LOC(data_out_i4) + f_ptr = C_LOC(data_out_i4(1)) CALL h5dread_f(dset_id4, h5kind_to_type(int_kind_4,H5_INTEGER_KIND), f_ptr, error) CALL check("h5dread_f",error, total_error) - f_ptr = C_LOC(data_out_i8) + f_ptr = C_LOC(data_out_i8(1)) CALL h5dread_f(dset_id8, h5kind_to_type(int_kind_8,H5_INTEGER_KIND), f_ptr, error) CALL check("h5dread_f",error, total_error) - f_ptr = C_LOC(data_out_i16) + f_ptr = C_LOC(data_out_i16(1)) CALL h5dread_f(dset_id16, h5kind_to_type(int_kind_16,H5_INTEGER_KIND), f_ptr, error) CALL check("h5dread_f",error, total_error) #if H5_HAVE_Fortran_INTEGER_SIZEOF_16!=0 - f_ptr = C_LOC(data_out_i32) + f_ptr = C_LOC(data_out_i32(1)) CALL h5dread_f(dset_id32, h5kind_to_type(int_kind_32,H5_INTEGER_KIND), f_ptr, error) CALL check("h5dread_f",error, total_error) #endif - f_ptr = C_LOC(data_out_r) + f_ptr = C_LOC(data_out_r(1)) CALL h5dread_f(dset_idr, H5T_NATIVE_REAL, f_ptr, error) CALL check("h5dread_f",error, total_error) - f_ptr = C_LOC(data_out_r7) + f_ptr = C_LOC(data_out_r7(1)) CALL h5dread_f(dset_idr4, h5kind_to_type(real_kind_7,H5_REAL_KIND), f_ptr, error) CALL check("h5dread_f",error, total_error) - f_ptr = C_LOC(data_out_r15) + f_ptr = C_LOC(data_out_r15(1)) CALL h5dread_f(dset_idr8, h5kind_to_type(real_kind_15,H5_REAL_KIND), f_ptr, error) CALL check("h5dread_f",error, total_error) - f_ptr = C_LOC(data_out_r31) + f_ptr = C_LOC(data_out_r31(1)) CALL h5dread_f(dset_idr16, h5kind_to_type(real_kind_31,H5_REAL_KIND), f_ptr, error) CALL check("h5dread_f",error, total_error) DO i = 1, 4 @@ -2000,7 +2000,7 @@ SUBROUTINE t_regref(total_error) CALL h5dcreate_f(file,dataset2, H5T_STD_I8LE, space, dset2, error) CALL check("h5dcreate_f",error, total_error) f_ptr = C_LOC(wdata2(1,1)) - CALL h5dwrite_f(dset2, H5T_NATIVE_INTEGER_1, f_ptr, error) + CALL h5dwrite_f(dset2, H5T_NATIVE_INTEGER_KIND(1), f_ptr, error) CALL check("h5dwrite_f",error, total_error) ! ! Create reference to a list of elements in dset2. @@ -2112,7 +2112,7 @@ SUBROUTINE t_regref(total_error) CALL check("h5screate_simple_f",error, total_error) f_ptr = C_LOC(rdata2(1)(1:1)) - CALL h5dread_f( dset2, H5T_NATIVE_INTEGER_1, f_ptr, error, memspace, space) + CALL h5dread_f( dset2, H5T_NATIVE_INTEGER_KIND(1), f_ptr, error, memspace, space) CALL check("H5Dread_f",error, total_error) CALL verify("h5dread_f",rdata2(1)(1:npoints),TRIM(chrref_correct(i)), total_error) @@ -2886,33 +2886,23 @@ SUBROUTINE setup_buffer(data_in, line_lengths, char_type) CHARACTER(len=10), DIMENSION(:) :: data_in INTEGER(size_t), DIMENSION(:) :: line_lengths - INTEGER, DIMENSION(1:3) :: letters - CHARACTER(LEN=3) :: lets + CHARACTER(LEN=3) :: lets = 'abc' CHARACTER(KIND=C_CHAR,LEN=*) :: char_type - CHARACTER(KIND=C_CHAR,LEN=1) :: char_tmp - INTEGER :: i, j, n, ff + INTEGER :: i, j, n - ! Convert the letters and special character to integers - lets = 'abc' - - READ(lets,'(3A1)') letters - READ(char_type,'(A1)') ff n = SIZE(data_in) j = 1 DO i=1,n-1 IF( j .EQ. 4 )THEN - WRITE(char_tmp,'(A1)') ff - data_in(i:i) = char_tmp + data_in(i:i) = char_type(1:1) ELSE - WRITE(char_tmp,'(A1)') letters(j) - data_in(i:i) = char_tmp + data_in(i:i) = lets(j:j) ENDIF line_lengths(i) = LEN_TRIM(data_in(i)) j = j + 1 IF( j .EQ. 5 ) j = 1 END DO - WRITE(char_tmp,'(A1)') ff - data_in(n:n) = char_tmp + data_in(n:n) = char_type(1:1) line_lengths(n) = 1 END SUBROUTINE setup_buffer |