61 integer,
parameter :: handle = 1
63 real(RP),
allocatable :: read2D(:,:)
64 real(RP),
allocatable :: read3D(:,:,:)
65 real(RP),
allocatable :: read3DL(:,:,:)
75 integer,
intent(out) :: dims(6)
80 if(
io_l )
write(
io_fid_log,*)
'+++ Real Case/Atom Input File Type: SCALE-RM' 108 real(RP),
intent(out) :: lon_org(:,:)
109 real(RP),
intent(out) :: lat_org(:,:)
110 real(RP),
intent(out) :: cz_org (:,:,:)
111 character(len=*),
intent(in) :: basename_org
112 integer,
intent(in) :: dims(6)
115 integer :: xloc, yloc
116 integer :: xs, xe, ys, ye
120 if(
io_l )
write(
io_fid_log,*)
'+++ ScaleLib/IO[realinput]/Categ[AtomOpenSCALE]' 127 yloc = int(
real(i-1) /
real(NEST_TILE_NUM_X) ) + 1
134 call fileread( read2d(:,:), basename_org,
"lon", 1, rank )
135 lon_org(xs:xe,ys:ye) = read2d(:,:) * d2r
137 call fileread( read2d(:,:), basename_org,
"lat", 1, rank )
138 lat_org(xs:xe,ys:ye) = read2d(:,:) * d2r
140 call fileread( read3d(:,:,:), basename_org,
"height", 1, rank )
142 cz_org(k+2,xs:xe,ys:ye) = read3d(:,:,k)
145 call fileread( read2d(:,:), basename_org,
"topo", 1, rank )
146 cz_org(2,xs:xe,ys:ye) = read2d(:,:)
150 cz_org(1,:,:) = 0.0_rp
182 hydrostatic_buildrho_real => atmos_hydrostatic_buildrho_real
184 thermodyn_temp_pres => atmos_thermodyn_temp_pres, &
185 thermodyn_pott => atmos_thermodyn_pott
200 real(RP),
intent(out) :: velz_org(:,:,:)
201 real(RP),
intent(out) :: velx_org(:,:,:)
202 real(RP),
intent(out) :: vely_org(:,:,:)
203 real(RP),
intent(out) :: pres_org(:,:,:)
204 real(RP),
intent(out) :: dens_org(:,:,:)
205 real(RP),
intent(out) :: pott_org(:,:,:)
206 real(RP),
intent(out) :: qtrc_org(:,:,:,:)
207 real(RP),
intent(in) :: cz_org(:,:,:)
208 logical,
intent(in) :: flg_bin
209 logical,
intent(in) :: flg_intrp
210 character(len=*),
intent(in) :: basename_org
211 integer,
intent(in) :: mptype_parent
212 integer,
intent(in) :: dims(6)
213 integer,
intent(in) :: it
217 real(RP) :: momz_org(dims(1)+2,dims(2),dims(3))
218 real(RP) :: momx_org(dims(1)+2,dims(2),dims(3))
219 real(RP) :: momy_org(dims(1)+2,dims(2),dims(3))
220 real(RP) :: rhot_org(dims(1)+2,dims(2),dims(3))
221 real(RP) :: tsfc_org( dims(2),dims(3))
227 integer :: xloc, yloc
230 integer :: k, i, j, iq, iqa
234 if(
io_l )
write(
io_fid_log,*)
'+++ ScaleLib/IO[realinput]/Categ[AtomInputSCALE]' 241 yloc = int(
real(i-1) /
real(NEST_TILE_NUM_X) ) + 1
248 call fileread( read2d(:,:), basename_org,
"T2", it, rank )
249 tsfc_org(xs:xe,ys:ye) = read2d(:,:)
251 call fileread( read2d(:,:), basename_org,
"MSLP", it, rank )
252 pres_org(1,xs:xe,ys:ye) = read2d(:,:)
254 call fileread( read3d(:,:,:), basename_org,
"DENS", it, rank )
256 dens_org(k+2,xs:xe,ys:ye) = read3d(:,:,k)
259 call fileread( read3d(:,:,:), basename_org,
"MOMZ", it, rank )
261 momz_org(k+2,xs:xe,ys:ye) = read3d(:,:,k)
264 call fileread( read3d(:,:,:), basename_org,
"MOMX", it, rank )
266 momx_org(k+2,xs:xe,ys:ye) = read3d(:,:,k)
269 call fileread( read3d(:,:,:), basename_org,
"MOMY", it, rank )
271 momy_org(k+2,xs:xe,ys:ye) = read3d(:,:,k)
274 call fileread( read3d(:,:,:), basename_org,
"RHOT", it, rank )
276 rhot_org(k+2,xs:xe,ys:ye) = read3d(:,:,k)
280 qtrc_org(:,xs:xe,ys:ye,iq) = 0.0_rp
283 if( flg_bin .and. flg_intrp )
then 285 if(
io_l )
write(
io_fid_log,*)
'+++ SDF of SBM(S10) is interpolated from Qxx and Nxx' 298 qtrc_org(2,xs:xe,ys:ye,iq) = qtrc_org(3,xs:xe,ys:ye,iq)
303 do iq = 1, mptype_parent
305 call fileread( read3d(:,:,:), basename_org,
tracer_name(iq), it, rank )
307 qtrc_org(k+2,xs:xe,ys:ye,iqa) = read3d(:,:,k)
309 qtrc_org(2,xs:xe,ys:ye,iqa) = qtrc_org(3,xs:xe,ys:ye,iqa)
310 qtrc_org(1,xs:xe,ys:ye,iqa) = qtrc_org(3,xs:xe,ys:ye,iqa)
324 velz_org(k,i,j) = ( momz_org(k-1,i,j) + momz_org(k,i,j) ) / dens_org(k,i,j) * 0.5_rp
330 velz_org(1:3 ,i,j) = 0.0_rp
331 velz_org(dims(1)+2,i,j) = 0.0_rp
339 velx_org(k,i,j) = ( momx_org(k,i-1,j) + momx_org(k,i,j) ) / dens_org(k,i,j) * 0.5_rp
345 velx_org(k,1,j) = momx_org(k,1,j) / dens_org(k,1,j)
348 velx_org(1:2,:,:) = 0.0_rp
354 vely_org(k,i,j) = ( momy_org(k,i,j-1) + momy_org(k,i,j) ) / dens_org(k,i,j) * 0.5_rp
360 vely_org(k,i,1) = momy_org(k,i,1) / dens_org(k,i,1)
363 vely_org(1:2,:,:) = 0.0_rp
373 call thermodyn_temp_pres( temp_org, &
381 pott_org(k,i,j) = rhot_org(k,i,j) / dens_org(k,i,j)
383 dz = cz_org(3,i,j) - cz_org(2,i,j)
384 dens_org(2,i,j) = ( pres_org(3,i,j) + grav * dens_org(3,i,j) * dz * 0.5_rp ) &
385 / ( rdry * tsfc_org(i,j) - grav * dz * 0.5_rp )
386 pres_org(2,i,j) = dens_org(2,i,j) * rdry * tsfc_org(i,j)
387 pott_org(2,i,j) = tsfc_org(i,j) * ( p00 / pres_org(2,i,j) )**(rdry/cpdry)
388 temp_org = tsfc_org(i,j) + laps * cz_org(2,i,j)
389 pott_org(1,i,j) = temp_org * ( p00 / pres_org(1,i,j) )**(rdry/cpdry)
390 dens_org(1,i,j) = pres_org(1,i,j) / ( rdry * temp_org )
403 integer,
intent(out) :: ldims(3)
408 if(
io_l )
write(
io_fid_log,*)
'+++ Real Case/Land Input File Type: SCALE-RM' 413 if ( .not.
allocated(read2d) )
then 435 use_file_landwater, &
443 real(RP),
intent(out) :: tg_org(:,:,:)
444 real(RP),
intent(out) :: strg_org(:,:,:)
445 real(RP),
intent(out) :: lst_org(:,:)
446 real(RP),
intent(out) :: ust_org(:,:)
447 real(RP),
intent(out) :: albg_org(:,:,:)
448 real(RP),
intent(out) :: topo_org(:,:)
449 real(RP),
intent(out) :: lmask_org(:,:)
450 real(RP),
intent(out) :: llon_org(:,:)
451 real(RP),
intent(out) :: llat_org(:,:)
452 real(RP),
intent(out) :: lz_org(:)
454 character(len=*),
intent(in) :: basename_land
455 integer,
intent(in) :: ldims(3)
456 logical,
intent(in) :: use_file_landwater
457 integer,
intent(in) :: it
461 integer :: k, i, j, n
462 integer :: xloc, yloc
467 if(
io_l )
write(
io_fid_log,*)
'+++ ScaleLib/IO[realinput]/Categ[LandInputSCALE]' 474 yloc = int(
real(i-1) /
real(NEST_TILE_NUM_X) ) + 1
481 call fileread( read3dl(:,:,:), basename_land,
"LAND_TEMP", it, rank )
483 tg_org(k,xs:xe,ys:ye) = read3dl(:,:,k)
486 if( use_file_landwater )
then 487 call fileread( read3dl(:,:,:), basename_land,
"LAND_WATER", it, rank )
489 strg_org(k,xs:xe,ys:ye) = read3dl(:,:,k)
493 call fileread( read2d(:,:), basename_land,
"lon", 1, rank )
494 llon_org(xs:xe,ys:ye) = read2d(:,:) * d2r
496 call fileread( read2d(:,:), basename_land,
"lat", 1, rank )
497 llat_org(xs:xe,ys:ye) = read2d(:,:) * d2r
499 call fileread( read2d(:,:), basename_land,
"LAND_SFC_TEMP", it, rank )
500 lst_org(xs:xe,ys:ye) = read2d(:,:)
502 call fileread( read2d(:,:), basename_land,
"URBAN_SFC_TEMP", it, rank )
503 ust_org(xs:xe,ys:ye) = read2d(:,:)
505 call fileread( read2d(:,:), basename_land,
"LAND_ALB_LW", it, rank )
506 albg_org(xs:xe,ys:ye,1) = read2d(:,:)
508 call fileread( read2d(:,:), basename_land,
"LAND_ALB_SW", it, rank )
509 albg_org(xs:xe,ys:ye,2) = read2d(:,:)
511 call fileread( read2d(:,:), basename_land,
"topo", it, rank )
512 topo_org(xs:xe,ys:ye) = read2d(:,:)
514 call fileread( read2d(:,:), basename_land,
"lsmask", it, rank )
515 lmask_org(xs:xe,ys:ye) = read2d(:,:)
519 call fileread( lz_org(:), basename_land,
"lz", 1, rank )
530 integer,
intent(out) :: odims(2)
535 if(
io_l )
write(
io_fid_log,*)
'+++ Real Case/Ocean Input File Type: SCALE-RM' 539 if ( .not.
allocated(read2d) )
then 558 real(RP),
intent(out) :: olon_org (:,:)
559 real(RP),
intent(out) :: olat_org (:,:)
560 real(RP),
intent(out) :: omask_org(:,:)
561 character(len=*),
intent(in) :: basename_ocean
562 integer,
intent(in) :: odims(2)
565 integer :: xloc, yloc
566 integer :: xs, xe, ys, ye
570 if(
io_l )
write(
io_fid_log,*)
'+++ ScaleLib/IO[realinput]/Categ[OceanOpenSCALE]' 577 yloc = int(
real(i-1) /
real(NEST_TILE_NUM_X) ) + 1
584 call fileread( read2d(:,:), basename_ocean,
"lon", 1, rank )
585 olon_org(xs:xe,ys:ye) = read2d(:,:) * d2r
587 call fileread( read2d(:,:), basename_ocean,
"lat", 1, rank )
588 olat_org(xs:xe,ys:ye) = read2d(:,:) * d2r
590 call fileread( read2d(:,:), basename_ocean,
"lsmask", 1, rank )
591 omask_org(xs:xe,ys:ye) = read2d(:,:)
612 real(RP),
intent(out) :: tw_org(:,:)
613 real(RP),
intent(out) :: sst_org(:,:)
614 real(RP),
intent(out) :: albw_org(:,:,:)
615 real(RP),
intent(out) :: z0w_org(:,:)
616 real(RP),
intent(out) :: omask_org(:,:)
618 character(len=*),
intent(in) :: basename_ocean
619 integer,
intent(in) :: odims(2)
620 integer,
intent(in) :: it
625 integer :: xloc, yloc
630 if(
io_l )
write(
io_fid_log,*)
'+++ ScaleLib/IO[realinput]/Categ[OceanInputSCALE]' 637 yloc = int(
real(i-1) /
real(NEST_TILE_NUM_X) ) + 1
644 call fileread( read2d(:,:), basename_ocean,
"OCEAN_TEMP", it, rank )
645 tw_org(xs:xe,ys:ye) = read2d(:,:)
647 call fileread( read2d(:,:), basename_ocean,
"OCEAN_SFC_TEMP", it, rank )
648 sst_org(xs:xe,ys:ye) = read2d(:,:)
650 call fileread( read2d(:,:), basename_ocean,
"OCEAN_ALB_LW", it, rank )
651 albw_org(xs:xe,ys:ye,1) = read2d(:,:)
653 call fileread( read2d(:,:), basename_ocean,
"OCEAN_ALB_SW", it, rank )
654 albw_org(xs:xe,ys:ye,2) = read2d(:,:)
656 call fileread( read2d(:,:), basename_ocean,
"OCEAN_SFC_Z0M", it, rank )
657 z0w_org(xs:xe,ys:ye) = read2d(:,:)
659 call fileread( read2d(:,:), basename_ocean,
"lsmask", it, rank )
660 omask_org(xs:xe,ys:ye) = read2d(:,:)
real(rp), public const_cpdry
specific heat (dry air,constant pressure) [J/kg/K]
subroutine, public prc_mpistop
Abort MPI.
module ATMOSPHERE / Physics Cloud Microphysics - Convert
integer, dimension(2), public parent_jmax
parent max number in y-direction
module GRID (nesting system)
real(rp), dimension(qa_max), public tracer_r
logical, public io_l
output log or not? (this process)
module ATMOSPHERE / Physics Cloud Microphysics
subroutine, public atmos_phy_mp_bulk2bin(xs, xe, ys, ye, dims, it, rank, handle, basename_org, dens_org, qtrc_org)
Bulk to Bin.
real(rp), public const_d2r
degree to radian
procedure(intrpnest_intfc_interp_2d), pointer, public intrpnest_interp_2d
integer, dimension(:), allocatable, public nest_tile_id
parent tile real id
real(rp), public const_laps
lapse rate of ISA [K/m]
character(len=h_short), dimension(qa_max), public tracer_name
real(rp), dimension(qa_max), public tracer_cv
subroutine, public intrpnest_interp_fact_llz(hfact, vfact, kgrd, igrd, jgrd, ncopy, myhgt, mylat, mylon, myKS, myKE, myIA, myJA, inhgt, inlat, inlon, inKA, inIA, inJA, landgrid)
real(rp), public const_rdry
specific gas constant (dry air) [J/kg/K]
real(rp), public const_pre00
pressure reference [Pa]
module ATMOSPHERE / Hydrostatic barance
real(rp), public const_grav
standard acceleration of gravity [m/s2]
real(rp), dimension(:,:,:), allocatable, public gtrans_rotc
rotation coefficient
integer, dimension(2), public parent_lkmax
parent max number in lz-direction
procedure(intrpnest_intfc_interp_3d), pointer, public intrpnest_interp_3d
integer, public nest_tile_num_y
parent tile number in y-direction
integer, dimension(2), public parent_kmax
parent max number in z-direction
integer, public prc_myrank
process num in local communicator
module INTERPOLATION (nesting system)
integer, dimension(2), public parent_imax
parent max number in x-direction
module ATMOSPHERE / Thermodynamics
integer, public nest_tile_num_x
parent tile number in x-direction
real(rp), dimension(:,:), allocatable, public topo_zsfc
absolute ground height [m]
integer, public io_fid_log
Log file ID.
real(rp), dimension(qa_max), public tracer_mass