Skip to content

Commit

Permalink
Merge branch 'dev/gfdl' into ke_from_GV
Browse files Browse the repository at this point in the history
  • Loading branch information
Hallberg-NOAA committed Dec 3, 2020
2 parents 4075e74 + 19fecf2 commit 1267431
Show file tree
Hide file tree
Showing 22 changed files with 1,750 additions and 681 deletions.
23 changes: 17 additions & 6 deletions config_src/coupled_driver/ocean_model_MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -48,6 +48,7 @@ module ocean_model_mod
use MOM_verticalGrid, only : verticalGrid_type
use MOM_ice_shelf, only : initialize_ice_shelf, shelf_calc_flux, ice_shelf_CS
use MOM_ice_shelf, only : add_shelf_forces, ice_shelf_end, ice_shelf_save_restart
use MOM_IS_diag_mediator, only : diag_IS_ctrl => diag_ctrl, diag_mediator_IS_end=>diag_mediator_end
use coupler_types_mod, only : coupler_1d_bc_type, coupler_2d_bc_type
use coupler_types_mod, only : coupler_type_spawn, coupler_type_write_chksums
use coupler_types_mod, only : coupler_type_initialized, coupler_type_copy_data
Expand Down Expand Up @@ -181,13 +182,13 @@ module ocean_model_mod
!! processes before time stepping the dynamics.

type(directories) :: dirs !< A structure containing several relevant directory paths.
type(mech_forcing) :: forces !< A structure with the driving mechanical surface forces
type(forcing) :: fluxes !< A structure containing pointers to
!! the thermodynamic ocean forcing fields.
type(forcing) :: flux_tmp !< A secondary structure containing pointers to the
type(mech_forcing), pointer :: forces => NULL() !< A structure with the driving mechanical surface forces
type(forcing), pointer :: fluxes => NULL() !< A structure containing pointers to
!! the thermodynamic ocean forcing fields.
type(forcing), pointer :: flux_tmp => NULL() !< A secondary structure containing pointers to the
!! ocean forcing fields for when multiple coupled
!! timesteps are taken per thermodynamic step.
type(surface) :: sfc_state !< A structure containing pointers to
type(surface), pointer :: sfc_state => NULL() !< A structure containing pointers to
!! the ocean surface state fields.
type(ocean_grid_type), pointer :: &
grid => NULL() !< A pointer to a grid structure containing metrics
Expand Down Expand Up @@ -216,6 +217,9 @@ module ocean_model_mod
!! that will be used for MOM restart files.
type(diag_ctrl), pointer :: &
diag => NULL() !< A pointer to the diagnostic regulatory structure
type(diag_IS_ctrl), pointer :: &
diag_IS => NULL() !< A pointer to the diagnostic regulatory structure
!! for the ice shelf module.
end type ocean_state_type

contains
Expand Down Expand Up @@ -269,6 +273,10 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, wind_stagger, gas
endif
allocate(OS)

allocate(OS%fluxes)
allocate(OS%forces)
allocate(OS%flux_tmp)

OS%is_ocean_pe = Ocean_sfc%is_ocean_pe
if (.not.OS%is_ocean_pe) return

Expand Down Expand Up @@ -357,6 +365,7 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, wind_stagger, gas
use_melt_pot=.false.
endif

allocate(OS%sfc_state)
call allocate_surface_state(OS%sfc_state, OS%grid, use_temperature, do_integrals=.true., &
gas_fields_ocn=gas_fields_ocn, use_meltpot=use_melt_pot)

Expand All @@ -370,7 +379,7 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, wind_stagger, gas

if (OS%use_ice_shelf) then
call initialize_ice_shelf(param_file, OS%grid, OS%Time, OS%ice_shelf_CSp, &
OS%diag, OS%forces, OS%fluxes)
OS%diag_IS, OS%forces, OS%fluxes)
endif
if (OS%icebergs_alter_ocean) then
call marine_ice_init(OS%Time, OS%grid, param_file, OS%diag, OS%marine_ice_CSp)
Expand Down Expand Up @@ -719,6 +728,8 @@ subroutine ocean_model_end(Ocean_sfc, Ocean_state, Time)

call ocean_model_save_restart(Ocean_state, Time)
call diag_mediator_end(Time, Ocean_state%diag)
if (Ocean_state%use_ice_shelf) &
call diag_mediator_IS_end(Time, Ocean_state%diag_IS)
call MOM_end(Ocean_state%MOM_CSp)
if (Ocean_state%use_ice_shelf) call ice_shelf_end(Ocean_state%Ice_shelf_CSp)
end subroutine ocean_model_end
Expand Down
65 changes: 40 additions & 25 deletions config_src/solo_driver/MOM_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ program MOM_main
use MOM_cpu_clock, only : CLOCK_COMPONENT
use MOM_diag_mediator, only : enable_averaging, disable_averaging, diag_mediator_end
use MOM_diag_mediator, only : diag_ctrl, diag_mediator_close_registration
use MOM_IS_diag_mediator, only : diag_IS_ctrl=>diag_ctrl, diag_mediator_IS_end=>diag_mediator_end
use MOM, only : initialize_MOM, step_MOM, MOM_control_struct, MOM_end
use MOM, only : extract_surface_state, finish_MOM_initialization
use MOM, only : get_MOM_state_elements, MOM_state_is_synchronized
Expand Down Expand Up @@ -61,7 +62,7 @@ program MOM_main
use MOM_verticalGrid, only : verticalGrid_type
use MOM_write_cputime, only : write_cputime, MOM_write_cputime_init
use MOM_write_cputime, only : write_cputime_start_clock, write_cputime_CS

use MOM_get_input, only : get_MOM_input
use ensemble_manager_mod, only : ensemble_manager_init, get_ensemble_size
use ensemble_manager_mod, only : ensemble_pelist_setup
use mpp_mod, only : set_current_pelist => mpp_set_current_pelist
Expand All @@ -70,7 +71,6 @@ program MOM_main

use MOM_ice_shelf, only : initialize_ice_shelf, ice_shelf_end, ice_shelf_CS
use MOM_ice_shelf, only : shelf_calc_flux, add_shelf_forces, ice_shelf_save_restart
! , add_shelf_flux_forcing, add_shelf_flux_IOB

use MOM_wave_interface, only: wave_parameters_CS, MOM_wave_interface_init
use MOM_wave_interface, only: MOM_wave_interface_init_lite, Update_Surface_Waves
Expand All @@ -80,22 +80,22 @@ program MOM_main
#include <MOM_memory.h>

! A structure with the driving mechanical surface forces
type(mech_forcing) :: forces
type(mech_forcing), pointer :: forces => NULL()
! A structure containing pointers to the thermodynamic forcing fields
! at the ocean surface.
type(forcing) :: fluxes
type(forcing), pointer :: fluxes => NULL()

! A structure containing pointers to the ocean surface state fields.
type(surface) :: sfc_state
type(surface), pointer :: sfc_state => NULL()

! A pointer to a structure containing metrics and related information.
type(ocean_grid_type), pointer :: grid
type(verticalGrid_type), pointer :: GV
type(ocean_grid_type), pointer :: grid => NULL()
type(verticalGrid_type), pointer :: GV => NULL()
! A pointer to a structure containing dimensional unit scaling factors.
type(unit_scale_type), pointer :: US
type(unit_scale_type), pointer :: US => NULL()

! If .true., use the ice shelf model for part of the domain.
logical :: use_ice_shelf
logical :: use_ice_shelf = .false.

! If .true., use surface wave coupling
logical :: use_waves = .false.
Expand Down Expand Up @@ -198,8 +198,10 @@ program MOM_main
type(MOM_restart_CS), pointer :: &
restart_CSp => NULL() !< A pointer to the restart control structure
!! that will be used for MOM restart files.
type(diag_ctrl), pointer :: &
diag => NULL() !< A pointer to the diagnostic regulatory structure
type(diag_ctrl), pointer :: &
diag => NULL() !< A pointer to the diagnostic regulatory structure
type(diag_IS_ctrl), pointer :: &
diag_IS => NULL() !< A pointer to the diagnostic regulatory structure
!-----------------------------------------------------------------------

character(len=4), parameter :: vers_num = 'v2.0'
Expand All @@ -219,6 +221,8 @@ program MOM_main

call MOM_infra_init() ; call io_infra_init()

allocate(forces,fluxes,sfc_state)

! Initialize the ensemble manager. If there are no settings for ensemble_size
! in input.nml(ensemble.nml), these should not do anything. In coupled
! configurations, this all occurs in the external driver.
Expand Down Expand Up @@ -257,7 +261,7 @@ program MOM_main
!$ call omp_set_num_threads(ocean_nthreads)
!$OMP PARALLEL
!$ write(6,*) "ocean_solo OMPthreading ", fms_affinity_get(), omp_get_thread_num(), omp_get_num_threads()
!$ call flush(6)
!$ flush(6)
!$OMP END PARALLEL

! Read ocean_solo restart, which can override settings from the namelist.
Expand Down Expand Up @@ -297,16 +301,34 @@ program MOM_main
! In this case, the segment starts at a time fixed by ocean_solo.res
segment_start_time = set_date(date(1),date(2),date(3),date(4),date(5),date(6))
Time = segment_start_time
call initialize_MOM(Time, Start_time, param_file, dirs, MOM_CSp, restart_CSp, &
segment_start_time, offline_tracer_mode=offline_tracer_mode, &
diag_ptr=diag, tracer_flow_CSp=tracer_flow_CSp)
else
! In this case, the segment starts at a time read from the MOM restart file
! or left as Start_time by MOM_initialize.
Time = Start_time
endif

! Read paths and filenames from namelist and store in "dirs".
! Also open the parsed input parameter file(s) and setup param_file.
call get_MOM_input(param_file, dirs)

call get_param(param_file, mod_name, "ICE_SHELF", use_ice_shelf, &
"If true, enables the ice shelf model.", default=.false.)
if (use_ice_shelf) then
! These arrays are not initialized in most solo cases, but are needed
! when using an ice shelf
call initialize_ice_shelf(param_file, grid, Time, ice_shelf_CSp, &
diag_IS, forces, fluxes, sfc_state)
endif
call close_param_file(param_file)

if (sum(date) >= 0) then
call initialize_MOM(Time, Start_time, param_file, dirs, MOM_CSp, restart_CSp, &
segment_start_time, offline_tracer_mode=offline_tracer_mode, &
diag_ptr=diag, tracer_flow_CSp=tracer_flow_CSp,ice_shelf_CSp=ice_shelf_CSp)
else
call initialize_MOM(Time, Start_time, param_file, dirs, MOM_CSp, restart_CSp, &
offline_tracer_mode=offline_tracer_mode, diag_ptr=diag, &
tracer_flow_CSp=tracer_flow_CSp)
tracer_flow_CSp=tracer_flow_CSp,ice_shelf_CSp=ice_shelf_CSp)
endif

call get_MOM_state_elements(MOM_CSp, G=grid, GV=GV, US=US, C_p_scaled=fluxes%C_p)
Expand All @@ -320,14 +342,6 @@ program MOM_main
surface_forcing_CSp, tracer_flow_CSp)
call callTree_waypoint("done surface_forcing_init")

call get_param(param_file, mod_name, "ICE_SHELF", use_ice_shelf, &
"If true, enables the ice shelf model.", default=.false.)
if (use_ice_shelf) then
! These arrays are not initialized in most solo cases, but are needed
! when using an ice shelf
call initialize_ice_shelf(param_file, grid, Time, ice_shelf_CSp, &
diag, forces, fluxes)
endif

call get_param(param_file,mod_name,"USE_WAVES",Use_Waves,&
"If true, enables surface wave modules.",default=.false.)
Expand Down Expand Up @@ -482,7 +496,7 @@ program MOM_main

if (use_ice_shelf) then
call shelf_calc_flux(sfc_state, fluxes, Time, dt_forcing, ice_shelf_CSp)
call add_shelf_forces(grid, US, Ice_shelf_CSp, forces)
call add_shelf_forces(grid, US, Ice_shelf_CSp, forces, external_call=.true.)
endif
fluxes%fluxes_used = .false.
fluxes%dt_buoy_accum = US%s_to_T*dt_forcing
Expand Down Expand Up @@ -652,6 +666,7 @@ program MOM_main

call callTree_waypoint("End MOM_main")
call diag_mediator_end(Time, diag, end_diag_manager=.true.)
if (use_ice_shelf) call diag_mediator_IS_end(Time, diag_IS)
if (cpu_steps > 0) call write_cputime(Time, ns-1, write_CPU_CSp, call_end=.true.)
call cpu_clock_end(termClock)

Expand Down
14 changes: 4 additions & 10 deletions src/ALE/MOM_ALE.F90
Original file line number Diff line number Diff line change
Expand Up @@ -331,7 +331,7 @@ subroutine ALE_main( G, GV, US, h, u, v, tv, Reg, CS, OBC, dt, frac_shelf_h)
type(ALE_CS), pointer :: CS !< Regridding parameters and options
type(ocean_OBC_type), pointer :: OBC !< Open boundary structure
real, optional, intent(in) :: dt !< Time step between calls to ALE_main [T ~> s]
real, dimension(:,:), optional, pointer :: frac_shelf_h !< Fractional ice shelf coverage
real, dimension(SZI_(G),SZJ_(G)), optional, intent(in) :: frac_shelf_h !< Fractional ice shelf coverage [nondim]
! Local variables
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1) :: dzRegrid ! The change in grid interface positions
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1) :: eta_preale
Expand All @@ -341,10 +341,7 @@ subroutine ALE_main( G, GV, US, h, u, v, tv, Reg, CS, OBC, dt, frac_shelf_h)

nk = GV%ke; isc = G%isc; iec = G%iec; jsc = G%jsc; jec = G%jec

ice_shelf = .false.
if (present(frac_shelf_h)) then
if (associated(frac_shelf_h)) ice_shelf = .true.
endif
ice_shelf = present(frac_shelf_h)

if (CS%show_call_tree) call callTree_enter("ALE_main(), MOM_ALE.F90")

Expand Down Expand Up @@ -621,7 +618,7 @@ subroutine ALE_build_grid( G, GV, regridCS, remapCS, h, tv, debug, frac_shelf_h
real, dimension(SZI_(G),SZJ_(G), SZK_(GV)), intent(inout) :: h !< Current 3D grid obtained after the
!! last time step [H ~> m or kg-2]
logical, optional, intent(in) :: debug !< If true, show the call tree
real, dimension(:,:), optional, pointer :: frac_shelf_h !< Fractional ice shelf coverage
real, dimension(SZI_(G),SZJ_(G)), optional, intent(in):: frac_shelf_h !< Fractional ice shelf coverage [nondim]
! Local variables
integer :: nk, i, j, k
real, dimension(SZI_(G), SZJ_(G), SZK_(GV)+1) :: dzRegrid ! The change in grid interface positions
Expand All @@ -631,10 +628,7 @@ subroutine ALE_build_grid( G, GV, regridCS, remapCS, h, tv, debug, frac_shelf_h
show_call_tree = .false.
if (present(debug)) show_call_tree = debug
if (show_call_tree) call callTree_enter("ALE_build_grid(), MOM_ALE.F90")
use_ice_shelf = .false.
if (present(frac_shelf_h)) then
if (associated(frac_shelf_h)) use_ice_shelf = .true.
endif
use_ice_shelf = present(frac_shelf_h)

! Build new grid. The new grid is stored in h_new. The old grid is h.
! Both are needed for the subsequent remapping of variables.
Expand Down
Loading

0 comments on commit 1267431

Please sign in to comment.