Skip to content

Commit

Permalink
Merge branch 'dev/master' of github.com:ESMG/MOM6 into dev/master
Browse files Browse the repository at this point in the history
  • Loading branch information
kshedstrom committed Jun 16, 2016
2 parents b0dfd01 + 47a351a commit ae0a293
Show file tree
Hide file tree
Showing 69 changed files with 5,896 additions and 4,985 deletions.
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -3,5 +3,6 @@
*~
# For locally install doxygen/
doxygen
doxygen.log
# For locally generated html /
html
4 changes: 2 additions & 2 deletions config_src/coupled_driver/MOM_surface_forcing.F90
Original file line number Diff line number Diff line change
Expand Up @@ -804,7 +804,7 @@ subroutine surface_forcing_init(Time, G, param_file, diag, CS, restore_salt)
#include "version_variable.h"
character(len=40) :: mod = "MOM_surface_forcing" ! This module's name.
character(len=48) :: stagger
character(len=128) :: basin_file
character(len=240) :: basin_file
integer :: i, j, isd, ied, jsd, jed

isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed
Expand Down Expand Up @@ -1041,7 +1041,7 @@ subroutine surface_forcing_init(Time, G, param_file, diag, CS, restore_salt)
endif ; endif

! Set up any restart fields associated with the forcing.
call restart_init(G, param_file, CS%restart_CSp, "MOM_forcing.res")
call restart_init(param_file, CS%restart_CSp, "MOM_forcing.res")
!### call register_ctrl_forcing_restarts(G, param_file, CS%ctrl_forcing_CSp, &
!### CS%restart_CSp)
call restart_init_end(CS%restart_CSp)
Expand Down
2 changes: 1 addition & 1 deletion config_src/solo_driver/MOM_surface_forcing.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1833,7 +1833,7 @@ subroutine surface_forcing_init(Time, G, param_file, diag, CS, tracer_flow_CSp)
call register_forcing_type_diags(Time, diag, CS%use_temperature, CS%handles)

! Set up any restart fields associated with the forcing.
call restart_init(G, param_file, CS%restart_CSp, "MOM_forcing.res")
call restart_init(param_file, CS%restart_CSp, "MOM_forcing.res")
!### call register_ctrl_forcing_restarts(G, param_file, CS%ctrl_forcing_CSp, &
!### CS%restart_CSp)
call restart_init_end(CS%restart_CSp)
Expand Down
231 changes: 117 additions & 114 deletions src/ALE/MOM_ALE.F90

Large diffs are not rendered by default.

248 changes: 130 additions & 118 deletions src/ALE/MOM_regridding.F90

Large diffs are not rendered by default.

165 changes: 112 additions & 53 deletions src/core/MOM.F90

Large diffs are not rendered by default.

19 changes: 10 additions & 9 deletions src/core/MOM_barotropic.F90
Original file line number Diff line number Diff line change
Expand Up @@ -103,6 +103,7 @@ module MOM_barotropic
use MOM_file_parser, only : get_param, log_param, log_version, param_file_type
use MOM_forcing_type, only : forcing
use MOM_grid, only : ocean_grid_type
use MOM_hor_index, only : hor_index_type
use MOM_io, only : vardesc, var_desc
use MOM_restart, only : register_restart_field, query_initialized, MOM_restart_CS
use MOM_tidal_forcing, only : tidal_forcing_sensitivity, tidal_forcing_CS
Expand Down Expand Up @@ -493,7 +494,7 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, &
! Coriolis terms is always used.

real :: ubt_Cor(SZIB_(G),SZJ_(G)) ! The barotropic velocities that had been
real :: vbt_Cor(SZI_(G),SZJB_(G)) ! use to calculate the input Coriolis
real :: vbt_Cor(SZI_(G),SZJB_(G)) ! used to calculate the input Coriolis
! terms, in m s-1.
real :: wt_u(SZIB_(G),SZJ_(G),SZK_(G)) ! wt_u and wt_v are the
real :: wt_v(SZI_(G),SZJB_(G),SZK_(G)) ! normalized weights to
Expand Down Expand Up @@ -4280,24 +4281,24 @@ subroutine barotropic_end(CS)
deallocate(CS)
end subroutine barotropic_end

subroutine register_barotropic_restarts(G, GV, param_file, CS, restart_CS)
type(ocean_grid_type), intent(in) :: G
type(param_file_type), intent(in) :: param_file
type(barotropic_CS), pointer :: CS
subroutine register_barotropic_restarts(HI, GV, param_file, CS, restart_CS)
type(hor_index_type), intent(in) :: HI
type(param_file_type), intent(in) :: param_file
type(barotropic_CS), pointer :: CS
type(verticalGrid_type), intent(in) :: GV
type(MOM_restart_CS), pointer :: restart_CS
type(MOM_restart_CS), pointer :: restart_CS
! This subroutine is used to register any fields from MOM_barotropic.F90
! that should be written to or read from the restart file.
! Arguments: G - The ocean's grid structure.
! Arguments: HI - A horizontal index type structure.
! (in) GV - The ocean's vertical grid structure.
! (in/out) CS - A pointer that is set to point to the control structure
! for this module
! (in) restart_CS - A pointer to the restart control structure.
type(vardesc) :: vd(3)
real :: slow_rate
integer :: isd, ied, jsd, jed, IsdB, IedB, JsdB, JedB
isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed
IsdB = G%IsdB ; IedB = G%IedB ; JsdB = G%JsdB ; JedB = G%JedB
isd = HI%isd ; ied = HI%ied ; jsd = HI%jsd ; jed = HI%jed
IsdB = HI%IsdB ; IedB = HI%IedB ; JsdB = HI%JsdB ; JedB = HI%JedB

if (associated(CS)) then
call MOM_error(WARNING, "register_barotropic_restarts called with an associated "// &
Expand Down
11 changes: 6 additions & 5 deletions src/core/MOM_dyn_horgrid.F90
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ module MOM_dyn_horgrid

use MOM_hor_index, only : hor_index_type
use MOM_domains, only : MOM_domain_type
use MOM_error_handler, only : MOM_error, MOM_mesg, FATAL
use MOM_error_handler, only : MOM_error, MOM_mesg, FATAL, WARNING

implicit none ; private

Expand All @@ -33,7 +33,7 @@ module MOM_dyn_horgrid
type(MOM_domain_type), pointer :: Domain_aux => NULL() ! A non-symmetric auxiliary domain type.

! These elements can be copied from a provided hor_index_type.
type(hor_index_type), pointer :: HI
type(hor_index_type) :: HI ! Make this a pointer?
integer :: isc, iec, jsc, jec ! The range of the computational domain indices
integer :: isd, ied, jsd, jed ! and data domain indices at tracer cell centers.
integer :: isg, ieg, jsg, jeg ! The range of the global domain tracer cell indices.
Expand Down Expand Up @@ -155,9 +155,10 @@ subroutine create_dyn_horgrid(G, HI)
! are always used and zeros them out.

if (associated(G)) then
call MOM_error(FATAL, "destroy_dyn_horgrid called with an unassociated horgrid_type.")
call MOM_error(WARNING, "create_dyn_horgrid called with an associated horgrid_type.")
else
allocate(G)
endif
allocate(G)

G%HI = HI

Expand Down Expand Up @@ -245,7 +246,7 @@ end subroutine create_dyn_horgrid

!> set_derived_dyn_horgrid calculates metric terms that are derived from other metrics.
subroutine set_derived_dyn_horgrid(G)
type(dyn_horgrid_type), pointer :: G !< The dynamic horizontal grid type
type(dyn_horgrid_type), intent(inout) :: G !< The dynamic horizontal grid type
! Various inverse grid spacings and derived areas are calculated within this
! subroutine.
integer :: i, j, isd, ied, jsd, jed
Expand Down
17 changes: 9 additions & 8 deletions src/core/MOM_dynamics_legacy_split.F90
Original file line number Diff line number Diff line change
Expand Up @@ -104,6 +104,7 @@ module MOM_dynamics_legacy_split
use MOM_diabatic_driver, only : diabatic, diabatic_driver_init, diabatic_CS
use MOM_error_checking, only : check_redundant
use MOM_grid, only : ocean_grid_type
use MOM_hor_index, only : hor_index_type
use MOM_hor_visc, only : horizontal_viscosity, hor_visc_init, hor_visc_CS
use MOM_interface_heights, only : find_eta
use MOM_lateral_mixing_coeffs, only : VarMix_CS
Expand Down Expand Up @@ -1103,19 +1104,19 @@ end subroutine adjustments_dyn_legacy_split

! =============================================================================

subroutine register_restarts_dyn_legacy_split(G, GV, param_file, CS, restart_CS, uh, vh)
type(ocean_grid_type), intent(in) :: G
subroutine register_restarts_dyn_legacy_split(HI, GV, param_file, CS, restart_CS, uh, vh)
type(hor_index_type), intent(in) :: HI
type(verticalGrid_type), intent(in) :: GV
type(param_file_type), intent(in) :: param_file
type(MOM_dyn_legacy_split_CS), pointer :: CS
type(MOM_restart_CS), pointer :: restart_CS
real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), target, intent(inout) :: uh
real, dimension(SZI_(G),SZJB_(G),SZK_(G)), target, intent(inout) :: vh
real, dimension(SZIB_(HI),SZJ_(HI),SZK_(GV)), target, intent(inout) :: uh
real, dimension(SZI_(HI),SZJB_(HI),SZK_(GV)), target, intent(inout) :: vh
! This subroutine sets up any auxiliary restart variables that are specific
! to the unsplit time stepping scheme. All variables registered here should
! have the ability to be recreated if they are not present in a restart file.

! Arguments: G - The ocean's grid structure.
! Arguments: HI - A horizontal index type structure.
! (in) GV - The ocean's vertical grid structure.
! (in) param_file - A structure indicating the open file to parse for
! model parameter values.
Expand All @@ -1129,8 +1130,8 @@ subroutine register_restarts_dyn_legacy_split(G, GV, param_file, CS, restart_CS,
character(len=48) :: thickness_units, flux_units
logical :: adiabatic, flux_BT_coupling, readjust_BT_trans
integer :: isd, ied, jsd, jed, nz, IsdB, IedB, JsdB, JedB
isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed ; nz = G%ke
IsdB = G%IsdB ; IedB = G%IedB ; JsdB = G%JsdB ; JedB = G%JedB
isd = HI%isd ; ied = HI%ied ; jsd = HI%jsd ; jed = HI%jed ; nz = GV%ke
IsdB = HI%IsdB ; IedB = HI%IedB ; JsdB = HI%JsdB ; JedB = HI%JedB

! This is where a control structure that is specific to this module would be allocated.
if (associated(CS)) then
Expand Down Expand Up @@ -1189,7 +1190,7 @@ subroutine register_restarts_dyn_legacy_split(G, GV, param_file, CS, restart_CS,
vd = var_desc("diffv","meter second-2","Meridional horizontal viscous acceleration",'v','L')
call register_restart_field(CS%diffv, vd, .false., restart_CS)

call register_legacy_barotropic_restarts(G, GV, param_file, &
call register_legacy_barotropic_restarts(HI, GV, param_file, &
CS%barotropic_CSp, restart_CS)

if (readjust_bt_trans) then
Expand Down
25 changes: 13 additions & 12 deletions src/core/MOM_dynamics_split_RK2.F90
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,7 @@ module MOM_dynamics_split_RK2
use MOM_diabatic_driver, only : diabatic, diabatic_driver_init, diabatic_CS
use MOM_error_checking, only : check_redundant
use MOM_grid, only : ocean_grid_type
use MOM_hor_index, only : hor_index_type
use MOM_hor_visc, only : horizontal_viscosity, hor_visc_init, hor_visc_CS
use MOM_interface_heights, only : find_eta
use MOM_lateral_mixing_coeffs, only : VarMix_CS
Expand Down Expand Up @@ -99,7 +100,7 @@ module MOM_dynamics_split_RK2
real ALLOCABLE_, dimension(NIMEMB_PTR_,NJMEM_) :: uhbt !< average x-volume or mass flux determined by barotropic solver
!! (m3 s-1 or kg s-1). uhbt should (roughly?) equal to vertical sum of uh.
real ALLOCABLE_, dimension(NIMEM_,NJMEMB_PTR_) :: vhbt !< average y-volume or mass flux determined by barotropic solver
!! (m3 s-1 or kg s-1). uhbt should (roughly?) equal to vertical sum of uh.
!! (m3 s-1 or kg s-1). vhbt should (roughly?) equal to vertical sum of vh.
real ALLOCABLE_, dimension(NIMEM_,NJMEM_,NKMEM_) :: pbce !< pbce times eta gives the baroclinic pressure anomaly in each layer due
!! to free surface height anomalies. pbce has units of m2 H-1 s-2.

Expand Down Expand Up @@ -930,22 +931,22 @@ end subroutine step_MOM_dyn_split_RK2
!> This subroutine sets up any auxiliary restart variables that are specific
!! to the unsplit time stepping scheme. All variables registered here should
!! have the ability to be recreated if they are not present in a restart file.
subroutine register_restarts_dyn_split_RK2(G, GV, param_file, CS, restart_CS, uh, vh)
type(ocean_grid_type), intent(in) :: G !< ocean grid structure
type(verticalGrid_type), intent(in) :: GV !< ocean vertical grid structure
type(param_file_type), intent(in) :: param_file !< parameter file
type(MOM_dyn_split_RK2_CS), pointer :: CS !< module control structure
type(MOM_restart_CS), pointer :: restart_CS !< restart control structure
real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), target, intent(inout) :: uh !< zonal volume/mass transport (m3/s or kg/s)
real, dimension(SZI_(G),SZJB_(G),SZK_(G)), target, intent(inout) :: vh !< merid volume/mass transport (m3/s or kg/s)
subroutine register_restarts_dyn_split_RK2(HI, GV, param_file, CS, restart_CS, uh, vh)
type(hor_index_type), intent(in) :: HI !< Horizontal index structure
type(verticalGrid_type), intent(in) :: GV !< ocean vertical grid structure
type(param_file_type), intent(in) :: param_file !< parameter file
type(MOM_dyn_split_RK2_CS), pointer :: CS !< module control structure
type(MOM_restart_CS), pointer :: restart_CS !< restart control structure
real, dimension(SZIB_(HI),SZJ_(HI),SZK_(GV)), target, intent(inout) :: uh !< zonal volume/mass transport (m3/s or kg/s)
real, dimension(SZI_(HI),SZJB_(HI),SZK_(GV)), target, intent(inout) :: vh !< merid volume/mass transport (m3/s or kg/s)

type(vardesc) :: vd
character(len=40) :: mod = "MOM_dynamics_split_RK2" ! This module's name.
character(len=48) :: thickness_units, flux_units

integer :: isd, ied, jsd, jed, nz, IsdB, IedB, JsdB, JedB
isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed ; nz = G%ke
IsdB = G%IsdB ; IedB = G%IedB ; JsdB = G%JsdB ; JedB = G%JedB
isd = HI%isd ; ied = HI%ied ; jsd = HI%jsd ; jed = HI%jed ; nz = GV%ke
IsdB = HI%IsdB ; IedB = HI%IedB ; JsdB = HI%JsdB ; JedB = HI%JedB

! This is where a control structure specific to this module would be allocated.
if (associated(CS)) then
Expand Down Expand Up @@ -994,7 +995,7 @@ subroutine register_restarts_dyn_split_RK2(G, GV, param_file, CS, restart_CS, uh
vd = var_desc("diffv","meter second-2","Meridional horizontal viscous acceleration",'v','L')
call register_restart_field(CS%diffv, vd, .false., restart_CS)

call register_barotropic_restarts(G, GV, param_file, CS%barotropic_CSp, &
call register_barotropic_restarts(HI, GV, param_file, CS%barotropic_CSp, &
restart_CS)

end subroutine register_restarts_dyn_split_RK2
Expand Down
11 changes: 6 additions & 5 deletions src/core/MOM_dynamics_unsplit.F90
Original file line number Diff line number Diff line change
Expand Up @@ -97,6 +97,7 @@ module MOM_dynamics_unsplit
use MOM_CoriolisAdv, only : CorAdCalc, CoriolisAdv_init, CoriolisAdv_CS
use MOM_error_checking, only : check_redundant
use MOM_grid, only : ocean_grid_type
use MOM_hor_index, only : hor_index_type
use MOM_hor_visc, only : horizontal_viscosity, hor_visc_init, hor_visc_CS
use MOM_interface_heights, only : find_eta
use MOM_lateral_mixing_coeffs, only : VarMix_CS
Expand Down Expand Up @@ -530,8 +531,8 @@ end subroutine step_MOM_dyn_unsplit

! =============================================================================

subroutine register_restarts_dyn_unsplit(G, GV, param_file, CS, restart_CS)
type(ocean_grid_type), intent(in) :: G
subroutine register_restarts_dyn_unsplit(HI, GV, param_file, CS, restart_CS)
type(hor_index_type), intent(in) :: HI
type(verticalGrid_type), intent(in) :: GV
type(param_file_type), intent(in) :: param_file
type(MOM_dyn_unsplit_CS), pointer :: CS
Expand All @@ -540,7 +541,7 @@ subroutine register_restarts_dyn_unsplit(G, GV, param_file, CS, restart_CS)
! to the unsplit time stepping scheme. All variables registered here should
! have the ability to be recreated if they are not present in a restart file.

! Arguments: G - The ocean's grid structure.
! Arguments: HI - A horizontal index type structure.
! (in) GV - The ocean's vertical grid structure.
! (in) param_file - A structure indicating the open file to parse for
! model parameter values.
Expand All @@ -551,8 +552,8 @@ subroutine register_restarts_dyn_unsplit(G, GV, param_file, CS, restart_CS)
character(len=40) :: mod = "MOM_dynamics_unsplit" ! This module's name.
character(len=48) :: thickness_units, flux_units
integer :: isd, ied, jsd, jed, nz, IsdB, IedB, JsdB, JedB
isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed ; nz = G%ke
IsdB = G%IsdB ; IedB = G%IedB ; JsdB = G%JsdB ; JedB = G%JedB
isd = HI%isd ; ied = HI%ied ; jsd = HI%jsd ; jed = HI%jed ; nz = GV%ke
IsdB = HI%IsdB ; IedB = HI%IedB ; JsdB = HI%JsdB ; JedB = HI%JedB

! This is where a control structure that is specific to this module would be allocated.
if (associated(CS)) then
Expand Down
11 changes: 6 additions & 5 deletions src/core/MOM_dynamics_unsplit_RK2.F90
Original file line number Diff line number Diff line change
Expand Up @@ -96,6 +96,7 @@ module MOM_dynamics_unsplit_RK2
use MOM_CoriolisAdv, only : CorAdCalc, CoriolisAdv_init, CoriolisAdv_CS
use MOM_error_checking, only : check_redundant
use MOM_grid, only : ocean_grid_type
use MOM_hor_index, only : hor_index_type
use MOM_hor_visc, only : horizontal_viscosity, hor_visc_init, hor_visc_CS
use MOM_lateral_mixing_coeffs, only : VarMix_CS
use MOM_MEKE_types, only : MEKE_type
Expand Down Expand Up @@ -480,8 +481,8 @@ end subroutine step_MOM_dyn_unsplit_RK2

! =============================================================================

subroutine register_restarts_dyn_unsplit_RK2(G, GV, param_file, CS, restart_CS)
type(ocean_grid_type), intent(in) :: G
subroutine register_restarts_dyn_unsplit_RK2(HI, GV, param_file, CS, restart_CS)
type(hor_index_type), intent(in) :: HI
type(verticalGrid_type), intent(in) :: GV
type(param_file_type), intent(in) :: param_file
type(MOM_dyn_unsplit_RK2_CS), pointer :: CS
Expand All @@ -490,7 +491,7 @@ subroutine register_restarts_dyn_unsplit_RK2(G, GV, param_file, CS, restart_CS)
! to the unsplit time stepping scheme. All variables registered here should
! have the ability to be recreated if they are not present in a restart file.

! Arguments: G - The ocean's grid structure.
! Arguments: HI - A horizontal index type structure.
! (in) GV - The ocean's vertical grid structure.
! (in) param_file - A structure indicating the open file to parse for
! model parameter values.
Expand All @@ -500,8 +501,8 @@ subroutine register_restarts_dyn_unsplit_RK2(G, GV, param_file, CS, restart_CS)
type(vardesc) :: vd
character(len=48) :: thickness_units, flux_units
integer :: isd, ied, jsd, jed, nz, IsdB, IedB, JsdB, JedB
isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed ; nz = G%ke
IsdB = G%IsdB ; IedB = G%IedB ; JsdB = G%JsdB ; JedB = G%JedB
isd = HI%isd ; ied = HI%ied ; jsd = HI%jsd ; jed = HI%jed ; nz = GV%ke
IsdB = HI%IsdB ; IedB = HI%IedB ; JsdB = HI%JsdB ; JedB = HI%JedB

! This is where a control structure that is specific to this module would be allocated.
if (associated(CS)) then
Expand Down
17 changes: 9 additions & 8 deletions src/core/MOM_legacy_barotropic.F90
Original file line number Diff line number Diff line change
Expand Up @@ -105,6 +105,7 @@ module MOM_legacy_barotropic
use MOM_file_parser, only : get_param, log_param, log_version, param_file_type
use MOM_forcing_type, only : forcing
use MOM_grid, only : ocean_grid_type
use MOM_hor_index, only : hor_index_type
use MOM_io, only : vardesc, var_desc
use MOM_restart, only : register_restart_field, query_initialized, MOM_restart_CS
use MOM_tidal_forcing, only : tidal_forcing_sensitivity, tidal_forcing_CS
Expand Down Expand Up @@ -4018,24 +4019,24 @@ subroutine legacy_barotropic_end(CS)
deallocate(CS)
end subroutine legacy_barotropic_end

subroutine register_legacy_barotropic_restarts(G, GV, param_file, CS, restart_CS)
type(ocean_grid_type), intent(in) :: G
subroutine register_legacy_barotropic_restarts(HI, GV, param_file, CS, restart_CS)
type(hor_index_type), intent(in) :: HI
type(verticalGrid_type), intent(in) :: GV
type(param_file_type), intent(in) :: param_file
type(legacy_barotropic_CS), pointer :: CS
type(MOM_restart_CS), pointer :: restart_CS
type(param_file_type), intent(in) :: param_file
type(legacy_barotropic_CS), pointer :: CS
type(MOM_restart_CS), pointer :: restart_CS
! This subroutine is used to register any fields from MOM_barotropic.F90
! that should be written to or read from the restart file.
! Arguments: G - The ocean's grid structure.
! Arguments: HI - A horizontal index type structure.
! (in) GV - The ocean's vertical grid structure.
! (in/out) CS - A pointer that is set to point to the control structure
! for this module
! (in) restart_CS - A pointer to the restart control structure.
type(vardesc) :: vd(3)
real :: slow_rate
integer :: isd, ied, jsd, jed, IsdB, IedB, JsdB, JedB
isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed
IsdB = G%IsdB ; IedB = G%IedB ; JsdB = G%JsdB ; JedB = G%JedB
isd = HI%isd ; ied = HI%ied ; jsd = HI%jsd ; jed = HI%jed
IsdB = HI%IsdB ; IedB = HI%IedB ; JsdB = HI%JsdB ; JedB = HI%JedB

if (associated(CS)) then
call MOM_error(WARNING, "register_barotropic_restarts called with an associated "// &
Expand Down
Loading

0 comments on commit ae0a293

Please sign in to comment.