OpenFAST
Wind turbine multiphysics simulator
Data Types | Functions/Subroutines | Variables
nwtc_num Module Reference

This module contains numeric-type routines with non-system-specific logic and references. More...

Data Types

interface  addorsub2pi
 This routine is used to convert NewAngle to an angle within Pi of OldAngle by adding or subtracting 2*Pi accordingly. More...
 
interface  angles_extrapinterp
 
interface  cross_product
 This function computes the cross product of two 3-element arrays (resulting in a vector):
cross_product = Vector1 \(\times\) Vector2
Use cross_product (nwtc_num::cross_product) instead of directly calling a specific routine in the generic interface. More...
 
interface  dcm_exp
 This function returns the matrix exponential, \(\Lambda = \exp(\lambda)\), of an input skew-symmetric matrix, \(\lambda\). More...
 
interface  dcm_logmap
 For any direction cosine matrix (DCM), \(\Lambda\), this routine calculates the logarithmic map, \(\lambda\), which a skew-symmetric matrix: More...
 
interface  dcm_setlogmapforinterp
 This routine sets the rotation parameters (logMap tensors from dcm_logmap) so that they can be appropriately interpolated, based on continunity of the neighborhood. More...
 
interface  equalrealnos
 This function compares two real numbers and determines if they are "almost" equal, i.e. More...
 
interface  eulerconstruct
 This function creates a rotation matrix, M, from a 1-2-3 rotation sequence of the 3 Euler angles, \(\theta_x\), \(\theta_y\), and \(\theta_z\), in radians. More...
 
interface  eulerextract
 if M is a rotation matrix from a 1-2-3 rotation sequence, this function returns the 3 Euler angles, \(\theta_x\), \(\theta_y\), and \(\theta_z\) (in radians), that formed the matrix. More...
 
interface  eye
 This routine sets the matrices in the first two dimensions of A equal to the identity matrix (all zeros, with ones on the diagonal). More...
 
interface  getsmllrotangs
 This subroutine computes the angles that make up the input direction cosine matrix, DCMat, assuming small angles. More...
 
interface  interparray
 This subroutine calculates interpolated values for an array of input values. More...
 
interface  interpbin
 This funtion returns a y-value that corresponds to an input x-value by interpolating into the arrays. More...
 
interface  interpstp
 This funtion returns a y-value that corresponds to an input x-value by interpolating into the arrays. More...
 
interface  interpwrappedstpreal
 This funtion returns a y-value that corresponds to an input x-value which is wrapped back into the range [0-XAry(AryLen)] by interpolating into the arrays. More...
 
interface  locatestp
 This subroutine finds the lower-bound index of an input x-value located in an array. More...
 
interface  mpi2pi
 This routine is used to convert Angle to an equivalent value between \(-\pi\) and \(pi\). More...
 
interface  outerproduct
 This routine calculates the outer product of two vectors, \(u = \left(u_1, u_2, \ldots, u_m\right)\) and \(v = \left(v_1, v_2, \ldots ,v_n\right)\). More...
 
interface  skewsymmat
 This function returns the 3x3 skew-symmetric matrix for cross-product calculation of vector \(\vec{x}\) via matrix multiplication, defined as

\begin{equation} f_{_\times}\left( \vec{x} \right) = \begin{bmatrix} 0 & -x_3 & x_2 \\ x_3 & 0 & -x_1 \\ -x_2 & x_1 & 0 \end{bmatrix} \end{equation}

Use SkewSymMat (nwtc_num::skewsymmat) instead of directly calling a specific routine in the generic interface. More...

 
interface  smllrottrans
 This routine computes the 3x3 transformation matrix, \(TransMat\), to a coordinate system \(x\) (with orthogonal axes \(x_1, x_2, x_3\)) resulting from three rotations ( \(\theta_1\), \(\theta_2\), \(\theta_3\)) about the orthogonal axes ( \(X_1, X_2, X_3\)) of coordinate system \(X\). More...
 
interface  taitbryanyxzconstruct
 
interface  taitbryanyxzextract
 If M is a rotation matrix from a 1-2-3 rotation sequence about Y-X-Z, this function returns the 3 sequential angles, \(\theta_y\), \(\theta_x\), and \(\theta_z\) (in radians), that formed the matrix. More...
 
interface  trace
 This function computes the trace of a matrix \(A \in \mathbb{R}^{m,n}\). More...
 
interface  twonorm
 This function returns the \(l_2\) (Euclidian) norm of a vector, \(v = \left(v_1, v_2, \ldots ,v_n\right)\). More...
 
interface  zero2twopi
 This routine is used to convert Angle to an equivalent value in the range \([0, 2\pi)\). More...
 

Functions/Subroutines

subroutine addorsub2pi_r4 (OldAngle, NewAngle)
 This routine is used to convert NewAngle to an angle within Pi of OldAngle by adding or subtracting 2*Pi accordingly. More...
 
subroutine addorsub2pi_r8 (OldAngle, NewAngle)
 This routine is used to convert NewAngle to an angle within Pi of OldAngle by adding or subtracting 2*Pi accordingly. More...
 
subroutine addorsub2pi_r16 (OldAngle, NewAngle)
 This routine is used to convert NewAngle to an angle within Pi of OldAngle by adding or subtracting 2*Pi accordingly. More...
 
real(reki) function blendcosine (x, LowerBound, UpperBound)
 
subroutine bsortreal (RealAry, NumPts)
 This routine sorts a list of real numbers. More...
 
subroutine convertunitstosi (Units, ScaleFactor)
 This subroutine takes an "oldUnits" array, compares the strings to a list of units that will be converted to SI, and returns two arrays that give the new units and the multiplicative scaling factor to convert the old units to the new ones. More...
 
subroutine convertunitstoengr (Units, ScaleFactor)
 This subroutine takes an "oldUnits" array, compares the strings to a list of units that will be converted to engineering units (kN and deg), and returns two arrays that give the new units and the multiplicative scaling factor to convert the old units to the new ones. More...
 
real(siki) function, dimension(3) cross_productr4 (Vector1, Vector2)
 This function computes the cross product of two 3-element arrays (resulting in a vector):
cross_product = Vector1 \(\times\) Vector2
Use cross_product (nwtc_num::cross_product) instead of directly calling a specific routine in the generic interface. More...
 
real(r8ki) function, dimension(3) cross_productr4r8 (Vector1, Vector2)
 This function computes the cross product of two 3-element arrays (resulting in a vector):
cross_product = Vector1 \(\times\) Vector2
Use cross_product (nwtc_num::cross_product) instead of directly calling a specific routine in the generic interface. More...
 
real(r8ki) function, dimension(3) cross_productr8 (Vector1, Vector2)
 This function computes the cross product of two 3-element arrays (resulting in a vector):
cross_product = Vector1 \(\times\) Vector2
Use cross_product (nwtc_num::cross_product) instead of directly calling a specific routine in the generic interface. More...
 
real(r8ki) function, dimension(3) cross_productr8r4 (Vector1, Vector2)
 This function computes the cross product of two 3-element arrays (resulting in a vector):
cross_product = Vector1 \(\times\) Vector2
Use cross_product (nwtc_num::cross_product) instead of directly calling a specific routine in the generic interface. More...
 
real(quki) function, dimension(3) cross_productr16 (Vector1, Vector2)
 This function computes the cross product of two 3-element arrays (resulting in a vector):
cross_product = Vector1 \(\times\) Vector2
Use cross_product (nwtc_num::cross_product) instead of directly calling a specific routine in the generic interface. More...
 
subroutine cubicsplineinit (AryLen, XAry, YAry, Coef, ErrStat, ErrMsg)
 This routine calculates the parameters needed to compute a irregularly-spaced natural cubic spline. More...
 
subroutine cubicsplineinitm (XAry, YAry, Coef, ErrStat, ErrMsg)
 This routine calculates the parameters needed to compute a irregularly-spaced natural cubic spline. More...
 
subroutine cubiclinsplineinitm (XAry, YAry, Coef, ErrStat, ErrMsg)
 This routine calculates the parameters needed to compute a irregularly-spaced natural linear spline. More...
 
real(reki) function cubicsplineinterp (X, AryLen, XAry, YAry, Coef, ErrStat, ErrMsg)
 This routine interpolates a pair of arrays using cubic splines to find the function value at X. More...
 
real(reki) function, dimension(:), allocatable cubicsplineinterpm (X, XAry, YAry, Coef, ErrStat, ErrMsg)
 This routine interpolates a pair of arrays using cubic splines to find the function value at X. More...
 
real(dbki) function, dimension(3, 3) dcm_expd (lambda)
 This function returns the matrix exponential, \(\Lambda = \exp(\lambda)\), of an input skew-symmetric matrix, \(\lambda\). More...
 
real(reki) function, dimension(3, 3) dcm_expr (lambda)
 This function returns the matrix exponential, \(\Lambda = \exp(\lambda)\), of an input skew-symmetric matrix, \(\lambda\). More...
 
subroutine dcm_logmapd (DCM, logMap, ErrStat, ErrMsg, thetaOut)
 For any direction cosine matrix (DCM), \(\Lambda\), this routine calculates the logarithmic map, \(\lambda\), which a skew-symmetric matrix: More...
 
subroutine dcm_logmapr (DCM, logMap, ErrStat, ErrMsg, thetaOut)
 For any direction cosine matrix (DCM), \(\Lambda\), this routine calculates the logarithmic map, \(\lambda\), which a skew-symmetric matrix: More...
 
subroutine dcm_setlogmapforinterpd (tensor)
 This routine sets the rotation parameters (logMap tensors from dcm_logmap) so that they can be appropriately interpolated, based on continunity of the neighborhood. More...
 
subroutine dcm_setlogmapforinterpr (tensor)
 This routine sets the rotation parameters (logMap tensors from dcm_logmap) so that they can be appropriately interpolated, based on continunity of the neighborhood. More...
 
logical function equalrealnos4 (ReNum1, ReNum2)
 This function compares two real numbers and determines if they are "almost" equal, i.e. More...
 
logical function equalrealnos8 (ReNum1, ReNum2)
 This function compares two real numbers and determines if they are "almost" equal, i.e. More...
 
logical function equalrealnos16 (ReNum1, ReNum2)
 This function compares two real numbers and determines if they are "almost" equal, i.e. More...
 
real(siki) function, dimension(3, 3) eulerconstructr4 (theta)
 This function creates a rotation matrix, M, from a 1-2-3 rotation sequence of the 3 Euler angles, \(\theta_x\), \(\theta_y\), and \(\theta_z\), in radians. More...
 
real(r8ki) function, dimension(3, 3) eulerconstructr8 (theta)
 This function creates a rotation matrix, M, from a 1-2-3 rotation sequence of the 3 Euler angles, \(\theta_x\), \(\theta_y\), and \(\theta_z\), in radians. More...
 
real(quki) function, dimension(3, 3) eulerconstructr16 (theta)
 This function creates a rotation matrix, M, from a 1-2-3 rotation sequence of the 3 Euler angles, \(\theta_x\), \(\theta_y\), and \(\theta_z\), in radians. More...
 
real(siki) function, dimension(3) eulerextractr4 (M)
 if M is a rotation matrix from a 1-2-3 rotation sequence, this function returns the 3 Euler angles, \(\theta_x\), \(\theta_y\), and \(\theta_z\) (in radians), that formed the matrix. More...
 
real(r8ki) function, dimension(3) eulerextractr8 (M)
 if M is a rotation matrix from a 1-2-3 rotation sequence, this function returns the 3 Euler angles, \(\theta_x\), \(\theta_y\), and \(\theta_z\) (in radians), that formed the matrix. More...
 
real(quki) function, dimension(3) eulerextractr16 (M)
 if M is a rotation matrix from a 1-2-3 rotation sequence, this function returns the 3 Euler angles, \(\theta_x\), \(\theta_y\), and \(\theta_z\) (in radians), that formed the matrix. More...
 
subroutine eye2 (A, ErrStat, ErrMsg)
 This routine sets the matrices in the first two dimensions of A equal to the identity matrix (all zeros, with ones on the diagonal). More...
 
subroutine eye2d (A, ErrStat, ErrMsg)
 This routine sets the matrices in the first two dimensions of A equal to the identity matrix (all zeros, with ones on the diagonal). More...
 
subroutine eye3 (A, ErrStat, ErrMsg)
 This routine sets the matrices in the first two dimensions of A equal to the identity matrix (all zeros, with ones on the diagonal).
 
subroutine eye3d (A, ErrStat, ErrMsg)
 This routine sets the matrices in the first two dimensions of A equal to the identity matrix (all zeros, with ones on the diagonal). More...
 
subroutine gausselim (AugMatIn, NumEq, x, ErrStat, ErrMsg)
 This routine uses the Gauss-Jordan elimination method for the solution of a given set of simultaneous linear equations. More...
 
subroutine getoffsetreg (Ary, NumPts, Val, Ind, Fract, ErrStat, ErrMsg)
 Determine index of the point in Ary just below Val and the fractional distance to the next point in the array. More...
 
real(dbki) function, dimension(3) getsmllrotangsd (DCMat, ErrStat, ErrMsg)
 This subroutine computes the angles that make up the input direction cosine matrix, DCMat, assuming small angles. More...
 
real(reki) function, dimension(3) getsmllrotangsr (DCMat, ErrStat, ErrMsg)
 This subroutine computes the angles that make up the input direction cosine matrix, DCMat, assuming small angles. More...
 
subroutine gl_pts (IPt, NPts, Loc, Wt, ErrStat, ErrMsg)
 This funtion returns the non-dimensional (-1:+1) location of the given Gauss-Legendre Quadrature point and its weight. More...
 
integer function indexcharary (CVal, CAry)
 This funtion returns an integer index such that CAry(IndexCharAry) = CVal. More...
 
complex(reki) function interpbincomp (XVal, XAry, YAry, ILo, AryLen)
 This funtion returns a y-value that corresponds to an input x-value by interpolating into the arrays. More...
 
real(reki) function interpbinreal (XVal, XAry, YAry, ILo, AryLen)
 This funtion returns a y-value that corresponds to an input x-value by interpolating into the arrays. More...
 
complex(siki) function interpstpcomp4 (XVal, XAry, YAry, Ind, AryLen)
 This funtion returns a y-value that corresponds to an input x-value by interpolating into the arrays. More...
 
complex(r8ki) function interpstpcomp8 (XVal, XAry, YAry, Ind, AryLen)
 This funtion returns a y-value that corresponds to an input x-value by interpolating into the arrays. More...
 
complex(quki) function interpstpcomp16 (XVal, XAry, YAry, Ind, AryLen)
 This funtion returns a y-value that corresponds to an input x-value by interpolating into the arrays. More...
 
real(siki) function interpstpreal4 (XVal, XAry, YAry, Ind, AryLen)
 This funtion returns a y-value that corresponds to an input x-value by interpolating into the arrays. More...
 
real(r8ki) function interpstpreal4_8 (XVal, XAry, YAry, Ind, AryLen)
 This funtion returns a y-value that corresponds to an input x-value by interpolating into the arrays. More...
 
real(r8ki) function interpstpreal8 (XVal, XAry, YAry, Ind, AryLen)
 This funtion returns a y-value that corresponds to an input x-value by interpolating into the arrays. More...
 
real(quki) function interpstpreal16 (XVal, XAry, YAry, Ind, AryLen)
 This funtion returns a y-value that corresponds to an input x-value by interpolating into the arrays. More...
 
subroutine interpstpmat (XVal, XAry, Y, Ind, AryLen, yInterp)
 This funtion returns a y-value array that corresponds to an input x-value by interpolating into the arrays. More...
 
subroutine interpstpreal2d (InCoord, Dataset, x, y, LastIndex, InterpData)
 
subroutine interpstpreal3d (InCoord, Dataset, x, y, z, LastIndex, InterpData)
 
real(siki) function interpwrappedstpreal4 (XValIn, XAry, YAry, Ind, AryLen)
 This funtion returns a y-value that corresponds to an input x-value which is wrapped back into the range [0-XAry(AryLen)] by interpolating into the arrays. More...
 
real(r8ki) function interpwrappedstpreal4_8 (XValIn, XAry, YAry, Ind, AryLen)
 This funtion returns a y-value that corresponds to an input x-value which is wrapped back into the range [0-XAry(AryLen)] by interpolating into the arrays. More...
 
real(r8ki) function interpwrappedstpreal8 (XValIn, XAry, YAry, Ind, AryLen)
 This funtion returns a y-value that corresponds to an input x-value which is wrapped back into the range [0-XAry(AryLen)] by interpolating into the arrays. More...
 
real(quki) function interpwrappedstpreal16 (XValIn, XAry, YAry, Ind, AryLen)
 This funtion returns a y-value that corresponds to an input x-value which is wrapped back into the range [0-XAry(AryLen)] by interpolating into the arrays. More...
 
subroutine interparrayr4 (xknown, yknown, xnew, ynew)
 This subroutine calculates interpolated values for an array of input values. More...
 
subroutine interparrayr8 (xknown, yknown, xnew, ynew)
 This subroutine calculates interpolated values for an array of input values. More...
 
subroutine interparrayr16 (xknown, yknown, xnew, ynew)
 This subroutine calculates interpolated values for an array of input values. More...
 
subroutine isoparametriccoords (InCoord, posLo, posHi, isopc)
 This subroutine calculates the iosparametric coordinates, isopc, which is a value between -1 and 1 (for each dimension of a dataset), indicating where InCoord falls between posLo and posHi. More...
 
logical function issymmetric (A)
 This function returns a logical TRUE/FALSE value that indicates if the given (2-dimensional) matrix, A, is symmetric. More...
 
subroutine kernelsmoothing (x, f, kernelType, radius, fNew)
 KERNELSMOOTHING Kernel smoothing of vector data. More...
 
subroutine locatebin (XVal, XAry, Ind, AryLen)
 This subroutine finds the lower-bound index of an input x-value located in an array. More...
 
subroutine locatestpr4 (XVal, XAry, Ind, AryLen)
 This subroutine finds the lower-bound index of an input x-value located in an array. More...
 
subroutine locatestpr8 (XVal, XAry, Ind, AryLen)
 This subroutine finds the lower-bound index of an input x-value located in an array. More...
 
subroutine locatestpr16 (XVal, XAry, Ind, AryLen)
 This subroutine finds the lower-bound index of an input x-value located in an array. More...
 
real(reki) function mean (Ary, AryLen)
 This routine calculates the mean value of an array. More...
 
subroutine mpi2pi_r4 (Angle)
 This routine is used to convert Angle to an equivalent value between \(-\pi\) and \(pi\). More...
 
subroutine mpi2pi_r8 (Angle)
 This routine is used to convert Angle to an equivalent value between \(-\pi\) and \(pi\). More...
 
subroutine mpi2pi_r16 (Angle)
 This routine is used to convert Angle to an equivalent value between \(-\pi\) and \(pi\). More...
 
real(reki) function rad2m180to180deg (Angle)
 This function takes an angle in radians and converts it to an angle in degrees in the range [-180,180]. More...
 
real(siki) function, dimension(size(u), size(v)) outerproductr4 (u, v)
 This routine calculates the outer product of two vectors, \(u = \left(u_1, u_2, \ldots, u_m\right)\) and \(v = \left(v_1, v_2, \ldots ,v_n\right)\). More...
 
real(r8ki) function, dimension(size(u), size(v)) outerproductr8 (u, v)
 This routine calculates the outer product of two vectors, \(u = \left(u_1, u_2, \ldots, u_m\right)\) and \(v = \left(v_1, v_2, \ldots ,v_n\right)\). More...
 
real(quki) function, dimension(size(u), size(v)) outerproductr16 (u, v)
 This routine calculates the outer product of two vectors, \(u = \left(u_1, u_2, \ldots, u_m\right)\) and \(v = \left(v_1, v_2, \ldots ,v_n\right)\). More...
 
subroutine perturborientationmatrix (Orientation, Perturbation, AngleDim, Perturbations, UseSmlAngle)
 This subroutine perturbs an orientation matrix by a small angle. More...
 
integer function psf (Npsf, NumPrimes, subtract)
 This routine factors the number N into its primes. More...
 
type(quaternion) function quaternion_conjugate (q)
 This function computes the conjugate of a quaternion, q. More...
 
real(reki) function quaternion_norm (q)
 This function computes the 2-norm of a quaternion, q. More...
 
type(quaternion) function quaternion_power (q, alpha)
 This function computes the quaternion, q, raised to an arbitrary real exponent, alpha. More...
 
type(quaternion) function quaternion_product (p, q)
 This function computes the product of two quaternions, p and q. More...
 
real(reki) function, dimension(3, 3) quaternion_to_dcm (q)
 This function converts a quaternion to an equivalent direction cosine matrix. More...
 
type(quaternion) function dcm_to_quaternion (DCM)
 This function converts a direction cosine matrix to an equivalent quaternion. More...
 
type(quaternion) function quaternion_interp (q1, q2, s)
 This function computes the interpolated quaternion at time t1 + s*(t2-t1) and s is in [0,1]. More...
 
subroutine regcubicsplineinit (AryLen, XAry, YAry, DelX, Coef, ErrStat, ErrMsg)
 This routine calculates the parameters needed to compute a regularly-spaced natural cubic spline. More...
 
subroutine regcubicsplineinitm (XAry, YAry, DelX, Coef, ErrStat, ErrMsg)
 This routine calculates the parameters needed to compute a regularly-spaced natural cubic spline. More...
 
real(reki) function regcubicsplineinterp (X, AryLen, XAry, YAry, DelX, Coef, ErrStat, ErrMsg)
 This routine interpolates a pair of arrays using cubic splines to find the function value at X. More...
 
real(reki) function, dimension(:), allocatable regcubicsplineinterpm (X, XAry, YAry, DelX, Coef, ErrStat, ErrMsg)
 This routine interpolates a pair of arrays using cubic splines to find the function value at X. More...
 
subroutine rombergint (f, a, b, R, err, eps, ErrStat)
 This routine is used to integrate funciton f over the interval [a, b]. More...
 
subroutine runtimes (StrtTime, UsrTime1, SimStrtTime, UsrTime2, ZTime, UnSum, UsrTime_out, DescStrIn)
 This routine displays a message that gives that status of the simulation and the predicted end time of day. More...
 
subroutine setanglesforinterp (angles)
 this routine takes angles (in radians) and converts them to appropriate ranges so they can be interpolated appropriately (i.e., interpolating between pi+.1 and -pi should give pi+0.5 instead of of 0.05 radians, so we return the angles pi+.1 and -pi+2pi=pi we assume the interpolation occurs in the second dimension of angles and it is done for each angle in the first dimension
 
subroutine setconstants ()
 This routine computes numeric constants stored in the NWTC Library.
 
subroutine simstatus_firsttime (PrevSimTime, PrevClockTime, SimStrtTime, UsrTimeSim, ZTime, TMax, DescStrIn)
 This routine displays a message that gives that status of the simulation. More...
 
subroutine simstatus (PrevSimTime, PrevClockTime, ZTime, TMax, DescStrIn, StatInfoIn)
 This routine displays a message that gives that status of the simulation and the predicted end time of day. More...
 
subroutine smllrottransd (RotationType, Theta1, Theta2, Theta3, TransMat, ErrTxt, ErrStat, ErrMsg)
 This routine computes the 3x3 transformation matrix, \(TransMat\), to a coordinate system \(x\) (with orthogonal axes \(x_1, x_2, x_3\)) resulting from three rotations ( \(\theta_1\), \(\theta_2\), \(\theta_3\)) about the orthogonal axes ( \(X_1, X_2, X_3\)) of coordinate system \(X\). More...
 
subroutine smllrottransdd (RotationType, Theta1, Theta2, Theta3, TransMat, ErrTxt, ErrStat, ErrMsg)
 This routine computes the 3x3 transformation matrix, \(TransMat\), to a coordinate system \(x\) (with orthogonal axes \(x_1, x_2, x_3\)) resulting from three rotations ( \(\theta_1\), \(\theta_2\), \(\theta_3\)) about the orthogonal axes ( \(X_1, X_2, X_3\)) of coordinate system \(X\). More...
 
subroutine smllrottransr (RotationType, Theta1, Theta2, Theta3, TransMat, ErrTxt, ErrStat, ErrMsg)
 This routine computes the 3x3 transformation matrix, \(TransMat\), to a coordinate system \(x\) (with orthogonal axes \(x_1, x_2, x_3\)) resulting from three rotations ( \(\theta_1\), \(\theta_2\), \(\theta_3\)) about the orthogonal axes ( \(X_1, X_2, X_3\)) of coordinate system \(X\). More...
 
subroutine sortunion (Ary1, N1, Ary2, N2, Ary, N)
 This routine takes two sorted arrays and finds the sorted union of the two. More...
 
real(reki) function stddevfn (Ary, AryLen, Mean, UseN)
 This routine calculates the standard deviation of a population contained in Ary. More...
 
real(siki) function, dimension(3, 3) skewsymmatr4 (x)
 This function returns the 3x3 skew-symmetric matrix for cross-product calculation of vector \(\vec{x}\) via matrix multiplication, defined as

\begin{equation} f_{_\times}\left( \vec{x} \right) = \begin{bmatrix} 0 & -x_3 & x_2 \\ x_3 & 0 & -x_1 \\ -x_2 & x_1 & 0 \end{bmatrix} \end{equation}

Use SkewSymMat (nwtc_num::skewsymmat) instead of directly calling a specific routine in the generic interface. More...

 
real(r8ki) function, dimension(3, 3) skewsymmatr8 (x)
 This function returns the 3x3 skew-symmetric matrix for cross-product calculation of vector \(\vec{x}\) via matrix multiplication, defined as

\begin{equation} f_{_\times}\left( \vec{x} \right) = \begin{bmatrix} 0 & -x_3 & x_2 \\ x_3 & 0 & -x_1 \\ -x_2 & x_1 & 0 \end{bmatrix} \end{equation}

Use SkewSymMat (nwtc_num::skewsymmat) instead of directly calling a specific routine in the generic interface. More...

 
real(quki) function, dimension(3, 3) skewsymmatr16 (x)
 This function returns the 3x3 skew-symmetric matrix for cross-product calculation of vector \(\vec{x}\) via matrix multiplication, defined as

\begin{equation} f_{_\times}\left( \vec{x} \right) = \begin{bmatrix} 0 & -x_3 & x_2 \\ x_3 & 0 & -x_1 \\ -x_2 & x_1 & 0 \end{bmatrix} \end{equation}

Use SkewSymMat (nwtc_num::skewsymmat) instead of directly calling a specific routine in the generic interface. More...

 
real(siki) function, dimension(3) taitbryanyxzextractr4 (M)
 If M is a rotation matrix from a 1-2-3 rotation sequence about Y-X-Z, this function returns the 3 sequential angles, \(\theta_y\), \(\theta_x\), and \(\theta_z\) (in radians), that formed the matrix. More...
 
real(r8ki) function, dimension(3) taitbryanyxzextractr8 (M)
 See nwtc_num::taitbryanyxzextractr4 for detailed explanation of algorithm. More...
 
real(quki) function, dimension(3) taitbryanyxzextractr16 (M)
 See nwtc_num::taitbryanyxzextractr4 for detailed explanation of algorithm. More...
 
real(siki) function, dimension(3, 3) taitbryanyxzconstructr4 (theta)
 
real(r8ki) function, dimension(3, 3) taitbryanyxzconstructr8 (theta)
 
real(quki) function, dimension(3, 3) taitbryanyxzconstructr16 (theta)
 
real(reki) function timevalues2seconds (TimeAry)
 This routine takes an array of time values such as that returned from CALL DATE_AND_TIME ( Values=TimeAry ) and converts TimeAry to the number of seconds past midnight. More...
 
real(siki) function tracer4 (A)
 This function computes the trace of a matrix \(A \in \mathbb{R}^{m,n}\). More...
 
real(r8ki) function tracer8 (A)
 This function computes the trace of a matrix \(A \in \mathbb{R}^{m,n}\). More...
 
real(quki) function tracer16 (A)
 This function computes the trace of a matrix \(A \in \mathbb{R}^{m,n}\). More...
 
real(siki) function twonormr4 (v)
 This function returns the \(l_2\) (Euclidian) norm of a vector, \(v = \left(v_1, v_2, \ldots ,v_n\right)\). More...
 
real(r8ki) function twonormr8 (v)
 This function returns the \(l_2\) (Euclidian) norm of a vector, \(v = \left(v_1, v_2, \ldots ,v_n\right)\). More...
 
real(quki) function twonormr16 (v)
 This function returns the \(l_2\) (Euclidian) norm of a vector, \(v = \left(v_1, v_2, \ldots ,v_n\right)\). More...
 
subroutine zero2twopir4 (Angle)
 This routine is used to convert Angle to an equivalent value in the range \([0, 2\pi)\). More...
 
subroutine zero2twopir8 (Angle)
 This routine is used to convert Angle to an equivalent value in the range \([0, 2\pi)\). More...
 
subroutine zero2twopir16 (Angle)
 This routine is used to convert Angle to an equivalent value in the range \([0, 2\pi)\). More...
 
subroutine angles_extrapinterp1_r4 (Angle1, Angle2, tin, Angle_out, tin_out)
 
subroutine angles_extrapinterp1_r8 (Angle1, Angle2, tin, Angle_out, tin_out)
 
subroutine angles_extrapinterp1_r16 (Angle1, Angle2, tin, Angle_out, tin_out)
 
subroutine angles_extrapinterp1_r4r (Angle1, Angle2, tin, Angle_out, tin_out)
 
subroutine angles_extrapinterp1_r8r (Angle1, Angle2, tin, Angle_out, tin_out)
 
subroutine angles_extrapinterp1_r16r (Angle1, Angle2, tin, Angle_out, tin_out)
 
subroutine angles_extrapinterp2_r4 (Angle1, Angle2, Angle3, tin, Angle_out, tin_out)
 
subroutine angles_extrapinterp2_r8 (Angle1, Angle2, Angle3, tin, Angle_out, tin_out)
 
subroutine angles_extrapinterp2_r16 (Angle1, Angle2, Angle3, tin, Angle_out, tin_out)
 
subroutine angles_extrapinterp2_r4r (Angle1, Angle2, Angle3, tin, Angle_out, tin_out)
 
subroutine angles_extrapinterp2_r8r (Angle1, Angle2, Angle3, tin, Angle_out, tin_out)
 
subroutine angles_extrapinterp2_r16r (Angle1, Angle2, Angle3, tin, Angle_out, tin_out)
 

Variables

real(dbki) d2r_d
 Factor to convert degrees to radians in double precision.
 
real(dbki) inf_d
 IEEE value for NaN (not-a-number) in double precision.
 
real(dbki) inv2pi_d
 0.5/Pi (1/(2*Pi)) in double precision
 
real(dbki) nan_d
 IEEE value for Inf (infinity) in double precision.
 
real(dbki) pi_d
 Ratio of a circle's circumference to its diameter in double precision.
 
real(dbki) piby2_d
 Pi/2 in double precision.
 
real(dbki) r2d_d
 Factor to convert radians to degrees in double precision.
 
real(dbki) rpm2rps_d
 Factor to convert revolutions per minute to radians per second in double precision.
 
real(dbki) rps2rpm_d
 Factor to convert radians per second to revolutions per minute in double precision.
 
real(dbki) twobypi_d
 2/Pi in double precision
 
real(dbki) twopi_d
 2*Pi in double precision
 
real(reki) d2r
 Factor to convert degrees to radians.
 
real(reki) inf
 IEEE value for NaN (not-a-number)
 
real(reki) inv2pi
 0.5/Pi = 1 / (2*pi)
 
real(reki) nan
 IEEE value for Inf (infinity)
 
real(reki) pi
 Ratio of a circle's circumference to its diameter.
 
real(reki) piby2
 Pi/2.
 
real(reki) r2d
 Factor to convert radians to degrees.
 
real(reki) rpm2rps
 Factor to convert revolutions per minute to radians per second.
 
real(reki) rps2rpm
 Factor to convert radians per second to revolutions per minute.
 
real(reki) twobypi
 2/Pi
 
real(reki) twopi
 2*Pi
 
real(siki) d2r_s
 Factor to convert degrees to radians in single precision.
 
real(siki) inf_s
 IEEE value for NaN (not-a-number) in single precision.
 
real(siki) inv2pi_s
 0.5/Pi (1/(2*Pi)) in single precision
 
real(siki) nan_s
 IEEE value for Inf (infinity) in single precision.
 
real(siki) pi_s
 Ratio of a circle's circumference to its diameter in single precision.
 
real(siki) piby2_s
 Pi/2 in single precision.
 
real(siki) r2d_s
 Factor to convert radians to degrees in single precision.
 
real(siki) rpm2rps_s
 Factor to convert revolutions per minute to radians per second in single precision.
 
real(siki) rps2rpm_s
 Factor to convert radians per second to revolutions per minute in single precision.
 
real(siki) twobypi_s
 2/Pi in single precision
 
real(siki) twopi_s
 2*Pi in single precision
 
real(siki) pi_r4
 Ratio of a circle's circumference to its diameter in 4-byte precision.
 
real(r8ki) pi_r8
 Ratio of a circle's circumference to its diameter in 8-byte precision.
 
real(quki) pi_r16
 Ratio of a circle's circumference to its diameter in 16-byte precision.
 
real(siki) twopi_r4
 2*pi in 4-byte precision
 
real(r8ki) twopi_r8
 2*pi in 8-byte precision
 
real(quki) twopi_r16
 2*pi in 16-byte precision
 
integer, parameter kerneltype_epanechinikov = 1
 
integer, parameter kerneltype_quartic = 2
 
integer, parameter kerneltype_biweight = 3
 
integer, parameter kerneltype_triweight = 4
 
integer, parameter kerneltype_tricube = 5
 
integer, parameter kerneltype_gaussian = 6
 
integer, parameter output_in_native_units = 0
 
integer, parameter output_in_si_units = 1
 
integer, parameter output_in_engr_units = 2
 

Detailed Description

This module contains numeric-type routines with non-system-specific logic and references.

Function/Subroutine Documentation

◆ addorsub2pi_r16()

subroutine nwtc_num::addorsub2pi_r16 ( real(quki), intent(in)  OldAngle,
real(quki), intent(inout)  NewAngle 
)

This routine is used to convert NewAngle to an angle within Pi of OldAngle by adding or subtracting 2*Pi accordingly.

This routine is useful for converting angles returned from a call to the ATAN2() FUNCTION into angles that may exceed the -Pi to Pi limit of ATAN2(). For example, if the nacelle yaw angle was 179deg in the previous time step and the yaw angle increased by 2deg in the new time step, we want the new yaw angle returned from a call to the ATAN2() FUNCTION to be 181deg instead of -179deg. This routine assumes that the angle change between calls is not more than Pi in absolute value. Use AddOrSub2Pi (nwtc_num::addorsub2pi) instead of directly calling a specific routine in the generic interface.

Parameters
[in]oldangleAngle from which NewAngle will be converted to within Pi of, rad.
[in,out]newangleAngle to be converted to within 2*Pi of OldAngle, rad.

◆ addorsub2pi_r4()

subroutine nwtc_num::addorsub2pi_r4 ( real(siki), intent(in)  OldAngle,
real(siki), intent(inout)  NewAngle 
)

This routine is used to convert NewAngle to an angle within Pi of OldAngle by adding or subtracting 2*Pi accordingly.

This routine is useful for converting angles returned from a call to the ATAN2() FUNCTION into angles that may exceed the -Pi to Pi limit of ATAN2(). For example, if the nacelle yaw angle was 179deg in the previous time step and the yaw angle increased by 2deg in the new time step, we want the new yaw angle returned from a call to the ATAN2() FUNCTION to be 181deg instead of -179deg. This routine assumes that the angle change between calls is not more than Pi in absolute value. Use AddOrSub2Pi (nwtc_num::addorsub2pi) instead of directly calling a specific routine in the generic interface.

Parameters
[in]oldangleAngle from which NewAngle will be converted to within Pi of, rad.
[in,out]newangleAngle to be converted to within 2*Pi of OldAngle, rad.

◆ addorsub2pi_r8()

subroutine nwtc_num::addorsub2pi_r8 ( real(r8ki), intent(in)  OldAngle,
real(r8ki), intent(inout)  NewAngle 
)

This routine is used to convert NewAngle to an angle within Pi of OldAngle by adding or subtracting 2*Pi accordingly.

This routine is useful for converting angles returned from a call to the ATAN2() FUNCTION into angles that may exceed the -Pi to Pi limit of ATAN2(). For example, if the nacelle yaw angle was 179deg in the previous time step and the yaw angle increased by 2deg in the new time step, we want the new yaw angle returned from a call to the ATAN2() FUNCTION to be 181deg instead of -179deg. This routine assumes that the angle change between calls is not more than Pi in absolute value. Use AddOrSub2Pi (nwtc_num::addorsub2pi) instead of directly calling a specific routine in the generic interface.

Parameters
[in]oldangleAngle from which NewAngle will be converted to within Pi of, rad.
[in,out]newangleAngle to be converted to within 2*Pi of OldAngle, rad.

◆ angles_extrapinterp1_r16()

subroutine nwtc_num::angles_extrapinterp1_r16 ( real(quki), intent(in)  Angle1,
real(quki), intent(in)  Angle2,
real(dbki), dimension(:), intent(in)  tin,
real(quki), intent(inout)  Angle_out,
real(dbki), intent(in)  tin_out 
)
Parameters
[in]angle1Angle at t1 > t2
[in]angle2Angle at t2
[in]tinTimes associated with the inputs
[in,out]angle_outInput at tin_out
[in]tin_outtime to be extrap/interp'd to

◆ angles_extrapinterp1_r16r()

subroutine nwtc_num::angles_extrapinterp1_r16r ( real(quki), intent(in)  Angle1,
real(quki), intent(in)  Angle2,
real(reki), dimension(:), intent(in)  tin,
real(quki), intent(inout)  Angle_out,
real(reki), intent(in)  tin_out 
)
Parameters
[in]angle1Angle at t1 > t2
[in]angle2Angle at t2
[in]tinTimes associated with the inputs
[in,out]angle_outInput at tin_out
[in]tin_outtime to be extrap/interp'd to

◆ angles_extrapinterp1_r4()

subroutine nwtc_num::angles_extrapinterp1_r4 ( real(siki), intent(in)  Angle1,
real(siki), intent(in)  Angle2,
real(dbki), dimension(:), intent(in)  tin,
real(siki), intent(inout)  Angle_out,
real(dbki), intent(in)  tin_out 
)
Parameters
[in]angle1Angle at t1 > t2
[in]angle2Angle at t2
[in]tinTimes associated with the inputs
[in,out]angle_outInput at tin_out
[in]tin_outtime to be extrap/interp'd to

◆ angles_extrapinterp1_r4r()

subroutine nwtc_num::angles_extrapinterp1_r4r ( real(siki), intent(in)  Angle1,
real(siki), intent(in)  Angle2,
real(reki), dimension(:), intent(in)  tin,
real(siki), intent(inout)  Angle_out,
real(reki), intent(in)  tin_out 
)
Parameters
[in]angle1Angle at t1 > t2
[in]angle2Angle at t2
[in]tinTimes associated with the inputs
[in,out]angle_outInput at tin_out
[in]tin_outtime to be extrap/interp'd to

◆ angles_extrapinterp1_r8()

subroutine nwtc_num::angles_extrapinterp1_r8 ( real(r8ki), intent(in)  Angle1,
real(r8ki), intent(in)  Angle2,
real(dbki), dimension(:), intent(in)  tin,
real(r8ki), intent(inout)  Angle_out,
real(dbki), intent(in)  tin_out 
)
Parameters
[in]angle1Angle at t1 > t2
[in]angle2Angle at t2
[in]tinTimes associated with the inputs
[in,out]angle_outInput at tin_out
[in]tin_outtime to be extrap/interp'd to

◆ angles_extrapinterp1_r8r()

subroutine nwtc_num::angles_extrapinterp1_r8r ( real(r8ki), intent(in)  Angle1,
real(r8ki), intent(in)  Angle2,
real(reki), dimension(:), intent(in)  tin,
real(r8ki), intent(inout)  Angle_out,
real(reki), intent(in)  tin_out 
)
Parameters
[in]angle1Angle at t1 > t2
[in]angle2Angle at t2
[in]tinTimes associated with the inputs
[in,out]angle_outInput at tin_out
[in]tin_outtime to be extrap/interp'd to

◆ angles_extrapinterp2_r16()

subroutine nwtc_num::angles_extrapinterp2_r16 ( real(quki), intent(in)  Angle1,
real(quki), intent(in)  Angle2,
real(quki), intent(in)  Angle3,
real(dbki), dimension(:), intent(in)  tin,
real(quki), intent(inout)  Angle_out,
real(dbki), intent(in)  tin_out 
)
Parameters
[in]angle1Angle at t1 > t2 > t3
[in]angle2Angle at t2 > t3
[in]angle3Angle at t3
[in]tinTimes associated with the inputs
[in,out]angle_outInput at tin_out
[in]tin_outtime to be extrap/interp'd to

◆ angles_extrapinterp2_r16r()

subroutine nwtc_num::angles_extrapinterp2_r16r ( real(quki), intent(in)  Angle1,
real(quki), intent(in)  Angle2,
real(quki), intent(in)  Angle3,
real(reki), dimension(:), intent(in)  tin,
real(quki), intent(inout)  Angle_out,
real(reki), intent(in)  tin_out 
)
Parameters
[in]angle1Angle at t1 > t2 > t3
[in]angle2Angle at t2 > t3
[in]angle3Angle at t3
[in]tinTimes associated with the inputs
[in,out]angle_outInput at tin_out
[in]tin_outtime to be extrap/interp'd to

◆ angles_extrapinterp2_r4()

subroutine nwtc_num::angles_extrapinterp2_r4 ( real(siki), intent(in)  Angle1,
real(siki), intent(in)  Angle2,
real(siki), intent(in)  Angle3,
real(dbki), dimension(:), intent(in)  tin,
real(siki), intent(inout)  Angle_out,
real(dbki), intent(in)  tin_out 
)
Parameters
[in]angle1Angle at t1 > t2 > t3
[in]angle2Angle at t2 > t3
[in]angle3Angle at t3
[in]tinTimes associated with the inputs
[in,out]angle_outInput at tin_out
[in]tin_outtime to be extrap/interp'd to

◆ angles_extrapinterp2_r4r()

subroutine nwtc_num::angles_extrapinterp2_r4r ( real(siki), intent(in)  Angle1,
real(siki), intent(in)  Angle2,
real(siki), intent(in)  Angle3,
real(reki), dimension(:), intent(in)  tin,
real(siki), intent(inout)  Angle_out,
real(reki), intent(in)  tin_out 
)
Parameters
[in]angle1Angle at t1 > t2 > t3
[in]angle2Angle at t2 > t3
[in]angle3Angle at t3
[in]tinTimes associated with the inputs
[in,out]angle_outInput at tin_out
[in]tin_outtime to be extrap/interp'd to

◆ angles_extrapinterp2_r8()

subroutine nwtc_num::angles_extrapinterp2_r8 ( real(r8ki), intent(in)  Angle1,
real(r8ki), intent(in)  Angle2,
real(r8ki), intent(in)  Angle3,
real(dbki), dimension(:), intent(in)  tin,
real(r8ki), intent(inout)  Angle_out,
real(dbki), intent(in)  tin_out 
)
Parameters
[in]angle1Angle at t1 > t2 > t3
[in]angle2Angle at t2 > t3
[in]angle3Angle at t3
[in]tinTimes associated with the inputs
[in,out]angle_outInput at tin_out
[in]tin_outtime to be extrap/interp'd to

◆ angles_extrapinterp2_r8r()

subroutine nwtc_num::angles_extrapinterp2_r8r ( real(r8ki), intent(in)  Angle1,
real(r8ki), intent(in)  Angle2,
real(r8ki), intent(in)  Angle3,
real(reki), dimension(:), intent(in)  tin,
real(r8ki), intent(inout)  Angle_out,
real(reki), intent(in)  tin_out 
)
Parameters
[in]angle1Angle at t1 > t2 > t3
[in]angle2Angle at t2 > t3
[in]angle3Angle at t3
[in]tinTimes associated with the inputs
[in,out]angle_outInput at tin_out
[in]tin_outtime to be extrap/interp'd to

◆ blendcosine()

real(reki) function nwtc_num::blendcosine ( real(reki), intent(in)  x,
real(reki), intent(in)  LowerBound,
real(reki), intent(in)  UpperBound 
)
Parameters
[in]lowerboundif x <= LowerBound, S=0
[in]upperboundif x >= UpperBound, S=1

◆ bsortreal()

subroutine nwtc_num::bsortreal ( real(reki), dimension(numpts), intent(inout)  RealAry,
integer, intent(in)  NumPts 
)

This routine sorts a list of real numbers.

It uses the bubble sort algorithm, which is only suitable for short lists.

Parameters
[in]numptsThe length of the list to be sorted.
[in,out]realaryThe list of real numbers to be sorted.

◆ convertunitstoengr()

subroutine nwtc_num::convertunitstoengr ( character(*), dimension(:), intent(inout)  Units,
real(reki), dimension(:), intent(out)  ScaleFactor 
)

This subroutine takes an "oldUnits" array, compares the strings to a list of units that will be converted to engineering units (kN and deg), and returns two arrays that give the new units and the multiplicative scaling factor to convert the old units to the new ones.

The three arrays must be the same size.

Parameters
[in,out]unitsin: the old units; out: the new units
[out]scalefactorscaling factor to convert old to new units (old*SF = new)

◆ convertunitstosi()

subroutine nwtc_num::convertunitstosi ( character(*), dimension(:), intent(inout)  Units,
real(reki), dimension(:), intent(out)  ScaleFactor 
)

This subroutine takes an "oldUnits" array, compares the strings to a list of units that will be converted to SI, and returns two arrays that give the new units and the multiplicative scaling factor to convert the old units to the new ones.

The three arrays must be the same size.

Parameters
[in,out]unitsin: the old units; out: the new units
[out]scalefactorscaling factor to convert old to new units (old*SF = new)

◆ cross_productr16()

real(quki) function, dimension (3) nwtc_num::cross_productr16 ( real(quki), dimension (3), intent(in)  Vector1,
real(quki), dimension (3), intent(in)  Vector2 
)

This function computes the cross product of two 3-element arrays (resulting in a vector):
cross_product = Vector1 \(\times\) Vector2
Use cross_product (nwtc_num::cross_product) instead of directly calling a specific routine in the generic interface.

◆ cross_productr4()

real(siki) function, dimension (3) nwtc_num::cross_productr4 ( real(siki), dimension (3), intent(in)  Vector1,
real(siki), dimension (3), intent(in)  Vector2 
)

This function computes the cross product of two 3-element arrays (resulting in a vector):
cross_product = Vector1 \(\times\) Vector2
Use cross_product (nwtc_num::cross_product) instead of directly calling a specific routine in the generic interface.

◆ cross_productr4r8()

real(r8ki) function, dimension (3) nwtc_num::cross_productr4r8 ( real(siki), dimension (3), intent(in)  Vector1,
real(r8ki), dimension (3), intent(in)  Vector2 
)

This function computes the cross product of two 3-element arrays (resulting in a vector):
cross_product = Vector1 \(\times\) Vector2
Use cross_product (nwtc_num::cross_product) instead of directly calling a specific routine in the generic interface.

◆ cross_productr8()

real(r8ki) function, dimension (3) nwtc_num::cross_productr8 ( real(r8ki), dimension (3), intent(in)  Vector1,
real(r8ki), dimension (3), intent(in)  Vector2 
)

This function computes the cross product of two 3-element arrays (resulting in a vector):
cross_product = Vector1 \(\times\) Vector2
Use cross_product (nwtc_num::cross_product) instead of directly calling a specific routine in the generic interface.

◆ cross_productr8r4()

real(r8ki) function, dimension (3) nwtc_num::cross_productr8r4 ( real(r8ki), dimension (3), intent(in)  Vector1,
real(siki), dimension (3), intent(in)  Vector2 
)

This function computes the cross product of two 3-element arrays (resulting in a vector):
cross_product = Vector1 \(\times\) Vector2
Use cross_product (nwtc_num::cross_product) instead of directly calling a specific routine in the generic interface.

◆ cubiclinsplineinitm()

subroutine nwtc_num::cubiclinsplineinitm ( real(reki), dimension (:), intent(in)  XAry,
real(reki), dimension (:,:), intent(in)  YAry,
real(reki), dimension (:,:,0:), intent(out)  Coef,
integer(intki), intent(out)  ErrStat,
character(*), intent(out)  ErrMsg 
)

This routine calculates the parameters needed to compute a irregularly-spaced natural linear spline.

This routine does not require that the XAry be regularly spaced.

Parameters
[out]coefThe coefficients for the cubic polynomials
[in]xaryInput array of x values
[in]yaryInput array of y values with multiple curves
[out]errstatError status
[out]errmsgError message

◆ cubicsplineinit()

subroutine nwtc_num::cubicsplineinit ( integer, intent(in)  AryLen,
real(reki), dimension (arylen), intent(in)  XAry,
real(reki), dimension (arylen), intent(in)  YAry,
real(reki), dimension (arylen-1,0:3), intent(out)  Coef,
integer(intki), intent(out)  ErrStat,
character(*), intent(out)  ErrMsg 
)

This routine calculates the parameters needed to compute a irregularly-spaced natural cubic spline.

Natural cubic splines are used in that the curvature at the end points is zero. This routine does not require that the XAry be regularly spaced.

Parameters
[in]arylenLength of the array
[out]coefThe coefficients for the cubic polynomials
[in]xaryInput array of x values
[in]yaryInput array of y values
[out]errstatError status
[out]errmsgError message

◆ cubicsplineinitm()

subroutine nwtc_num::cubicsplineinitm ( real(reki), dimension (:), intent(in)  XAry,
real(reki), dimension (:,:), intent(in)  YAry,
real(reki), dimension (:,:,0:), intent(out)  Coef,
integer(intki), intent(out)  ErrStat,
character(*), intent(out)  ErrMsg 
)

This routine calculates the parameters needed to compute a irregularly-spaced natural cubic spline.

Natural cubic splines are used in that the curvature at the end points is zero. This routine does not require that the XAry be regularly spaced. This version of the routine works with multiple curves that share the same X values.

Parameters
[out]coefThe coefficients for the cubic polynomials
[in]xaryInput array of x values
[in]yaryInput array of y values with multiple curves
[out]errstatError status
[out]errmsgError message

◆ cubicsplineinterp()

real(reki) function nwtc_num::cubicsplineinterp ( real(reki), intent(in)  X,
integer, intent(in)  AryLen,
real(reki), dimension (arylen), intent(in)  XAry,
real(reki), dimension (arylen), intent(in)  YAry,
real(reki), dimension (arylen-1,0:3), intent(in)  Coef,
integer(intki), intent(out)  ErrStat,
character(*), intent(out)  ErrMsg 
)

This routine interpolates a pair of arrays using cubic splines to find the function value at X.

One must call cubicsplineinit first to compute the coefficients of the cubics. This routine does not require that the XAry be regularly spaced.

Parameters
[in]arylenLength of the array
[in]coefThe coefficients for the cubic polynomials
[in]xThe value we are trying to interpolate for
[in]xaryInput array of regularly spaced x values
[in]yaryInput array of y values
[out]errstatError status
[out]errmsgError message

◆ cubicsplineinterpm()

real(reki) function, dimension(:), allocatable nwtc_num::cubicsplineinterpm ( real(reki), intent(in)  X,
real(reki), dimension (:), intent(in)  XAry,
real(reki), dimension (:,:), intent(in)  YAry,
real(reki), dimension (:,:,0:), intent(in)  Coef,
integer(intki), intent(out)  ErrStat,
character(*), intent(out)  ErrMsg 
)

This routine interpolates a pair of arrays using cubic splines to find the function value at X.

One must call cubicsplineinit first to compute the coefficients of the cubics. This routine does not require that the XAry be regularly spaced. This version of the routine works with multiple curves that share the same X values.

Parameters
[in]coefThe coefficients for the cubic polynomials
[in]xThe value we are trying to interpolate for
[in]xaryInput array of regularly spaced x values
[in]yaryInput array of y values with multiple curves
[out]errstatError status
[out]errmsgError message

◆ dcm_expd()

real(dbki) function, dimension(3,3) nwtc_num::dcm_expd ( real(dbki), dimension(3), intent(in)  lambda)

This function returns the matrix exponential, \(\Lambda = \exp(\lambda)\), of an input skew-symmetric matrix, \(\lambda\).

\(\lambda\) is defined as:

\begin{equation} \lambda = \begin{bmatrix} 0 & \lambda_3 & -\lambda_2 \\ -\lambda_3 & 0 & \lambda_1 \\ \lambda_2 & -\lambda_1 & 0 \end{bmatrix} \end{equation}

The angle of rotation for \(\lambda\) is

\begin{equation} \theta = \sqrt{{\lambda_1}^2+{\lambda_2}^2+{\lambda_3}^2} \end{equation}

The matrix exponential is calculated as

\begin{equation} \Lambda = \exp(\lambda) = \left\{ \begin{matrix} I & \theta = 0 \\ I + \frac{\sin\theta}{\theta}\lambda + \frac{1-\cos\theta}{\theta^2}\lambda^2 & \theta > 0 \end{matrix} \right. \end{equation}

This routine is the inverse of DCM_logMap (nwtc_num::dcm_logmap).
Use DCM_exp (nwtc_num::dcm_exp) instead of directly calling a specific routine in the generic interface.

Parameters
[in]lambdavector containing \(\lambda_1\), \(\lambda_2\), and \(\lambda_3\), the unique components of skew-symmetric matrix \(\lambda\)
Returns
the computed matrix exponential, \(\Lambda\)

◆ dcm_expr()

real(reki) function, dimension(3,3) nwtc_num::dcm_expr ( real(reki), dimension(3), intent(in)  lambda)

This function returns the matrix exponential, \(\Lambda = \exp(\lambda)\), of an input skew-symmetric matrix, \(\lambda\).

\(\lambda\) is defined as:

\begin{equation} \lambda = \begin{bmatrix} 0 & \lambda_3 & -\lambda_2 \\ -\lambda_3 & 0 & \lambda_1 \\ \lambda_2 & -\lambda_1 & 0 \end{bmatrix} \end{equation}

The angle of rotation for \(\lambda\) is

\begin{equation} \theta = \sqrt{{\lambda_1}^2+{\lambda_2}^2+{\lambda_3}^2} \end{equation}

The matrix exponential is calculated as

\begin{equation} \Lambda = \exp(\lambda) = \left\{ \begin{matrix} I & \theta = 0 \\ I + \frac{\sin\theta}{\theta}\lambda + \frac{1-\cos\theta}{\theta^2}\lambda^2 & \theta > 0 \end{matrix} \right. \end{equation}

This routine is the inverse of DCM_logMap (nwtc_num::dcm_logmap).
Use DCM_exp (nwtc_num::dcm_exp) instead of directly calling a specific routine in the generic interface.

Parameters
[in]lambdavector containing \(\lambda_1\), \(\lambda_2\), and \(\lambda_3\), the unique components of skew-symmetric matrix \(\lambda\)
Returns
the computed matrix exponential, \(\Lambda\)
Parameters
[in]lambdavector containing unique components of skew-symmetric matrix: \(\lambda_1\), \(\lambda_2\), and \(\lambda_3\)
Returns
the computed matrix exponential, \(\Lambda\)

◆ dcm_logmapd()

subroutine nwtc_num::dcm_logmapd ( real(dbki), dimension(3,3), intent(in)  DCM,
real(dbki), dimension(3), intent(out)  logMap,
integer(intki), intent(out)  ErrStat,
character(*), intent(out)  ErrMsg,
real(dbki), intent(out), optional  thetaOut 
)

For any direction cosine matrix (DCM), \(\Lambda\), this routine calculates the logarithmic map, \(\lambda\), which a skew-symmetric matrix:

\begin{equation} \lambda = \log( \Lambda ) = \begin{bmatrix} 0 & \lambda_3 & -\lambda_2 \\ -\lambda_3 & 0 & \lambda_1 \\ \lambda_2 & -\lambda_1 & 0 \end{bmatrix} \end{equation}

The angle of rotation for \(\Lambda\) is

\begin{equation} \theta= \begin{matrix} \cos^{-1}\left(\frac{1}{2}\left(\mathrm{trace}(\Lambda)-1\right)\right) & \theta \in \left[0,\pi\right]\end{matrix} \end{equation}

And the logarithmic map is

\begin{equation} \lambda = \left\{ \begin{matrix} 0 & \theta = 0 \\ \frac{\theta}{2\sin\theta} \left( \Lambda - \Lambda^T\right) & \theta \in \left(0,\pi\right) \\ \pm\pi v & \theta = \pi \end{matrix} \right. \end{equation}

where \(v\) is the skew-symmetric matrix associated with the unit-length eigenvector of \(\Lambda\) associated with the eigenvalue 1. However, this equation has numerical issues near \(\theta = \pi\), so for \(\theta > 3.1\) we instead implement a separate equation to find lambda * sign(lambda(indx_max)) and use \(\Lambda - \Lambda^T\) to choose the appropriate signs.

This routine is the inverse of DCM_exp (nwtc_num::dcm_exp).
Use DCM_logMap (nwtc_num::dcm_logmap) instead of directly calling a specific routine in the generic interface.

Parameters
[in]dcmthe direction cosine matrix, \(\Lambda\)
[out]logmapvector containing \(\lambda_1\), \(\lambda_2\), and \(\lambda_3\), the unique components of skew-symmetric matrix \(\lambda\)
[out]thetaoutthe angle of rotation, \(\theta\); output only for debugging
[out]errstatError status of the operation
[out]errmsgError message if ErrStat /= ErrID_None

Note that \( DCM = \begin{bmatrix} 1-\frac{1-\cos\theta}{\theta^2}\left( \lambda_3^2 + \lambda_2^2\right) & \frac{\sin\theta}{\theta}\lambda_3+\frac{1-\cos\theta}{\theta^2}\lambda_1\lambda_2 & -\frac{\sin\theta}{\theta}\lambda_2+\frac{1-\cos\theta}{\theta^2}\lambda_1\lambda_3 \\ -\frac{\sin\theta}{\theta}\lambda_3+\frac{1-\cos\theta}{\theta^2}\lambda_1\lambda_2 & 1-\frac{1-\cos\theta}{\theta^2}\left( \lambda_3^2 + \lambda_1^2\right) & \frac{\sin\theta}{\theta}\lambda_1+\frac{1-\cos\theta}{\theta^2}\lambda_2\lambda_3 \\ \frac{\sin\theta}{\theta}\lambda_2+\frac{1-\cos\theta}{\theta^2}\lambda_1\lambda_3 & -\frac{\sin\theta}{\theta}\lambda_1+\frac{1-\cos\theta}{\theta^2}\lambda_2\lambda_3 & 1-\frac{1-\cos\theta}{\theta^2}\left( \lambda_2^2 + \lambda_1^2\right) \\ \end{bmatrix} \)

◆ dcm_logmapr()

subroutine nwtc_num::dcm_logmapr ( real(reki), dimension(3,3), intent(in)  DCM,
real(reki), dimension(3), intent(out)  logMap,
integer(intki), intent(out)  ErrStat,
character(*), intent(out)  ErrMsg,
real(reki), intent(out), optional  thetaOut 
)

For any direction cosine matrix (DCM), \(\Lambda\), this routine calculates the logarithmic map, \(\lambda\), which a skew-symmetric matrix:

\begin{equation} \lambda = \log( \Lambda ) = \begin{bmatrix} 0 & \lambda_3 & -\lambda_2 \\ -\lambda_3 & 0 & \lambda_1 \\ \lambda_2 & -\lambda_1 & 0 \end{bmatrix} \end{equation}

The angle of rotation for \(\Lambda\) is

\begin{equation} \theta= \begin{matrix} \cos^{-1}\left(\frac{1}{2}\left(\mathrm{trace}(\Lambda)-1\right)\right) & \theta \in \left[0,\pi\right]\end{matrix} \end{equation}

And the logarithmic map is

\begin{equation} \lambda = \left\{ \begin{matrix} 0 & \theta = 0 \\ \frac{\theta}{2\sin\theta} \left( \Lambda - \Lambda^T\right) & \theta \in \left(0,\pi\right) \\ \pm\pi v & \theta = \pi \end{matrix} \right. \end{equation}

where \(v\) is the skew-symmetric matrix associated with the unit-length eigenvector of \(\Lambda\) associated with the eigenvalue 1. However, this equation has numerical issues near \(\theta = \pi\), so for \(\theta > 3.1\) we instead implement a separate equation to find lambda * sign(lambda(indx_max)) and use \(\Lambda - \Lambda^T\) to choose the appropriate signs.

This routine is the inverse of DCM_exp (nwtc_num::dcm_exp).
Use DCM_logMap (nwtc_num::dcm_logmap) instead of directly calling a specific routine in the generic interface.

Parameters
[in]dcmthe direction cosine matrix, \(\Lambda\)
[out]logmapvector containing \(\lambda_1\), \(\lambda_2\), and \(\lambda_3\), the unique components of skew-symmetric matrix \(\lambda\)
[out]thetaoutthe angle of rotation, \(\theta\); output only for debugging
[out]errstatError status of the operation
[out]errmsgError message if ErrStat /= ErrID_None

◆ dcm_setlogmapforinterpd()

subroutine nwtc_num::dcm_setlogmapforinterpd ( real(dbki), dimension(:,:), intent(inout)  tensor)

This routine sets the rotation parameters (logMap tensors from dcm_logmap) so that they can be appropriately interpolated, based on continunity of the neighborhood.

The tensor input matrix has columns of rotational parameters; one column for each set of values to be interpolated (i.e., for each column, i, tensor(:,i) is the returned logMap value from the routine dcm_logmap).

This is based on the \(2\pi\) periodicity of rotations:
if \(\lambda\) is one solution to \(\log(\Lambda)\), then so is \(\lambda_k = \lambda \left( 1 + \frac{2k\pi}{\left\| \lambda \right\|}\right)\) for any integer k.

Use DCM_SetLogMapForInterp (nwtc_num::dcm_setlogmapforinterp) instead of directly calling a specific routine in the generic interface.

Parameters
[in,out]tensora 3xn matrix, whose columns represent individual skew-symmmetric matrices. On exit, each column will be within \(2\pi\) of the previous column, allowing for interpolation of the quantities.

◆ dcm_setlogmapforinterpr()

subroutine nwtc_num::dcm_setlogmapforinterpr ( real(reki), dimension(:,:), intent(inout)  tensor)

This routine sets the rotation parameters (logMap tensors from dcm_logmap) so that they can be appropriately interpolated, based on continunity of the neighborhood.

The tensor input matrix has columns of rotational parameters; one column for each set of values to be interpolated (i.e., for each column, i, tensor(:,i) is the returned logMap value from the routine dcm_logmap).

This is based on the \(2\pi\) periodicity of rotations:
if \(\lambda\) is one solution to \(\log(\Lambda)\), then so is \(\lambda_k = \lambda \left( 1 + \frac{2k\pi}{\left\| \lambda \right\|}\right)\) for any integer k.

Use DCM_SetLogMapForInterp (nwtc_num::dcm_setlogmapforinterp) instead of directly calling a specific routine in the generic interface.

Parameters
[in,out]tensora 3xn matrix, whose columns represent individual skew-symmmetric matrices. On exit, each column will be within \(2\pi\) of the previous column, allowing for interpolation of the quantities.

◆ dcm_to_quaternion()

type(quaternion) function nwtc_num::dcm_to_quaternion ( real(reki), dimension (3,3), intent(in)  DCM)

This function converts a direction cosine matrix to an equivalent quaternion.

Parameters
[in]dcmdirection cosine matrix
Returns
equivalent quaternion

◆ equalrealnos16()

logical function nwtc_num::equalrealnos16 ( real(quki), intent(in)  ReNum1,
real(quki), intent(in)  ReNum2 
)

This function compares two real numbers and determines if they are "almost" equal, i.e.

within some relative tolerance (basically ignoring the last 2 significant digits) (see "Safe Comparisons" suggestion from http://www.lahey.com/float.htm)

Note that the numbers are added together in this routine, so overflow can result if comparing two "huge" numbers.
Use EqualRealNos (nwtc_num::equalrealnos) instead of directly calling a specific routine in the generic interface.

Parameters
[in]renum1the first real number to compare
[in]renum2the second real number to compare
Returns
.true. if and only if the numbers are almost equal
.true. if and only if the numbers are almost equal

◆ equalrealnos4()

logical function nwtc_num::equalrealnos4 ( real(siki), intent(in)  ReNum1,
real(siki), intent(in)  ReNum2 
)

This function compares two real numbers and determines if they are "almost" equal, i.e.

within some relative tolerance (basically ignoring the last 2 significant digits) (see "Safe Comparisons" suggestion from http://www.lahey.com/float.htm)

Note that the numbers are added together in this routine, so overflow can result if comparing two "huge" numbers.
Use EqualRealNos (nwtc_num::equalrealnos) instead of directly calling a specific routine in the generic interface.

Parameters
[in]renum1the first real number to compare
[in]renum2the second real number to compare
Returns
.true. if and only if the numbers are almost equal

◆ equalrealnos8()

logical function nwtc_num::equalrealnos8 ( real(r8ki), intent(in)  ReNum1,
real(r8ki), intent(in)  ReNum2 
)

This function compares two real numbers and determines if they are "almost" equal, i.e.

within some relative tolerance (basically ignoring the last 2 significant digits) (see "Safe Comparisons" suggestion from http://www.lahey.com/float.htm)

Note that the numbers are added together in this routine, so overflow can result if comparing two "huge" numbers.
Use EqualRealNos (nwtc_num::equalrealnos) instead of directly calling a specific routine in the generic interface.

Parameters
[in]renum1the first real number to compare
[in]renum2the second real number to compare
Returns
.true. if and only if the numbers are almost equal
.true. if and only if the numbers are almost equal

◆ eulerconstructr16()

real(quki) function, dimension(3,3) nwtc_num::eulerconstructr16 ( real(quki), dimension(3), intent(in)  theta)

This function creates a rotation matrix, M, from a 1-2-3 rotation sequence of the 3 Euler angles, \(\theta_x\), \(\theta_y\), and \(\theta_z\), in radians.

M represents a change of basis (from global to local coordinates; not a physical rotation of the body). It is the inverse of EulerExtract (nwtc_num::eulerextract).

\begin{eqnarray*} M & = & R(\theta_z) R(\theta_y) R(\theta_x) \\ & = & \begin{bmatrix} \cos(\theta_z) & \sin(\theta_z) & 0 \\ -\sin(\theta_z) & \cos(\theta_z) & 0 \\ 0 & 0 & 1 \end{bmatrix} \begin{bmatrix} \cos(\theta_y) & 0 & -\sin(\theta_y) \\ 0 & 1 & 0 \\ \sin(\theta_y) & 0 & \cos(\theta_y) \end{bmatrix} \begin{bmatrix} 1 & 0 & 0 \\ 0 & \cos(\theta_x) & \sin(\theta_x) \\ 0 & -\sin(\theta_x) & \cos(\theta_x) \end{bmatrix} \\ & = & \begin{bmatrix} \cos(\theta_y)\cos(\theta_z) & \cos(\theta_x)\sin(\theta_z)+\sin(\theta_x)\sin(\theta_y)\cos(\theta_z) & \sin(\theta_x)\sin(\theta_z)-\cos(\theta_x)\sin(\theta_y)\cos(\theta_z) \\ -\cos(\theta_y)\sin(\theta_z) & \cos(\theta_x)\cos(\theta_z)-\sin(\theta_x)\sin(\theta_y)\sin(\theta_z) & \sin(\theta_x)\cos(\theta_z)+\cos(\theta_x)\sin(\theta_y)\sin(\theta_z) \\ \sin(\theta_y) & -\sin(\theta_x)\cos(\theta_y) & \cos(\theta_x)\cos(\theta_y) \\ \end{bmatrix} \end{eqnarray*}

Use EulerConstruct (nwtc_num::eulerconstruct) instead of directly calling a specific routine in the generic interface.

Returns
rotation matrix, M
Parameters
[in]thetathe 3 rotation angles: \(\theta_x, \theta_y, \theta_z\)

◆ eulerconstructr4()

real(siki) function, dimension(3,3) nwtc_num::eulerconstructr4 ( real(siki), dimension(3), intent(in)  theta)

This function creates a rotation matrix, M, from a 1-2-3 rotation sequence of the 3 Euler angles, \(\theta_x\), \(\theta_y\), and \(\theta_z\), in radians.

M represents a change of basis (from global to local coordinates; not a physical rotation of the body). It is the inverse of EulerExtract (nwtc_num::eulerextract).

\begin{eqnarray*} M & = & R(\theta_z) R(\theta_y) R(\theta_x) \\ & = & \begin{bmatrix} \cos(\theta_z) & \sin(\theta_z) & 0 \\ -\sin(\theta_z) & \cos(\theta_z) & 0 \\ 0 & 0 & 1 \end{bmatrix} \begin{bmatrix} \cos(\theta_y) & 0 & -\sin(\theta_y) \\ 0 & 1 & 0 \\ \sin(\theta_y) & 0 & \cos(\theta_y) \end{bmatrix} \begin{bmatrix} 1 & 0 & 0 \\ 0 & \cos(\theta_x) & \sin(\theta_x) \\ 0 & -\sin(\theta_x) & \cos(\theta_x) \end{bmatrix} \\ & = & \begin{bmatrix} \cos(\theta_y)\cos(\theta_z) & \cos(\theta_x)\sin(\theta_z)+\sin(\theta_x)\sin(\theta_y)\cos(\theta_z) & \sin(\theta_x)\sin(\theta_z)-\cos(\theta_x)\sin(\theta_y)\cos(\theta_z) \\ -\cos(\theta_y)\sin(\theta_z) & \cos(\theta_x)\cos(\theta_z)-\sin(\theta_x)\sin(\theta_y)\sin(\theta_z) & \sin(\theta_x)\cos(\theta_z)+\cos(\theta_x)\sin(\theta_y)\sin(\theta_z) \\ \sin(\theta_y) & -\sin(\theta_x)\cos(\theta_y) & \cos(\theta_x)\cos(\theta_y) \\ \end{bmatrix} \end{eqnarray*}

Use EulerConstruct (nwtc_num::eulerconstruct) instead of directly calling a specific routine in the generic interface.

Returns
rotation matrix, M
Parameters
[in]thetathe 3 rotation angles: \(\theta_x, \theta_y, \theta_z\)

◆ eulerconstructr8()

real(r8ki) function, dimension(3,3) nwtc_num::eulerconstructr8 ( real(r8ki), dimension(3), intent(in)  theta)

This function creates a rotation matrix, M, from a 1-2-3 rotation sequence of the 3 Euler angles, \(\theta_x\), \(\theta_y\), and \(\theta_z\), in radians.

M represents a change of basis (from global to local coordinates; not a physical rotation of the body). It is the inverse of EulerExtract (nwtc_num::eulerextract).

\begin{eqnarray*} M & = & R(\theta_z) R(\theta_y) R(\theta_x) \\ & = & \begin{bmatrix} \cos(\theta_z) & \sin(\theta_z) & 0 \\ -\sin(\theta_z) & \cos(\theta_z) & 0 \\ 0 & 0 & 1 \end{bmatrix} \begin{bmatrix} \cos(\theta_y) & 0 & -\sin(\theta_y) \\ 0 & 1 & 0 \\ \sin(\theta_y) & 0 & \cos(\theta_y) \end{bmatrix} \begin{bmatrix} 1 & 0 & 0 \\ 0 & \cos(\theta_x) & \sin(\theta_x) \\ 0 & -\sin(\theta_x) & \cos(\theta_x) \end{bmatrix} \\ & = & \begin{bmatrix} \cos(\theta_y)\cos(\theta_z) & \cos(\theta_x)\sin(\theta_z)+\sin(\theta_x)\sin(\theta_y)\cos(\theta_z) & \sin(\theta_x)\sin(\theta_z)-\cos(\theta_x)\sin(\theta_y)\cos(\theta_z) \\ -\cos(\theta_y)\sin(\theta_z) & \cos(\theta_x)\cos(\theta_z)-\sin(\theta_x)\sin(\theta_y)\sin(\theta_z) & \sin(\theta_x)\cos(\theta_z)+\cos(\theta_x)\sin(\theta_y)\sin(\theta_z) \\ \sin(\theta_y) & -\sin(\theta_x)\cos(\theta_y) & \cos(\theta_x)\cos(\theta_y) \\ \end{bmatrix} \end{eqnarray*}

Use EulerConstruct (nwtc_num::eulerconstruct) instead of directly calling a specific routine in the generic interface.

Returns
rotation matrix, M
Parameters
[in]thetathe 3 rotation angles: \(\theta_x, \theta_y, \theta_z\)

◆ eulerextractr16()

real(quki) function, dimension(3) nwtc_num::eulerextractr16 ( real(quki), dimension(3,3), intent(in)  M)

if M is a rotation matrix from a 1-2-3 rotation sequence, this function returns the 3 Euler angles, \(\theta_x\), \(\theta_y\), and \(\theta_z\) (in radians), that formed the matrix.

M represents a change of basis (from global to local coordinates; not a physical rotation of the body). M is the inverse of EulerConstruct (nwtc_num::eulerconstruct).

\begin{eqnarray*} M & = & R(\theta_z) R(\theta_y) R(\theta_x) \\ & = & \begin{bmatrix} \cos(\theta_z) & \sin(\theta_z) & 0 \\ -\sin(\theta_z) & \cos(\theta_z) & 0 \\ 0 & 0 & 1 \end{bmatrix} \begin{bmatrix} \cos(\theta_y) & 0 & -\sin(\theta_y) \\ 0 & 1 & 0 \\ \sin(\theta_y) & 0 & \cos(\theta_y) \end{bmatrix} \begin{bmatrix} 1 & 0 & 0 \\ 0 & \cos(\theta_x) & \sin(\theta_x) \\ 0 & -\sin(\theta_x) & \cos(\theta_x) \end{bmatrix} \\ & = & \begin{bmatrix} \cos(\theta_y)\cos(\theta_z) & \cos(\theta_x)\sin(\theta_z)+\sin(\theta_x)\sin(\theta_y)\cos(\theta_z) & \sin(\theta_x)\sin(\theta_z)-\cos(\theta_x)\sin(\theta_y)\cos(\theta_z) \\ -\cos(\theta_y)\sin(\theta_z) & \cos(\theta_x)\cos(\theta_z)-\sin(\theta_x)\sin(\theta_y)\sin(\theta_z) & \sin(\theta_x)\cos(\theta_z)+\cos(\theta_x)\sin(\theta_y)\sin(\theta_z) \\ \sin(\theta_y) & -\sin(\theta_x)\cos(\theta_y) & \cos(\theta_x)\cos(\theta_y) \\ \end{bmatrix} \end{eqnarray*}

returned angles are in the range \(\theta_x,\theta_y, \theta_z \in \left[ \pi, -\pi \right]\)
Use EulerExtract (nwtc_num::eulerextract) instead of directly calling a specific routine in the generic interface.

Parameters
[in]mrotation matrix, M
Returns
the 3 rotation angles: \(\theta_x, \theta_y, \theta_z\)

◆ eulerextractr4()

real(siki) function, dimension(3) nwtc_num::eulerextractr4 ( real(siki), dimension(3,3), intent(in)  M)

if M is a rotation matrix from a 1-2-3 rotation sequence, this function returns the 3 Euler angles, \(\theta_x\), \(\theta_y\), and \(\theta_z\) (in radians), that formed the matrix.

M represents a change of basis (from global to local coordinates; not a physical rotation of the body). M is the inverse of EulerConstruct (nwtc_num::eulerconstruct).

\begin{eqnarray*} M & = & R(\theta_z) R(\theta_y) R(\theta_x) \\ & = & \begin{bmatrix} \cos(\theta_z) & \sin(\theta_z) & 0 \\ -\sin(\theta_z) & \cos(\theta_z) & 0 \\ 0 & 0 & 1 \end{bmatrix} \begin{bmatrix} \cos(\theta_y) & 0 & -\sin(\theta_y) \\ 0 & 1 & 0 \\ \sin(\theta_y) & 0 & \cos(\theta_y) \end{bmatrix} \begin{bmatrix} 1 & 0 & 0 \\ 0 & \cos(\theta_x) & \sin(\theta_x) \\ 0 & -\sin(\theta_x) & \cos(\theta_x) \end{bmatrix} \\ & = & \begin{bmatrix} \cos(\theta_y)\cos(\theta_z) & \cos(\theta_x)\sin(\theta_z)+\sin(\theta_x)\sin(\theta_y)\cos(\theta_z) & \sin(\theta_x)\sin(\theta_z)-\cos(\theta_x)\sin(\theta_y)\cos(\theta_z) \\ -\cos(\theta_y)\sin(\theta_z) & \cos(\theta_x)\cos(\theta_z)-\sin(\theta_x)\sin(\theta_y)\sin(\theta_z) & \sin(\theta_x)\cos(\theta_z)+\cos(\theta_x)\sin(\theta_y)\sin(\theta_z) \\ \sin(\theta_y) & -\sin(\theta_x)\cos(\theta_y) & \cos(\theta_x)\cos(\theta_y) \\ \end{bmatrix} \end{eqnarray*}

returned angles are in the range \(\theta_x,\theta_y, \theta_z \in \left[ \pi, -\pi \right]\)
Use EulerExtract (nwtc_num::eulerextract) instead of directly calling a specific routine in the generic interface.

Parameters
[in]mrotation matrix, M
Returns
the 3 rotation angles: \(\theta_x, \theta_y, \theta_z\)

◆ eulerextractr8()

real(r8ki) function, dimension(3) nwtc_num::eulerextractr8 ( real(r8ki), dimension(3,3), intent(in)  M)

if M is a rotation matrix from a 1-2-3 rotation sequence, this function returns the 3 Euler angles, \(\theta_x\), \(\theta_y\), and \(\theta_z\) (in radians), that formed the matrix.

M represents a change of basis (from global to local coordinates; not a physical rotation of the body). M is the inverse of EulerConstruct (nwtc_num::eulerconstruct).

\begin{eqnarray*} M & = & R(\theta_z) R(\theta_y) R(\theta_x) \\ & = & \begin{bmatrix} \cos(\theta_z) & \sin(\theta_z) & 0 \\ -\sin(\theta_z) & \cos(\theta_z) & 0 \\ 0 & 0 & 1 \end{bmatrix} \begin{bmatrix} \cos(\theta_y) & 0 & -\sin(\theta_y) \\ 0 & 1 & 0 \\ \sin(\theta_y) & 0 & \cos(\theta_y) \end{bmatrix} \begin{bmatrix} 1 & 0 & 0 \\ 0 & \cos(\theta_x) & \sin(\theta_x) \\ 0 & -\sin(\theta_x) & \cos(\theta_x) \end{bmatrix} \\ & = & \begin{bmatrix} \cos(\theta_y)\cos(\theta_z) & \cos(\theta_x)\sin(\theta_z)+\sin(\theta_x)\sin(\theta_y)\cos(\theta_z) & \sin(\theta_x)\sin(\theta_z)-\cos(\theta_x)\sin(\theta_y)\cos(\theta_z) \\ -\cos(\theta_y)\sin(\theta_z) & \cos(\theta_x)\cos(\theta_z)-\sin(\theta_x)\sin(\theta_y)\sin(\theta_z) & \sin(\theta_x)\cos(\theta_z)+\cos(\theta_x)\sin(\theta_y)\sin(\theta_z) \\ \sin(\theta_y) & -\sin(\theta_x)\cos(\theta_y) & \cos(\theta_x)\cos(\theta_y) \\ \end{bmatrix} \end{eqnarray*}

returned angles are in the range \(\theta_x,\theta_y, \theta_z \in \left[ \pi, -\pi \right]\)
Use EulerExtract (nwtc_num::eulerextract) instead of directly calling a specific routine in the generic interface.

Parameters
[in]mrotation matrix, M
Returns
the 3 rotation angles: \(\theta_x, \theta_y, \theta_z\)

◆ eye2()

subroutine nwtc_num::eye2 ( real(reki), dimension (:,:), intent(inout)  A,
integer(intki), intent(out)  ErrStat,
character(*), intent(out)  ErrMsg 
)

This routine sets the matrices in the first two dimensions of A equal to the identity matrix (all zeros, with ones on the diagonal).

If the first two dimensions of A are not equal (i.e., matrix A(:,:,n) is non-square), this routine returns the pseudo-identity.

Use eye (nwtc_num::eye) instead of directly calling a specific routine in the generic interface.

Parameters
[in,out]aArray to set to the identity matrix (nr,nc,n)
[out]errstatError level
[out]errmsgErrMsg corresponding to ErrStat

◆ eye2d()

subroutine nwtc_num::eye2d ( real(dbki), dimension (:,:), intent(inout)  A,
integer(intki), intent(out)  ErrStat,
character(*), intent(out)  ErrMsg 
)

This routine sets the matrices in the first two dimensions of A equal to the identity matrix (all zeros, with ones on the diagonal).

If the first two dimensions of A are not equal (i.e., matrix A(:,:,n) is non-square), this routine returns the pseudo-identity.

Use eye (nwtc_num::eye) instead of directly calling a specific routine in the generic interface.

Parameters
[in,out]aArray to set to the identity matrix (nr,nc,n)
[out]errstatError level
[out]errmsgErrMsg corresponding to ErrStat
[in,out]aArray to set to the identity matrix (nr,nc,n)
[out]errstatError level
[out]errmsgErrMsg corresponding to ErrStat

◆ eye3d()

subroutine nwtc_num::eye3d ( real(dbki), dimension (:,:,:), intent(inout)  A,
integer(intki), intent(out)  ErrStat,
character(*), intent(out)  ErrMsg 
)

This routine sets the matrices in the first two dimensions of A equal to the identity matrix (all zeros, with ones on the diagonal).

Parameters
[in,out]aArray to set to the identity matrix (nr,nc,n)
[out]errstatError level
[out]errmsgErrMsg corresponding to ErrStat

◆ gausselim()

subroutine nwtc_num::gausselim ( real(reki), dimension (numeq, numeq+1 ), intent(in)  AugMatIn,
integer(intki), intent(in)  NumEq,
real(reki), dimension (numeq), intent(out)  x,
integer(intki), intent(out)  ErrStat,
character(*), intent(out)  ErrMsg 
)

This routine uses the Gauss-Jordan elimination method for the solution of a given set of simultaneous linear equations.

NOTE: this routine works if no pivot points are zero and you don't want the eschelon or reduced eschelon form of the augmented matrix. The form of the original augmented matrix IS preserved in this call. This routine was originally in FAST.f90. When AugMatIn = [ A b ], this routine returns the solution vector x to the equation Ax = b.

Parameters
[in]numeqNumber of equations in augmented matrix
[in]augmatinAugmented matrix passed into this subroutine ( AugMatIn = [ A b ]
[out]xSolution vector
[out]errstatError level
[out]errmsgErrMsg corresponding to ErrStat

◆ getoffsetreg()

subroutine nwtc_num::getoffsetreg ( real(reki), dimension (numpts), intent(in)  Ary,
integer, intent(in)  NumPts,
real(reki), intent(in)  Val,
integer(intki), intent(out)  Ind,
real(reki), intent(out)  Fract,
integer(intki), intent(out)  ErrStat,
character(*), intent(out)  ErrMsg 
)

Determine index of the point in Ary just below Val and the fractional distance to the next point in the array.

The elements of the array are assumed to be regularly spaced.

Parameters
[in]numptsLength of the array.
[in]aryInput array of regularly spaced values.
[out]fractThe fractional distance of Val between the surrounding array elements.
[in]valThe value we hope to bound in the array.
[out]errstatError status.
[out]indThe index of the point in Ary just below Val.
[out]errmsgError message.

◆ getsmllrotangsd()

real(dbki) function, dimension ( 3 ) nwtc_num::getsmllrotangsd ( real(dbki), dimension (3,3), intent(in)  DCMat,
integer, intent(out)  ErrStat,
character(*), intent(out), optional  ErrMsg 
)

This subroutine computes the angles that make up the input direction cosine matrix, DCMat, assuming small angles.

It is the inverse of SmllRotTrans (nwtc_num::smllrottrans).
Use GetSmllRotAngs (nwtc_num::getsmllrotangs) instead of directly calling a specific routine in the generic interface.

Parameters
[in]dcmata direction cosine matrix
[out]errstata non-zero value indicates an error in the permutation matrix algorithm
[out]errmsga non-zero value indicates an error in the permutation matrix algorithm
Returns
the rotational angles

◆ getsmllrotangsr()

real(reki) function, dimension ( 3 ) nwtc_num::getsmllrotangsr ( real(reki), dimension (3,3), intent(in)  DCMat,
integer, intent(out)  ErrStat,
character(*), intent(out), optional  ErrMsg 
)

This subroutine computes the angles that make up the input direction cosine matrix, DCMat, assuming small angles.

It is the inverse of SmllRotTrans (nwtc_num::smllrottrans).
Use GetSmllRotAngs (nwtc_num::getsmllrotangs) instead of directly calling a specific routine in the generic interface.

Parameters
[in]dcmata direction cosine matrix
[out]errstata non-zero value indicates an error in the permutation matrix algorithm
[out]errmsga non-zero value indicates an error in the permutation matrix algorithm
Returns
the rotational angles

◆ gl_pts()

subroutine nwtc_num::gl_pts ( integer, intent(in)  IPt,
integer, intent(in)  NPts,
real(reki), intent(out)  Loc,
real(reki), intent(out)  Wt,
integer, intent(out)  ErrStat,
character(*), intent(out)  ErrMsg 
)

This funtion returns the non-dimensional (-1:+1) location of the given Gauss-Legendre Quadrature point and its weight.

It works for NPts \(\in \left[{1,6\right]\). The values came from Carnahan, Brice; Luther, H.A.; Wilkes, James O. (1969) "Applied Numerical Methods."

Parameters
[out]locThe location of the specified point.
[out]wtThe weight for the specified point.
[out]errstatError status
[out]errmsgError message
[in]iptThe quadrature point in question.
[in]nptsThe number of points used in the quadrature.

◆ indexcharary()

integer function nwtc_num::indexcharary ( character(*), intent(in)  CVal,
character(*), dimension(:), intent(in)  CAry 
)

This funtion returns an integer index such that CAry(IndexCharAry) = CVal.

If no element in the array matches CVal, the value -1 is returned. The routine performs a binary search on the input array to determine if CVal is an element of the array; thus, CAry must be sorted and stored in increasing alphebetical (ASCII) order. The routine does not check that the array is sorted. The routine assumes that CVal is type CHARACTER and CAry is an array of CHARACTERS.

Returns
integer index such that CAry(IndexCharAry) = CVal
Parameters
[in]cvalString to find
[in]caryArray of strings to search

◆ interparrayr16()

subroutine nwtc_num::interparrayr16 ( real(quki), dimension(:), intent(in)  xknown,
real(quki), dimension(:), intent(in)  yknown,
real(quki), dimension(:), intent(in)  xnew,
real(quki), dimension(:), intent(out)  ynew 
)

This subroutine calculates interpolated values for an array of input values.

The size of the xknown and yknown arrays must match, and the size of the xnew and ynew arrays must match. Xknown must be in ascending order. Values outside the range of xknown are fixed to the end points.

◆ interparrayr4()

subroutine nwtc_num::interparrayr4 ( real(siki), dimension(:), intent(in)  xknown,
real(siki), dimension(:), intent(in)  yknown,
real(siki), dimension(:), intent(in)  xnew,
real(siki), dimension(:), intent(out)  ynew 
)

This subroutine calculates interpolated values for an array of input values.

The size of the xknown and yknown arrays must match, and the size of the xnew and ynew arrays must match. Xknown must be in ascending order. Values outside the range of xknown are fixed to the end points.

◆ interparrayr8()

subroutine nwtc_num::interparrayr8 ( real(r8ki), dimension(:), intent(in)  xknown,
real(r8ki), dimension(:), intent(in)  yknown,
real(r8ki), dimension(:), intent(in)  xnew,
real(r8ki), dimension(:), intent(out)  ynew 
)

This subroutine calculates interpolated values for an array of input values.

The size of the xknown and yknown arrays must match, and the size of the xnew and ynew arrays must match. Xknown must be in ascending order. Values outside the range of xknown are fixed to the end points.

◆ interpbincomp()

complex(reki) function nwtc_num::interpbincomp ( real(reki), intent(in)  XVal,
real(reki), dimension (arylen), intent(in)  XAry,
complex(reki), dimension (arylen), intent(in)  YAry,
integer, intent(inout)  ILo,
integer, intent(in)  AryLen 
)

This funtion returns a y-value that corresponds to an input x-value by interpolating into the arrays.

It uses a binary interpolation scheme that takes about log(AryLen) / log(2) steps to converge. It returns the first or last YAry() value if XVal is outside the limits of XAry().

Use InterpBin (nwtc_num::interpbin) instead of directly calling a specific routine in the generic interface.

Returns
The interpolated value of Y at XVal
Parameters
[in]arylenLength of the arrays.
[in,out]iloThe low index into the arrays.
[in]xaryArray of X values to be interpolated.
[in]xvalX value to be interpolated.
[in]yaryArray of Y values to be interpolated.

◆ interpbinreal()

real(reki) function nwtc_num::interpbinreal ( real(reki), intent(in)  XVal,
real(reki), dimension (arylen), intent(in)  XAry,
real(reki), dimension (arylen), intent(in)  YAry,
integer, intent(inout)  ILo,
integer, intent(in)  AryLen 
)

This funtion returns a y-value that corresponds to an input x-value by interpolating into the arrays.

It uses a binary interpolation scheme that takes about log(AryLen) / log(2) steps to converge. It returns the first or last YAry() value if XVal is outside the limits of XAry().

Use InterpBin (nwtc_num::interpbin) instead of directly calling a specific routine in the generic interface.

Returns
The interpolated value of Y at XVal
Parameters
[in]arylenLength of the arrays.
[in,out]iloThe low index into the arrays.
[in]xaryArray of X values to be interpolated.
[in]xvalX value to be interpolated.
[in]yaryArray of Y values to be interpolated.
Returns
The interpolated value of Y at XVal
Parameters
[in]arylenLength of the arrays.
[in,out]iloThe low index into the arrays.
[in]xaryArray of X values to be interpolated.
[in]xvalX value to be interpolated.
[in]yaryArray of Y values to be interpolated.

◆ interpstpcomp16()

complex(quki) function nwtc_num::interpstpcomp16 ( real(quki), intent(in)  XVal,
real(quki), dimension (arylen), intent(in)  XAry,
complex(quki), dimension (arylen), intent(in)  YAry,
integer, intent(inout)  Ind,
integer, intent(in)  AryLen 
)

This funtion returns a y-value that corresponds to an input x-value by interpolating into the arrays.

It uses the passed index as the starting point and does a stepwise interpolation from there. This is especially useful when the calling routines save the value from the last time this routine was called for a given case where XVal does not change much from call to call. When there is no correlation from one interpolation to another, InterpBin() (nwtc_num::interpbin) may be a better choice. It returns the first or last YAry() value if XVal is outside the limits of XAry().

Use InterpStp (nwtc_num::interpstp) instead of directly calling a specific routine in the generic interface.

Parameters
[in]arylenLength of the arrays.
[in,out]indInitial and final index into the arrays.
[in]xaryArray of X values to be interpolated.
[in]xvalX value to be interpolated.
[in]yaryArray of Y values to be interpolated.
Returns
The interpolated value of Y at XVal
Parameters
[in]arylenLength of the arrays.
[in,out]indInitial and final index into the arrays.
[in]xaryArray of X values to be interpolated.
[in]xvalX value to be interpolated.
[in]yaryArray of Y values to be interpolated.

◆ interpstpcomp4()

complex(siki) function nwtc_num::interpstpcomp4 ( real(siki), intent(in)  XVal,
real(siki), dimension (arylen), intent(in)  XAry,
complex(siki), dimension (arylen), intent(in)  YAry,
integer, intent(inout)  Ind,
integer, intent(in)  AryLen 
)

This funtion returns a y-value that corresponds to an input x-value by interpolating into the arrays.

It uses the passed index as the starting point and does a stepwise interpolation from there. This is especially useful when the calling routines save the value from the last time this routine was called for a given case where XVal does not change much from call to call. When there is no correlation from one interpolation to another, InterpBin() (nwtc_num::interpbin) may be a better choice. It returns the first or last YAry() value if XVal is outside the limits of XAry().

Use InterpStp (nwtc_num::interpstp) instead of directly calling a specific routine in the generic interface.

Parameters
[in]arylenLength of the arrays.
[in,out]indInitial and final index into the arrays.
[in]xaryArray of X values to be interpolated.
[in]xvalX value to be interpolated.
[in]yaryArray of Y values to be interpolated.

◆ interpstpcomp8()

complex(r8ki) function nwtc_num::interpstpcomp8 ( real(r8ki), intent(in)  XVal,
real(r8ki), dimension (arylen), intent(in)  XAry,
complex(r8ki), dimension (arylen), intent(in)  YAry,
integer, intent(inout)  Ind,
integer, intent(in)  AryLen 
)

This funtion returns a y-value that corresponds to an input x-value by interpolating into the arrays.

It uses the passed index as the starting point and does a stepwise interpolation from there. This is especially useful when the calling routines save the value from the last time this routine was called for a given case where XVal does not change much from call to call. When there is no correlation from one interpolation to another, InterpBin() (nwtc_num::interpbin) may be a better choice. It returns the first or last YAry() value if XVal is outside the limits of XAry().

Use InterpStp (nwtc_num::interpstp) instead of directly calling a specific routine in the generic interface.

Parameters
[in]arylenLength of the arrays.
[in,out]indInitial and final index into the arrays.
[in]xaryArray of X values to be interpolated.
[in]xvalX value to be interpolated.
[in]yaryArray of Y values to be interpolated.
Returns
The interpolated value of Y at XVal
Parameters
[in]arylenLength of the arrays.
[in,out]indInitial and final index into the arrays.
[in]xaryArray of X values to be interpolated.
[in]xvalX value to be interpolated.
[in]yaryArray of Y values to be interpolated.

◆ interpstpmat()

subroutine nwtc_num::interpstpmat ( real(reki), intent(in)  XVal,
real(reki), dimension (arylen), intent(in)  XAry,
real(reki), dimension (:,:), intent(in)  Y,
integer, intent(inout)  Ind,
integer, intent(in)  AryLen,
real(reki), dimension(:), intent(out)  yInterp 
)

This funtion returns a y-value array that corresponds to an input x-value by interpolating into the arrays.

It uses the passed index as the starting point and does a stepwise interpolation from there. This is especially useful when the calling routines save the value from the last time this routine was called for a given case where XVal does not change much from call to call. It returns the first or last Y() row value if XVal is outside the limits of XAry().

Parameters
[out]yinterpThe interpolated value(s) of Y(dim=2) at XVal
[in]arylenLength of the arrays.
[in,out]indInitial and final index into the arrays.
[in]xaryArray of X values to be interpolated.
[in]xvalX value to be interpolated.
[in]yMatrix of Y values to be interpolated; First dimension is AryLen.

◆ interpstpreal16()

real(quki) function nwtc_num::interpstpreal16 ( real(quki), intent(in)  XVal,
real(quki), dimension (arylen), intent(in)  XAry,
real(quki), dimension (arylen), intent(in)  YAry,
integer, intent(inout)  Ind,
integer, intent(in)  AryLen 
)

This funtion returns a y-value that corresponds to an input x-value by interpolating into the arrays.

It uses the passed index as the starting point and does a stepwise interpolation from there. This is especially useful when the calling routines save the value from the last time this routine was called for a given case where XVal does not change much from call to call. When there is no correlation from one interpolation to another, InterpBin() (nwtc_num::interpbin) may be a better choice. It returns the first or last YAry() value if XVal is outside the limits of XAry().

Use InterpStp (nwtc_num::interpstp) instead of directly calling a specific routine in the generic interface.

Parameters
[in]arylenLength of the arrays.
[in,out]indInitial and final index into the arrays.
[in]xaryArray of X values to be interpolated.
[in]xvalX value to be interpolated.
[in]yaryArray of Y values to be interpolated.
Returns
The interpolated value of Y at XVal

◆ interpstpreal2d()

subroutine nwtc_num::interpstpreal2d ( real(reki), dimension(numdimensions), intent(in)  InCoord,
real(reki), dimension(:,:), intent(in)  Dataset,
real(reki), dimension(:), intent(in)  x,
real(reki), dimension(:), intent(in)  y,
integer(intki), dimension(numdimensions), intent(inout)  LastIndex,
real(reki), intent(out)  InterpData 
)
Parameters
[in]incoordArranged as (x, y)
[in]datasetArranged as (x, y)
[in]xfirst dimension in increasing order
[in]ysecond dimension in increasing order
[in,out]lastindexIndex for the last (x, y) used
[out]interpdataThe interpolated value of Dataset(:,:) at InCoord

◆ interpstpreal3d()

subroutine nwtc_num::interpstpreal3d ( real(reki), dimension(numdimensions), intent(in)  InCoord,
real(reki), dimension(:,:,:), intent(in)  Dataset,
real(reki), dimension(:), intent(in)  x,
real(reki), dimension(:), intent(in)  y,
real(reki), dimension(:), intent(in)  z,
integer(intki), dimension(numdimensions), intent(inout)  LastIndex,
real(reki), intent(out)  InterpData 
)
Parameters
[in]incoordArranged as (x, y, z)
[in]datasetArranged as (x, y, z)
[in]xfirst dimension in increasing order
[in]ysecond dimension in increasing order
[in]zthird dimension in increasing order
[in,out]lastindexIndex for the last (x, y, z) used
[out]interpdataThe interpolated value of Dataset(:,:,:) at InCoord

◆ interpstpreal4()

real(siki) function nwtc_num::interpstpreal4 ( real(siki), intent(in)  XVal,
real(siki), dimension (arylen), intent(in)  XAry,
real(siki), dimension (arylen), intent(in)  YAry,
integer, intent(inout)  Ind,
integer, intent(in)  AryLen 
)

This funtion returns a y-value that corresponds to an input x-value by interpolating into the arrays.

It uses the passed index as the starting point and does a stepwise interpolation from there. This is especially useful when the calling routines save the value from the last time this routine was called for a given case where XVal does not change much from call to call. When there is no correlation from one interpolation to another, InterpBin() (nwtc_num::interpbin) may be a better choice. It returns the first or last YAry() value if XVal is outside the limits of XAry().

Use InterpStp (nwtc_num::interpstp) instead of directly calling a specific routine in the generic interface.

Parameters
[in]arylenLength of the arrays.
[in,out]indInitial and final index into the arrays.
[in]xaryArray of X values to be interpolated.
[in]xvalX value to be interpolated.
[in]yaryArray of Y values to be interpolated.
Returns
The interpolated value of Y at XVal

◆ interpstpreal4_8()

real(r8ki) function nwtc_num::interpstpreal4_8 ( real(siki), intent(in)  XVal,
real(siki), dimension (arylen), intent(in)  XAry,
real(r8ki), dimension (arylen), intent(in)  YAry,
integer, intent(inout)  Ind,
integer, intent(in)  AryLen 
)

This funtion returns a y-value that corresponds to an input x-value by interpolating into the arrays.

It uses the passed index as the starting point and does a stepwise interpolation from there. This is especially useful when the calling routines save the value from the last time this routine was called for a given case where XVal does not change much from call to call. When there is no correlation from one interpolation to another, InterpBin() (nwtc_num::interpbin) may be a better choice. It returns the first or last YAry() value if XVal is outside the limits of XAry().

Use InterpStp (nwtc_num::interpstp) instead of directly calling a specific routine in the generic interface.

Parameters
[in]arylenLength of the arrays.
[in,out]indInitial and final index into the arrays.
[in]xaryArray of X values to be interpolated.
[in]xvalX value to be interpolated.
[in]yaryArray of Y values to be interpolated.
Returns
The interpolated value of Y at XVal

◆ interpstpreal8()

real(r8ki) function nwtc_num::interpstpreal8 ( real(r8ki), intent(in)  XVal,
real(r8ki), dimension (arylen), intent(in)  XAry,
real(r8ki), dimension (arylen), intent(in)  YAry,
integer, intent(inout)  Ind,
integer, intent(in)  AryLen 
)

This funtion returns a y-value that corresponds to an input x-value by interpolating into the arrays.

It uses the passed index as the starting point and does a stepwise interpolation from there. This is especially useful when the calling routines save the value from the last time this routine was called for a given case where XVal does not change much from call to call. When there is no correlation from one interpolation to another, InterpBin() (nwtc_num::interpbin) may be a better choice. It returns the first or last YAry() value if XVal is outside the limits of XAry().

Use InterpStp (nwtc_num::interpstp) instead of directly calling a specific routine in the generic interface.

Parameters
[in]arylenLength of the arrays.
[in,out]indInitial and final index into the arrays.
[in]xaryArray of X values to be interpolated.
[in]xvalX value to be interpolated.
[in]yaryArray of Y values to be interpolated.
Returns
The interpolated value of Y at XVal

◆ interpwrappedstpreal16()

real(quki) function nwtc_num::interpwrappedstpreal16 ( real(quki), intent(in)  XValIn,
real(quki), dimension (arylen), intent(in)  XAry,
real(quki), dimension (arylen), intent(in)  YAry,
integer, intent(inout)  Ind,
integer, intent(in)  AryLen 
)

This funtion returns a y-value that corresponds to an input x-value which is wrapped back into the range [0-XAry(AryLen)] by interpolating into the arrays.

It is assumed that XAry is sorted in ascending order. It uses the passed index as the starting point and does a stepwise interpolation from there. This is especially useful when the calling routines save the value from the last time this routine was called for a given case where XVal does not change much from call to call. When there is no correlation from one interpolation to another, InterpBin() may be a better choice. It returns the first or last YAry() value if XVal is outside the limits of XAry().

Use InterpWrappedStpReal (nwtc_num::interpwrappedstpreal) instead of directly calling a specific routine in the generic interface.

Returns
The interpolated value of Y at XVal
Parameters
[in]arylenLength of the arrays.
[in,out]indInitial and final index into the arrays.
[in]xaryArray of X values to be interpolated.
[in]xvalinX value to be interpolated.
[in]yaryArray of Y values to be interpolated.
Returns
The interpolated value of Y at XVal
Parameters
[in]arylenLength of the arrays.

◆ interpwrappedstpreal4()

real(siki) function nwtc_num::interpwrappedstpreal4 ( real(siki), intent(in)  XValIn,
real(siki), dimension (arylen), intent(in)  XAry,
real(siki), dimension (arylen), intent(in)  YAry,
integer, intent(inout)  Ind,
integer, intent(in)  AryLen 
)

This funtion returns a y-value that corresponds to an input x-value which is wrapped back into the range [0-XAry(AryLen)] by interpolating into the arrays.

It is assumed that XAry is sorted in ascending order. It uses the passed index as the starting point and does a stepwise interpolation from there. This is especially useful when the calling routines save the value from the last time this routine was called for a given case where XVal does not change much from call to call. When there is no correlation from one interpolation to another, InterpBin() may be a better choice. It returns the first or last YAry() value if XVal is outside the limits of XAry().

Use InterpWrappedStpReal (nwtc_num::interpwrappedstpreal) instead of directly calling a specific routine in the generic interface.

Returns
The interpolated value of Y at XVal
Parameters
[in]arylenLength of the arrays.
[in,out]indInitial and final index into the arrays.
[in]xaryArray of X values to be interpolated.
[in]xvalinX value to be interpolated.
[in]yaryArray of Y values to be interpolated.

◆ interpwrappedstpreal4_8()

real(r8ki) function nwtc_num::interpwrappedstpreal4_8 ( real(siki), intent(in)  XValIn,
real(siki), dimension (arylen), intent(in)  XAry,
real(r8ki), dimension (arylen), intent(in)  YAry,
integer, intent(inout)  Ind,
integer, intent(in)  AryLen 
)

This funtion returns a y-value that corresponds to an input x-value which is wrapped back into the range [0-XAry(AryLen)] by interpolating into the arrays.

It is assumed that XAry is sorted in ascending order. It uses the passed index as the starting point and does a stepwise interpolation from there. This is especially useful when the calling routines save the value from the last time this routine was called for a given case where XVal does not change much from call to call. When there is no correlation from one interpolation to another, InterpBin() may be a better choice. It returns the first or last YAry() value if XVal is outside the limits of XAry().

Use InterpWrappedStpReal (nwtc_num::interpwrappedstpreal) instead of directly calling a specific routine in the generic interface.

Returns
The interpolated value of Y at XVal
Parameters
[in]arylenLength of the arrays.
[in,out]indInitial and final index into the arrays.
[in]xaryArray of X values to be interpolated.
[in]xvalinX value to be interpolated.
[in]yaryArray of Y values to be interpolated.
Returns
The interpolated value of Y at XVal

◆ interpwrappedstpreal8()

real(r8ki) function nwtc_num::interpwrappedstpreal8 ( real(r8ki), intent(in)  XValIn,
real(r8ki), dimension (arylen), intent(in)  XAry,
real(r8ki), dimension (arylen), intent(in)  YAry,
integer, intent(inout)  Ind,
integer, intent(in)  AryLen 
)

This funtion returns a y-value that corresponds to an input x-value which is wrapped back into the range [0-XAry(AryLen)] by interpolating into the arrays.

It is assumed that XAry is sorted in ascending order. It uses the passed index as the starting point and does a stepwise interpolation from there. This is especially useful when the calling routines save the value from the last time this routine was called for a given case where XVal does not change much from call to call. When there is no correlation from one interpolation to another, InterpBin() may be a better choice. It returns the first or last YAry() value if XVal is outside the limits of XAry().

Use InterpWrappedStpReal (nwtc_num::interpwrappedstpreal) instead of directly calling a specific routine in the generic interface.

Returns
The interpolated value of Y at XVal
Parameters
[in]arylenLength of the arrays.
[in,out]indInitial and final index into the arrays.
[in]xaryArray of X values to be interpolated.
[in]xvalinX value to be interpolated.
[in]yaryArray of Y values to be interpolated.
Returns
The interpolated value of Y at XVal

◆ isoparametriccoords()

subroutine nwtc_num::isoparametriccoords ( real(reki), dimension(:), intent(in)  InCoord,
real(reki), dimension(:), intent(in)  posLo,
real(reki), dimension(:), intent(in)  posHi,
real(reki), dimension(:), intent(out)  isopc 
)

This subroutine calculates the iosparametric coordinates, isopc, which is a value between -1 and 1 (for each dimension of a dataset), indicating where InCoord falls between posLo and posHi.

It is used in InterpStpReal2D (nwtcnum::interpstpreal2d) and InterpStpReal3D (nwtcnum::interpstpreal3d).

Parameters
[in]incoordCoordinate values we're interpolating to; (size = number of interpolation dimensions)
[in]poslocoordinate values associated with Indx_Lo; (size = number of interpolation dimensions)
[in]poshicoordinate values associated with Indx_Hi; (size = number of interpolation dimensions)
[out]isopcisoparametric coordinates; (position within the box)

◆ issymmetric()

logical function nwtc_num::issymmetric ( real(reki), dimension(:,:), intent(in)  A)

This function returns a logical TRUE/FALSE value that indicates if the given (2-dimensional) matrix, A, is symmetric.

If A is not square it returns FALSE.

Parameters
[in]aa real matrix A, whose symmetry is questioned
Returns
true if A is symmetric, false if not

◆ kernelsmoothing()

subroutine nwtc_num::kernelsmoothing ( real(reki), dimension(:), intent(in)  x,
real(reki), dimension(x), intent(in)  f,
integer, intent(in)  kernelType,
real(reki), intent(in)  radius,
real(reki), dimension(:), intent(out)  fNew 
)

KERNELSMOOTHING Kernel smoothing of vector data.

fNew = kernelSmoothing( x, f, KERNELTYPE, RADIUS ) generates a smoothed version of the data f(x) in fNew. Supported KERNELTYPE values are 'EPANECHINIKOV', 'QUARTIC' or 'BIWEIGHT', 'TRIWEIGHT', 'TRICUBE' and 'GAUSSIAN'. RADIUS controls the width of the kernel relative to the vector x.

See also: https://en.wikipedia.org/wiki/Kernel_(statistics)#Kernel_functions_in_common_use

◆ locatebin()

subroutine nwtc_num::locatebin ( real(reki), intent(in)  XVal,
real(reki), dimension (arylen), intent(in)  XAry,
integer, intent(out)  Ind,
integer, intent(in)  AryLen 
)

This subroutine finds the lower-bound index of an input x-value located in an array.

On return, Ind has a value such that XAry(Ind) <= XVal < XAry(Ind+1), with the exceptions that Ind = 0 when XVal < XAry(1), and Ind = AryLen when XAry(AryLen) <= XVal.

It uses a binary interpolation scheme that takes about log(AryLen)/log(2) steps to converge. If the index doesn't change much between calls, LocateStp() (nwtc_num::locatestp) may be a better option.

Parameters
[in]arylenLength of the array.
[out]indFinal (low) index into the array.
[in]xaryArray of X values to be interpolated.
[in]xvalX value to be interpolated.

◆ locatestpr16()

subroutine nwtc_num::locatestpr16 ( real(quki), intent(in)  XVal,
real(quki), dimension (arylen), intent(in)  XAry,
integer, intent(inout)  Ind,
integer, intent(in)  AryLen 
)

This subroutine finds the lower-bound index of an input x-value located in an array.

On return, Ind has a value such that XAry(Ind) <= XVal < XAry(Ind+1), with the exceptions that Ind = 0 when XVal < XAry(1), and Ind = AryLen when XAry(AryLen) <= XVal.

It uses the passed index as the starting point and does a stepwise search from there. This is especially useful when the calling routines save the value from the last time this routine was called for a given case where XVal does not change much from call to call. When there is no correlation from one interpolation to another, a binary search may be a better choice (see nwtc_num::locatebin).

Use LocateStp (nwtc_num::locatestp) instead of directly calling a specific routine in the generic interface.

Parameters
[in]arylenLength of the array.
[in,out]indInitial and final index into the array.
[in]xaryArray of X values to be interpolated.
[in]xvalX value to be interpolated.

◆ locatestpr4()

subroutine nwtc_num::locatestpr4 ( real(siki), intent(in)  XVal,
real(siki), dimension (arylen), intent(in)  XAry,
integer, intent(inout)  Ind,
integer, intent(in)  AryLen 
)

This subroutine finds the lower-bound index of an input x-value located in an array.

On return, Ind has a value such that XAry(Ind) <= XVal < XAry(Ind+1), with the exceptions that Ind = 0 when XVal < XAry(1), and Ind = AryLen when XAry(AryLen) <= XVal.

It uses the passed index as the starting point and does a stepwise search from there. This is especially useful when the calling routines save the value from the last time this routine was called for a given case where XVal does not change much from call to call. When there is no correlation from one interpolation to another, a binary search may be a better choice (see nwtc_num::locatebin).

Use LocateStp (nwtc_num::locatestp) instead of directly calling a specific routine in the generic interface.

Parameters
[in]arylenLength of the array.
[in,out]indInitial and final index into the array.
[in]xaryArray of X values to be interpolated.
[in]xvalX value to be interpolated.

◆ locatestpr8()

subroutine nwtc_num::locatestpr8 ( real(r8ki), intent(in)  XVal,
real(r8ki), dimension (arylen), intent(in)  XAry,
integer, intent(inout)  Ind,
integer, intent(in)  AryLen 
)

This subroutine finds the lower-bound index of an input x-value located in an array.

On return, Ind has a value such that XAry(Ind) <= XVal < XAry(Ind+1), with the exceptions that Ind = 0 when XVal < XAry(1), and Ind = AryLen when XAry(AryLen) <= XVal.

It uses the passed index as the starting point and does a stepwise search from there. This is especially useful when the calling routines save the value from the last time this routine was called for a given case where XVal does not change much from call to call. When there is no correlation from one interpolation to another, a binary search may be a better choice (see nwtc_num::locatebin).

Use LocateStp (nwtc_num::locatestp) instead of directly calling a specific routine in the generic interface.

Parameters
[in]arylenLength of the array.
[in,out]indInitial and final index into the array.
[in]xaryArray of X values to be interpolated.
[in]xvalX value to be interpolated.

◆ mean()

real(reki) function nwtc_num::mean ( real(reki), dimension (arylen), intent(in)  Ary,
integer, intent(in)  AryLen 
)

This routine calculates the mean value of an array.

Parameters
[in]arylenLength of the array.
[in]aryInput array.

◆ mpi2pi_r16()

subroutine nwtc_num::mpi2pi_r16 ( real(quki), intent(inout)  Angle)

This routine is used to convert Angle to an equivalent value between \(-\pi\) and \(pi\).

Use MPi2Pi (nwtc_num::mpi2pi) instead of directly calling a specific routine in the generic interface.

Parameters
[in,out]angleAngle (in radians) to be converted

◆ mpi2pi_r4()

subroutine nwtc_num::mpi2pi_r4 ( real(siki), intent(inout)  Angle)

This routine is used to convert Angle to an equivalent value between \(-\pi\) and \(pi\).

Use MPi2Pi (nwtc_num::mpi2pi) instead of directly calling a specific routine in the generic interface.

Parameters
[in,out]angleAngle (in radians) to be converted

◆ mpi2pi_r8()

subroutine nwtc_num::mpi2pi_r8 ( real(r8ki), intent(inout)  Angle)

This routine is used to convert Angle to an equivalent value between \(-\pi\) and \(pi\).

Use MPi2Pi (nwtc_num::mpi2pi) instead of directly calling a specific routine in the generic interface.

Parameters
[in,out]angleAngle (in radians) to be converted

◆ outerproductr16()

real(quki) function, dimension(size(u),size(v)) nwtc_num::outerproductr16 ( real(quki), dimension(:), intent(in)  u,
real(quki), dimension(:), intent(in)  v 
)

This routine calculates the outer product of two vectors, \(u = \left(u_1, u_2, \ldots, u_m\right)\) and \(v = \left(v_1, v_2, \ldots ,v_n\right)\).

The outer product is defined as

\begin{equation} A = u \otimes v = \begin{bmatrix} u_1 v_1 & u_1 v_2 & \dots & u_1 v_n \\ u_2 v_1 & u_2 v_2 & \dots & u_2 v_n \\ \vdots & \vdots & \ddots & \vdots \\ u_m v_1 & u_m v_2 & \dots & u_m v_n \end{bmatrix} \end{equation}

Use OuterProduct (nwtc_num::outerproduct) instead of directly calling a specific routine in the generic interface.

Parameters
[in]ufirst vector, \(u\), in the outer product
[in]vsecond vector, \(v\), in the outer product
Returns
the resultant matrix, A

◆ outerproductr4()

real(siki) function, dimension(size(u),size(v)) nwtc_num::outerproductr4 ( real(siki), dimension(:), intent(in)  u,
real(siki), dimension(:), intent(in)  v 
)

This routine calculates the outer product of two vectors, \(u = \left(u_1, u_2, \ldots, u_m\right)\) and \(v = \left(v_1, v_2, \ldots ,v_n\right)\).

The outer product is defined as

\begin{equation} A = u \otimes v = \begin{bmatrix} u_1 v_1 & u_1 v_2 & \dots & u_1 v_n \\ u_2 v_1 & u_2 v_2 & \dots & u_2 v_n \\ \vdots & \vdots & \ddots & \vdots \\ u_m v_1 & u_m v_2 & \dots & u_m v_n \end{bmatrix} \end{equation}

Use OuterProduct (nwtc_num::outerproduct) instead of directly calling a specific routine in the generic interface.

Parameters
[in]ufirst vector, \(u\), in the outer product
[in]vsecond vector, \(v\), in the outer product
Returns
the resultant matrix, A

◆ outerproductr8()

real(r8ki) function, dimension(size(u),size(v)) nwtc_num::outerproductr8 ( real(r8ki), dimension(:), intent(in)  u,
real(r8ki), dimension(:), intent(in)  v 
)

This routine calculates the outer product of two vectors, \(u = \left(u_1, u_2, \ldots, u_m\right)\) and \(v = \left(v_1, v_2, \ldots ,v_n\right)\).

The outer product is defined as

\begin{equation} A = u \otimes v = \begin{bmatrix} u_1 v_1 & u_1 v_2 & \dots & u_1 v_n \\ u_2 v_1 & u_2 v_2 & \dots & u_2 v_n \\ \vdots & \vdots & \ddots & \vdots \\ u_m v_1 & u_m v_2 & \dots & u_m v_n \end{bmatrix} \end{equation}

Use OuterProduct (nwtc_num::outerproduct) instead of directly calling a specific routine in the generic interface.

Parameters
[in]ufirst vector, \(u\), in the outer product
[in]vsecond vector, \(v\), in the outer product
Returns
the resultant matrix, A

◆ perturborientationmatrix()

subroutine nwtc_num::perturborientationmatrix ( real(r8ki), dimension(3,3), intent(inout)  Orientation,
real(r8ki), intent(in), optional  Perturbation,
integer, intent(in), optional  AngleDim,
real(r8ki), dimension(3), intent(in), optional  Perturbations,
logical, intent(in), optional  UseSmlAngle 
)

This subroutine perturbs an orientation matrix by a small angle.

Two methods are used: small angle DCM: perturb small angles extracted from DCM large angle DCM: multiply input DCM with DCM created with small angle perturbations NOTE1: this routine originally used logarithmic mapping for small angle perturbations NOTE2: all warnings from SmllRotTrans are ignored. NOTE3: notice no checks are made to verify correct set of inputs given one of the follwing combinations must be provided (others truly optional): Perturbations Perturbation + AngleDim

◆ psf()

integer function nwtc_num::psf ( integer, intent(in)  Npsf,
integer, intent(in)  NumPrimes,
logical, intent(in), optional  subtract 
)

This routine factors the number N into its primes.

If any of those prime factors is greater than the NumPrimes'th prime, a value of 1 is added to N and the new number is factored. This process is repeated until no prime factors are greater than the NumPrimes'th prime.

If subract is .true., we will subtract 1 from the value of N instead of adding it.

Parameters
[in]npsfInitial number we're trying to factor.
[in]numprimesNumber of unique primes.
Returns
The smallest number at least as large as Npsf, that is the product of small factors when we return. IF subtract is present and .TRUE., PSF is the largest number not greater than Npsf that is a product of small factors.
Parameters
[in]subtractif PRESENT and .TRUE., we will subtract instead of add 1 to the number when looking for the value of PSF to return.

◆ quaternion_conjugate()

type(quaternion) function nwtc_num::quaternion_conjugate ( type(quaternion), intent(in)  q)

This function computes the conjugate of a quaternion, q.

Parameters
[in]qquaternion
Returns
conjugate of the quaternion

◆ quaternion_interp()

type(quaternion) function nwtc_num::quaternion_interp ( type(quaternion), intent(in)  q1,
type(quaternion), intent(in)  q2,
real(reki), intent(in)  s 
)

This function computes the interpolated quaternion at time t1 + s*(t2-t1) and s is in [0,1].

Parameters
[in]q1quaternion at t1
[in]q2quaternion at t2
[in]sfraction of distance between t1 and t2: s must be in [0,1]
Returns
interpolated quaternion at s

◆ quaternion_norm()

real(reki) function nwtc_num::quaternion_norm ( type(quaternion), intent(in)  q)

This function computes the 2-norm of a quaternion, q.

Parameters
[in]qquaternion
Returns
2-norm of q

◆ quaternion_power()

type(quaternion) function nwtc_num::quaternion_power ( type(quaternion), intent(in)  q,
real(reki), intent(in)  alpha 
)

This function computes the quaternion, q, raised to an arbitrary real exponent, alpha.

Parameters
[in]qquaternion
[in]alphaexponent
Returns
q^alpha

◆ quaternion_product()

type(quaternion) function nwtc_num::quaternion_product ( type(quaternion), intent(in)  p,
type(quaternion), intent(in)  q 
)

This function computes the product of two quaternions, p and q.

Parameters
[in]pquaternion
[in]qquaternion
Returns
quaternion product, p*q

◆ quaternion_to_dcm()

real(reki) function, dimension (3,3) nwtc_num::quaternion_to_dcm ( type(quaternion), intent(in)  q)

This function converts a quaternion to an equivalent direction cosine matrix.

Parameters
[in]qquaternion

◆ rad2m180to180deg()

real(reki) function nwtc_num::rad2m180to180deg ( real(reki), intent(in)  Angle)

This function takes an angle in radians and converts it to an angle in degrees in the range [-180,180].

Parameters
[in]angleinput angle, radians

◆ regcubicsplineinit()

subroutine nwtc_num::regcubicsplineinit ( integer, intent(in)  AryLen,
real(reki), dimension (arylen), intent(in)  XAry,
real(reki), dimension (arylen), intent(in)  YAry,
real(reki), intent(out)  DelX,
real(reki), dimension (arylen-1,0:3), intent(out)  Coef,
integer(intki), intent(out)  ErrStat,
character(*), intent(out)  ErrMsg 
)

This routine calculates the parameters needed to compute a regularly-spaced natural cubic spline.

Natural cubic splines are used in that the curvature at the end points is zero. It assumes the XAry values are equally spaced for speed. If you have multiple curves that share the same value, use RegCubicSplineInitM (nwtc_num::regcubicsplineinitm) instead of calling this routine multiple times.

Parameters
[in]arylenLength of the array.
[out]coefThe coefficients for the cubic polynomials.
[out]delxThe distance between the equally spaced points.
[in]xaryInput array of x values.
[in]yaryInput array of y values.
[out]errstatError status.
[out]errmsgError message.

◆ regcubicsplineinitm()

subroutine nwtc_num::regcubicsplineinitm ( real(reki), dimension (:), intent(in)  XAry,
real(reki), dimension (:,:), intent(in)  YAry,
real(reki), intent(out)  DelX,
real(reki), dimension (:,:,0:), intent(out)  Coef,
integer(intki), intent(out)  ErrStat,
character(*), intent(out)  ErrMsg 
)

This routine calculates the parameters needed to compute a regularly-spaced natural cubic spline.

Natural cubic splines are used in that the curvature at the end points is zero. It assumes the XAry values are equally spaced for speed. This version of the routine works with multiple curves that share the same X values.

◆ regcubicsplineinterp()

real(reki) function nwtc_num::regcubicsplineinterp ( real(reki), intent(in)  X,
integer, intent(in)  AryLen,
real(reki), dimension (arylen), intent(in)  XAry,
real(reki), dimension (arylen), intent(in)  YAry,
real(reki), intent(in)  DelX,
real(reki), dimension (arylen-1,0:3), intent(in)  Coef,
integer(intki), intent(out)  ErrStat,
character(*), intent(out)  ErrMsg 
)

This routine interpolates a pair of arrays using cubic splines to find the function value at X.

One must call RegCubicSplineInit() (nwtc_num::regcubicsplineinit) first to compute the coefficients of the cubics. This routine requires that the XAry be regularly spaced, which improves performance.

Returns
This function.
Parameters
[in]arylenLength of the array.
[in]coefThe coefficients for the cubic polynomials.
[in]delxThe distance between X values in XAry.
[in]xThe value we are trying to interpolate for.
[in]xaryInput array of regularly spaced x values.
[in]yaryInput array of y values.
[out]errstatError status.
[out]errmsgError message.

◆ regcubicsplineinterpm()

real(reki) function, dimension(:), allocatable nwtc_num::regcubicsplineinterpm ( real(reki), intent(in)  X,
real(reki), dimension (:), intent(in)  XAry,
real(reki), dimension (:,:), intent(in)  YAry,
real(reki), intent(in)  DelX,
real(reki), dimension (:,:,0:), intent(in)  Coef,
integer(intki), intent(out)  ErrStat,
character(*), intent(out)  ErrMsg 
)

This routine interpolates a pair of arrays using cubic splines to find the function value at X.

One must call RegCubicSplineInitM() (nwtc_num::regcubicsplineinitm) first to compute the coefficients of the cubics. This routine requires that the XAry be regularly spaced, which improves performance. This version of the routine works with multiple curves that share the same X values.

Returns
The result of this function.
Parameters
[in]coefThe coefficients for the cubic polynomials.
[in]delxThe distance between X values in XAry.
[in]xThe value we are trying to interpolate for.
[in]xaryInput array of regularly spaced x values.
[in]yaryInput array of y values.
[out]errstatError status.
[out]errmsgError message.

◆ rombergint()

subroutine nwtc_num::rombergint ( real(reki), external  f,
real(reki), intent(in)  a,
real(reki), intent(in)  b,
real(reki), intent(out)  R,
real(reki), intent(out)  err,
real(reki), intent(in)  eps,
integer, intent(out), optional  ErrStat 
)

This routine is used to integrate funciton f over the interval [a, b].

This routine is useful for sufficiently smooth (e.g., analytic) integrands, integrated over intervals which contain no singularities, and where the endpoints are also nonsingular.

f is an external function. For example f(x) = 1 + x.

FUNCTION f(x) USE PRECISION IMPLICIT NONE

REAL(ReKi) f REAL(ReKi) x

f = 1 + x

RETURN END FUNCTION f

Parameters
fIntegrand function name
[in]aLower integration limit
[in]bUpper integration limit
[in]epsAbsolute error bound
[out]rThe result of integration
[out]errActual absolute error
[out]errstatError status; if present, program does not abort on error

◆ runtimes()

subroutine nwtc_num::runtimes ( integer, dimension (8), intent(in)  StrtTime,
real(reki), intent(in)  UsrTime1,
integer, dimension (8), intent(in)  SimStrtTime,
real(reki), intent(in)  UsrTime2,
real(dbki), intent(in)  ZTime,
integer(intki), intent(in), optional  UnSum,
real(reki), intent(out), optional  UsrTime_out,
character(*), intent(in), optional  DescStrIn 
)

This routine displays a message that gives that status of the simulation and the predicted end time of day.

It is intended to be used with SimStatus (nwtc_num::simstatus) and SimStatus_FirstTime (nwtc_num::simstatus_firsttime).

Parameters
[in]strttimeStart time of simulation (including initialization)
[in]simstrttimeStart time of simulation (after initialization)
[in]usrtime1User CPU time for simulation initialization.
[in]usrtime2User CPU time for simulation (without intialization)
[in]ztimeThe final simulation time (not necessarially TMax)
[in]unsumoptional unit number of file. If present and > 0,
[out]usrtime_outUser CPU time for entire run - optional value returned to calling routine
[in]descstrinoptional additional string to print for SimStatus

◆ simstatus()

subroutine nwtc_num::simstatus ( real(dbki), intent(inout)  PrevSimTime,
real(reki), intent(inout)  PrevClockTime,
real(dbki), intent(in)  ZTime,
real(dbki), intent(in)  TMax,
character(*), intent(in), optional  DescStrIn,
character(*), intent(in), optional  StatInfoIn 
)

This routine displays a message that gives that status of the simulation and the predicted end time of day.

It is intended to be used with RunTimes (nwtc_num::runtimes) and SimStatus_FirstTime (nwtc_num::simstatus_firsttime).

Parameters
[in]ztimeCurrent simulation time (s)
[in]tmaxExpected simulation time (s)
[in,out]prevsimtimePrevious time message was written to screen (s > 0)
[in,out]prevclocktimePrevious clock time in seconds past midnight
[in]descstrinoptional additional string to print at start of SimStatus
[in]statinfoinoptional additional string to print at end of SimStatus

◆ simstatus_firsttime()

subroutine nwtc_num::simstatus_firsttime ( real(dbki), intent(out)  PrevSimTime,
real(reki), intent(out)  PrevClockTime,
integer, dimension (8), intent(out)  SimStrtTime,
real(reki), intent(out)  UsrTimeSim,
real(dbki), intent(in)  ZTime,
real(dbki), intent(in)  TMax,
character(*), intent(in), optional  DescStrIn 
)

This routine displays a message that gives that status of the simulation.

It is intended to be used with RunTimes (nwtc_num::runtimes) and SimStatus (nwtc_num::simstatus).

Parameters
[in]ztimeCurrent simulation time (s)
[in]tmaxExpected simulation time (s)
[out]prevsimtimePrevious time message was written to screen (s > 0)
[out]prevclocktimePrevious clock time in seconds past midnight
[out]simstrttimeAn array containing the elements of the start time.
[out]usrtimesimUser CPU time for simulation (without intialization)
[in]descstrinoptional additional string to print for SimStatus

◆ skewsymmatr16()

real(quki) function, dimension(3,3) nwtc_num::skewsymmatr16 ( real(quki), dimension(3), intent(in)  x)

This function returns the 3x3 skew-symmetric matrix for cross-product calculation of vector \(\vec{x}\) via matrix multiplication, defined as

\begin{equation} f_{_\times}\left( \vec{x} \right) = \begin{bmatrix} 0 & -x_3 & x_2 \\ x_3 & 0 & -x_1 \\ -x_2 & x_1 & 0 \end{bmatrix} \end{equation}

Use SkewSymMat (nwtc_num::skewsymmat) instead of directly calling a specific routine in the generic interface.

Returns
skew-symmetric matrix formed from input vector \(x\)
Parameters
[in]xinput vector \(x\)

◆ skewsymmatr4()

real(siki) function, dimension(3,3) nwtc_num::skewsymmatr4 ( real(siki), dimension(3), intent(in)  x)

This function returns the 3x3 skew-symmetric matrix for cross-product calculation of vector \(\vec{x}\) via matrix multiplication, defined as

\begin{equation} f_{_\times}\left( \vec{x} \right) = \begin{bmatrix} 0 & -x_3 & x_2 \\ x_3 & 0 & -x_1 \\ -x_2 & x_1 & 0 \end{bmatrix} \end{equation}

Use SkewSymMat (nwtc_num::skewsymmat) instead of directly calling a specific routine in the generic interface.

Returns
skew-symmetric matrix formed from input vector \(x\)
Parameters
[in]xinput vector \(x\)

◆ skewsymmatr8()

real(r8ki) function, dimension(3,3) nwtc_num::skewsymmatr8 ( real(r8ki), dimension(3), intent(in)  x)

This function returns the 3x3 skew-symmetric matrix for cross-product calculation of vector \(\vec{x}\) via matrix multiplication, defined as

\begin{equation} f_{_\times}\left( \vec{x} \right) = \begin{bmatrix} 0 & -x_3 & x_2 \\ x_3 & 0 & -x_1 \\ -x_2 & x_1 & 0 \end{bmatrix} \end{equation}

Use SkewSymMat (nwtc_num::skewsymmat) instead of directly calling a specific routine in the generic interface.

Returns
skew-symmetric matrix formed from input vector \(x\)
Parameters
[in]xinput vector \(x\)

◆ smllrottransd()

subroutine nwtc_num::smllrottransd ( character(*), intent(in)  RotationType,
real(reki), intent(in)  Theta1,
real(reki), intent(in)  Theta2,
real(reki), intent(in)  Theta3,
real(dbki), dimension (3,3), intent(out)  TransMat,
character(*), intent(in), optional  ErrTxt,
integer(intki), intent(out)  ErrStat,
character(*), intent(out)  ErrMsg 
)

This routine computes the 3x3 transformation matrix, \(TransMat\), to a coordinate system \(x\) (with orthogonal axes \(x_1, x_2, x_3\)) resulting from three rotations ( \(\theta_1\), \(\theta_2\), \(\theta_3\)) about the orthogonal axes ( \(X_1, X_2, X_3\)) of coordinate system \(X\).

All angles are assummed to be small, as such, the order of rotations does not matter and Euler angles do not need to be used. This routine is used to compute the transformation matrix ( \(TransMat\)) between undeflected ( \(X\)) and deflected ( \(x\)) coordinate systems. In matrix form:

\begin{equation} \left\{ \begin{matrix} x_1 \\ x_2 \\ x_3 \end{matrix} \right\} = \left[ TransMat(\theta_1, \theta_2, \theta_3) \right] \left\{ \begin{matrix} X_1 \\ X_2 \\ X_3 \end{matrix} \right\} \end{equation}

The transformation matrix, \(TransMat\), is the closest orthonormal matrix to the nonorthonormal, but skew-symmetric, Bernoulli-Euler matrix:

\begin{equation} A = \begin{bmatrix} 1 & \theta_3 & -\theta_2 \\ -\theta_3 & 1 & \theta_1 \\ \theta_2 & -\theta_1 & 1 \end{bmatrix} \end{equation}

In the Frobenius Norm sense, the closest orthornormal matrix is: \(TransMat = U V^T\), where the columns of \(U\) contain the eigenvectors of \( AA^T\) and the columns of \(V\) contain the eigenvectors of \(A^TA\) (note that \(^T\) = transpose). This result comes directly from the Singular Value Decomposition (SVD) of \(A = USV^T\) where \(S\) is a diagonal matrix containing the singular values of \(A\), which are sqrt( eigenvalues of \(AA^T\) ) = sqrt( eigenvalues of \(A^TA\) ).

The algebraic form of the transformation matrix, as implemented below, was derived symbolically by J. Jonkman by computing \(UV^T\) by hand with verification in Mathematica.

This routine is the inverse of GetSmllRotAngs (nwtc_num::getsmllrotangs).
Use SmllRotTrans (nwtc_num::smllrottrans) instead of directly calling a specific routine in the generic interface.

Parameters
[in]theta1\(\theta_1\): the small rotation about \(X_1\), (rad).
[in]theta2\(\theta_2\): the small rotation about \(X_2\), (rad).
[in]theta3\(\theta_3\): the small rotation about \(X_3\), (rad).
[out]transmatThe resulting transformation matrix from \(X\) to \(x\), (-).
[out]errstatError status
[out]errmsgError message corresponding to ErrStat
[in]rotationtypeThe type of rotation; used to inform the user where a large rotation is occuring upon such an event.
[in]errtxtan additional message to be displayed as a warning (typically the simulation time)

◆ smllrottransdd()

subroutine nwtc_num::smllrottransdd ( character(*), intent(in)  RotationType,
real(dbki), intent(in)  Theta1,
real(dbki), intent(in)  Theta2,
real(dbki), intent(in)  Theta3,
real(dbki), dimension (3,3), intent(out)  TransMat,
character(*), intent(in), optional  ErrTxt,
integer(intki), intent(out)  ErrStat,
character(*), intent(out)  ErrMsg 
)

This routine computes the 3x3 transformation matrix, \(TransMat\), to a coordinate system \(x\) (with orthogonal axes \(x_1, x_2, x_3\)) resulting from three rotations ( \(\theta_1\), \(\theta_2\), \(\theta_3\)) about the orthogonal axes ( \(X_1, X_2, X_3\)) of coordinate system \(X\).

All angles are assummed to be small, as such, the order of rotations does not matter and Euler angles do not need to be used. This routine is used to compute the transformation matrix ( \(TransMat\)) between undeflected ( \(X\)) and deflected ( \(x\)) coordinate systems. In matrix form:

\begin{equation} \left\{ \begin{matrix} x_1 \\ x_2 \\ x_3 \end{matrix} \right\} = \left[ TransMat(\theta_1, \theta_2, \theta_3) \right] \left\{ \begin{matrix} X_1 \\ X_2 \\ X_3 \end{matrix} \right\} \end{equation}

The transformation matrix, \(TransMat\), is the closest orthonormal matrix to the nonorthonormal, but skew-symmetric, Bernoulli-Euler matrix:

\begin{equation} A = \begin{bmatrix} 1 & \theta_3 & -\theta_2 \\ -\theta_3 & 1 & \theta_1 \\ \theta_2 & -\theta_1 & 1 \end{bmatrix} \end{equation}

In the Frobenius Norm sense, the closest orthornormal matrix is: \(TransMat = U V^T\), where the columns of \(U\) contain the eigenvectors of \( AA^T\) and the columns of \(V\) contain the eigenvectors of \(A^TA\) (note that \(^T\) = transpose). This result comes directly from the Singular Value Decomposition (SVD) of \(A = USV^T\) where \(S\) is a diagonal matrix containing the singular values of \(A\), which are sqrt( eigenvalues of \(AA^T\) ) = sqrt( eigenvalues of \(A^TA\) ).

The algebraic form of the transformation matrix, as implemented below, was derived symbolically by J. Jonkman by computing \(UV^T\) by hand with verification in Mathematica.

This routine is the inverse of GetSmllRotAngs (nwtc_num::getsmllrotangs).
Use SmllRotTrans (nwtc_num::smllrottrans) instead of directly calling a specific routine in the generic interface.

Parameters
[in]theta1\(\theta_1\): the small rotation about \(X_1\), (rad).
[in]theta2\(\theta_2\): the small rotation about \(X_2\), (rad).
[in]theta3\(\theta_3\): the small rotation about \(X_3\), (rad).
[out]transmatThe resulting transformation matrix from \(X\) to \(x\), (-).
[out]errstatError status
[out]errmsgError message corresponding to ErrStat
[in]rotationtypeThe type of rotation; used to inform the user where a large rotation is occuring upon such an event.
[in]errtxtan additional message to be displayed as a warning (typically the simulation time)
[in]theta1The small rotation about X1, (rad).
[in]theta2The small rotation about X2, (rad).
[in]theta3The small rotation about X3, (rad).
[out]transmatThe resulting transformation matrix from X to x, (-).
[out]errstatError status
[out]errmsgError message corresponding to ErrStat
[in]rotationtypeThe type of rotation; used to inform the user where a large rotation is occuring upon such an event.
[in]errtxtan additional message to be displayed as a warning (typically the simulation time)

◆ smllrottransr()

subroutine nwtc_num::smllrottransr ( character(*), intent(in)  RotationType,
real(reki), intent(in)  Theta1,
real(reki), intent(in)  Theta2,
real(reki), intent(in)  Theta3,
real(reki), dimension (3,3), intent(out)  TransMat,
character(*), intent(in), optional  ErrTxt,
integer(intki), intent(out)  ErrStat,
character(*), intent(out)  ErrMsg 
)

This routine computes the 3x3 transformation matrix, \(TransMat\), to a coordinate system \(x\) (with orthogonal axes \(x_1, x_2, x_3\)) resulting from three rotations ( \(\theta_1\), \(\theta_2\), \(\theta_3\)) about the orthogonal axes ( \(X_1, X_2, X_3\)) of coordinate system \(X\).

All angles are assummed to be small, as such, the order of rotations does not matter and Euler angles do not need to be used. This routine is used to compute the transformation matrix ( \(TransMat\)) between undeflected ( \(X\)) and deflected ( \(x\)) coordinate systems. In matrix form:

\begin{equation} \left\{ \begin{matrix} x_1 \\ x_2 \\ x_3 \end{matrix} \right\} = \left[ TransMat(\theta_1, \theta_2, \theta_3) \right] \left\{ \begin{matrix} X_1 \\ X_2 \\ X_3 \end{matrix} \right\} \end{equation}

The transformation matrix, \(TransMat\), is the closest orthonormal matrix to the nonorthonormal, but skew-symmetric, Bernoulli-Euler matrix:

\begin{equation} A = \begin{bmatrix} 1 & \theta_3 & -\theta_2 \\ -\theta_3 & 1 & \theta_1 \\ \theta_2 & -\theta_1 & 1 \end{bmatrix} \end{equation}

In the Frobenius Norm sense, the closest orthornormal matrix is: \(TransMat = U V^T\), where the columns of \(U\) contain the eigenvectors of \( AA^T\) and the columns of \(V\) contain the eigenvectors of \(A^TA\) (note that \(^T\) = transpose). This result comes directly from the Singular Value Decomposition (SVD) of \(A = USV^T\) where \(S\) is a diagonal matrix containing the singular values of \(A\), which are sqrt( eigenvalues of \(AA^T\) ) = sqrt( eigenvalues of \(A^TA\) ).

The algebraic form of the transformation matrix, as implemented below, was derived symbolically by J. Jonkman by computing \(UV^T\) by hand with verification in Mathematica.

This routine is the inverse of GetSmllRotAngs (nwtc_num::getsmllrotangs).
Use SmllRotTrans (nwtc_num::smllrottrans) instead of directly calling a specific routine in the generic interface.

Parameters
[in]theta1\(\theta_1\): the small rotation about \(X_1\), (rad).
[in]theta2\(\theta_2\): the small rotation about \(X_2\), (rad).
[in]theta3\(\theta_3\): the small rotation about \(X_3\), (rad).
[out]transmatThe resulting transformation matrix from \(X\) to \(x\), (-).
[out]errstatError status
[out]errmsgError message corresponding to ErrStat
[in]rotationtypeThe type of rotation; used to inform the user where a large rotation is occuring upon such an event.
[in]errtxtan additional message to be displayed as a warning (typically the simulation time)

◆ sortunion()

subroutine nwtc_num::sortunion ( real(reki), dimension(n1), intent(in)  Ary1,
integer, intent(in)  N1,
real(reki), dimension(n2), intent(in)  Ary2,
integer, intent(in)  N2,
real(reki), dimension(n1+n2), intent(out)  Ary,
integer, intent(out)  N 
)

This routine takes two sorted arrays and finds the sorted union of the two.

Note: If the same value is found in both arrays, only one is kept. However, if either array as multiple occurances of the same value, the largest multiple will be kept. Duplicates should be eliminated externally if this is not desirable.

Parameters
[out]nThe length of the output array.
[in]n1The length of the first input array.
[in]n2The length of the second input array.
[out]aryThe sorted union.
[in]ary1The first list of sorted real numbers.
[in]ary2The second list of sorted real numbers.

◆ stddevfn()

real(reki) function nwtc_num::stddevfn ( real(reki), dimension (arylen), intent(in)  Ary,
integer, intent(in)  AryLen,
real(reki), intent(in)  Mean,
logical, intent(in), optional  UseN 
)

This routine calculates the standard deviation of a population contained in Ary.

This can be calculated as either
\( \sqrt{ \frac{\sum_{i=1}^N \left(x_i -\bar{x}\right)^2 }{N-1} } \)
or
\( \sqrt{ \frac{\sum_{i=1}^N \left(x_i -\bar{x}\right)^2 }{N} } \) if UseN is true

Returns
This function.
Parameters
[in]arylenLength of the array.
[in]aryInput array.
[in]meanThe previously calculated mean of the array.
[in]usenUse N insted of N-1 in denomenator

◆ taitbryanyxzconstructr4()

real(siki) function, dimension(3,3) nwtc_num::taitbryanyxzconstructr4 ( real(siki), dimension(3), intent(in)  theta)
Returns
rotation matrix, M
Parameters
[in]thetathe 3 rotation angles: \(\theta_x, \theta_y, \theta_z\)

◆ taitbryanyxzextractr16()

real(quki) function, dimension(3) nwtc_num::taitbryanyxzextractr16 ( real(quki), dimension(3,3), intent(in)  M)

See nwtc_num::taitbryanyxzextractr4 for detailed explanation of algorithm.

Parameters
[in]mrotation matrix, M
Returns
the 3 rotation angles, \((\theta_y, \theta_x, \theta_z)\), corresponding to the Tait-Bryan rotation angle corresponding to cant-toe-twist

See nwtc_num::taitbryanyxzextractr4 for detailed description of how this works.

◆ taitbryanyxzextractr4()

real(siki) function, dimension(3) nwtc_num::taitbryanyxzextractr4 ( real(siki), dimension(3,3), intent(in)  M)

If M is a rotation matrix from a 1-2-3 rotation sequence about Y-X-Z, this function returns the 3 sequential angles, \(\theta_y\), \(\theta_x\), and \(\theta_z\) (in radians), that formed the matrix.

M represents a change of basis (from global to local coordinates; not a physical rotation of the body; passive rotation).

See Tait-Bryan angle \( Y_1 X_2 Z_3 \) at https://en.wikipedia.org/wiki/Euler_angles#Rotation_matrix Note that what we are using here is the passive rotation, which is the transpose of what appears in the wikipedia article.

\begin{eqnarray*} M & = & R(\theta_z) R(\theta_x) R(\theta_y) & = & R(\theta_3) R(\theta_2) R(\theta_1) \\ & = & \begin{bmatrix} \cos(\theta_z) & \sin(\theta_z) & 0 \\ -\sin(\theta_z) & \cos(\theta_z) & 0 \\ 0 & 0 & 1 \end{bmatrix} \begin{bmatrix} 1 & 0 & 0 \\ 0 & \cos(\theta_x) & \sin(\theta_x) \\ 0 & -\sin(\theta_x) & \cos(\theta_x) \end{bmatrix} \begin{bmatrix} \cos(\theta_y) & 0 & -\sin(\theta_y) \\ 0 & 1 & 0 \\ \sin(\theta_y) & 0 & \cos(\theta_y) \end{bmatrix} & = & \begin{bmatrix} C_3 & S_3 & 0 \\ -S_3 & C_3 & 0 \\ 0 & 0 & 1 \end{bmatrix} \begin{bmatrix} 1 & 0 & 0 \\ 0 & C_2 & S_2 \\ 0 & -S_2 & C_2 \end{bmatrix} \begin{bmatrix} C_1 & 0 & -S_1 \\ 0 & 1 & 0 \\ S_1 & 0 & C_1 \end{bmatrix} \\ & = & \begin{bmatrix} \cos(\theta_y) \cos(\theta_z) + \sin(\theta_y) \sin(\theta_x) \sin(\theta_z) & \cos(\theta_x) \sin(\theta_z) & \cos(\theta_y) \sin(\theta_x) \sin(\theta_z) - \sin(\theta_y) \cos(\theta_z) \\ \sin(\theta_y) \sin(\theta_x) \cos(\theta_z) - \cos(\theta_y) \sin(\theta_z) & \cos(\theta_x) \cos(\theta_z) & \cos(\theta_y) \sin(\theta_x) \cos(\theta_z) + \sin(\theta_y) \sin(\theta_z) \\ \sin(\theta_y) \cos(\theta_x) & -\sin(\theta_x) & \cos(\theta_y) \cos(\theta_x) \\ \end{bmatrix} & = & \begin{bmatrix} C_1 C_3 + S_1 S_2 S_3 & C_2 S_3 & C_1 S_2 S_3 - S_1 C_3 \\ S_1 S_2 C_3 - C_1 S_3 & C_2 C_3 & C_1 S_2 C_3 + S_1 S_3 \\ S_1 C_2 & -S_2 & C_1 C_2 \\ \end{bmatrix} \end{eqnarray*}

returned angles are in the range \(\theta_y,\theta_x, \theta_z \in \left[ \pi, -\pi \right]\)
Use TaitBryanYXZExtract (nwtc_num::taitbryanyxzextract) instead of directly calling a specific routine in the generic interface.

Parameters
[in]mrotation matrix, M
Returns
the 3 rotation angles, \((\theta_y, \theta_x, \theta_z)\), corresponding to the Tait-Bryan rotation angle corresponding to cant-toe-twist

Algorithm

Starting with the trig identity of \( \sin(\theta_3)^2 + \cos(\theta_3)^2 = S_3^2 + C_3^2 \equiv 1\), we can find \( \cos(\theta_2) \) from matrix elements \(M(1,2)\) and \(M(2,2)\) by

\begin{equation} \cos(\theta_2) = C_2 = \sqrt{ M(1,2)^2 + M(2,2)^2} = \sqrt{ C_2^2 S_3^2 + C_2^2 C_3^2 } = \sqrt{ C_2^2 ( S_3^2 + C_3^2 ) }. \end{equation}

If \form#566:

If \(\cos(\theta_2) = C_2 = 0\), then \( \theta_2 \) is \( \pm\pi/2 \) and \( S_2 = \pm 1\). We can solve for the sign of \(\theta_2\) by using

\begin{equation} \theta_2 = \arctan{\left( \frac{-M(3,2)}{C_2} \right)} = \arctan{\left( \frac{S_2}{C_2} \right)} \end{equation}

(but using the atan2 function in the complex plane instead of \( \arctan \)).

Considering \( C_2 = 0 \) and \( S_2 = \pm 1\), the matrix \( M \) reduces to

\begin{equation} M = \begin{bmatrix} C_1 C_3 \pm S_1 S_3 & 0 & \pm C_1 S_3 - S_1 C_3 \\ \pm S_1 C_3 - C_1 S_3 & 0 & \pm C_1 C_3 + S_1 S_3 \\ 0 & \mp 1 & 0 \\ \end{bmatrix} \end{equation}

At this point we can choose \( \theta_3 = 0 \) due to gimbal lock giving \( \sin(\theta_3) = 0 \), \( \cos(\theta_3) = 1\).

This further reduces \( M \) to

\begin{equation} M = \begin{bmatrix} C_1 & 0 & - S_1 \\ \pm S_1 & 0 & \pm C_1 \\ 0 & \mp 1 & 0 \\ \end{bmatrix}, \end{equation}

allowing us to solve for \( \theta_1 \) by \( \theta_1 = \arctan{\left( \frac{-M(1,3)}{M(1,1)} \right)} = \arctan{\left( \frac{S_1}{C_1} \right)}\).

Else \form#581:

First, start by finding \( \theta(1) \) from \( M(3,1) \) and \( M(3,3) \) using

\begin{equation} \theta_1 = \arctan{\left( \frac{M(3,1)}{M(3,3)} \right)} = \arctan{\left( \frac{S_1 C_2}{C_1 C_2} \right)}. \end{equation}

With this we calculate values for \(S_1\) and \(C_1\).

We already know \( \text{abs}( C_2 ) \), but need the sign of it. This can be found by comparing the \( S_1 C_2 \) and \( C_1 C_2 \) terms with the \( C_1 \) and \( S_1 \) terms we just found. If \( C_1 = 0 \), then we use

\begin{equation} C_2 = C_2 \cdot \text{sgn}{\left( \frac{M(3,1)}{S_1} \right)} = C_2 \cdot \text{sgn}{( C_2 )}, \end{equation}

otherwise

\begin{equation} C_2 = C_2 \cdot \text{sgn}{\left( \frac{M(3,3)}{C_1} \right)} = C_2 \cdot \text{sgn}{( C_2 )} \end{equation}

Now can calculate \( \theta_2 \) from

\begin{equation} \theta_2 = \arctan{\left( \frac{-M(3,2)}{C_2} \right)} = \arctan{\left( \frac{S_2}{C_2} \right)} \end{equation}

For numerical reasons, we're going to get \( \theta_3 \) ( \(\theta_z\)) using

\begin{eqnarray*} M' &=& M \cdot (R(\theta_2) \cdot R(\theta_1))^\text{T} = M \cdot R(\theta_1)^\text{T} \cdot R(\theta_2)^\text{T} & = & R(\theta_3) \\ &=& R(\theta_3) R(\theta_2) R(\theta_1) R(\theta_1)^T R(\theta_2)^T &=& R(\theta_3) \\ &=& M \cdot \begin{bmatrix} C_1 & 0 & S_1 \\ 0 & 1 & 0 \\ -S_1 & 0 & C_1 \end{bmatrix} \cdot \begin{bmatrix} 1 & 0 & 0 \\ 0 & C_2 & -S_2 \\ 0 & S_2 & C_2 \end{bmatrix} &=& \begin{bmatrix} C_3 & S_3 & 0 \\ -S_3 & C_3 & 0 \\ 0 & 0 & 1 \end{bmatrix} \\ &=& M \cdot \begin{bmatrix} C_1 & S_1 S_2 & S_1 C_2 \\ 0 & C_2 & -S_2 \\ -S_1 & C_1 S_2 & C_1 C_2 \end{bmatrix} &=& \begin{bmatrix} C_3 & S_3 & 0 \\ -S_3 & C_3 & 0 \\ 0 & 0 & 1 \end{bmatrix} \\ \end{eqnarray*}

From this we can find \( -S_3 \) and \( C_3 \) as

\begin{eqnarray} -S_3 &=& M(2,1) C_1 + M(2,3) (- S_1 ) &=& ( S_1 S_2 C_3 - C_1 S_3 ) C_1 + ( C_1 S_2 C_3 + S_1 S_3 ) ( - S_1 ) \\ && &=& S_1 C_1 S_2 C_3 - C_1^2 S_3 - S_1^2 S_3 - S_1 C_1 S_2 C_3 \\ && &=& -( C_1^2 + S_1^2 ) S_3 \\ && &=& -S_3 \end{eqnarray}

and

\begin{eqnarray} C_3 &=& M(1,1) C_1 + M(1,3) (- S_1 ) &=& ( C_1 C_3 + S_1 S_2 S_3 ) C_1 + ( C_1 S_2 S_3 - S_1 C_3 ) (- S_1 ) \\ && &=& C_1^2 C_3 + S_1 C_1 S_2 S_3 - S_1 C_1 S_2 S_3 + S_1^2 C_3 \\ && &=& ( C_1^2 + S_1^2 ) C_3 \\ && &=& C_3 \end{eqnarray}

\(\theta_3\) is then found as \(\theta_3 = \arctan{\left( \frac{S_3}{C_3} \right)}\).

◆ taitbryanyxzextractr8()

real(r8ki) function, dimension(3) nwtc_num::taitbryanyxzextractr8 ( real(r8ki), dimension(3,3), intent(in)  M)

See nwtc_num::taitbryanyxzextractr4 for detailed explanation of algorithm.

Parameters
[in]mrotation matrix, M
Returns
the 3 rotation angles, \((\theta_y, \theta_x, \theta_z)\), corresponding to the Tait-Bryan rotation angle corresponding to cant-toe-twist

See nwtc_num::taitbryanyxzextractr4 for detailed description of how this works.

◆ timevalues2seconds()

real(reki) function nwtc_num::timevalues2seconds ( integer, dimension (8), intent(in)  TimeAry)

This routine takes an array of time values such as that returned from CALL DATE_AND_TIME ( Values=TimeAry ) and converts TimeAry to the number of seconds past midnight.

◆ tracer16()

real(quki) function nwtc_num::tracer16 ( real(quki), dimension(:,:), intent(in)  A)

This function computes the trace of a matrix \(A \in \mathbb{R}^{m,n}\).

The trace of \(A\), \(\mathrm{Tr}\left[ A \right]\), is the sum of the diagonal elements of \(A\):

\begin{equation} \mathrm{Tr}\left[ A \right] = \sum_{i=1}^{\min(m,n)} A(i,i) \end{equation}

Use trace (nwtc_num::trace) instead of directly calling a specific routine in the generic interface.

Parameters
[in]amatrix A
Returns
sum of the diagonal elements of A

◆ tracer4()

real(siki) function nwtc_num::tracer4 ( real(siki), dimension(:,:), intent(in)  A)

This function computes the trace of a matrix \(A \in \mathbb{R}^{m,n}\).

The trace of \(A\), \(\mathrm{Tr}\left[ A \right]\), is the sum of the diagonal elements of \(A\):

\begin{equation} \mathrm{Tr}\left[ A \right] = \sum_{i=1}^{\min(m,n)} A(i,i) \end{equation}

Use trace (nwtc_num::trace) instead of directly calling a specific routine in the generic interface.

Parameters
[in]amatrix A
Returns
sum of the diagonal elements of A

◆ tracer8()

real(r8ki) function nwtc_num::tracer8 ( real(r8ki), dimension(:,:), intent(in)  A)

This function computes the trace of a matrix \(A \in \mathbb{R}^{m,n}\).

The trace of \(A\), \(\mathrm{Tr}\left[ A \right]\), is the sum of the diagonal elements of \(A\):

\begin{equation} \mathrm{Tr}\left[ A \right] = \sum_{i=1}^{\min(m,n)} A(i,i) \end{equation}

Use trace (nwtc_num::trace) instead of directly calling a specific routine in the generic interface.

Parameters
[in]amatrix A
Returns
sum of the diagonal elements of A
Parameters
[in]amatrix A
Returns
sum of the diagonal elements of A

◆ twonormr16()

real(quki) function nwtc_num::twonormr16 ( real(quki), dimension(:), intent(in)  v)

This function returns the \(l_2\) (Euclidian) norm of a vector, \(v = \left(v_1, v_2, \ldots ,v_n\right)\).

The \(l_2\)-norm is defined as

\begin{equation} \lVert v \rVert_2 = \left( \sum_{i=1}^{n} {v_i}^2 \right)^{1/2} \end{equation}


Use TwoNorm (nwtc_num::twonorm) instead of directly calling a specific routine in the generic interface.

Parameters
[in]vvector, v
Returns
two-norm of v

◆ twonormr4()

real(siki) function nwtc_num::twonormr4 ( real(siki), dimension(:), intent(in)  v)

This function returns the \(l_2\) (Euclidian) norm of a vector, \(v = \left(v_1, v_2, \ldots ,v_n\right)\).

The \(l_2\)-norm is defined as

\begin{equation} \lVert v \rVert_2 = \left( \sum_{i=1}^{n} {v_i}^2 \right)^{1/2} \end{equation}


Use TwoNorm (nwtc_num::twonorm) instead of directly calling a specific routine in the generic interface.

Parameters
[in]vvector, v
Returns
two-norm of v

◆ twonormr8()

real(r8ki) function nwtc_num::twonormr8 ( real(r8ki), dimension(:), intent(in)  v)

This function returns the \(l_2\) (Euclidian) norm of a vector, \(v = \left(v_1, v_2, \ldots ,v_n\right)\).

The \(l_2\)-norm is defined as

\begin{equation} \lVert v \rVert_2 = \left( \sum_{i=1}^{n} {v_i}^2 \right)^{1/2} \end{equation}


Use TwoNorm (nwtc_num::twonorm) instead of directly calling a specific routine in the generic interface.

Parameters
[in]vvector, v
Returns
two-norm of v

◆ zero2twopir16()

subroutine nwtc_num::zero2twopir16 ( real(quki), intent(inout)  Angle)

This routine is used to convert Angle to an equivalent value in the range \([0, 2\pi)\).


Use Zero2TwoPi (nwtc_num::zero2twopi) instead of directly calling a specific routine in the generic interface.

Parameters
[in,out]angleangle that is input and converted to equivalent in range \([0, 2\pi)\)

◆ zero2twopir4()

subroutine nwtc_num::zero2twopir4 ( real(siki), intent(inout)  Angle)

This routine is used to convert Angle to an equivalent value in the range \([0, 2\pi)\).


Use Zero2TwoPi (nwtc_num::zero2twopi) instead of directly calling a specific routine in the generic interface.

Parameters
[in,out]angleangle that is input and converted to equivalent in range \([0, 2\pi)\)

◆ zero2twopir8()

subroutine nwtc_num::zero2twopir8 ( real(r8ki), intent(inout)  Angle)

This routine is used to convert Angle to an equivalent value in the range \([0, 2\pi)\).


Use Zero2TwoPi (nwtc_num::zero2twopi) instead of directly calling a specific routine in the generic interface.

Parameters
[in,out]angleangle that is input and converted to equivalent in range \([0, 2\pi)\)