Skip to content

Commit

Permalink
Merge pull request #761 from Hallberg-NOAA/code_standardization
Browse files Browse the repository at this point in the history
Code standardization
  • Loading branch information
adcroft authored May 5, 2018
2 parents 426bf30 + dbfe909 commit 026907e
Show file tree
Hide file tree
Showing 83 changed files with 3,388 additions and 2,704 deletions.
442 changes: 280 additions & 162 deletions config_src/coupled_driver/MOM_surface_forcing.F90

Large diffs are not rendered by default.

248 changes: 73 additions & 175 deletions config_src/coupled_driver/ocean_model_MOM.F90

Large diffs are not rendered by default.

24 changes: 13 additions & 11 deletions config_src/ice_solo_driver/atmos_ocean_fluxes.F90
Original file line number Diff line number Diff line change
Expand Up @@ -10,21 +10,23 @@ module atmos_ocean_fluxes_mod

contains

!> This subroutine duplicates an interface used by the FMS coupler, but only
!! returns a value of -1. None of the arguments are used for anything.
function aof_set_coupler_flux(name, flux_type, implementation, atm_tr_index, &
param, flag, ice_restart_file, ocean_restart_file, &
units, caller, verbosity) result (coupler_index)

character(len=*), intent(in) :: name
character(len=*), intent(in) :: flux_type
character(len=*), intent(in) :: implementation
integer, intent(in), optional :: atm_tr_index
real, intent(in), dimension(:), optional :: param
logical, intent(in), dimension(:), optional :: flag
character(len=*), intent(in), optional :: ice_restart_file
character(len=*), intent(in), optional :: ocean_restart_file
character(len=*), intent(in), optional :: units
character(len=*), intent(in), optional :: caller
integer, intent(in), optional :: verbosity
character(len=*), intent(in) :: name !< An unused argument
character(len=*), intent(in) :: flux_type !< An unused argument
character(len=*), intent(in) :: implementation !< An unused argument
integer, optional, intent(in) :: atm_tr_index !< An unused argument
real, dimension(:), optional, intent(in) :: param !< An unused argument
logical, dimension(:), optional, intent(in) :: flag !< An unused argument
character(len=*), optional, intent(in) :: ice_restart_file !< An unused argument
character(len=*), optional, intent(in) :: ocean_restart_file !< An unused argument
character(len=*), optional, intent(in) :: units !< An unused argument
character(len=*), optional, intent(in) :: caller !< An unused argument
integer, optional, intent(in) :: verbosity !< An unused argument

! None of these arguments are used for anything.

Expand Down
12 changes: 6 additions & 6 deletions config_src/ice_solo_driver/coupler_types.F90
Original file line number Diff line number Diff line change
Expand Up @@ -294,7 +294,7 @@ subroutine coupler_type_copy_1d_2d(var_in, var_out, is, ie, js, je, &
character(len=*), intent(in) :: diag_name !< name for diagnostic file--if blank, then don't register the fields
integer, dimension(:), intent(in) :: axes !< array of axes identifiers for diagnostic variable registration
type(time_type), intent(in) :: time !< model time variable for registering diagnostic field
character(len=*), intent(in), optional :: suffix !< optional suffix to make the name identifier unique
character(len=*), optional, intent(in) :: suffix !< optional suffix to make the name identifier unique

character(len=256), parameter :: error_header = &
'==>Error from coupler_types_mod (coupler_type_copy_1d_2d):'
Expand Down Expand Up @@ -343,7 +343,7 @@ subroutine coupler_type_copy_1d_3d(var_in, var_out, is, ie, js, je, kd, &
character(len=*), intent(in) :: diag_name !< name for diagnostic file--if blank, then don't register the fields
integer, dimension(:), intent(in) :: axes !< array of axes identifiers for diagnostic variable registration
type(time_type), intent(in) :: time !< model time variable for registering diagnostic field
character(len=*), intent(in), optional :: suffix !< optional suffix to make the name identifier unique
character(len=*), optional, intent(in) :: suffix !< optional suffix to make the name identifier unique

character(len=256), parameter :: error_header = &
'==>Error from coupler_types_mod (coupler_type_copy_1d_3d):'
Expand Down Expand Up @@ -386,7 +386,7 @@ subroutine coupler_type_copy_2d_2d(var_in, var_out, is, ie, js, je, &
character(len=*), intent(in) :: diag_name !< name for diagnostic file--if blank, then don't register the fields
integer, dimension(:), intent(in) :: axes !< array of axes identifiers for diagnostic variable registration
type(time_type), intent(in) :: time !< model time variable for registering diagnostic field
character(len=*), intent(in), optional :: suffix !< optional suffix to make the name identifier unique
character(len=*), optional, intent(in) :: suffix !< optional suffix to make the name identifier unique

character(len=256), parameter :: error_header = &
'==>Error from coupler_types_mod (coupler_type_copy_2d_2d):'
Expand Down Expand Up @@ -435,7 +435,7 @@ subroutine coupler_type_copy_2d_3d(var_in, var_out, is, ie, js, je, kd, &
character(len=*), intent(in) :: diag_name !< name for diagnostic file--if blank, then don't register the fields
integer, dimension(:), intent(in) :: axes !< array of axes identifiers for diagnostic variable registration
type(time_type), intent(in) :: time !< model time variable for registering diagnostic field
character(len=*), intent(in), optional :: suffix !< optional suffix to make the name identifier unique
character(len=*), optional, intent(in) :: suffix !< optional suffix to make the name identifier unique

character(len=256), parameter :: error_header = &
'==>Error from coupler_types_mod (coupler_type_copy_2d_3d):'
Expand Down Expand Up @@ -478,7 +478,7 @@ subroutine coupler_type_copy_3d_2d(var_in, var_out, is, ie, js, je, &
character(len=*), intent(in) :: diag_name !< name for diagnostic file--if blank, then don't register the fields
integer, dimension(:), intent(in) :: axes !< array of axes identifiers for diagnostic variable registration
type(time_type), intent(in) :: time !< model time variable for registering diagnostic field
character(len=*), intent(in), optional :: suffix !< optional suffix to make the name identifier unique
character(len=*), optional, intent(in) :: suffix !< optional suffix to make the name identifier unique

character(len=256), parameter :: error_header = &
'==>Error from coupler_types_mod (coupler_type_copy_3d_2d):'
Expand Down Expand Up @@ -527,7 +527,7 @@ subroutine coupler_type_copy_3d_3d(var_in, var_out, is, ie, js, je, kd, &
character(len=*), intent(in) :: diag_name !< name for diagnostic file--if blank, then don't register the fields
integer, dimension(:), intent(in) :: axes !< array of axes identifiers for diagnostic variable registration
type(time_type), intent(in) :: time !< model time variable for registering diagnostic field
character(len=*), intent(in), optional :: suffix !< optional suffix to make the name identifier unique
character(len=*), optional, intent(in) :: suffix !< optional suffix to make the name identifier unique

character(len=256), parameter :: error_header = &
'==>Error from coupler_types_mod (coupler_type_copy_3d_3d):'
Expand Down
45 changes: 23 additions & 22 deletions config_src/mct_driver/ocn_comp_mct.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1675,7 +1675,7 @@ subroutine update_ocean_model(OS, Ocean_sfc, time_start_update, &
type(cpl_indices), intent(inout) :: ind !< Structure with MCT attribute vectors and indices
logical, intent(in) :: sw_decomp !< controls if shortwave is
!!decomposed into four components
real(kind=8), intent(in), optional :: c1, c2, c3, c4 !< Coeffs. used in the shortwave decomposition
real(kind=8), optional, intent(in) :: c1, c2, c3, c4 !< Coeffs. used in the shortwave decomposition

! local variables
type(time_type) :: Master_time !< This allows step_MOM to temporarily change
Expand Down Expand Up @@ -1769,8 +1769,7 @@ subroutine update_ocean_model(OS, Ocean_sfc, time_start_update, &
call set_net_mass_forcing(OS%fluxes, OS%forces, OS%grid)

if (OS%nstep==0) then
call finish_MOM_initialization(OS%Time, OS%dirs, OS%MOM_CSp, OS%fluxes, &
OS%restart_CSp)
call finish_MOM_initialization(OS%Time, OS%dirs, OS%MOM_CSp, S%restart_CSp)
endif

call disable_averaging(OS%diag)
Expand Down Expand Up @@ -1813,21 +1812,21 @@ end subroutine update_ocean_model
!! the future.
subroutine ocn_import(forces, fluxes, Time, G, CS, state, x2o_o, ind, sw_decomp, &
c1, c2, c3, c4, restore_salt, restore_temp)
type(mech_forcing), intent(inout) :: forces !< Driving mechanical forces
type(forcing), intent(inout) :: fluxes !< Surface fluxes
type(time_type), intent(in) :: Time !< Model time
type(ocean_grid_type), intent(inout) :: G !< The ocean's grid
type(surface_forcing_CS), pointer :: CS !< control structure returned by
!! a previous call to surface_forcing_init
type(surface), intent(in) :: state !< control structure to ocean
!! surface state fields.
real(kind=8), intent(in) :: x2o_o(:,:)!< Fluxes from coupler to ocean, computed by ocean
type(cpl_indices), intent(inout) :: ind !< Structure with MCT attribute vectors and indices
logical, intent(in) :: sw_decomp !< controls if shortwave is
!!decomposed into four components
real(kind=8), intent(in), optional :: c1, c2, c3, c4 !< Coeffs. used in the shortwave decomposition
logical, optional, intent(in) :: restore_salt, restore_temp !< Controls if salt and temp are
!! restored
type(mech_forcing), intent(inout) :: forces !< Driving mechanical forces
type(forcing), intent(inout) :: fluxes !< Surface fluxes
type(time_type), intent(in) :: Time !< Model time
type(ocean_grid_type), intent(inout) :: G !< The ocean's grid
type(surface_forcing_CS), pointer :: CS !< control structure returned by
!! a previous call to surface_forcing_init
type(surface), intent(in) :: state !< control structure to ocean
!! surface state fields.
real(kind=8), intent(in) :: x2o_o(:,:)!< Fluxes from coupler to ocean, computed by ocean
type(cpl_indices), intent(inout) :: ind !< Structure with MCT attribute vectors and indices
logical, intent(in) :: sw_decomp !< controls if shortwave is
!!decomposed into four components
real(kind=8), optional, intent(in) :: c1, c2, c3, c4 !< Coeffs. used in the shortwave decomposition
logical, optional, intent(in) :: restore_salt, restore_temp !< Controls if salt and temp are
!! restored

! local variables
real, dimension(SZIB_(G),SZJB_(G)) :: &
Expand Down Expand Up @@ -1942,9 +1941,11 @@ subroutine ocn_import(forces, fluxes, Time, G, CS, state, x2o_o, ind, sw_decomp,
endif ! endif for allocation and initialization

if (CS%allow_flux_adjustments) then
fluxes%heat_added(:,:)=0.0
fluxes%salt_flux_added(:,:)=0.0
fluxes%heat_added(:,:)=0.0
fluxes%salt_flux_added(:,:)=0.0
endif
if (associated(forces%rigidity_ice_u)) forces%rigidity_ice_u(:,:) = 0.0
if (associated(forces%rigidity_ice_v)) forces%rigidity_ice_v(:,:) = 0.0

if (CS%area_surf < 0.0) then
do j=js,je ; do i=is,ie
Expand Down Expand Up @@ -2293,7 +2294,7 @@ subroutine ocn_import(forces, fluxes, Time, G, CS, state, x2o_o, ind, sw_decomp,
endif
! CAUTION: with both rigid_sea_ice and ice shelves, we will need to make this
! a maximum for the second call.
forces%rigidity_ice_u(I,j) = Kv_rho_ice * mass_eff
forces%rigidity_ice_u(I,j) = forces%rigidity_ice_u(I,j) + Kv_rho_ice * mass_eff
enddo ; enddo
do i=isd,ied ; do J=jsd,jed-1
mass_ice = min(forces%p_surf_full(i,j), forces%p_surf_full(i,j+1)) * I_GEarth
Expand All @@ -2302,7 +2303,7 @@ subroutine ocn_import(forces, fluxes, Time, G, CS, state, x2o_o, ind, sw_decomp,
mass_eff = (mass_ice - CS%rigid_sea_ice_mass) **2 / &
(mass_ice + CS%rigid_sea_ice_mass)
endif
forces%rigidity_ice_v(i,J) = Kv_rho_ice * mass_eff
forces%rigidity_ice_v(i,J) = forces%rigidity_ice_v(i,J) + Kv_rho_ice * mass_eff
enddo ; enddo
endif

Expand Down
2 changes: 1 addition & 1 deletion config_src/solo_driver/MOM_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -496,7 +496,7 @@ program MOM_main
endif

if (ns==1) then
call finish_MOM_initialization(Time, dirs, MOM_CSp, fluxes, restart_CSp)
call finish_MOM_initialization(Time, dirs, MOM_CSp, restart_CSp)
endif

! This call steps the model over a time dt_forcing.
Expand Down
24 changes: 13 additions & 11 deletions config_src/solo_driver/atmos_ocean_fluxes.F90
Original file line number Diff line number Diff line change
Expand Up @@ -10,21 +10,23 @@ module atmos_ocean_fluxes_mod

contains

!> This subroutine duplicates an interface used by the FMS coupler, but only
!! returns a value of -1. None of the arguments are used for anything.
function aof_set_coupler_flux(name, flux_type, implementation, atm_tr_index, &
param, flag, ice_restart_file, ocean_restart_file, &
units, caller, verbosity) result (coupler_index)

character(len=*), intent(in) :: name
character(len=*), intent(in) :: flux_type
character(len=*), intent(in) :: implementation
integer, intent(in), optional :: atm_tr_index
real, intent(in), dimension(:), optional :: param
logical, intent(in), dimension(:), optional :: flag
character(len=*), intent(in), optional :: ice_restart_file
character(len=*), intent(in), optional :: ocean_restart_file
character(len=*), intent(in), optional :: units
character(len=*), intent(in), optional :: caller
integer, intent(in), optional :: verbosity
character(len=*), intent(in) :: name !< An unused argument
character(len=*), intent(in) :: flux_type !< An unused argument
character(len=*), intent(in) :: implementation !< An unused argument
integer, optional, intent(in) :: atm_tr_index !< An unused argument
real, dimension(:), optional, intent(in) :: param !< An unused argument
logical, dimension(:), optional, intent(in) :: flag !< An unused argument
character(len=*), optional, intent(in) :: ice_restart_file !< An unused argument
character(len=*), optional, intent(in) :: ocean_restart_file !< An unused argument
character(len=*), optional, intent(in) :: units !< An unused argument
character(len=*), optional, intent(in) :: caller !< An unused argument
integer, optional, intent(in) :: verbosity !< An unused argument

! None of these arguments are used for anything.

Expand Down
Loading

0 comments on commit 026907e

Please sign in to comment.