Skip to content

Commit

Permalink
Shortened excesively long lines
Browse files Browse the repository at this point in the history
  Split lines exceeding 120 characters in 55 source files to promote readability
and compliance with MOM6 code standards.  All answers are bitwise identical.
  • Loading branch information
Hallberg-NOAA committed May 4, 2018
1 parent ceb6100 commit c36fa49
Show file tree
Hide file tree
Showing 55 changed files with 1,369 additions and 995 deletions.
2 changes: 1 addition & 1 deletion config_src/coupled_driver/MOM_surface_forcing.F90
Original file line number Diff line number Diff line change
Expand Up @@ -632,7 +632,7 @@ subroutine convert_IOB_to_forces(IOB, forces, index_bounds, Time, G, CS)
call safe_alloc_ptr(forces%rigidity_ice_u,IsdB,IedB,jsd,jed)
call safe_alloc_ptr(forces%rigidity_ice_v,isd,ied,JsdB,JedB)
endif

forces%initialized = .true.
endif

Expand Down
2 changes: 1 addition & 1 deletion config_src/coupled_driver/ocean_model_MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -585,7 +585,7 @@ subroutine update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, &
Waves=OS%Waves, do_dynamics=do_thermo, do_thermodynamics=do_dyn, &
reset_therm=Ocn_fluxes_used)
!### What to do with these? , start_cycle=(n==1), end_cycle=.false., cycle_length=dt_coupling)

elseif (OS%single_step_call) then
call step_MOM(OS%forces, OS%fluxes, OS%sfc_state, Time1, dt_coupling, OS%MOM_CSp, Waves=OS%Waves)
else
Expand Down
87 changes: 58 additions & 29 deletions config_src/solo_driver/coupler_types.F90

Large diffs are not rendered by default.

52 changes: 30 additions & 22 deletions src/ALE/MOM_ALE.F90
Original file line number Diff line number Diff line change
Expand Up @@ -295,7 +295,8 @@ end subroutine ALE_end
subroutine ALE_main( G, GV, h, u, v, tv, Reg, CS, dt, frac_shelf_h)
type(ocean_grid_type), intent(in) :: G !< Ocean grid informations
type(verticalGrid_type), intent(in) :: GV !< Ocean vertical grid structure
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(inout) :: h !< Current 3D grid obtained after last time step (m or Pa)
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(inout) :: h !< Current 3D grid obtained after the
!! last time step (m or Pa)
real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), intent(inout) :: u !< Zonal velocity field (m/s)
real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), intent(inout) :: v !< Meridional velocity field (m/s)
type(thermo_var_ptrs), intent(inout) :: tv !< Thermodynamic variable structure
Expand Down Expand Up @@ -381,7 +382,8 @@ end subroutine ALE_main
subroutine ALE_main_offline( G, GV, h, tv, Reg, CS, dt)
type(ocean_grid_type), intent(in) :: G !< Ocean grid informations
type(verticalGrid_type), intent(in) :: GV !< Ocean vertical grid structure
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(inout) :: h !< Current 3D grid obtained after last time step (m or Pa)
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(inout) :: h !< Current 3D grid obtained after the
!! last time step (m or Pa)
type(thermo_var_ptrs), intent(inout) :: tv !< Thermodynamic variable structure
type(tracer_registry_type), pointer :: Reg !< Tracer registry structure
type(ALE_CS), pointer :: CS !< Regridding parameters and options
Expand Down Expand Up @@ -514,7 +516,7 @@ end subroutine ALE_offline_inputs
subroutine ALE_offline_tracer_final( G, GV, h, tv, h_target, Reg, CS)
type(ocean_grid_type), intent(in) :: G !< Ocean grid informations
type(verticalGrid_type), intent(in) :: GV !< Ocean vertical grid structure
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(inout) :: h !< Current 3D grid obtained after
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(inout) :: h !< Current 3D grid obtained after the
!! last time step (m or Pa)
type(thermo_var_ptrs), intent(inout) :: tv !< Thermodynamic variable structure
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(inout) :: h_target !< Current 3D grid obtained after
Expand Down Expand Up @@ -556,9 +558,10 @@ end subroutine ALE_offline_tracer_final

!> Check grid for negative thicknesses
subroutine check_grid( G, GV, h, threshold )
type(ocean_grid_type), intent(in) :: G !< Ocean grid structure
type(verticalGrid_type), intent(in) :: GV !< Ocean vertical grid structure
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h !< Current 3D grid obtained after the last time step (H units)
type(ocean_grid_type), intent(in) :: G !< Ocean grid structure
type(verticalGrid_type), intent(in) :: GV !< Ocean vertical grid structure
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h !< Current 3D grid obtained after the
!! last time step (H units)
real, intent(in) :: threshold !< Value below which to flag issues (H units)
! Local variables
integer :: i, j
Expand Down Expand Up @@ -586,7 +589,8 @@ subroutine ALE_build_grid( G, GV, regridCS, remapCS, h, tv, debug, frac_shelf_h
type(regridding_CS), intent(in) :: regridCS !< Regridding parameters and options
type(remapping_CS), intent(in) :: remapCS !< Remapping parameters and options
type(thermo_var_ptrs), intent(inout) :: tv !< Thermodynamical variable structure
real, dimension(SZI_(G),SZJ_(G), SZK_(GV)), intent(inout) :: h !< Current 3D grid obtained after the last time step (m or Pa)
real, dimension(SZI_(G),SZJ_(G), SZK_(GV)), intent(inout) :: h !< Current 3D grid obtained after the
!! last time step (m or Pa)
logical, optional, intent(in) :: debug !< If true, show the call tree
real, dimension(:,:), optional, pointer :: frac_shelf_h !< Fractional ice shelf coverage
! Local variables
Expand Down Expand Up @@ -640,7 +644,8 @@ subroutine ALE_regrid_accelerated(CS, G, GV, h, tv, n, u, v, Reg, dt, dzRegrid,
real, optional, intent(in) :: dt !< Model timestep to provide a timescale for regridding
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1), &
optional, intent(inout) :: dzRegrid !< Final change in interface positions
logical, optional, intent(in) :: initial !< Whether we're being called from an initialization routine (and expect diagnostics to work)
logical, optional, intent(in) :: initial !< Whether we're being called from an initialization
!! routine (and expect diagnostics to work)

! Local variables
integer :: i, j, k, nz
Expand Down Expand Up @@ -707,18 +712,21 @@ end subroutine ALE_regrid_accelerated
!! remap initiali conditions to the model grid. It is also called during a
!! time step to update the state.
subroutine remap_all_state_vars(CS_remapping, CS_ALE, G, GV, h_old, h_new, Reg, dxInterface, u, v, debug, dt)
type(remapping_CS), intent(in) :: CS_remapping !< Remapping control structure
type(ALE_CS), intent(in) :: CS_ALE !< ALE control structure
type(ocean_grid_type), intent(in) :: G !< Ocean grid structure
type(verticalGrid_type), intent(in) :: GV !< Ocean vertical grid structure
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_old !< Thickness of source grid (m or Pa)
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_new !< Thickness of destination grid (m or Pa)
type(tracer_registry_type), pointer :: Reg !< Tracer registry structure
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1),optional, intent(in) :: dxInterface !< Change in interface position (Hm or Pa)
real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), optional, intent(inout) :: u !< Zonal velocity component (m/s)
real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), optional, intent(inout) :: v !< Meridional velocity component (m/s)
logical, optional, intent(in) :: debug !< If true, show the call tree
real, optional, intent(in) :: dt !< time step for diagnostics
type(remapping_CS), intent(in) :: CS_remapping !< Remapping control structure
type(ALE_CS), intent(in) :: CS_ALE !< ALE control structure
type(ocean_grid_type), intent(in) :: G !< Ocean grid structure
type(verticalGrid_type), intent(in) :: GV !< Ocean vertical grid structure
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_old !< Thickness of source grid (m or Pa)
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h_new !< Thickness of destination grid (m or Pa)
type(tracer_registry_type), pointer :: Reg !< Tracer registry structure
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1), &
optional, intent(in) :: dxInterface !< Change in interface position (Hm or Pa)
real, dimension(SZIB_(G),SZJ_(G),SZK_(GV)), &
optional, intent(inout) :: u !< Zonal velocity component (m/s)
real, dimension(SZI_(G),SZJB_(G),SZK_(GV)), &
optional, intent(inout) :: v !< Meridional velocity component (m/s)
logical, optional, intent(in) :: debug !< If true, show the call tree
real, optional, intent(in) :: dt !< time step for diagnostics
! Local variables
integer :: i, j, k, m
integer :: nz, ntr
Expand All @@ -740,8 +748,8 @@ subroutine remap_all_state_vars(CS_remapping, CS_ALE, G, GV, h_old, h_new, Reg,
! If remap_uv_using_old_alg is .true. and u or v is requested, then we must have dxInterface. Otherwise,
! u and v can be remapped without dxInterface
if ( .not. present(dxInterface) .and. (CS_ALE%remap_uv_using_old_alg .and. (present(u) .or. present(v))) ) then
call MOM_error(FATAL, "remap_all_state_vars: dxInterface must be present if using old algorithm and u/v are to"// &
"be remapped")
call MOM_error(FATAL, "remap_all_state_vars: dxInterface must be present if using old algorithm "// &
"and u/v are to be remapped")
endif

!### Try replacing both of these with GV%H_subroundoff
Expand Down
43 changes: 28 additions & 15 deletions src/ALE/MOM_remapping.F90
Original file line number Diff line number Diff line change
Expand Up @@ -224,9 +224,11 @@ subroutine remapping_core_h(CS, n0, h0, u0, n1, h1, u1, h_neglect, h_neglect_ed
.or. (u1min<u0min .or. u1max>u0max) ) then
write(0,*) 'iMethod = ',iMethod
write(0,*) 'H: h0tot=',h0tot,'h1tot=',h1tot,'dh=',h1tot-h0tot,'h0err=',h0err,'h1err=',h1err
if (abs(h1tot-h0tot)>h0err+h1err) write(0,*) 'H non-conservation difference=',h1tot-h0tot,'allowed err=',h0err+h1err,' <-----!'
if (abs(h1tot-h0tot)>h0err+h1err) &
write(0,*) 'H non-conservation difference=',h1tot-h0tot,'allowed err=',h0err+h1err,' <-----!'
write(0,*) 'UH: u0tot=',u0tot,'u1tot=',u1tot,'duh=',u1tot-u0tot,'u0err=',u0err,'u1err=',u1err,'uh_err=',uh_err
if (abs(u1tot-u0tot)>(u0err+u1err)+uh_err) write(0,*) 'U non-conservation difference=',u1tot-u0tot,'allowed err=',u0err+u1err+uh_err,' <-----!'
if (abs(u1tot-u0tot)>(u0err+u1err)+uh_err) &
write(0,*) 'U non-conservation difference=',u1tot-u0tot,'allowed err=',u0err+u1err+uh_err,' <-----!'
write(0,*) 'U: u0min=',u0min,'u1min=',u1min
if (u1min<u0min) write(0,*) 'U minimum overshoot=',u1min-u0min,' <-----!'
write(0,*) 'U: u0max=',u0max,'u1max=',u1max
Expand Down Expand Up @@ -311,9 +313,11 @@ subroutine remapping_core_w( CS, n0, h0, u0, n1, dx, u1, h_neglect, h_neglect_ed
.or. (u1min<u0min .or. u1max>u0max) ) then
write(0,*) 'iMethod = ',iMethod
write(0,*) 'H: h0tot=',h0tot,'h1tot=',h1tot,'dh=',h1tot-h0tot,'h0err=',h0err,'h1err=',h1err
if (abs(h1tot-h0tot)>h0err+h1err) write(0,*) 'H non-conservation difference=',h1tot-h0tot,'allowed err=',h0err+h1err,' <-----!'
if (abs(h1tot-h0tot)>h0err+h1err) &
write(0,*) 'H non-conservation difference=',h1tot-h0tot,'allowed err=',h0err+h1err,' <-----!'
write(0,*) 'UH: u0tot=',u0tot,'u1tot=',u1tot,'duh=',u1tot-u0tot,'u0err=',u0err,'u1err=',u1err,'uh_err=',uh_err
if (abs(u1tot-u0tot)>(u0err+u1err)+uh_err) write(0,*) 'U non-conservation difference=',u1tot-u0tot,'allowed err=',u0err+u1err+uh_err,' <-----!'
if (abs(u1tot-u0tot)>(u0err+u1err)+uh_err) &
write(0,*) 'U non-conservation difference=',u1tot-u0tot,'allowed err=',u0err+u1err+uh_err,' <-----!'
write(0,*) 'U: u0min=',u0min,'u1min=',u1min
if (u1min<u0min) write(0,*) 'U minimum overshoot=',u1min-u0min,' <-----!'
write(0,*) 'U: u0max=',u0max,'u1max=',u1max
Expand Down Expand Up @@ -836,19 +840,26 @@ subroutine remap_via_sub_cells( n0, h0, u0, ppoly0_E, ppoly0_coefficients, n1, h
write(0,*) 'method = ',method
write(0,*) 'Source to sub-cells:'
write(0,*) 'H: h0tot=',h0tot,'h2tot=',h2tot,'dh=',h2tot-h0tot,'h0err=',h0err,'h2err=',h2err
if (abs(h2tot-h0tot)>h0err+h2err) write(0,*) 'H non-conservation difference=',h2tot-h0tot,'allowed err=',h0err+h2err,' <-----!'
write(0,*) 'UH: u0tot=',u0tot,'u2tot=',u2tot,'duh=',u2tot-u0tot,'u0err=',u0err,'u2err=',u2err,'adjustment err=',u02_err
if (abs(u2tot-u0tot)>u0err+u2err) write(0,*) 'U non-conservation difference=',u2tot-u0tot,'allowed err=',u0err+u2err,' <-----!'
if (abs(h2tot-h0tot)>h0err+h2err) &
write(0,*) 'H non-conservation difference=',h2tot-h0tot,'allowed err=',h0err+h2err,' <-----!'
write(0,*) 'UH: u0tot=',u0tot,'u2tot=',u2tot,'duh=',u2tot-u0tot,'u0err=',u0err,'u2err=',u2err,&
'adjustment err=',u02_err
if (abs(u2tot-u0tot)>u0err+u2err) &
write(0,*) 'U non-conservation difference=',u2tot-u0tot,'allowed err=',u0err+u2err,' <-----!'
write(0,*) 'Sub-cells to target:'
write(0,*) 'H: h2tot=',h2tot,'h1tot=',h1tot,'dh=',h1tot-h2tot,'h2err=',h2err,'h1err=',h1err
if (abs(h1tot-h2tot)>h2err+h1err) write(0,*) 'H non-conservation difference=',h1tot-h2tot,'allowed err=',h2err+h1err,' <-----!'
if (abs(h1tot-h2tot)>h2err+h1err) &
write(0,*) 'H non-conservation difference=',h1tot-h2tot,'allowed err=',h2err+h1err,' <-----!'
write(0,*) 'UH: u2tot=',u2tot,'u1tot=',u1tot,'duh=',u1tot-u2tot,'u2err=',u2err,'u1err=',u1err,'uh_err=',uh_err
if (abs(u1tot-u2tot)>u2err+u1err) write(0,*) 'U non-conservation difference=',u1tot-u2tot,'allowed err=',u2err+u1err,' <-----!'
if (abs(u1tot-u2tot)>u2err+u1err) &
write(0,*) 'U non-conservation difference=',u1tot-u2tot,'allowed err=',u2err+u1err,' <-----!'
write(0,*) 'Source to target:'
write(0,*) 'H: h0tot=',h0tot,'h1tot=',h1tot,'dh=',h1tot-h0tot,'h0err=',h0err,'h1err=',h1err
if (abs(h1tot-h0tot)>h0err+h1err) write(0,*) 'H non-conservation difference=',h1tot-h0tot,'allowed err=',h0err+h1err,' <-----!'
if (abs(h1tot-h0tot)>h0err+h1err) &
write(0,*) 'H non-conservation difference=',h1tot-h0tot,'allowed err=',h0err+h1err,' <-----!'
write(0,*) 'UH: u0tot=',u0tot,'u1tot=',u1tot,'duh=',u1tot-u0tot,'u0err=',u0err,'u1err=',u1err,'uh_err=',uh_err
if (abs(u1tot-u0tot)>(u0err+u1err)+uh_err) write(0,*) 'U non-conservation difference=',u1tot-u0tot,'allowed err=',u0err+u1err+uh_err,' <-----!'
if (abs(u1tot-u0tot)>(u0err+u1err)+uh_err) &
write(0,*) 'U non-conservation difference=',u1tot-u0tot,'allowed err=',u0err+u1err+uh_err,' <-----!'
write(0,*) 'U: u0min=',u0min,'u1min=',u1min,'u2min=',u2min
if (u1min<u0min) write(0,*) 'U minimum overshoot=',u1min-u0min,' <-----!'
if (u2min<u0min) write(0,*) 'U2 minimum overshoot=',u2min-u0min,' <-----!'
Expand Down Expand Up @@ -1787,8 +1798,9 @@ logical function remapping_unit_tests(verbose)

call edge_values_explicit_h4( 5, (/1.,1.,1.,1.,1./), (/1.,3.,5.,7.,9./), ppoly0_E, &
h_neglect=1e-10 )
thisTest = test_answer(v, 5, ppoly0_E(:,1), (/0.,2.,4.,6.,8./), 'Line H4: left edges') ! Currently fails due to roundoff
thisTest = test_answer(v, 5, ppoly0_E(:,2), (/2.,4.,6.,8.,10./), 'Line H4: right edges') ! Currently fails due to roundoff
! The next two tests currently fail due to roundoff.
thisTest = test_answer(v, 5, ppoly0_E(:,1), (/0.,2.,4.,6.,8./), 'Line H4: left edges')
thisTest = test_answer(v, 5, ppoly0_E(:,2), (/2.,4.,6.,8.,10./), 'Line H4: right edges')
ppoly0_E(:,1) = (/0.,2.,4.,6.,8./)
ppoly0_E(:,2) = (/2.,4.,6.,8.,10./)
call PPM_reconstruction(5, (/1.,1.,1.,1.,1./), (/1.,3.,5.,7.,9./), ppoly0_E(1:5,:), &
Expand All @@ -1802,8 +1814,9 @@ logical function remapping_unit_tests(verbose)

call edge_values_explicit_h4( 5, (/1.,1.,1.,1.,1./), (/1.,1.,7.,19.,37./), ppoly0_E, &
h_neglect=1e-10 )
thisTest = test_answer(v, 5, ppoly0_E(:,1), (/3.,0.,3.,12.,27./), 'Parabola H4: left edges') ! Currently fails due to roundoff
thisTest = test_answer(v, 5, ppoly0_E(:,2), (/0.,3.,12.,27.,48./), 'Parabola H4: right edges') ! Currently fails due to roundoff
! The next two tests currently fail due to roundoff.
thisTest = test_answer(v, 5, ppoly0_E(:,1), (/3.,0.,3.,12.,27./), 'Parabola H4: left edges')
thisTest = test_answer(v, 5, ppoly0_E(:,2), (/0.,3.,12.,27.,48./), 'Parabola H4: right edges')
ppoly0_E(:,1) = (/0.,0.,3.,12.,27./)
ppoly0_E(:,2) = (/0.,3.,12.,27.,48./)
call PPM_reconstruction(5, (/1.,1.,1.,1.,1./), (/0.,1.,7.,19.,37./), ppoly0_E(1:5,:), &
Expand Down
17 changes: 10 additions & 7 deletions src/ALE/coord_adapt.F90
Original file line number Diff line number Diff line change
Expand Up @@ -64,7 +64,7 @@ end subroutine init_coord_adapt

!> Clean up the coordinate control structure
subroutine end_coord_adapt(CS)
type(adapt_CS), pointer :: CS
type(adapt_CS), pointer :: CS !< The control structure for this module

! nothing to do
if (.not. associated(CS)) return
Expand All @@ -74,7 +74,7 @@ end subroutine end_coord_adapt

subroutine set_adapt_params(CS, adaptTimeRatio, adaptAlpha, adaptZoom, adaptZoomCoeff, &
adaptBuoyCoeff, adaptDrho0, adaptDoMin)
type(adapt_CS), pointer :: CS
type(adapt_CS), pointer :: CS !< The control structure for this module
real, optional, intent(in) :: adaptTimeRatio, adaptAlpha, adaptZoom, adaptZoomCoeff
real, optional, intent(in) :: adaptBuoyCoeff, adaptDrho0
logical, optional, intent(in) :: adaptDoMin
Expand All @@ -91,14 +91,17 @@ subroutine set_adapt_params(CS, adaptTimeRatio, adaptAlpha, adaptZoom, adaptZoom
end subroutine set_adapt_params

subroutine build_adapt_column(CS, G, GV, tv, i, j, zInt, tInt, sInt, h, zNext)
type(adapt_CS), intent(in) :: CS
type(adapt_CS), intent(in) :: CS !< The control structure for this module
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
type(verticalGrid_type), intent(in) :: GV !< The ocean's vertical grid structure
type(thermo_var_ptrs), intent(in) :: tv !< A structure pointing to various thermodynamic variables
integer, intent(in) :: i, j
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1), intent(in) :: zInt, tInt, sInt
type(thermo_var_ptrs), intent(in) :: tv !< A structure pointing to various
!! thermodynamic variables
integer, intent(in) :: i, j !< The indices of the column to work on
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1), intent(in) :: zInt !< Interface heights, in H (m or kg m-2).
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1), intent(in) :: tInt !< Interface temperatures, in C
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)+1), intent(in) :: sInt !< Interface salinities, in psu
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h !< Layer thicknesses, in H (usually m or kg m-2)
real, dimension(SZK_(GV)+1), intent(inout) :: zNext ! updated interface positions
real, dimension(SZK_(GV)+1), intent(inout) :: zNext !< updated interface positions

! Local variables
integer :: k, nz
Expand Down
Loading

0 comments on commit c36fa49

Please sign in to comment.