Skip to content

Commit

Permalink
Fixed conflict
Browse files Browse the repository at this point in the history
  • Loading branch information
Andrew Shao committed Oct 13, 2016
2 parents 44d71c9 + 7808bfd commit ecdde94
Show file tree
Hide file tree
Showing 5 changed files with 55 additions and 53 deletions.
41 changes: 17 additions & 24 deletions config_src/solo_driver/MOM_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -174,7 +174,7 @@ program MOM_main
logical :: do_online ! If true, use the model in prognostic mode where
! the barotropic and baroclinic dynamics, thermodynamics,
! etc. are stepped forward integrated in time.
! If false, the all of the above are bypassed with all
! If false, then all of the above are bypassed with all
! fields necessary to integrate only the tracer advection
! and diffusion equation are read in from files stored from
! a previous integration of the prognostic model
Expand Down Expand Up @@ -260,17 +260,18 @@ program MOM_main
else
Start_time = set_time(0,days=0)
endif

if (sum(date) >= 0) then
! 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, param_file, dirs, MOM_CSp, segment_start_time)
! Note the not before CS%d
call initialize_MOM(Time, param_file, dirs, MOM_CSp, segment_start_time, do_online_out = do_online)
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
call initialize_MOM(Time, param_file, dirs, MOM_CSp)
call initialize_MOM(Time, param_file, dirs, MOM_CSp, do_online_out=do_online)
endif
fluxes%C_p = MOM_CSp%tv%C_p ! Copy the heat capacity for consistency.

Expand Down Expand Up @@ -308,16 +309,7 @@ program MOM_main
call get_param(param_file, mod, "DT_FORCING", time_step, &
"The time step for changing forcing, coupling with other \n"//&
"components, or potentially writing certain diagnostics. \n"//&
"The default value is given by DT.", units="s", default=dt)

call get_param(param_file, mod, "DO_ONLINE", do_online, &
"If true, use the model in prognostic mode where\n"//&
"the barotropic and baroclinic dynamics, thermodynamics,\n"//&
"etc. are stepped forward integrated in time.\n"//&
"If false, the all of the above are bypassed with all\n"//&
"fields necessary to integrate only the tracer advection\n"//&
"and diffusion equation are read in from files stored from\n"//&
"a previous integration of the prognostic model", default=.true.)
"The default value is given by DT.", units="s", default=dt)
if (.not. do_online) then
call get_param(param_file, mod, "DT_OFFLINE", time_step, &
"Time step for the offline time step")
Expand Down Expand Up @@ -478,16 +470,17 @@ program MOM_main
call disable_averaging(MOM_CSp%diag)

if (do_online) then
if (fluxes%fluxes_used) then
call enable_averaging(fluxes%dt_buoy_accum, Time, MOM_CSp%diag)
call forcing_diagnostics(fluxes, state, fluxes%dt_buoy_accum, grid, &
MOM_CSp%diag, surface_forcing_CSp%handles)
call accumulate_net_input(fluxes, state, fluxes%dt_buoy_accum, grid, sum_output_CSp)
call disable_averaging(MOM_CSp%diag)
else
call MOM_error(FATAL, "The solo MOM_driver is not yet set up to handle "//&
"thermodynamic time steps that are longer than the coupling timestep.")
endif ; endif
if (fluxes%fluxes_used) then
call enable_averaging(fluxes%dt_buoy_accum, Time, MOM_CSp%diag)
call forcing_diagnostics(fluxes, state, fluxes%dt_buoy_accum, grid, &
MOM_CSp%diag, surface_forcing_CSp%handles)
call accumulate_net_input(fluxes, state, fluxes%dt_buoy_accum, grid, sum_output_CSp)
call disable_averaging(MOM_CSp%diag)
else
call MOM_error(FATAL, "The solo MOM_driver is not yet set up to handle "//&
"thermodynamic time steps that are longer than the coupling timestep.")
endif
endif



Expand Down
46 changes: 29 additions & 17 deletions src/core/MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -200,7 +200,9 @@ module MOM
!! set by calling the function useRegridding() from the
!! MOM_regridding module.
logical :: do_dynamics !< If false, does not call step_MOM_dyn_*. This is an

!! undocumented run-time flag that is fragile.
logical :: do_online !< If false, step_tracers is called instead of step_MOM.
!! This is intended for running MOM6 in offline tracer mode
real :: dt !< (baroclinic) dynamics time step (seconds)
real :: dt_therm !< thermodynamics time step (seconds)
logical :: thermo_spans_coupling !< If true, thermodynamic and tracer time
Expand All @@ -211,7 +213,7 @@ module MOM
type(time_type) :: Z_diag_interval !< amount of time between calculating Z-space diagnostics
type(time_type) :: Z_diag_time !< next time to compute Z-space diagnostics
type(time_type), pointer :: Time !< pointer to ocean clock
real :: rel_time = 0.0 !< relative time (sec) since start of current execution
real :: rel_time = 0.0 !< relative time (sec) sinc.e start of current execution
real :: dtbt_reset_period !< The time interval in seconds between dynamic
!! recalculation of the barotropic time step. If
!! this is negative, it is never calculated, and
Expand Down Expand Up @@ -463,10 +465,6 @@ subroutine step_MOM(fluxes, state, Time_start, time_interval, CS)
eta_av, & ! average sea surface height or column mass over a timestep (meter or kg/m2)
ssh ! sea surface height based on eta_av (meter or kg/m2)

real, dimension(SZIB_(CS%G),SZJ_(CS%G),SZK_(CS%G)) :: write_all_3du
real, dimension(SZI_(CS%G),SZJB_(CS%G),SZK_(CS%G)) :: write_all_3dv
real, dimension(SZI_(CS%G),SZJ_(CS%G),SZK_(CS%G)) :: write_all_3dt

real, allocatable, dimension(:,:) :: &
tmp, & ! temporary 2d field
zos, & ! dynamic sea lev (zero area mean) from inverse-barometer adjusted ssh (meter)
Expand Down Expand Up @@ -710,7 +708,6 @@ subroutine step_MOM(fluxes, state, Time_start, time_interval, CS)
fluxes%fluxes_used = .true.
call cpu_clock_end(id_clock_diabatic)

write_all_3dt(:,:,:) = 1.
if (CS%id_u_preale > 0) call post_data(CS%id_u_preale, u, CS%diag)
if (CS%id_v_preale > 0) call post_data(CS%id_v_preale, v, CS%diag)
if (CS%id_h_preale > 0) call post_data(CS%id_h_preale, h, CS%diag)
Expand Down Expand Up @@ -1059,7 +1056,6 @@ subroutine step_MOM(fluxes, state, Time_start, time_interval, CS)
! Regridding/remapping is done here, at the end of the thermodynamics time step
! (that may comprise several dynamical time steps)
! The routine 'ALE_main' can be found in 'MOM_ALE.F90'.
write_all_3dt(:,:,:) = 1.
if (CS%id_u_preale > 0) call post_data(CS%id_u_preale, u, CS%diag)
if (CS%id_v_preale > 0) call post_data(CS%id_v_preale, v, CS%diag)
if (CS%id_h_preale > 0) call post_data(CS%id_h_preale, h, CS%diag)
Expand Down Expand Up @@ -1464,6 +1460,9 @@ subroutine step_tracers(fluxes, state, Time_start, time_interval, CS)
integer :: IsdB, IedB, JsdB, JedB
logical :: z_first, x_before_y

! Fail out if do_online is true
if(CS%do_online) call MOM_error(FATAL,"DO_ONLINE=True when calling step_tracers")

! Grid-related pointer assignments
G => CS%G
GV => CS%GV
Expand Down Expand Up @@ -1540,7 +1539,7 @@ subroutine step_tracers(fluxes, state, Time_start, time_interval, CS)

! Do horizontal diffusion first (but only half of it), remainder will be applied after advection
call tracer_hordiff(h_pre, CS%offline_CSp%dt_offline*0.5, CS%MEKE, CS%VarMix, G, GV, &
CS%tracer_diff_CSp, CS%tracer_Reg, CS%tv, do_online_flag=.false., read_khdt_x=khdt_x*0.5, &
CS%tracer_diff_CSp, CS%tracer_Reg, CS%tv, do_online_flag=CS%do_online, read_khdt_x=khdt_x*0.5, &
read_khdt_y=khdt_y*0.5)

do j=jsd,jed ; do i=isd,ied
Expand Down Expand Up @@ -1823,13 +1822,14 @@ end subroutine step_tracers


!> This subroutine initializes MOM.
subroutine initialize_MOM(Time, param_file, dirs, CS, Time_in)
subroutine initialize_MOM(Time, param_file, dirs, CS, Time_in, do_online_out)
type(time_type), target, intent(inout) :: Time !< model time, set in this routine
type(param_file_type), intent(out) :: param_file !< structure indicating paramater file to parse
type(directories), intent(out) :: dirs !< structure with directory paths
type(MOM_control_struct), pointer :: CS !< pointer set in this routine to MOM control structure
type(time_type), optional, intent(in) :: Time_in !< time passed to MOM_initialize_state when
!! model is not being started from a restart file
logical, optional, intent(out) :: do_online_out !< .false. if tracers are being run offline

! local
type(ocean_grid_type), pointer :: G => NULL() ! A pointer to a structure with metrics and related
Expand Down Expand Up @@ -1942,7 +1942,15 @@ subroutine initialize_MOM(Time, param_file, dirs, CS, Time_in)
"If False, skips the dynamics calls that update u & v, as well as\n"//&
"the gravity wave adjustment to h. This is a fragile feature and\n"//&
"thus undocumented.", default=.true., do_not_log=.true. )

call get_param(param_file, "MOM", "DO_ONLINE", CS%do_online, &
"If false, use the model in prognostic mode where\n"//&
"the barotropic and baroclinic dynamics, thermodynamics,\n"//&
"etc. are stepped forward integrated in time.\n"//&
"If true, the all of the above are bypassed with all\n"//&
"fields necessary to integrate only the tracer advection\n"//&
"and diffusion equation are read in from files stored from\n"//&
"a previous integration of the prognostic model\n"//&
"NOTE: This option only used in the ocean_solo_driver.", default=.true.)
call get_param(param_file, "MOM", "USE_REGRIDDING", CS%use_ALE_algorithm , &
"If True, use the ALE algorithm (regridding/remapping).\n"//&
"If False, use the layered isopycnal algorithm.", default=.false. )
Expand All @@ -1957,8 +1965,8 @@ subroutine initialize_MOM(Time, param_file, dirs, CS, Time_in)
call get_param(param_file, "MOM", "THICKNESSDIFFUSE", CS%thickness_diffuse, &
"If true, interface heights are diffused with a \n"//&
"coefficient of KHTH.", default=.false.)
call get_param(param_file, "MOM", "`_FIRST", &
CS%thickness_diffuse_first, &
call get_param(param_file, "MOM", "THICKNESSDIFFUSE_FIRST", &
CS%thickness_diffuse_first, &
"If true, do thickness diffusion before dynamics.\n"//&
"This is only used if THICKNESSDIFFUSE is true.", &
default=.false.)
Expand Down Expand Up @@ -2525,10 +2533,14 @@ subroutine initialize_MOM(Time, param_file, dirs, CS, Time_in)
cmor_long_name ="Sea Water Salinity")
endif

call offline_transport_init(param_file, CS%offline_CSp, &
CS%diabatic_CSp%diabatic_aux_CSp, G, GV)
call register_diags_offline_transport(Time, CS%diag, CS%offline_CSp)

! If running in offline tracer mode, initialize the necessary control structure and
! parameters
if(present(do_online_out)) do_online_out=CS%do_online

if(.not. CS%do_online) then
call offline_transport_init(param_file, CS%offline_CSp, CS%diabatic_CSp, G, GV)
call register_diags_offline_transport(Time, CS%diag, CS%offline_CSp)
endif

! This subroutine initializes any tracer packages.
new_sim = ((dirs%input_filename(1:1) == 'n') .and. &
Expand Down
2 changes: 0 additions & 2 deletions src/parameterizations/vertical/MOM_diabatic_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -331,7 +331,6 @@ subroutine diabatic(u, v, h, tv, fluxes, visc, ADp, CDp, dt, G, GV, CS)
! (H units = m for Bouss, kg/m^2 for non-Bouss).
real :: dt_mix ! amount of time over which to apply mixing (seconds)
real :: Idt ! inverse time step (1/s)
real, dimension(SZI_(G),SZJ_(G),SZK_(G)) :: write_all_3dt

type(p3d) :: z_ptrs(7) ! pointers to diagnostics to be interpolated to depth
integer :: num_z_diags ! number of diagnostics to be interpolated to depth
Expand Down Expand Up @@ -1409,7 +1408,6 @@ subroutine diabatic(u, v, h, tv, fluxes, visc, ADp, CDp, dt, G, GV, CS)
if (CS%id_Kd_salt > 0) call post_data(CS%id_Kd_salt, Kd_salt, CS%diag)
if (CS%id_Kd_ePBL > 0) call post_data(CS%id_Kd_ePBL, Kd_ePBL, CS%diag)

write_all_3dt(:,:,:) = 1.
if (CS%id_ea > 0) call post_data(CS%id_ea, ea, CS%diag)
if (CS%id_eb > 0) call post_data(CS%id_eb, eb, CS%diag)

Expand Down
12 changes: 7 additions & 5 deletions src/tracer/MOM_offline_control.F90
Original file line number Diff line number Diff line change
Expand Up @@ -204,7 +204,7 @@ end subroutine transport_by_files
subroutine register_diags_offline_transport(Time, diag, CS)

type(offline_transport_CS), pointer :: CS !< control structure for MOM
type(time_type), intent(in) :: Time !< current model time
type(time_type), intent(in) :: Time !< current model time
type(diag_ctrl) :: diag


Expand All @@ -226,7 +226,7 @@ subroutine register_diags_offline_transport(Time, diag, CS)

end subroutine register_diags_offline_transport

! Initializes the control structure for offline transport and reads in some of the
!> Initializes the control structure for offline transport and reads in some of the
! run time parameters from MOM_input
subroutine offline_transport_init(param_file, CS, diabatic_aux_CSp, G, GV)

Expand Down Expand Up @@ -285,8 +285,10 @@ subroutine offline_transport_init(param_file, CS, diabatic_aux_CSp, G, GV)
if(.not. CS%fields_are_offset) CS%ridx_snap = CS%start_index

! Copy over parameters from other control structures
CS%evap_CFL_limit = diabatic_aux_CSp%evap_CFL_limit
CS%minimum_forcing_depth = diabatic_aux_CSp%minimum_forcing_depth
if(associated(diabatic_CSp%diabatic_aux_CSp)) then
CS%evap_CFL_limit = diabatic_aux_CSp%evap_CFL_limit
CS%minimum_forcing_depth = diabatic_aux_CSp%minimum_forcing_depth
endif

call callTree_leave("offline_transport_init")

Expand Down Expand Up @@ -536,7 +538,7 @@ end subroutine limit_mass_flux_3d
!! -# Repeat steps 1 and 2
!! -# Force a remapping to the stored layer thicknesses that correspond to the snapshot of
!! the online model at the end of an accumulation interval
!! -3 Reset T/S and h to their stored snapshotted values to prevent model drift
!! -# Reset T/S and h to their stored snapshotted values to prevent model drift
!!
!! \section offline_evaluation Evaluating the utility of an offline tracer model
!! How well an offline tracer model can be used as an alternative to integrating tracers online
Expand Down
7 changes: 2 additions & 5 deletions src/tracer/MOM_tracer_hor_diff.F90
Original file line number Diff line number Diff line change
Expand Up @@ -119,15 +119,13 @@ subroutine tracer_hordiff(h, dt, MEKE, VarMix, G, GV, CS, Reg, tv, do_online_fla
! the distance between adjacent tracer points, in m2.
Coef_x, & ! The coefficients relating zonal tracer differences
! to time-integrated fluxes, in m3 or kg.
Kh_u, & ! Tracer mixing coefficient at u-points, in m2 s-1.
write_all_2du ! Make sure that all the data gets written
Kh_u ! Tracer mixing coefficient at u-points, in m2 s-1.
real, dimension(SZI_(G),SZJB_(G)) :: &
khdt_y, & ! The value of Khtr*dt times the open face width divided by
! the distance between adjacent tracer points, in m2.
Coef_y, & ! The coefficients relating meridional tracer differences
! to time-integrated fluxes, in m3 or kg.
Kh_v, & ! Tracer mixing coefficient at u-points, in m2 s-1.
write_all_2dv ! Make sure that all the data gets written
Kh_v ! Tracer mixing coefficient at u-points, in m2 s-1.

real :: max_CFL ! The global maximum of the diffusive CFL number.
logical :: use_VarMix, Resoln_scaled
Expand Down Expand Up @@ -481,7 +479,6 @@ subroutine tracer_hordiff(h, dt, MEKE, VarMix, G, GV, CS, Reg, tv, do_online_fla
call vchksum(Coef_y,"After tracer diffusion Coef_y", G%HI, haloshift=2)
endif

write_all_2du = 1. ; write_all_2dv = 1.
if (CS%id_khdt_x > 0) call post_data(CS%id_khdt_x, khdt_x, CS%diag)
if (CS%id_khdt_y > 0) call post_data(CS%id_khdt_y, khdt_y, CS%diag)

Expand Down

0 comments on commit ecdde94

Please sign in to comment.