Skip to content

Commit

Permalink
TYPE: bug fix
Browse files Browse the repository at this point in the history
KEYWORDS: vertical refinement clean-up

SOURCE: Katie Lundquist (LLNL)

PURPOSE: fix incorrect diag messages, fix incorrect if tests, pass necessary nml variables to interpolating routines

DESCRIPTION OF CHANGES: 
M       Registry/Registry.EM_COMMON
Clean up descriptions of vert refine_method and vert_refine_fact. 

M       dyn_em/module_initialize_les.F
print out for eta levels
Check for top/bottom specified eta levels set to 0, 1 respectively (all domains, even though IC is only for domain #1)

M       dyn_em/module_initialize_real.F
Fix comments about vertical refinement, so no confusion over which method is being used
Verify specified eta levels have 1,0 bounds for each domain

M       dyn_em/nest_init_utils.F
pass through the nml argument use_baseparam_fr_nml
compute eta levels based on whether ideal or real-data case

M       main/depend.common
Add module_model_constants dependecy to nest_init_utils (for real data base state computation)

M       main/real_em.F
Fix logic for better control of which nests are vertically refined.

M       share/mediation_integrate.F
Pass through use_baseparam_fr_nml to init_domain_vert_nesting

M       share/module_check_a_mundo.F
Fix error checks when user selects the vertical refinement


LIST OF MODIFIED FILES (annotated if not obvious, not required to be on a single line): 
M       Registry/Registry.EM_COMMON
M       dyn_em/module_initialize_les.F
M       dyn_em/module_initialize_real.F
M       dyn_em/nest_init_utils.F
M       main/depend.common
M       main/real_em.F
M       share/mediation_integrate.F
M       share/module_check_a_mundo.F

TESTS CONDUCTED (explicitly state mandatory, voluntary, and assigned tests, not required to be on a single line):
1) regression test - do no harm
2) before vs after comparison of most regression tests are identical - only misses on tests that are not bit-for-bit identical anyways.



git-svn-id: https://svn-wrf-model.cgd.ucar.edu/trunk@9156 b0b5d27b-6f0f-0410-a2a3-cb1e977edc3d
  • Loading branch information
davegill committed Feb 22, 2016
1 parent 80b22b3 commit 99a689e
Show file tree
Hide file tree
Showing 8 changed files with 541 additions and 56 deletions.
4 changes: 2 additions & 2 deletions Registry/Registry.EM_COMMON
Original file line number Diff line number Diff line change
Expand Up @@ -1981,8 +1981,8 @@ rconfig integer num_metgrid_soil_levels namelist,domains 1 4
rconfig real p_top_requested namelist,domains 1 5000 irh "p_top_requested" "Pa" ""
rconfig logical interp_theta namelist,domains 1 .false. irh "interp_theta" "inside real, vertically interpolate theta (T) or temperature (F)" ""
rconfig integer interp_type namelist,domains 1 2 irh "interp_type" "1=interp in pressure, 2=interp in LOG pressure" ""
rconfig integer vert_refine_method namelist,domains max_domains 0 irh "vert_refine_method" "0=no vertical nesting, 1=integer refinement, 2=native WRF" ""
rconfig integer vert_refine_fact namelist,domains 1 1 irh "vertical refinment factor for ndown or for vertical nesting in a concurrent run" "" ""
rconfig integer vert_refine_method namelist,domains max_domains 0 irh "vert_refine_method" "0=no vertical nesting, 1=integer refinement, 2=use specified eta levels or compute_eta routine" ""
rconfig integer vert_refine_fact namelist,domains 1 1 irh "vertical refinment factor for ndown, not used for concurrent vertical grid nesting" "" ""
rconfig integer extrap_type namelist,domains 1 2 irh "extrap_type" "1= use 2 lowest levels, 2=constant" ""
rconfig integer t_extrap_type namelist,domains 1 2 irh "t_extrap_type" "1=isothermal, 2=6.5 K/km, 3=adiabatic" ""
rconfig integer hypsometric_opt namelist,domains 1 2 irh "hypsometric_opt" "Z relates P, 1=linearly, 2=LOG-linearly" ""
Expand Down
65 changes: 65 additions & 0 deletions dyn_em/module_initialize_les.F
Original file line number Diff line number Diff line change
Expand Up @@ -111,6 +111,11 @@ SUBROUTINE init_domain_rk ( grid &
! For LES, add randx
real :: randx


!DJW added for specifying different eta levels for each domain
INTEGER :: ks, ke, id
LOGICAL :: vnest !DJW T if using vertical nesting, otherwise F

#ifdef DM_PARALLEL
# include "data_calls.inc"
#endif
Expand Down Expand Up @@ -229,16 +234,76 @@ SUBROUTINE init_domain_rk ( grid &

! set up the grid

!DJW Added code for specifying multiple domains' eta_levels.
!First check to make sure that we've not specified more
!eta_levels than the dimensionality of eta_levels can handle! This
!issue will most likely cause a break sometime before we real this
!check, however it doesn't hurt to include it. To increase max_eta,
!go to frame/module_driver_constants.F.
vnest = .FALSE.
DO id=1,model_config_rec%max_dom
IF (model_config_rec%vert_refine_method(id) .NE. 0) THEN
vnest = .TRUE.
ENDIF
ENDDO
IF (model_config_rec%eta_levels(1) .EQ. -1) THEN !we do not have eta_levels from namelist
!DJW start of original code to set eta levels
IF (stretch_grid) THEN ! exponential stretch for eta (nearly constant dz)
CALL wrf_debug(0, "module_initialize_les: eta_levels is not specified in the namelist, setting levels with stretched spacing in eta.")
DO k=1, kde
grid%znw(k) = (exp(-(k-1)/float(kde-1)/z_scale) - exp(-1./z_scale))/ &
(1.-exp(-1./z_scale))
ENDDO
ELSE
CALL wrf_debug(0,"module_initialize_les: eta_levels is not specified in the namelist, setting levels with constant spacing in eta.")
DO k=1, kde
grid%znw(k) = 1. - float(k-1)/float(kde-1)
ENDDO
ENDIF
ELSE !we have specified eta levels from the namelist
CALL wrf_debug(0,"module_initialize_les: vertical nesting is enabled, using eta_levels specified in namelist.input")
ks = 0
DO id=1,grid%id
ks = ks+model_config_rec%e_vert(id)
ENDDO
IF (ks .GT. max_eta) THEN
CALL wrf_error_fatal("too many vertical levels, increase max_eta in frame/module_driver_constants.F")
ENDIF
!Now set the eta_levels to what we specified in the namelist. We've
!packed all the domains' eta_levels into a 'vector' and now we need
!to pull only the section of the vector associated with our domain
!of interest, which is between indicies ks and ke.
IF (grid%id .EQ. 1) THEN
ks = 1
ke = model_config_rec%e_vert(1)
ELSE
id = 1
ks = 1
ke = 0
DO WHILE (grid%id .GT. id)
id = id+1
ks = ks+model_config_rec%e_vert(id-1)
ke = ks+model_config_rec%e_vert(id)
ENDDO
ENDIF
DO k=1,kde
grid%znw(k) = model_config_rec%eta_levels(ks+k-1)
ENDDO
!Check the value of the first and last eta level for our domain,
!then check that the vector of eta levels is only decreasing
IF (grid%znw(1) .NE. 1.0) THEN
CALL wrf_error_fatal("error with specified eta_levels, first level is not 1.0")
ENDIF
IF (grid%znw(kde) .NE. 0.0) THEN
CALL wrf_error_fatal("error with specified eta_levels, last level is not 0.0")
ENDIF
DO k=2,kde
IF (grid%znw(k) .GT. grid%znw(k-1)) THEN
CALL wrf_error_fatal("eta_levels are not uniformly decreasing from 1.0 to 0.0")
ENDIF
ENDDO
ENDIF
DO k=1, kde-1
grid%dnw(k) = grid%znw(k+1) - grid%znw(k)
Expand Down
64 changes: 48 additions & 16 deletions dyn_em/module_initialize_real.F
Original file line number Diff line number Diff line change
Expand Up @@ -157,9 +157,9 @@ SUBROUTINE init_domain_rk ( grid &
REAL :: t_start , t_end
REAL , ALLOCATABLE , DIMENSION(:,:) :: clat_glob

! multiple specified sets of eta_levels
! added for multiple specified sets of eta_levels with vertical grid nesting
INTEGER :: ks, ke, id
LOGICAL :: vnest ! T if using vertical nesting, otherwise F
LOGICAL :: vnest !T if using vertical nesting with vet_refine_method=2, otherwise F

INTEGER :: j_save

Expand Down Expand Up @@ -1397,22 +1397,25 @@ SUBROUTINE init_domain_rk ( grid &
! Compute the eta levels if not defined already.
IF ( grid%znw(1) .NE. 1.0 ) THEN
!DJW Check if any of the domains are going to use vertical
!nesting with vert_refine_method=2. If so, set vnest as true.
vnest = .FALSE.
DO id=1,model_config_rec%max_dom
IF (model_config_rec%vert_refine_method(id) .NE. 0) THEN
IF (model_config_rec%vert_refine_method(id) .EQ. 2) THEN
vnest = .TRUE.
ENDIF
ENDDO
IF (vnest) THEN
!Added code for specifying multiple domains' eta_levels.
!DJW If there are eta_levels defined in the namelist and at
!least one domain is using vertical nesting, then we need to read in
!the eta_levels.
IF ((model_config_rec%eta_levels(1) .NE. -1.0) .AND. (vnest)) THEN
!DJW Added code for specifying multiple domains' eta_levels.
!First check to make sure that we've not specified more
!eta_levels than the dimensionality of eta_levels can handle! This
!issue will most likely cause a break sometime before we real this
!issue will most likely cause a break sometime before this
!check, however it doesn't hurt to include it. To increase max_eta,
!go to frame/module_driver_constants.F.

CALL wrf_debug ( 0, "using vertical nesting, reading in eta_levels specified in namelist.input" )
CALL wrf_debug (0, "module_initialize_real: using vert_refine_method=2, reading in eta_levels from namelist.input")
ks = 0
DO id=1,grid%id
ks = ks+model_config_rec%e_vert(id)
Expand Down Expand Up @@ -1441,22 +1444,51 @@ SUBROUTINE init_domain_rk ( grid &
!Check the value of the first and last eta level for our domain,
!then check that the vector of eta levels is only decreasing
IF (eta_levels(1) .NE. 1.0) THEN
CALL wrf_error_fatal("error with specified eta_levels, first level is not 1.0")
CALL wrf_error_fatal("--- ERROR: the first specified eta_level is not 1.0")
ENDIF
IF (eta_levels(kde) .NE. 0.0) THEN
CALL wrf_error_fatal("error with specified eta_levels, last level is not 0.0")
CALL wrf_error_fatal("--- ERROR: the last specified eta_level is not 0.0")
ENDIF
DO k=2,kde
IF (eta_levels(k) .GT. eta_levels(k-1)) THEN
CALL wrf_error_fatal("eta_levels are not uniformly decreasing from 1.0 to 0.0")
CALL wrf_error_fatal("--- ERROR: specified eta_levels are not uniformly decreasing from 1.0 to 0.0")
ENDIF
ENDDO
DO k=1,kde
write(a_message,'(A,I3,A,F5.3)') "eta_levels(",k,")=",eta_levels(k)
CALL wrf_message ( a_message )
!DJW End of added code for specifying eta_levels
ELSE !We're not using vertical nesting with eta_levels defined for every domain
!DJW Check if we're doing vertical nesting with integer refinement.
vnest = .FALSE.
DO id=1,model_config_rec%max_dom
IF (model_config_rec%vert_refine_method(id) .EQ. 1) THEN
vnest = .TRUE.
ENDIF
ENDDO
ELSE !We're not using vertical nesting
!DJW If we're doing vertical nesting using integer refinement and
!we've got eta_levels specified in the namelist then make sure they are
!for the parent domain and nothing else.
IF ((vnest) .AND. (model_config_rec%eta_levels(kde+1) .NE. -1.0)) THEN
write(wrf_err_message,'(A)') "--- ERROR: too many eta_levels defined in namelist.input."
CALL wrf_error_fatal( wrf_err_message )
!DJW Check the value of the first and last eta level for our
!domain, then check that the vector of eta levels is only decreasing
ELSEIF ((vnest) .AND. (model_config_rec%eta_levels(1) .NE. -1.0)) THEN
CALL wrf_debug(0, "module_initialize_real: using vert_refine_method=1, reading in eta_levels for d01 from namelist.input")
eta_levels(1:kde) = model_config_rec%eta_levels(1:kde)
IF (eta_levels(1) .NE. 1.0) THEN
CALL wrf_error_fatal("--- ERROR: the first specified eta_level is not 1.0")
ENDIF
IF (eta_levels(kde) .NE. 0.0) THEN
CALL wrf_error_fatal("--- ERROR: the last specified eta_level is not 0.0")
ENDIF
DO k=2,kde
IF (eta_levels(k) .GT. eta_levels(k-1)) THEN
CALL wrf_error_fatal("--- ERROR: specified eta_levels are not uniformly decreasing from 1.0 to 0.0")
ENDIF
ENDDO
ELSE
!DJW original code to set eta_levels
eta_levels(1:kde) = model_config_rec%eta_levels(1:kde)
ENDIF
ENDIF

max_dz = model_config_rec%max_dz
Expand Down
Loading

0 comments on commit 99a689e

Please sign in to comment.