remove unnecessary deallocations

1. Local variables are automatically deallocated when they go out of
   scope.

2. When calling exit() during CLI processing some stuff wasn't being
   deallocated, but it doesnt matter because the OS does it anyway.
   So, get rid of it entirely.
This commit is contained in:
Michele Guerini Rocco 2024-11-04 09:12:15 +01:00
parent fde048d3ee
commit 72eb224568
Signed by: rnhmjoj
GPG Key ID: BFBAF4C975F76450
8 changed files with 20 additions and 154 deletions

View File

@ -186,21 +186,6 @@ contains
params%phi(2) = phi2v(ii)
end if
deallocate(alphastv, betastv, waist1v, waist2v, &
rci1v, rci2v, phi1v, phi2v, &
x00v, y00v, z00v)
call beta%deinit
call waist1%deinit
call waist2%deinit
call rci1%deinit
call rci2%deinit
call phi1%deinit
call phi2%deinit
call x0%deinit
call y0%deinit
call z0%deinit
end subroutine read_beam1
@ -348,8 +333,6 @@ contains
params%ri(2)=rci2v(1)
params%phi(2)=phi1v(1)
params%phi(1)=phi2v(1)
deallocate(alphastv,betastv,waist1v,waist2v,rci1v,rci2v,phi1v, &
phi2v,x00v,y00v,z00v,xcoord,ycoord)
return
end if
!#######################################################################################
@ -717,10 +700,6 @@ contains
ycoord0 = yvert(1)
ii = 1
END SELECT
! c----------------------------------------------------------------------------------
!
deallocate(polygA%R, polygA%z, polygC%R, polygC%z, polygB%R, polygB%z, &
polygD%R, polygD%z, outA%R, outA%z, outB%R, outB%z, outC%R, outC%z)
end if
! c====================================================================================
!
@ -773,20 +752,6 @@ contains
! c====================================================================================
end if
!#######################################################################################
!
if(fdeg.ne.0) then
deallocate(cycoord, txycoord, cwaist1, txwaist1, cwaist2, &
txwaist2, crci1, txrci1, crci2, txrci2, cphi1, txphi1, &
cphi2, txphi2, cx0, txx0, cy0, txy0, cz0, txz0, w)
else
deallocate(cwaist1, txwaist1, tywaist1, cwaist2, txwaist2, tywaist2, &
crci1, txrci1, tyrci1, crci2, txrci2, tyrci2, &
cphi1, txphi1, typhi1, cphi2, txphi2, typhi2, &
cx0, txx0, tyx0, cy0, txy0, tyy0, cz0, txz0, tyz0, &
wrk2, polyg%R, polyg%z, w)
end if
!
!#######################################################################################
! set correct values for alpha, beta
if(fdeg.eq.2) then
params%alpha = ycoord0
@ -795,10 +760,6 @@ contains
params%alpha = xcoord0
params%beta = ycoord0
end if
!#######################################################################################
deallocate(alphastv,betastv,waist1v,waist2v,rci1v,rci2v,phi1v, &
phi2v,x00v,y00v,z00v,xcoord,ycoord)
!
end subroutine read_beam2

View File

@ -322,8 +322,6 @@ contains
effjcd=-ceff*anum/(anucc*denom)
end if
deallocate(apar)
end subroutine eccdeff
function fpp(upl,extrapar,npar)

View File

@ -107,7 +107,7 @@ contains
type(cli_options), intent(out) :: opts
! local variables
character(len=:), allocatable :: argument, temp
character(len=:), allocatable :: argument
integer :: i, nargs
integer :: error, commas
@ -128,12 +128,10 @@ contains
select case (argument)
case ('-h', '--help')
call print_help()
deallocate(argument)
call exit(0)
case ('-V', '--version')
call print_version()
deallocate(argument)
call exit(0)
case ('-v', '--verbose')
@ -155,34 +153,29 @@ contains
call get_next_command(i, opts%sum_filelist)
case ('-t', '--tables')
call get_next_command(i, temp)
call get_next_command(i, argument)
if (temp == 'none') then
if (argument == 'none') then
! disable all output tables
deallocate(opts%tables)
allocate(opts%tables(0))
elseif (temp == 'all') then
elseif (argument == 'all') then
! enable all output tables
deallocate(opts%tables)
opts%tables = [-1]
else
! resize the array
commas = count([(temp(i:i) == ',', i = 1, len(temp))])
commas = count([(argument(i:i) == ',', i = 1, len(argument))])
deallocate(opts%tables)
allocate(opts%tables(commas + 1))
! read the list of table IDs
read (temp, *, iostat=error) opts%tables
read (argument, *, iostat=error) opts%tables
if (error > 0) then
print '(a,a)', 'invalid table IDs: ', temp
deallocate(argument)
deallocate(temp)
print '(a,a)', 'invalid table IDs: ', argument
call exit(1)
end if
end if
deallocate(temp)
case ('-g', '--gray-param')
! these overrides are parsed later since they need to
! be applied to the final gray_parameters structure
@ -191,14 +184,11 @@ contains
case default
print '(a,a,/)', 'Unknown option: ', argument
call print_help()
deallocate(argument)
call exit(1)
end select
end do
! free temporary string
if (nargs > 0) deallocate(argument)
end subroutine
@ -212,7 +202,7 @@ contains
type(gray_parameters), intent(inout) :: params
! local variables
character(len=:), allocatable :: argument, temp, id, val
character(len=:), allocatable :: argument, id, val
integer :: i, nargs
integer :: sep
@ -226,17 +216,16 @@ contains
! parse gray parameters
select case (argument)
case ('-g', '--gray-param')
call get_next_command(i, temp)
call get_next_command(i, argument)
! split at "=" (id=value)
sep = index(temp, '=')
id = temp(1:sep - 1)
val = temp(sep + 1:)
sep = index(argument, '=')
id = argument(1:sep - 1)
val = argument(sep + 1:)
if (sep == 0) then
print '(a,a)', 'invalid GRAY parameter declaration: ', temp
print '(a,a)', 'invalid GRAY parameter declaration: ', argument
print '(a)', 'correct syntax is ID=VALUE, ex. antenna.alpha=45'
deallocate(temp)
call exit(1)
end if
@ -244,17 +233,13 @@ contains
select case (update_parameter(params, id, val))
case (ERR_VALUE)
print '(4a)', 'invalid value for ', id, ': ', val
deallocate(temp)
call exit(1)
case (ERR_UNKNOWN)
print '(a,a)', 'unknown GRAY parameter: ', id
deallocate(temp)
call exit(1)
end select
deallocate(temp)
! skip everything else
case default
cycle
@ -262,8 +247,6 @@ contains
end select
end do
! free temporary string
if (nargs > 0) deallocate(argument)
end subroutine parse_param_overrides

View File

@ -1795,7 +1795,6 @@ contains
ithn, cst2, fjncl, eccdpar, effjcd, iokhawa, ierrcd)
end select
error = error + ierrcd
if (allocated(eccdpar)) deallocate(eccdpar)
! current drive efficiency R* = <J_>/<dP/dV> [Am/W]
effjcdav = rbavi*effjcd

View File

@ -861,7 +861,6 @@ contains
rv1d, zv1d, fvpsi, tension=zero, &
range=[self%r_range, self%z_range], err=err)
end if
deallocate(rv1d, zv1d, fvpsi)
! reset nrz to the total number of grid points for next allocations
nrz = nr*nz
@ -883,7 +882,6 @@ contains
range=[self%r_range, self%z_range], tension=zero)
err = 0
end if
deallocate(fvpsi)
end select
if (err /= 0) then

View File

@ -137,7 +137,6 @@ contains
case (ERR_VALUE)
write (msg, '("invalid value for property `",a,"`: ", a)') name, value
call log_error(msg, proc='parse_ini', mod='ini_parser')
deallocate(line)
error = ERR_VALUE
exit

View File

@ -97,12 +97,10 @@ contains
! parse optional arguments
case ('-h', '--help')
call print_help()
deallocate(argument)
call exit(0)
case ('-V', '--version')
call print_version()
deallocate(argument)
call exit(0)
case ('-f', '--format')
@ -128,14 +126,11 @@ contains
print '(a,a,/)', 'Unknown option: ', argument
call print_help()
deallocate(argument)
call exit(1)
end select
end do
! free temporary string
if (nargs > 0) deallocate(argument)
end subroutine
subroutine write_gray_config(filename, params)

View File

@ -16,7 +16,6 @@ module splines
real(wp_), allocatable :: coeffs(:,:) ! Spline coefficients (ndata, 4)
contains
procedure :: init => spline_simple_init
procedure :: deinit => spline_simple_deinit
procedure :: eval => spline_simple_eval
procedure :: raw_eval => spline_simple_raw_eval
procedure :: deriv => spline_simple_deriv
@ -29,7 +28,6 @@ module splines
real(wp_), allocatable :: coeffs(:) ! B-spline coefficients
contains
procedure :: init => spline_1d_init
procedure :: deinit => spline_1d_deinit
procedure :: eval => spline_1d_eval
procedure :: deriv => spline_1d_deriv
end type
@ -53,7 +51,6 @@ module splines
contains
procedure :: init => spline_2d_init
procedure :: init_nonreg => spline_2d_init_nonreg
procedure :: deinit => spline_2d_deinit
procedure :: eval => spline_2d_eval
procedure :: init_deriv => spline_2d_init_deriv
procedure :: deriv => spline_2d_deriv
@ -68,7 +65,6 @@ module splines
real(wp_), allocatable :: ydata(:) ! Y data (ndata)
contains
procedure :: init => linear_1d_init
procedure :: deinit => linear_1d_deinit
procedure :: eval => linear_1d_eval
procedure :: raw_eval => linear_1d_raw_eval
end type
@ -86,7 +82,6 @@ contains
integer, intent(in) :: n
real(wp_), dimension(n), intent(in) :: x, y
call self%deinit
self%ndata = n
allocate(self%data(n))
allocate(self%coeffs(n, 4))
@ -96,18 +91,6 @@ contains
end subroutine spline_simple_init
subroutine spline_simple_deinit(self)
! Deinitialises a simple_spline
! subroutine arguments
class(spline_simple), intent(inout) :: self
if (allocated(self%data)) deallocate(self%data)
if (allocated(self%coeffs)) deallocate(self%coeffs)
self%ndata = 0
end subroutine spline_simple_deinit
pure function spline_simple_eval(self, x) result(y)
! Evaluates the spline at x
use utils, only : locate
@ -297,12 +280,11 @@ contains
if (present(weights)) weights_def = weights
if (present(tension)) tension_def = tension
! clear memory, if necessary
call self%deinit
! allocate the spline arrays
nknots_est = n + 4
allocate(self%knots(nknots_est), self%coeffs(nknots_est))
if (.not. allocated(self%coeffs)) then
allocate(self%knots(nknots_est), self%coeffs(nknots_est))
end if
call curfit(0, n, x, y, weights_def, range(1), range(2), 3, tension_def, &
nknots_est, self%nknots, self%knots, self%coeffs, residuals, &
@ -312,17 +294,6 @@ contains
end subroutine spline_1d_init
subroutine spline_1d_deinit(self)
! Deinitialises a spline_1d
class(spline_1d), intent(inout) :: self
if (allocated(self%knots)) deallocate(self%knots)
if (allocated(self%coeffs)) deallocate(self%coeffs)
self%nknots = 0
end subroutine spline_1d_deinit
pure function spline_1d_eval(self, x) result(y)
! Evaluates the spline at x
use dierckx, only : splev
@ -403,14 +374,13 @@ contains
tension_def = 0
if (present(tension)) tension_def = tension
! clear memory, if necessary
call self%deinit
! allocate the spline arrays
nknots_x_est = nx + 4
nknots_y_est = ny + 4
allocate(self%knots_x(nknots_x_est), self%knots_y(nknots_y_est))
allocate(self%coeffs(nx * ny))
if (.not. allocated(self%coeffs)) then
allocate(self%knots_x(nknots_x_est), self%knots_y(nknots_y_est))
allocate(self%coeffs(nx * ny))
end if
call regrid(0, nx, x, ny, y, z, range(1), range(2), range(3), range(4), &
3, 3, tension_def, nknots_x_est, nknots_y_est, &
@ -484,30 +454,6 @@ contains
end subroutine spline_2d_init_nonreg
subroutine spline_2d_deinit(self)
! Deinitialises a spline_2d
class(spline_2d), intent(inout) :: self
if (allocated(self%knots_x)) deallocate(self%knots_x)
if (allocated(self%knots_y)) deallocate(self%knots_y)
if (allocated(self%coeffs)) deallocate(self%coeffs)
! Note: partial derivatives coeff. are pointers
if (allocated(self%partial)) then
deallocate(self%partial(1, 0)%ptr)
deallocate(self%partial(0, 1)%ptr)
deallocate(self%partial(1, 1)%ptr)
deallocate(self%partial(2, 0)%ptr)
deallocate(self%partial(0, 2)%ptr)
deallocate(self%partial)
end if
self%nknots_x = 0
self%nknots_y = 0
end subroutine spline_2d_deinit
subroutine spline_2d_final(self)
! Deallocates pointer components in a spline_2d
@ -657,7 +603,6 @@ contains
integer, intent(in) :: n
real(wp_), dimension(n), intent(in) :: x, y
call self%deinit
self%ndata = n
allocate(self%xdata(n))
allocate(self%ydata(n))
@ -667,18 +612,6 @@ contains
end subroutine linear_1d_init
subroutine linear_1d_deinit(self)
! Deinitialises a linear_1d
! subroutine arguments
class(linear_1d), intent(inout) :: self
if (allocated(self%xdata)) deallocate(self%xdata)
if (allocated(self%ydata)) deallocate(self%ydata)
self%ndata = 0
end subroutine linear_1d_deinit
pure function linear_1d_eval(self, x) result(y)
! Evaluates the linear interpolated data at x
use utils, only : locate