Skip to content
Snippets Groups Projects
Commit 81c7ac2b authored by WAUTELET Philippe's avatar WAUTELET Philippe
Browse files

Philippe 22/08/2024: add finalizer/destructor procedure for tdimsnc type

parent c79197ba
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(:), POINTER :: TBOXNCDIMS => NULL() ! 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
......
!MNH_LIC Copyright 1994-2020 CNRS, Meteo-France and Universite Paul Sabatier
!MNH_LIC Copyright 1994-2024 CNRS, Meteo-France and Universite Paul Sabatier
!MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
!MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
!MNH_LIC for details. version 1.
......@@ -15,6 +15,8 @@ implicit none
public
private :: tdimsnc_destructor
integer, parameter :: NMAXDIMNAMELGTNC4 = 16
!Datatype to store metadata of 1 dimension
......@@ -30,6 +32,19 @@ type tdimsnc
type(tdimnc), dimension(:), pointer :: tdims => null()
integer :: nmaxdims_str = 0 ! For character strings
type(tdimnc), dimension(:), pointer :: tdims_str => null() ! For character strings
contains
private
final :: tdimsnc_destructor
end type tdimsnc
contains
elemental subroutine tdimsnc_destructor( tpdimsnc)
type(tdimsnc), intent(inout) :: tpdimsnc
if ( associated( tpdimsnc%tdims ) ) deallocate( tpdimsnc%tdims )
if ( associated( tpdimsnc%tdims_str ) ) deallocate( tpdimsnc%tdims_str )
end subroutine tdimsnc_destructor
end module modd_netcdf
......@@ -696,9 +696,7 @@ TYPE(tdimsnc), POINTER :: tpdimsnc
CALL PRINT_MSG(NVERB_DEBUG,'IO','IO_Iocdf_dealloc_nc4','called')
if ( Associated( tpdimsnc%tdims ) ) deallocate( tpdimsnc%tdims )
if ( Associated( tpdimsnc%tdims_str ) ) deallocate( tpdimsnc%tdims_str )
! tpdimsnc components are deallocated / cleaned in the tdimsnc finalizer
deallocate( tpdimsnc )
tpdimsnc => Null()
......
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