Skip to content

Commit

Permalink
Merge pull request #113 from dalesteam/dev-fix-uninitialized
Browse files Browse the repository at this point in the history
fix uninitialized variables
  • Loading branch information
fjansson authored Sep 4, 2024
2 parents 025d602 + a6845de commit 9640d69
Show file tree
Hide file tree
Showing 8 changed files with 26 additions and 28 deletions.
20 changes: 8 additions & 12 deletions src/modboundary.f90
Original file line number Diff line number Diff line change
Expand Up @@ -36,8 +36,8 @@ module modboundary
integer :: ksp = -1 !< lowest level of sponge layer
real(field_r),allocatable :: tsc(:) !< damping coefficients to be used in grwdamp.
real(field_r) :: rnu0 = 2.75e-3
logical :: lboundopen !GT added on off switch for open boundary conditions
real(field_r), allocatable :: fillvalues(:) !GT added a new array variable
logical :: lboundopen = .false. !GT switch for open boundary conditions for all scalars
real(field_r) :: fillvalues(100) = 0 !GT fill value for each scalar to apply at the boundary
contains
!>
!! Initializing Boundary; specifically the sponge layer
Expand All @@ -51,10 +51,10 @@ subroutine initboundary

real :: zspb, zspt
integer :: k, ierr !GT added ierr
! --- Read & broadcast namelist DEPOSITION -----------------------------------
! --- Read & broadcast namelist NAMBOUNDSET -----------------------------------
namelist/NAMBOUNDSET/ lboundopen, fillvalues !GT added
allocate(fillvalues(nsv)) !GT added

call timer_tic('modboundary/initboundary', 0)

if (myid == 0) then
open(ifnamopt,file=fname_options,status='old',iostat=ierr)
Expand All @@ -67,7 +67,6 @@ subroutine initboundary
call d_mpi_bcast(lboundopen, 1, 0, comm3d, ierr) !GT added
call d_mpi_bcast(fillvalues, nsv, 0, comm3d, ierr) !GT added

call timer_tic('modboundary/initboundary', 0)

allocate(tsc(k1))
! Sponge layer
Expand Down Expand Up @@ -120,15 +119,14 @@ end subroutine boundary
subroutine exitboundary
implicit none

deallocate(fillvalues)
!$acc exit data delete(tsc)
deallocate(tsc)
end subroutine exitboundary

!> Sets lateral periodic boundary conditions for the scalars
subroutine cyclich

use modglobal, only : i1,ih,j1,jh,k1,nsv,is_starting
use modglobal, only : i1,ih,j1,jh,k1,nsv
use modfields, only : thl0,qt0,sv0
use modmpi, only : excjs

Expand All @@ -149,7 +147,7 @@ end subroutine cyclich
!>set lateral periodic boundary conditions for momentum
subroutine cyclicm

use modglobal, only : i1,ih,j1,jh,k1,is_starting
use modglobal, only : i1,ih,j1,jh,k1
use modfields, only : u0,v0,w0,e120
use modmpi, only : excjs

Expand Down Expand Up @@ -272,8 +270,6 @@ subroutine grwdamp
!$acc wait
end if

call timer_toc('modboundary/grwdamp')

! damp layer-average horizontal velocity towards geowind with udvamprate
if (uvdamprate > 0) then
do k=1,kmax
Expand All @@ -282,7 +278,7 @@ subroutine grwdamp
end do
end if

return
call timer_toc('modboundary/grwdamp')
end subroutine grwdamp

!> Sets top boundary conditions for scalars
Expand Down
6 changes: 3 additions & 3 deletions src/moddrydeposition.f90
Original file line number Diff line number Diff line change
Expand Up @@ -35,12 +35,12 @@ module moddrydeposition
save
public :: initdrydep, drydep, exitdrydep

logical :: ldrydep !< On/Off switch dry deposition
logical :: ldrydep = .false. !< On/Off switch dry deposition
real, allocatable :: depfield(:,:,:) !< deposition flux (i,j,sv) [ug * m / (g * s)]
logical, dimension(100) :: ldeptracers = .false. !< List of switches determining which of the tracers to deposit
integer :: ndeptracers = 0 !< Number of tracers that deposits
integer :: iname
real :: nh3_avg, so2_avg !GT added to not have the valiables needed for the calculations of ccomp hardcoded
real :: nh3_avg = -1, so2_avg = -1 !GT added to not have the variables needed for the calculations of ccomp hardcoded

private :: Rc, Rb, vd

Expand Down Expand Up @@ -108,7 +108,7 @@ subroutine initdrydep
enddo

! --- Local pre-calculations and settings
if (ldrydep .and. ndeptracers == 0) then
if (ldrydep .and. ndeptracers == 0 .and. myid == 0) then
write (*,*) "initdrydep: WARNING .. drydeposition switched on, but no tracers to deposit. &
Continuing without deposition model"
end if
Expand Down
2 changes: 1 addition & 1 deletion src/modemisdata.f90
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,7 @@ module modemisdata
svskip = 0, & ! no. scalars to exclude for emission
nemis = 0 ! no. of emitted scalars
logical :: l_scale = .false. ! emission scaling switch
real, dimension(100) :: scalefactor
real, dimension(100) :: scalefactor = 1

character(len = 6), dimension(100) :: &
emisnames = (/ (' ', iname=1, 100) /) ! list with scalar names,
Expand Down
4 changes: 1 addition & 3 deletions src/modglobal.f90
Original file line number Diff line number Diff line change
Expand Up @@ -227,7 +227,7 @@ module modglobal
type(boundary_type), dimension(5) :: boundary
logical, dimension(5) :: lboundary = .false.
logical, dimension(5) :: lperiodic = (/.true., .true., .true., .true., .false./)
real(field_r) :: dxint=-1.,dyint=-1.,dzint=-1.,tauh=60.,taum=0.,tau=60.,lambda,lambdas=-1.,lambdas_x=-1.,lambdas_y=-1.,lambdas_z=-1.,dxturb=-1.,dyturb=-1.
real(field_r) :: dxint=-1.,dyint=-1.,dzint=-1.,tauh=60.,taum=0.,tau=60.,lambda=-1,lambdas=-1.,lambdas_x=-1.,lambdas_y=-1.,lambdas_z=-1.,dxturb=-1.,dyturb=-1.
integer :: nmodes=100,ntboundary=1,pbc = 3,iturb=0
real,dimension(:),allocatable :: tboundary

Expand Down Expand Up @@ -262,8 +262,6 @@ module modglobal
logical :: leq = .true. !< switch for (non)-equidistant mode.
logical :: lmomsubs = .false. !< switch to apply subsidence on the momentum or not

logical :: is_starting = .true. !< flag for knowing if a routine is called during startup

character(80) :: author='', version='DALES 4.4.2'
contains

Expand Down
4 changes: 2 additions & 2 deletions src/modlsm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -36,8 +36,8 @@ module modlsm
integer, parameter :: iinterp_max = 4 ! val = max(a,b)

! Soil grid
integer :: kmax_soil
real :: z_size_soil
integer :: kmax_soil = -1
real :: z_size_soil = -1
real, allocatable :: z_soil(:), zh_soil(:)
real, allocatable :: dz_soil(:), dzh_soil(:)
real, allocatable :: dzi_soil(:), dzhi_soil(:)
Expand Down
6 changes: 5 additions & 1 deletion src/modpois.f90
Original file line number Diff line number Diff line change
Expand Up @@ -82,8 +82,12 @@ subroutine initpois
allocate(pvp(2-ih:i1+ih,2-jh:j1+jh,kmax))
allocate(pwp(2-ih:i1+ih,2-jh:j1+jh,k1))

pup = 0 ! these fields use only one halo cell but are exchanged with ih,jh halo cells
pvp = 0 ! initialize now to not have uninitialized data in the unused halo cells

allocate(a(kmax), b(kmax), c(kmax))
!$acc enter data create(pup, pvp, pwp, a, b, c)
!$acc enter data copyin(pup, pvp)
!$acc enter data create(pwp, a, b, c)

end subroutine initpois

Expand Down
10 changes: 5 additions & 5 deletions src/modsurfdata.f90
Original file line number Diff line number Diff line change
Expand Up @@ -57,16 +57,16 @@ module modsurfdata
real, allocatable :: phiw (:,:,:) !< Water content soil matrix [-]
real, allocatable :: phiwm (:,:,:) !< Water content soil matrix previous time step [-]
real, allocatable :: phifrac (:,:,:) !< Relative water content per layer [-]
real :: phiwav (ksoilmax)
real :: phiwav (ksoilmax) = -1
real, allocatable :: phitot (:,:) !< Total soil water content [-]
real, allocatable :: pCs (:,:,:) !< Volumetric heat capacity [J/m3/K]
real, allocatable :: rootf (:,:,:) !< Root fraction per soil layer [-]
real :: rootfav (ksoilmax)
real :: rootfav (ksoilmax) = -1
real, allocatable :: tsoil (:,:,:) !< Soil temperature [K]
real, allocatable :: tsoilm (:,:,:) !< Soil temperature previous time step [K]
real :: tsoilav (ksoilmax)
real :: tsoilav (ksoilmax) = -1
real, allocatable :: tsoildeep (:,:) !< Soil temperature [K]
real :: tsoildeepav
real :: tsoildeepav = -1

real, allocatable :: swdavn (:,:,:)
real, allocatable :: swuavn (:,:,:)
Expand Down Expand Up @@ -206,7 +206,7 @@ module modsurfdata
real :: rssoilminav = -1
real, allocatable :: tendskin (:,:) !< Tendency of skin [W/m2]
real, allocatable :: gD (:,:) !< Response factor vegetation to vapor pressure deficit [-]
real :: gDav
real :: gDav = -1

! Turbulent exchange variables
logical :: lmostlocal = .false. !< Switch to apply MOST locally to get local Obukhov length
Expand Down
2 changes: 1 addition & 1 deletion src/modthermodynamics.f90
Original file line number Diff line number Diff line change
Expand Up @@ -85,7 +85,7 @@ end subroutine initthermodynamics
!! Calculate the liquid water content, do the microphysics, calculate the mean hydrostatic pressure,
!! calculate the fields at the half levels, and finally calculate the virtual potential temperature.
subroutine thermodynamics
use modglobal, only : lmoist,timee,k1,i1,j1,ih,jh,rd,rv,ijtot,cp,rlv,lnoclouds,lfast_thermo,is_starting
use modglobal, only : lmoist,timee,k1,i1,j1,ih,jh,rd,rv,ijtot,cp,rlv,lnoclouds,lfast_thermo
use modfields, only : thl0, qt0, ql0, presf, exnf, thvh, thv0h, qt0av, ql0av, thvf, rhof
use modmpi, only : slabsum, myid
implicit none
Expand Down

0 comments on commit 9640d69

Please sign in to comment.