Skip to content

Commit

Permalink
2D advection of cellular automata (#686)
Browse files Browse the repository at this point in the history
* 2D advection of cellular automata
  • Loading branch information
lisa-bengtsson authored Sep 5, 2023
1 parent d9525db commit 379ef21
Show file tree
Hide file tree
Showing 4 changed files with 30 additions and 4 deletions.
2 changes: 1 addition & 1 deletion atmos_model.F90
Original file line number Diff line number Diff line change
Expand Up @@ -748,7 +748,7 @@ subroutine atmos_model_init (Atmos, Time_init, Time, Time_step)
call fv3atm_restart_read (GFS_data, GFS_restart_var, Atm_block, GFS_control, Atmos%domain_for_read, &
Atm(mygrid)%flagstruct%warm_start, ignore_rst_cksum)
if(GFS_control%do_ca .and. Atm(mygrid)%flagstruct%warm_start)then
call read_ca_restart (Atmos%domain,GFS_control%ncells,GFS_control%nca,GFS_control%ncells_g,GFS_control%nca_g)
call read_ca_restart (Atmos%domain,3,GFS_control%ncells,GFS_control%nca,GFS_control%ncells_g,GFS_control%nca_g)
endif
! Populate the GFS_data%Statein container with the prognostic state
! in Atm_block, which contains the initial conditions/restart data.
Expand Down
6 changes: 5 additions & 1 deletion ccpp/data/GFS_typedefs.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1328,6 +1328,7 @@ module GFS_typedefs
integer :: nseed !< cellular automata seed frequency
integer :: nseed_g !< cellular automata seed frequency
logical :: do_ca !< cellular automata main switch
logical :: ca_advect !< Advection of cellular automata
logical :: ca_sgs !< switch for sgs ca
logical :: ca_global !< switch for global ca
logical :: ca_smooth !< switch for gaussian spatial filter
Expand Down Expand Up @@ -3765,6 +3766,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
integer :: iseed_ca = 1
integer :: nspinup = 1
logical :: do_ca = .false.
logical :: ca_advect = .false.
logical :: ca_sgs = .false.
logical :: ca_global = .false.
logical :: ca_smooth = .false.
Expand Down Expand Up @@ -3974,7 +3976,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
h0facu, h0facs, &
!--- cellular automata
nca, ncells, nlives, nca_g, ncells_g, nlives_g, nfracseed, &
nseed, nseed_g, nthresh, do_ca, &
nseed, nseed_g, nthresh, do_ca, ca_advect, &
ca_sgs, ca_global,iseed_ca,ca_smooth, &
nspinup,ca_amplitude,nsmooth,ca_closure,ca_entr,ca_trigger, &
!--- IAU
Expand Down Expand Up @@ -4943,6 +4945,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
Model%nseed_g = nseed_g
Model%ca_global = ca_global
Model%do_ca = do_ca
Model%ca_advect = ca_advect
Model%ca_sgs = ca_sgs
Model%iseed_ca = iseed_ca
Model%ca_smooth = ca_smooth
Expand Down Expand Up @@ -6705,6 +6708,7 @@ subroutine control_print(Model)
print *, ' ca_global : ', Model%ca_global
print *, ' ca_sgs : ', Model%ca_sgs
print *, ' do_ca : ', Model%do_ca
print *, ' ca_advect : ', Model%ca_advect
print *, ' iseed_ca : ', Model%iseed_ca
print *, ' ca_smooth : ', Model%ca_smooth
print *, ' nspinup : ', Model%nspinup
Expand Down
6 changes: 6 additions & 0 deletions ccpp/data/GFS_typedefs.meta
Original file line number Diff line number Diff line change
Expand Up @@ -5698,6 +5698,12 @@
units = flag
dimensions = ()
type = logical
[ca_advect]
standard_name = flag_for_cellular_automata_advection
long_name = cellular automata main switch
units = flag
dimensions = ()
type = logical
[ca_sgs]
standard_name = flag_for_sgs_cellular_automata
long_name = switch for sgs ca
Expand Down
20 changes: 18 additions & 2 deletions stochastic_physics/stochastic_physics_wrapper.F90
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,10 @@ module stochastic_physics_wrapper_mod
real(kind=kind_phys), dimension(:,:), allocatable, save :: sst
real(kind=kind_phys), dimension(:,:), allocatable, save :: lmsk
real(kind=kind_phys), dimension(:,:), allocatable, save :: lake
real(kind=kind_phys), dimension(:,:,:), allocatable, save :: uwind
real(kind=kind_phys), dimension(:,:,:), allocatable, save :: vwind
real(kind=kind_phys), dimension(:,:,:), allocatable, save :: height
real(kind=kind_phys), dimension(:,:), allocatable, save :: dx
real(kind=kind_phys), dimension(:,:), allocatable, save :: condition
real(kind=kind_phys), dimension(:,:), allocatable, save :: ca_deep_cpl, ca_turb_cpl, ca_shal_cpl
real(kind=kind_phys), dimension(:,:), allocatable, save :: ca1_cpl, ca2_cpl, ca3_cpl
Expand Down Expand Up @@ -189,7 +193,11 @@ subroutine stochastic_physics_wrapper (GFS_Control, GFS_Data, Atm_block, ierr)
allocate(sst (1:nblks, maxblk))
allocate(lmsk (1:nblks, maxblk))
allocate(lake (1:nblks, maxblk))
allocate(uwind (1:nblks, maxblk, 1:levs))
allocate(vwind (1:nblks, maxblk, 1:levs))
allocate(height (1:nblks, maxblk, 1:levs))
allocate(condition (1:nblks, maxblk))
allocate(dx (1:nblks, maxblk))
allocate(ca_deep_cpl (1:nblks, maxblk))
allocate(ca_turb_cpl (1:nblks, maxblk))
allocate(ca_shal_cpl (1:nblks, maxblk))
Expand Down Expand Up @@ -374,16 +382,20 @@ subroutine stochastic_physics_wrapper (GFS_Control, GFS_Data, Atm_block, ierr)
sst (nb,1:GFS_Control%blksz(nb)) = GFS_Data(nb)%Sfcprop%tsfco(:)
lmsk (nb,1:GFS_Control%blksz(nb)) = GFS_Data(nb)%Sfcprop%slmsk(:)
lake (nb,1:GFS_Control%blksz(nb)) = GFS_Data(nb)%Sfcprop%lakefrac(:)
uwind (nb,1:GFS_Control%blksz(nb),:) = GFS_Data(nb)%Statein%ugrs(:,:)
vwind (nb,1:GFS_Control%blksz(nb),:) = GFS_Data(nb)%Statein%vgrs(:,:)
height (nb,1:GFS_Control%blksz(nb),:) = GFS_Data(nb)%Statein%phil(:,:)
dx (nb,1:GFS_Control%blksz(nb)) = GFS_Data(nb)%Grid%dx(:)
condition (nb,1:GFS_Control%blksz(nb)) = GFS_Data(nb)%Coupling%condition(:)
ca_deep_cpl(nb,1:GFS_Control%blksz(nb)) = GFS_Data(nb)%Coupling%ca_deep(:)
ca_turb_cpl(nb,1:GFS_Control%blksz(nb)) = GFS_Data(nb)%Coupling%ca_turb(:)
ca_shal_cpl(nb,1:GFS_Control%blksz(nb)) = GFS_Data(nb)%Coupling%ca_shal(:)
enddo
call cellular_automata_sgs(GFS_Control%kdt,GFS_control%dtp,GFS_control%restart,GFS_Control%first_time_step, &
sst,lmsk,lake,condition,ca_deep_cpl,ca_turb_cpl,ca_shal_cpl, Atm(mygrid)%domain_for_coupler,nblks, &
sst,lmsk,lake,uwind,vwind,height,dx,condition,ca_deep_cpl,ca_turb_cpl,ca_shal_cpl, Atm(mygrid)%domain_for_coupler,nblks, &
Atm_block%isc,Atm_block%iec,Atm_block%jsc,Atm_block%jec,Atm(mygrid)%npx,Atm(mygrid)%npy, levs, &
GFS_Control%nthresh,GFS_Control%tile_num,GFS_Control%nca,GFS_Control%ncells,GFS_Control%nlives, &
GFS_Control%nfracseed, GFS_Control%nseed,GFS_Control%iseed_ca, &
GFS_Control%nfracseed, GFS_Control%nseed,GFS_Control%iseed_ca,GFS_Control%ca_advect, &
GFS_Control%nspinup,GFS_Control%ca_trigger,Atm_block%blksz(1),GFS_Control%master,GFS_Control%communicator)
! Copy contiguous data back as needed
do nb=1,nblks
Expand Down Expand Up @@ -461,6 +473,10 @@ subroutine stochastic_physics_wrapper_end (GFS_Control)
deallocate(sst )
deallocate(lmsk )
deallocate(lake )
deallocate(uwind )
deallocate(vwind )
deallocate(height )
deallocate(dx )
deallocate(condition )
deallocate(ca_deep_cpl )
deallocate(ca_turb_cpl )
Expand Down

0 comments on commit 379ef21

Please sign in to comment.