43 use fv_mp_nlm_mod,
only: is_master, switch_current_atm, mp_reduce_min, mp_reduce_max
55 use mpp_mod,
only:
mpp_send,
mpp_recv, mpp_sync_self, mpp_set_current_pelist, mpp_get_current_pelist, mpp_npes, mpp_pe, mpp_sync
56 use mpp_domains_mod,
only: center, corner, north, east, mpp_get_c2f_index, west, south
93 subroutine fv_restart(fv_domain, Atm, dt_atmos, seconds, days, cold_start, grid_type, grids_on_this_pe)
96 real,
intent(in) :: dt_atmos
97 integer,
intent(out) :: seconds
98 integer,
intent(out) :: days
99 logical,
intent(inout) :: cold_start
101 logical,
intent(INOUT) :: grids_on_this_pe(:)
104 integer :: i, j, k, n, ntileme, nt, iq
105 integer :: isc, iec, jsc, jec, npz, npz_rst, ncnst, ntprog, ntdiag
106 integer :: isd, ied, jsd, jed
107 integer isd_p, ied_p, jsd_p, jed_p, isc_p, iec_p, jsc_p, jec_p, isg, ieg, jsg,jeg, npx_p, npy_p
108 real,
allocatable :: g_dat(:,:,:)
111 real,
allocatable :: dz1(:)
112 real rgrav, f00, ztop, pertn
114 logical :: cold_start_grids(
size(atm))
115 character(len=128):: tname, errstring, fname, tracer_name
116 character(len=120):: fname_ne, fname_sw
117 character(len=3) :: gn
126 ntileme =
size(atm(:))
128 cold_start_grids(:) = cold_start
131 if (is_master())
then 132 print*,
'FV_RESTART: ', n, cold_start_grids(n)
135 if (atm(n)%neststruct%nested)
then 136 write(fname,
'(A, I2.2, A)')
'INPUT/fv_core.res.nest', atm(n)%grid_number,
'.nc' 137 write(fname_ne,
'(A, I2.2, A)')
'INPUT/fv_BC_ne.res.nest', atm(n)%grid_number,
'.nc' 138 write(fname_sw,
'(A, I2.2, A)')
'INPUT/fv_BC_sw.res.nest', atm(n)%grid_number,
'.nc' 139 if (atm(n)%flagstruct%external_ic)
then 140 if (is_master()) print*,
'External IC set on grid', atm(n)%grid_number,
', re-initializing grid' 141 cold_start_grids(n) = .true.
142 atm(n)%flagstruct%warm_start = .false.
144 if (is_master()) print*,
'Searching for nested grid restart file ', trim(fname)
145 cold_start_grids(n) = .not. file_exist(fname, atm(n)%domain)
146 atm(n)%flagstruct%warm_start = file_exist(fname, atm(n)%domain)
150 if (.not. grids_on_this_pe(n))
then 157 if (atm(n)%neststruct%nested)
then 158 if (cold_start_grids(n))
then 160 if (atm(n)%flagstruct%nggps_ic)
then 163 call nested_grid_bc(atm(n)%ps, atm(n)%parent_grid%ps, atm(n)%neststruct%nest_domain, &
164 atm(n)%neststruct%ind_h, atm(n)%neststruct%wt_h, 0, 0, &
165 atm(n)%npx, atm(n)%npy,atm(n)%bd, isg, ieg, jsg, jeg, proc_in=.false.)
173 if (is_master()) print*,
'Searching for nested grid BC files ', trim(fname_ne),
' ', trim(fname_sw)
176 if (file_exist(fname_ne, atm(n)%domain) .and. file_exist(fname_sw, atm(n)%domain))
then 178 if ( is_master() )
write(*,*)
'BC files not found, re-generating nested grid boundary conditions' 181 atm(n)%neststruct%first_step = .true.
185 if (.not. atm(n)%flagstruct%hydrostatic .and. atm(n)%flagstruct%make_nh .and. &
186 (.not. atm(n)%flagstruct%nggps_ic .and. .not. atm(n)%flagstruct%ecmwf_ic) )
then 187 call nested_grid_bc(atm(n)%delz, atm(n)%parent_grid%delz, atm(n)%neststruct%nest_domain, &
188 atm(n)%neststruct%ind_h, atm(n)%neststruct%wt_h, 0, 0, &
189 atm(n)%npx, atm(n)%npy, npz, atm(n)%bd, isg, ieg, jsg, jeg, proc_in=.false.)
190 call nested_grid_bc(atm(n)%w, atm(n)%parent_grid%w, atm(n)%neststruct%nest_domain, &
191 atm(n)%neststruct%ind_h, atm(n)%neststruct%wt_h, 0, 0, &
192 atm(n)%npx, atm(n)%npy, npz, atm(n)%bd, isg, ieg, jsg, jeg, proc_in=.false.)
202 call switch_current_atm(atm(n))
205 npz_rst = atm(1)%flagstruct%npz_rst
210 if( .not.cold_start_grids(n) .and. (.not. atm(n)%flagstruct%external_ic) )
then 213 if ( npz_rst /= 0 .and. npz_rst /= npz )
then 215 if( is_master() )
then 217 write(*,*)
'***** Important Note from FV core ********************' 218 write(*,*)
'Remapping dynamic IC from', npz_rst,
'levels to ', npz,
'levels' 219 write(*,*)
'***** End Note from FV core **************************' 223 if( is_master() )
write(*,*)
'Done remapping dynamical IC' 225 if( is_master() )
write(*,*)
'Warm starting, calling fv_io_restart' 233 if (atm(n)%neststruct%nested)
then 236 if (cold_start_grids(n))
then 237 if (atm(n)%parent_grid%flagstruct%n_zs_filter > 0 .or. atm(n)%flagstruct%nggps_ic)
call fill_nested_grid_topo_halo(atm(n), .true.)
239 if (atm(n)%flagstruct%external_ic .and. atm(n)%flagstruct%nggps_ic)
then 241 call nested_grid_bc(atm(n)%ps, atm(n)%parent_grid%ps, atm(n)%neststruct%nest_domain, &
242 atm(n)%neststruct%ind_h, atm(n)%neststruct%wt_h, 0, 0, &
243 atm(n)%npx, atm(n)%npy,atm(n)%bd, isg, ieg, jsg, jeg, proc_in=.true.)
246 if ( atm(n)%flagstruct%external_ic )
then 247 if( is_master() )
write(*,*)
'Calling get_external_ic' 249 if( is_master() )
write(*,*)
'IC generated from the specified external source' 252 seconds = 0; days = 0
263 if( is_master() )
write(*,*)
'in fv_restart ncnst=', ncnst
264 isc = atm(n)%bd%isc; iec = atm(n)%bd%iec; jsc = atm(n)%bd%jsc; jec = atm(n)%bd%jec
267 if(.not.cold_start_grids(n))
then 268 atm(n)%neststruct%first_step = .false.
269 if (atm(n)%neststruct%nested)
then 270 if ( npz_rst /= 0 .and. npz_rst /= npz )
then 274 if (is_master()) print*,
'Searching for nested grid BC files ', trim(fname_ne),
' ', trim(fname_sw)
275 if (file_exist(fname_ne, atm(n)%domain) .and. file_exist(fname_sw, atm(n)%domain))
then 278 if ( is_master() )
write(*,*)
'BC files not found, re-generating nested grid boundary conditions' 281 atm(n)%neststruct%first_step = .true.
284 call mpp_update_domains(atm(n)%u, atm(n)%v, atm(n)%domain, gridtype=dgrid_ne, complete=.true.)
288 if ( atm(n)%flagstruct%mountain )
then 292 if ( atm(n)%flagstruct%n_zs_filter > 0 )
then 293 if ( atm(n)%flagstruct%nord_zs_filter == 2 )
then 295 atm(n)%gridstruct%area_64, atm(n)%gridstruct%dx, atm(n)%gridstruct%dy, &
296 atm(n)%gridstruct%dxc, atm(n)%gridstruct%dyc, atm(n)%gridstruct%sin_sg, &
297 atm(n)%flagstruct%n_zs_filter,
cnst_0p20*atm(n)%gridstruct%da_min, &
298 .false., oro_g, atm(n)%neststruct%nested, atm(n)%domain, atm(n)%bd)
299 if ( is_master() )
write(*,*)
'Warning !!! del-2 terrain filter has been applied ', &
300 atm(n)%flagstruct%n_zs_filter,
' times' 301 else if( atm(n)%flagstruct%nord_zs_filter == 4 )
then 302 call del4_cubed_sphere(atm(n)%npx, atm(n)%npy, atm(n)%phis, atm(n)%gridstruct%area_64, &
303 atm(n)%gridstruct%dx, atm(n)%gridstruct%dy, &
304 atm(n)%gridstruct%dxc, atm(n)%gridstruct%dyc, atm(n)%gridstruct%sin_sg, &
305 atm(n)%flagstruct%n_zs_filter, .false., oro_g, atm(n)%neststruct%nested, &
306 atm(n)%domain, atm(n)%bd)
307 if ( is_master() )
write(*,*)
'Warning !!! del-4 terrain filter has been applied ', &
308 atm(n)%flagstruct%n_zs_filter,
' times' 315 if( is_master() )
write(*,*)
'phis set to zero' 322 if ( .not.atm(n)%flagstruct%hybrid_z )
then 323 if(atm(n)%ptop/=atm(n)%ak(1))
call mpp_error(fatal,
'FV restart: ptop not equal Atm(n)%ak(1)')
325 atm(n)%ptop = atm(n)%ak(1); atm(n)%ks = 0
328 atm(n)%delp, atm(n)%delz, atm(n)%pt, atm(n)%ps, atm(n)%pe, atm(n)%peln, &
329 atm(n)%pk, atm(n)%pkz,
kappa, atm(n)%q, atm(n)%ng, &
330 ncnst, atm(n)%gridstruct%area_64, atm(n)%flagstruct%dry_mass, &
331 atm(n)%flagstruct%adjust_dry_mass, atm(n)%flagstruct%mountain, &
332 atm(n)%flagstruct%moist_phys, atm(n)%flagstruct%hydrostatic, &
333 atm(n)%flagstruct%nwat, atm(n)%domain, atm(n)%flagstruct%make_nh)
341 atm(n)%gridstruct%fc(i,j) = 2.*
omega*( -cos(atm(n)%gridstruct%grid(i,j,1))*cos(atm(n)%gridstruct%grid(i,j,2))*sin(
alpha) + &
342 sin(atm(n)%gridstruct%grid(i,j,2))*cos(
alpha) )
347 atm(n)%gridstruct%f0(i,j) = 2.*
omega*( -cos(atm(n)%gridstruct%agrid(i,j,1))*cos(atm(n)%gridstruct%agrid(i,j,2))*sin(
alpha) + &
348 sin(atm(n)%gridstruct%agrid(i,j,2))*cos(
alpha) )
352 f00 = 2.*
omega*sin(atm(n)%flagstruct%deglat/180.*
pi)
355 atm(n)%gridstruct%fc(i,j) = f00
360 atm(n)%gridstruct%f0(i,j) = f00
365 if ( atm(n)%flagstruct%warm_start )
then 366 call mpp_error(fatal,
'FV restart files not found; set warm_start = .F. if cold_start is desired.')
369 if ( atm(n)%flagstruct%make_hybrid_z )
then 372 hybrid = atm(n)%flagstruct%hybrid_z
375 if ( .not. atm(n)%flagstruct%external_ic )
then 376 call init_case(atm(n)%u,atm(n)%v,atm(n)%w,atm(n)%pt,atm(n)%delp,atm(n)%q, &
377 atm(n)%phis, atm(n)%ps,atm(n)%pe, atm(n)%peln,atm(n)%pk,atm(n)%pkz, &
378 atm(n)%uc,atm(n)%vc, atm(n)%ua,atm(n)%va, &
379 atm(n)%ak, atm(n)%bk, atm(n)%gridstruct, atm(n)%flagstruct,&
380 atm(n)%npx, atm(n)%npy, npz, atm(n)%ng, &
381 ncnst, atm(n)%flagstruct%nwat, &
382 atm(n)%flagstruct%ndims, atm(n)%flagstruct%ntiles, &
383 atm(n)%flagstruct%dry_mass, &
384 atm(n)%flagstruct%mountain, &
385 atm(n)%flagstruct%moist_phys, atm(n)%flagstruct%hydrostatic, &
386 hybrid, atm(n)%delz, atm(n)%ze0, &
387 atm(n)%flagstruct%adiabatic, atm(n)%ks, atm(n)%neststruct%npx_global, &
388 atm(n)%ptop, atm(n)%domain, atm(n)%tile, atm(n)%bd)
392 atm(n)%delp,atm(n)%q,atm(n)%phis, atm(n)%ps,atm(n)%pe, &
393 atm(n)%peln,atm(n)%pk,atm(n)%pkz, &
394 atm(n)%uc,atm(n)%vc, atm(n)%ua,atm(n)%va, &
395 atm(n)%ak, atm(n)%bk, &
396 atm(n)%gridstruct, atm(n)%flagstruct, &
397 atm(n)%npx, atm(n)%npy, npz, atm(n)%ng, &
398 ncnst, atm(n)%flagstruct%nwat, &
399 atm(n)%flagstruct%ndims, atm(n)%flagstruct%ntiles, &
400 atm(n)%flagstruct%dry_mass, atm(n)%flagstruct%mountain, &
401 atm(n)%flagstruct%moist_phys, atm(n)%flagstruct%hydrostatic, &
402 hybrid, atm(n)%delz, atm(n)%ze0, atm(n)%ks, atm(n)%ptop, &
403 atm(n)%domain, atm(n)%tile, atm(n)%bd)
404 if( is_master() )
write(*,*)
'Doubly Periodic IC generated' 406 call init_latlon(atm(n)%u,atm(n)%v,atm(n)%pt,atm(n)%delp,atm(n)%q,&
407 atm(n)%phis, atm(n)%ps,atm(n)%pe, &
408 atm(n)%peln,atm(n)%pk,atm(n)%pkz, &
409 atm(n)%uc,atm(n)%vc, atm(n)%ua,atm(n)%va, &
410 atm(n)%ak, atm(n)%bk, atm(n)%gridstruct, &
411 atm(n)%npx, atm(n)%npy, npz, atm(n)%ng, ncnst, &
412 atm(n)%flagstruct%ndims, atm(n)%flagstruct%ntiles, &
413 atm(n)%flagstruct%dry_mass, &
414 atm(n)%flagstruct%mountain, &
415 atm(n)%flagstruct%moist_phys, hybrid, atm(n)%delz, &
416 atm(n)%ze0, atm(n)%domain, atm(n)%tile)
420 if ( atm(n)%flagstruct%fv_land )
then 423 atm(n)%sgh(i,j) = sgh_g(i,j)
424 atm(n)%oro(i,j) = oro_g(i,j)
436 if (atm(n)%neststruct%nested)
then 438 if (atm(n)%flagstruct%external_ic .and. .not. atm(n)%flagstruct%nggps_ic .and.
grid_type < 4 )
then 445 if ( (.not.atm(n)%flagstruct%hydrostatic) .and. atm(n)%flagstruct%make_nh .and. atm(n)%neststruct%nested)
then 446 call nested_grid_bc(atm(n)%delz, atm(n)%parent_grid%delz, atm(n)%neststruct%nest_domain, &
447 atm(n)%neststruct%ind_h, atm(n)%neststruct%wt_h, 0, 0, &
448 atm(n)%npx, atm(n)%npy, npz, atm(n)%bd, isg, ieg, jsg, jeg, proc_in=.true.)
449 call nested_grid_bc(atm(n)%w, atm(n)%parent_grid%w, atm(n)%neststruct%nest_domain, &
450 atm(n)%neststruct%ind_h, atm(n)%neststruct%wt_h, 0, 0, &
451 atm(n)%npx, atm(n)%npy, npz, atm(n)%bd, isg, ieg, jsg, jeg, proc_in=.true.)
459 if (atm(n)%neststruct%nested .and. atm(n)%flagstruct%external_ic .and. &
460 atm(n)%flagstruct%grid_type < 4 .and. cold_start_grids(n))
then 466 if (.not. grids_on_this_pe(n)) cycle
473 ntprog =
size(atm(n)%q,4)
474 ntdiag =
size(atm(n)%qdiag,4)
475 isc = atm(n)%bd%isc; iec = atm(n)%bd%iec; jsc = atm(n)%bd%jsc; jec = atm(n)%bd%jec
480 if ( atm(n)%flagstruct%hybrid_z )
then 481 if ( atm(n)%flagstruct%make_hybrid_z )
then 482 allocate ( dz1(npz) )
489 call set_hybrid_z(isc, iec, jsc, jec, atm(n)%ng, npz, ztop, dz1, rgrav, &
490 atm(n)%phis, atm(n)%ze0)
499 if (atm(n)%flagstruct%add_noise > 0.)
then 500 write(errstring,
'(A, E16.9)')
"Adding thermal noise of amplitude ", atm(n)%flagstruct%add_noise
508 call random_number(pertn)
509 atm(n)%pt(i,j,k) = atm(n)%pt(i,j,k) + pertn*atm(n)%flagstruct%add_noise
511 sumpertn = sumpertn + pertn*atm(n)%flagstruct%add_noise ** 2
518 write(errstring,
'(A, E16.9)')
"RMS added noise: ", sqrt(sumpertn/npts)
522 if (atm(n)%grid_number > 1)
then 523 write(gn,
'(A2, I1)')
" g", atm(n)%grid_number
530 write(unit,*)
'fv_restart u ', trim(gn),
' = ',
mpp_chksum(atm(n)%u(isc:iec,jsc:jec,:))
531 write(unit,*)
'fv_restart v ', trim(gn),
' = ',
mpp_chksum(atm(n)%v(isc:iec,jsc:jec,:))
532 if ( .not.atm(n)%flagstruct%hydrostatic ) &
533 write(unit,*)
'fv_restart w ', trim(gn),
' = ',
mpp_chksum(atm(n)%w(isc:iec,jsc:jec,:))
534 write(unit,*)
'fv_restart delp', trim(gn),
' = ',
mpp_chksum(atm(n)%delp(isc:iec,jsc:jec,:))
535 write(unit,*)
'fv_restart phis', trim(gn),
' = ',
mpp_chksum(atm(n)%phis(isc:iec,jsc:jec))
538 call prt_maxmin(
'H ', atm(n)%delp, isc, iec, jsc, jec, atm(n)%ng, 1, rgrav)
540 write(unit,*)
'fv_restart pt ', trim(gn),
' = ',
mpp_chksum(atm(n)%pt(isc:iec,jsc:jec,:))
542 write(unit,*)
'fv_restart q(prog) nq ', trim(gn),
' =',ntprog,
mpp_chksum(atm(n)%q(isc:iec,jsc:jec,:,:))
544 write(unit,*)
'fv_restart q(diag) nq ', trim(gn),
' =',ntdiag,
mpp_chksum(atm(n)%qdiag(isc:iec,jsc:jec,:,:))
545 do iq=1,
min(17, ntprog)
546 call get_tracer_names(
model_atmos, iq, tracer_name)
547 write(unit,*)
'fv_restart '//trim(tracer_name)//
' = ',
mpp_chksum(atm(n)%q(isc:iec,jsc:jec,:,iq))
552 call pmaxmn_g(
'ZS', atm(n)%phis, isc, iec, jsc, jec, 1, rgrav, atm(n)%gridstruct%area_64, atm(n)%domain)
553 call pmaxmn_g(
'PS', atm(n)%ps, isc, iec, jsc, jec, 1, 0.01, atm(n)%gridstruct%area_64, atm(n)%domain)
554 call pmaxmn_g(
'T ', atm(n)%pt, isc, iec, jsc, jec, npz, 1., atm(n)%gridstruct%area_64, atm(n)%domain)
559 call pmaxmn_g(trim(tname), atm(n)%q(isd:ied,jsd:jed,1:npz,i:i), isc, iec, jsc, jec, npz, &
560 1., atm(n)%gridstruct%area_64, atm(n)%domain)
563 call prt_maxmin(
'U ', atm(n)%u(isc:iec,jsc:jec,1:npz), isc, iec, jsc, jec, 0, npz, 1.)
564 call prt_maxmin(
'V ', atm(n)%v(isc:iec,jsc:jec,1:npz), isc, iec, jsc, jec, 0, npz, 1.)
566 if ( (.not.atm(n)%flagstruct%hydrostatic) .and. atm(n)%flagstruct%make_nh )
then 567 call mpp_error(note,
" Initializing w to 0")
569 if ( .not.atm(n)%flagstruct%hybrid_z )
then 570 call mpp_error(note,
" Initializing delz from hydrostatic state")
574 atm(n)%delz(i,j,k) = (
rdgas*rgrav)*atm(n)%pt(i,j,k)*(atm(n)%peln(i,k,j)-atm(n)%peln(i,k+1,j))
581 if ( .not.atm(n)%flagstruct%hydrostatic ) &
582 call pmaxmn_g(
'W ', atm(n)%w, isc, iec, jsc, jec, npz, 1., atm(n)%gridstruct%area_64, atm(n)%domain)
584 if (is_master())
write(unit,*)
589 if ( .not. atm(n)%flagstruct%srf_init )
then 592 atm(n)%npx, atm(n)%npy, npz, 1, &
593 atm(n)%gridstruct%grid_type, atm(n)%domain, &
594 atm(n)%gridstruct%nested, atm(n)%flagstruct%c2l_ord, atm(n)%bd)
597 atm(n)%u_srf(i,j) = atm(n)%ua(i,j,npz)
598 atm(n)%v_srf(i,j) = atm(n)%va(i,j,npz)
601 atm(n)%flagstruct%srf_init = .true.
617 logical,
INTENT(IN),
OPTIONAL :: proc_in
618 real,
allocatable :: g_dat(:,:,:), g_dat2(:,:,:)
619 real,
allocatable :: pt_coarse(:,:,:)
620 integer i,j,k,nq, sphum, ncnst, istart, iend, npz, nwat
621 integer isc, iec, jsc, jec, isd, ied, jsd, jed, is, ie, js, je
622 integer isd_p, ied_p, jsd_p, jed_p, isc_p, iec_p, jsc_p, jec_p, isg, ieg, jsg,jeg, npx_p, npy_p
625 integer :: liq_wat, ice_wat, rainwat, snowwat, graupel
626 real :: qv, dp1, q_liq, q_sol, q_con, cvm, cappa, dp, pt, dz, pkz, rdg
628 if (
PRESENT(proc_in))
then 639 isc = atm%bd%isc; iec = atm%bd%iec; jsc = atm%bd%jsc; jec = atm%bd%jec
640 is = atm%bd%is ; ie = atm%bd%ie ; js = atm%bd%js ; je = atm%bd%je
642 nwat = atm%flagstruct%nwat
663 isd_p, ied_p, jsd_p, jed_p )
665 isc_p, iec_p, jsc_p, jec_p )
667 isg, ieg, jsg, jeg, xsize=npx_p, ysize=npy_p)
669 call nested_grid_bc(atm%delp, atm%parent_grid%delp, atm%neststruct%nest_domain, &
670 atm%neststruct%ind_h, atm%neststruct%wt_h, 0, 0, &
671 atm%npx, atm%npy, npz, atm%bd, isg, ieg, jsg, jeg, proc_in=process)
674 atm%parent_grid%q(:,:,:,nq), atm%neststruct%nest_domain, &
675 atm%neststruct%ind_h, atm%neststruct%wt_h, 0, 0, &
676 atm%npx, atm%npy, npz, atm%bd, isg, ieg, jsg, jeg, proc_in=process)
680 if (is_master()) print*,
'FILLING NESTED GRID HALO' 682 if (is_master()) print*,
'SENDING DATA TO FILL NESTED GRID HALO' 704 call nested_grid_bc(atm%pt, atm%parent_grid%pt, atm%neststruct%nest_domain, &
705 atm%neststruct%ind_h, atm%neststruct%wt_h, 0, 0, &
706 atm%npx, atm%npy, npz, atm%bd, isg, ieg, jsg, jeg, proc_in=process)
708 if (.not. atm%flagstruct%hydrostatic)
then 712 atm%parent_grid%w(:,:,:), &
713 atm%neststruct%nest_domain, atm%neststruct%ind_h, atm%neststruct%wt_h, 0, 0, &
714 atm%npx, atm%npy, npz, atm%bd, isg, ieg, jsg, jeg, proc_in=process)
719 atm%parent_grid%delz(:,:,:), &
720 atm%neststruct%nest_domain, atm%neststruct%ind_h, atm%neststruct%wt_h, 0, 0, &
721 atm%npx, atm%npy, npz, atm%bd, isg, ieg, jsg, jeg, proc_in=process)
727 if (atm%neststruct%child_proc)
then 729 atm%neststruct%nest_domain, atm%neststruct%ind_u, atm%neststruct%wt_u, 0, 1, &
730 atm%npx, atm%npy, npz, atm%bd, isg, ieg, jsg, jeg, proc_in=process)
732 atm%neststruct%nest_domain, atm%neststruct%ind_v, atm%neststruct%wt_v, 1, 0, &
733 atm%npx, atm%npy, npz, atm%bd, isg, ieg, jsg, jeg, proc_in=process)
736 atm%neststruct%nest_domain, 0, 1)
738 atm%neststruct%nest_domain, 1, 0)
764 type(fv_atmos_type),
intent(INOUT) :: Atm
765 logical,
intent(IN),
OPTIONAL :: proc_in
766 integer :: isg, ieg, jsg, jeg
768 if (.not. atm%neststruct%nested)
return 773 if (is_master()) print*,
' FILLING NESTED GRID HALO WITH INTERPOLATED TERRAIN' 774 call nested_grid_bc(atm%phis, atm%parent_grid%phis, atm%neststruct%nest_domain, &
775 atm%neststruct%ind_h, atm%neststruct%wt_h, 0, 0, &
776 atm%npx, atm%npy, atm%bd, isg, ieg, jsg, jeg, proc_in=proc_in)
784 type(fv_atmos_type),
intent(INOUT) :: Atm
785 logical,
intent(IN),
OPTIONAL :: proc_in
786 real,
allocatable :: g_dat(:,:,:)
787 integer :: p, sending_proc
788 integer :: isd_p, ied_p, jsd_p, jed_p
789 integer :: isg, ieg, jsg,jeg
794 if (
present(proc_in))
then 805 isd_p, ied_p, jsd_p, jed_p )
807 allocate(g_dat( isg:ieg, jsg:jeg, 1) )
813 if (is_master() .and. .not. atm%flagstruct%external_ic ) print*,
' FILLING NESTED GRID INTERIOR WITH INTERPOLATED TERRAIN' 815 sending_proc = atm%parent_grid%pelist(1) + (atm%neststruct%parent_tile-1)*atm%parent_grid%npes_per_tile
816 if (atm%neststruct%parent_proc .and. atm%neststruct%parent_tile == atm%parent_grid%tile)
then 818 atm%parent_grid%domain, &
819 atm%parent_grid%phis(isd_p:ied_p,jsd_p:jed_p), g_dat(isg:,jsg:,1), position=center)
820 if (mpp_pe() == sending_proc)
then 821 do p=1,
size(atm%pelist)
822 call mpp_send(g_dat,
size(g_dat),atm%pelist(p))
827 if (any(atm%pelist == mpp_pe()))
then 828 call mpp_recv(g_dat,
size(g_dat), sending_proc)
833 atm%neststruct%ind_h, atm%neststruct%wt_h, &
834 0, 0, isg, ieg, jsg, jeg, atm%bd)
845 type(fv_atmos_type),
intent(INOUT) :: Atm(:)
846 logical,
intent(IN),
OPTIONAL :: proc_in
847 real,
allocatable :: g_dat(:,:,:), pt_coarse(:,:,:)
848 integer :: i,j,k,nq, sphum, ncnst, istart, iend, npz
849 integer :: isc, iec, jsc, jec, isd, ied, jsd, jed
850 integer :: isd_p, ied_p, jsd_p, jed_p, isc_p, iec_p, jsc_p, jec_p
851 integer :: isg, ieg, jsg,jeg, npx_p, npy_p
852 integer :: isg_n, ieg_n, jsg_n, jeg_n, npx_n, npy_n
853 real zvir, gh0, p1(2), p2(2), r, r0
855 integer :: p, sending_proc, gid
858 if (
present(proc_in))
then 869 isc = atm(1)%bd%isc; iec = atm(1)%bd%iec; jsc = atm(1)%bd%jsc; jec = atm(1)%bd%jec
874 sending_proc = atm(1)%parent_grid%pelist(1) + (atm(1)%neststruct%parent_tile-1)*atm(1)%parent_grid%npes_per_tile
877 isd_p, ied_p, jsd_p, jed_p )
879 isc_p, iec_p, jsc_p, jec_p )
881 isg, ieg, jsg, jeg, xsize=npx_p, ysize=npy_p)
885 call mpp_error(note,
"FILLING NESTED GRID DATA")
889 call mpp_error(note,
"SENDING TO FILL NESTED GRID DATA")
895 allocate(g_dat( isg:ieg, jsg:jeg, npz) )
901 if (atm(1)%neststruct%parent_proc .and. atm(1)%neststruct%parent_tile == atm(1)%parent_grid%tile)
then 903 atm(1)%parent_grid%domain, &
904 atm(1)%parent_grid%delp(isd_p:ied_p,jsd_p:jed_p,:), g_dat, position=center)
905 if (gid == sending_proc)
then 906 do p=1,
size(atm(1)%pelist)
907 call mpp_send(g_dat,
size(g_dat),atm(1)%pelist(p))
911 if (any(atm(1)%pelist == gid))
then 912 call mpp_recv(g_dat,
size(g_dat), sending_proc)
917 atm(1)%neststruct%ind_h, atm(1)%neststruct%wt_h, &
918 0, 0, isg, ieg, jsg, jeg, npz, atm(1)%bd)
927 if (any(atm(1)%parent_grid%pelist == gid) .and. atm(1)%neststruct%parent_tile == atm(1)%parent_grid%tile)
then 929 atm(1)%parent_grid%domain, &
930 atm(1)%parent_grid%q(isd_p:ied_p,jsd_p:jed_p,:,nq), g_dat, position=center)
931 if (gid == sending_proc)
then 932 do p=1,
size(atm(1)%pelist)
933 call mpp_send(g_dat,
size(g_dat),atm(1)%pelist(p))
937 if (any(atm(1)%pelist == gid))
then 938 call mpp_recv(g_dat,
size(g_dat), sending_proc)
943 atm(1)%neststruct%ind_h, atm(1)%neststruct%wt_h, &
944 0, 0, isg, ieg, jsg, jeg, npz, atm(1)%bd)
959 if (any(atm(1)%parent_grid%pelist == gid) .and. atm(1)%neststruct%parent_tile == atm(1)%parent_grid%tile)
then 961 atm(1)%parent_grid%domain, &
962 atm(1)%parent_grid%pt(isd_p:ied_p,jsd_p:jed_p,:), g_dat, position=center)
963 if (gid == sending_proc)
then 964 do p=1,
size(atm(1)%pelist)
965 call mpp_send(g_dat,
size(g_dat),atm(1)%pelist(p))
969 if (any(atm(1)%pelist == gid))
then 970 call mpp_recv(g_dat,
size(g_dat), sending_proc)
977 atm(1)%neststruct%ind_h, atm(1)%neststruct%wt_h, &
978 0, 0, isg, ieg, jsg, jeg, npz, atm(1)%bd)
983 if ( atm(1)%flagstruct%nwat > 0 )
then 989 if ( atm(1)%parent_grid%flagstruct%adiabatic .or. atm(1)%parent_grid%flagstruct%do_Held_Suarez )
then 997 if (any(atm(1)%parent_grid%pelist == gid) .and. atm(1)%neststruct%parent_tile == atm(1)%parent_grid%tile)
then 999 atm(1)%parent_grid%domain, &
1000 atm(1)%parent_grid%pkz(isc_p:iec_p,jsc_p:jec_p,:), g_dat, position=center)
1001 if (gid == sending_proc)
then 1002 do p=1,
size(atm(1)%pelist)
1003 call mpp_send(g_dat,
size(g_dat),atm(1)%pelist(p))
1007 if (any(atm(1)%pelist == gid))
then 1008 call mpp_recv(g_dat,
size(g_dat), sending_proc)
1015 allocate(pt_coarse(isd:ied,jsd:jed,npz))
1017 atm(1)%neststruct%ind_h, atm(1)%neststruct%wt_h, &
1018 0, 0, isg, ieg, jsg, jeg, npz, atm(1)%bd)
1020 if (atm(1)%bd%is == 1)
then 1022 do j=atm(1)%bd%jsd,atm(1)%bd%jed
1023 do i=atm(1)%bd%isd,0
1024 atm(1)%pt(i,j,k) =
cp_air*atm(1)%pt(i,j,k)/pt_coarse(i,j,k)*(1.+zvir*atm(1)%q(i,j,k,sphum))
1030 if (atm(1)%bd%js == 1)
then 1031 if (atm(1)%bd%is == 1)
then 1032 istart = atm(1)%bd%is
1034 istart = atm(1)%bd%isd
1036 if (atm(1)%bd%ie == atm(1)%npx-1)
then 1039 iend = atm(1)%bd%ied
1043 do j=atm(1)%bd%jsd,0
1045 atm(1)%pt(i,j,k) =
cp_air*atm(1)%pt(i,j,k)/pt_coarse(i,j,k)*(1.+zvir*atm(1)%q(i,j,k,sphum))
1051 if (atm(1)%bd%ie == atm(1)%npx-1)
then 1053 do j=atm(1)%bd%jsd,atm(1)%bd%jed
1054 do i=atm(1)%npx,atm(1)%bd%ied
1055 atm(1)%pt(i,j,k) =
cp_air*atm(1)%pt(i,j,k)/pt_coarse(i,j,k)*(1.+zvir*atm(1)%q(i,j,k,sphum))
1061 if (atm(1)%bd%je == atm(1)%npy-1)
then 1062 if (atm(1)%bd%is == 1)
then 1063 istart = atm(1)%bd%is
1065 istart = atm(1)%bd%isd
1067 if (atm(1)%bd%ie == atm(1)%npx-1)
then 1070 iend = atm(1)%bd%ied
1074 do j=atm(1)%npy,atm(1)%bd%jed
1076 atm(1)%pt(i,j,k) =
cp_air*atm(1)%pt(i,j,k)/pt_coarse(i,j,k)*(1.+zvir*atm(1)%q(i,j,k,sphum))
1082 deallocate(pt_coarse)
1086 if (.not. atm(1)%flagstruct%hydrostatic)
then 1091 if (any(atm(1)%parent_grid%pelist == gid) .and. atm(1)%neststruct%parent_tile == atm(1)%parent_grid%tile)
then 1093 atm(1)%parent_grid%domain, &
1094 atm(1)%parent_grid%delz(isd_p:ied_p,jsd_p:jed_p,:), g_dat, position=center)
1095 if (gid == sending_proc)
then 1096 do p=1,
size(atm(1)%pelist)
1097 call mpp_send(g_dat,
size(g_dat),atm(1)%pelist(p))
1101 if (any(atm(1)%pelist == gid))
then 1102 call mpp_recv(g_dat,
size(g_dat), sending_proc)
1109 atm(1)%neststruct%ind_h, atm(1)%neststruct%wt_h, &
1110 0, 0, isg, ieg, jsg, jeg, npz, atm(1)%bd)
1116 if (any(atm(1)%parent_grid%pelist == gid) .and. atm(1)%neststruct%parent_tile == atm(1)%parent_grid%tile)
then 1118 atm(1)%parent_grid%domain, &
1119 atm(1)%parent_grid%w(isd_p:ied_p,jsd_p:jed_p,:), g_dat, position=center)
1120 if (gid == sending_proc)
then 1121 do p=1,
size(atm(1)%pelist)
1122 call mpp_send(g_dat,
size(g_dat),atm(1)%pelist(p))
1126 if (any(atm(1)%pelist == gid))
then 1127 call mpp_recv(g_dat,
size(g_dat), sending_proc)
1134 atm(1)%neststruct%ind_h, atm(1)%neststruct%wt_h, &
1135 0, 0, isg, ieg, jsg, jeg, npz, atm(1)%bd)
1145 allocate(g_dat( isg:ieg, jsg:jeg+1, npz) )
1150 if (any(atm(1)%parent_grid%pelist == gid) .and. atm(1)%neststruct%parent_tile == atm(1)%parent_grid%tile)
then 1152 atm(1)%parent_grid%domain, &
1153 atm(1)%parent_grid%u(isd_p:ied_p,jsd_p:jed_p+1,:), g_dat, position=north)
1154 if (gid == sending_proc)
then 1155 do p=1,
size(atm(1)%pelist)
1156 call mpp_send(g_dat,
size(g_dat),atm(1)%pelist(p))
1160 if (any(atm(1)%pelist == gid))
then 1161 call mpp_recv(g_dat,
size(g_dat), sending_proc)
1169 atm(1)%neststruct%ind_u, atm(1)%neststruct%wt_u, &
1170 0, 1, isg, ieg, jsg, jeg, npz, atm(1)%bd)
1175 allocate(g_dat( isg:ieg+1, jsg:jeg, npz) )
1180 if (any(atm(1)%parent_grid%pelist == gid) .and. atm(1)%neststruct%parent_tile == atm(1)%parent_grid%tile)
then 1182 atm(1)%parent_grid%domain, &
1183 atm(1)%parent_grid%v(isd_p:ied_p+1,jsd_p:jed_p,:), g_dat, position=east)
1184 if (gid == sending_proc)
then 1185 do p=1,
size(atm(1)%pelist)
1186 call mpp_send(g_dat,
size(g_dat),atm(1)%pelist(p))
1190 if (any(atm(1)%pelist == gid))
then 1191 call mpp_recv(g_dat,
size(g_dat), sending_proc)
1198 atm(1)%neststruct%ind_v, atm(1)%neststruct%wt_v, &
1199 1, 0, isg, ieg, jsg, jeg, npz, atm(1)%bd)
1207 type(fv_atmos_type),
intent(INOUT) :: Atm
1208 logical,
intent(IN),
OPTIONAL :: proc_in
1209 real,
allocatable :: g_dat(:,:,:), pt_coarse(:,:,:)
1210 integer :: i,j,k,nq, sphum, ncnst, istart, iend, npz
1211 integer :: isc, iec, jsc, jec, isd, ied, jsd, jed
1212 integer :: isd_p, ied_p, jsd_p, jed_p, isc_p, iec_p, jsc_p, jec_p
1213 integer :: isg, ieg, jsg,jeg, npx_p, npy_p
1214 integer :: isg_n, ieg_n, jsg_n, jeg_n, npx_n, npy_n
1217 integer :: p , sending_proc
1220 if (
present(proc_in))
then 1231 isc = atm%bd%isc; iec = atm%bd%iec; jsc = atm%bd%jsc; jec = atm%bd%jec
1234 isd_p = atm%parent_grid%bd%isd
1235 ied_p = atm%parent_grid%bd%ied
1236 jsd_p = atm%parent_grid%bd%jsd
1237 jed_p = atm%parent_grid%bd%jed
1238 isc_p = atm%parent_grid%bd%isc
1239 iec_p = atm%parent_grid%bd%iec
1240 jsc_p = atm%parent_grid%bd%jsc
1241 jec_p = atm%parent_grid%bd%jec
1242 sending_proc = atm%parent_grid%pelist(1) + (atm%neststruct%parent_tile-1)*atm%parent_grid%npes_per_tile
1245 isg, ieg, jsg, jeg, xsize=npx_p, ysize=npy_p)
1251 if (atm%neststruct%twowaynest)
then 1252 if (any(atm%parent_grid%pelist == mpp_pe()) .or. atm%neststruct%child_proc)
then 1254 atm%phis, atm%neststruct%nest_domain, &
1255 atm%neststruct%ind_update_h(isd_p:ied_p+1,jsd_p:jed_p+1,:), &
1256 atm%gridstruct%dx, atm%gridstruct%dy, atm%gridstruct%area, &
1257 isd_p, ied_p, jsd_p, jed_p, isd, ied, jsd, jed, &
1258 atm%neststruct%isu, atm%neststruct%ieu, atm%neststruct%jsu, atm%neststruct%jeu, &
1259 atm%npx, atm%npy, 0, 0, &
1260 atm%neststruct%refinement, atm%neststruct%nestupdate, 0, 0, &
1261 atm%neststruct%parent_proc, atm%neststruct%child_proc, atm%parent_grid)
1262 atm%parent_grid%neststruct%parent_of_twoway = .true.
1267 if (atm%neststruct%parent_proc)
call mpp_update_domains(atm%parent_grid%phis, atm%parent_grid%domain)
1289 if (process)
call p_var(npz, isc, iec, jsc, jec, atm%ptop,
ptop_min, atm%delp, &
1290 atm%delz, atm%pt, atm%ps, &
1291 atm%pe, atm%peln, atm%pk, atm%pkz,
kappa, atm%q, &
1292 atm%ng, ncnst, atm%gridstruct%area_64, atm%flagstruct%dry_mass, .false., atm%flagstruct%mountain, &
1293 atm%flagstruct%moist_phys, .true., atm%flagstruct%nwat, atm%domain)
1308 character(len=*),
intent(in) :: timestamp
1309 logical,
intent(IN) :: grids_on_this_pe(:)
1314 if (atm(n)%neststruct%nested .and. grids_on_this_pe(n))
then 1333 logical,
intent(INOUT) :: grids_on_this_pe(:)
1335 integer :: isc, iec, jsc, jec
1336 integer :: iq, n, ntileme, ncnst, ntprog, ntdiag
1337 integer :: isd, ied, jsd, jed, npz
1339 integer :: file_unit
1340 integer,
allocatable :: pelist(:)
1341 character(len=128):: tracer_name
1342 character(len=3):: gn
1345 ntileme =
size(atm(:))
1349 if (.not. grids_on_this_pe(n))
then 1353 call mpp_set_current_pelist(atm(n)%pelist)
1355 isc = atm(n)%bd%isc; iec = atm(n)%bd%iec; jsc = atm(n)%bd%jsc; jec = atm(n)%bd%jec
1362 ncnst = atm(n)%ncnst
1363 ntprog =
size(atm(n)%q,4)
1364 ntdiag =
size(atm(n)%qdiag,4)
1366 if (atm(n)%grid_number > 1)
then 1367 write(gn,
'(A2, I1)')
" g", atm(n)%grid_number
1374 write(unit,*)
'fv_restart_end u ', trim(gn),
' = ',
mpp_chksum(atm(n)%u(isc:iec,jsc:jec,:))
1375 write(unit,*)
'fv_restart_end v ', trim(gn),
' = ',
mpp_chksum(atm(n)%v(isc:iec,jsc:jec,:))
1376 if ( .not. atm(n)%flagstruct%hydrostatic ) &
1377 write(unit,*)
'fv_restart_end w ', trim(gn),
' = ',
mpp_chksum(atm(n)%w(isc:iec,jsc:jec,:))
1378 write(unit,*)
'fv_restart_end delp', trim(gn),
' = ',
mpp_chksum(atm(n)%delp(isc:iec,jsc:jec,:))
1379 write(unit,*)
'fv_restart_end phis', trim(gn),
' = ',
mpp_chksum(atm(n)%phis(isc:iec,jsc:jec))
1381 write(unit,*)
'fv_restart_end pt ', trim(gn),
' = ',
mpp_chksum(atm(n)%pt(isc:iec,jsc:jec,:))
1383 write(unit,*)
'fv_restart_end q(prog) nq ', trim(gn),
' =',ntprog,
mpp_chksum(atm(n)%q(isc:iec,jsc:jec,:,:))
1385 write(unit,*)
'fv_restart_end q(diag) nq ', trim(gn),
' =',ntdiag,
mpp_chksum(atm(n)%qdiag(isc:iec,jsc:jec,:,:))
1386 do iq=1,
min(17, ntprog)
1387 call get_tracer_names(
model_atmos, iq, tracer_name)
1388 write(unit,*)
'fv_restart_end '//trim(tracer_name)// trim(gn),
' = ',
mpp_chksum(atm(n)%q(isc:iec,jsc:jec,:,iq))
1395 call pmaxmn_g(
'ZS', atm(n)%phis, isc, iec, jsc, jec, 1, 1./
grav, atm(n)%gridstruct%area_64, atm(n)%domain)
1396 call pmaxmn_g(
'PS ', atm(n)%ps, isc, iec, jsc, jec, 1, 0.01 , atm(n)%gridstruct%area_64, atm(n)%domain)
1397 call prt_maxmin(
'PS*', atm(n)%ps, isc, iec, jsc, jec, atm(n)%ng, 1, 0.01)
1398 call prt_maxmin(
'U ', atm(n)%u(isd:ied,jsd:jed,1:npz), isc, iec, jsc, jec, atm(n)%ng, npz, 1.)
1399 call prt_maxmin(
'V ', atm(n)%v(isd:ied,jsd:jed,1:npz), isc, iec, jsc, jec, atm(n)%ng, npz, 1.)
1400 if ( .not. atm(n)%flagstruct%hydrostatic ) &
1401 call prt_maxmin(
'W ', atm(n)%w , isc, iec, jsc, jec, atm(n)%ng, npz, 1.)
1402 call prt_maxmin(
'T ', atm(n)%pt, isc, iec, jsc, jec, atm(n)%ng, npz, 1.)
1404 call get_tracer_names (
model_atmos, iq, tracer_name )
1405 call pmaxmn_g(trim(tracer_name), atm(n)%q(isd:ied,jsd:jed,1:npz,iq:iq), isc, iec, jsc, jec, npz, &
1406 1., atm(n)%gridstruct%area_64, atm(n)%domain)
1415 if (atm(n)%neststruct%nested .and. grids_on_this_pe(n))
call fv_io_write_bcs(atm(n))
1421 if( is_master() )
then 1422 write(*,*) steps,
'Mean equivalent Heat flux for this integration period=',atm(1)%idiag%efx_sum/
real(max(1,Atm(1)%idiag%steps)), &
1423 'Mean nesting-related flux for this integration period=',atm(1)%idiag%efx_sum_nest/
real(max(1,Atm(1)%idiag%steps)), &
1424 'Mean mountain torque=',atm(1)%idiag%mtq_sum/
real(
max(1,atm(1)%idiag%steps))
1425 file_unit = get_unit()
1426 open (unit=file_unit, file=
'e_flux.data', form=
'unformatted',status=
'unknown', access=
'sequential')
1428 write(file_unit) atm(1)%idiag%efx(n)
1429 write(file_unit) atm(1)%idiag%mtq(n)
1432 close(unit=file_unit)
1442 isd,ied,jsd,jed, is,ie,js,je, npx,npy, &
1443 grid_type, nested, &
1444 se_corner, sw_corner, ne_corner, nw_corner, &
1445 rsin_u,rsin_v,cosa_s,rsin2 )
1447 logical,
intent(in):: dord4
1448 real,
intent(in) :: u(isd:ied,jsd:jed+1)
1449 real,
intent(in) :: v(isd:ied+1,jsd:jed)
1450 real,
intent(out),
dimension(isd:ied ,jsd:jed ):: ua
1451 real,
intent(out),
dimension(isd:ied ,jsd:jed ):: va
1452 real,
intent(out),
dimension(isd:ied+1,jsd:jed ):: uc
1453 real,
intent(out),
dimension(isd:ied ,jsd:jed+1):: vc
1454 integer,
intent(in) :: isd,ied,jsd,jed, is,ie,js,je, npx,npy,
grid_type 1455 logical,
intent(in) :: nested, se_corner, sw_corner, ne_corner, nw_corner
1456 real,
intent(in) :: rsin_u(isd:ied+1,jsd:jed)
1457 real,
intent(in) :: rsin_v(isd:ied,jsd:jed+1)
1458 real,
intent(in) :: cosa_s(isd:ied,jsd:jed)
1459 real,
intent(in) :: rsin2(isd:ied,jsd:jed)
1462 real,
dimension(isd:ied,jsd:jed):: utmp, vtmp
1463 real,
parameter:: t11=27./28., t12=-13./28., t13=3./7., t14=6./7., t15=3./28.
1464 real,
parameter:: a1 = 0.5625
1465 real,
parameter:: a2 = -0.0625
1466 real,
parameter:: c1 = -2./14.
1467 real,
parameter:: c2 = 11./14.
1468 real,
parameter:: c3 = 5./14.
1469 integer npt, i, j, ifirst, ilast, id
1478 if (
grid_type < 3 .and. .not. nested)
then 1488 utmp(i,j) = a2*(u(i,j-1)+u(i,j+2)) + a1*(u(i,j)+u(i,j+1))
1493 utmp(i,j) = 0.5*(u(i,j)+u(i,j+1))
1495 utmp(i,j) = 0.5*(u(i,j)+u(i,j+1))
1500 vtmp(i,j) = a2*(v(i-1,j)+v(i+2,j)) + a1*(v(i,j)+v(i+1,j))
1503 vtmp(i,j) = 0.5*(v(i,j)+v(i+1,j))
1505 vtmp(i,j) = 0.5*(v(i,j)+v(i+1,j))
1510 ua(i,j) = (utmp(i,j)-vtmp(i,j)*cosa_s(i,j)) * rsin2(i,j)
1511 va(i,j) = (vtmp(i,j)-utmp(i,j)*cosa_s(i,j)) * rsin2(i,j)
1524 do j=
max(npt,js-1),
min(npy-npt,je+1)
1525 do i=
max(npt,isd),
min(npx-npt,ied)
1526 utmp(i,j) = a2*(u(i,j-1)+u(i,j+2)) + a1*(u(i,j)+u(i,j+1))
1529 do j=
max(npt,jsd),
min(npy-npt,jed)
1530 do i=
max(npt,is-1),
min(npx-npt,ie+1)
1531 vtmp(i,j) = a2*(v(i-1,j)+v(i+2,j)) + a1*(v(i,j)+v(i+1,j))
1540 if ( js==1 .or. jsd<npt)
then 1543 utmp(i,j) = 0.5*(u(i,j) + u(i,j+1))
1544 vtmp(i,j) = 0.5*(v(i,j) + v(i+1,j))
1549 if ( (je+1)==npy .or. jed>=(npy-npt))
then 1552 utmp(i,j) = 0.5*(u(i,j) + u(i,j+1))
1553 vtmp(i,j) = 0.5*(v(i,j) + v(i+1,j))
1558 if ( is==1 .or. isd<npt )
then 1559 do j=
max(npt,jsd),
min(npy-npt,jed)
1561 utmp(i,j) = 0.5*(u(i,j) + u(i,j+1))
1562 vtmp(i,j) = 0.5*(v(i,j) + v(i+1,j))
1567 if ( (ie+1)==npx .or. ied>=(npx-npt))
then 1568 do j=
max(npt,jsd),
min(npy-npt,jed)
1570 utmp(i,j) = 0.5*(u(i,j) + u(i,j+1))
1571 vtmp(i,j) = 0.5*(v(i,j) + v(i+1,j))
1577 do j=js-1-id,je+1+id
1578 do i=is-1-id,ie+1+id
1579 ua(i,j) = (utmp(i,j)-vtmp(i,j)*cosa_s(i,j)) * rsin2(i,j)
1580 va(i,j) = (vtmp(i,j)-utmp(i,j)*cosa_s(i,j)) * rsin2(i,j)
1591 if( sw_corner )
then 1593 utmp(i,0) = -vtmp(0,1-i)
1596 if( se_corner )
then 1598 utmp(npx+i,0) = vtmp(npx,i+1)
1601 if( ne_corner )
then 1603 utmp(npx+i,npy) = -vtmp(npx,je-i)
1606 if( nw_corner )
then 1608 utmp(i,npy) = vtmp(0,je+i)
1612 if (
grid_type < 3 .and. .not. nested)
then 1613 ifirst =
max(3, is-1)
1614 ilast =
min(npx-2,ie+2)
1624 uc(i,j) = a1*(utmp(i-1,j)+utmp(i,j))+a2*(utmp(i-2,j)+utmp(i+1,j))
1630 if( is==1 .and. .not. nested )
then 1632 uc(0,j) = c1*utmp(-2,j) + c2*utmp(-1,j) + c3*utmp(0,j)
1633 uc(1,j) = ( t14*(utmp( 0,j)+utmp(1,j)) &
1634 + t12*(utmp(-1,j)+utmp(2,j)) &
1635 + t15*(utmp(-2,j)+utmp(3,j)) )*rsin_u(1,j)
1636 uc(2,j) = c1*utmp(3,j) + c2*utmp(2,j) + c3*utmp(1,j)
1640 if( (ie+1)==npx .and. .not. nested )
then 1642 uc(npx-1,j) = c1*utmp(npx-3,j)+c2*utmp(npx-2,j)+c3*utmp(npx-1,j)
1643 uc(npx,j) = (t14*(utmp(npx-1,j)+utmp(npx,j))+ &
1644 t12*(utmp(npx-2,j)+utmp(npx+1,j)) &
1645 + t15*(utmp(npx-3,j)+utmp(npx+2,j)))*rsin_u(npx,j)
1646 uc(npx+1,j) = c3*utmp(npx,j)+c2*utmp(npx+1,j)+c1*utmp(npx+2,j)
1655 if( sw_corner )
then 1657 vtmp(0,j) = -utmp(1-j,0)
1660 if( nw_corner )
then 1662 vtmp(0,npy+j) = utmp(j+1,npy)
1665 if( se_corner )
then 1667 vtmp(npx,j) = utmp(ie+j,0)
1670 if( ne_corner )
then 1672 vtmp(npx,npy+j) = -utmp(ie-j,npy)
1679 if ( j==1 .and. .not. nested)
then 1681 vc(i,1) = (t14*(vtmp(i, 0)+vtmp(i,1)) &
1682 + t12*(vtmp(i,-1)+vtmp(i,2)) &
1683 + t15*(vtmp(i,-2)+vtmp(i,3)))*rsin_v(i,1)
1685 elseif ( (j==0 .or. j==(npy-1)) .and. .not. nested)
then 1687 vc(i,j) = c1*vtmp(i,j-2) + c2*vtmp(i,j-1) + c3*vtmp(i,j)
1689 elseif ( (j==2 .or. j==(npy+1)) .and. .not. nested)
then 1691 vc(i,j) = c1*vtmp(i,j+1) + c2*vtmp(i,j) + c3*vtmp(i,j-1)
1693 elseif ( j==npy .and. .not. nested)
then 1695 vc(i,npy) = (t14*(vtmp(i,npy-1)+vtmp(i,npy)) &
1696 + t12*(vtmp(i,npy-2)+vtmp(i,npy+1)) &
1697 + t15*(vtmp(i,npy-3)+vtmp(i,npy+2)))*rsin_v(i,npy)
1702 vc(i,j) = a2*(vtmp(i,j-2)+vtmp(i,j+1))+a1*(vtmp(i,j-1)+vtmp(i,j))
1710 vc(i,j) = a2*(vtmp(i,j-2)+vtmp(i,j+1))+a1*(vtmp(i,j-1)+vtmp(i,j))
1717 subroutine d2a_setup(u, v, ua, va, dord4, &
1718 isd,ied,jsd,jed, is,ie,js,je, npx,npy, &
1719 grid_type, nested, &
1722 logical,
intent(in):: dord4
1723 real,
intent(in) :: u(isd:ied,jsd:jed+1)
1724 real,
intent(in) :: v(isd:ied+1,jsd:jed)
1725 real,
intent(out),
dimension(isd:ied ,jsd:jed ):: ua
1726 real,
intent(out),
dimension(isd:ied ,jsd:jed ):: va
1727 integer,
intent(in) :: isd,ied,jsd,jed, is,ie,js,je, npx,npy,
grid_type 1728 real,
intent(in) :: cosa_s(isd:ied,jsd:jed)
1729 real,
intent(in) :: rsin2(isd:ied,jsd:jed)
1730 logical,
intent(in) :: nested
1733 real,
dimension(isd:ied,jsd:jed):: utmp, vtmp
1734 real,
parameter:: t11=27./28., t12=-13./28., t13=3./7., t14=6./7., t15=3./28.
1735 real,
parameter:: a1 = 0.5625
1736 real,
parameter:: a2 = -0.0625
1737 real,
parameter:: c1 = -2./14.
1738 real,
parameter:: c2 = 11./14.
1739 real,
parameter:: c3 = 5./14.
1740 integer npt, i, j, ifirst, ilast, id
1749 if (
grid_type < 3 .and. .not. nested)
then 1759 utmp(i,j) = a2*(u(i,j-1)+u(i,j+2)) + a1*(u(i,j)+u(i,j+1))
1764 utmp(i,j) = 0.5*(u(i,j)+u(i,j+1))
1766 utmp(i,j) = 0.5*(u(i,j)+u(i,j+1))
1771 vtmp(i,j) = a2*(v(i-1,j)+v(i+2,j)) + a1*(v(i,j)+v(i+1,j))
1774 vtmp(i,j) = 0.5*(v(i,j)+v(i+1,j))
1776 vtmp(i,j) = 0.5*(v(i,j)+v(i+1,j))
1785 do j=
max(npt,js-1),
min(npy-npt,je+1)
1786 do i=
max(npt,isd),
min(npx-npt,ied)
1787 utmp(i,j) = a2*(u(i,j-1)+u(i,j+2)) + a1*(u(i,j)+u(i,j+1))
1790 do j=
max(npt,jsd),
min(npy-npt,jed)
1791 do i=
max(npt,is-1),
min(npx-npt,ie+1)
1792 vtmp(i,j) = a2*(v(i-1,j)+v(i+2,j)) + a1*(v(i,j)+v(i+1,j))
1801 if ( js==1 .or. jsd<npt)
then 1804 utmp(i,j) = 0.5*(u(i,j) + u(i,j+1))
1805 vtmp(i,j) = 0.5*(v(i,j) + v(i+1,j))
1810 if ( (je+1)==npy .or. jed>=(npy-npt))
then 1813 utmp(i,j) = 0.5*(u(i,j) + u(i,j+1))
1814 vtmp(i,j) = 0.5*(v(i,j) + v(i+1,j))
1819 if ( is==1 .or. isd<npt )
then 1820 do j=
max(npt,jsd),
min(npy-npt,jed)
1822 utmp(i,j) = 0.5*(u(i,j) + u(i,j+1))
1823 vtmp(i,j) = 0.5*(v(i,j) + v(i+1,j))
1828 if ( (ie+1)==npx .or. ied>=(npx-npt))
then 1829 do j=
max(npt,jsd),
min(npy-npt,jed)
1831 utmp(i,j) = 0.5*(u(i,j) + u(i,j+1))
1832 vtmp(i,j) = 0.5*(v(i,j) + v(i+1,j))
1843 do j=js-1-id,je+1+id
1844 do i=is-1-id,ie+1+id
1845 ua(i,j) = (utmp(i,j)-vtmp(i,j)*cosa_s(i,j)) * rsin2(i,j)
1846 va(i,j) = (vtmp(i,j)-utmp(i,j)*cosa_s(i,j)) * rsin2(i,j)
1852 subroutine pmaxmn_g(qname, q, is, ie, js, je, km, fac, area, domain)
1853 character(len=*),
intent(in):: qname
1854 integer,
intent(in):: is, ie, js, je
1855 integer,
intent(in):: km
1856 real,
intent(in):: q(is-3:ie+3, js-3:je+3, km)
1857 real,
intent(in):: fac
1858 real(kind=R_GRID),
intent(IN):: area(is-3:ie+3, js-3:je+3)
1859 type(domain2d),
intent(INOUT) :: domain
1861 real qmin, qmax, gmean
1870 if( q(i,j,k) < qmin )
then 1872 elseif( q(i,j,k) > qmax )
then 1879 call mp_reduce_min(qmin)
1880 call mp_reduce_max(qmax)
1882 gmean =
g_sum(domain, q(is:ie,js:je,km), is, ie, js, je, 3, area, 1, .true.)
1883 if(is_master())
write(6,*) qname, qmax*fac, qmin*fac, gmean*fac
subroutine fill_nested_grid_data(Atm, proc_in)
subroutine, public fv_restart_end(Atm, grids_on_this_pe)
real, parameter, public radius
Radius of the Earth [m].
subroutine, public del4_cubed_sphere(npx, npy, q, area, dx, dy, dxc, dyc, sin_sg, nmax, zero_ocean, oro, nested, domain, bd)
subroutine, public fv_write_restart(Atm, grids_on_this_pe, timestamp)
integer, parameter, public model_atmos
subroutine, public p_var(km, ifirst, ilast, jfirst, jlast, ptop, ptop_min, delp, delz, pt, ps, pe, peln, pk, pkz, cappa, q, ng, nq, area, dry_mass, adjust_dry_mass, mountain, moist_phys, hydrostatic, nwat, domain, make_nh)
subroutine, public fv_io_register_restart(fv_domain, Atm)
real, parameter, public omega
Rotation rate of the Earth [1/s].
subroutine, public d2c_setup(u, v, ua, va, uc, vc, dord4, isd, ied, jsd, jed, is, ie, js, je, npx, npy, grid_type, nested, se_corner, sw_corner, ne_corner, nw_corner, rsin_u, rsin_v, cosa_s, rsin2)
real, parameter, public ptop_min
subroutine, public init_double_periodic(u, v, w, pt, delp, q, phis, ps, pe, peln, pk, pkz, uc, vc, ua, va, ak, bk, gridstruct, flagstruct, npx, npy, npz, ng, ncnst, nwat, ndims, nregions, dry_mass, mountain, moist_phys, hydrostatic, hybrid_z, delz, ze0, ks, ptop, domain_in, tile_in, bd)
real(kind=8), parameter, public pi_8
Ratio of circle circumference to diameter [N/A].
subroutine, public fv_restart(fv_domain, Atm, dt_atmos, seconds, days, cold_start, grid_type, grids_on_this_pe)
subroutine, public fv_io_register_restart_bcs_nh(Atm)
subroutine, public fv_io_read_restart(fv_domain, Atm)
subroutine, public init_case(u, v, w, pt, delp, q, phis, ps, pe, peln, pk, pkz, uc, vc, ua, va, ak, bk, gridstruct, flagstruct, npx, npy, npz, ng, ncnst, nwat, ndims, nregions, dry_mass, mountain, moist_phys, hydrostatic, hybrid_z, delz, ze0, adiabatic, ks, npx_global, ptop, domain_in, tile_in, bd)
subroutine, public fv_io_register_restart_bcs(Atm)
real, parameter, public rdgas
Gas constant for dry air [J/kg/deg].
subroutine, public init_latlon(u, v, pt, delp, q, phis, ps, pe, peln, pk, pkz, uc, vc, ua, va, ak, bk, gridstruct, npx, npy, npz, ng, ncnst, ndims, nregions, dry_mass, mountain, moist_phys, hybrid_z, delz, ze0, domain_in, tile_in)
real, dimension(:,:), allocatable, public oro_g
subroutine, public cubed_to_latlon(u, v, ua, va, gridstruct, npx, npy, km, mode, grid_type, domain, nested, c2l_ord, bd)
subroutine, public get_external_ic(Atm, fv_domain, use_geos_latlon_restart, use_geos_cubed_restart, ntracers)
subroutine fill_nested_grid_topo(Atm, proc_in)
subroutine, public fv_io_init()
subroutine, public get_cubed_sphere_terrain(Atm, fv_domain)
real, parameter, public rvgas
Gas constant for water vapor [J/kg/deg].
subroutine timing_on(blk_name)
real, parameter, public cp_air
Specific heat capacity of dry air at constant pressure [J/kg/deg].
subroutine, public fv_io_read_bcs(Atm)
subroutine, public fv_io_register_nudge_restart(Atm)
integer, parameter, public r_grid
real function, public great_circle_dist(q1, q2, radius)
subroutine fill_nested_grid_data_end(Atm, proc_in)
subroutine, public fv_io_write_bcs(Atm, timestamp)
subroutine, public compute_dz_var(km, ztop, dz)
subroutine, public make_eta_level(km, pe, area, kks, ak, bk, ptop, domain, bd)
subroutine fill_nested_grid_topo_halo(Atm, proc_in)
real, parameter, public grav
Acceleration due to gravity [m/s^2].
real function, public g_sum(domain, p, ifirst, ilast, jfirst, jlast, ngc, area, mode, reproduce)
************************************************************************GNU Lesser General Public License **This file is part of the GFDL Flexible Modeling System(FMS). ! *! *FMS is free software without even the implied warranty of MERCHANTABILITY or *FITNESS FOR A PARTICULAR PURPOSE See the GNU General Public License *for more details **You should have received a copy of the GNU Lesser General Public *License along with FMS If see< http:! ***********************************************************************subroutine READ_RECORD_CORE_(unit, field, nwords, data, start, axsiz) integer, intent(in) ::unit type(fieldtype), intent(in) ::field integer, intent(in) ::nwords MPP_TYPE_, intent(inout) ::data(nwords) integer, intent(in) ::start(:), axsiz(:) integer(SHORT_KIND) ::i2vals(nwords)!rab used in conjunction with transfer intrinsic to determine size of a variable integer(KIND=1) ::one_byte(8) integer ::word_sz!#ifdef __sgi integer(INT_KIND) ::ivals(nwords) real(FLOAT_KIND) ::rvals(nwords)!#else! integer ::ivals(nwords)! real ::rvals(nwords)!#endif real(DOUBLE_KIND) ::r8vals(nwords) pointer(ptr1, i2vals) pointer(ptr2, ivals) pointer(ptr3, rvals) pointer(ptr4, r8vals) if(mpp_io_stack_size< nwords) call mpp_io_set_stack_size(nwords) call mpp_error(FATAL, 'MPP_READ currently requires use_netCDF option') end subroutine READ_RECORD_CORE_ subroutine READ_RECORD_(unit, field, nwords, data, time_level, domain, position, tile_count, start_in, axsiz_in)!routine that is finally called by all mpp_read routines to perform the read!a non-netCDF record contains:! field ID! a set of 4 coordinates(is:ie, js:je) giving the data subdomain! a timelevel and a timestamp(=NULLTIME if field is static)! 3D real data(stored as 1D)!if you are using direct access I/O, the RECL argument to OPEN must be large enough for the above!in a global direct access file, record position on PE is given by %record.!Treatment of timestamp:! We assume that static fields have been passed without a timestamp.! Here that is converted into a timestamp of NULLTIME.! For non-netCDF fields, field is treated no differently, but is written! with a timestamp of NULLTIME. There is no check in the code to prevent! the user from repeatedly writing a static field. integer, intent(in) ::unit, nwords type(fieldtype), intent(in) ::field MPP_TYPE_, intent(inout) ::data(nwords) integer, intent(in), optional ::time_level type(domain2D), intent(in), optional ::domain integer, intent(in), optional ::position, tile_count integer, intent(in), optional ::start_in(:), axsiz_in(:) integer, dimension(size(field%axes(:))) ::start, axsiz integer ::tlevel !, subdomain(4) integer ::i, error, is, ie, js, je, isg, ieg, jsg, jeg type(domain2d), pointer ::io_domain=> tlevel if(PRESENT(start_in) .AND. PRESENT(axsiz_in)) then if(size(start(! the data domain and compute domain must refer to the subdomain being passed ! In this ! since that attempts to gather all data on PE size(field%axes(:)) axsiz(i)
logical module_is_initialized
subroutine, public get_tracer_names(model, n, name, longname, units, err_msg)
subroutine, public fv_restart_init()
subroutine, public fv_io_write_restart(Atm, grids_on_this_pe, timestamp)
subroutine pmaxmn_g(qname, q, is, ie, js, je, km, fac, area, domain)
subroutine, public set_hybrid_z(is, ie, js, je, ng, km, ztop, dz, rgrav, hs, ze, dz3)
real, dimension(:,:), allocatable, public sgh_g
subroutine, public compute_dz_l32(km, ztop, dz)
subroutine, public del2_cubed_sphere(npx, npy, q, area, dx, dy, dxc, dyc, sin_sg, nmax, cd, zero_ocean, oro, nested, domain, bd)
subroutine, public prt_maxmin(qname, q, is, ie, js, je, n_g, km, fac)
integer, public test_case
subroutine, public d2a_setup(u, v, ua, va, dord4, isd, ied, jsd, jed, is, ie, js, je, npx, npy, grid_type, nested, cosa_s, rsin2)
real(kind=r_grid), parameter cnst_0p20
real, parameter, public kappa
RDGAS / CP_AIR [dimensionless].
subroutine, public remap_restart(fv_domain, Atm)
Derived type containing the data.
subroutine, public setup_nested_boundary_halo(Atm, proc_in)
real(fp), parameter, public pi
subroutine timing_off(blk_name)