Skip to content
Snippets Groups Projects
Commit c79197ba authored by Juan Escobar's avatar Juan Escobar
Browse files

Juan 21/08/2024:modd_netcdf.f90++, Bypass Gfortran/7.X++ Bug by replacing...

Juan 21/08/2024:modd_netcdf.f90++, Bypass Gfortran/7.X++ Bug by replacing allocatable by pointer member in type(tdimsnc)
parent a418193a
No related branches found
No related tags found
No related merge requests found
......@@ -136,7 +136,7 @@ TYPE TFILEDATA
INTEGER(KIND=CDFINT) :: NNCCOMPRESS_LOSSY_NSD = 3 ! Number of Significant Digits (or Bits)
TYPE(TDIMSNC), POINTER :: TNCDIMS => NULL() ! Dimensions of netCDF file
INTEGER(KIND=CDFINT), DIMENSION(:), ALLOCATABLE :: NBOXNCID ! Box HDF group identifiers (used for MNHOUTPUT files)
TYPE(TDIMSNC), DIMENSION(:), ALLOCATABLE :: TBOXNCDIMS ! Box dimensions of netCDF file (used for MNHOUTPUT files)
TYPE(TDIMSNC), DIMENSION(:), POINTER :: TBOXNCDIMS => NULL() ! Box dimensions of netCDF file (used for MNHOUTPUT files)
#endif
!
!Fields for other files
......
......@@ -27,9 +27,9 @@ end type tdimnc
!Datatype to store dimension metadata of a netCDF file
type tdimsnc
integer :: nmaxdims = 0
type(tdimnc), dimension(:), allocatable :: tdims
type(tdimnc), dimension(:), pointer :: tdims => null()
integer :: nmaxdims_str = 0 ! For character strings
type(tdimnc), dimension(:), allocatable :: tdims_str ! For character strings
type(tdimnc), dimension(:), pointer :: tdims_str => null() ! For character strings
end type tdimsnc
end module modd_netcdf
......@@ -64,7 +64,7 @@ if ( .not.Associated( tpfile%tncdims ) ) then
return
end if
if ( .not.Allocated( tpfile%tncdims%tdims ) ) then
if ( .not.Associated( tpfile%tncdims%tdims ) ) then
call Print_msg( NVERB_WARNING, 'IO', 'IO_Dim_find_byname_nc4', 'tdims not allocated for file '//trim(tpfile%cname) )
kresp = -1
return
......@@ -328,7 +328,7 @@ if ( .not.Associated( tpfile%tncdims ) ) then
Allocate( tpfile%tncdims )
end if
if ( Allocated( tpfile%tncdims%tdims ) ) then
if ( Associated( tpfile%tncdims%tdims ) ) then
call Print_msg( NVERB_ERROR, 'IO', 'IO_Knowndims_set_nc4', 'tdims already allocated for ' // Trim( tpfile%cname ) )
Deallocate( tpfile%tncdims%tdims )
end if
......@@ -696,8 +696,8 @@ TYPE(tdimsnc), POINTER :: tpdimsnc
CALL PRINT_MSG(NVERB_DEBUG,'IO','IO_Iocdf_dealloc_nc4','called')
if ( Allocated( tpdimsnc%tdims ) ) deallocate( tpdimsnc%tdims )
if ( Allocated( tpdimsnc%tdims_str ) ) deallocate( tpdimsnc%tdims_str )
if ( Associated( tpdimsnc%tdims ) ) deallocate( tpdimsnc%tdims )
if ( Associated( tpdimsnc%tdims_str ) ) deallocate( tpdimsnc%tdims_str )
deallocate( tpdimsnc )
tpdimsnc => Null()
......@@ -953,14 +953,14 @@ if ( kidx == - 1 ) then
#else
!Do the Move_alloc by hand...
#if 0
if ( Allocated( tpfile%tncdims%tdims ) ) Deallocate( tpfile%tncdims%tdims )
if ( Associated( tpfile%tncdims%tdims ) ) Deallocate( tpfile%tncdims%tdims )
Allocate( tpfile%tncdims%tdims(Size( tzncdims )) )
tpfile%tncdims%tdims(:) = tzncdims
#else
!Use intermediate pointer to work around problem with gfortran/10.3.0 and Cray/cce/15.0 compilers (on Adastra)
!(does not like to modify pointed data if intent(in))
tz_tncdims => tpfile%tncdims
if ( Allocated( tz_tncdims%tdims ) ) Deallocate( tz_tncdims%tdims )
if ( Associated( tz_tncdims%tdims ) ) Deallocate( tz_tncdims%tdims )
Allocate( tz_tncdims%tdims(Size( tzncdims )) )
tz_tncdims%tdims(:) = tzncdims
#endif
......@@ -1056,7 +1056,7 @@ END IF
! Search string dimension with KLEN length
idx = -1
if ( Allocated( tpfile%tncdims%tdims_str ) ) then
if ( Associated( tpfile%tncdims%tdims_str ) ) then
do ji = 1, Size( tpfile%tncdims%tdims_str )
if ( tpfile%tncdims%tdims_str(ji)%nlen == klen ) then
idx = ji
......@@ -1069,7 +1069,7 @@ if ( idx == -1 ) then
!Create new dimension
inewsize = tpfile%tncdims%nmaxdims_str + 1
allocate( tzncdims(inewsize) )
if ( Allocated( tpfile%tncdims%tdims_str ) ) &
if ( Associated( tpfile%tncdims%tdims_str ) ) &
tzncdims(1 : inewsize - 1) = tpfile%tncdims%tdims_str(:)
Write( ysuffix, '( i0 )' ) klen
......@@ -1086,14 +1086,14 @@ if ( idx == -1 ) then
#else
!Do the Move_alloc by hand...
#if 0
if ( Allocated( tpfile%tncdims%tdims_str ) ) Deallocate( tpfile%tncdims%tdims_str )
if ( Associated( tpfile%tncdims%tdims_str ) ) Deallocate( tpfile%tncdims%tdims_str )
Allocate( tpfile%tncdims%tdims_str(Size( tzncdims )) )
tpfile%tncdims%tdims_str(:) = tzncdims(:)
#else
!Use intermediate pointer to work around problem with gfortran/10.3.0 and Cray/cce/15.0 compilers (on Adastra)
!(does not like to modify pointed data if intent(in))
tz_tncdims => tpfile%tncdims
if ( Allocated( tz_tncdims%tdims_str ) ) Deallocate( tz_tncdims%tdims_str )
if ( Associated( tz_tncdims%tdims_str ) ) Deallocate( tz_tncdims%tdims_str )
Allocate( tz_tncdims%tdims_str(Size( tzncdims )) )
tz_tncdims%tdims_str(:) = tzncdims
#endif
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment