59 character(len=32) :: name =
""
60 logical :: zstg = .false.
61 logical :: xstg = .false.
62 logical :: ystg = .false.
63 real(RP) :: fact = 1.0_rp
64 real(RP) :: offset = 0.0_rp
67 type(hash_table) :: vars_atmos
68 type(hash_table) :: vars_ocean
69 type(hash_table) :: vars_land
71 real(RP),
allocatable :: work3d(:,:,:)
72 real(RP),
allocatable :: work2d(:,:)
75 logical :: SCALE_tile_atm
76 logical :: SCALE_tile_lnd
77 logical :: SCALE_tile_ocn
78 integer :: SCALE_DOMID_atm = -1
79 integer :: SCALE_DOMID_lnd = -1
80 integer :: SCALE_DOMID_ocn = -1
81 integer :: nfiles_atm = 0
82 integer :: nfiles_lnd = 0
83 integer :: nfiles_ocn = 0
84 integer :: fid_atm = -1
85 integer :: fid_lnd = -1
86 integer :: fid_ocn = -1
87 integer,
allocatable :: fids_atm(:)
88 integer,
allocatable :: fids_lnd(:)
89 integer,
allocatable :: fids_ocn(:)
90 integer,
allocatable :: tile_id_atm(:)
91 integer,
allocatable :: tile_id_lnd(:)
92 integer,
allocatable :: tile_id_ocn(:)
94 integer,
parameter :: vars_max = 100
97 character(len=32) :: zname, zhname
98 character(len=32) :: xname, xhname
99 character(len=32) :: yname, yhname
100 character(len=32) :: tname
102 namelist / netcdf_dims / &
111 character(len=32) :: item
112 character(len=32) :: name
113 logical :: zstg, xstg, ystg
114 real(RP) :: fact, offset
116 namelist / netcdf_item / &
158 file_get_attribute, &
171 integer,
intent(out) :: dims(6)
172 integer,
intent(out) :: timelen
173 logical,
intent(out) :: mixing_ratio
174 logical,
intent(out) :: update_coord
176 logical,
intent(out) :: qtrc_flag(
qa)
177 real(rp),
allocatable,
intent(out) :: lon_all(:,:)
178 real(rp),
allocatable,
intent(out) :: lat_all(:,:)
180 character(len=*),
intent(in) :: basename_org
181 character(len=*),
intent(in) :: basename_num
182 logical,
intent(in) :: same_mp_type
184 logical,
intent(inout) :: pt_dry
185 logical,
intent(inout) :: serial
186 logical,
intent(inout) :: do_read
188 character(len=8) :: file_type
189 character(len=FILE_HLONG) :: nm_file
190 integer :: scale_parent_prc_num_x
191 integer :: scale_parent_prc_num_y
192 character(len=FILE_HLONG) :: scale_latlon_catalogue
194 namelist / param_mkinit_real_atmos_netcdf / &
198 scale_parent_prc_num_x, &
199 scale_parent_prc_num_y, &
200 scale_latlon_catalogue
202 character(len=H_SHORT) :: mapping_name
203 real(
dp) :: false_easting
204 real(
dp) :: false_northing
205 real(
dp) :: longitude_of_central_meridian
206 real(
dp) :: longitude_of_projection_origin
207 real(
dp) :: latitude_of_projection_origin
208 real(
dp) :: straight_vertical_longitude_from_pole
209 real(
dp) :: standard_parallel(2)
212 namelist / netcdf_mapprojection / &
216 longitude_of_central_meridian, &
217 longitude_of_projection_origin, &
218 latitude_of_projection_origin, &
219 straight_vertical_longitude_from_pole, &
223 character(len=32) :: items(vars_max)
225 type(vinfo),
pointer :: var_info
226 class(*),
pointer :: v
228 character(len=FILE_HLONG) :: basename
229 character(len=FILE_HLONG) :: fname
230 character(len=32) :: map
235 logical :: exist, error
239 log_info(
"ParentAtmosSetupNetCDF",*)
'Real Case/Atmos Setup'
243 mixing_ratio = .false.
244 scale_parent_prc_num_x = -1
245 scale_parent_prc_num_y = -1
246 scale_latlon_catalogue =
""
250 read(
io_fid_conf,nml=param_mkinit_real_atmos_netcdf,iostat=ierr)
252 log_error(
"ParentAtmosSetupNetCDF",*)
'Not appropriate names in namelist PARAM_MKINIT_REAL_ATMOS_NetCDF. Check!'
255 log_nml(param_mkinit_real_atmos_netcdf)
257 basename = trim(basename_org) // trim(basename_num)
261 call check_filetype(fid_atm, file_type, basename, scale_tile_atm,
"ParentAtmosOpenNetCDF")
264 call comm_bcast( file_type )
266 if ( file_type ==
"SCALE-RM" )
then
267 call comm_bcast( scale_tile_atm )
268 if ( scale_tile_atm )
then
278 false_easting = undef
279 false_northing = undef
280 longitude_of_central_meridian = undef
281 longitude_of_projection_origin = undef
282 latitude_of_projection_origin = undef
283 straight_vertical_longitude_from_pole = undef
284 standard_parallel = (/ undef, undef /)
289 select case( file_type )
299 call vars_atmos%put(
"lon", vinfo(
"lon"))
300 call vars_atmos%put(
"lat", vinfo(
"lat"))
302 call vars_atmos%put(
"height", vinfo(
"height"))
303 call vars_atmos%put(
"pressure", vinfo(
"PRES"))
305 call vars_atmos%put(
"DENS", vinfo(
"DENS"))
306 call vars_atmos%put(
"W", vinfo(
"W"))
307 call vars_atmos%put(
"MOMZ", vinfo(
"MOMZ", zstg=.true.))
308 call vars_atmos%put(
"Umet", vinfo(
"Umet"))
309 call vars_atmos%put(
"U", vinfo(
"U"))
310 call vars_atmos%put(
"MOMX", vinfo(
"MOMX", xstg=.true.))
311 call vars_atmos%put(
"Vmet", vinfo(
"Vmet"))
312 call vars_atmos%put(
"V", vinfo(
"V"))
313 call vars_atmos%put(
"MOMY", vinfo(
"MOMY", ystg=.true.))
315 call vars_atmos%put(
"PT", vinfo(
"PT"))
316 call vars_atmos%put(
"T", vinfo(
"T"))
317 call vars_atmos%put(
"RHOT", vinfo(
"RHOT"))
319 call vars_atmos%put(
"QV", vinfo(
"QV"))
320 call vars_atmos%put(
"RH", vinfo(
"RH"))
322 if ( same_mp_type )
then
327 call vars_atmos%put(
"QC", vinfo(
"QC"))
328 call vars_atmos%put(
"QR", vinfo(
"QR"))
329 call vars_atmos%put(
"QI", vinfo(
"QI"))
330 call vars_atmos%put(
"QS", vinfo(
"QS"))
331 call vars_atmos%put(
"QG", vinfo(
"QG"))
333 call vars_atmos%put(
"NC", vinfo(
"NC"))
334 call vars_atmos%put(
"NR", vinfo(
"NR"))
335 call vars_atmos%put(
"NI", vinfo(
"NI"))
336 call vars_atmos%put(
"NS", vinfo(
"NS"))
337 call vars_atmos%put(
"NG", vinfo(
"NG"))
340 call vars_atmos%put(
"topo", vinfo(
"topo"))
341 call vars_atmos%put(
"MSLP", vinfo(
"MSLP"))
342 call vars_atmos%put(
"SFC_PRES", vinfo(
"SFC_PRES"))
343 call vars_atmos%put(
"U10met", vinfo(
"U10met"))
344 call vars_atmos%put(
"U10", vinfo(
"U10"))
345 call vars_atmos%put(
"V10met", vinfo(
"V10met"))
346 call vars_atmos%put(
"V10", vinfo(
"V10"))
347 call vars_atmos%put(
"T2", vinfo(
"T2"))
348 call vars_atmos%put(
"Q2", vinfo(
"Q2"))
349 call vars_atmos%put(
"RH2", vinfo(
"RH2"))
351 mixing_ratio = .false.
352 update_coord = .false.
356 call file_get_attribute( fid_atm,
"QV",
"grid_mapping", map, existed=exist )
358 call file_get_attribute( fid_atm, map,
"grid_mapping_name", mapping_name )
360 call file_get_attribute( fid_atm, map,
"false_easting", false_easting, existed=exist )
361 call file_get_attribute( fid_atm, map,
"false_northing", false_northing, existed=exist )
362 call file_get_attribute( fid_atm, map,
"longitude_of_central_meridian", longitude_of_central_meridian, existed=exist )
363 call file_get_attribute( fid_atm, map,
"longitude_of_projection_origin", longitude_of_projection_origin, existed=exist )
364 call file_get_attribute( fid_atm, map,
"latitude_of_projection_origin", latitude_of_projection_origin, existed=exist )
365 call file_get_attribute( fid_atm, map,
"straight_vertical_longitude_from_pole", straight_vertical_longitude_from_pole, existed=exist )
366 call file_get_attribute( fid_atm, map,
"standard_parallel", standard_parallel(1:1), existed=exist )
368 call file_get_attribute( fid_atm, map,
"standard_parallel", standard_parallel(:), existed=exist )
369 call file_get_attribute( fid_atm, map,
"rotation", rotation, existed=exist )
373 call comm_bcast( mapping_name )
375 call comm_bcast( false_easting )
376 call comm_bcast( false_northing )
377 call comm_bcast( longitude_of_central_meridian )
378 call comm_bcast( longitude_of_projection_origin )
379 call comm_bcast( latitude_of_projection_origin )
380 call comm_bcast( straight_vertical_longitude_from_pole )
381 call comm_bcast( 2, standard_parallel )
382 call comm_bcast( rotation )
386 zhname =
"bottom_top_stag"
388 xhname =
"west_east_stag"
389 yname =
"south_north"
390 yhname =
"south_north_stag"
393 call vars_atmos%put(
"lon", vinfo(
"XLONG"))
394 call vars_atmos%put(
"lat", vinfo(
"XLAT"))
396 call vars_atmos%put(
"hbar", vinfo(
"PHB", zstg=.true., fact=1.0_rp/grav))
397 call vars_atmos%put(
"hdev", vinfo(
"PH", zstg=.true., fact=1.0_rp/grav))
399 call vars_atmos%put(
"pbar", vinfo(
"PB"))
400 call vars_atmos%put(
"pdev", vinfo(
"P"))
402 call file_get_datainfo( fid_atm,
"U", existed=exist )
404 log_info(
"ParentAtmosSetupNetCDF",*)
'WRF-ARW FILE-TYPE: WRF History Output'
405 call vars_atmos%put(
"W", vinfo(
"W",zstg=.true.))
406 call vars_atmos%put(
"U", vinfo(
"U",xstg=.true.))
407 call vars_atmos%put(
"V", vinfo(
"V",ystg=.true.))
408 call vars_atmos%put(
"PT", vinfo(
"T", offset=300.0_rp))
410 log_info(
"ParentAtmosSetupNetCDF",*)
'WRF-ARW FILE-TYPE: WRF Restart'
411 call vars_atmos%put(
"W", vinfo(
"W_1"))
412 call vars_atmos%put(
"U", vinfo(
"U_1"))
413 call vars_atmos%put(
"V", vinfo(
"V_1"))
414 call vars_atmos%put(
"PT", vinfo(
"T_1", offset=300.0_rp))
417 if ( same_mp_type )
then
418 log_error(
"ParentAtmosSetupNetCDF",*)
'same_mp_type must be .false. for WRF file'
421 call vars_atmos%put(
"QV", vinfo(
"QVAPOR"))
422 call vars_atmos%put(
"QC", vinfo(
"QCLOUD"))
423 call vars_atmos%put(
"QR", vinfo(
"QRAIN"))
424 call vars_atmos%put(
"QI", vinfo(
"QICE"))
425 call vars_atmos%put(
"QS", vinfo(
"QSNOW"))
426 call vars_atmos%put(
"QG", vinfo(
"QGRAUP"))
427 call vars_atmos%put(
"NC", vinfo(
"NC"))
428 call vars_atmos%put(
"NR", vinfo(
"NR"))
429 call vars_atmos%put(
"NI", vinfo(
"NI"))
430 call vars_atmos%put(
"NS", vinfo(
"NS"))
431 call vars_atmos%put(
"NG", vinfo(
"NG"))
433 mixing_ratio = .true.
436 call vars_atmos%put(
"topo", vinfo(
"HGT"))
437 call vars_atmos%put(
"U10", vinfo(
"U10"))
438 call vars_atmos%put(
"V10", vinfo(
"V10"))
439 call vars_atmos%put(
"T2", vinfo(
"T2"))
440 call vars_atmos%put(
"Q2", vinfo(
"Q2"))
441 call vars_atmos%put(
"RH2", vinfo(
"RH2"))
442 call vars_atmos%put(
"SFC_PRES", vinfo(
"PSFC"))
444 call file_get_attribute( fid_atm,
"global",
"MAP_PROJ", i, existed=exist )
447 mapping_name =
"lambert_conformal_conic"
448 call file_get_attribute( fid_atm,
"global",
"TRUELAT1", standard_parallel(1) )
449 call file_get_attribute( fid_atm,
"global",
"TRUELAT2", standard_parallel(2) )
450 call file_get_attribute( fid_atm,
"global",
"STAND_LON", longitude_of_central_meridian )
451 else if ( i >= 3 )
then
454 log_warn(
"ParentAtmodSetupNetCDF",*)
"This map projection type is not supported: ", i
455 log_warn_cont(*)
"Specify map projection parameter manually"
459 update_coord = .true.
463 update_coord = .true.
466 log_error(
"ParentAtmosSetupNetCDF",*)
'FILE_TYPE must be "SCALE-RM", "WRFARW", "NAMELIST", or "AUTO", ', trim(file_type)
472 if ( nm_file /=
"" )
then
475 open(nmfid, file=fname, form=
"formatted", status=
"old", action=
"read", iostat=ierr)
476 if ( ierr /= 0 )
then
477 log_error(
"ParentAtmosSetupNetCDF",*)
'namelist file is not found! ', trim(fname)
481 read(nmfid, nml=netcdf_dims, iostat=ierr)
483 log_error(
"ParentAtmosSetupNetCDF",*)
'Not appropriate names in namelist NetCDF_DIMS in ', trim(fname),
'. Check!'
488 read(nmfid, nml=netcdf_mapprojection, iostat=ierr)
490 log_error(
"ParentAtmosSetupNetCDF",*)
'Not appropriate names in namelist NetCDF_MAPPROJECTION in ', trim(fname),
'. Check!'
497 read(nmfid, nml=netcdf_item, iostat=ierr)
499 log_error(
"ParentAtmosSetupNetCDF",*)
'Not appropriate names in namelist NetCDF_ITEM in ', trim(fname),
'. Check!'
501 else if( ierr < 0 )
then
507 if ( nvars > vars_max )
then
508 log_error(
"ParentAtmosSetupNetCDF",*)
"The number of item in the namelist file exceeds the limit! ", nvars
514 if ( vars_atmos%has_key(items(n)) )
then
516 v => vars_atmos%get(item)
526 offset = var_info%offset
536 read(nmfid, nml=netcdf_item, iostat=ierr)
537 if ( ierr /= 0 )
exit
539 call vars_atmos%put(item, vinfo(name=name, zstg=zstg, xstg=xstg, ystg=ystg, fact=fact, offset=offset))
542 else if ( file_type ==
"NAMELIST" )
then
543 log_error(
"ParentAtmosSetupNetCDF",*)
'NM_FILE is necessary'
547 mapping_info%mapping_name = mapping_name
548 if ( false_easting /= undef ) mapping_info%false_easting = false_easting
549 if ( false_northing /= undef ) mapping_info%false_northing = false_northing
550 if ( longitude_of_central_meridian /= undef ) mapping_info%longitude_of_central_meridian = longitude_of_central_meridian
551 if ( longitude_of_projection_origin /= undef ) mapping_info%longitude_of_projection_origin = longitude_of_projection_origin
552 if ( latitude_of_projection_origin /= undef ) mapping_info%latitude_of_projection_origin = latitude_of_projection_origin
553 if ( straight_vertical_longitude_from_pole /= undef ) mapping_info%straight_vertical_longitude_from_pole = straight_vertical_longitude_from_pole
554 if ( standard_parallel(1) /= undef ) mapping_info%standard_parallel(1) = standard_parallel(1)
555 if ( standard_parallel(2) /= undef ) mapping_info%standard_parallel(2) = standard_parallel(2)
556 if ( rotation /= undef ) mapping_info%rotation = rotation
560 if ( scale_tile_atm )
then
565 scale_parent_prc_num_x, &
566 scale_parent_prc_num_y, &
567 scale_latlon_catalogue )
574 num_tile=nfiles_atm )
580 allocate( fids_atm(nfiles_atm) )
581 allocate( tile_id_atm(nfiles_atm) )
585 tile_id = tile_id_atm )
589 else if ( do_read )
then
604 qtrc_flag(iq) = .false.
606 select type ( v => vars_atmos%get(
tracer_name(iq) ) )
608 if ( v%name .ne.
"" )
then
609 call file_get_datainfo( fid_atm, v%name, existed = qtrc_flag(iq) )
616 if ( error ) timelen = 1
618 allocate( lon_all(dims(2), dims(3)) )
619 allocate( lat_all(dims(2), dims(3)) )
621 call read2d( dims(2), 1, dims(2), dims(3), 1, dims(3), &
622 lon_all(:,:), vars_atmos%get(
"lon"), &
623 1, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm )
624 lon_all(:,:) = lon_all(:,:) * d2r
625 call read2d( dims(2), 1, dims(2), dims(3), 1, dims(3), &
626 lat_all(:,:), vars_atmos%get(
"lat"), &
627 1, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm )
628 lat_all(:,:) = lat_all(:,:) * d2r
641 basename_org, basename_num )
645 character(len=*),
intent(in) :: basename_org
646 character(len=*),
intent(in) :: basename_num
648 character(len=FILE_HLONG) :: basename
654 log_info(
"ParentAtmosOpenNetCDF",*)
'Real Case/Atmos Open'
657 basename = trim(basename_org) // trim(basename_num)
659 if ( scale_tile_atm )
then
667 rankid=tile_id_atm(n) )
670 fid_atm = fids_atm(1)
674 call file_open(basename, fid_atm, postfix=
"")
688 log_info(
"ParentAtmosFinalizeNetCDF",*)
'Real Case/Atmos Finalize'
692 if (
allocated(fids_atm) )
deallocate( fids_atm )
693 if (
allocated(tile_id_atm) )
deallocate( tile_id_atm )
695 call vars_atmos%destroy()
706 KA_org, KS_org, KE_org, &
707 IA_org, IS_org, IE_org, &
708 JA_org, JS_org, JE_org, &
711 w_org, u_org, v_org, &
717 qhyd_org, qnum_org, &
737 integer,
intent(in) :: ka_org, ks_org, ke_org
738 integer,
intent(in) :: ia_org, is_org, ie_org
739 integer,
intent(in) :: ja_org, js_org, je_org
740 integer,
intent(in) ::
qa
742 real(rp),
intent(inout) :: cz_org(ka_org,ia_org,ja_org)
744 real(rp),
intent(out) :: w_org(ka_org,ia_org,ja_org)
745 real(rp),
intent(out) :: u_org(ka_org,ia_org,ja_org)
746 real(rp),
intent(out) :: v_org(ka_org,ia_org,ja_org)
747 real(rp),
intent(out) :: pres_org(ka_org,ia_org,ja_org)
748 real(rp),
intent(out) :: dens_org(ka_org,ia_org,ja_org)
749 real(rp),
intent(out) :: temp_org(ka_org,ia_org,ja_org)
750 real(rp),
intent(out) :: pt_org(ka_org,ia_org,ja_org)
751 real(rp),
intent(out) :: qtrc_org(ka_org,ia_org,ja_org,
qa)
752 real(rp),
intent(out) :: qv_org(ka_org,ia_org,ja_org)
753 real(rp),
intent(out) :: rh_org(ka_org,ia_org,ja_org)
754 real(rp),
intent(out) :: qhyd_org(ka_org,ia_org,ja_org,
n_hyd)
755 real(rp),
intent(out) :: qnum_org(ka_org,ia_org,ja_org,
n_hyd)
756 logical,
intent(out) :: nopres
757 logical,
intent(out) :: nodens
758 logical,
intent(out) :: uvmet
759 logical,
intent(out) :: temp2pt
760 logical,
intent(out) :: rh2qv
761 logical,
intent(out) :: qnum_flag
763 logical,
intent(in) :: same_mp_type
764 logical,
intent(in) :: sfc_diagnoses
765 logical,
intent(in) :: update_coord
766 integer,
intent(in) :: dims(6)
767 integer,
intent(in) :: it
771 integer ::
k, i, j, iq
774 if ( .not.
allocated( work2d ) )
then
775 allocate( work2d(ia_org,ja_org) )
776 allocate( work3d(ka_org-2,ia_org,ja_org) )
780 if ( first_atm .or. update_coord )
then
781 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
782 cz_org(:,:,:), vars_atmos%get(
"height"), &
783 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
785 if ( .not. exist )
then
786 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
787 cz_org(:,:,:), vars_atmos%get(
"hbar"), &
788 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
791 call read3d( ka_org-2, ks_org, ke_org-2, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
792 work3d(:,:,:), vars_atmos%get(
"hdev"), &
793 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
796 if ( .not. exist )
then
797 log_error(
"ParentAtmosInputNetCDF",*)
'"height" or "hbar"+"hdev" is necessary'
804 cz_org(
k+2,i,j) = cz_org(
k+2,i,j) + work3d(
k,i,j)
815 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
816 qtrc_org(:,:,:,iq), vars_atmos%get(
tracer_name(iq)), &
817 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
819 if ( .not. exist )
then
824 qtrc_org(
k+2,i,j,iq) = undef
832 if ( same_mp_type )
then
835 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
836 qtrc_org(:,:,:,iq), vars_atmos%get(
tracer_name(iq)), &
837 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
839 if ( .not. exist )
then
844 qtrc_org(
k+2,i,j,iq) = undef
854 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
855 qv_org(:,:,:), vars_atmos%get(
"QV"), &
856 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
861 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
862 rh_org(:,:,:), vars_atmos%get(
"RH"), &
863 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm )
870 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
871 qhyd_org(:,:,:,iq), vars_atmos%get(
hyd_name(iq)), &
872 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
874 if ( .not. exist )
then
879 qhyd_org(
k+2,i,j,iq) = 0.0_rp
885 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
886 qnum_org(:,:,:,iq), vars_atmos%get(
num_name(iq)), &
887 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
896 qnum_org(
k+2,i,j,iq) = undef
906 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
907 pres_org(:,:,:), vars_atmos%get(
"pressure"), &
908 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
910 if ( .not. exist )
then
911 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
912 pres_org(:,:,:), vars_atmos%get(
"pbar"), &
913 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
916 call read3d( ka_org-2, ks_org, ke_org-2, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
917 work3d(:,:,:), vars_atmos%get(
"pdev"), &
918 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
920 if ( .not. exist )
then
921 log_error(
"ParentAtmosInputNetCDF",*)
'"pdev" is necessary if "pbar" exists'
928 pres_org(
k+2,i,j) = pres_org(
k+2,i,j) + work3d(
k,i,j)
941 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
942 dens_org(:,:,:), vars_atmos%get(
"DENS"), &
943 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
945 nodens = ( .not. exist )
948 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
949 pt_org(:,:,:), vars_atmos%get(
"PT"), &
950 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
955 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
956 pt_org(:,:,:), vars_atmos%get(
"RHOT"), &
957 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
962 log_warn(
"ParentAtmosInputNetCDF",*)
"RHOT is not used because DENS does not exist"
969 pt_org(
k+2,i,j) = pt_org(
k+2,i,j) / dens_org(
k+2,i,j)
977 if ( .not. exist )
then
978 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
979 temp_org(:,:,:), vars_atmos%get(
"T"), &
980 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
984 if ( .not. exist )
then
985 log_error(
"ParentAtmosInputNetCDF",*)
'Either "PT", "RHOT", or "T" is necessary'
990 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
991 w_org(:,:,:), vars_atmos%get(
"W"), &
992 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
994 if ( .not. exist )
then
995 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
996 w_org(:,:,:), vars_atmos%get(
"MOMZ"), &
997 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
1002 log_warn(
"ParentAtmosInputNetCDF",*)
"MOMZ is not used because DENS does not exist"
1009 w_org(
k+2,i,j) = w_org(
k+2,i,j) / dens_org(
k+2,i,j)
1016 if ( .not. exist )
then
1021 w_org(
k+2,i,j) = 0.0_rp
1028 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1029 u_org(:,:,:), vars_atmos%get(
"Umet"), &
1030 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
1035 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1036 u_org(:,:,:), vars_atmos%get(
"U"), &
1037 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
1043 if ( .not. exist )
then
1044 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1045 u_org(:,:,:), vars_atmos%get(
"MOMX"), &
1046 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
1051 log_warn(
"ParentAtmosInputNetCDF",*)
"MOMX is not used because DENS does not exist"
1058 u_org(
k+2,i,j) = u_org(
k+2,i,j) / dens_org(
k+2,i,j)
1066 if ( .not. exist )
then
1067 log_error(
"ParentAtmosInputNetCDF",*)
'Either "Ument", "U", or "MOMX" is necessary'
1073 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1074 v_org(:,:,:), vars_atmos%get(
"Vmet"), &
1075 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
1077 if ( .not. exist )
then
1078 log_error(
"ParentAtmosInputNetCDF",*)
"Vmet is required when Umet exists"
1082 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1083 v_org(:,:,:), vars_atmos%get(
"V"), &
1084 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
1086 if ( .not. exist )
then
1087 call read3d( ka_org, ks_org+2, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1088 v_org(:,:,:), vars_atmos%get(
"MOMY"), &
1089 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
1094 log_warn(
"ParentAtmosInputNetCDF",*)
"MOMY is not used because DENS does not exist"
1101 v_org(
k+2,i,j) = v_org(
k+2,i,j) / dens_org(
k+2,i,j)
1108 if ( .not. exist )
then
1109 log_error(
"ParentAtmosInputNetCDF",*)
'Either "V" or "MOMY" is required when "U" or "MOMX" exists'
1115 if ( sfc_diagnoses )
then
1120 cz_org(1,i,j) = 0.0_rp
1125 if ( first_atm .or. update_coord )
then
1127 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1128 work2d(:,:), vars_atmos%get(
"topo"), &
1129 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
1135 cz_org(2,i,j) = work2d(i,j)
1142 cz_org(2,i,j) = undef
1149 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1150 work2d(:,:), vars_atmos%get(
"MSLP"), &
1151 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
1157 pres_org(1,i,j) = work2d(i,j)
1164 pres_org(1,i,j) = undef
1170 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1171 work2d(:,:), vars_atmos%get(
"SFC_PRES"), &
1172 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
1178 pres_org(2,i,j) = work2d(i,j)
1185 pres_org(2,i,j) = undef
1192 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1193 work2d(:,:), vars_atmos%get(
"U10met"), &
1194 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
1200 u_org(2,i,j) = work2d(i,j)
1207 u_org(2,i,j) = undef
1211 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1212 work2d(:,:), vars_atmos%get(
"V10met"), &
1213 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
1219 v_org(2,i,j) = work2d(i,j)
1226 v_org(2,i,j) = undef
1231 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1232 work2d(:,:), vars_atmos%get(
"U10"), &
1233 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
1239 u_org(2,i,j) = work2d(i,j)
1246 u_org(2,i,j) = undef
1250 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1251 work2d(:,:), vars_atmos%get(
"V10"), &
1252 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
1258 v_org(2,i,j) = work2d(i,j)
1265 v_org(2,i,j) = undef
1272 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1273 work2d(:,:), vars_atmos%get(
"T2"), &
1274 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
1280 temp_org(2,i,j) = work2d(i,j)
1287 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1288 work2d(:,:), vars_atmos%get(
"RH2"), &
1289 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
1295 rh_org(2,i,j) = work2d(i,j)
1302 rh_org(2,i,j) = undef
1307 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1308 work2d(:,:), vars_atmos%get(
"Q2"), &
1309 it, nfiles_atm, fid_atm, fids_atm, scale_tile_atm, scale_domid_atm, &
1312 if ( same_mp_type )
then
1316 qtrc_org(2,i,j,
qs_mp) = work2d(i,j)
1323 qv_org(2,i,j) = work2d(i,j)
1331 qv_org(2,i,j) = undef
1343 cz_org(1,i,j) = 0.0_rp
1344 cz_org(2,i,j) = 0.0_rp
1345 pres_org(1,i,j) = undef
1346 pres_org(2,i,j) = undef
1347 u_org(2,i,j) = undef
1348 v_org(2,i,j) = undef
1349 temp_org(2,i,j) = undef
1350 pt_org(2,i,j) = undef
1351 qv_org(2,i,j) = undef
1352 rh_org(2,i,j) = undef
1372 use_file_landwater, &
1387 integer,
intent(out) :: ldims(3)
1388 integer,
intent(out) :: timelen
1389 real(rp),
allocatable,
intent(out) :: lon_all(:,:)
1390 real(rp),
allocatable,
intent(out) :: lat_all(:,:)
1392 character(len=*),
intent(in) :: basename_org
1393 character(len=*),
intent(in) :: basename_num
1394 logical,
intent(in) :: use_file_landwater
1396 logical,
intent(inout) :: serial
1397 logical,
intent(inout) :: do_read
1399 character(len=8) :: file_type =
"AUTO"
1400 character(len=FILE_HLONG) :: nm_file
1401 logical :: scale_multi_file = .true.
1402 integer :: scale_parent_prc_num_x
1403 integer :: scale_parent_prc_num_y
1404 character(len=FILE_HLONG) :: scale_latlon_catalogue
1406 namelist / param_mkinit_real_land_netcdf / &
1409 scale_parent_prc_num_x, &
1410 scale_parent_prc_num_y, &
1411 scale_latlon_catalogue
1413 character(len=FILE_HLONG) :: basename
1414 character(len=FILE_HLONG) :: fname
1417 character(len=32) :: items(vars_max)
1419 type(vinfo),
pointer :: var_info
1420 class(*),
pointer :: v
1422 logical :: error, exist
1427 log_info(
"ParentLandSetupNetCDF",*)
'Real Case/Land Setup'
1431 scale_parent_prc_num_x = -1
1432 scale_parent_prc_num_y = -1
1433 scale_latlon_catalogue =
""
1437 read(
io_fid_conf,nml=param_mkinit_real_land_netcdf,iostat=ierr)
1439 log_error(
"ParentLandSetupNetCDF",*)
'Not appropriate names in namelist PARAM_MKINIT_REAL_LAND_NetCDF. Check!'
1442 log_nml(param_mkinit_real_land_netcdf)
1445 basename = trim(basename_org) // trim(basename_num)
1449 call check_filetype(fid_lnd, file_type, basename, scale_tile_lnd,
"ParentLandSetupNetCDF")
1452 call comm_bcast( file_type )
1454 if ( file_type ==
"SCALE-RM" )
then
1455 call comm_bcast( scale_tile_lnd )
1456 if ( scale_tile_lnd )
then
1465 select case( file_type )
1472 call vars_land%put(
"lon", vinfo(
"lon"))
1473 call vars_land%put(
"lat", vinfo(
"lat"))
1474 call vars_land%put(
"lz", vinfo(
"lz"))
1476 call vars_land%put(
"topo", vinfo(
"topo"))
1477 call vars_land%put(
"lsmask", vinfo(
"lsmask"))
1479 call vars_land%put(
"LAND_TEMP", vinfo(
"LAND_TEMP"))
1480 if ( use_file_landwater )
then
1481 call vars_land%put(
"LAND_WATER", vinfo(
"LAND_WATER"))
1484 call vars_land%put(
"LAND_SFC_TEMP", vinfo(
"LAND_SFC_TEMP"))
1486 call vars_land%put(
"LAND_SFC_ALB_IR_dir", vinfo(
"LAND_SFC_ALB_IR_dir"))
1487 call vars_land%put(
"LAND_SFC_ALB_IR_dif", vinfo(
"LAND_SFC_ALB_IR_dif"))
1488 call vars_land%put(
"LAND_SFC_ALB_NIR_dir", vinfo(
"LAND_SFC_ALB_NIR_dir"))
1489 call vars_land%put(
"LAND_SFC_ALB_NIR_dif", vinfo(
"LAND_SFC_ALB_NIR_dif"))
1490 call vars_land%put(
"LAND_SFC_ALB_VIS_dir", vinfo(
"LAND_SFC_ALB_VIS_dir"))
1491 call vars_land%put(
"LAND_SFC_ALB_VIS_dif", vinfo(
"LAND_SFC_ALB_VIS_dif"))
1493 call vars_land%put(
"URBAN_SFC_TEMP", vinfo(
"URBAN_SFC_TEMP"))
1496 zname =
"soil_layers_stag"
1498 yname =
"south_north"
1501 call vars_land%put(
"lon", vinfo(
"XLONG"))
1502 call vars_land%put(
"lat", vinfo(
"XLAT"))
1503 call vars_land%put(
"lz", vinfo(
"ZS"))
1505 call vars_land%put(
"topo", vinfo(
"HGT"))
1506 call vars_land%put(
"lsmask", vinfo(
"LANDMASK"))
1508 call vars_land%put(
"LAND_TEMP", vinfo(
"TSLB"))
1509 if ( use_file_landwater )
then
1510 call vars_land%put(
"LAND_WATER", vinfo(
"SH2O"))
1513 call vars_land%put(
"LAND_SFC_TEMP", vinfo(
"TSK"))
1515 call vars_land%put(
"LAND_SFC_ALB_VIS_dir", vinfo(
"ALBEDO"))
1516 call vars_land%put(
"LAND_SFC_EMIS_IR_dif", vinfo(
"EMISS"))
1518 call vars_land%put(
"URBAN_SFC_TEMP", vinfo(
"URBAN_SFC_TEMP"))
1525 log_error(
"ParentLandSetupNetCDF",*)
'FILE_TYPE must be "SCALE-RM", "WRFARW", or "AUTO", ', trim(file_type)
1532 if ( nm_file /=
"" )
then
1535 open(nmfid, file=fname, form=
"formatted", status=
"old", action=
"read", iostat=ierr)
1536 if ( ierr /= 0 )
then
1537 log_error(
"ParentLandSetupNetCDF",*)
'namelist file is not found! ', trim(fname)
1542 read(nmfid, nml=netcdf_dims, iostat=ierr)
1544 log_error(
"ParentLandSetupNetCDF",*)
'Not appropriate names in namelist NetCDF_DIMS in ', trim(fname),
'. Check!'
1552 read(nmfid, nml=netcdf_item, iostat=ierr)
1554 log_error(
"ParentLandSetupNetCDF",*)
'Not appropriate names in namelist NetCDF_ITEM in ', trim(fname),
'. Check!'
1556 else if( ierr < 0 )
then
1562 if ( nvars > vars_max )
then
1563 log_error(
"ParentLandSetupNetCDF",*)
"The number of item in the namelist file exceeds the limit! ", nvars
1569 if ( vars_land%has_key(items(n)) )
then
1571 v => vars_land%get(item)
1576 name = var_info%name
1577 fact = var_info%fact
1578 offset = var_info%offset
1588 read(nmfid, nml=netcdf_item, iostat=ierr)
1589 if ( ierr /= 0 )
exit
1591 call vars_land%put(item, vinfo(name=name, zstg=zstg, xstg=xstg, ystg=ystg, fact=fact, offset=offset))
1594 else if ( file_type ==
"NAMELIST" )
then
1595 log_error(
"ParentLANDSetupNetCDF",*)
'NM_FILE is necessary'
1601 if ( scale_tile_lnd )
then
1606 scale_parent_prc_num_x, &
1607 scale_parent_prc_num_y, &
1608 scale_latlon_catalogue )
1615 num_tile=nfiles_lnd )
1617 allocate( fids_lnd(nfiles_lnd) )
1618 allocate( tile_id_lnd(nfiles_lnd) )
1622 tile_id = tile_id_lnd )
1626 else if ( do_read )
then
1637 if ( error ) timelen = 1
1639 allocate( lon_all(ldims(2), ldims(3)) )
1640 allocate( lat_all(ldims(2), ldims(3)) )
1642 call read2d( ldims(2), 1, ldims(2), ldims(3), 1, ldims(3), &
1643 lon_all(:,:), vars_land%get(
"lon"), &
1644 1, nfiles_lnd, fid_lnd, fids_lnd, scale_tile_lnd, scale_domid_lnd )
1645 lon_all(:,:) = lon_all(:,:) * d2r
1646 call read2d( ldims(2), 1, ldims(2), ldims(3), 1, ldims(3), &
1647 lat_all(:,:), vars_land%get(
"lat"), &
1648 1, nfiles_lnd, fid_lnd, fids_lnd, scale_tile_lnd, scale_domid_lnd )
1649 lat_all(:,:) = lat_all(:,:) * d2r
1661 basename_org, basename_num )
1665 character(len=*),
intent(in) :: basename_org
1666 character(len=*),
intent(in) :: basename_num
1668 character(len=FILE_HLONG) :: basename
1674 log_info(
"ParentLandOpenNetCDF",*)
'Real Case/Land Open'
1676 basename = trim(basename_org) // trim(basename_num)
1678 if ( scale_tile_lnd )
then
1680 do n = 1, nfiles_lnd
1684 aggregate=.false., &
1686 rankid=tile_id_lnd(n) )
1689 fid_lnd = fids_lnd(1)
1693 call file_open(basename, fid_lnd, postfix=
"")
1707 log_info(
"ParentLandFinalizeNetCDF",*)
'Real Case/Land Finalize'
1709 if (
allocated(fids_lnd) )
deallocate( fids_lnd )
1710 if (
allocated(tile_id_lnd) )
deallocate( tile_id_lnd )
1712 call vars_land%destroy()
1714 scale_domid_lnd = -1
1723 KA_org, KS_org, KE_org, &
1724 IA_org, IS_org, IE_org, &
1725 JA_org, JS_org, JE_org, &
1734 use_file_landwater, &
1741 integer,
intent(in) :: ka_org, ks_org, ke_org
1742 integer,
intent(in) :: ia_org, is_org, ie_org
1743 integer,
intent(in) :: ja_org, js_org, je_org
1745 real(rp),
intent(out) :: tg_org(ka_org,ia_org,ja_org)
1746 real(rp),
intent(out) :: strg_org(ka_org,ia_org,ja_org)
1747 real(rp),
intent(out) :: lst_org(ia_org,ja_org)
1748 real(rp),
intent(out) :: ust_org(ia_org,ja_org)
1751 real(rp),
intent(inout) :: topo_org(ia_org,ja_org)
1752 real(rp),
intent(inout) :: lmask_org(ia_org,ja_org)
1753 real(rp),
intent(inout) :: lz_org(ka_org)
1755 logical,
intent(in) :: use_file_landwater
1756 integer,
intent(in) :: ldims(3)
1757 integer,
intent(in) :: it
1763 if ( first_lnd )
then
1764 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1765 topo_org(:,:), vars_land%get(
"topo"), &
1766 it, nfiles_lnd, fid_lnd, fids_lnd, scale_tile_lnd, scale_domid_lnd )
1768 call read1d( ka_org, lz_org(:), vars_land%get(
"lz"), it, fid_lnd )
1770 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1771 lmask_org(:,:), vars_land%get(
"lsmask"), &
1772 it, nfiles_lnd, fid_lnd, fids_lnd, scale_tile_lnd, scale_domid_lnd )
1775 call read3d( ka_org, ks_org, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1776 tg_org(:,:,:), vars_land%get(
"LAND_TEMP"), &
1777 it, nfiles_lnd, fid_lnd, fids_lnd, scale_tile_lnd, scale_domid_lnd )
1781 if( use_file_landwater )
then
1782 call read3d( ka_org, ks_org, ke_org, ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1783 strg_org(:,:,:), vars_land%get(
"LAND_WATER"), &
1784 it, nfiles_lnd, fid_lnd, fids_lnd, scale_tile_lnd, scale_domid_lnd )
1787 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1788 lst_org(:,:), vars_land%get(
"LAND_SFC_TEMP"), &
1789 it, nfiles_lnd, fid_lnd, fids_lnd, scale_tile_lnd, scale_domid_lnd )
1791 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1792 ust_org(:,:), vars_land%get(
"URBAN_SFC_TEMP"), &
1793 it, nfiles_lnd, fid_lnd, fids_lnd, scale_tile_lnd, scale_domid_lnd, &
1795 if ( .not. exist )
then
1799 ust_org(i,j) = lst_org(i,j)
1804 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1806 it, nfiles_lnd, fid_lnd, fids_lnd, scale_tile_lnd, scale_domid_lnd, &
1808 if ( .not. exist )
then
1816 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1818 it, nfiles_lnd, fid_lnd, fids_lnd, scale_tile_lnd, scale_domid_lnd, &
1820 if ( .not. exist )
then
1828 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1830 it, nfiles_lnd, fid_lnd, fids_lnd, scale_tile_lnd, scale_domid_lnd, &
1832 if ( .not. exist )
then
1840 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1842 it, nfiles_lnd, fid_lnd, fids_lnd, scale_tile_lnd, scale_domid_lnd, &
1844 if ( .not. exist )
then
1852 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1854 it, nfiles_lnd, fid_lnd, fids_lnd, scale_tile_lnd, scale_domid_lnd, &
1856 if ( .not. exist )
then
1857 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1859 it, nfiles_lnd, fid_lnd, fids_lnd, scale_tile_lnd, scale_domid_lnd, &
1877 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
1879 it, nfiles_lnd, fid_lnd, fids_lnd, scale_tile_lnd, scale_domid_lnd, &
1881 if ( .not. exist )
then
1918 integer,
intent(out) :: odims(2)
1919 integer,
intent(out) :: timelen
1920 real(rp),
allocatable,
intent(out) :: lon_all(:,:)
1921 real(rp),
allocatable,
intent(out) :: lat_all(:,:)
1923 character(len=*),
intent(in) :: basename_org
1924 character(len=*),
intent(in) :: basename_num
1926 logical,
intent(inout) :: serial
1927 logical,
intent(inout) :: do_read
1929 character(len=8) :: file_type =
"AUTO"
1930 character(len=FILE_HLONG) :: nm_file
1931 logical :: scale_multi_file = .true.
1932 integer :: scale_parent_prc_num_x
1933 integer :: scale_parent_prc_num_y
1934 character(len=FILE_HLONG) :: scale_latlon_catalogue
1936 namelist / param_mkinit_real_ocean_netcdf / &
1940 scale_parent_prc_num_x, &
1941 scale_parent_prc_num_y, &
1942 scale_latlon_catalogue
1944 character(len=FILE_HLONG) :: basename
1945 character(len=FILE_HLONG) :: fname
1948 character(len=32) :: items(vars_max)
1950 type(vinfo),
pointer :: var_info
1951 class(*),
pointer :: v
1958 log_info(
"ParentOceanSetupNetCDF",*)
'Real Case/Ocean Setup'
1962 scale_parent_prc_num_x = -1
1963 scale_parent_prc_num_y = -1
1964 scale_latlon_catalogue =
""
1968 read(
io_fid_conf,nml=param_mkinit_real_ocean_netcdf,iostat=ierr)
1970 log_error(
"ParentOceanSetupNetCDF",*)
'Not appropriate names in namelist PARAM_MKINIT_REAL_OCEAN_NetCDF. Check!'
1973 log_nml(param_mkinit_real_ocean_netcdf)
1976 basename = trim(basename_org) // trim(basename_num)
1980 call check_filetype(fid_ocn, file_type, basename, scale_tile_ocn,
"ParentOceanSetupNetCDF")
1983 call comm_bcast( file_type )
1985 if ( file_type ==
"SCALE-RM" )
then
1986 call comm_bcast( scale_tile_ocn )
1987 if ( scale_tile_ocn )
then
1997 select case( file_type )
2003 call vars_ocean%put(
"lon", vinfo(
"lon"))
2004 call vars_ocean%put(
"lat", vinfo(
"lat"))
2006 call vars_ocean%put(
"lsmask", vinfo(
"lsmask"))
2008 call vars_ocean%put(
"OCEAN_TEMP", vinfo(
"OCEAN_TEMP"))
2010 call vars_ocean%put(
"OCEAN_SFC_TEMP", vinfo(
"OCEAN_SFC_TEMP"))
2011 call vars_ocean%put(
"OCEAN_SFC_Z0M", vinfo(
"OCEAN_SFC_Z0M"))
2013 call vars_ocean%put(
"OCEAN_SFC_ALB_IR_dir", vinfo(
"OCEAN_SFC_ALB_IR_dir"))
2014 call vars_ocean%put(
"OCEAN_SFC_ALB_IR_dif", vinfo(
"OCEAN_SFC_ALB_IR_dif"))
2015 call vars_ocean%put(
"OCEAN_SFC_ALB_NIR_dir", vinfo(
"OCEAN_SFC_ALB_NIR_dir"))
2016 call vars_ocean%put(
"OCEAN_SFC_ALB_NIR_dif", vinfo(
"OCEAN_SFC_ALB_NIR_dif"))
2017 call vars_ocean%put(
"OCEAN_SFC_ALB_VIS_dir", vinfo(
"OCEAN_SFC_ALB_VIS_dir"))
2018 call vars_ocean%put(
"OCEAN_SFC_ALB_VIS_dif", vinfo(
"OCEAN_SFC_ALB_VIS_dif"))
2022 yname =
"south_north"
2025 call vars_ocean%put(
"lon", vinfo(
"XLONG"))
2026 call vars_ocean%put(
"lat", vinfo(
"XLAT"))
2027 call vars_ocean%put(
"lz", vinfo(
"ZS"))
2029 call vars_ocean%put(
"topo", vinfo(
"HGT"))
2030 call vars_ocean%put(
"lsmask", vinfo(
"LANDMASK"))
2032 call vars_ocean%put(
"OCEAN_TEMP", vinfo(
"OCEAN_TEMP"))
2034 call vars_ocean%put(
"OCEAN_SFC_TEMP", vinfo(
"SST"))
2035 call vars_ocean%put(
"OCEAN_SFC_Z0M", vinfo(
"ZNT"))
2037 call vars_ocean%put(
"OCEAN_SFC_ALB_VIS_dir", vinfo(
"ALBEDO"))
2038 call vars_ocean%put(
"OCEAN_SFC_EMIS_IR_dif", vinfo(
"EMISS"))
2042 log_error(
"ParentOCEANSetupNetCDF",*)
'FILE_TYPE must be "SCALE-RM", "WRFARW", "NAMELIST", or "AUTO", ', trim(file_type)
2049 if ( nm_file /=
"" )
then
2052 open(nmfid, file=fname, form=
"formatted", status=
"old", action=
"read", iostat=ierr)
2053 if ( ierr /= 0 )
then
2054 log_error(
"ParentOceanSetupNetCDF",*)
'namelist file is not found! ', trim(fname)
2059 read(nmfid, nml=netcdf_dims, iostat=ierr)
2061 log_error(
"ParentOceanSetupNetCDF",*)
'Not appropriate names in namelist NetCDF_DIMS in ', trim(fname),
'. Check!'
2069 read(nmfid, nml=netcdf_item, iostat=ierr)
2071 log_error(
"ParentLandSetupNetCDF",*)
'Not appropriate names in namelist NetCDF_ITEM in ', trim(fname),
'. Check!'
2073 else if( ierr < 0 )
then
2079 if ( nvars > vars_max )
then
2080 log_error(
"ParentLandSetupNetCDF",*)
"The number of item in the namelist file exceeds the limit! ", nvars
2086 if ( vars_ocean%has_key(items(n)) )
then
2088 v => vars_ocean%get(item)
2093 name = var_info%name
2094 fact = var_info%fact
2095 offset = var_info%offset
2105 read(nmfid, nml=netcdf_item, iostat=ierr)
2106 if ( ierr /= 0 )
exit
2108 call vars_ocean%put(item, vinfo(name=name, zstg=zstg, xstg=xstg, ystg=ystg, fact=fact, offset=offset))
2111 else if ( file_type ==
"NAMELIST" )
then
2112 log_error(
"ParentLANDSetupNetCDF",*)
'NM_FILE is necessary'
2118 if ( scale_tile_ocn )
then
2123 scale_parent_prc_num_x, &
2124 scale_parent_prc_num_y, &
2125 scale_latlon_catalogue )
2131 num_tile=nfiles_ocn )
2133 allocate( fids_ocn(nfiles_ocn) )
2134 allocate( tile_id_ocn(nfiles_ocn) )
2138 tile_id = tile_id_ocn )
2142 else if ( do_read )
then
2152 if ( error ) timelen = 1
2154 allocate( lon_all(odims(1),odims(2)) )
2155 allocate( lat_all(odims(1),odims(2)) )
2157 call read2d( odims(1), 1, odims(1), odims(2), 1, odims(2), &
2158 lon_all(:,:), vars_ocean%get(
"lon"), &
2159 1, nfiles_ocn, fid_ocn, fids_ocn, scale_tile_ocn, scale_domid_ocn )
2160 lon_all(:,:) = lon_all(:,:) * d2r
2161 call read2d( odims(1), 1, odims(1), odims(2), 1, odims(2), &
2162 lat_all(:,:), vars_ocean%get(
"lat"), &
2163 1, nfiles_ocn, fid_ocn, fids_ocn, scale_tile_ocn, scale_domid_ocn )
2164 lat_all(:,:) = lat_all(:,:) * d2r
2176 basename_org, basename_num )
2180 character(len=*),
intent(in) :: basename_org
2181 character(len=*),
intent(in) :: basename_num
2183 character(len=FILE_HLONG) :: basename
2189 log_info(
"ParentOceanOpenNetCDF",*)
'Real Case/Ocean Open'
2191 basename = trim(basename_org) // trim(basename_num)
2193 if ( scale_tile_ocn )
then
2195 do n = 1, nfiles_ocn
2199 aggregate=.false., &
2201 rankid=tile_id_ocn(n) )
2204 fid_ocn = fids_ocn(1)
2208 call file_open(basename, fid_ocn, postfix=
"")
2221 log_info(
"ParentOceanFinalizeNetCDF",*)
'Real Case/Ocean Finalize'
2223 if (
allocated(fids_ocn) )
deallocate( fids_ocn )
2224 if (
allocated(tile_id_ocn) )
deallocate( tile_id_ocn )
2226 call vars_ocean%destroy()
2228 scale_domid_ocn = -1
2237 IA_org, IS_org, IE_org, &
2238 JA_org, JS_org, JE_org, &
2250 integer,
intent(in) :: ia_org, is_org, ie_org
2251 integer,
intent(in) :: ja_org, js_org, je_org
2253 real(rp),
intent(out) :: tw_org(ia_org,ja_org)
2254 real(rp),
intent(out) :: sst_org(ia_org,ja_org)
2256 real(rp),
intent(out) :: z0w_org(ia_org,ja_org)
2257 real(rp),
intent(inout) :: omask_org(ia_org,ja_org)
2259 integer,
intent(in) :: odims(2)
2260 integer,
intent(in) :: it
2266 if ( first_ocn )
then
2267 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
2268 omask_org(:,:), vars_ocean%get(
"lsmask"), &
2269 it, nfiles_ocn, fid_ocn, fids_ocn, scale_tile_ocn, scale_domid_ocn )
2272 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
2273 tw_org(:,:), vars_ocean%get(
"OCEAN_SFC_TEMP"), &
2274 it, nfiles_ocn, fid_ocn, fids_ocn, scale_tile_ocn, scale_domid_ocn )
2275 sst_org(:,:) = tw_org(:,:)
2277 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
2278 z0w_org(:,:), vars_ocean%get(
"OCEAN_SFC_Z0M"), &
2279 it, nfiles_ocn, fid_ocn, fids_ocn, scale_tile_ocn, scale_domid_ocn, &
2281 if ( .not. exist )
then
2285 z0w_org(:,:) = undef
2290 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
2292 it, nfiles_ocn, fid_ocn, fids_ocn, scale_tile_ocn, scale_domid_ocn, &
2294 if ( .not. exist )
then
2302 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
2304 it, nfiles_ocn, fid_ocn, fids_ocn, scale_tile_ocn, scale_domid_ocn, &
2306 if ( .not. exist )
then
2314 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
2316 it, nfiles_ocn, fid_ocn, fids_ocn, scale_tile_ocn, scale_domid_ocn, &
2318 if ( .not. exist )
then
2326 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
2328 it, nfiles_ocn, fid_ocn, fids_ocn, scale_tile_ocn, scale_domid_ocn, &
2330 if ( .not. exist )
then
2338 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
2340 it, nfiles_ocn, fid_ocn, fids_ocn, scale_tile_ocn, scale_domid_ocn, &
2342 if ( .not. exist )
then
2343 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
2345 it, nfiles_ocn, fid_ocn, fids_ocn, scale_tile_ocn, scale_domid_ocn, &
2363 call read2d( ia_org, is_org, ie_org, ja_org, js_org, je_org, &
2365 it, nfiles_ocn, fid_ocn, fids_ocn, scale_tile_ocn, scale_domid_ocn, &
2367 if ( .not. exist )
then
2383 subroutine check_filetype(fid, FILE_TYPE, basename_org, SCALE_tile, subname)
2387 integer,
intent(out) :: fid
2388 character(len=*),
intent(inout) :: FILE_TYPE
2389 logical,
intent(out) :: SCALE_tile
2390 character(len=*),
intent(in) :: basename_org
2391 character(len=*),
intent(in) :: subname
2393 character(len=FILE_HLONG) :: fname
2394 character(len=32) :: att
2398 fname = basename_org
2399 inquire(file=fname, exist=exist)
2400 if ( .not. exist )
then
2401 fname = trim(basename_org)//
".nc"
2402 inquire(file=fname, exist=exist)
2404 if ( .not. exist )
then
2405 fname = trim(basename_org)//
".pe000000.nc"
2406 inquire(file=fname, exist=exist)
2408 if ( .not. exist )
then
2409 log_error(subname,*)
"file is not found: ", trim(basename_org)
2412 call file_open(fname, fid, postfix=
"", allnodes=.false.)
2413 if ( file_type ==
"AUTO" )
then
2414 call file_get_attribute( &
2415 fid,
"global",
"source", &
2418 if ( exist .and. att(:8)==
"SCALE-RM" )
then
2419 file_type =
"SCALE-RM"
2420 log_info(subname,*)
'FILE-TYPE SCALE-RM was detected'
2422 call file_get_attribute( &
2423 fid,
"global",
"TITLE", &
2426 if ( exist .and. index(att,
"WRF") > 0 )
then
2427 file_type =
"WRFARW"
2428 log_info(subname,*)
'FILE-TYPE WRF was detected'
2430 file_type =
"NAMELIST"
2435 scale_tile = .false.
2436 if ( file_type ==
"SCALE-RM" )
then
2437 call file_get_attribute( &
2438 fid,
"global",
"scale_cartesC_prc_num_x", &
2441 if ( exist .and. i > 1 )
then
2443 log_info(subname,*)
'Multi files was detected'
2445 call file_get_attribute( &
2446 fid,
"global",
"scale_cartesC_prc_num_y", &
2449 if ( exist .and. i > 1 )
then
2451 log_info(subname,*)
'Multi files was detected'
2460 KA_org, KS_org, KE_org, &
2461 IA_org, IS_org, IE_org, &
2462 JA_org, JS_org, JE_org, &
2466 nfiles, fid, fids, &
2467 scale_tile, scale_domid, &
2470 file_get_datainfo, &
2475 integer,
intent(in) :: KA_org, KS_org, KE_org
2476 integer,
intent(in) :: IA_org, IS_org, IE_org
2477 integer,
intent(in) :: JA_org, JS_org, JE_org
2479 real(RP),
intent(out),
target :: val(KA_org,IA_org,JA_org)
2481 class(*),
pointer,
intent(in) :: var
2482 integer,
intent(in) :: it
2483 integer,
intent(in) :: nfiles
2484 integer,
intent(in) :: fid, fids(nfiles)
2485 logical,
intent(in) :: scale_tile
2486 integer,
intent(in) :: scale_domid
2488 logical,
intent(out),
optional :: exist
2490 real(RP),
allocatable :: buf3d(:,:,:)
2491 real(RP),
pointer :: work(:,:,:)
2492 real(RP),
allocatable,
target :: work_t(:,:,:)
2495 integer :: tilei, tilej
2497 integer :: cxs, cxe, cys, cye
2498 integer :: pxs, pxe, pys, pye
2500 logical :: transpose
2502 integer :: i0, i1, j0, j1
2503 integer :: kst, ist, jst
2505 integer :: k, i, j, n
2507 if ( .not.
associated(var) )
then
2508 if (
present(exist) )
then
2511 log_error(
"read3d",*)
'data is not found '
2519 if ( var%name ==
"" )
then
2520 if (
present(exist) )
then
2523 log_error(
"read3d",*)
'data is not found '
2529 call file_get_datainfo( fid, var%name, has_tdim=has_tdim, existed=exist_ )
2530 if ( .not. exist_ )
then
2531 if (
present(exist) )
then
2535 log_error(
"read3d",*)
'data is not found: ', trim(var%name)
2540 if ( has_tdim )
then
2546 kmax = ke_org - ks_org + 1
2548 if ( var%zstg )
then
2553 if ( var%xstg )
then
2558 if ( var%ystg )
then
2564 call file_get_shape( fid, var%name, dims(:) )
2565 transpose = dims(1) .ne. kmax+kst
2567 if ( scale_tile )
then
2568 if ( var%xstg .or. var%ystg )
then
2569 allocate( work_t(ka_org,ia_org+ist,ja_org+jst) )
2577 cxs, cxe, cys, cye, &
2578 pxs, pxe, pys, pye, &
2582 i0 = max(is_org - cxs, 0)
2583 i1 = max(cxe - ie_org - ist, 0)
2584 j0 = max(js_org - cys, 0)
2585 j1 = max(cye - je_org - jst, 0)
2586 if ( pxs+i0 > pxe-i1 .or. pys+j0 > pye-j1 ) cycle
2587 if ( transpose )
then
2588 allocate( buf3d(pxs+i0:pxe-i1,pys+j0:pye-j1,ks_org:ke_org+kst) )
2589 call file_read( fids(n), var%name, buf3d(:,:,:), &
2590 step=it_, start=(/pxs+i0,pys+j0,1/), count=(/pxe-pxs+1-i1-i0,pye-pys+1-j1-j0,kmax+kst/) )
2591 if ( var%zstg )
then
2593 do j = j0, pye-pys-j1
2594 do i = i0, pxe-pxs-i1
2595 do k = ks_org, ke_org
2596 work(k,cxs+i-is_org+1,cys+j-js_org+1) = ( buf3d(pxs+i,pys+j,k) + buf3d(pxs+i,pys+j,k+1) ) * 0.5_rp * var%fact + var%offset
2602 do j = j0, pye-pys-j1
2603 do i = i0, pxe-pxs-i1
2604 do k = ks_org, ke_org
2605 work(k,cxs+i-is_org+1,cys+j-js_org+1) = buf3d(pxs+i,pys+j,k) * var%fact + var%offset
2611 if ( var%xstg .and. cxs==2 .and. is_org==1 )
then
2613 do j = j0, pye-pys-j1
2614 do k = ks_org, ke_org
2615 work(k,1,cys+j-js_org+1) = work(k,2,cys+j-js_org+1)
2619 if ( var%ystg .and. cys==2 .and. js_org==1 )
then
2621 do i = i0, pxe-pxs-i1
2622 do k = ks_org, ke_org
2623 work(k,cxs+i-is_org+1,1) = work(k,cxs+i-is_org+1,2)
2628 allocate( buf3d(ks_org:ke_org+kst,pxs+i0:pxe-i1,pys+j0:pye-j1) )
2629 call file_read( fids(n), var%name, buf3d(:,:,:), &
2630 step=it_, start=(/1,pxs+i0,pys+j0/), count=(/kmax+kst,pxe-pxs+1-i1-i0,pye-pys+1-j1-j0/) )
2631 if ( var%zstg )
then
2633 do j = j0, pye-pys-j1
2634 do i = i0, pxe-pxs-i1
2635 do k = ks_org, ke_org
2636 work(k,cxs+i-is_org+1,cys+j-js_org+1) = ( buf3d(k,pxs+i,pys+j) + buf3d(k+1,pxs+i,pys+j) ) * 0.5_rp * var%fact + var%offset
2642 do j = j0, pye-pys-j1
2643 do i = i0, pxe-pxs-i1
2644 do k = ks_org, ke_org
2645 work(k,cxs+i-is_org+1,cys+j-js_org+1) = buf3d(k,pxs+i,pys+j) * var%fact + var%offset
2653 if ( var%xstg )
then
2657 do k = ks_org, ke_org
2658 val(k,i,j) = ( work(k,i,j) + work(k,i+1,j) ) * 0.5_rp
2662 else if ( var%ystg )
then
2666 do k = ks_org, ke_org
2667 val(k,i,j) = ( work(k,i,j) + work(k,i,j+1) ) * 0.5_rp
2672 if ( var%xstg .or. var%ystg )
then
2673 deallocate( work_t )
2677 if ( transpose )
then
2678 allocate( buf3d(is_org:ie_org+ist,js_org:je_org+jst,ks_org:ke_org+kst) )
2683 start=(/is_org,js_org,1/), &
2684 count=(/ia_org+ist,ja_org+jst,kmax+kst/))
2685 if ( var%zstg )
then
2689 do k = ks_org, ke_org
2690 val(k,i,j) = ( buf3d(i+is_org-1,j+js_org-1,k) + buf3d(i+is_org-1,j+js_org-1,k+1) ) * 0.5_rp * var%fact + var%offset
2694 else if ( var%xstg )
then
2698 do k = ks_org, ke_org
2699 val(k,i,j) = ( buf3d(i+is_org-1,j+js_org-1,k) + buf3d(i+is_org,j+js_org-1,k) ) * 0.5_rp * var%fact + var%offset
2703 else if ( var%ystg )
then
2707 do k = ks_org, ke_org
2708 val(k,i,j) = ( buf3d(i+is_org-1,j+js_org-1,k) + buf3d(i+is_org-1,j+js_org,k) ) * 0.5_rp * var%fact + var%offset
2716 do k = ks_org, ke_org
2717 val(k,i,j) = buf3d(i+is_org-1,j+js_org-1,k) * var%fact + var%offset
2724 allocate( buf3d(ks_org:ke_org+kst,is_org:ie_org+ist,js_org:je_org+jst) )
2729 start=(/1,is_org,js_org/), &
2730 count=(/kmax+kst,ia_org+ist,ja_org+jst/) )
2731 if ( var%zstg )
then
2735 do k = ks_org, ke_org
2736 val(k,i,j) = ( buf3d(k,i+is_org-1,j+js_org-1) + buf3d(k+1,i+is_org-1,j+js_org-1) ) * 0.5_rp * var%fact + var%offset
2740 else if ( var%xstg )
then
2744 do k = ks_org, ke_org
2745 val(k,i,j) = ( buf3d(k,i+is_org-1,j+js_org-1) + buf3d(k,i+is_org,j+js_org-1) ) * 0.5_rp * var%fact + var%offset
2749 else if ( var%ystg )
then
2753 do k = ks_org, ke_org
2754 val(k,i,j) = ( buf3d(k,i+is_org-1,j+js_org-1) + buf3d(k,i+is_org-1,j+js_org) ) * 0.5_rp * var%fact + var%offset
2762 do k = ks_org, ke_org
2763 val(k,i,j) = buf3d(k,i+is_org-1,j+js_org-1) * var%fact + var%offset
2772 if (
present(exist) ) exist = .true.
2779 IA_org, IS_org, IE_org, &
2780 JA_org, JS_org, JE_org, &
2784 nfiles, fid, fids, &
2785 scale_tile, scale_domid, &
2788 file_get_datainfo, &
2793 integer,
intent(in) :: IA_org, IS_org, IE_org
2794 integer,
intent(in) :: JA_org, JS_org, JE_org
2796 real(RP),
intent(out),
target :: val(IA_org,JA_org)
2798 class(*),
pointer,
intent(in) :: var
2799 integer,
intent(in) :: it
2800 integer,
intent(in) :: nfiles
2801 integer,
intent(in) :: fid, fids(nfiles)
2802 logical,
intent(in) :: scale_tile
2803 integer,
intent(in) :: scale_domid
2805 logical,
intent(out),
optional :: exist
2807 real(RP),
allocatable :: buf2d(:,:)
2808 real(RP),
pointer :: work(:,:)
2809 real(RP),
allocatable,
target :: work_t(:,:)
2811 integer :: tilei, tilej
2812 integer :: cxs, cxe, cys, cye
2813 integer :: pxs, pxe, pys, pye
2817 integer :: i0, i1, j0, j1
2825 if ( .not.
associated(var) )
then
2826 if (
present(exist) )
then
2829 log_error(
"read2d",*)
'data is not found '
2837 if ( var%name ==
"" )
then
2838 if (
present(exist) )
then
2841 log_error(
"read2d",*)
'data is not found '
2847 call file_get_datainfo( fid, var%name, has_tdim=has_tdim, existed=exist_ )
2848 if ( .not. exist_ )
then
2849 if (
present(exist) )
then
2853 log_error(
"read2d",*)
'data is not found: ', trim(var%name)
2858 if ( has_tdim )
then
2864 if ( var%xstg )
then
2869 if ( var%ystg )
then
2875 if ( scale_domid > 0 )
then
2876 if ( var%xstg .or. var%ystg )
then
2877 allocate( work_t(ia_org+ist,ja_org+jst) )
2885 cxs, cxe, cys, cye, &
2886 pxs, pxe, pys, pye, &
2890 i0 = max(is_org - cxs, 0)
2891 i1 = max(cxe - ie_org - ist, 0)
2892 j0 = max(js_org - cys, 0)
2893 j1 = max(cye - je_org - jst, 0)
2894 if ( pxs+i0 > pxe-i1 .or. pys+j0 > pye-j1 ) cycle
2895 allocate( buf2d(pxs+i0:pxe-i1,pys+j0:pye-j1) )
2896 call file_read( fids(n), var%name, buf2d(:,:), &
2897 step=it_, start=(/pxs+i0,pys+j0/), count=(/pxe-pxs+1-i1-i0,pye-pys+1-j1-j0/) )
2899 do j = j0, pye-pys-j1
2900 do i = i0, pxe-pxs-i1
2901 work(cxs+i-is_org+1,cys+j-js_org+1) = buf2d(pxs+i,pys+j) * var%fact + var%offset
2905 if ( var%xstg .and. cxs==2 .and. is_org==1 )
then
2907 do j = j0, pye-pys-j1
2908 work(1,cys+j-js_org+1) = work(2,cys+j-js_org+1)
2911 if ( var%ystg .and. cys==2 .and. js_org==1 )
then
2913 do i = i0, pxe-pxs-i1
2914 work(cxs+i-is_org+1,1) = work(cxs+i-is_org+1,2)
2918 if ( var%xstg )
then
2922 val(i,j) = ( work(i,j) + work(i+1,j) ) * 0.5_rp
2925 else if ( var%ystg )
then
2929 val(i,j) = ( work(i,j) + work(i,j+1) ) * 0.5_rp
2933 if ( var%xstg .or. var%ystg )
then
2934 deallocate( work_t )
2938 if ( var%xstg .or. var%ystg )
then
2939 allocate( work_t(is_org:ie_org+ist,js_org:je_org+jst) )
2948 start=(/is_org,js_org/), &
2949 count=(/ia_org+ist,ja_org+jst/) )
2950 if ( var%xstg )
then
2954 val(i,j) = ( work(i,j) + work(i+1,j) ) * 0.5_rp * var%fact + var%offset
2957 else if ( var%ystg )
then
2961 val(i,j) = ( work(i,j) + work(i,j+1) ) * 0.5_rp * var%fact + var%offset
2964 else if ( var%fact .ne. 1.0_rp .or. var%offset .ne. 0.0_rp )
then
2968 val(i,j) = val(i,j) * var%fact + var%offset
2972 if ( var%xstg .or. var%ystg )
then
2973 deallocate( work_t )
2978 if (
present(exist) ) exist = .true.
2992 file_get_datainfo, &
2994 integer,
intent(in) :: KA_org
2996 real(RP),
intent(out) :: val(KA_org)
2998 class(*),
pointer,
intent(in) :: var
2999 integer,
intent(in) :: it
3000 integer,
intent(in) :: fid
3002 logical,
intent(out),
optional :: exist
3009 if ( .not.
associated(var) )
then
3010 if (
present(exist) )
then
3013 log_error(
"read1d",*)
'data is not found '
3021 if ( var%name ==
"" )
then
3022 if (
present(exist) )
then
3025 log_error(
"read1d",*)
'data is not found '
3031 call file_get_datainfo( fid, var%name, has_tdim=has_tdim, existed=exist_ )
3032 if ( .not. exist_ )
then
3033 if (
present(exist) )
then
3037 log_error(
"read1d",*)
'data is not found: ', trim(var%name)
3042 if ( has_tdim )
then
3048 call file_read( fid, var%name, val(:), step=it_ )
3049 if ( var%fact .ne. 1.0_rp .or. var%offset .ne. 0.0_rp )
then
3050 val(:) = val(:) * var%fact + var%offset
3053 if (
present(exist) ) exist = .true.