FEDEM Solver  R8.0
Source code of the dynamics solver
Data Types | Functions/Subroutines | Variables
hydrodynamicsmodule Module Reference

Module with subroutines for hydrodynamic load calculations. More...

Data Types

interface  updateatconvergence
 Updates hydrodynamics quantities after a time step is converged. More...
 

Functions/Subroutines

subroutine, public initfluidmotions (time, env, triads, sups, ierr)
 Initializes the fluid particle motion cache for all triads in water. More...
 
logical function, public getcalculatedfluidmotion (triad, elev, fvel, facc)
 Returns the latest calculated fluid particle motion at a triad. More...
 
real(dp) function watersurfacenormal (normal, gravity, Tlg)
 Returns the water surface normal vector in local coordinate system. More...
 
subroutine evaluatewave (waveFunc, waveTheory, Twave, g, depth, Xg, time, scale, wave, dynp, stat)
 Evaluates the wave profile, velocity and acceleration at a point. More...
 
subroutine evaluatecurrent (currFunc, dirFunc, Tsea, Xg, time, scale, cvel, stat)
 Evaluates the sea current velocity at the given point and time. More...
 
subroutine evaluatesea (env, g, time, istep, inod, x, waterMotion, stat)
 Evaluates the sea state at the given point and time. More...
 
real(dp) function, public getwaveelevation (env, Xg, time, stat)
 Returns the wave height at the given point and time. More...
 
subroutine, public getseastate (env, time, Xg, sea, stat)
 Evaluates the sea state at the given point and time. More...
 
subroutine, public initiatehydrodynbodies (sups, elms, env, restart, ierr)
 Initiates all hydrodynamic bodies in the model. More...
 
subroutine updatehydrodynbody (hydyn, triads, supTr, sLev, gravity, g, wb, ierr)
 Updates the hydrodynamic body quantities. More...
 
subroutine getbeamlength (triad1, triad2, normal, h1, h2, Tlg, weight, Lb, C0b, iEnd)
 Computes the buoyancy length and center for a two-noded beam. More...
 
subroutine, public getmorisonforces (beamId, triads, supTr, urd, urdd, Q, eMa, eCd, hydyn, env, time, istep, iter, ierr)
 Calculates Morison force contributions for a two-noded beam element. More...
 
subroutine, public getbuoyancyforces (supId, triads, supTr, hydyn, env, g, time, iter, Q, ierr)
 Calculates buoyancy force resultant for a superelement or beam. More...
 
subroutine, public getdragforces (Fd, sup, hydyn, env, time, dt, ierr)
 Calculates drag (and slam) forces for a (partly) submerged body. More...
 
subroutine updatehydrodynamicsatconvergence (hydyn, supTr, ierr)
 Updates the HydroDynType object after convergence has been achieved. More...
 
subroutine, public closehydrodyn (lpu)
 Closes the hydrodynamics module and report some timings. More...
 
subroutine, public diffractioncalc (env, waveFunc, ierr)
 Performs diffraction analysis using Nemoh. More...
 
subroutine, public getdiffractionforces (Q, sup, hydyn, env, time, ierr)
 Extracts the diffraction force at a given time for a superelement. More...
 

Variables

real(dp), dimension(:,:), allocatable, save watermotion
 Fluid particle motions. More...
 
integer, dimension(:), allocatable, save calcwmotion
 Have calculated motions? More...
 
real(dp), parameter eps_p = 1.0e-16_dp
 Zero tolerance. More...
 

Detailed Description

Module with subroutines for hydrodynamic load calculations.

This module deals with the calculation of hydrodynamic loads (buoyancy, inertia loads due to added mass, damping forces due to drag, etc.) for beam- and superelements. It also manages the evaluation of the fluid particle motions, which are needed in the hydrodynamic load calculations.

Some of the subroutines and functions of this module are not documented. You have to configure doxygen with the option ENABLED_SECTIONS = FULL_DOC to extract detailed documentation of those subroutines and functions.

Function/Subroutine Documentation

◆ closehydrodyn()

subroutine, public hydrodynamicsmodule::closehydrodyn ( integer, intent(in)  lpu)

Closes the hydrodynamics module and report some timings.

Parameters
[in]lpuFile unit number for res-file output
Author
Knut Morten Okstad
Date
9 Jan 2012
Here is the call graph for this function:
Here is the caller graph for this function:

◆ diffractioncalc()

subroutine, public hydrodynamicsmodule::diffractioncalc ( type(environmenttype), intent(in)  env,
type(functiontype), intent(in)  waveFunc,
integer, intent(out)  ierr 
)

Performs diffraction analysis using Nemoh.

Parameters
[in]envEnvironmental data
[in]waveFuncThe wave function to use in the diffraction analysis
[out]ierrError flag
Author
Knut Morten Okstad
Date
06 Mar 2015
Here is the call graph for this function:
Here is the caller graph for this function:

◆ evaluatecurrent()

subroutine hydrodynamicsmodule::evaluatecurrent ( type(functiontype), pointer  currFunc,
type(functiontype), pointer  dirFunc,
real(dp), dimension(3,4), intent(in)  Tsea,
real(dp), dimension(3), intent(in)  Xg,
real(dp), intent(in)  time,
real(dp), intent(in)  scale,
real(dp), dimension(3), intent(out)  cvel,
integer, intent(inout)  stat 
)

Evaluates the sea current velocity at the given point and time.

Parameters
[in]currFuncThe sea current velocity function to evaluate for
[in]dirFuncThe sea current direction function
[in]TseaCoordinate system for the sea current
[in]XgGlobal coordinates of the evaluation point
[in]timeCurrent simulation time
[in]scaleScaling factor
[out]cvelSea current velocity in global axis directions
statStatus flag (negative on error exit). 1 = The point is below or on the water surface. 2 = The point is above the water surface (no kinematics).
Author
Knut Morten Okstad
Date
27 Oct 2009
Here is the call graph for this function:
Here is the caller graph for this function:

◆ evaluatesea()

subroutine hydrodynamicsmodule::evaluatesea ( type(environmenttype), intent(in)  env,
real(dp), intent(in)  g,
real(dp), intent(in)  time,
integer, intent(in)  istep,
integer, intent(in)  inod,
real(dp), dimension(3), intent(in)  x,
real(dp), dimension(:), intent(out)  waterMotion,
integer, intent(inout)  stat 
)
private

Evaluates the sea state at the given point and time.

Parameters
[in]envEnvironmental data
[in]gGravitation constant
[in]timeCurrent simulation time
[in]istepTime increment counter
[in]inodNodal number of sea kinematics evaluation point
[in]xGlobal coordinates of sea kinematics evaluation point
[out]waterMotionSea kinematics state at current point. waterMotion(1:3) = Projection of point x onto the current sea surface. waterMotion(4:6) = Particle velocity at point x in global coordinates. waterMotion(7:9) = Particle acceleration at point x in global coordinates.
statStatus flag (negative on error exit)
Author
Knut Morten Okstad
Date
9 Sep 2011
Here is the call graph for this function:
Here is the caller graph for this function:

◆ evaluatewave()

subroutine hydrodynamicsmodule::evaluatewave ( type(functiontype), intent(in)  waveFunc,
integer, intent(in)  waveTheory,
real(dp), dimension(3,4), intent(in)  Twave,
real(dp), intent(in)  g,
real(dp), intent(in)  depth,
real(dp), dimension(3), intent(in)  Xg,
real(dp), intent(in)  time,
real(dp), intent(in)  scale,
real(dp), dimension(3,3), intent(out)  wave,
real(dp), intent(out), optional  dynp,
integer, intent(inout)  stat 
)

Evaluates the wave profile, velocity and acceleration at a point.

Parameters
[in]waveFuncThe wave function to evaluate for
[in]waveTheoryFlag indicating which wave theory to use
[in]TwaveWave coordinate system (axis directions and origin)
[in]gGravitation constant
[in]depthWater depth (zero means infinite)
[in]XgGlobal coordinates of the evaluation point
[in]timeCurrent simulation time
[in]scaleScaling factor
[out]waveWave kinematics quantities at the evaluation point. wave(:,1) = Projection of point coordinates onto the current sea surface. wave(:,2) = Water particle velocity. wave(:,3) = Water particle acceleration.
[out]dynpDynamic pressure (optional)
statStatus flag (negative on error exit). 1 = The point is below or on the water surface. 2 = The point is above the water surface (no kinematics).

The calculated wave kinematics quantities are referring to the global coordinate system, unless when stat is negative on entry. In the latter case the wave coordinate system is used.

Author
Knut Morten Okstad
Date
25 Mar 2009
Here is the call graph for this function:
Here is the caller graph for this function:

◆ getbeamlength()

subroutine hydrodynamicsmodule::getbeamlength ( type(triadtype), intent(in)  triad1,
type(triadtype), intent(in)  triad2,
real(dp), dimension(3), intent(in)  normal,
real(dp), intent(in)  h1,
real(dp), intent(in)  h2,
real(dp), dimension(3,4), intent(in), optional  Tlg,
real(dp), dimension(2), intent(out), optional  weight,
real(dp), intent(out)  Lb,
real(dp), dimension(3), intent(out), optional  C0b,
integer, intent(out), optional  iEnd 
)

Computes the buoyancy length and center for a two-noded beam.

Parameters
[in]triad1Triad art first end of the beam
[in]triad2Triad art second end of the beam
[in]normalNormal vector of the water surface in global coordinates
[in]h1Height of the water surface along the normal vector for end 1
[in]h2Height of the water surface along the normal vector for end 2
[in]TlgLocal to global transformation matrix for the beam element
[out]weightBuoyancy weight factors
[out]LbLength of the submerged part of the beam (buoyancy length)
[out]C0bCentre of buoyancy
[out]iEndWhich end is below the water surface, if partly submerged. iEnd < 0 : This element is completely submerged. iEnd = 0 : This element is completely in the air.
Author
Knut Morten Okstad
Date
29 Sep 2008
Here is the caller graph for this function:

◆ getbuoyancyforces()

subroutine, public hydrodynamicsmodule::getbuoyancyforces ( character(len=*), intent(in)  supId,
type(triadptrtype), dimension(:), intent(in)  triads,
real(dp), dimension(:,:), intent(in)  supTr,
type(hydrodyntype), intent(inout)  hydyn,
type(environmenttype), intent(inout)  env,
real(dp), intent(out)  g,
real(dp), intent(in)  time,
integer, intent(in)  iter,
real(dp), dimension(:), intent(inout), optional  Q,
integer, intent(out)  ierr 
)

Calculates buoyancy force resultant for a superelement or beam.

Parameters
[in]supIdID string of the superelement used in feedback messages
[in]triadsTriads connected to the superelement
[in]supTrPosition matrix for the superelement
hydynData for hydrodynamic force calculation
envEnvironmental data
[out]gGravitation constant
[in]timeCurrent simulation time
[in]iterIteration counter
QExternal nodal forces for beams, including buoyancy on output
[out]ierrError flag

The contributions to the external load vector form the hydrostatic buoyancy may optionally be calculated, but only for two-noded elements.

Author
Knut Morten Okstad
Date
2 Jul 2008
Here is the call graph for this function:
Here is the caller graph for this function:

◆ getcalculatedfluidmotion()

logical function, public hydrodynamicsmodule::getcalculatedfluidmotion ( type(triadtype), intent(in)  triad,
real(dp), intent(out), optional  elev,
real(dp), dimension(3), intent(out), optional  fvel,
real(dp), dimension(3), intent(out), optional  facc 
)

Returns the latest calculated fluid particle motion at a triad.

Parameters
[in]triadThe triad object to get particle motion data for
[out]elevSea surface elevation at the triad location
[out]fvelWater particle velocity at the triad location
[out]faccWater particle acceleration at the triad location
Author
Knut Morten Okstad
Date
29 Nov 2010
Here is the caller graph for this function:

◆ getdiffractionforces()

subroutine, public hydrodynamicsmodule::getdiffractionforces ( real(dp), dimension(:), intent(inout)  Q,
type(supeltype), intent(in)  sup,
type(hydrodyntype), intent(inout)  hydyn,
type(environmenttype), intent(in)  env,
real(dp), intent(in)  time,
integer, intent(inout)  ierr 
)

Extracts the diffraction force at a given time for a superelement.

Parameters
QExternal forces at centre of gravity including diffraction effects
[in]supSuperelement to extract diffraction forces
hydynData for hydrodynamic force calculation
[in]envEnvironmental data
[in]timeCurrent simulation time
ierrError flag
Author
Knut Morten Okstad
Date
16 Mar 2015
Here is the call graph for this function:
Here is the caller graph for this function:

◆ getdragforces()

subroutine, public hydrodynamicsmodule::getdragforces ( real(dp), dimension(:), intent(inout)  Fd,
type(supeltype), intent(in)  sup,
type(hydrodyntype), intent(inout)  hydyn,
type(environmenttype), intent(in)  env,
real(dp), intent(in)  time,
real(dp), intent(in)  dt,
integer, intent(inout)  ierr 
)

Calculates drag (and slam) forces for a (partly) submerged body.

Parameters
FdDamping forces at the centre of gravity due to drag and slam
[in]supSuperelement to calculate damping forces for
hydynData for hydrodynamic force calculation
[in]envEnvironmental data
[in]timeCurrent simulation time
[in]dtTime increment size
ierrError flag
Author
Knut Morten Okstad
Date
8 Jul 2008
Here is the call graph for this function:
Here is the caller graph for this function:

◆ getmorisonforces()

subroutine, public hydrodynamicsmodule::getmorisonforces ( character(len=*), intent(in)  beamId,
type(triadptrtype), dimension(:), intent(in)  triads,
real(dp), dimension(:,:), intent(in)  supTr,
real(dp), dimension(:), intent(in)  urd,
real(dp), dimension(:), intent(in)  urdd,
real(dp), dimension(:), intent(inout)  Q,
real(dp), dimension(:,:), intent(out)  eMa,
real(dp), dimension(:,:), intent(out)  eCd,
type(hydrodyntype), intent(inout)  hydyn,
type(environmenttype), intent(inout)  env,
real(dp), intent(in)  time,
integer, intent(in)  istep,
integer, intent(in)  iter,
integer, intent(out)  ierr 
)

Calculates Morison force contributions for a two-noded beam element.

Parameters
[in]beamIdID string of the beam element used in feedback messages
[in]triadsTriads connected to the beam elements
[in]supTrPosition matrix for the beam element
[in]urdNodal velocities in local coordinates
[in]urddNodal accelerations in local coordinates
QExternal nodal forces with added mass, drag and buoyancy terms
[out]eMaElement added mass matrix
[out]eCdElement damping matrix due to drag
hydynData for hydrodynamic force calculation
envEnvironmental data
[in]timeCurrent simulation time
[in]istepTime increment counter
[in]iterIteration counter
[out]ierrError flag

The inertia- and damping forces due to added mass and drag are calculated for a two-noded element assuming a circular cross section. The corresponding left-hand side matrix contributions are also calculated. Buoyancy forces are also calculated, but no load-correction stiffness.

Author
Knut Morten Okstad
Date
27 Mar 2009
Here is the call graph for this function:
Here is the caller graph for this function:

◆ getseastate()

subroutine, public hydrodynamicsmodule::getseastate ( type(environmenttype), intent(in)  env,
real(dp), intent(in)  time,
real(dp), dimension(3), intent(in)  Xg,
real(dp), dimension(:), intent(out)  sea,
integer, intent(out)  stat 
)

Evaluates the sea state at the given point and time.

Parameters
[in]envEnvironmental data
[in]timeCurrent simulation time
[in]XgGlobal coordinates of sea kinematics evaluation point
[out]seaSea kinematics state at current point. sea(1:3) = Particle velocity at point Xg in global coordinates. sea(4:6) = Particle acceleration at point Xg in global coordinates. sea(7) = Dynamic pressure at point Xg in global coordinates.
[out]statStatus flag (negative on error exit)
Author
Knut Morten Okstad
Date
29 Jun 2015
Here is the call graph for this function:
Here is the caller graph for this function:

◆ getwaveelevation()

real(dp) function, public hydrodynamicsmodule::getwaveelevation ( type(environmenttype), intent(in)  env,
real(dp), dimension(3), intent(in)  Xg,
real(dp), intent(in)  time,
integer, intent(out)  stat 
)

Returns the wave height at the given point and time.

Parameters
[in]envEnvironmental data
[in]XgGlobal coordinates of sea kinematics evaluation point
[in]timeCurrent simulation time
[out]statStatus flag (negative on error exit)
Author
Knut Morten Okstad
Date
8 Feb 2013
Here is the call graph for this function:
Here is the caller graph for this function:

◆ initfluidmotions()

subroutine, public hydrodynamicsmodule::initfluidmotions ( real(dp), intent(in)  time,
type(environmenttype), intent(in)  env,
type(triadtype), dimension(:), intent(in)  triads,
type(supeltype), dimension(:), intent(in)  sups,
integer, intent(out)  ierr 
)

Initializes the fluid particle motion cache for all triads in water.

Parameters
[in]timeCurrent simulation time
[in]envEnvironmental data
[in]triadsAll triads in the model
[in]supsAll superelements in the model
[out]ierrError flag
Author
Knut Morten Okstad
Date
30 Jun 2010
Here is the call graph for this function:
Here is the caller graph for this function:

◆ initiatehydrodynbodies()

subroutine, public hydrodynamicsmodule::initiatehydrodynbodies ( type(supeltype), dimension(:), intent(inout)  sups,
type(userdefeltype), dimension(:), intent(inout)  elms,
type(environmenttype), intent(in)  env,
logical, intent(in)  restart,
integer, intent(out)  ierr 
)

Initiates all hydrodynamic bodies in the model.

Parameters
supsAll superelements in the model
elmsAll user-defined elements in the model
[in]envEnvironmental data
[in]restartIf .true., this is a restart simulation
[out]ierrError flag
Author
Knut Morten Okstad
Date
12 Aug 2008
Here is the call graph for this function:
Here is the caller graph for this function:

◆ updatehydrodynamicsatconvergence()

subroutine hydrodynamicsmodule::updatehydrodynamicsatconvergence ( type(hydrodyntype), intent(inout)  hydyn,
real(dp), dimension(3,4), intent(in)  supTr,
integer, intent(out)  ierr 
)
private

Updates the HydroDynType object after convergence has been achieved.

Parameters
hydynData for hydrodynamic force calculation
[in]supTrPosition matrix for the superelement to update for
[out]ierrError flag
Author
Knut Morten Okstad
Date
11 Aug 2008

◆ updatehydrodynbody()

subroutine hydrodynamicsmodule::updatehydrodynbody ( type(hydrodyntype), intent(inout)  hydyn,
type(triadptrtype), dimension(:), intent(in)  triads,
real(dp), dimension(:,:), intent(in)  supTr,
real(dp), intent(in)  sLev,
real(dp), dimension(3), intent(in)  gravity,
real(dp), intent(out), optional  g,
real(dp), dimension(2), intent(out), optional  wb,
integer, intent(out)  ierr 
)

Updates the hydrodynamic body quantities.

Parameters
hydynData for hydrodynamic force calculation
[in]triadsTriads on the superelement to update hydrodynamics for
[in]supTrSuperelement position matrix
[in]sLevCurrent sea level
[in]gravityGlobal gravitation vector
[out]gGravitation constant
[out]wbBuoyancy weight factors for two-noded beams
[out]ierrError flag
Author
Knut Morten Okstad
Date
12 Aug 2008
Here is the call graph for this function:
Here is the caller graph for this function:

◆ watersurfacenormal()

real(dp) function hydrodynamicsmodule::watersurfacenormal ( real(dp), dimension(3), intent(out)  normal,
real(dp), dimension(3), intent(in)  gravity,
real(dp), dimension(:,:), intent(in), optional  Tlg 
)

Returns the water surface normal vector in local coordinate system.

Parameters
[out]normalUnit normal vector for the water surface
[in]gravityGlobal gravitation vector
[in]TlgLocal to global transformation matrix (optional)
Returns
The gravitation constant
Author
Knut Morten Okstad
Date
27 Mar 2009
Here is the caller graph for this function:

Variable Documentation

◆ calcwmotion

integer, dimension(:), allocatable, save hydrodynamicsmodule::calcwmotion
private

Have calculated motions?

◆ eps_p

real(dp), parameter hydrodynamicsmodule::eps_p = 1.0e-16_dp
private

Zero tolerance.

◆ watermotion

real(dp), dimension(:,:), allocatable, save hydrodynamicsmodule::watermotion
private

Fluid particle motions.