CCPP SciDoc v7.0.0  v7.0.0
Common Community Physics Package Developed at DTC
 
Loading...
Searching...
No Matches
cires_ugwp_module.F90
1
3
6
7!
8! driver is called after pbl & before chem-parameterizations
9!
10
11 implicit none
12 logical :: module_is_initialized
13
14 logical :: do_physb_gwsrcs = .false.
15 logical :: do_rfdamp = .false.
16
17 real, parameter :: arad=6370.e3
18 real, parameter :: pi = atan(1.0)
19 real, parameter :: pi2 = 2.*pi
20 real, parameter :: hps = 7000.
21 real, parameter :: hpskm = hps/1000.
22!
23 real :: kxw = 6.28e-3/100.
24 real, parameter :: ricrit = 0.25
25 real, parameter :: frcrit = 0.50
26 real, parameter :: linsat = 1.00
27 real, parameter :: linsat2 = linsat*linsat
28!
29
30 integer :: knob_ugwp_solver=1
31 integer, dimension(4) :: knob_ugwp_source
32 integer, dimension(4) :: knob_ugwp_wvspec
33 integer, dimension(4) :: knob_ugwp_azdir
34 integer, dimension(4) :: knob_ugwp_stoch
35 real, dimension(4) :: knob_ugwp_effac
36
37 integer :: knob_ugwp_doaxyz=1
38 integer :: knob_ugwp_doheat=1
39 integer :: knob_ugwp_dokdis=0
40 integer :: knob_ugwp_ndx4lh = 2
41!
42 integer :: ugwp_azdir
43 integer :: ugwp_stoch
44
45 integer :: ugwp_src
46 integer :: ugwp_nws
47 real :: ugwp_effac
48
49!
50 data knob_ugwp_source / 1,0, 1, 0 /
51 data knob_ugwp_wvspec /1,32,32,32/
52 data knob_ugwp_azdir /2, 4, 4,4/
53 data knob_ugwp_stoch /0, 0, 0,0/
54 data knob_ugwp_effac /1.,1.,1.,1./
55 integer :: knob_ugwp_version = 0
56 integer :: launch_level = 55
57!
58 namelist /cires_ugwp_nml/ knob_ugwp_solver, knob_ugwp_source,knob_ugwp_wvspec, knob_ugwp_azdir, &
59 knob_ugwp_stoch, knob_ugwp_effac,knob_ugwp_doaxyz, knob_ugwp_doheat, knob_ugwp_dokdis, &
60 knob_ugwp_ndx4lh, knob_ugwp_version, launch_level
61
62!&cires_ugwp_nml
63! knob_ugwp_solver=2
64! knob_ugwp_source=1,1,1,0
65! knob_ugwp_wvspec=1,32,32,32
66! knob_ugwp_azdir =2, 4, 4,4
67! knob_ugwp_stoch =0, 0, 0,0
68! knob_ugwp_effac=1, 1, 1,1
69! knob_ugwp_doaxyz=1
70! knob_ugwp_doheat=1
71! knob_ugwp_dokdis=0
72! knob_ugwp_ndx4lh=4
73!/
74!
75! allocatable arrays, initilized during "cires_ugwp_init" &
76! released during "cires_ugwp_finalize"
77!
78 real, allocatable :: kvg(:), ktg(:), krad(:), kion(:)
79 real, allocatable :: zkm(:), pmb(:)
80 real, allocatable :: rfdis(:), rfdist(:)
81 integer :: levs_rf
82 real :: pa_rf, tau_rf
83!
84! limiters
85!
86 real, parameter :: max_kdis = 400. ! 400 m2/s
87 real, parameter :: max_axyz = 400.e-5 ! 400 m/s/day
88 real, parameter :: max_eps = max_kdis*4.e-7 ! ~16 K/day
89!
90!======================================================================
91 real, parameter :: f_coriol=1 ! Coriolis effects
92 real, parameter :: f_nonhyd=1 ! Nonhydrostatic waves
93 real, parameter :: f_kds =0 ! Eddy mixing due to GW-unstable below
94 real, parameter :: ipr_ktgw =1./3., ipr_spgw=ipr_ktgw
95 real, parameter :: ipr_turb =1./3., ipr_mol =1.95
96 real, parameter :: rhp1=1./hps, rhp2=0.5*rhp1, rhp4 = rhp2*rhp2
97 real, parameter :: khp = 0.287*rhp1 ! R/Cp/Hp
98 real, parameter :: cd_ulim = 1.0 ! critical level precision or Lz ~ 0 ~dz of model
99
100 contains
101!
102! -----------------------------------------------------------------------
103!
104! init of cires_ugwp (_init) called from GFS_driver.F90
105!
106! -----------------------------------------------------------------------
108 subroutine cires_ugwpv0_mod_init (me, master, nlunit, input_nml_file, logunit, &
109 fn_nml, lonr, latr, levs, ak, bk, pref, dtp, cdmvgwd, cgwf, &
110 pa_rf_in, tau_rf_in)
111
112 use ugwpv0_oro_init, only : init_oro_gws_v0
113 use ugwpv0_wmsdis_init, only : initsolv_wmsdis_v0, ilaunch
114 use ugwpv0_lsatdis_init, only : initsolv_lsatdis_v0
115
116 implicit none
117
118 integer, intent (in) :: me
119 integer, intent (in) :: master
120 integer, intent (in) :: nlunit
121 character (len = *), intent (in) :: input_nml_file(:)
122 integer, intent (in) :: logunit
123 character(len=64), intent (in) :: fn_nml
124 integer, intent (in) :: lonr
125 integer, intent (in) :: levs
126 integer, intent (in) :: latr
127 real, intent (in) :: ak(levs+1), bk(levs+1), pref
128 real, intent (in) :: dtp
129 real, intent (in) :: cdmvgwd(2), cgwf(2) ! "scaling" controls for "old" GFS-GW schemes
130 real, intent (in) :: pa_rf_in, tau_rf_in
131
132 integer :: ios
133 logical :: exists
134 real :: dxsg
135 integer :: k
136
137#ifdef INTERNAL_FILE_NML
138 read (input_nml_file, nml = cires_ugwp_nml)
139#else
140 if (me == master) print *, trim(fn_nml), ' GW-namelist file '
141
142 inquire (file =trim(fn_nml) , exist = exists)
143
144 if (.not. exists) then
145 if (me == master) &
146 write (6, *) 'separate ugwp :: namelist file: ', trim(fn_nml), ' does not exist'
147 else
148 open (unit = nlunit, file = trim(fn_nml), action = 'read', status = 'old', iostat = ios)
149 endif
150 rewind(nlunit)
151 read (nlunit, nml = cires_ugwp_nml)
152 close (nlunit)
153#endif
154
155!
156 ilaunch = launch_level
157 pa_rf = pa_rf_in
158 tau_rf = tau_rf_in
159
160! write version number and namelist to log file
161 if (me == master) then
162 write (logunit, *) " ================================================================== "
163 write (logunit, *) "cires_ugwp_cires"
164 write (logunit, nml = cires_ugwp_nml)
165 endif
166!
167! effective kxw - resolution-aware
168!
169 dxsg = pi2*arad/float(lonr) * knob_ugwp_ndx4lh
170!
171 allocate( kvg(levs+1), ktg(levs+1) )
172 allocate( krad(levs+1), kion(levs+1) )
173 allocate( zkm(levs), pmb(levs) )
174 allocate( rfdis(levs), rfdist(levs) )
175!
176! ak -pa bk-dimensionless from surf => tol_lid_pressure =0
177!
178 do k=1, levs
179 pmb(k) = 1.e0*(ak(k) + pref*bk(k)) ! Pa -unit Pref = 1.e5
180 zkm(k) = -hpskm*alog(pmb(k)/pref)
181 enddo
182!
183! Part-1 :init_global_gwdis
184!
185 call init_global_gwdis_v0(levs, zkm, pmb, kvg, ktg, krad, kion)
186
187!
188! Part-2 :init_SOURCES_gws -- only orowaves, but ugwp-v0 is based on gwdps.f of EMC
189!
190
191!
192! call init-solver for "stationary" multi-wave spectra and sub-grid oro
193!
194 call init_oro_gws_v0( knob_ugwp_wvspec(1), knob_ugwp_azdir(1), &
195 knob_ugwp_stoch(1), knob_ugwp_effac(1), lonr, kxw, cdmvgwd )
196!
197! call init-sources for "non-sationary" multi-wave spectra
198!
199 do_physb_gwsrcs=.true.
200
201!======================
202! Part-3 :init_SOLVERS
203! =====================
204!
205! call init-solvers for "broad" non-stationary multi-wave spectra
206!
207 if (knob_ugwp_solver==1) then
208!
209 call initsolv_lsatdis_v0(me, master, knob_ugwp_wvspec(2), knob_ugwp_azdir(2), &
210 knob_ugwp_stoch(2), knob_ugwp_effac(2), do_physb_gwsrcs, kxw )
211 endif
212 if (knob_ugwp_solver==2) then
213
214 call initsolv_wmsdis_v0(me, master, knob_ugwp_wvspec(2), knob_ugwp_azdir(2), &
215 knob_ugwp_stoch(2), knob_ugwp_effac(2), do_physb_gwsrcs, kxw)
216 endif
217
218
219!======================
220 module_is_initialized = .true.
221
222 end subroutine cires_ugwpv0_mod_init
223!
224! -----------------------------------------------------------------------
225! finalize of cires_ugwp (_finalize)
226! -----------------------------------------------------------------------
227
229 subroutine cires_ugwpv0_mod_finalize
230!
231! deallocate sources/spectra & some diagnostics need to find where "deaalocate them"
232! before "end" of the FV3GFS
233!
234 implicit none
235!
236! deallocate arrays employed in V0
237!
238 deallocate( kvg, ktg )
239 deallocate( krad, kion )
240 deallocate( zkm, pmb )
241 deallocate( rfdis, rfdist)
242
243 end subroutine cires_ugwpv0_mod_finalize
244!
245 end module cires_ugwpv0_module
246
This module contains the UGWPv0 driver.
This module contains initialization of wave solvers for UGWP v0.
This module contains orographic wave source schemes for UGWP v0.
This module contains init-solvers for "broad" non-stationary multi-wave spectra.