Skip to content

Commit

Permalink
Allocation of radar LUT. Delete unused variables. Update ifort KGO v0…
Browse files Browse the repository at this point in the history
…02. (#77)

* Update ifort KGO

* Update KGO_VERSION

* Update cosp2_output.um_global.ifort.kgo.v002.out

* Delete cosp2_output.um_global.ifort.kgo.v003.out

* Update continuous_integration.yml

* KGV version back to v002

* Delete unused variables. Loop exit condition.

* Remove unused variables and prevent an unbound do loop from going out of bounds (causing a seg fault in some LFRic tests).

* Update cosp2_output.um_global.ifort.kgo.v002.out

* Delete minimum allocation

* Deallocate radar configuration.
  • Loading branch information
alejandrobodas authored Jun 7, 2023
1 parent f368fb4 commit 49c0d7e
Show file tree
Hide file tree
Showing 8 changed files with 33 additions and 15 deletions.
1 change: 0 additions & 1 deletion .github/workflows/continuous_integration.yml
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,6 @@ jobs:
F90FLAGS: "-O3 -ffree-line-length-none -fcheck=bounds -finit-real=nan"
ATOL: 0.0
RTOL: 0.0
#KGO_VERSION: v001
KGO_VERSION: v002
NFHOME: /home/runner/netcdf-fortran
LD_LIBRARY_PATH: /home/runner/netcdf-fortran/lib
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
Variable N AvgDiff MinDiff MaxDiff StDev
atb532_perp 2 -7.6571e-04 -7.6571e-04 -7.6571e-04 0.0000e+00
cfadLidarsr355 2 0.0000e+00 -1.0000e+00 1.0000e+00 1.0000e+00
dbze94 146 -8.4773e-04 -1.8231e-02 7.1885e-03 3.1420e-03
dbze94 137 -3.9947e-04 -1.0969e-02 1.2829e-02 2.8062e-03
boxtauisccp 14 7.7717e-04 -1.3064e-03 1.3325e-03 8.7738e-04
cltmodis 1 5.0000e-01 5.0000e-01 5.0000e-01 0.0000e+00
clwmodis 1 5.0000e-01 5.0000e-01 5.0000e-01 0.0000e+00
Expand Down
10 changes: 10 additions & 0 deletions driver/src/cosp2_test.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1371,6 +1371,16 @@ subroutine destroy_cospIN(y)
if (allocated(y%tau_mol_atlid)) deallocate(y%tau_mol_atlid)
if (allocated(y%tautot_atlid)) deallocate(y%tautot_atlid)
if (allocated(y%fracPrecipIce)) deallocate(y%fracPrecipIce)
if (allocated(y%rcfg_cloudsat%N_scale_flag)) deallocate(y%rcfg_cloudsat%N_scale_flag)
if (allocated(y%rcfg_cloudsat%Z_scale_flag)) deallocate(y%rcfg_cloudsat%Z_scale_flag)
if (allocated(y%rcfg_cloudsat%Z_scale_added_flag)) deallocate(y%rcfg_cloudsat%Z_scale_added_flag)
if (allocated(y%rcfg_cloudsat%Ze_scaled)) deallocate(y%rcfg_cloudsat%Ze_scaled)
if (allocated(y%rcfg_cloudsat%Zr_scaled)) deallocate(y%rcfg_cloudsat%Zr_scaled)
if (allocated(y%rcfg_cloudsat%kr_scaled)) deallocate(y%rcfg_cloudsat%kr_scaled)
if (allocated(y%rcfg_cloudsat%fc)) deallocate(y%rcfg_cloudsat%fc)
if (allocated(y%rcfg_cloudsat%rho_eff)) deallocate(y%rcfg_cloudsat%rho_eff)
if (allocated(y%rcfg_cloudsat%base_list)) deallocate(y%rcfg_cloudsat%base_list)
if (allocated(y%rcfg_cloudsat%step_list)) deallocate(y%rcfg_cloudsat%step_list)
end subroutine destroy_cospIN
!%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
! SUBROUTINE destroy_cospstateIN
Expand Down
3 changes: 1 addition & 2 deletions src/cosp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -385,7 +385,7 @@ function COSP_SIMULATOR(cospIN,cospgridIN,cospOUT,start_idx,stop_idx,debug)
out1D_1,out1D_2,out1D_3,out1D_4,out1D_5,out1D_6,out1D_7,out1D_8, &
out1D_9,out1D_10,out1D_11,out1D_12
real(wp),dimension(:,:,:),allocatable :: &
betamol_in,betamoli,pnormi,ze_toti,ze_noni
betamol_in,betamoli,pnormi,ze_toti
real(wp),dimension(:,:,:),allocatable :: &
t_in,tempI,frac_outI ! subscript "I": vertical interpolation (use_vgrid=.true.)
real(wp), allocatable :: &
Expand Down Expand Up @@ -1884,7 +1884,6 @@ subroutine cosp_errorCheck(cospgridIN, cospIN, Lisccp_subcolumn, Lisccp_column,
integer,intent(out) :: nError

! Local variables
character(len=100) :: parasolErrorMessage
logical :: alloc_status

nError = 0
Expand Down
3 changes: 1 addition & 2 deletions src/cosp_stats.F90
Original file line number Diff line number Diff line change
Expand Up @@ -108,6 +108,7 @@ SUBROUTINE COSP_CHANGE_VERTICAL_GRID(Npoints,Ncolumns,Nlevels,zfull,zhalf,y,Ngle
do
l = l + 1
w = 0.0 ! Initialise weight to 0
if (l > Nlevels) exit
! Distances between edges of both grids
dbb = oldgrid_bot(l) - newgrid_bot(k)
dtb = oldgrid_top(l) - newgrid_bot(k)
Expand Down Expand Up @@ -322,13 +323,11 @@ SUBROUTINE COSP_DIAG_WARMRAIN( Npoints, Ncolumns, Nlevels, & !! in

! Local variables
integer :: i, j, k
integer :: ix, iy
integer :: kctop, kcbtm
integer :: icls
integer :: iregime
real :: cmxdbz
real(wp) :: diagcgt !! diagnosed cloud geometric thickness [m]
real(wp) :: diagdbze !! diagnosed dBZe
real(wp) :: diagicod !! diagnosed in-cloud optical depth
real(wp) :: cbtmh !! diagnosed in-cloud optical depth
real(wp), dimension(Npoints,Ncolumns,Nlevels) :: icod !! in-cloud optical depth (ICOD)
Expand Down
2 changes: 1 addition & 1 deletion src/simulator/actsim/lidar_simulator.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1165,7 +1165,7 @@ SUBROUTINE COSP_CLDFRAC_NOPHASE(Npoints,Ncolumns,Nlevels,Ncat,x,ATB,pplay,

! Local variables
integer :: &
ip, k, iz, ic, ncol, nlev, i
ip, k, iz, ic
real(wp) :: &
p1
real(wp),dimension(Npoints,Nlevels) :: &
Expand Down
14 changes: 13 additions & 1 deletion src/simulator/cosp_cloudsat_interface.F90
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,8 @@
! %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
MODULE MOD_COSP_CLOUDSAT_INTERFACE
USE COSP_KINDS, ONLY: wp
USE quickbeam, ONLY: quickbeam_init,radar_cfg,Re_MAX_BIN,Re_BIN_LENGTH
USE quickbeam, ONLY: quickbeam_init,radar_cfg,Re_MAX_BIN,Re_BIN_LENGTH, &
maxhclass, nRe_types, nd, mt_ntt
IMPLICIT NONE

! Directory where LUTs will be stored
Expand Down Expand Up @@ -99,6 +100,17 @@ SUBROUTINE COSP_CLOUDSAT_INIT(radar_freq,k2,use_gas_abs,do_ray,undef,nhydro, &
trim(cloudsat_micro_scheme)

! Initialize for NEW radar-configurarion derived type (radar_cfg)
allocate(rcfg%N_scale_flag(maxhclass,nRe_types))
allocate(rcfg%Z_scale_flag(maxhclass,mt_ntt,nRe_types))
allocate(rcfg%Z_scale_added_flag(maxhclass,mt_ntt,nRe_types))
allocate(rcfg%Ze_scaled(maxhclass,mt_ntt,nRe_types))
allocate(rcfg%Zr_scaled(maxhclass,mt_ntt,nRe_types))
allocate(rcfg%kr_scaled(maxhclass,mt_ntt,nRe_types))
allocate(rcfg%fc(maxhclass,nd,nRe_types))
allocate(rcfg%rho_eff(maxhclass,nd,nRe_types))
allocate(rcfg%base_list(Re_MAX_BIN))
allocate(rcfg%step_list(Re_MAX_BIN))

rcfg%freq = radar_freq
rcfg%k2 = k2
rcfg%use_gas_abs = use_gas_abs
Expand Down
13 changes: 6 additions & 7 deletions src/simulator/quickbeam/quickbeam.F90
Original file line number Diff line number Diff line change
Expand Up @@ -90,12 +90,11 @@ module quickbeam
! Variables used to store Z scale factors
character(len=240) :: scale_LUT_file_name
logical :: load_scale_LUTs, update_scale_LUTs
logical, dimension(maxhclass,nRe_types) :: N_scale_flag
logical, dimension(maxhclass,mt_ntt,nRe_types) :: Z_scale_flag,Z_scale_added_flag
real(wp),dimension(maxhclass,mt_ntt,nRe_types) :: Ze_scaled,Zr_scaled,kr_scaled
real(wp),dimension(maxhclass,nd,nRe_types) :: fc, rho_eff
real(wp),dimension(Re_MAX_BIN) :: base_list,step_list

logical, allocatable, dimension(:,:) :: N_scale_flag
logical, allocatable, dimension(:,:,:) :: Z_scale_flag, Z_scale_added_flag
real(wp), allocatable, dimension(:,:,:) :: Ze_scaled, Zr_scaled, kr_scaled
real(wp), allocatable, dimension(:,:,:) :: fc, rho_eff
real(wp), allocatable, dimension(:) :: base_list, step_list
end type radar_cfg

contains
Expand Down Expand Up @@ -383,7 +382,7 @@ subroutine cloudsat_precipOccurence(Npoints, Ncolumns, llm, Nhydro, Ze_out, Ze_n
integer,dimension(Npoints) :: &
cloudsat_preclvl_index ! Altitude index for precip flags calculation
! in 40-level grid (one layer above surfelev)
integer :: pr,i,k,m,j
integer :: pr,i,k
real(wp) :: Zmax

! Initialize
Expand Down

0 comments on commit 49c0d7e

Please sign in to comment.