SCALE-RM
Functions/Subroutines
mod_realinput_wrfarw Module Reference

module REAL input WRF-ARW More...

Functions/Subroutines

subroutine, public parentatmossetupwrfarw (dims, timelen, basename_org)
 Atmos Setup. More...
 
subroutine, public parentatmosopenwrfarw
 
subroutine, public parentatmosinputwrfarw (velz_org, llvelx_org, llvely_org, pres_org, temp_org, qv_org, qhyd_org, qnum_org, lon_org, lat_org, cz_org, basename, sfc_diagnoses, dims, it)
 
subroutine, public parentlandsetupwrfarw (ldims, basename_land)
 Land Setup. More...
 
subroutine, public parentlandinputwrfarw (tg_org, sh2o_org, lst_org, ust_org, albg_org, topo_org, lmask_org, llon_org, llat_org, lz_org, basename, ldims, use_file_landwater, it)
 
subroutine, public parentoceansetupwrfarw (odims, timelen, basename_org)
 Ocean Setup. More...
 
subroutine, public parentoceanopenwrfarw
 
subroutine, public parentoceaninputwrfarw (tw_org, sst_org, albw_org, z0w_org, omask_org, olon_org, olat_org, basename, odims, it)
 
subroutine wrf_arwpost_calc_uvmet (u_latlon, v_latlon, u_on_map, v_on_map, xlon, xlat, basename, K1, I1, J1)
 convert vector varibles from map-projected grid on wrf model to lat-lon grid More...
 

Detailed Description

module REAL input WRF-ARW

Description
read data from WRF-ARW file for real atmospheric simulations
Author
Team SCALE
NAMELIST
  • PARAM_MKINIT_REAL_WRFARW
    nametypedefault valuecomment
    WRF_FILE_TYPE logical .false. wrf filetype: T=wrfout, F=wrfrst

History Output
No history output

Function/Subroutine Documentation

◆ parentatmossetupwrfarw()

subroutine, public mod_realinput_wrfarw::parentatmossetupwrfarw ( integer, dimension(6), intent(out)  dims,
integer, intent(out)  timelen,
character(len=*), intent(in)  basename_org 
)

Atmos Setup.

Definition at line 83 of file mod_realinput_wrfarw.F90.

83  use scale_file, only: &
84  file_open, &
86  implicit none
87 
88  integer, intent(out) :: dims(6)
89  integer, intent(out) :: timelen
90  character(len=*), intent(in) :: basename_org
91 
92  logical :: WRF_FILE_TYPE = .false. ! wrf filetype: T=wrfout, F=wrfrst
93 
94  namelist / param_mkinit_real_wrfarw / &
95  wrf_file_type
96 
97  integer :: fid
98  integer :: ierr
99  logical :: error
100  !---------------------------------------------------------------------------
101 
102  log_newline
103  log_info("ParentAtmosSetupWRFARW",*) 'Setup'
104 
105  !--- read namelist
106  rewind(io_fid_conf)
107  read(io_fid_conf,nml=param_mkinit_real_wrfarw,iostat=ierr)
108  if( ierr > 0 ) then
109  log_error("ParentAtmosSetupWRFARW",*) 'Not appropriate names in namelist PARAM_MKINIT_REAL_WRFARW. Check!'
110  call prc_abort
111  endif
112  log_nml(param_mkinit_real_wrfarw)
113 
114  call file_open( basename_org, fid, rankid=myrank, single=.true., postfix="" )
115 
116  call file_get_dimlength( fid, "bottom_top", dims(1) )
117  call file_get_dimlength( fid, "west_east", dims(2) )
118  call file_get_dimlength( fid, "south_north", dims(3) )
119  call file_get_dimlength( fid, "bottom_top_stag", dims(4) )
120  call file_get_dimlength( fid, "west_east_stag", dims(5) )
121  call file_get_dimlength( fid, "south_north_stag", dims(6) )
122 
123  call file_get_dimlength( fid, "Time", timelen, error=error )
124  if ( error ) call file_get_dimlength( fid, "time", timelen, error=error)
125  if ( error ) timelen = 0
126 
127  if ( wrf_file_type ) then
128  wrfout = .true.
129  log_info("ParentAtmosSetupWRFARW",*) 'WRF-ARW FILE-TYPE: WRF History Output'
130  else
131  wrfout = .false.
132  log_info("ParentAtmosSetupWRFARW",*) 'WRF-ARW FILE-TYPE: WRF Restart'
133  endif
134 
135 
136  allocate( read_xy(dims(2),dims(3)) )
137  allocate( read_xyz(dims(2),dims(3),dims(1)) )
138  allocate( read_xyw(dims(2),dims(3),dims(4)) )
139 
140  allocate( p_org(dims(1),dims(2),dims(3)) )
141  allocate( pb_org(dims(1),dims(2),dims(3)) )
142  allocate( ph_org(dims(4),dims(2),dims(3)) )
143  allocate( phb_org(dims(4),dims(2),dims(3)) )
144 
145  return

References scale_file::file_get_dimlength(), scale_file::file_open(), scale_io::io_fid_conf, and scale_prc::prc_abort().

Referenced by mod_realinput::realinput_surface().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ parentatmosopenwrfarw()

subroutine, public mod_realinput_wrfarw::parentatmosopenwrfarw

Definition at line 150 of file mod_realinput_wrfarw.F90.

150  implicit none
151 
152  return

Referenced by mod_realinput::realinput_surface().

Here is the caller graph for this function:

◆ parentatmosinputwrfarw()

subroutine, public mod_realinput_wrfarw::parentatmosinputwrfarw ( real(rp), dimension(:,:,:), intent(out)  velz_org,
real(rp), dimension(:,:,:), intent(out)  llvelx_org,
real(rp), dimension(:,:,:), intent(out)  llvely_org,
real(rp), dimension(:,:,:), intent(out)  pres_org,
real(rp), dimension(:,:,:), intent(out)  temp_org,
real(rp), dimension(:,:,:), intent(out)  qv_org,
real(rp), dimension(:,:,:,:), intent(out)  qhyd_org,
real(rp), dimension(:,:,:,:), intent(out)  qnum_org,
real(rp), dimension(:,:), intent(out)  lon_org,
real(rp), dimension(:,:), intent(out)  lat_org,
real(rp), dimension(:,:,:), intent(out)  cz_org,
character(len=*), intent(in)  basename,
logical, intent(in)  sfc_diagnoses,
integer, dimension(6), intent(in)  dims,
integer, intent(in)  it 
)

Definition at line 172 of file mod_realinput_wrfarw.F90.

172  use scale_const, only: &
173  undef => const_undef, &
174  d2r => const_d2r, &
175  laps => const_laps, &
176  rdry => const_rdry, &
177  grav => const_grav
178  use scale_file, only: &
179  file_open, &
180  file_read
181  use scale_atmos_hydrometeor, only: &
182  n_hyd, &
183  i_hc, &
184  i_hr, &
185  i_hi, &
186  i_hs, &
187  i_hg
188  implicit none
189 
190  real(RP), intent(out) :: velz_org(:,:,:)
191  real(RP), intent(out) :: llvelx_org(:,:,:)
192  real(RP), intent(out) :: llvely_org(:,:,:)
193  real(RP), intent(out) :: pres_org(:,:,:)
194  real(RP), intent(out) :: temp_org(:,:,:)
195  real(RP), intent(out) :: qv_org(:,:,:)
196  real(RP), intent(out) :: qhyd_org(:,:,:,:)
197  real(RP), intent(out) :: qnum_org(:,:,:,:)
198  real(RP), intent(out) :: lon_org(:,:)
199  real(RP), intent(out) :: lat_org(:,:)
200  real(RP), intent(out) :: cz_org(:,:,:)
201  character(len=*), intent(in) :: basename
202  logical, intent(in) :: sfc_diagnoses
203  integer, intent(in) :: dims(6)
204  integer, intent(in) :: it
205 
206  ! k, i, j
207  real(RP) :: velx_org(dims(1)+2,dims(2),dims(3))
208  real(RP) :: vely_org(dims(1)+2,dims(2),dims(3))
209  real(RP) :: pott_org(dims(1)+2,dims(2),dims(3))
210  real(RP) :: topo_org( dims(2),dims(3))
211  real(RP) :: geof_org(dims(4) ,dims(2),dims(3))
212 
213 
214  ! i, j, k
215  real(RP) :: velzs_org(dims(2),dims(3),dims(4))
216  real(RP) :: velxs_org(dims(5),dims(3),dims(1))
217  real(RP) :: velys_org(dims(2),dims(6),dims(1))
218 
219  real(RP) :: dz
220  real(RP) :: dens
221  real(RP) :: qtot
222 
223  integer :: k, i, j, iq
224 
225  character(len=H_MID) :: varname_T
226  character(len=H_MID) :: varname_W
227  character(len=H_MID) :: varname_U
228  character(len=H_MID) :: varname_V
229 
230  integer :: fid
231  !---------------------------------------------------------------------------
232 
233  if ( wrfout ) then
234  varname_t = "T"
235  varname_w = "W"
236  varname_u = "U"
237  varname_v = "V"
238  else
239  varname_t = "T_1"
240  varname_w = "W_1"
241  varname_u = "U_1"
242  varname_v = "V_1"
243  endif
244 
245 
246  call file_open( basename, fid, rankid=myrank, single=.true., postfix="" )
247 
248  call file_read( fid, "XLAT", lat_org(:,:), step=it )
249  lat_org(:,:) = lat_org(:,:) * d2r
250 
251  call file_read( fid, "XLONG", lon_org(:,:), step=it )
252  lon_org(:,:) = lon_org(:,:) * d2r
253 
254  call file_read( fid, "HGT", topo_org(:,:), step=it )
255 
256  call file_read( fid, "PH", read_xyw(:,:,:), step=it )
257  !$omp parallel do
258  do j = 1, dims(3)
259  do i = 1, dims(2)
260  do k = 1, dims(4)
261  ph_org(k,i,j) = read_xyw(i,j,k)
262  end do
263  end do
264  end do
265 
266  call file_read( fid, "PHB", read_xyw(:,:,:), step=it )
267  !$omp parallel do
268  do j = 1, dims(3)
269  do i = 1, dims(2)
270  do k = 1, dims(4)
271  phb_org(k,i,j) = read_xyw(i,j,k)
272  end do
273  end do
274  end do
275 
276  call file_read( fid, "P", read_xyz(:,:,:), step=it )
277  !$omp parallel do
278  do j = 1, dims(3)
279  do i = 1, dims(2)
280  do k = 1, dims(1)
281  p_org(k,i,j) = read_xyz(i,j,k)
282  end do
283  end do
284  end do
285 
286  call file_read( fid, "PB", read_xyz(:,:,:), step=it )
287  !$omp parallel do
288  do j = 1, dims(3)
289  do i = 1, dims(2)
290  do k = 1, dims(1)
291  pb_org(k,i,j) = read_xyz(i,j,k)
292  end do
293  end do
294  end do
295 
296  call file_read( fid, varname_w, velzs_org(:,:,:), step=it )
297 
298  call file_read( fid, varname_u, velxs_org(:,:,:), step=it )
299 
300  call file_read( fid, varname_v, velys_org(:,:,:), step=it )
301 
302 
303  ! from half level to full level
304  !$omp parallel do
305  do j = 1, dims(3)
306  do i = 1, dims(2)
307  do k = 1, dims(1)
308  velz_org(k+2,i,j) = ( velzs_org(i,j,k) + velzs_org(i,j,k+1) ) * 0.5_rp
309  velx_org(k+2,i,j) = ( velxs_org(i,j,k) + velxs_org(i+1,j,k) ) * 0.5_rp
310  vely_org(k+2,i,j) = ( velys_org(i,j,k) + velys_org(i,j+1,k) ) * 0.5_rp
311  end do
312  velz_org(1:2,i,j) = 0.0_rp
313  velx_org(1:2,i,j) = 0.0_rp
314  vely_org(1:2,i,j) = 0.0_rp
315  end do
316  end do
317 
318  call wrf_arwpost_calc_uvmet( llvelx_org, llvely_org, & ! (out)
319  velx_org, vely_org, & ! (in)
320  lon_org, lat_org, & ! (in)
321  basename, & ! (in)
322  dims(1)+2, dims(2), dims(3) ) ! (in)
323 
324  !$omp parallel do collapse(4)
325  do iq = 1, n_hyd
326  do j = 1, dims(3)
327  do i = 1, dims(2)
328  do k = 1, dims(1)+2
329  qhyd_org(k,i,j,iq) = 0.0_rp
330  end do
331  end do
332  end do
333  end do
334 
335  call file_read( fid, "QVAPOR", read_xyz(:,:,:), step=it )
336  !$omp parallel do
337  do j = 1, dims(3)
338  do i = 1, dims(2)
339  do k = 1, dims(1)
340  qv_org(k+2,i,j) = read_xyz(i,j,k)
341  end do
342  end do
343  end do
344 
345  if ( sfc_diagnoses ) then
346  call file_read( fid, "Q2", read_xy(:,:), step=it )
347  !$omp parallel do
348  do j = 1, dims(3)
349  do i = 1, dims(2)
350  qv_org(1,i,j) = read_xy(i,j)
351  qv_org(2,i,j) = read_xy(i,j)
352  end do
353  end do
354  else
355  !$omp parallel do
356  do j = 1, dims(3)
357  do i = 1, dims(2)
358  qv_org(1:2,i,j) = undef
359  end do
360  end do
361  end if
362 
363 
364  call file_read( fid, "QCLOUD", read_xyz(:,:,:), step=it, allow_missing=.true. )
365  !$omp parallel do
366  do j = 1, dims(3)
367  do i = 1, dims(2)
368  do k = 1, dims(1)
369  qhyd_org(k+2,i,j,i_hc) = read_xyz(i,j,k)
370  end do
371  end do
372  end do
373 
374  call file_read( fid, "QRAIN", read_xyz(:,:,:), step=it, allow_missing=.true. )
375  !$omp parallel do
376  do j = 1, dims(3)
377  do i = 1, dims(2)
378  do k = 1, dims(1)
379  qhyd_org(k+2,i,j,i_hc) = read_xyz(i,j,k)
380  end do
381  end do
382  end do
383 
384  call file_read( fid, "QICE", read_xyz(:,:,:), step=it, allow_missing=.true. )
385  !$omp parallel do
386  do j = 1, dims(3)
387  do i = 1, dims(2)
388  do k = 1, dims(1)
389  qhyd_org(k+2,i,j,i_hi) = read_xyz(i,j,k)
390  end do
391  end do
392  end do
393 
394  call file_read( fid, "QSNOW", read_xyz(:,:,:), step=it, allow_missing=.true. )
395  !$omp parallel do
396  do j = 1, dims(3)
397  do i = 1, dims(2)
398  do k = 1, dims(1)
399  qhyd_org(k+2,i,j,i_hs) = read_xyz(i,j,k)
400  end do
401  end do
402  end do
403 
404  call file_read( fid, "QGRAUP", read_xyz(:,:,:), step=it, allow_missing=.true. )
405  !$omp parallel do
406  do j = 1, dims(3)
407  do i = 1, dims(2)
408  do k = 1, dims(1)
409  qhyd_org(k+2,i,j,i_hg) = read_xyz(i,j,k)
410  end do
411  end do
412  end do
413 
414 
415  ! convert mixing ratio to specific ratio
416  !$omp parallel do &
417  !$omp private(qtot)
418  do j = 1, dims(3)
419  do i = 1, dims(2)
420  do k = 1, dims(1)+2
421  if ( k<3 .and. .not. sfc_diagnoses ) then
422  qv_org(k,i,j) = undef
423  do iq = 1, n_hyd
424  qhyd_org(k,i,j,iq) = undef
425  end do
426  else
427  qtot = qv_org(k,i,j)
428  do iq = 1, n_hyd
429  qtot = qtot + qhyd_org(k,i,j,iq)
430  end do
431  qv_org(k,i,j) = qv_org(k,i,j) / ( 1.0_rp + qtot )
432  do iq = 1, n_hyd
433  qhyd_org(k,i,j,iq) = qhyd_org(k,i,j,iq) / ( 1.0_rp + qtot )
434  end do
435  end if
436  end do
437  end do
438  end do
439 
440  call file_read( fid, "NC", read_xyz(:,:,:), step=it, allow_missing=.true. )
441  !$omp parallel do
442  do j = 1, dims(3)
443  do i = 1, dims(2)
444  do k = 1, dims(1)
445  qnum_org(k+2,i,j,i_hc) = read_xyz(i,j,k)
446  end do
447  end do
448  end do
449 
450  call file_read( fid, "NR", read_xyz(:,:,:), step=it, allow_missing=.true. )
451  !$omp parallel do
452  do j = 1, dims(3)
453  do i = 1, dims(2)
454  do k = 1, dims(1)
455  qnum_org(k+2,i,j,i_hr) = read_xyz(i,j,k)
456  end do
457  end do
458  end do
459 
460  call file_read( fid, "NI", read_xyz(:,:,:), step=it, allow_missing=.true. )
461  !$omp parallel do
462  do j = 1, dims(3)
463  do i = 1, dims(2)
464  do k = 1, dims(1)
465  qnum_org(k+2,i,j,i_hi) = read_xyz(i,j,k)
466  end do
467  end do
468  end do
469 
470  call file_read( fid, "NS", read_xyz(:,:,:), step=it, allow_missing=.true. )
471  !$omp parallel do
472  do j = 1, dims(3)
473  do i = 1, dims(2)
474  do k = 1, dims(1)
475  qnum_org(k+2,i,j,i_hs) = read_xyz(i,j,k)
476  end do
477  end do
478  end do
479 
480  call file_read( fid, "NG", read_xyz(:,:,:), step=it, allow_missing=.true. )
481  !$omp parallel do
482  do j = 1, dims(3)
483  do i = 1, dims(2)
484  do k = 1, dims(1)
485  qnum_org(k+2,i,j,i_hg) = read_xyz(i,j,k)
486  end do
487  end do
488  end do
489 
490  !$omp parallel do collapse(4)
491  do iq = 1, n_hyd
492  do j = 1, dims(3)
493  do i = 1, dims(2)
494  do k = 1, dims(1)+2
495  if ( k<3 .and. .not. sfc_diagnoses ) then
496  qhyd_org(k,i,j,iq) = undef
497  qnum_org(k,i,j,iq) = undef
498  else
499  qhyd_org(k,i,j,iq) = max( qhyd_org(k,i,j,iq), 0.0_rp )
500  qnum_org(k,i,j,iq) = max( qnum_org(k,i,j,iq), 0.0_rp )
501  end if
502  end do
503  end do
504  end do
505  end do
506 
507 
508  call file_read( fid, varname_t, read_xyz(:,:,:), step=it, allow_missing=.true. )
509  !$omp parallel do
510  do j = 1, dims(3)
511  do i = 1, dims(2)
512  do k = 1, dims(1)
513  pott_org(k+2,i,j) = read_xyz(i,j,k) + t0
514  end do
515  end do
516  end do
517  if ( sfc_diagnoses ) then
518  call file_read( fid, "T2", read_xy(:,:), step=it, allow_missing=.false. )
519  !$omp parallel do
520  do j = 1, dims(3)
521  do i = 1, dims(2)
522  temp_org(2,i,j) = read_xy(i,j)
523  end do
524  end do
525 
526  call file_read( fid, "PSFC", read_xy(:,:), step=it, allow_missing=.false. )
527  !$omp parallel do
528  do j = 1, dims(3)
529  do i = 1, dims(2)
530  pres_org(2,i,j) = read_xy(i,j)
531  end do
532  end do
533  else
534  !$omp parallel do
535  do j = 1, dims(3)
536  do i = 1, dims(2)
537  temp_org(2,i,j) = undef
538  pres_org(2,i,j) = undef
539  end do
540  end do
541  end if
542 
543  !$omp parallel do
544  do j = 1, dims(3)
545  do i = 1, dims(2)
546  ! convert to geopotential height to use as real height in WRF
547  do k = 1, dims(4)
548  geof_org(k,i,j) = ( ph_org(k,i,j) + phb_org(k,i,j) ) / grav
549  end do
550  ! make half level of geopotential height from face level
551  do k = 1, dims(1)
552  cz_org(k+2,i,j) = ( geof_org(k,i,j) + geof_org(k+1,i,j) ) * 0.5_rp
553  end do
554  cz_org(2,i,j) = topo_org(i,j)
555  cz_org(1,i,j) = 0.0_rp
556  end do
557  end do
558 
559  !$omp parallel do &
560  !$omp private(dens)
561  do j = 1, dims(3)
562  do i = 1, dims(2)
563  do k = 3, dims(1)+2
564  pres_org(k,i,j) = p_org(k-2,i,j) + pb_org(k-2,i,j)
565  temp_org(k,i,j) = pott_org(k,i,j) * ( pres_org(k,i,j) / p0 )**rcp
566  end do
567  if ( sfc_diagnoses ) then
568  pott_org(2,i,j) = temp_org(2,i,j) * ( p0/pres_org(2,i,j) )**rcp
569  temp_org(1,i,j) = temp_org(2,i,j) + laps * topo_org(i,j)
570  dens = pres_org(2,i,j) / ( rdry * temp_org(2,i,j) )
571  pres_org(1,i,j) = ( pres_org(2,i,j) + grav * dens * cz_org(2,i,j) * 0.5_rp ) &
572  / ( rdry * temp_org(1,i,j) - grav * cz_org(2,i,j) * 0.5_rp ) &
573  * rdry * temp_org(1,i,j)
574  else
575  pott_org(2,i,j) = undef
576  temp_org(1,i,j) = undef
577  pres_org(1,i,j) = undef
578  end if
579  end do
580  end do
581 
582 
583 #ifdef DEBUG
584  !k=1 ; i=int(dims(2)/2) ; j=int(dims(3)/2)
585  k=2 ; i=3 ; j=3
586  log_info("ParentAtmosInputWRFARW",*) "read 3D wrf data",i,j,k
587  log_info("ParentAtmosInputWRFARW",*) "lon_org ",lon_org(i,j)/d2r
588  log_info("ParentAtmosInputWRFARW",*) "lat_org ",lat_org(i,j)/d2r
589  log_info("ParentAtmosInputWRFARW",*) "cz_org ",cz_org(k,i,j)
590  log_info("ParentAtmosInputWRFARW",*) "pres_org ",pres_org(k,i,j)
591  log_info("ParentAtmosInputWRFARW",*) "velx_org ",llvelx_org(k,i,j)
592  log_info("ParentAtmosInputWRFARW",*) "vely_org ",llvely_org(k,i,j)
593  log_info("ParentAtmosInputWRFARW",*) "velz_org ",velz_org(k,i,j)
594  log_info("ParentAtmosInputWRFARW",*) "temp_org ",temp_org(k,i,j)
595  log_info("ParentAtmosInputWRFARW",*) "qv_org ",qv_org(k,i,j)
596  k=3 ; i=3 ; j=3 ; iq = 1
597  log_info("ParentAtmosInputWRFARW",*) "read 3D wrf data",i,j,k
598  log_info("ParentAtmosInputWRFARW",*) "lon_org ",lon_org(i,j)/d2r
599  log_info("ParentAtmosInputWRFARW",*) "lat_org ",lat_org(i,j)/d2r
600  log_info("ParentAtmosInputWRFARW",*) "cz_org ",cz_org(k,i,j)
601  log_info("ParentAtmosInputWRFARW",*) "pres_org ",pres_org(k,i,j)
602  log_info("ParentAtmosInputWRFARW",*) "velx_org ",llvelx_org(k,i,j)
603  log_info("ParentAtmosInputWRFARW",*) "vely_org ",llvely_org(k,i,j)
604  log_info("ParentAtmosInputWRFARW",*) "velz_org ",velz_org(k,i,j)
605  log_info("ParentAtmosInputWRFARW",*) "temp_org ",temp_org(k,i,j)
606  log_info("ParentAtmosInputWRFARW",*) "qv_org ",qv_org(k,i,j)
607 #endif
608 
609  return

References scale_const::const_d2r, scale_const::const_grav, scale_const::const_laps, scale_const::const_rdry, scale_const::const_undef, scale_file::file_open(), scale_atmos_hydrometeor::i_hc, scale_atmos_hydrometeor::i_hg, scale_atmos_hydrometeor::i_hi, scale_atmos_hydrometeor::i_hr, scale_atmos_hydrometeor::i_hs, scale_tracer::k, scale_atmos_hydrometeor::n_hyd, and wrf_arwpost_calc_uvmet().

Referenced by mod_realinput::realinput_surface().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ parentlandsetupwrfarw()

subroutine, public mod_realinput_wrfarw::parentlandsetupwrfarw ( integer, dimension(3), intent(out)  ldims,
character(len=*), intent(in)  basename_land 
)

Land Setup.

Definition at line 617 of file mod_realinput_wrfarw.F90.

617  use scale_file, only: &
618  file_open, &
620  implicit none
621 
622  integer, intent(out) :: ldims(3)
623  character(len=*), intent(in) :: basename_land
624 
625  logical :: WRF_FILE_TYPE = .false. ! wrf filetype: T=wrfout, F=wrfrst
626 
627  namelist / param_mkinit_real_wrfarw / &
628  wrf_file_type
629 
630  integer :: fid
631  integer :: ierr
632  !---------------------------------------------------------------------------
633 
634  log_info("ParentLandSetupWRFARW",*) 'Real Case/Atmos Input File Type: WRF-ARW'
635 
636  !--- read namelist
637  rewind(io_fid_conf)
638  read(io_fid_conf,nml=param_mkinit_real_wrfarw,iostat=ierr)
639  if( ierr > 0 ) then
640  log_error("ParentLandSetupWRFARW",*) 'Not appropriate names in namelist PARAM_MKINIT_REAL_WRFARW. Check!'
641  call prc_abort
642  endif
643  log_nml(param_mkinit_real_wrfarw)
644 
645 
646  call file_open( basename_land, fid, rankid=myrank, single=.true., postfix="" )
647 
648  call file_get_dimlength( fid, "soil_layers_stag", ldims(1) )
649  call file_get_dimlength( fid, "west_east", ldims(2) )
650  call file_get_dimlength( fid, "south_north", ldims(3) )
651 
652  if ( wrf_file_type ) then
653  wrfout = .true.
654  log_info("ParentLandSetupWRFARW",*) 'WRF-ARW FILE-TYPE: WRF History Output'
655  else
656  wrfout = .false.
657  log_info("ParentLandSetupWRFARW",*) 'WRF-ARW FILE-TYPE: WRF Restart'
658  endif
659 
660 
661  if ( .not. allocated(read_xy) ) then
662  allocate( read_xy(ldims(2),ldims(3)) )
663  end if
664 
665  allocate( read_xyl(ldims(2),ldims(3),ldims(1)) )
666 
667  return

References scale_file::file_get_dimlength(), scale_file::file_open(), scale_io::io_fid_conf, and scale_prc::prc_abort().

Referenced by mod_realinput::realinput_surface().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ parentlandinputwrfarw()

subroutine, public mod_realinput_wrfarw::parentlandinputwrfarw ( real(rp), dimension(:,:,:), intent(out)  tg_org,
real(rp), dimension(:,:,:), intent(out)  sh2o_org,
real(rp), dimension(:,:), intent(out)  lst_org,
real(rp), dimension(:,:), intent(out)  ust_org,
real(rp), dimension(:,:,:,:), intent(out)  albg_org,
real(rp), dimension(:,:), intent(out)  topo_org,
real(rp), dimension(:,:), intent(out)  lmask_org,
real(rp), dimension(:,:), intent(out)  llon_org,
real(rp), dimension(:,:), intent(out)  llat_org,
real(rp), dimension(:), intent(out)  lz_org,
character(len=*), intent(in)  basename,
integer, dimension(3), intent(in)  ldims,
logical, intent(in)  use_file_landwater,
integer, intent(in)  it 
)

Definition at line 686 of file mod_realinput_wrfarw.F90.

686  use scale_const, only: &
687  d2r => const_d2r, &
688  undef => const_undef
689  use scale_file, only: &
690  file_open, &
691  file_read
692  implicit none
693  real(RP), intent(out) :: tg_org(:,:,:)
694  real(RP), intent(out) :: sh2o_org(:,:,:)
695  real(RP), intent(out) :: lst_org(:,:)
696  real(RP), intent(out) :: ust_org(:,:)
697  real(RP), intent(out) :: albg_org(:,:,:,:)
698  real(RP), intent(out) :: topo_org(:,:)
699  real(RP), intent(out) :: lmask_org(:,:)
700  real(RP), intent(out) :: llon_org(:,:)
701  real(RP), intent(out) :: llat_org(:,:)
702  real(RP), intent(out) :: lz_org(:)
703  character(len=*), intent( in) :: basename
704  integer, intent( in) :: ldims(3)
705  logical, intent( in) :: use_file_landwater ! use land water data from files
706  integer, intent( in) :: it
707 
708  integer :: fid
709  integer :: k, i, j
710  !---------------------------------------------------------------------------
711 
712  call file_open( basename, fid, rankid=myrank, single=.true., postfix="" )
713 
714  call file_read( fid, "XLAT", llat_org(:,:), step=it )
715  !$omp parallel do
716  do j = 1, ldims(3)
717  do i = 1, ldims(2)
718  llat_org(i,j) = llat_org(i,j) * d2r
719  end do
720  end do
721 
722  call file_read( fid, "XLONG", llon_org(:,:), step=it )
723  !$omp parallel do
724  do j = 1, ldims(3)
725  do i = 1, ldims(2)
726  llon_org(i,j) = llon_org(i,j) * d2r
727  end do
728  end do
729 
730  call file_read( fid, "HGT", topo_org(:,:), step=it )
731 
732 
733  ! depth
734  call file_read( fid, "ZS", lz_org(:), step=it )
735 
736  ! land mask (1:land, 0:water)
737  call file_read( fid, "LANDMASK", lmask_org(:,:), step=it )
738 
739  ! soil temperature [K]
740  call file_read( fid, "TSLB", read_xyl(:,:,:), step=it )
741  !$omp parallel do
742  do j = 1, ldims(3)
743  do i = 1, ldims(2)
744  do k = 1, ldims(1)
745  tg_org(k,i,j) = read_xyl(i,j,k)
746  end do
747  end do
748  end do
749 
750  ! soil liquid water [m3 m-3] (no wrfout-default)
751  if( use_file_landwater ) then
752  call file_read( fid, "SH2O", read_xyl(:,:,:), step=it, allow_missing=.true., missing_value=undef )
753  !$omp parallel do
754  do j = 1, ldims(3)
755  do i = 1, ldims(2)
756  do k = 1, ldims(1)
757  sh2o_org(k,i,j) = read_xyl(i,j,k)
758  end do
759  end do
760  end do
761  endif
762 
763 ! ! surface runoff [mm]
764 ! call FILE_read( fid, "SFROFF", org_3D(:,:), step=it )
765 ! !$omp parallel do
766 ! do j = 1, ldims(3)
767 ! do i = 1, ldims(2)
768 ! org_3D(k,i,j) = org_3D(i,j,k) * 1000.0_RP * dwatr
769 ! end do
770 ! end do
771 
772 
773  ! SURFACE SKIN TEMPERATURE [K]
774  call file_read( fid, "TSK", lst_org(:,:), step=it )
775 
776  !$omp parallel do
777  do j = 1, ldims(3)
778  do i = 1, ldims(2)
779  ust_org(i,j) = lst_org(i,j)
780  end do
781  end do
782 
783  ! ALBEDO [-]
784  call file_read( fid, "ALBEDO", albg_org(:,:,i_r_direct ,i_r_vis), step=it )
785  !$omp parallel do
786  do j = 1, ldims(3)
787  do i = 1, ldims(2)
788  albg_org(i,j,i_r_direct ,i_r_nir) = albg_org(i,j,i_r_direct ,i_r_vis)
789  albg_org(i,j,i_r_diffuse,i_r_nir) = albg_org(i,j,i_r_direct ,i_r_vis)
790  albg_org(i,j,i_r_diffuse,i_r_vis) = albg_org(i,j,i_r_direct ,i_r_vis)
791  end do
792  end do
793 
794  ! SURFACE EMISSIVITY [-]
795  call file_read( fid, "EMISS", read_xy(:,:), step=it )
796  !$omp parallel do
797  do j = 1, ldims(3)
798  do i = 1, ldims(2)
799  albg_org(i,j,i_r_diffuse,i_r_ir) = 1.0_rp - read_xy(i,j)
800  end do
801  end do
802  !$omp parallel do
803  do j = 1, ldims(3)
804  do i = 1, ldims(2)
805  albg_org(i,j,i_r_direct,i_r_ir) = albg_org(i,j,i_r_diffuse,i_r_ir)
806  end do
807  end do
808 
809 ! ! SNOW WATER EQUIVALENT [kg m-2] (no wrfout-default)
810 ! call FILE_read( fid, "SNOW", snowq_org(:,:), step=it, allow_missing=.true., missing_value=UNDEF )
811 
812 ! ! AVERAGE SNOW TEMPERATURE [C] (no wrfout-default)
813 ! call FILE_read( fid, "TSNAV", snowt_org(:,:), step=it, allow_missing=.true., missing_value=UNDEF )
814 ! !$omp parallel do
815 ! do j = 1, ldims(3)
816 ! do i = 1, ldims(2)
817 ! if ( snowt_org(k,i,j) /= UNDEF ) snowt_org(k,i,j) = snowt_org(i,j,k) + TEM00
818 ! end do
819 ! end do
820 
821  return

References scale_const::const_d2r, scale_const::const_undef, scale_file::file_open(), scale_cpl_sfc_index::i_r_diffuse, scale_cpl_sfc_index::i_r_direct, scale_cpl_sfc_index::i_r_ir, scale_cpl_sfc_index::i_r_nir, scale_cpl_sfc_index::i_r_vis, and scale_tracer::k.

Referenced by mod_realinput::realinput_surface().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ parentoceansetupwrfarw()

subroutine, public mod_realinput_wrfarw::parentoceansetupwrfarw ( integer, dimension(2), intent(out)  odims,
integer, intent(out)  timelen,
character(len=*), intent(in)  basename_org 
)

Ocean Setup.

Definition at line 830 of file mod_realinput_wrfarw.F90.

830  use scale_file, only: &
831  file_open, &
833  implicit none
834 
835  integer, intent(out) :: odims(2)
836  integer, intent(out) :: timelen
837  character(len=*), intent(in) :: basename_org
838 
839  logical :: WRF_FILE_TYPE = .false. ! wrf filetype: T=wrfout, F=wrfrst
840 
841  namelist / param_mkinit_real_wrfarw / &
842  wrf_file_type
843 
844  integer :: fid
845  integer :: ierr
846  logical :: error
847  !---------------------------------------------------------------------------
848 
849  log_info("ParentOceanSetupWRFARW",*) 'Real Case/Ocean Input File Type: WRF-ARW'
850 
851  !--- read namelist
852  rewind(io_fid_conf)
853  read(io_fid_conf,nml=param_mkinit_real_wrfarw,iostat=ierr)
854  if( ierr > 0 ) then
855  log_error("ParentOceanSetupWRFARW",*) 'Not appropriate names in namelist PARAM_MKINIT_REAL_WRFARW. Check!'
856  call prc_abort
857  endif
858  log_nml(param_mkinit_real_wrfarw)
859 
860 
861  call file_open( basename_org, fid, rankid=myrank, single=.true., postfix="" )
862 
863  call file_get_dimlength(fid, "west_east", odims(1) )
864  call file_get_dimlength(fid, "south_north", odims(2) )
865 
866  call file_get_dimlength(fid, "Time", timelen, error=error )
867  if ( error ) call file_get_dimlength(fid, "time", timelen, error=error)
868  if ( error ) timelen = 0
869 
870  if ( wrf_file_type ) then
871  wrfout = .true.
872  log_info("ParentOceanSetupWRFARW",*) 'WRF-ARW FILE-TYPE: WRF History Output'
873  else
874  wrfout = .false.
875  log_info("ParentOceanSetupWRFARW",*) 'WRF-ARW FILE-TYPE: WRF Restart'
876  endif
877 
878 
879  if ( .not. allocated(read_xy) ) then
880  allocate( read_xy(odims(1),odims(2)) )
881  end if
882 
883  return

References scale_file::file_get_dimlength(), scale_file::file_open(), scale_io::io_fid_conf, and scale_prc::prc_abort().

Referenced by mod_realinput::realinput_surface().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ parentoceanopenwrfarw()

subroutine, public mod_realinput_wrfarw::parentoceanopenwrfarw

Definition at line 888 of file mod_realinput_wrfarw.F90.

888  implicit none
889 
890  return

Referenced by mod_realinput::realinput_surface().

Here is the caller graph for this function:

◆ parentoceaninputwrfarw()

subroutine, public mod_realinput_wrfarw::parentoceaninputwrfarw ( real(rp), dimension(:,:), intent(out)  tw_org,
real(rp), dimension(:,:), intent(out)  sst_org,
real(rp), dimension(:,:,:,:), intent(out)  albw_org,
real(rp), dimension(:,:), intent(out)  z0w_org,
real(rp), dimension(:,:), intent(out)  omask_org,
real(rp), dimension(:,:), intent(out)  olon_org,
real(rp), dimension(:,:), intent(out)  olat_org,
character(len=*), intent(in)  basename,
integer, dimension(2), intent(in)  odims,
integer, intent(in)  it 
)

Definition at line 905 of file mod_realinput_wrfarw.F90.

905  use scale_const, only: &
906  d2r => const_d2r, &
907  undef => const_undef
908  use scale_file, only: &
909  file_open, &
910  file_read
911  implicit none
912  real(RP), intent(out) :: tw_org(:,:)
913  real(RP), intent(out) :: sst_org(:,:)
914  real(RP), intent(out) :: albw_org(:,:,:,:)
915  real(RP), intent(out) :: z0w_org(:,:)
916  real(RP), intent(out) :: omask_org(:,:)
917  real(RP), intent(out) :: olon_org(:,:)
918  real(RP), intent(out) :: olat_org(:,:)
919  character(len=*), intent( in) :: basename
920  integer, intent( in) :: odims(2)
921  integer, intent( in) :: it
922 
923  integer :: fid
924  integer :: i, j
925  !---------------------------------------------------------------------------
926 
927  call file_open( basename, fid, rankid=myrank, single=.true., postfix="" )
928 
929  call file_read( fid, "XLAT", olat_org(:,:), step=it )
930  !$omp parallel do
931  do j = 1, odims(2)
932  do i = 1, odims(1)
933  olat_org(i,j) = olat_org(i,j) * d2r
934  end do
935  end do
936 
937  call file_read( fid, "XLONG", olon_org(:,:), step=it )
938  !$omp parallel do
939  do j = 1, odims(2)
940  do i = 1, odims(1)
941  olon_org(i,j) = olon_org(i,j) * d2r
942  end do
943  end do
944 
945 
946  ! land mask (1:land, 0:water)
947  call file_read( fid, "LANDMASK", omask_org(:,:), step=it )
948 
949  ! SEA SURFACE TEMPERATURE [K]
950  call file_read( fid, "SST", sst_org(:,:), step=it )
951  !$omp parallel do
952  do j = 1, odims(2)
953  do i = 1, odims(1)
954  tw_org(i,j) = sst_org(i,j)
955  end do
956  end do
957 
958  ! ALBEDO [-]
959  call file_read( fid, "ALBEDO", albw_org(:,:,i_r_direct ,i_r_vis), step=it )
960  !$omp parallel do
961  do j = 1, odims(2)
962  do i = 1, odims(1)
963  albw_org(i,j,i_r_direct ,i_r_nir) = albw_org(i,j,i_r_direct ,i_r_vis)
964  albw_org(i,j,i_r_diffuse,i_r_nir) = albw_org(i,j,i_r_direct ,i_r_vis)
965  albw_org(i,j,i_r_diffuse,i_r_vis) = albw_org(i,j,i_r_direct ,i_r_vis)
966  end do
967  end do
968 
969  ! SURFACE EMISSIVITY [-]
970  call file_read( fid, "EMISS", read_xy(:,:), step=it )
971  !$omp parallel do
972  do j = 1, odims(2)
973  do i = 1, odims(1)
974  albw_org(i,j,i_r_diffuse,i_r_ir) = 1.0_rp - read_xy(i,j)
975  enddo
976  enddo
977  !$omp parallel do
978  do j = 1, odims(2)
979  do i = 1, odims(1)
980  albw_org(i,j,i_r_direct,i_r_ir) = albw_org(i,j,i_r_diffuse,i_r_ir)
981  end do
982  end do
983 
984  ! TIME-VARYING ROUGHNESS LENGTH [m] (no wrfout-default)
985  call file_read( fid, "ZNT", z0w_org(:,:), step=it, allow_missing=.true., missing_value=undef )
986 
987 
988  return

References scale_const::const_d2r, scale_const::const_undef, scale_file::file_open(), scale_cpl_sfc_index::i_r_diffuse, scale_cpl_sfc_index::i_r_direct, scale_cpl_sfc_index::i_r_ir, scale_cpl_sfc_index::i_r_nir, and scale_cpl_sfc_index::i_r_vis.

Referenced by mod_realinput::realinput_surface().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ wrf_arwpost_calc_uvmet()

subroutine mod_realinput_wrfarw::wrf_arwpost_calc_uvmet ( real(rp), dimension(:,:,:), intent(out)  u_latlon,
real(rp), dimension(:,:,:), intent(out)  v_latlon,
real(rp), dimension(:,:,:), intent(in)  u_on_map,
real(rp), dimension(:,:,:), intent(in)  v_on_map,
real(rp), dimension(:,:), intent(in)  xlon,
real(rp), dimension(:,:), intent(in)  xlat,
character(len=*), intent(in)  basename,
integer, intent(in)  K1,
integer, intent(in)  I1,
integer, intent(in)  J1 
)

convert vector varibles from map-projected grid on wrf model to lat-lon grid

Definition at line 1003 of file mod_realinput_wrfarw.F90.

1003  use scale_const, only: &
1004  d2r => const_d2r, &
1005  pi => const_pi
1006  use scale_file, only: &
1007  file_open, &
1008  file_get_attribute
1009  implicit none
1010  real(RP), intent(out) :: u_latlon(:,:,:)
1011  real(RP), intent(out) :: v_latlon(:,:,:)
1012  real(RP), intent(in ) :: u_on_map(:,:,:)
1013  real(RP), intent(in ) :: v_on_map(:,:,:)
1014  real(RP), intent(in ) :: xlon(:,:)
1015  real(RP), intent(in ) :: xlat(:,:)
1016  integer , intent(in ) :: K1, I1, J1
1017 
1018  character(len=*), intent( in) :: basename
1019 
1020  integer :: fid
1021 
1022  real(RP) :: truelat1, truelat2
1023  real(RP) :: stand_lon
1024  real(RP) :: diff
1025  real(RP) :: alpha
1026  real(RP) :: sine(I1,J1)
1027  real(RP) :: cose(I1,J1)
1028  real(RP) :: cone
1029  integer :: map_proj
1030 
1031  real(RP) :: dum_r(1)
1032  integer :: dum_i(1)
1033 
1034 
1035  integer :: k, i, j
1036  !---------------------------------------------------------------------------
1037 
1038  call file_open( basename, fid, rankid=myrank, single=.true., postfix="" )
1039 
1040  call file_get_attribute( fid, "global", "MAP_PROJ", dum_i(:) )
1041  map_proj = dum_i(1)
1042 
1043  call file_get_attribute( fid, "global", "TRUELAT1", dum_r(:) )
1044  truelat1 = dum_r(1) * d2r
1045  call file_get_attribute( fid, "global", "TRUELAT2", dum_r(:) )
1046  truelat2 = dum_r(1) * d2r
1047  call file_get_attribute( fid, "global", "STAND_LON", dum_r(:) )
1048  stand_lon = dum_r(1) * d2r
1049 
1050  ! No need to rotate
1051  if ( map_proj .ge. 3 ) then
1052  !$omp parallel do
1053  do j = 1, j1
1054  do i = 1, i1
1055  do k = 1, k1
1056  u_latlon(k,i,j) = u_on_map(k,i,j)
1057  v_latlon(k,i,j) = v_on_map(k,i,j)
1058  end do
1059  end do
1060  end do
1061 
1062  return
1063  endif
1064 
1065  ! Lambert Conformal mapping
1066  cone = 1.0_rp ! PS
1067  if ( map_proj .eq. 1 ) then
1068  if ( abs(truelat1-truelat2) .gt. 0.1_rp*d2r ) then
1069  cone = ( log(cos(truelat1)) - &
1070  log(cos(truelat2)) ) / &
1071  ( log(tan((pi*0.5_rp-abs(truelat1))*0.5_rp )) - &
1072  log(tan((pi*0.5_rp-abs(truelat2))*0.5_rp )) )
1073  else
1074  cone = sin( abs(truelat1) )
1075  endif
1076  endif
1077 
1078  !$omp parallel do &
1079  !$omp private(diff,alpha)
1080  do j = 1, j1
1081  do i = 1, i1
1082  diff = xlon(i,j) - stand_lon
1083  if ( diff .gt. pi ) then
1084  diff = diff - pi*2.0_rp
1085  endif
1086  if ( diff .lt. -pi ) then
1087  diff = diff + pi*2.0_rp
1088  endif
1089  alpha = diff * cone * sign(1.0_rp, xlat(i,j))
1090  sine(i,j) = sin( alpha )
1091  cose(i,j) = cos( alpha )
1092  enddo
1093  enddo
1094 
1095  !$omp parallel do
1096  do j = 1, j1
1097  do i = 1, i1
1098  do k = 1, k1
1099  u_latlon(k,i,j) = v_on_map(k,i,j)*sine(i,j) + u_on_map(k,i,j)*cose(i,j)
1100  v_latlon(k,i,j) = v_on_map(k,i,j)*cose(i,j) - u_on_map(k,i,j)*sine(i,j)
1101  enddo
1102  enddo
1103  enddo
1104 
1105  return

References scale_const::const_d2r, scale_const::const_pi, and scale_file::file_open().

Referenced by parentatmosinputwrfarw().

Here is the call graph for this function:
Here is the caller graph for this function:
scale_const::const_grav
real(rp), public const_grav
standard acceleration of gravity [m/s2]
Definition: scale_const.F90:46
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:342
scale_atmos_hydrometeor::i_hr
integer, parameter, public i_hr
liquid water rain
Definition: scale_atmos_hydrometeor.F90:82
scale_atmos_hydrometeor::i_hs
integer, parameter, public i_hs
snow
Definition: scale_atmos_hydrometeor.F90:84
scale_atmos_hydrometeor
module atmosphere / hydrometeor
Definition: scale_atmos_hydrometeor.F90:12
scale_file::file_get_dimlength
subroutine, public file_get_dimlength(fid, dimname, len, error)
get length of dimension
Definition: scale_file.F90:565
scale_file
module file
Definition: scale_file.F90:15
scale_const::const_pi
real(rp), public const_pi
pi
Definition: scale_const.F90:31
scale_atmos_hydrometeor::i_hi
integer, parameter, public i_hi
ice water cloud
Definition: scale_atmos_hydrometeor.F90:83
mod_atmos_vars::dens
real(rp), dimension(:,:,:), allocatable, target, public dens
Definition: mod_atmos_vars.F90:75
scale_const
module CONSTANT
Definition: scale_const.F90:11
scale_file::file_open
subroutine, public file_open(basename, fid, mode, single, aggregate, rankid, postfix)
Definition: scale_file.F90:487
scale_atmos_hydrometeor::i_hc
integer, parameter, public i_hc
liquid water cloud
Definition: scale_atmos_hydrometeor.F90:81
scale_const::const_rdry
real(rp), public const_rdry
specific gas constant (dry air) [J/kg/K]
Definition: scale_const.F90:55
scale_const::const_d2r
real(rp), public const_d2r
degree to radian
Definition: scale_const.F90:32
scale_const::const_laps
real(rp), public const_laps
lapse rate of ISA [K/m]
Definition: scale_const.F90:58
scale_const::const_undef
real(rp), public const_undef
Definition: scale_const.F90:41
scale_atmos_hydrometeor::n_hyd
integer, parameter, public n_hyd
Definition: scale_atmos_hydrometeor.F90:79
scale_atmos_hydrometeor::i_hg
integer, parameter, public i_hg
graupel
Definition: scale_atmos_hydrometeor.F90:85