137 use constants_mod,
only: kappa, pi=>pi_8, omega, rdgas, grav, rvgas, cp_air, radius
146 use mpp_domains_mod,
only: mpp_get_compute_domain, mpp_get_data_domain, mpp_get_global_domain
147 use mpp_domains_mod,
only: mpp_update_domains, domain2d, dgrid_ne
148 use mpp_domains_mod,
only: center, corner, north, east, mpp_get_c2f_index, west, south
149 use mpp_domains_mod,
only: mpp_global_field
150 use mpp_mod,
only: mpp_chksum, stdout, mpp_error, fatal, note
151 use mpp_mod,
only: get_unit, mpp_sum
152 use mpp_mod,
only: mpp_get_current_pelist, mpp_set_current_pelist
153 use mpp_mod,
only: mpp_send, mpp_recv, mpp_sync_self, mpp_npes, mpp_pe, mpp_sync
155 use fv_mp_mod,
only: is_master, switch_current_atm, mp_reduce_min, mp_reduce_max
158 use tracer_manager_mod,
only: get_tracer_names
159 use tracer_manager_mod,
only: get_tracer_index
160 use field_manager_mod,
only: model_atmos
164 use field_manager_mod,
only: model_atmos
166 use fms_mod,
only: file_exist
195 subroutine fv_restart(fv_domain, Atm, dt_atmos, seconds, days, cold_start, grid_type, grids_on_this_pe)
196 type(domain2d),
intent(inout) :: fv_domain
198 real,
intent(in) :: dt_atmos
199 integer,
intent(out) :: seconds
200 integer,
intent(out) :: days
201 logical,
intent(inout) :: cold_start
202 integer,
intent(in) :: grid_type
203 logical,
intent(INOUT) :: grids_on_this_pe(:)
206 integer :: i, j, k, n, ntileme, nt, iq
207 integer :: isc, iec, jsc, jec, npz, npz_rst, ncnst, ntprog, ntdiag
208 integer :: isd, ied, jsd, jed
209 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
210 real,
allocatable :: g_dat(:,:,:)
213 real,
allocatable :: dz1(:)
214 real rgrav, f00, ztop, pertn
216 logical :: cold_start_grids(size(atm))
217 character(len=128):: tname, errstring, fname, tracer_name
218 character(len=120):: fname_ne, fname_sw
219 character(len=3) :: gn
228 ntileme =
size(atm(:))
230 cold_start_grids(:) = cold_start
233 if (is_master())
then 234 print*,
'FV_RESTART: ', n, cold_start_grids(n)
237 if (atm(n)%neststruct%nested)
then 238 write(fname,
'(A, I2.2, A)')
'INPUT/fv_core.res.nest', atm(n)%grid_number,
'.nc' 239 write(fname_ne,
'(A, I2.2, A)')
'INPUT/fv_BC_ne.res.nest', atm(n)%grid_number,
'.nc' 240 write(fname_sw,
'(A, I2.2, A)')
'INPUT/fv_BC_sw.res.nest', atm(n)%grid_number,
'.nc' 241 if (atm(n)%flagstruct%external_ic)
then 242 if (is_master()) print*,
'External IC set on grid', atm(n)%grid_number,
', re-initializing grid' 243 cold_start_grids(n) = .true.
244 atm(n)%flagstruct%warm_start = .false.
246 if (is_master()) print*,
'Searching for nested grid restart file ', trim(fname)
247 cold_start_grids(n) = .not. file_exist(fname, atm(n)%domain)
248 atm(n)%flagstruct%warm_start = file_exist(fname, atm(n)%domain)
252 if (.not. grids_on_this_pe(n))
then 259 if (atm(n)%neststruct%nested)
then 260 if (cold_start_grids(n))
then 262 if (atm(n)%flagstruct%nggps_ic)
then 265 call nested_grid_bc(atm(n)%ps, atm(n)%parent_grid%ps, atm(n)%neststruct%nest_domain, &
266 atm(n)%neststruct%ind_h, atm(n)%neststruct%wt_h, 0, 0, &
267 atm(n)%npx, atm(n)%npy,atm(n)%bd, isg, ieg, jsg, jeg, proc_in=.false.)
272 if ( atm(n)%flagstruct%external_ic .and. grid_type < 4 )
call fill_nested_grid_data(atm(n:n), .false.)
275 if (is_master()) print*,
'Searching for nested grid BC files ', trim(fname_ne),
' ', trim(fname_sw)
278 if (file_exist(fname_ne, atm(n)%domain) .and. file_exist(fname_sw, atm(n)%domain))
then 280 if ( is_master() )
write(*,*)
'BC files not found, re-generating nested grid boundary conditions' 283 atm(n)%neststruct%first_step = .true.
287 if (.not. atm(n)%flagstruct%hydrostatic .and. atm(n)%flagstruct%make_nh .and. &
288 (.not. atm(n)%flagstruct%nggps_ic .and. .not. atm(n)%flagstruct%ecmwf_ic) )
then 289 call nested_grid_bc(atm(n)%delz, atm(n)%parent_grid%delz, atm(n)%neststruct%nest_domain, &
290 atm(n)%neststruct%ind_h, atm(n)%neststruct%wt_h, 0, 0, &
291 atm(n)%npx, atm(n)%npy, atm(n)%npz, atm(n)%bd, isg, ieg, jsg, jeg, proc_in=.false.)
292 call nested_grid_bc(atm(n)%w, atm(n)%parent_grid%w, atm(n)%neststruct%nest_domain, &
293 atm(n)%neststruct%ind_h, atm(n)%neststruct%wt_h, 0, 0, &
294 atm(n)%npx, atm(n)%npy, atm(n)%npz, atm(n)%bd, isg, ieg, jsg, jeg, proc_in=.false.)
303 call switch_current_atm(atm(n))
308 if( .not.cold_start_grids(n) .and. (.not. atm(n)%flagstruct%external_ic) )
then 311 if ( atm(n)%flagstruct%npz_rst /= 0 .and. atm(n)%flagstruct%npz_rst /= atm(n)%npz )
then 313 if( is_master() )
then 315 write(*,*)
'***** Important Note from FV core ********************' 316 write(*,*)
'Remapping dynamic IC from', atm(n)%flagstruct%npz_rst,
'levels to ', atm(n)%npz,
'levels' 317 write(*,*)
'***** End Note from FV core **************************' 321 if( is_master() )
write(*,*)
'Done remapping dynamical IC' 323 if( is_master() )
write(*,*)
'Warm starting, calling fv_io_restart' 326 if (atm(n)%flagstruct%read_increment)
then 328 i = (atm(n)%bd%isc + atm(n)%bd%iec)/2
329 j = (atm(n)%bd%jsc + atm(n)%bd%jec)/2
331 if( is_master() )
write(*,*)
'Calling read_da_inc',atm(n)%pt(i,j,k)
333 if( is_master() )
write(*,*)
'Back from read_da_inc',atm(n)%pt(i,j,k)
342 if (atm(n)%neststruct%nested)
then 345 if (cold_start_grids(n))
then 346 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.)
348 if (atm(n)%flagstruct%external_ic .and. atm(n)%flagstruct%nggps_ic)
then 350 call nested_grid_bc(atm(n)%ps, atm(n)%parent_grid%ps, atm(n)%neststruct%nest_domain, &
351 atm(n)%neststruct%ind_h, atm(n)%neststruct%wt_h, 0, 0, &
352 atm(n)%npx, atm(n)%npy,atm(n)%bd, isg, ieg, jsg, jeg, proc_in=.true.)
355 if ( atm(n)%flagstruct%external_ic )
then 356 if( is_master() )
write(*,*)
'Calling get_external_ic' 358 if( is_master() )
write(*,*)
'IC generated from the specified external source' 361 seconds = 0; days = 0
372 if( is_master() )
write(*,*)
'in fv_restart ncnst=', ncnst
373 isc = atm(n)%bd%isc; iec = atm(n)%bd%iec; jsc = atm(n)%bd%jsc; jec = atm(n)%bd%jec
376 if(.not.cold_start_grids(n))
then 377 atm(n)%neststruct%first_step = .false.
378 if (atm(n)%neststruct%nested)
then 379 if ( atm(n)%flagstruct%npz_rst /= 0 .and. atm(n)%flagstruct%npz_rst /= atm(n)%npz )
then 383 if (is_master()) print*,
'Searching for nested grid BC files ', trim(fname_ne),
' ', trim(fname_sw)
384 if (file_exist(fname_ne, atm(n)%domain) .and. file_exist(fname_sw, atm(n)%domain))
then 387 if ( is_master() )
write(*,*)
'BC files not found, re-generating nested grid boundary conditions' 390 atm(n)%neststruct%first_step = .true.
393 call mpp_update_domains(atm(n)%u, atm(n)%v, atm(n)%domain, gridtype=dgrid_ne, complete=.true.)
397 if ( atm(n)%flagstruct%mountain )
then 401 if ( atm(n)%flagstruct%n_zs_filter > 0 )
then 402 if ( atm(n)%flagstruct%nord_zs_filter == 2 )
then 404 atm(n)%gridstruct%area_64, atm(n)%gridstruct%dx, atm(n)%gridstruct%dy, &
405 atm(n)%gridstruct%dxc, atm(n)%gridstruct%dyc, atm(n)%gridstruct%sin_sg, &
406 atm(n)%flagstruct%n_zs_filter,
cnst_0p20*atm(n)%gridstruct%da_min, &
407 .false., oro_g, atm(n)%neststruct%nested, atm(n)%domain, atm(n)%bd, atm(n)%flagstruct%regional)
408 if ( is_master() )
write(*,*)
'Warning !!! del-2 terrain filter has been applied ', &
409 atm(n)%flagstruct%n_zs_filter,
' times' 410 else if( atm(n)%flagstruct%nord_zs_filter == 4 )
then 411 call del4_cubed_sphere(atm(n)%npx, atm(n)%npy, atm(n)%phis, atm(n)%gridstruct%area_64, &
412 atm(n)%gridstruct%dx, atm(n)%gridstruct%dy, &
413 atm(n)%gridstruct%dxc, atm(n)%gridstruct%dyc, atm(n)%gridstruct%sin_sg, &
414 atm(n)%flagstruct%n_zs_filter, .false., oro_g, atm(n)%neststruct%nested, &
415 atm(n)%domain, atm(n)%bd, atm(n)%flagstruct%regional)
416 if ( is_master() )
write(*,*)
'Warning !!! del-4 terrain filter has been applied ', &
417 atm(n)%flagstruct%n_zs_filter,
' times' 421 call mpp_update_domains( atm(n)%phis, atm(n)%domain, complete=.true. )
424 if( is_master() )
write(*,*)
'phis set to zero' 428 atm(n)%pt(:,:,:) = 1.
430 if ( .not.atm(n)%flagstruct%hybrid_z )
then 431 if(atm(n)%ptop /= atm(n)%ak(1))
call mpp_error(fatal,
'FV restart: ptop not equal Atm(n)%ak(1)')
433 atm(n)%ptop = atm(n)%ak(1) ; atm(n)%ks = 0
435 call p_var(atm(n)%npz, isc, iec, jsc, jec, atm(n)%ptop,
ptop_min, &
436 atm(n)%delp, atm(n)%delz, atm(n)%pt, atm(n)%ps, atm(n)%pe, atm(n)%peln, &
437 atm(n)%pk, atm(n)%pkz, kappa, atm(n)%q, atm(n)%ng, &
438 ncnst, atm(n)%gridstruct%area_64, atm(n)%flagstruct%dry_mass, &
439 atm(n)%flagstruct%adjust_dry_mass, atm(n)%flagstruct%mountain, &
440 atm(n)%flagstruct%moist_phys, atm(n)%flagstruct%hydrostatic, &
441 atm(n)%flagstruct%nwat, atm(n)%domain, atm(n)%flagstruct%make_nh)
444 if ( grid_type < 7 .and. grid_type /= 4 )
then 449 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) + &
450 sin(atm(n)%gridstruct%grid(i,j,2))*cos(
alpha) )
455 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) + &
456 sin(atm(n)%gridstruct%agrid(i,j,2))*cos(
alpha) )
460 f00 = 2.*omega*sin(atm(n)%flagstruct%deglat/180.*pi)
463 atm(n)%gridstruct%fc(i,j) = f00
468 atm(n)%gridstruct%f0(i,j) = f00
473 if ( atm(n)%flagstruct%warm_start )
then 474 call mpp_error(fatal,
'FV restart files not found; set warm_start = .F. if cold_start is desired.')
477 if ( atm(n)%flagstruct%make_hybrid_z )
then 480 hybrid = atm(n)%flagstruct%hybrid_z
482 if (grid_type < 4)
then 483 if ( .not. atm(n)%flagstruct%external_ic )
then 484 call init_case(atm(n)%u,atm(n)%v,atm(n)%w,atm(n)%pt,atm(n)%delp,atm(n)%q, &
485 atm(n)%phis, atm(n)%ps,atm(n)%pe, atm(n)%peln,atm(n)%pk,atm(n)%pkz, &
486 atm(n)%uc,atm(n)%vc, atm(n)%ua,atm(n)%va, &
487 atm(n)%ak, atm(n)%bk, atm(n)%gridstruct, atm(n)%flagstruct,&
488 atm(n)%npx, atm(n)%npy, atm(n)%npz, atm(n)%ng, &
489 ncnst, atm(n)%flagstruct%nwat, &
490 atm(n)%flagstruct%ndims, atm(n)%flagstruct%ntiles, &
491 atm(n)%flagstruct%dry_mass, &
492 atm(n)%flagstruct%mountain, &
493 atm(n)%flagstruct%moist_phys, atm(n)%flagstruct%hydrostatic, &
494 hybrid, atm(n)%delz, atm(n)%ze0, &
495 atm(n)%flagstruct%adiabatic, atm(n)%ks, atm(n)%neststruct%npx_global, &
496 atm(n)%ptop, atm(n)%domain, atm(n)%tile, atm(n)%bd)
498 elseif (grid_type == 4)
then 500 atm(n)%delp,atm(n)%q,atm(n)%phis, atm(n)%ps,atm(n)%pe, &
501 atm(n)%peln,atm(n)%pk,atm(n)%pkz, &
502 atm(n)%uc,atm(n)%vc, atm(n)%ua,atm(n)%va, &
503 atm(n)%ak, atm(n)%bk, &
504 atm(n)%gridstruct, atm(n)%flagstruct, &
505 atm(n)%npx, atm(n)%npy, atm(n)%npz, atm(n)%ng, &
506 ncnst, atm(n)%flagstruct%nwat, &
507 atm(n)%flagstruct%ndims, atm(n)%flagstruct%ntiles, &
508 atm(n)%flagstruct%dry_mass, atm(n)%flagstruct%mountain, &
509 atm(n)%flagstruct%moist_phys, atm(n)%flagstruct%hydrostatic, &
510 hybrid, atm(n)%delz, atm(n)%ze0, atm(n)%ks, atm(n)%ptop, &
511 atm(n)%domain, atm(n)%tile, atm(n)%bd)
512 if( is_master() )
write(*,*)
'Doubly Periodic IC generated' 513 elseif (grid_type == 5 .or. grid_type == 6)
then 514 call init_latlon(atm(n)%u,atm(n)%v,atm(n)%pt,atm(n)%delp,atm(n)%q,&
515 atm(n)%phis, atm(n)%ps,atm(n)%pe, &
516 atm(n)%peln,atm(n)%pk,atm(n)%pkz, &
517 atm(n)%uc,atm(n)%vc, atm(n)%ua,atm(n)%va, &
518 atm(n)%ak, atm(n)%bk, atm(n)%gridstruct, &
519 atm(n)%npx, atm(n)%npy, atm(n)%npz, atm(n)%ng, ncnst, &
520 atm(n)%flagstruct%ndims, atm(n)%flagstruct%ntiles, &
521 atm(n)%flagstruct%dry_mass, &
522 atm(n)%flagstruct%mountain, &
523 atm(n)%flagstruct%moist_phys, hybrid, atm(n)%delz, &
524 atm(n)%ze0, atm(n)%domain, atm(n)%tile)
528 if ( atm(n)%flagstruct%fv_land )
then 531 atm(n)%sgh(i,j) = sgh_g(i,j)
532 atm(n)%oro(i,j) = oro_g(i,j)
544 if (atm(n)%neststruct%nested)
then 546 if (atm(n)%flagstruct%external_ic .and. .not. atm(n)%flagstruct%nggps_ic .and. grid_type < 4 )
then 553 if ( (.not.atm(n)%flagstruct%hydrostatic) .and. atm(n)%flagstruct%make_nh .and. atm(n)%neststruct%nested)
then 554 call nested_grid_bc(atm(n)%delz, atm(n)%parent_grid%delz, atm(n)%neststruct%nest_domain, &
555 atm(n)%neststruct%ind_h, atm(n)%neststruct%wt_h, 0, 0, &
556 atm(n)%npx, atm(n)%npy, npz, atm(n)%bd, isg, ieg, jsg, jeg, proc_in=.true.)
557 call nested_grid_bc(atm(n)%w, atm(n)%parent_grid%w, atm(n)%neststruct%nest_domain, &
558 atm(n)%neststruct%ind_h, atm(n)%neststruct%wt_h, 0, 0, &
559 atm(n)%npx, atm(n)%npy, npz, atm(n)%bd, isg, ieg, jsg, jeg, proc_in=.true.)
567 if (atm(n)%neststruct%nested .and. atm(n)%flagstruct%external_ic .and. &
568 atm(n)%flagstruct%grid_type < 4 .and. cold_start_grids(n))
then 574 if (.not. grids_on_this_pe(n)) cycle
581 ntprog =
size(atm(n)%q,4)
582 ntdiag =
size(atm(n)%qdiag,4)
583 isc = atm(n)%bd%isc; iec = atm(n)%bd%iec; jsc = atm(n)%bd%jsc; jec = atm(n)%bd%jec
587 if ( atm(n)%flagstruct%hybrid_z )
then 588 if ( atm(n)%flagstruct%make_hybrid_z )
then 589 allocate ( dz1(atm(n)%npz) )
590 if( atm(n)%npz==32 )
then 596 call set_hybrid_z(isc, iec, jsc, jec, atm(n)%ng, atm(n)%npz, ztop, dz1, rgrav, &
597 atm(n)%phis, atm(n)%ze0)
606 if (atm(n)%flagstruct%add_noise > 0.)
then 607 write(errstring,
'(A, E16.9)')
"Adding thermal noise of amplitude ", atm(n)%flagstruct%add_noise
608 call mpp_error(note, errstring)
615 call random_number(pertn)
616 atm(n)%pt(i,j,k) = atm(n)%pt(i,j,k) + pertn*atm(n)%flagstruct%add_noise
618 sumpertn = sumpertn + pertn*atm(n)%flagstruct%add_noise ** 2
622 call mpp_update_domains(atm(n)%pt, atm(n)%domain)
623 call mpp_sum(sumpertn)
625 write(errstring,
'(A, E16.9)')
"RMS added noise: ", sqrt(sumpertn/npts)
626 call mpp_error(note, errstring)
629 if (atm(n)%grid_number > 1)
then 630 write(gn,
'(A2, I1)')
" g", atm(n)%grid_number
637 write(unit,*)
'fv_restart u ', trim(gn),
' = ', mpp_chksum(atm(n)%u(isc:iec,jsc:jec,:))
638 write(unit,*)
'fv_restart v ', trim(gn),
' = ', mpp_chksum(atm(n)%v(isc:iec,jsc:jec,:))
639 if ( .not.atm(n)%flagstruct%hydrostatic ) &
640 write(unit,*)
'fv_restart w ', trim(gn),
' = ', mpp_chksum(atm(n)%w(isc:iec,jsc:jec,:))
641 write(unit,*)
'fv_restart delp', trim(gn),
' = ', mpp_chksum(atm(n)%delp(isc:iec,jsc:jec,:))
642 write(unit,*)
'fv_restart phis', trim(gn),
' = ', mpp_chksum(atm(n)%phis(isc:iec,jsc:jec))
645 call prt_maxmin(
'H ', atm(n)%delp, isc, iec, jsc, jec, atm(n)%ng, 1, rgrav)
647 write(unit,*)
'fv_restart pt ', trim(gn),
' = ', mpp_chksum(atm(n)%pt(isc:iec,jsc:jec,:))
649 write(unit,*)
'fv_restart q(prog) nq ', trim(gn),
' =',ntprog, mpp_chksum(atm(n)%q(isc:iec,jsc:jec,:,:))
651 write(unit,*)
'fv_restart q(diag) nq ', trim(gn),
' =',ntdiag, mpp_chksum(atm(n)%qdiag(isc:iec,jsc:jec,:,:))
652 do iq=1,min(17, ntprog)
653 call get_tracer_names(model_atmos, iq, tracer_name)
654 write(unit,*)
'fv_restart '//trim(tracer_name)//
' = ', mpp_chksum(atm(n)%q(isc:iec,jsc:jec,:,iq))
659 call pmaxmn_g(
'ZS', atm(n)%phis, isc, iec, jsc, jec, 1, rgrav, atm(n)%gridstruct%area_64, atm(n)%domain)
660 call pmaxmn_g(
'PS', atm(n)%ps, isc, iec, jsc, jec, 1, 0.01, atm(n)%gridstruct%area_64, atm(n)%domain)
661 call pmaxmn_g(
'T ', atm(n)%pt, isc, iec, jsc, jec, atm(n)%npz, 1., atm(n)%gridstruct%area_64, atm(n)%domain)
665 call get_tracer_names ( model_atmos, i, tname )
666 call pmaxmn_g(trim(tname), atm(n)%q(isd:ied,jsd:jed,1:atm(n)%npz,i:i), isc, iec, jsc, jec, atm(n)%npz, &
667 1., atm(n)%gridstruct%area_64, atm(n)%domain)
670 call prt_maxmin(
'U ', atm(n)%u(isc:iec,jsc:jec,1:atm(n)%npz), isc, iec, jsc, jec, 0, atm(n)%npz, 1.)
671 call prt_maxmin(
'V ', atm(n)%v(isc:iec,jsc:jec,1:atm(n)%npz), isc, iec, jsc, jec, 0, atm(n)%npz, 1.)
673 if ( (.not.atm(n)%flagstruct%hydrostatic) .and. atm(n)%flagstruct%make_nh )
then 674 call mpp_error(note,
" Initializing w to 0")
676 if ( .not.atm(n)%flagstruct%hybrid_z )
then 677 call mpp_error(note,
" Initializing delz from hydrostatic state")
681 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))
688 if ( .not.atm(n)%flagstruct%hydrostatic ) &
689 call pmaxmn_g(
'W ', atm(n)%w, isc, iec, jsc, jec, atm(n)%npz, 1., atm(n)%gridstruct%area_64, atm(n)%domain)
691 if (is_master())
write(unit,*)
696 if ( .not. atm(n)%flagstruct%srf_init )
then 699 atm(n)%npx, atm(n)%npy, atm(n)%npz, 1, &
700 atm(n)%gridstruct%grid_type, atm(n)%domain, &
701 atm(n)%gridstruct%nested, atm(n)%flagstruct%c2l_ord, atm(n)%bd)
704 atm(n)%u_srf(i,j) = atm(n)%ua(i,j,atm(n)%npz)
705 atm(n)%v_srf(i,j) = atm(n)%va(i,j,atm(n)%npz)
708 atm(n)%flagstruct%srf_init = .true.
723 logical,
INTENT(IN),
OPTIONAL :: proc_in
724 real,
allocatable :: g_dat(:,:,:), g_dat2(:,:,:)
725 real,
allocatable :: pt_coarse(:,:,:)
726 integer i,j,k,nq, sphum, ncnst, istart, iend, npz, nwat
727 integer isc, iec, jsc, jec, isd, ied, jsd, jed, is, ie, js, je
728 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
731 integer :: liq_wat, ice_wat, rainwat, snowwat, graupel
732 real :: qv, dp1, q_liq, q_sol, q_con, cvm, cappa, dp, pt, dz, pkz, rdg
734 if (
PRESENT(proc_in))
then 745 isc = atm%bd%isc; iec = atm%bd%iec; jsc = atm%bd%jsc; jec = atm%bd%jec
746 is = atm%bd%is ; ie = atm%bd%ie ; js = atm%bd%js ; je = atm%bd%je
748 nwat = atm%flagstruct%nwat
751 liq_wat = get_tracer_index(model_atmos,
'liq_wat')
752 ice_wat = get_tracer_index(model_atmos,
'ice_wat')
755 rainwat = get_tracer_index(model_atmos,
'rainwat')
756 snowwat = get_tracer_index(model_atmos,
'snowwat')
757 elseif (nwat == 6)
then 758 rainwat = get_tracer_index(model_atmos,
'rainwat')
759 snowwat = get_tracer_index(model_atmos,
'snowwat')
760 graupel = get_tracer_index(model_atmos,
'graupel')
763 call mpp_get_data_domain( atm%parent_grid%domain, &
764 isd_p, ied_p, jsd_p, jed_p )
765 call mpp_get_compute_domain( atm%parent_grid%domain, &
766 isc_p, iec_p, jsc_p, jec_p )
767 call mpp_get_global_domain( atm%parent_grid%domain, &
768 isg, ieg, jsg, jeg, xsize=npx_p, ysize=npy_p)
770 call nested_grid_bc(atm%delp, atm%parent_grid%delp, atm%neststruct%nest_domain, &
771 atm%neststruct%ind_h, atm%neststruct%wt_h, 0, 0, &
772 atm%npx, atm%npy, npz, atm%bd, isg, ieg, jsg, jeg, proc_in=process)
775 atm%parent_grid%q(:,:,:,nq), atm%neststruct%nest_domain, &
776 atm%neststruct%ind_h, atm%neststruct%wt_h, 0, 0, &
777 atm%npx, atm%npy, npz, atm%bd, isg, ieg, jsg, jeg, proc_in=process)
781 if (is_master()) print*,
'FILLING NESTED GRID HALO' 783 if (is_master()) print*,
'SENDING DATA TO FILL NESTED GRID HALO' 805 call nested_grid_bc(atm%pt, atm%parent_grid%pt, atm%neststruct%nest_domain, &
806 atm%neststruct%ind_h, atm%neststruct%wt_h, 0, 0, &
807 atm%npx, atm%npy, npz, atm%bd, isg, ieg, jsg, jeg, proc_in=process)
809 if (.not. atm%flagstruct%hydrostatic)
then 813 atm%parent_grid%w(:,:,:), &
814 atm%neststruct%nest_domain, atm%neststruct%ind_h, atm%neststruct%wt_h, 0, 0, &
815 atm%npx, atm%npy, npz, atm%bd, isg, ieg, jsg, jeg, proc_in=process)
820 atm%parent_grid%delz(:,:,:), &
821 atm%neststruct%nest_domain, atm%neststruct%ind_h, atm%neststruct%wt_h, 0, 0, &
822 atm%npx, atm%npy, npz, atm%bd, isg, ieg, jsg, jeg, proc_in=process)
828 if (atm%neststruct%child_proc)
then 830 atm%neststruct%nest_domain, atm%neststruct%ind_u, atm%neststruct%wt_u, 0, 1, &
831 atm%npx, atm%npy, npz, atm%bd, isg, ieg, jsg, jeg, proc_in=process)
833 atm%neststruct%nest_domain, atm%neststruct%ind_v, atm%neststruct%wt_v, 1, 0, &
834 atm%npx, atm%npy, npz, atm%bd, isg, ieg, jsg, jeg, proc_in=process)
837 atm%neststruct%nest_domain, 0, 1)
839 atm%neststruct%nest_domain, 1, 0)
855 call mpp_update_domains(atm%u, atm%v, atm%domain, gridtype=dgrid_ne)
856 call mpp_update_domains(atm%w, atm%domain, complete=.true.)
865 type(fv_atmos_type),
intent(INOUT) :: Atm
866 logical,
intent(IN),
OPTIONAL :: proc_in
867 integer :: isg, ieg, jsg, jeg
869 if (.not. atm%neststruct%nested)
return 871 call mpp_get_global_domain( atm%parent_grid%domain, &
874 if (is_master()) print*,
' FILLING NESTED GRID HALO WITH INTERPOLATED TERRAIN' 875 call nested_grid_bc(atm%phis, atm%parent_grid%phis, atm%neststruct%nest_domain, &
876 atm%neststruct%ind_h, atm%neststruct%wt_h, 0, 0, &
877 atm%npx, atm%npy, atm%bd, isg, ieg, jsg, jeg, proc_in=proc_in)
885 type(fv_atmos_type),
intent(INOUT) :: Atm
886 logical,
intent(IN),
OPTIONAL :: proc_in
887 real,
allocatable :: g_dat(:,:,:)
888 integer :: p, sending_proc
889 integer :: isd_p, ied_p, jsd_p, jed_p
890 integer :: isg, ieg, jsg,jeg
895 if (
present(proc_in))
then 903 call mpp_get_global_domain( atm%parent_grid%domain, &
905 call mpp_get_data_domain( atm%parent_grid%domain, &
906 isd_p, ied_p, jsd_p, jed_p )
908 allocate(g_dat( isg:ieg, jsg:jeg, 1) )
914 if (is_master() .and. .not. atm%flagstruct%external_ic ) print*,
' FILLING NESTED GRID INTERIOR WITH INTERPOLATED TERRAIN' 916 sending_proc = atm%parent_grid%pelist(1) + (atm%neststruct%parent_tile-1)*atm%parent_grid%npes_per_tile
917 if (atm%neststruct%parent_proc .and. atm%neststruct%parent_tile == atm%parent_grid%tile)
then 918 call mpp_global_field( &
919 atm%parent_grid%domain, &
920 atm%parent_grid%phis(isd_p:ied_p,jsd_p:jed_p), g_dat(isg:,jsg:,1), position=center)
921 if (mpp_pe() == sending_proc)
then 922 do p=1,
size(atm%pelist)
923 call mpp_send(g_dat,
size(g_dat),atm%pelist(p))
928 if (any(atm%pelist == mpp_pe()))
then 929 call mpp_recv(g_dat,
size(g_dat), sending_proc)
934 atm%neststruct%ind_h, atm%neststruct%wt_h, &
935 0, 0, isg, ieg, jsg, jeg, atm%bd)
946 type(fv_atmos_type),
intent(INOUT) :: Atm(:)
947 logical,
intent(IN),
OPTIONAL :: proc_in
948 real,
allocatable :: g_dat(:,:,:), pt_coarse(:,:,:)
949 integer :: i,j,k,nq, sphum, ncnst, istart, iend, npz
950 integer :: isc, iec, jsc, jec, isd, ied, jsd, jed
951 integer :: isd_p, ied_p, jsd_p, jed_p, isc_p, iec_p, jsc_p, jec_p
952 integer :: isg, ieg, jsg,jeg, npx_p, npy_p
953 integer :: isg_n, ieg_n, jsg_n, jeg_n, npx_n, npy_n
954 real zvir, gh0, p1(2), p2(2), r, r0
956 integer :: p, sending_proc, gid, n
959 if (
present(proc_in))
then 970 isc = atm(1)%bd%isc; iec = atm(1)%bd%iec; jsc = atm(1)%bd%jsc; jec = atm(1)%bd%jec
976 sending_proc = atm(1)%parent_grid%pelist(1) + (atm(1)%neststruct%parent_tile-1)*atm(1)%parent_grid%npes_per_tile
978 call mpp_get_data_domain( atm(1)%parent_grid%domain, &
979 isd_p, ied_p, jsd_p, jed_p )
980 call mpp_get_compute_domain( atm(1)%parent_grid%domain, &
981 isc_p, iec_p, jsc_p, jec_p )
982 call mpp_get_global_domain( atm(1)%parent_grid%domain, &
983 isg, ieg, jsg, jeg, xsize=npx_p, ysize=npy_p)
987 call mpp_error(note,
"FILLING NESTED GRID DATA")
991 call mpp_error(note,
"SENDING TO FILL NESTED GRID DATA")
997 allocate(g_dat( isg:ieg, jsg:jeg, npz) )
1003 if (atm(1)%neststruct%parent_proc .and. atm(1)%neststruct%parent_tile == atm(1)%parent_grid%tile)
then 1004 call mpp_global_field( &
1005 atm(1)%parent_grid%domain, &
1006 atm(1)%parent_grid%delp(isd_p:ied_p,jsd_p:jed_p,:), g_dat, position=center)
1007 if (gid == sending_proc)
then 1008 do p=1,
size(atm(1)%pelist)
1009 call mpp_send(g_dat,
size(g_dat),atm(1)%pelist(p))
1013 if (any(atm(1)%pelist == gid))
then 1014 call mpp_recv(g_dat,
size(g_dat), sending_proc)
1019 atm(1)%neststruct%ind_h, atm(1)%neststruct%wt_h, &
1020 0, 0, isg, ieg, jsg, jeg, npz, atm(1)%bd)
1029 if (any(atm(1)%parent_grid%pelist == gid) .and. atm(1)%neststruct%parent_tile == atm(1)%parent_grid%tile)
then 1030 call mpp_global_field( &
1031 atm(1)%parent_grid%domain, &
1032 atm(1)%parent_grid%q(isd_p:ied_p,jsd_p:jed_p,:,nq), g_dat, position=center)
1033 if (gid == sending_proc)
then 1034 do p=1,
size(atm(1)%pelist)
1035 call mpp_send(g_dat,
size(g_dat),atm(1)%pelist(p))
1039 if (any(atm(1)%pelist == gid))
then 1040 call mpp_recv(g_dat,
size(g_dat), sending_proc)
1044 if (process)
call fill_nested_grid(atm(1)%q(isd:ied,jsd:jed,:,nq), g_dat, &
1045 atm(1)%neststruct%ind_h, atm(1)%neststruct%wt_h, &
1046 0, 0, isg, ieg, jsg, jeg, npz, atm(1)%bd)
1061 if (any(atm(1)%parent_grid%pelist == gid) .and. atm(1)%neststruct%parent_tile == atm(1)%parent_grid%tile)
then 1062 call mpp_global_field( &
1063 atm(1)%parent_grid%domain, &
1064 atm(1)%parent_grid%pt(isd_p:ied_p,jsd_p:jed_p,:), g_dat, position=center)
1065 if (gid == sending_proc)
then 1066 do p=1,
size(atm(1)%pelist)
1067 call mpp_send(g_dat,
size(g_dat),atm(1)%pelist(p))
1071 if (any(atm(1)%pelist == gid))
then 1072 call mpp_recv(g_dat,
size(g_dat), sending_proc)
1079 atm(1)%neststruct%ind_h, atm(1)%neststruct%wt_h, &
1080 0, 0, isg, ieg, jsg, jeg, npz, atm(1)%bd)
1083 if ( atm(1)%flagstruct%nwat > 0 )
then 1084 sphum = get_tracer_index(model_atmos,
'sphum')
1088 if ( atm(1)%parent_grid%flagstruct%adiabatic .or. atm(1)%parent_grid%flagstruct%do_Held_Suarez )
then 1091 zvir = rvgas/rdgas - 1.
1096 if (any(atm(1)%parent_grid%pelist == gid) .and. atm(1)%neststruct%parent_tile == atm(1)%parent_grid%tile)
then 1097 call mpp_global_field( &
1098 atm(1)%parent_grid%domain, &
1099 atm(1)%parent_grid%pkz(isc_p:iec_p,jsc_p:jec_p,:), g_dat, position=center)
1100 if (gid == sending_proc)
then 1101 do p=1,
size(atm(1)%pelist)
1102 call mpp_send(g_dat,
size(g_dat),atm(1)%pelist(p))
1106 if (any(atm(1)%pelist == gid))
then 1107 call mpp_recv(g_dat,
size(g_dat), sending_proc)
1114 allocate(pt_coarse(isd:ied,jsd:jed,npz))
1116 atm(1)%neststruct%ind_h, atm(1)%neststruct%wt_h, &
1117 0, 0, isg, ieg, jsg, jeg, npz, atm(1)%bd)
1119 if (atm(1)%bd%is == 1)
then 1121 do j=atm(1)%bd%jsd,atm(1)%bd%jed
1122 do i=atm(1)%bd%isd,0
1124 atm(1)%pt(i,j,k) = cp_air*atm(1)%pt(i,j,k)/pt_coarse(i,j,k)*
virq(atm(1)%q(i,j,k,:))
1126 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))
1133 if (atm(1)%bd%js == 1)
then 1134 if (atm(1)%bd%is == 1)
then 1135 istart = atm(1)%bd%is
1137 istart = atm(1)%bd%isd
1139 if (atm(1)%bd%ie == atm(1)%npx-1)
then 1142 iend = atm(1)%bd%ied
1146 do j=atm(1)%bd%jsd,0
1149 atm(1)%pt(i,j,k) = cp_air*atm(1)%pt(i,j,k)/pt_coarse(i,j,k)*
virq(atm(1)%q(i,j,k,:))
1151 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))
1158 if (atm(1)%bd%ie == atm(1)%npx-1)
then 1160 do j=atm(1)%bd%jsd,atm(1)%bd%jed
1161 do i=atm(1)%npx,atm(1)%bd%ied
1163 atm(1)%pt(i,j,k) = cp_air*atm(1)%pt(i,j,k)/pt_coarse(i,j,k)*
virq(atm(1)%q(i,j,k,:))
1165 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))
1172 if (atm(1)%bd%je == atm(1)%npy-1)
then 1173 if (atm(1)%bd%is == 1)
then 1174 istart = atm(1)%bd%is
1176 istart = atm(1)%bd%isd
1178 if (atm(1)%bd%ie == atm(1)%npx-1)
then 1181 iend = atm(1)%bd%ied
1185 do j=atm(1)%npy,atm(1)%bd%jed
1188 atm(1)%pt(i,j,k) = cp_air*atm(1)%pt(i,j,k)/pt_coarse(i,j,k)*
virq(atm(1)%q(i,j,k,:))
1190 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))
1197 deallocate(pt_coarse)
1201 if (.not. atm(1)%flagstruct%hydrostatic)
then 1206 if (any(atm(1)%parent_grid%pelist == gid) .and. atm(1)%neststruct%parent_tile == atm(1)%parent_grid%tile)
then 1207 call mpp_global_field( &
1208 atm(1)%parent_grid%domain, &
1209 atm(1)%parent_grid%delz(isd_p:ied_p,jsd_p:jed_p,:), g_dat, position=center)
1210 if (gid == sending_proc)
then 1211 do p=1,
size(atm(1)%pelist)
1212 call mpp_send(g_dat,
size(g_dat),atm(1)%pelist(p))
1216 if (any(atm(1)%pelist == gid))
then 1217 call mpp_recv(g_dat,
size(g_dat), sending_proc)
1224 atm(1)%neststruct%ind_h, atm(1)%neststruct%wt_h, &
1225 0, 0, isg, ieg, jsg, jeg, npz, atm(1)%bd)
1231 if (any(atm(1)%parent_grid%pelist == gid) .and. atm(1)%neststruct%parent_tile == atm(1)%parent_grid%tile)
then 1232 call mpp_global_field( &
1233 atm(1)%parent_grid%domain, &
1234 atm(1)%parent_grid%w(isd_p:ied_p,jsd_p:jed_p,:), g_dat, position=center)
1235 if (gid == sending_proc)
then 1236 do p=1,
size(atm(1)%pelist)
1237 call mpp_send(g_dat,
size(g_dat),atm(1)%pelist(p))
1241 if (any(atm(1)%pelist == gid))
then 1242 call mpp_recv(g_dat,
size(g_dat), sending_proc)
1249 atm(1)%neststruct%ind_h, atm(1)%neststruct%wt_h, &
1250 0, 0, isg, ieg, jsg, jeg, npz, atm(1)%bd)
1260 allocate(g_dat( isg:ieg, jsg:jeg+1, npz) )
1265 if (any(atm(1)%parent_grid%pelist == gid) .and. atm(1)%neststruct%parent_tile == atm(1)%parent_grid%tile)
then 1266 call mpp_global_field( &
1267 atm(1)%parent_grid%domain, &
1268 atm(1)%parent_grid%u(isd_p:ied_p,jsd_p:jed_p+1,:), g_dat, position=north)
1269 if (gid == sending_proc)
then 1270 do p=1,
size(atm(1)%pelist)
1271 call mpp_send(g_dat,
size(g_dat),atm(1)%pelist(p))
1275 if (any(atm(1)%pelist == gid))
then 1276 call mpp_recv(g_dat,
size(g_dat), sending_proc)
1284 atm(1)%neststruct%ind_u, atm(1)%neststruct%wt_u, &
1285 0, 1, isg, ieg, jsg, jeg, npz, atm(1)%bd)
1290 allocate(g_dat( isg:ieg+1, jsg:jeg, npz) )
1295 if (any(atm(1)%parent_grid%pelist == gid) .and. atm(1)%neststruct%parent_tile == atm(1)%parent_grid%tile)
then 1296 call mpp_global_field( &
1297 atm(1)%parent_grid%domain, &
1298 atm(1)%parent_grid%v(isd_p:ied_p+1,jsd_p:jed_p,:), g_dat, position=east)
1299 if (gid == sending_proc)
then 1300 do p=1,
size(atm(1)%pelist)
1301 call mpp_send(g_dat,
size(g_dat),atm(1)%pelist(p))
1305 if (any(atm(1)%pelist == gid))
then 1306 call mpp_recv(g_dat,
size(g_dat), sending_proc)
1313 atm(1)%neststruct%ind_v, atm(1)%neststruct%wt_v, &
1314 1, 0, isg, ieg, jsg, jeg, npz, atm(1)%bd)
1323 type(fv_atmos_type),
intent(INOUT) :: Atm
1324 logical,
intent(IN),
OPTIONAL :: proc_in
1325 real,
allocatable :: g_dat(:,:,:), pt_coarse(:,:,:)
1326 integer :: i,j,k,nq, sphum, ncnst, istart, iend, npz
1327 integer :: isc, iec, jsc, jec, isd, ied, jsd, jed
1328 integer :: isd_p, ied_p, jsd_p, jed_p, isc_p, iec_p, jsc_p, jec_p
1329 integer :: isg, ieg, jsg,jeg, npx_p, npy_p
1330 integer :: isg_n, ieg_n, jsg_n, jeg_n, npx_n, npy_n
1333 integer :: p , sending_proc
1336 if (
present(proc_in))
then 1347 isc = atm%bd%isc; iec = atm%bd%iec; jsc = atm%bd%jsc; jec = atm%bd%jec
1350 isd_p = atm%parent_grid%bd%isd
1351 ied_p = atm%parent_grid%bd%ied
1352 jsd_p = atm%parent_grid%bd%jsd
1353 jed_p = atm%parent_grid%bd%jed
1354 isc_p = atm%parent_grid%bd%isc
1355 iec_p = atm%parent_grid%bd%iec
1356 jsc_p = atm%parent_grid%bd%jsc
1357 jec_p = atm%parent_grid%bd%jec
1358 sending_proc = atm%parent_grid%pelist(1) + (atm%neststruct%parent_tile-1)*atm%parent_grid%npes_per_tile
1360 call mpp_get_global_domain( atm%parent_grid%domain, &
1361 isg, ieg, jsg, jeg, xsize=npx_p, ysize=npy_p)
1366 if ( process )
call mpp_update_domains(atm%phis, atm%domain, complete=.true.)
1367 if (atm%neststruct%twowaynest)
then 1368 if (any(atm%parent_grid%pelist == mpp_pe()) .or. atm%neststruct%child_proc)
then 1370 atm%phis, atm%neststruct%nest_domain, &
1371 atm%neststruct%ind_update_h(isd_p:ied_p+1,jsd_p:jed_p+1,:), &
1372 atm%gridstruct%dx, atm%gridstruct%dy, atm%gridstruct%area, &
1373 isd_p, ied_p, jsd_p, jed_p, isd, ied, jsd, jed, &
1374 atm%neststruct%isu, atm%neststruct%ieu, atm%neststruct%jsu, atm%neststruct%jeu, &
1375 atm%npx, atm%npy, 0, 0, &
1376 atm%neststruct%refinement, atm%neststruct%nestupdate, 0, 0, &
1377 atm%neststruct%parent_proc, atm%neststruct%child_proc, atm%parent_grid)
1378 atm%parent_grid%neststruct%parent_of_twoway = .true.
1383 if (atm%neststruct%parent_proc)
call mpp_update_domains(atm%parent_grid%phis, atm%parent_grid%domain)
1405 if (process)
call p_var(npz, isc, iec, jsc, jec, atm%ptop,
ptop_min, atm%delp, &
1406 atm%delz, atm%pt, atm%ps, &
1407 atm%pe, atm%peln, atm%pk, atm%pkz, kappa, atm%q, &
1408 atm%ng, ncnst, atm%gridstruct%area_64, atm%flagstruct%dry_mass, .false., atm%flagstruct%mountain, &
1409 atm%flagstruct%moist_phys, .true., atm%flagstruct%nwat, atm%domain)
1421 character(len=*),
intent(in) :: timestamp
1422 logical,
intent(IN) :: grids_on_this_pe(:)
1427 if (atm(n)%neststruct%nested .and. grids_on_this_pe(n))
then 1439 logical,
intent(INOUT) :: grids_on_this_pe(:)
1441 integer :: isc, iec, jsc, jec
1442 integer :: iq, n, ntileme, ncnst, ntprog, ntdiag
1443 integer :: isd, ied, jsd, jed, npz
1445 integer :: file_unit
1446 integer,
allocatable :: pelist(:)
1447 character(len=128):: tracer_name
1448 character(len=3):: gn
1451 ntileme =
size(atm(:))
1455 if (.not. grids_on_this_pe(n))
then 1459 call mpp_set_current_pelist(atm(n)%pelist)
1461 isc = atm(n)%bd%isc; iec = atm(n)%bd%iec; jsc = atm(n)%bd%jsc; jec = atm(n)%bd%jec
1468 ncnst = atm(n)%ncnst
1469 ntprog =
size(atm(n)%q,4)
1470 ntdiag =
size(atm(n)%qdiag,4)
1472 if (atm(n)%grid_number > 1)
then 1473 write(gn,
'(A2, I1)')
" g", atm(n)%grid_number
1480 write(unit,*)
'fv_restart_end u ', trim(gn),
' = ', mpp_chksum(atm(n)%u(isc:iec,jsc:jec,:))
1481 write(unit,*)
'fv_restart_end v ', trim(gn),
' = ', mpp_chksum(atm(n)%v(isc:iec,jsc:jec,:))
1482 if ( .not. atm(n)%flagstruct%hydrostatic ) &
1483 write(unit,*)
'fv_restart_end w ', trim(gn),
' = ', mpp_chksum(atm(n)%w(isc:iec,jsc:jec,:))
1484 write(unit,*)
'fv_restart_end delp', trim(gn),
' = ', mpp_chksum(atm(n)%delp(isc:iec,jsc:jec,:))
1485 write(unit,*)
'fv_restart_end phis', trim(gn),
' = ', mpp_chksum(atm(n)%phis(isc:iec,jsc:jec))
1487 write(unit,*)
'fv_restart_end pt ', trim(gn),
' = ', mpp_chksum(atm(n)%pt(isc:iec,jsc:jec,:))
1489 write(unit,*)
'fv_restart_end q(prog) nq ', trim(gn),
' =',ntprog, mpp_chksum(atm(n)%q(isc:iec,jsc:jec,:,:))
1491 write(unit,*)
'fv_restart_end q(diag) nq ', trim(gn),
' =',ntdiag, mpp_chksum(atm(n)%qdiag(isc:iec,jsc:jec,:,:))
1492 do iq=1,min(17, ntprog)
1493 call get_tracer_names(model_atmos, iq, tracer_name)
1494 write(unit,*)
'fv_restart_end '//trim(tracer_name)// trim(gn),
' = ', mpp_chksum(atm(n)%q(isc:iec,jsc:jec,:,iq))
1501 call pmaxmn_g(
'ZS', atm(n)%phis, isc, iec, jsc, jec, 1, 1./grav, atm(n)%gridstruct%area_64, atm(n)%domain)
1502 call pmaxmn_g(
'PS ', atm(n)%ps, isc, iec, jsc, jec, 1, 0.01 , atm(n)%gridstruct%area_64, atm(n)%domain)
1503 call prt_maxmin(
'PS*', atm(n)%ps, isc, iec, jsc, jec, atm(n)%ng, 1, 0.01)
1504 call prt_maxmin(
'U ', atm(n)%u(isd:ied,jsd:jed,1:npz), isc, iec, jsc, jec, atm(n)%ng, npz, 1.)
1505 call prt_maxmin(
'V ', atm(n)%v(isd:ied,jsd:jed,1:npz), isc, iec, jsc, jec, atm(n)%ng, npz, 1.)
1506 if ( .not. atm(n)%flagstruct%hydrostatic ) &
1507 call prt_maxmin(
'W ', atm(n)%w , isc, iec, jsc, jec, atm(n)%ng, npz, 1.)
1508 call prt_maxmin(
'T ', atm(n)%pt, isc, iec, jsc, jec, atm(n)%ng, npz, 1.)
1510 call get_tracer_names ( model_atmos, iq, tracer_name )
1511 call pmaxmn_g(trim(tracer_name), atm(n)%q(isd:ied,jsd:jed,1:npz,iq:iq), isc, iec, jsc, jec, npz, &
1512 1., atm(n)%gridstruct%area_64, atm(n)%domain)
1521 if (atm(n)%neststruct%nested .and. grids_on_this_pe(n))
call fv_io_write_bcs(atm(n))
1527 if( is_master() )
then 1528 write(*,*) steps,
'Mean equivalent Heat flux for this integration period=',atm(1)%idiag%efx_sum/
real(max(1,Atm(1)%idiag%steps)), &
1529 'Mean nesting-related flux for this integration period=',atm(1)%idiag%efx_sum_nest/
real(max(1,Atm(1)%idiag%steps)), &
1530 'Mean mountain torque=',atm(1)%idiag%mtq_sum/
real(max(1,atm(1)%idiag%steps))
1531 file_unit = get_unit()
1532 open (unit=file_unit, file=
'e_flux.data', form=
'unformatted',status=
'unknown', access=
'sequential')
1534 write(file_unit) atm(1)%idiag%efx(n)
1535 write(file_unit) atm(1)%idiag%mtq(n)
1538 close(unit=file_unit)
1547 isd,ied,jsd,jed, is,ie,js,je, npx,npy, &
1548 grid_type, nested, &
1549 se_corner, sw_corner, ne_corner, nw_corner, &
1550 rsin_u,rsin_v,cosa_s,rsin2,regional )
1552 logical,
intent(in):: dord4
1553 real,
intent(in) :: u(isd:ied,jsd:jed+1)
1554 real,
intent(in) :: v(isd:ied+1,jsd:jed)
1555 real,
intent(out),
dimension(isd:ied ,jsd:jed ):: ua
1556 real,
intent(out),
dimension(isd:ied ,jsd:jed ):: va
1557 real,
intent(out),
dimension(isd:ied+1,jsd:jed ):: uc
1558 real,
intent(out),
dimension(isd:ied ,jsd:jed+1):: vc
1559 integer,
intent(in) :: isd,ied,jsd,jed, is,ie,js,je, npx,npy,grid_type
1560 logical,
intent(in) :: nested, se_corner, sw_corner, ne_corner, nw_corner, regional
1561 real,
intent(in) :: rsin_u(isd:ied+1,jsd:jed)
1562 real,
intent(in) :: rsin_v(isd:ied,jsd:jed+1)
1563 real,
intent(in) :: cosa_s(isd:ied,jsd:jed)
1564 real,
intent(in) :: rsin2(isd:ied,jsd:jed)
1567 real,
dimension(isd:ied,jsd:jed):: utmp, vtmp
1568 real,
parameter:: t11=27./28., t12=-13./28., t13=3./7., t14=6./7., t15=3./28.
1569 real,
parameter:: a1 = 0.5625
1570 real,
parameter:: a2 = -0.0625
1571 real,
parameter:: c1 = -2./14.
1572 real,
parameter:: c2 = 11./14.
1573 real,
parameter:: c3 = 5./14.
1574 integer npt, i, j, ifirst, ilast, id
1583 if (grid_type < 3 .and. .not. (nested .or. regional))
then 1593 utmp(i,j) = a2*(u(i,j-1)+u(i,j+2)) + a1*(u(i,j)+u(i,j+1))
1598 utmp(i,j) = 0.5*(u(i,j)+u(i,j+1))
1600 utmp(i,j) = 0.5*(u(i,j)+u(i,j+1))
1605 vtmp(i,j) = a2*(v(i-1,j)+v(i+2,j)) + a1*(v(i,j)+v(i+1,j))
1608 vtmp(i,j) = 0.5*(v(i,j)+v(i+1,j))
1610 vtmp(i,j) = 0.5*(v(i,j)+v(i+1,j))
1615 ua(i,j) = (utmp(i,j)-vtmp(i,j)*cosa_s(i,j)) * rsin2(i,j)
1616 va(i,j) = (vtmp(i,j)-utmp(i,j)*cosa_s(i,j)) * rsin2(i,j)
1629 do j=max(npt,js-1),min(npy-npt,je+1)
1630 do i=max(npt,isd),min(npx-npt,ied)
1631 utmp(i,j) = a2*(u(i,j-1)+u(i,j+2)) + a1*(u(i,j)+u(i,j+1))
1634 do j=max(npt,jsd),min(npy-npt,jed)
1635 do i=max(npt,is-1),min(npx-npt,ie+1)
1636 vtmp(i,j) = a2*(v(i-1,j)+v(i+2,j)) + a1*(v(i,j)+v(i+1,j))
1643 if (grid_type < 3)
then 1645 if ( js==1 .or. jsd<npt)
then 1648 utmp(i,j) = 0.5*(u(i,j) + u(i,j+1))
1649 vtmp(i,j) = 0.5*(v(i,j) + v(i+1,j))
1654 if ( (je+1)==npy .or. jed>=(npy-npt))
then 1657 utmp(i,j) = 0.5*(u(i,j) + u(i,j+1))
1658 vtmp(i,j) = 0.5*(v(i,j) + v(i+1,j))
1663 if ( is==1 .or. isd<npt )
then 1664 do j=max(npt,jsd),min(npy-npt,jed)
1666 utmp(i,j) = 0.5*(u(i,j) + u(i,j+1))
1667 vtmp(i,j) = 0.5*(v(i,j) + v(i+1,j))
1672 if ( (ie+1)==npx .or. ied>=(npx-npt))
then 1673 do j=max(npt,jsd),min(npy-npt,jed)
1675 utmp(i,j) = 0.5*(u(i,j) + u(i,j+1))
1676 vtmp(i,j) = 0.5*(v(i,j) + v(i+1,j))
1682 do j=js-1-id,je+1+id
1683 do i=is-1-id,ie+1+id
1684 ua(i,j) = (utmp(i,j)-vtmp(i,j)*cosa_s(i,j)) * rsin2(i,j)
1685 va(i,j) = (vtmp(i,j)-utmp(i,j)*cosa_s(i,j)) * rsin2(i,j)
1696 if( sw_corner )
then 1698 utmp(i,0) = -vtmp(0,1-i)
1701 if( se_corner )
then 1703 utmp(npx+i,0) = vtmp(npx,i+1)
1706 if( ne_corner )
then 1708 utmp(npx+i,npy) = -vtmp(npx,je-i)
1711 if( nw_corner )
then 1713 utmp(i,npy) = vtmp(0,je+i)
1717 if (grid_type < 3 .and. .not. (nested .or. regional))
then 1718 ifirst = max(3, is-1)
1719 ilast = min(npx-2,ie+2)
1729 uc(i,j) = a1*(utmp(i-1,j)+utmp(i,j))+a2*(utmp(i-2,j)+utmp(i+1,j))
1733 if (grid_type < 3)
then 1735 if( is==1 .and. .not. (nested .or. regional) )
then 1737 uc(0,j) = c1*utmp(-2,j) + c2*utmp(-1,j) + c3*utmp(0,j)
1738 uc(1,j) = ( t14*(utmp( 0,j)+utmp(1,j)) &
1739 + t12*(utmp(-1,j)+utmp(2,j)) &
1740 + t15*(utmp(-2,j)+utmp(3,j)) )*rsin_u(1,j)
1741 uc(2,j) = c1*utmp(3,j) + c2*utmp(2,j) + c3*utmp(1,j)
1745 if( (ie+1)==npx .and. .not. (nested .or. regional) )
then 1747 uc(npx-1,j) = c1*utmp(npx-3,j)+c2*utmp(npx-2,j)+c3*utmp(npx-1,j)
1748 uc(npx,j) = (t14*(utmp(npx-1,j)+utmp(npx,j))+ &
1749 t12*(utmp(npx-2,j)+utmp(npx+1,j)) &
1750 + t15*(utmp(npx-3,j)+utmp(npx+2,j)))*rsin_u(npx,j)
1751 uc(npx+1,j) = c3*utmp(npx,j)+c2*utmp(npx+1,j)+c1*utmp(npx+2,j)
1760 if( sw_corner )
then 1762 vtmp(0,j) = -utmp(1-j,0)
1765 if( nw_corner )
then 1767 vtmp(0,npy+j) = utmp(j+1,npy)
1770 if( se_corner )
then 1772 vtmp(npx,j) = utmp(ie+j,0)
1775 if( ne_corner )
then 1777 vtmp(npx,npy+j) = -utmp(ie-j,npy)
1781 if (grid_type < 3)
then 1784 if ( j==1 .and. .not. (nested .or. regional))
then 1786 vc(i,1) = (t14*(vtmp(i, 0)+vtmp(i,1)) &
1787 + t12*(vtmp(i,-1)+vtmp(i,2)) &
1788 + t15*(vtmp(i,-2)+vtmp(i,3)))*rsin_v(i,1)
1790 elseif ( (j==0 .or. j==(npy-1)) .and. .not. (nested .or. regional))
then 1792 vc(i,j) = c1*vtmp(i,j-2) + c2*vtmp(i,j-1) + c3*vtmp(i,j)
1794 elseif ( (j==2 .or. j==(npy+1)) .and. .not. (nested .or. regional))
then 1796 vc(i,j) = c1*vtmp(i,j+1) + c2*vtmp(i,j) + c3*vtmp(i,j-1)
1798 elseif ( j==npy .and. .not. (nested .or. regional))
then 1800 vc(i,npy) = (t14*(vtmp(i,npy-1)+vtmp(i,npy)) &
1801 + t12*(vtmp(i,npy-2)+vtmp(i,npy+1)) &
1802 + t15*(vtmp(i,npy-3)+vtmp(i,npy+2)))*rsin_v(i,npy)
1807 vc(i,j) = a2*(vtmp(i,j-2)+vtmp(i,j+1))+a1*(vtmp(i,j-1)+vtmp(i,j))
1815 vc(i,j) = a2*(vtmp(i,j-2)+vtmp(i,j+1))+a1*(vtmp(i,j-1)+vtmp(i,j))
1822 subroutine d2a_setup(u, v, ua, va, dord4, &
1823 isd,ied,jsd,jed, is,ie,js,je, npx,npy, &
1824 grid_type, nested, &
1825 cosa_s,rsin2,regional )
1827 logical,
intent(in):: dord4
1828 real,
intent(in) :: u(isd:ied,jsd:jed+1)
1829 real,
intent(in) :: v(isd:ied+1,jsd:jed)
1830 real,
intent(out),
dimension(isd:ied ,jsd:jed ):: ua
1831 real,
intent(out),
dimension(isd:ied ,jsd:jed ):: va
1832 integer,
intent(in) :: isd,ied,jsd,jed, is,ie,js,je, npx,npy,grid_type
1833 real,
intent(in) :: cosa_s(isd:ied,jsd:jed)
1834 real,
intent(in) :: rsin2(isd:ied,jsd:jed)
1835 logical,
intent(in) :: nested, regional
1838 real,
dimension(isd:ied,jsd:jed):: utmp, vtmp
1839 real,
parameter:: t11=27./28., t12=-13./28., t13=3./7., t14=6./7., t15=3./28.
1840 real,
parameter:: a1 = 0.5625
1841 real,
parameter:: a2 = -0.0625
1842 real,
parameter:: c1 = -2./14.
1843 real,
parameter:: c2 = 11./14.
1844 real,
parameter:: c3 = 5./14.
1845 integer npt, i, j, ifirst, ilast, id
1854 if (grid_type < 3 .and. .not. (nested .or. regional))
then 1864 utmp(i,j) = a2*(u(i,j-1)+u(i,j+2)) + a1*(u(i,j)+u(i,j+1))
1869 utmp(i,j) = 0.5*(u(i,j)+u(i,j+1))
1871 utmp(i,j) = 0.5*(u(i,j)+u(i,j+1))
1876 vtmp(i,j) = a2*(v(i-1,j)+v(i+2,j)) + a1*(v(i,j)+v(i+1,j))
1879 vtmp(i,j) = 0.5*(v(i,j)+v(i+1,j))
1881 vtmp(i,j) = 0.5*(v(i,j)+v(i+1,j))
1890 do j=max(npt,js-1),min(npy-npt,je+1)
1891 do i=max(npt,isd),min(npx-npt,ied)
1892 utmp(i,j) = a2*(u(i,j-1)+u(i,j+2)) + a1*(u(i,j)+u(i,j+1))
1895 do j=max(npt,jsd),min(npy-npt,jed)
1896 do i=max(npt,is-1),min(npx-npt,ie+1)
1897 vtmp(i,j) = a2*(v(i-1,j)+v(i+2,j)) + a1*(v(i,j)+v(i+1,j))
1904 if (grid_type < 3)
then 1906 if ( js==1 .or. jsd<npt)
then 1909 utmp(i,j) = 0.5*(u(i,j) + u(i,j+1))
1910 vtmp(i,j) = 0.5*(v(i,j) + v(i+1,j))
1915 if ( (je+1)==npy .or. jed>=(npy-npt))
then 1918 utmp(i,j) = 0.5*(u(i,j) + u(i,j+1))
1919 vtmp(i,j) = 0.5*(v(i,j) + v(i+1,j))
1924 if ( is==1 .or. isd<npt )
then 1925 do j=max(npt,jsd),min(npy-npt,jed)
1927 utmp(i,j) = 0.5*(u(i,j) + u(i,j+1))
1928 vtmp(i,j) = 0.5*(v(i,j) + v(i+1,j))
1933 if ( (ie+1)==npx .or. ied>=(npx-npt))
then 1934 do j=max(npt,jsd),min(npy-npt,jed)
1936 utmp(i,j) = 0.5*(u(i,j) + u(i,j+1))
1937 vtmp(i,j) = 0.5*(v(i,j) + v(i+1,j))
1948 do j=js-1-id,je+1+id
1949 do i=is-1-id,ie+1+id
1950 ua(i,j) = (utmp(i,j)-vtmp(i,j)*cosa_s(i,j)) * rsin2(i,j)
1951 va(i,j) = (vtmp(i,j)-utmp(i,j)*cosa_s(i,j)) * rsin2(i,j)
1958 subroutine pmaxmn_g(qname, q, is, ie, js, je, km, fac, area, domain)
1959 character(len=*),
intent(in):: qname
1960 integer,
intent(in):: is, ie, js, je
1961 integer,
intent(in):: km
1962 real,
intent(in):: q(is-3:ie+3, js-3:je+3, km)
1963 real,
intent(in):: fac
1964 real(kind=R_GRID),
intent(IN):: area(is-3:ie+3, js-3:je+3)
1965 type(domain2d),
intent(INOUT) :: domain
1967 real qmin, qmax, gmean
1976 if( q(i,j,k) < qmin )
then 1978 elseif( q(i,j,k) > qmax )
then 1985 call mp_reduce_min(qmin)
1986 call mp_reduce_max(qmax)
1988 gmean =
g_sum(domain, q(is:ie,js:je,km), is, ie, js, je, 3, area, 1, .true.)
1989 if(is_master())
write(6,*) qname, qmax*fac, qmin*fac, gmean*fac
subroutine, public fv_io_read_bcs(Atm)
The subroutine 'fv_io_read_BCs' reads BCs from a restart file.
subroutine, public fv_restart(fv_domain, Atm, dt_atmos, seconds, days, cold_start, grid_type, grids_on_this_pe)
The subroutine 'fv_restart' initializes the model state, including prognaostic variables and several ...
subroutine, public del2_cubed_sphere(npx, npy, q, area, dx, dy, dxc, dyc, sin_sg, nmax, cd, zero_ocean, oro, nested, domain, bd, regional)
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)
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)
The module 'fv_mp_mod' is a single program multiple data (SPMD) parallel decompostion/communication m...
subroutine timing_off(blk_name)
The subroutine 'timing_off' stops a timer.
subroutine, public fv_write_restart(Atm, grids_on_this_pe, timestamp)
The subroutine 'fv_write_restart' writes restart files to disk.
subroutine, public fv_restart_end(Atm, grids_on_this_pe)
The subroutine 'fv_restart_end' writes ending restart files, terminates I/O, and prints out diagnosti...
logical module_is_initialized
The interface'update_coarse_grid_mpp'contains subroutines that fetch data from the nested grid and in...
subroutine fill_nested_grid_data(Atm, proc_in)
subroutine, public fv_io_write_restart(Atm, grids_on_this_pe, timestamp)
The subroutine 'fv_io_write_restart' writes restart files.
subroutine, public fv_io_init()
Initialize the fv core restart facilities.
real(kind=r_grid), parameter cnst_0p20
The module 'multi_gases' peforms multi constitutents computations.
subroutine, public set_hybrid_z(is, ie, js, je, ng, km, ztop, dz, rgrav, hs, ze, dz3)
integer, public test_case
subroutine, public del4_cubed_sphere(npx, npy, q, area, dx, dy, dxc, dyc, sin_sg, nmax, zero_ocean, oro, nested, domain, bd, regional)
real function, public g_sum(domain, p, ifirst, ilast, jfirst, jlast, ngc, area, mode, reproduce)
The function 'g_sum' is the fast version of 'globalsum'.
subroutine, public fv_io_read_restart(fv_domain, Atm)
Write the fv core restart quantities.
The module 'fv_io' contains restart facilities for FV core.
integer, parameter, public r_grid
subroutine, public fv_io_register_restart(fv_domain, Atm)
The subroutine 'fv_io_register_restart' registers model restart fields.
subroutine, public fv_io_register_restart_bcs(Atm)
The subroutine 'fv_io_register_restart_BCs' registers restarts for nested-grid boundary conditions...
subroutine, public make_eta_level(km, pe, area, kks, ak, bk, ptop, domain, bd)
The module 'fv_timing' contains FV3 timers.
pure real function, public virq(q)
The module 'boundary' contains utility routines for grid nesting and boundary conditions.
subroutine, public fv_restart_init()
subroutine fill_nested_grid_topo(Atm, proc_in)
The subroutine 'fill_nested_grid_topo' fills the nested grid with topo to enable boundary smoothing...
real, parameter, public ptop_min
subroutine, public compute_dz_l32(km, ztop, dz)
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, regional)
subroutine, public setup_nested_boundary_halo(Atm, proc_in)
The module 'fv_arrays' contains the 'fv_atmos_type' and associated datatypes.
real function, public great_circle_dist(q1, q2, radius)
interface 'nested_grid_BC' includes subroutines 'nested_grid_BC_2d' and 'nested_grid_BC_3d' that fetc...
The module 'fv_eta' contains routine to set up the reference (Eulerian) pressure coordinate.
The module 'external_ic_mod' contains routines that read in and remap initial conditions.
subroutine, public fv_io_write_bcs(Atm, timestamp)
The subroutine 'fv_io_write_BCs' writes BCs to a restart file.
subroutine, public compute_dz_var(km, ztop, dz)
The interface 'fill_nested_grid' includes subroutines 'fill_nested_grid_2d' and 'fill_nested_grid_3d'...
'The module 'tread_da_increment' contains routines for treating the increments of the prognostic vari...
real, dimension(:,:), allocatable, public sgh_g
subroutine timing_on(blk_name)
The subroutine 'timing_on' starts a timer.
subroutine fill_nested_grid_data_end(Atm, proc_in)
The subroutine ' fill_nested_grid_data_end' actually sets up the coarse-grid TOPOGRAPHY.
@ The module 'fv_diagnostics' contains routines to compute diagnosic fields.
subroutine, public fv_io_register_nudge_restart(Atm)
The subroutine 'fv_io_register_nudge_restart' registers restarts for SST fields used in HiRAM...
The module 'fv_grid_utils' contains routines for setting up and computing grid-related quantities...
real, dimension(:,:), allocatable, public oro_g
subroutine, public prt_maxmin(qname, q, is, ie, js, je, n_g, km, fac)
subroutine, public get_cubed_sphere_terrain(Atm, fv_domain)
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)
subroutine, public read_da_inc(Atm, fv_domain)
The subroutine 'read_da_inc' reads the increments of the diagnostic variables from the DA-generated f...
subroutine, public get_external_ic(Atm, fv_domain, cold_start)
subroutine, public cubed_to_latlon(u, v, ua, va, gridstruct, npx, npy, km, mode, grid_type, domain, nested, c2l_ord, bd)
subroutine fill_nested_grid_topo_halo(Atm, proc_in)
subroutine, public remap_restart(fv_domain, Atm)
The subroutine 'remap_restart' remaps the model state from remap files to a new set of Eulerian coord...
subroutine pmaxmn_g(qname, q, is, ie, js, je, km, fac, area, domain)
The subroutine 'pmaxn_g' writes domain max, min, and averages quantities.
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, regional)
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)
the subroutine 'p_var' computes auxiliary pressure variables for a hydrostatic state.
subroutine, public fv_io_register_restart_bcs_nh(Atm)