Skip to content

Commit

Permalink
Variable renaming, whitespace and documentation. mom-ocean#334
Browse files Browse the repository at this point in the history
  • Loading branch information
Nicholas Hannah committed Nov 4, 2016
1 parent fdb4caf commit 8fb94a2
Show file tree
Hide file tree
Showing 2 changed files with 63 additions and 77 deletions.
18 changes: 10 additions & 8 deletions src/framework/MOM_diag_mediator.F90
Original file line number Diff line number Diff line change
Expand Up @@ -43,8 +43,8 @@ module MOM_diag_mediator
use MOM_diag_remap, only : diag_remap_update
use MOM_diag_remap, only : diag_remap_init, diag_remap_end, diag_remap_do_remap
use MOM_diag_remap, only : vertically_reintegrate_diag_field, vertically_interpolate_diag_field
use MOM_diag_remap, only : diag_remap_set_vertical_axes, diag_remap_get_nz
use MOM_diag_remap, only : diag_remap_axes_setup_done, diag_remap_get_vertical_ids
use MOM_diag_remap, only : diag_remap_configure_axes, diag_remap_axes_configured
use MOM_diag_remap, only : diag_remap_get_axes_info
use regrid_consts, only : coordinateMode, DEFAULT_COORDINATE_MODE, REGRIDDING_NUM_TYPES
use regrid_consts, only : vertical_coords, vertical_coord_strings

Expand Down Expand Up @@ -303,13 +303,15 @@ subroutine set_axes_info(G, GV, param_file, diag_cs, set_vertical)

do i=1, size(diag_cs%diag_remap_cs)
! For each possible diagnostic coordinate
call diag_remap_set_vertical_axes(diag_cs%diag_remap_cs(i), G, GV, param_file)
! This fetches the 1D-axis id for layers and interfaces and overwrite id_zl and id_zi from above
nz = diag_remap_get_nz(diag_cs%diag_remap_cs(i))
call diag_remap_configure_axes(diag_cs%diag_remap_cs(i), G, GV, param_file)

! This vertical coordinate has been configured so can be used.
if (diag_remap_axes_configured(diag_cs%diag_remap_cs(i))) then

! This fetches the 1D-axis id for layers and interfaces and overwrite
! id_zl and id_zi from above. It also returns the number of layers.
call diag_remap_get_axes_info(diag_cs%diag_remap_cs(i), nz, id_zL, id_zi)

! If nz > 0 this vertical coordinate has been configured so can be used.
if (nz>0) then
call diag_remap_get_vertical_ids(diag_cs%diag_remap_cs(i), id_zL, id_zi)
! Axes for z layers
call define_axes_group(diag_cs, (/ id_xh, id_yh, id_zL /), diag_cs%remap_axesTL(i), &
nz=nz, vertical_coordinate_number=i, &
Expand Down
122 changes: 53 additions & 69 deletions src/framework/MOM_diag_remap.F90
Original file line number Diff line number Diff line change
@@ -1,31 +1,20 @@
!> This module is used for runtime remapping of diagnostics to z star, sigma and
!! rho vertical coordinates. It defines the diag_remap_ctrl type which
!! represents a remapping of diagnostics to a particular vertical coordinate.
!! The module is It is used by the diag mediator module in the following way:
!! 1) _init() is called to initialise a diag_remap_ctrl instance.
!! 2) _configure_axes() is called to read the configuration file and set up the
!! vertical coordinate / axes definitions.
!! 3) _get_axes_info() returns information needed for the diag mediator to
!! define new axes for the remapped diagnostics.
!! 4) _update() is called periodically (whenever h, T or S change) to either
!! create or update the target remapping grids.
!! 5) _do_remap() is called from within a diag post() to do the remapping before
!! the diagnostic is written out.

module MOM_diag_remap

!***********************************************************************
!* GNU General Public License *
!* This file is a part of MOM. *
!* *
!* MOM is free software; you can redistribute it and/or modify it and *
!* are expected to follow the terms of the GNU General Public License *
!* as published by the Free Software Foundation; either version 2 of *
!* the License, or (at your option) any later version. *
!* *
!* MOM is distributed in the hope that it will be useful, but WITHOUT *
!* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY *
!* or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public *
!* License for more details. *
!* *
!* For the full text of the GNU General Public License, *
!* write to: Free Software Foundation, Inc., *
!* 675 Mass Ave, Cambridge, MA 02139, USA. *
!* or see: http://www.gnu.org/licenses/gpl.html *
!***********************************************************************

!********+*********+*********+*********+*********+*********+*********+**
!* *
!* The subroutines here are used for runtime remapping of *
!* diagnostics. *
!* *
!********+*********+*********+*********+*********+*********+*********+**
! This file is part of MOM6. See LICENSE.md for the license.

use MOM_error_handler, only : MOM_error, FATAL, assert
use MOM_diag_vkernels, only : interpolate_column, reintegrate_column
Expand Down Expand Up @@ -53,18 +42,18 @@ module MOM_diag_remap

public diag_remap_ctrl
public diag_remap_init, diag_remap_end, diag_remap_update, diag_remap_do_remap
public diag_remap_set_vertical_axes, diag_remap_axes_setup_done, diag_remap_get_nz
public diag_remap_get_vertical_ids
public diag_remap_configure_axes, diag_remap_axes_configured
public diag_remap_get_axes_info
public vertically_reintegrate_diag_field
public vertically_interpolate_diag_field

!> This type represents a remapping of a diagnostic to a particular vertical
!> This type represents remapping of diagnostics to a particular vertical
!! coordinate.
!! There is one of these types for each vertical coordinate. The vertical axes
!! of a diagnostic will reference an instance of this type indicating how (or
!! if) the diagnostic should be vertically remapped when being posted.
type :: diag_remap_ctrl
logical :: defined = .false. !< Whether a coordinate has been defined
logical :: configured = .false. !< Whether vertical coordinate has been configured
logical :: initialized = .false. !< Whether remappping initialized
integer :: vertical_coord = 0 !< The vertical coordinate that we remap to
type(remapping_CS), pointer :: remap_cs => null() !< type for remapping using ALE module
Expand All @@ -85,8 +74,8 @@ subroutine diag_remap_init(remap_cs, vertical_coord)
integer, intent(in) :: vertical_coord !< The vertical coordinate it represents

remap_cs%vertical_coord = vertical_coord
remap_cs%configured = .false.
remap_cs%initialized = .false.
remap_cs%defined = .false.
remap_cs%nz = 0

end subroutine diag_remap_init
Expand All @@ -98,27 +87,29 @@ subroutine diag_remap_end(remap_cs)

if (allocated(remap_cs%h)) deallocate(remap_cs%h)
if (allocated(remap_cs%dz)) deallocate(remap_cs%dz)
remap_cs%configured = .false.
remap_cs%initialized = .false.
remap_cs%nz = 0

end subroutine diag_remap_end

!> Configure the vertical axes for a diagnostic remapping control structure.
!! Reads a configuration file to determine nominal location of vertical
!! layers/interfaces.
subroutine diag_remap_set_vertical_axes(remap_cs, G, GV, param_file)
subroutine diag_remap_configure_axes(remap_cs, G, GV, param_file)
type(diag_remap_ctrl), intent(inout) :: remap_cs !< Diag remap control structure
type(ocean_grid_type), intent(inout) :: G !< Ocean grid structure
type(verticalGrid_type), intent(in) :: GV !< ocean vertical grid structure
type(param_file_type), intent(in) :: param_file !< Parameter file structure

if (remap_cs%vertical_coord /= coordinateMode('LAYER')) then
call setup_axes(remap_cs, G, GV, param_file)
call configure_axes(remap_cs, G, GV, param_file)
endif

end subroutine diag_remap_set_vertical_axes
end subroutine diag_remap_configure_axes

!> Read grid definition spec to configure axes.
subroutine setup_axes(remap_cs, G, GV, param_file)
subroutine configure_axes(remap_cs, G, GV, param_file)
type(diag_remap_ctrl), intent(inout) :: remap_cs !< Diag remap control structure
type(ocean_grid_type), intent(inout) :: G !< Ocean grid structure
type(verticalGrid_type), intent(in) :: GV !< ocean vertical grid structure
Expand Down Expand Up @@ -271,13 +262,18 @@ subroutine setup_axes(remap_cs, G, GV, param_file)
endif

! Make axes objects
remap_cs%defined = .true.
remap_cs%layer_axes_id = diag_axis_init(lowercase(trim(vertical_coord_strings(remap_cs%vertical_coord)))//'_l', &
layers, trim(units), 'z', &
trim(longname)//' at cell center', direction=-1)
remap_cs%interface_axes_id = diag_axis_init(lowercase(trim(vertical_coord_strings(remap_cs%vertical_coord)))//'_i', &
interfaces, trim(units), 'z', &
trim(longname)//' Depth at interface', direction=-1)
remap_cs%layer_axes_id = &
diag_axis_init(lowercase(trim(vertical_coord_strings(remap_cs%vertical_coord)))//'_l', &
layers, trim(units), 'z', &
trim(longname)//' at cell center', direction=-1)
remap_cs%interface_axes_id = &
diag_axis_init(lowercase(trim(vertical_coord_strings(remap_cs%vertical_coord)))//'_i', &
interfaces, trim(units), 'z', &
trim(longname)//' Depth at interface', direction=-1)

! Axes have now been configured.
remap_cs%configured = .true.

deallocate(interfaces)
deallocate(layers)
else
Expand All @@ -286,7 +282,7 @@ subroutine setup_axes(remap_cs, G, GV, param_file)
remap_cs%interface_axes_id = -1
endif

end subroutine setup_axes
end subroutine configure_axes

subroutine check_grid_def(filename, varname, expected_units, msg, ierr)
! Do some basic checks on the vertical grid definition file, variable
Expand Down Expand Up @@ -339,35 +335,28 @@ subroutine check_grid_def(filename, varname, expected_units, msg, ierr)
end subroutine check_grid_def

!> Get layer and interface axes ids for this coordinate
subroutine diag_remap_get_vertical_ids(remap_cs, id_layer, id_interface)
!! Needed when defining axes groups.
subroutine diag_remap_get_axes_info(remap_cs, nz, id_layer, id_interface)
type(diag_remap_ctrl), intent(in) :: remap_cs !< Diagnostic coordinate control structure
integer, intent(out) :: nz !< Number of vertical levels for the coordinate
integer, intent(out) :: id_layer !< 1D-axes id for layer points
integer, intent(out) :: id_interface !< 1D-axes id for interface points

nz = remap_cs%nz
id_layer = remap_cs%layer_axes_id
id_interface = remap_cs%interface_axes_id

end subroutine diag_remap_get_vertical_ids

!> Get the number of vertical levels for this coordinate.
!! This is needed when defining axes groups.
function diag_remap_get_nz(remap_cs)
type(diag_remap_ctrl), intent(in) :: remap_cs
integer :: diag_remap_get_nz
end subroutine diag_remap_get_axes_info

diag_remap_get_nz = remap_cs%nz

end function

function diag_remap_axes_setup_done(remap_cs)
!> Whether or not the axes for this vertical coordinated has been configured.
!! Configuration is complete when diag_remap_configure_axes() has been
!! successfully called.
function diag_remap_axes_configured(remap_cs)
type(diag_remap_ctrl), intent(in) :: remap_cs
logical :: diag_remap_axes_setup_done
logical :: diag_remap_axes_configured

if (allocated(remap_cs%dz)) then
diag_remap_axes_setup_done = .true.
else
diag_remap_axes_setup_done = .false.
endif
diag_remap_axes_configured = remap_cs%configured

end function

Expand All @@ -384,18 +373,14 @@ subroutine diag_remap_update(remap_cs, G, h, T, S, eqn_of_state)

! Local variables
integer :: i, j, k, nz
logical :: checked
real, dimension(remap_cs%nz + 1) :: zInterfaces
real, dimension(remap_cs%nz) :: resolution

if (remap_cs%vertical_coord == coordinateMode('LAYER') .or. &
.not. diag_remap_axes_setup_done(remap_cs)) then
.not. diag_remap_axes_configured(remap_cs)) then
return
endif

call assert(remap_cs%defined, 'diag_remap_update: Attempting to update an undefined coordinate!')

checked = .false.
nz = remap_cs%nz

if (.not. remap_cs%initialized) then
Expand All @@ -404,12 +389,12 @@ subroutine diag_remap_update(remap_cs, G, h, T, S, eqn_of_state)
call initialize_remapping(remap_cs%remap_cs, 'PPM_IH4', boundary_extrapolation=.false.)

allocate(remap_cs%regrid_cs)
call initialize_regridding(remap_cs%nz, &
call initialize_regridding(nz, &
vertical_coord_strings(remap_cs%vertical_coord), 'PPM_IH4', remap_cs%regrid_cs)
call set_regrid_params(remap_cs%regrid_cs, min_thickness=0., integrate_downward_for_e=.false.)
call setCoordinateResolution(remap_cs%dz, remap_cs%regrid_cs)

allocate(remap_cs%h(G%isd:G%ied,G%jsd:G%jed,remap_cs%nz))
allocate(remap_cs%h(G%isd:G%ied,G%jsd:G%jed, nz))
endif

! Calculate remapping thicknesses for different target grids based on
Expand Down Expand Up @@ -470,7 +455,6 @@ subroutine diag_remap_do_remap(remap_cs, G, h, staggered_in_x, staggered_in_y, &
real :: depth, bathy


call assert(remap_cs%defined, 'diag_remap_do_remap: remap_cs is for an undefined coordinate!')
call assert(remap_cs%initialized, 'diag_remap_do_remap: remap_cs not initialized.')
call assert(size(field, 3) == size(h, 3), &
'diag_remap_do_remap: Remap field and thickness z-axes do not match.')
Expand Down

0 comments on commit 8fb94a2

Please sign in to comment.