Instantiates a plume object with initial coniditions provided by the arguments.At present only a 1D model is supported. If information is provided for higher dimensions then it will be ignored.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(static_plume), | intent(out) | :: | this | A plume object with its domain and initial conditions set according to the arguments of the constructor function. |
||
real(kind=r8), | intent(in), | dimension(:,:) | :: | domain | An array containing the upper and lower limits of the domain for the plume. The first index represents the dimension for which the boundaries apply. If the second index is 1 then it corresponds to the lower bound. If the second index is 2 then it corresponds to the upper bound. |
|
integer, | intent(in), | dimension(:) | :: | resolution | The number of data points in each dimension |
|
procedure(scalar_func) | :: | thickness | A function which calculates the initial value of the thickness of the plume at a given location. |
|||
procedure(velocity_func) | :: | velocity | A function which calculates the initial value of the velocity (vector) of the water at a given location in a plume. |
|||
procedure(scalar_func) | :: | temperature | A function which calculates the initial value of the temperature of the plume at a given location. |
|||
procedure(scalar_func) | :: | salinity | A function which calculates the initial value of the salinity of the plume at a given location. |
|||
class(abstract_entrainment), | intent(inout), | optional | allocatable | :: | entrainment_formulation | An object which calculates entrainment into the plume. Will be unallocated on exit. Defaults to that used by Jenkins (1991) with the coefficient $E_0 = 1$. |
class(abstract_melt_relationship), | intent(inout), | optional | allocatable | :: | melt_formulation | An object which calculates melting and the resulting thermal transfer into/out of the plume. Will be unallocated on exit. Defaults to that used by Dallaston et al. (2015), scaled to be consistent with the nondimensionalisation used here. |
class(ambient_conditions), | intent(inout), | optional | allocatable | :: | ambient_conds | An object specifying the salinity and temperature of the ambient ocean. Will be unallocated on exit. Defaults to uniform ambient salinity and temperature, both of which are set to 0 (as temperature and salinity are measured relative to some reference value). |
class(equation_of_state), | intent(inout), | optional | allocatable | :: | eos | An object specifying the equation of state for the water in the plume. Will be unallocated on exit. Defaults to linearised equation of state with no temperature dependence and a haline contraction coefficient of 1. The reference density is set to be 1 in the dimensionless units when salinity and temeprature are 0. |
class(plume_boundary), | intent(inout), | optional | allocatable | :: | boundaries | An object providing the boundary conditions for the plume. Will be unallocated on exit. Defaults to those used by Dallaston et al. (2015). |
real(kind=r8), | intent(in), | optional | :: | delta | The dimensionless ratio . Defaults to 0.036. |
|
real(kind=r8), | intent(in), | optional | :: | nu | The dimensionless ratio . Defaults to 0. |
|
real(kind=r8), | intent(in), | optional | :: | mu | The dimensionless ratio . Defaults to 0. |
|
real(kind=r8), | intent(in), | optional | :: | r_val | The dimensionless ratio of the water density to the ice shelf density, Defaults to 1.12. |
|
real(kind=r8), | intent(in), | optional | :: | phi | The inverse Rossby number, . Defaults to 0. |
subroutine static_plume_initialise(this, domain, resolution, thickness, velocity, &
temperature, salinity, entrainment_formulation, &
melt_formulation, ambient_conds, eos, boundaries, &
delta, nu, mu, r_val, phi)
!* Author: Christopher MacMackin
! Date: April 2016
!
! Instantiates a [[plume(type)]] object with initial coniditions
! provided by the arguments.At present only a 1D model is
! supported. If information is provided for higher dimensions then
! it will be ignored.
!
class(static_plume), intent(out) :: this
!! A plume object with its domain and initial conditions set according
!! to the arguments of the constructor function.
real(r8), dimension(:,:), intent(in) :: domain
!! An array containing the upper and lower limits of the domain for
!! the plume. The first index represents the dimension for which the
!! boundaries apply. If the second index is 1 then it corresponds to
!! the lower bound. If the second index is 2 then it corresponds to
!! the upper bound.
integer, dimension(:), intent(in) :: resolution
!! The number of data points in each dimension
procedure(scalar_func) :: thickness
!! A function which calculates the initial value of the thickness of
!! the plume at a given location.
procedure(velocity_func) :: velocity
!! A function which calculates the initial value of the velocity
!! (vector) of the water at a given location in a plume.
procedure(scalar_func) :: temperature
!! A function which calculates the initial value of the temperature of
!! the plume at a given location.
procedure(scalar_func) :: salinity
!! A function which calculates the initial value of the salinity of
!! the plume at a given location.
class(abstract_entrainment), allocatable, optional, &
intent(inout) :: entrainment_formulation
!! An object which calculates entrainment into the plume. Will
!! be unallocated on exit. Defaults to that used by Jenkins
!! (1991) with the coefficient $E_0 = 1$.
class(abstract_melt_relationship), allocatable, optional, &
intent(inout) :: melt_formulation
!! An object which calculates melting and the resulting thermal
!! transfer into/out of the plume. Will be unallocated on
!! exit. Defaults to that used by Dallaston et al. (2015),
!! scaled to be consistent with the nondimensionalisation used
!! here.
class(ambient_conditions), allocatable, optional, &
intent(inout) :: ambient_conds
!! An object specifying the salinity and temperature of the
!! ambient ocean. Will be unallocated on exit. Defaults to
!! uniform ambient salinity and temperature, both of which are
!! set to 0 (as temperature and salinity are measured relative
!! to some reference value).
class(equation_of_state), allocatable, optional, &
intent(inout) :: eos
!! An object specifying the equation of state for the water in
!! the plume. Will be unallocated on exit. Defaults to
!! linearised equation of state with no temperature dependence
!! and a haline contraction coefficient of 1. The reference
!! density is set to be 1 in the dimensionless units when
!! salinity and temeprature are 0.
class(plume_boundary), allocatable, optional, &
intent(inout) :: boundaries
!! An object providing the boundary conditions for the
!! plume. Will be unallocated on exit. Defaults to those used by
!! Dallaston et al. (2015).
real(r8), optional, intent(in) :: delta
!! The dimensionless ratio \(\delta \equiv
!! \frac{D_0}{h_0}\). Defaults to 0.036.
real(r8), optional, intent(in) :: nu
!! The dimensionless ratio \(\nu \equiv
!! \frac{\kappa_0}{x_0U_o}\). Defaults to 0.
real(r8), optional, intent(in) :: mu
!! The dimensionless ratio \(\mu \equiv
!! \frac{\C_dx_0}{D_0}\). Defaults to 0.
real(r8), optional, intent(in) :: r_val
!! The dimensionless ratio of the water density to the ice shelf
!! density, \( r = \rho_0/\rho_i. \) Defaults to 1.12.
real(r8), optional, intent(in) :: phi
!! The inverse Rossby number, \(\Phi \equif
!! \frac{fx_0}{U_0}\). Defaults to 0.
integer :: i, btype_l, btype_u, bdepth_l, bdepth_u
i = size(velocity([0._r8]))
this%thickness = cheb1d_scalar_field(resolution(1),thickness,domain(1,1),domain(1,2))
this%velocity = cheb1d_vector_field(resolution(1),velocity,domain(1,1),domain(1,2),i-1)
this%temperature = cheb1d_scalar_field(resolution(1),temperature,domain(1,1),domain(1,2))
this%salinity = cheb1d_scalar_field(resolution(1),salinity,domain(1,1),domain(1,2))
this%thickness_size = this%thickness%raw_size()
this%velocity_size = this%velocity%raw_size()
this%temperature_size = this%temperature%raw_size()
this%salinity_size = this%salinity%raw_size()
this%velocity_dx = this%velocity%d_dx(1)
this%salinity_dx = this%salinity%d_dx(1)
this%temperature_dx = this%temperature%d_dx(1)
if (present(entrainment_formulation)) then
call move_alloc(entrainment_formulation, this%entrainment_formulation)
else
allocate(jenkins1991_entrainment :: this%entrainment_formulation)
end if
if (present(melt_formulation)) then
call move_alloc(melt_formulation, this%melt_formulation)
else
allocate(dallaston2015_melt :: this%melt_formulation)
end if
if (present(ambient_conds)) then
call move_alloc(ambient_conds, this%ambient_conds)
else
allocate(uniform_ambient_conditions :: this%ambient_conds)
end if
if (present(eos)) then
call move_alloc(eos, this%eos)
else
allocate(linear_eos :: this%eos)
end if
if (present(boundaries)) then
call move_alloc(boundaries, this%boundaries)
else
allocate(simple_plume_boundary :: this%boundaries)
end if
if (present(delta)) then
this%delta = delta
else
this%delta = 0.036_r8
end if
if (present(nu)) then
this%nu = nu
else
this%nu = 0.0_r8
end if
if (present(mu)) then
this%mu = mu
else
this%mu = 0.0_r8
end if
if (present(r_val)) then
this%r_val = r_val
else
this%r_val = 1.12_r8
end if
if (present(phi)) then
this%phi = phi
else
this%phi = 0.0_r8
end if
this%time = 0.0_r8
#ifdef DEBUG
call logger%debug('static_plume','Initialised new ice shelf object.')
#endif
end subroutine static_plume_initialise