basal_surface Derived Type

type, public, abstract :: basal_surface

An abstract data type which represents whatever lies below a glacier. This could be the ground, a plume, or a fully dynamic ocean model. Methods are available to provide the coupling information between the glacier and the basal surface.


Inherited by

type~~basal_surface~~InheritedByGraph type~basal_surface basal_surface type~plume plume type~plume->type~basal_surface type~static_plume static_plume type~static_plume->type~basal_surface type~cryosphere cryosphere type~cryosphere->type~basal_surface sub_ice type~ground ground type~ground->type~basal_surface type~asym_plume asym_plume type~asym_plume->type~basal_surface

Contents

Source Code


Type-Bound Procedures

procedure(get_scalar), public, deferred :: basal_melt

Returns the basal melt rate.

  • function get_scalar(this) result(property) Prototype

    Arguments

    Type IntentOptional AttributesName
    class(basal_surface), intent(in) :: this

    Return Value class(scalar_field), pointer

    The value of whatever property of the basal surface is being returned.

procedure(get_scalar), public, deferred :: basal_drag_parameter

Returns a value which may be needed to calculate basal drag, such as the coefficient of friction.

  • function get_scalar(this) result(property) Prototype

    Arguments

    Type IntentOptional AttributesName
    class(basal_surface), intent(in) :: this

    Return Value class(scalar_field), pointer

    The value of whatever property of the basal surface is being returned.

procedure(get_real), public, deferred :: water_density

Density of the water at the basal surface.

  • function get_real(this) result(property) Prototype

    Arguments

    Type IntentOptional AttributesName
    class(basal_surface), intent(in) :: this

    Return Value real(kind=r8)

    The value of whatever property of the basal surface is being returned.

procedure(setter), public, deferred :: update

Sets the state of the basal surface

  • subroutine setter(this, state_vector, ice_thickness) Prototype

    Arguments

    Type IntentOptional AttributesName
    class(basal_surface), intent(inout) :: this
    real(kind=r8), intent(in), dimension(:):: state_vector

    A real array containing the data describing the state of the basal surface.

    class(scalar_field), intent(in), optional :: ice_thickness

    The ice thickness which, if present, will be used to update the calculation of the melt rate and/or drag parameter.

procedure(get_i), public, deferred :: data_size

Returns the number of elements in the basal surface's state vector

  • function get_i(this) result(property) Prototype

    Arguments

    Type IntentOptional AttributesName
    class(basal_surface), intent(in) :: this

    Return Value integer

    The value of whatever property of the basal surface is being returned.

procedure(get_r81d), public, deferred :: state_vector

Returns the basal surface's state vector, a 1D array with all necessary data to describe its state.

  • function get_r81d(this) result(state_vector) Prototype

    Arguments

    Type IntentOptional AttributesName
    class(basal_surface), intent(in) :: this

    Return Value real(kind=r8), dimension(:), allocatable

    The state vector of the basal surface

procedure(read_dat), public, deferred :: read_data

Read the basal surface data from an HDF5 file on the disc.

  • subroutine read_dat(this, file_id, group_name, error) Prototype

    Arguments

    Type IntentOptional AttributesName
    class(basal_surface), intent(inout) :: this
    integer(kind=hid_t), intent(in) :: file_id

    The identifier for the HDF5 file/group from which the data will be read.

    character(len=*), intent(in) :: group_name

    The name of the group in the HDF5 file from which to read basal surface's data.

    integer, intent(out) :: error

    Flag indicating whether routine ran without error. If no error occurs then has value 0.

procedure(write_dat), public, deferred :: write_data

Writes the data describing the basal surface to the disc as an HDF5 file.

  • subroutine write_dat(this, file_id, group_name, error) Prototype

    Arguments

    Type IntentOptional AttributesName
    class(basal_surface), intent(in) :: this
    integer(kind=hid_t), intent(in) :: file_id

    The identifier for the HDF5 file/group in which this data is meant to be written.

    character(len=*), intent(in) :: group_name

    The name to give the group in the HDF5 file storing the basal surface's data.

    integer, intent(out) :: error

    Flag indicating whether routine ran without error. If no error occurs then has value 0.

procedure(surface_solve), public, deferred :: solve

Solves for the state of the basal surface given a particular ice shelf geometry.

  • subroutine surface_solve(this, ice_thickness, ice_density, ice_temperature, time, success) Prototype

    Arguments

    Type IntentOptional AttributesName
    class(basal_surface), intent(inout) :: this
    class(scalar_field), intent(in) :: ice_thickness

    Thickness of the ice above the basal surface

    real(kind=r8), intent(in) :: ice_density

    The density of the ice above the basal surface, assumed uniform

    real(kind=r8), intent(in) :: ice_temperature

    The temperature of the ice above the basal surface, assumed uniform

    real(kind=r8), intent(in) :: time

    The time to which the basal surface should be solved

    logical, intent(out) :: success

    True if the solver is successful, false otherwise

Source Code

  type, abstract, public :: basal_surface
    !* Author: Christopher MacMackin
    !  Date: April 2016
    !
    ! An abstract data type which represents whatever lies below a [[glacier]].
    ! This could be the ground, a plume, or a fully dynamic ocean model.
    ! Methods are available to provide the coupling information between the
    ! [[glacier]] and the basal surface.
    !
  contains
    procedure(get_scalar), deferred    :: basal_melt
      !! Returns the basal melt rate.
    procedure(get_scalar), deferred    :: basal_drag_parameter
      !! Returns a value which may be needed to calculate basal drag,
      !! such as the coefficient of friction.
    procedure(get_real), deferred      :: water_density
      !! Density of the water at the basal surface.
    procedure(setter), deferred        :: update
      !! Sets the state of the basal surface
    procedure(get_i), deferred         :: data_size
      !! Returns the number of elements in the basal surface's state
      !! vector
    procedure(get_r81d), deferred      :: state_vector
      !! Returns the basal surface's state vector, a 1D array with all
      !! necessary data to describe its state.
    procedure(read_dat), deferred      :: read_data
      !! Read the basal surface data from an HDF5 file on the disc.
    procedure(write_dat), deferred     :: write_data
      !! Writes the data describing the basal surface to the disc as
      !! an HDF5 file.
    procedure(surface_solve), deferred :: solve
      !! Solves for the state of the basal surface given a particular
      !! ice shelf geometry.
  end type basal_surface