PageRenderTime 58ms CodeModel.GetById 21ms RepoModel.GetById 1ms app.codeStats 0ms

/wrfv2_fire/dyn_em/module_initialize_scm_xy.F

http://github.com/jbeezley/wrf-fire
FORTRAN Legacy | 852 lines | 503 code | 197 blank | 152 comment | 17 complexity | 4b5a0b7aeaf09f7a33b602a035425cb9 MD5 | raw file
Possible License(s): AGPL-1.0
  1. !IDEAL:MODEL_LAYER:INITIALIZATION
  2. !
  3. ! This MODULE holds the routines which are used to perform various initializations
  4. ! for the individual domains.
  5. ! This MODULE CONTAINS the following routines:
  6. ! initialize_field_test - 1. Set different fields to different constant
  7. ! values. This is only a test. If the correct
  8. ! domain is not found (based upon the "id")
  9. ! then a fatal error is issued.
  10. !-----------------------------------------------------------------------
  11. MODULE module_initialize_ideal
  12. USE module_domain
  13. USE module_io_domain
  14. USE module_state_description
  15. USE module_model_constants
  16. USE module_bc
  17. USE module_timing
  18. USE module_configure
  19. USE module_init_utilities
  20. USE module_soil_pre
  21. #ifdef DM_PARALLEL
  22. USE module_dm
  23. #endif
  24. CONTAINS
  25. !-------------------------------------------------------------------
  26. ! this is a wrapper for the solver-specific init_domain routines.
  27. ! Also dereferences the grid variables and passes them down as arguments.
  28. ! This is crucial, since the lower level routines may do message passing
  29. ! and this will get fouled up on machines that insist on passing down
  30. ! copies of assumed-shape arrays (by passing down as arguments, the
  31. ! data are treated as assumed-size -- ie. f77 -- arrays and the copying
  32. ! business is avoided). Fie on the F90 designers. Fie and a pox.
  33. ! NOTE: Modified to remove all but arrays of rank 4 or more from the
  34. ! argument list. Arrays with rank>3 are still problematic due to the
  35. ! above-noted fie- and pox-ities. TBH 20061129.
  36. SUBROUTINE init_domain ( grid )
  37. IMPLICIT NONE
  38. ! Input data.
  39. TYPE (domain), POINTER :: grid
  40. ! Local data.
  41. INTEGER :: idum1, idum2
  42. CALL set_scalar_indices_from_config ( head_grid%id , idum1, idum2 )
  43. CALL init_domain_rk( grid &
  44. !
  45. #include <actual_new_args.inc>
  46. !
  47. )
  48. END SUBROUTINE init_domain
  49. !-------------------------------------------------------------------
  50. SUBROUTINE init_domain_rk ( grid &
  51. !
  52. # include <dummy_new_args.inc>
  53. !
  54. )
  55. USE module_optional_input
  56. IMPLICIT NONE
  57. ! Input data.
  58. TYPE (domain), POINTER :: grid
  59. # include <dummy_new_decl.inc>
  60. TYPE (grid_config_rec_type) :: config_flags
  61. ! Local data
  62. INTEGER :: &
  63. ids, ide, jds, jde, kds, kde, &
  64. ims, ime, jms, jme, kms, kme, &
  65. its, ite, jts, jte, kts, kte, &
  66. i, j, k
  67. ! JPH should add a read to a config file with:
  68. ! ----- check to make sure everything is initialized from the LU index, etc.
  69. ! ----- need to make a dummy category?
  70. ! cen_lat, cen_lon
  71. ! land-use category
  72. ! soil category
  73. ! Local data
  74. INTEGER, PARAMETER :: nl_max = 1000
  75. REAL, DIMENSION(nl_max) :: zk, p_in, theta, rho, u, v, qv, pd_in
  76. INTEGER :: nl_in
  77. INTEGER :: ii, im1, jj, jm1, loop, error, fid, lm
  78. REAL :: u_mean,v_mean, f0, p_surf, p_level, qvf, z_at_v, z_at_u
  79. REAL :: xrad, yrad, zrad, rad, cof1, cof2
  80. REAL :: pi, rnd
  81. ! stuff from original initialization that has been dropped from the Registry
  82. REAL :: vnu, xnu, xnus, dinit0, cbh, p0_temp, t0_temp, zd
  83. REAL :: qvf1, qvf2, pd_surf
  84. INTEGER :: it
  85. real :: thtmp, ptmp, temp(3)
  86. real :: zsfc
  87. LOGICAL :: moisture_init
  88. LOGICAL :: dry_sounding
  89. character (len=256) :: mminlu2
  90. ! soil input
  91. INTEGER :: ns_input
  92. REAL :: tmn_input, tsk_input
  93. REAL :: zs_input(100),tslb_input(100),smois_input(100)
  94. LOGICAL :: real_soil = .true.
  95. REAL :: zrwa(200), zwa(200)
  96. #ifdef DM_PARALLEL
  97. # include <data_calls.inc>
  98. #endif
  99. SELECT CASE ( model_data_order )
  100. CASE ( DATA_ORDER_ZXY )
  101. kds = grid%sd31 ; kde = grid%ed31 ;
  102. ids = grid%sd32 ; ide = grid%ed32 ;
  103. jds = grid%sd33 ; jde = grid%ed33 ;
  104. kms = grid%sm31 ; kme = grid%em31 ;
  105. ims = grid%sm32 ; ime = grid%em32 ;
  106. jms = grid%sm33 ; jme = grid%em33 ;
  107. kts = grid%sp31 ; kte = grid%ep31 ; ! note that tile is entire patch
  108. its = grid%sp32 ; ite = grid%ep32 ; ! note that tile is entire patch
  109. jts = grid%sp33 ; jte = grid%ep33 ; ! note that tile is entire patch
  110. CASE ( DATA_ORDER_XYZ )
  111. ids = grid%sd31 ; ide = grid%ed31 ;
  112. jds = grid%sd32 ; jde = grid%ed32 ;
  113. kds = grid%sd33 ; kde = grid%ed33 ;
  114. ims = grid%sm31 ; ime = grid%em31 ;
  115. jms = grid%sm32 ; jme = grid%em32 ;
  116. kms = grid%sm33 ; kme = grid%em33 ;
  117. its = grid%sp31 ; ite = grid%ep31 ; ! note that tile is entire patch
  118. jts = grid%sp32 ; jte = grid%ep32 ; ! note that tile is entire patch
  119. kts = grid%sp33 ; kte = grid%ep33 ; ! note that tile is entire patch
  120. CASE ( DATA_ORDER_XZY )
  121. ids = grid%sd31 ; ide = grid%ed31 ;
  122. kds = grid%sd32 ; kde = grid%ed32 ;
  123. jds = grid%sd33 ; jde = grid%ed33 ;
  124. ims = grid%sm31 ; ime = grid%em31 ;
  125. kms = grid%sm32 ; kme = grid%em32 ;
  126. jms = grid%sm33 ; jme = grid%em33 ;
  127. its = grid%sp31 ; ite = grid%ep31 ; ! note that tile is entire patch
  128. kts = grid%sp32 ; kte = grid%ep32 ; ! note that tile is entire patch
  129. jts = grid%sp33 ; jte = grid%ep33 ; ! note that tile is entire patch
  130. END SELECT
  131. pi = 2.*asin(1.0)
  132. write(6,*) ' pi is ',pi
  133. CALL model_to_grid_config_rec ( grid%id , model_config_rec , config_flags )
  134. ! here we check to see if the boundary conditions are set properly
  135. CALL boundary_condition_check( config_flags, bdyzone, error, grid%id )
  136. moisture_init = .true.
  137. grid%itimestep=0
  138. mminlu2 = ' '
  139. mminlu2(1:4) = 'USGS'
  140. CALL nl_set_mminlu(1, mminlu2)
  141. ! CALL nl_set_mminlu(1, 'USGS')
  142. CALL nl_set_iswater(1,16)
  143. CALL nl_set_isice(1,3)
  144. CALL nl_set_truelat1(1,0.)
  145. CALL nl_set_truelat2(1,0.)
  146. CALL nl_set_moad_cen_lat (1,0.)
  147. CALL nl_set_stand_lon(1,0.)
  148. CALL nl_set_pole_lon (1,0.)
  149. CALL nl_set_pole_lat (1,90.)
  150. CALL nl_set_map_proj(1,0)
  151. ! CALL model_to_grid_config_rec(1,model_config_rec,config_flags)
  152. CALL nl_get_iswater(1,grid%iswater)
  153. ! here we initialize data that currently is not initialized
  154. ! in the input data
  155. DO j = jts, jte
  156. DO i = its, ite
  157. grid%msft(i,j) = 1.
  158. grid%msfu(i,j) = 1.
  159. grid%msfv(i,j) = 1.
  160. grid%msftx(i,j) = 1.
  161. grid%msfty(i,j) = 1.
  162. grid%msfux(i,j) = 1.
  163. grid%msfuy(i,j) = 1.
  164. grid%msfvx(i,j) = 1.
  165. grid%msfvx_inv(i,j) = 1.
  166. grid%msfvy(i,j) = 1.
  167. grid%sina(i,j) = 0.
  168. grid%cosa(i,j) = 1.
  169. grid%e(i,j) = 2.0*EOMEG*cos(config_flags%scm_lat*DEGRAD)
  170. grid%f(i,j) = 2.0*EOMEG*sin(config_flags%scm_lat*DEGRAD)
  171. grid%xlat(i,j) = config_flags%scm_lat
  172. grid%xlong(i,j) = config_flags%scm_lon
  173. grid%xland(i,j) = 1.
  174. grid%landmask(i,j) = 1.
  175. grid%lu_index(i,j) = config_flags%scm_lu_index
  176. END DO
  177. END DO
  178. ! for LSM, additional variables need to be initialized
  179. ! other_masked_fields : SELECT CASE ( model_config_rec%sf_surface_physics(grid%id) )
  180. ! CASE (SLABSCHEME)
  181. ! CASE (LSMSCHEME)
  182. ! JPH free of snow and ice, and only valid over land
  183. DO j = jts , MIN(jde-1,jte)
  184. DO i = its , MIN(ide-1,ite)
  185. grid%vegfra(i,j) = config_flags%scm_vegfra
  186. grid%canwat(i,j) = config_flags%scm_canwat
  187. grid%isltyp(i,j) = config_flags%scm_isltyp
  188. grid%ivgtyp(i,j) = config_flags%scm_lu_index
  189. grid%xice(i,j) = 0.
  190. grid%snow(i,j) = 0.
  191. END DO
  192. END DO
  193. ! CASE (RUCLSMSCHEME)
  194. ! END SELECT other_masked_fields
  195. grid%step_number = 0
  196. IF ( real_soil ) THEN ! from input file
  197. IF (config_flags%sf_surface_physics .NE. 2) WRITE (6, *) &
  198. 'If using LSM option other than Noah, must edit input_soil file in test/em_scm_xy/ directory'
  199. CALL read_soil(100,ns_input,tmn_input,tsk_input,zs_input,tslb_input,smois_input)
  200. CALL init_module_optional_input(grid,config_flags)
  201. num_st_levels_input = ns_input
  202. num_sm_levels_input = ns_input
  203. num_sw_levels_input = ns_input
  204. DO k = 1,ns_input
  205. st_levels_input(k) = zs_input(k)*100.0 ! to cm
  206. sm_levels_input(k) = zs_input(k)*100.0 ! to cm
  207. sw_levels_input(k) = zs_input(k)*100.0 ! to cm
  208. st_input(:,k+1,:) = tslb_input(k)
  209. sm_input(:,k+1,:) = smois_input(k)
  210. sw_input(:,k+1,:) = smois_input(k)
  211. ENDDO
  212. grid%tsk = tsk_input
  213. grid%sst = tsk_input
  214. grid%tmn = tmn_input
  215. flag_soil_layers = 0 ! go ahead and put skin temp in
  216. flag_soil_levels = 0 ! go ahead and put skin moisture in
  217. flag_sst = 0 ! don't modify for ocean
  218. flag_tavgsfc = 0
  219. flag_soilhgt = 0
  220. CALL process_soil_real ( grid%tsk , grid%tmn , grid%tavgsfc, &
  221. grid%landmask , grid%sst , grid%ht, grid%toposoil, &
  222. st_input , sm_input , sw_input , &
  223. st_levels_input , sm_levels_input , sw_levels_input , &
  224. grid%zs , grid%dzs , grid%tslb , grid%smois , grid%sh2o , &
  225. flag_sst , flag_tavgsfc, flag_soilhgt, flag_soil_layers, flag_soil_levels, &
  226. ids , ide , jds , jde , kds , kde , &
  227. ims , ime , jms , jme , kms , kme , &
  228. its , ite , jts , jte , kts , kte , &
  229. model_config_rec%sf_surface_physics(grid%id) , &
  230. model_config_rec%num_soil_layers , &
  231. model_config_rec%real_data_init_type , &
  232. num_st_levels_input , num_sm_levels_input , num_sw_levels_input , &
  233. num_st_levels_alloc , num_sm_levels_alloc , num_sw_levels_alloc )
  234. ELSE ! ideal soil
  235. ! Process the soil; note that there are some things hard-wired into share/module_soil_pre.F
  236. CALL process_soil_ideal(grid%xland,grid%xice,grid%vegfra,grid%snow,grid%canwat, &
  237. grid%ivgtyp,grid%isltyp,grid%tslb,grid%smois, &
  238. grid%tsk,grid%tmn,grid%zs,grid%dzs,model_config_rec%num_soil_layers, &
  239. model_config_rec%sf_surface_physics(grid%id), &
  240. ids,ide, jds,jde, kds,kde,&
  241. ims,ime, jms,jme, kms,kme,&
  242. its,ite, jts,jte, kts,kte )
  243. ENDIF
  244. DO j = jts, jte
  245. DO k = kts, kte
  246. DO i = its, ite
  247. grid%ww(i,k,j) = 0.
  248. END DO
  249. END DO
  250. END DO
  251. ! this is adopted from Wayne Angevine's GABLS case
  252. grid%znw(1) = 1.0
  253. zrwa(kde) = exp((kde-1)/40.)
  254. zwa(kde) = grid%ztop
  255. DO k=2, kde-1
  256. zrwa(k) = exp((k-1)/40.)
  257. zwa(k) = (zrwa(k)-1.) * grid%ztop/(zrwa(kde)-1.)
  258. grid%znw(k) = 1. - (zwa(k) / zwa(kde))
  259. ENDDO
  260. grid%znw(kde) = 0.
  261. DO k=1, kde-1
  262. grid%dnw(k) = grid%znw(k+1) - grid%znw(k)
  263. grid%rdnw(k) = 1./grid%dnw(k)
  264. grid%znu(k) = 0.5*(grid%znw(k+1)+grid%znw(k))
  265. ENDDO
  266. DO k=2, kde-1
  267. grid%dn(k) = 0.5*(grid%dnw(k)+grid%dnw(k-1))
  268. grid%rdn(k) = 1./grid%dn(k)
  269. grid%fnp(k) = .5* grid%dnw(k )/grid%dn(k)
  270. grid%fnm(k) = .5* grid%dnw(k-1)/grid%dn(k)
  271. ENDDO
  272. cof1 = (2.*grid%dn(2)+grid%dn(3))/(grid%dn(2)+grid%dn(3))*grid%dnw(1)/grid%dn(2)
  273. cof2 = grid%dn(2) /(grid%dn(2)+grid%dn(3))*grid%dnw(1)/grid%dn(3)
  274. grid%cf1 = grid%fnp(2) + cof1
  275. grid%cf2 = grid%fnm(2) - cof1 - cof2
  276. grid%cf3 = cof2
  277. grid%cfn = (.5*grid%dnw(kde-1)+grid%dn(kde-1))/grid%dn(kde-1)
  278. grid%cfn1 = -.5*grid%dnw(kde-1)/grid%dn(kde-1)
  279. grid%rdx = 1./config_flags%dx
  280. grid%rdy = 1./config_flags%dy
  281. ! get the sounding from the ascii sounding file, first get dry sounding and
  282. ! calculate base state
  283. write(6,*) ' getting dry sounding for base state '
  284. dry_sounding = .true.
  285. CALL get_sounding( zsfc, zk, p_in, pd_in, theta, rho, u, v, qv, dry_sounding, nl_max, nl_in )
  286. write(6,*) ' returned from reading sounding, nl_in is ',nl_in
  287. ! find ptop for the desired ztop (ztop is input from the namelist),
  288. ! and find surface pressure
  289. grid%p_top = interp_0( p_in, zk, config_flags%ztop, nl_in )
  290. DO j=jts,jte
  291. DO i=its,ite ! flat surface
  292. grid%ht(i,j) = zsfc
  293. grid%phb(i,1,j) = grid%ht(i,j) * g
  294. grid%ph0(i,1,j) = grid%ht(i,j) * g
  295. grid%php(i,1,j) = 0.
  296. ENDDO
  297. ENDDO
  298. DO J = jts, jte
  299. DO I = its, ite
  300. p_surf = interp_0( p_in, zk, grid%phb(i,1,j)/g, nl_in )
  301. grid%mub(i,j) = p_surf-grid%p_top
  302. ! this is dry hydrostatic sounding (base state), so given grid%p (coordinate),
  303. ! interp theta (from interp) and compute 1/rho from eqn. of state
  304. DO K = 1, kte-1
  305. p_level = grid%znu(k)*(p_surf - grid%p_top) + grid%p_top
  306. grid%pb(i,k,j) = p_level
  307. grid%t_init(i,k,j) = interp_0( theta, p_in, p_level, nl_in ) - t0
  308. grid%alb(i,k,j) = (r_d/p1000mb)*(grid%t_init(i,k,j)+t0)*(grid%pb(i,k,j)/p1000mb)**cvpm
  309. ENDDO
  310. ! calc hydrostatic balance (alternatively we could interp the geopotential from the
  311. ! sounding, but this assures that the base state is in exact hydrostatic balance with
  312. ! respect to the model eqns.
  313. DO k = 2,kte
  314. grid%phb(i,k,j) = grid%phb(i,k-1,j) - grid%dnw(k-1)*grid%mub(i,j)*grid%alb(i,k-1,j)
  315. ENDDO
  316. ENDDO
  317. ENDDO
  318. write(6,*) ' ptop is ',grid%p_top
  319. write(6,*) ' base state grid%mub(1,1), p_surf is ',grid%mub(1,1),grid%mub(1,1)+grid%p_top
  320. ! calculate full state for each column - this includes moisture.
  321. write(6,*) ' getting moist sounding for full state '
  322. dry_sounding = .false.
  323. CALL get_sounding( zsfc, zk, p_in, pd_in, theta, rho, u, v, qv, dry_sounding, nl_max, nl_in )
  324. DO J = jts, min(jde-1,jte)
  325. DO I = its, min(ide-1,ite)
  326. ! At this point grid%p_top is already set. find the DRY mass in the column
  327. ! by interpolating the DRY pressure.
  328. pd_surf = interp_0( pd_in, zk, grid%phb(i,1,j)/g, nl_in )
  329. ! compute the perturbation mass and the full mass
  330. grid%mu_1(i,j) = pd_surf-grid%p_top - grid%mub(i,j)
  331. grid%mu_2(i,j) = grid%mu_1(i,j)
  332. grid%mu0(i,j) = grid%mu_1(i,j) + grid%mub(i,j)
  333. ! given the dry pressure and coordinate system, interp the potential
  334. ! temperature and qv
  335. do k=1,kde-1
  336. p_level = grid%znu(k)*(pd_surf - grid%p_top) + grid%p_top
  337. moist(i,k,j,P_QV) = interp_0( qv, pd_in, p_level, nl_in )
  338. grid%t_1(i,k,j) = interp_0( theta, pd_in, p_level, nl_in ) - t0
  339. grid%t_2(i,k,j) = grid%t_1(i,k,j)
  340. enddo
  341. ! integrate the hydrostatic equation (from the RHS of the bigstep
  342. ! vertical momentum equation) down from the top to get grid%p.
  343. ! first from the top of the model to the top pressure
  344. k = kte-1 ! top level
  345. qvf1 = 0.5*(moist(i,k,j,P_QV)+moist(i,k,j,P_QV))
  346. qvf2 = 1./(1.+qvf1)
  347. qvf1 = qvf1*qvf2
  348. ! grid%p(i,k,j) = - 0.5*grid%mu_1(i,j)/grid%rdnw(k)
  349. grid%p(i,k,j) = - 0.5*(grid%mu_1(i,j)+qvf1*grid%mub(i,j))/grid%rdnw(k)/qvf2
  350. qvf = 1. + rvovrd*moist(i,k,j,P_QV)
  351. grid%alt(i,k,j) = (r_d/p1000mb)*(grid%t_1(i,k,j)+t0)*qvf* &
  352. (((grid%p(i,k,j)+grid%pb(i,k,j))/p1000mb)**cvpm)
  353. grid%al(i,k,j) = grid%alt(i,k,j) - grid%alb(i,k,j)
  354. ! down the column
  355. do k=kte-2,1,-1
  356. qvf1 = 0.5*(moist(i,k,j,P_QV)+moist(i,k+1,j,P_QV))
  357. qvf2 = 1./(1.+qvf1)
  358. qvf1 = qvf1*qvf2
  359. grid%p(i,k,j) = grid%p(i,k+1,j) - (grid%mu_1(i,j) + qvf1*grid%mub(i,j))/qvf2/grid%rdn(k+1)
  360. qvf = 1. + rvovrd*moist(i,k,j,P_QV)
  361. grid%alt(i,k,j) = (r_d/p1000mb)*(grid%t_1(i,k,j)+t0)*qvf* &
  362. (((grid%p(i,k,j)+grid%pb(i,k,j))/p1000mb)**cvpm)
  363. grid%al(i,k,j) = grid%alt(i,k,j) - grid%alb(i,k,j)
  364. enddo
  365. ! this is the hydrostatic equation used in the model after the
  366. ! small timesteps. In the model, grid%al (inverse density)
  367. ! is computed from the geopotential.
  368. grid%ph_1(i,1,j) = 0.
  369. DO k = 2,kte
  370. grid%ph_1(i,k,j) = grid%ph_1(i,k-1,j) - (1./grid%rdnw(k-1))*( &
  371. (grid%mub(i,j)+grid%mu_1(i,j))*grid%al(i,k-1,j)+ &
  372. grid%mu_1(i,j)*grid%alb(i,k-1,j) )
  373. grid%ph_2(i,k,j) = grid%ph_1(i,k,j)
  374. grid%ph0(i,k,j) = grid%ph_1(i,k,j) + grid%phb(i,k,j)
  375. ENDDO
  376. if((i==2) .and. (j==2)) then
  377. write(6,*) ' grid%ph_1 calc ',grid%ph_1(2,1,2),grid%ph_1(2,2,2),&
  378. grid%mu_1(2,2)+grid%mub(2,2),grid%mu_1(2,2), &
  379. grid%alb(2,1,2),grid%al(1,2,1),grid%rdnw(1)
  380. endif
  381. ENDDO
  382. ENDDO
  383. write(6,*) ' grid%mu_1 from comp ', grid%mu_1(1,1)
  384. write(6,*) ' full state sounding from comp, ph, grid%p, grid%al, grid%t_1, qv '
  385. do k=1,kde-1
  386. write(6,'(i3,1x,5(1x,1pe10.3))') k, grid%ph_1(1,k,1)+grid%phb(1,k,1), &
  387. grid%p(1,k,1)+grid%pb(1,k,1), grid%alt(1,k,1), &
  388. grid%t_1(1,k,1)+t0, moist(1,k,1,P_QV)
  389. enddo
  390. write(6,*) ' pert state sounding from comp, grid%ph_1, pp, alp, grid%t_1, qv '
  391. do k=1,kde-1
  392. write(6,'(i3,1x,5(1x,1pe10.3))') k, grid%ph_1(1,k,1), &
  393. grid%p(1,k,1), grid%al(1,k,1), &
  394. grid%t_1(1,k,1), moist(1,k,1,P_QV)
  395. enddo
  396. ! interp v
  397. DO J = jts, jte
  398. DO I = its, min(ide-1,ite)
  399. IF (j == jds) THEN
  400. z_at_v = grid%phb(i,1,j)/g
  401. ELSE IF (j == jde) THEN
  402. z_at_v = grid%phb(i,1,j-1)/g
  403. ELSE
  404. z_at_v = 0.5*(grid%phb(i,1,j)+grid%phb(i,1,j-1))/g
  405. END IF
  406. p_surf = interp_0( p_in, zk, z_at_v, nl_in )
  407. DO K = 1, kte
  408. p_level = grid%znu(k)*(p_surf - grid%p_top) + grid%p_top
  409. grid%v_1(i,k,j) = interp_0( v, p_in, p_level, nl_in )
  410. grid%v_2(i,k,j) = grid%v_1(i,k,j)
  411. ENDDO
  412. ENDDO
  413. ENDDO
  414. ! interp u
  415. DO J = jts, min(jde-1,jte)
  416. DO I = its, ite
  417. IF (i == ids) THEN
  418. z_at_u = grid%phb(i,1,j)/g
  419. ELSE IF (i == ide) THEN
  420. z_at_u = grid%phb(i-1,1,j)/g
  421. ELSE
  422. z_at_u = 0.5*(grid%phb(i,1,j)+grid%phb(i-1,1,j))/g
  423. END IF
  424. p_surf = interp_0( p_in, zk, z_at_u, nl_in )
  425. DO K = 1, kte
  426. p_level = grid%znu(k)*(p_surf - grid%p_top) + grid%p_top
  427. grid%u_1(i,k,j) = interp_0( u, p_in, p_level, nl_in )
  428. grid%u_2(i,k,j) = grid%u_1(i,k,j)
  429. ENDDO
  430. ENDDO
  431. ENDDO
  432. ! set w
  433. DO J = jts, min(jde-1,jte)
  434. DO K = kts, kte
  435. DO I = its, min(ide-1,ite)
  436. grid%w_1(i,k,j) = 0.
  437. grid%w_2(i,k,j) = 0.
  438. ENDDO
  439. ENDDO
  440. ENDDO
  441. ! set a few more things
  442. DO J = jts, min(jde-1,jte)
  443. DO K = kts, kte-1
  444. DO I = its, min(ide-1,ite)
  445. grid%h_diabatic(i,k,j) = 0.
  446. ENDDO
  447. ENDDO
  448. ENDDO
  449. ! Go ahead and initialize these from the sounding. This will allow a run
  450. ! to actually succeed even if scm_force = 0
  451. DO k=1,kte-1
  452. grid%t_base(k) = grid%t_1(1,k,1)
  453. grid%qv_base(k) = moist(1,k,1,P_QV)
  454. grid%u_base(k) = grid%u_1(1,k,1)
  455. grid%v_base(k) = grid%v_1(1,k,1)
  456. grid%z_base(k) = 0.5*(grid%phb(1,k,1)+grid%phb(1,k+1,1)+grid%ph_1(1,k,1)+grid%ph_1(1,k+1,1))/g
  457. ENDDO
  458. RETURN
  459. END SUBROUTINE init_domain_rk
  460. SUBROUTINE init_module_initialize
  461. END SUBROUTINE init_module_initialize
  462. !---------------------------------------------------------------------
  463. ! test driver for get_sounding
  464. !
  465. ! implicit none
  466. ! integer n
  467. ! parameter(n = 1000)
  468. ! real zk(n),p(n),theta(n),rho(n),u(n),v(n),qv(n),pd(n)
  469. ! logical dry
  470. ! integer nl,k
  471. !
  472. ! dry = .false.
  473. ! dry = .true.
  474. ! call get_sounding( zk, p, pd, theta, rho, u, v, qv, dry, n, nl )
  475. ! write(6,*) ' input levels ',nl
  476. ! write(6,*) ' sounding '
  477. ! write(6,*) ' k height(m) press (Pa) pd(Pa) theta (K) den(kg/m^3) u(m/s) v(m/s) qv(g/g) '
  478. ! do k=1,nl
  479. ! write(6,'(1x,i3,8(1x,1pe10.3))') k, zk(k), p(k), pd(k), theta(k), rho(k), u(k), v(k), qv(k)
  480. ! enddo
  481. ! end
  482. !
  483. !---------------------------------------------------------------------------
  484. subroutine get_sounding( zsfc, zk, p, p_dry, theta, rho, &
  485. u, v, qv, dry, nl_max, nl_in )
  486. implicit none
  487. integer nl_max, nl_in
  488. real zsfc
  489. real zk(nl_max), p(nl_max), theta(nl_max), rho(nl_max), &
  490. u(nl_max), v(nl_max), qv(nl_max), p_dry(nl_max)
  491. logical dry
  492. integer n
  493. parameter(n=3000)
  494. logical debug
  495. parameter( debug = .true.)
  496. ! input sounding data
  497. real p_surf, th_surf, qv_surf
  498. real pi_surf, pi(n)
  499. real h_input(n), th_input(n), qv_input(n), u_input(n), v_input(n)
  500. ! diagnostics
  501. real rho_surf, p_input(n), rho_input(n)
  502. real pm_input(n) ! this are for full moist sounding
  503. ! local data
  504. real r
  505. parameter (r = r_d)
  506. integer k, it, nl
  507. real qvf, qvf1, dz
  508. ! first, read the sounding
  509. call read_sounding( zsfc, p_surf, th_surf, qv_surf, &
  510. h_input, th_input, qv_input, u_input, v_input,n, nl, debug )
  511. if(dry) then
  512. do k=1,nl
  513. qv_input(k) = 0.
  514. enddo
  515. endif
  516. if(debug) write(6,*) ' number of input levels = ',nl
  517. nl_in = nl
  518. if(nl_in .gt. nl_max ) then
  519. write(6,*) ' too many levels for input arrays ',nl_in,nl_max
  520. call wrf_error_fatal ( ' too many levels for input arrays ' )
  521. end if
  522. ! compute diagnostics,
  523. ! first, convert qv(g/kg) to qv(g/g)
  524. do k=1,nl
  525. qv_input(k) = 0.001*qv_input(k)
  526. enddo
  527. p_surf = 100.*p_surf ! convert to pascals
  528. qvf = 1. + rvovrd*qv_input(1)
  529. rho_surf = 1./((r/p1000mb)*th_surf*qvf*((p_surf/p1000mb)**cvpm))
  530. pi_surf = (p_surf/p1000mb)**(r/cp)
  531. if(debug) then
  532. write(6,*) ' surface density is ',rho_surf
  533. write(6,*) ' surface pi is ',pi_surf
  534. end if
  535. ! integrate moist sounding hydrostatically, starting from the
  536. ! specified surface pressure
  537. ! -> first, integrate from surface to lowest level
  538. qvf = 1. + rvovrd*qv_input(1)
  539. qvf1 = 1. + qv_input(1)
  540. rho_input(1) = rho_surf
  541. dz = h_input(1)-zsfc
  542. ! error check here
  543. if ( dz < 0.0 ) then
  544. write(6,*) "Your first input sounding level is below the WRF terrain elevation, aborting"
  545. stop "module_initialize_scm_xy:get_sounding"
  546. endif
  547. do it=1,10
  548. pm_input(1) = p_surf &
  549. - 0.5*dz*(rho_surf+rho_input(1))*g*qvf1
  550. rho_input(1) = 1./((r/p1000mb)*th_input(1)*qvf*((pm_input(1)/p1000mb)**cvpm))
  551. enddo
  552. ! integrate up the column
  553. do k=2,nl
  554. rho_input(k) = rho_input(k-1)
  555. dz = h_input(k)-h_input(k-1)
  556. qvf1 = 0.5*(2.+(qv_input(k-1)+qv_input(k)))
  557. qvf = 1. + rvovrd*qv_input(k) ! qv is in g/kg here
  558. do it=1,10
  559. pm_input(k) = pm_input(k-1) &
  560. - 0.5*dz*(rho_input(k)+rho_input(k-1))*g*qvf1
  561. rho_input(k) = 1./((r/p1000mb)*th_input(k)*qvf*((pm_input(k)/p1000mb)**cvpm))
  562. enddo
  563. enddo
  564. ! we have the moist sounding
  565. ! next, compute the dry sounding using p at the highest level from the
  566. ! moist sounding and integrating down.
  567. p_input(nl) = pm_input(nl)
  568. do k=nl-1,1,-1
  569. dz = h_input(k+1)-h_input(k)
  570. p_input(k) = p_input(k+1) + 0.5*dz*(rho_input(k)+rho_input(k+1))*g
  571. enddo
  572. do k=1,nl
  573. zk(k) = h_input(k)
  574. p(k) = pm_input(k)
  575. p_dry(k) = p_input(k)
  576. theta(k) = th_input(k)
  577. rho(k) = rho_input(k)
  578. u(k) = u_input(k)
  579. v(k) = v_input(k)
  580. qv(k) = qv_input(k)
  581. enddo
  582. if(debug) then
  583. write(6,*) ' sounding '
  584. write(6,*) ' k height(m) press (Pa) pd(Pa) theta (K) den(kg/m^3) u(m/s) v(m/s) qv(g/g) '
  585. do k=1,nl
  586. write(6,'(1x,i3,8(1x,1pe10.3))') k, zk(k), p(k), p_dry(k), theta(k), rho(k), u(k), v(k), qv(k)
  587. enddo
  588. end if
  589. end subroutine get_sounding
  590. !-------------------------------------------------------
  591. subroutine read_sounding( zsfc,ps,ts,qvs,h,th,qv,u,v,n,nl,debug )
  592. implicit none
  593. integer n,nl
  594. real zsfc,ps,ts,qvs,h(n),th(n),qv(n),u(n),v(n)
  595. real u10,v10,t2,q2
  596. logical end_of_file
  597. logical debug
  598. integer k
  599. open(unit=10,file='input_sounding',form='formatted',status='old')
  600. rewind(10)
  601. read(10,*) zsfc, u10, v10, t2, q2, ps
  602. ps = ps/100.0
  603. ts = t2
  604. qvs = q2*1000
  605. if(debug) then
  606. write(6,*) ' input sounding surface parameters '
  607. write(6,*) ' surface pressure (mb) ',ps
  608. write(6,*) ' surface pot. temp (K) ',ts
  609. write(6,*) ' surface mixing ratio (g/kg) ',qvs
  610. end if
  611. end_of_file = .false.
  612. k = 0
  613. do while (.not. end_of_file)
  614. read(10,*,end=100) h(k+1), u(k+1), v(k+1), th(k+1), qv(k+1)
  615. qv(k+1) = qv(k+1)*1000.0
  616. k = k+1
  617. if(debug) write(6,'(1x,i3,5(1x,e10.3))') k, h(k), th(k), qv(k), u(k), v(k)
  618. go to 110
  619. 100 end_of_file = .true.
  620. 110 continue
  621. enddo
  622. nl = k
  623. close(unit=10,status = 'keep')
  624. end subroutine read_sounding
  625. !-------------------------------------------------------
  626. subroutine read_soil( n,nl,tmn,tsk,zs,tslb,smois )
  627. implicit none
  628. integer n,nl
  629. real tmn,tsk
  630. real zs(n),tslb(n),smois(n)
  631. logical end_of_file
  632. logical debug
  633. integer k
  634. debug = .true.
  635. open(unit=11,file='input_soil',form='formatted',status='old')
  636. rewind(11)
  637. read(11,*) zs(1),tmn,tsk
  638. if(debug) then
  639. write(6,*) ' input deep soil temperature (K) ',tmn
  640. write(6,*) ' input skin temperature (K) ',tsk
  641. end if
  642. end_of_file = .false.
  643. k = 0
  644. do while (.not. end_of_file)
  645. read(11,*,end=100) zs(k+1), tslb(k+1), smois(k+1)
  646. k = k+1
  647. if(debug) write(6,'(1x,i3,3(1x,f16.7))') k, zs(k), tslb(k), smois(k)
  648. go to 110
  649. 100 end_of_file = .true.
  650. 110 continue
  651. enddo
  652. nl = k
  653. close(unit=11,status = 'keep')
  654. end subroutine read_soil
  655. END MODULE module_initialize_ideal