Safe Haskell | None |
---|---|
Language | Haskell98 |
Numerical computations used by the cubic bezier functions. Also contains functions that aren't used anymore, but might be useful on its own.
Synopsis
- quadraticRoot :: Double -> Double -> Double -> [Double]
- cubicRoot :: Double -> Double -> Double -> Double -> [Double]
- cubicRootNorm :: Double -> Double -> Double -> [Double]
- solveLinear2x2 :: (Eq a, Fractional a) => a -> a -> a -> a -> a -> a -> Maybe (a, a)
- goldSearch :: (Ord a, Floating a) => (a -> a) -> Int -> a
- makeSparse :: Unbox a => Vector Int -> Matrix a -> SparseMatrix a
- data SparseMatrix a
- sparseMulT :: (Num a, Unbox a) => Vector a -> SparseMatrix a -> Vector a
- sparseMul :: (Num a, Unbox a) => SparseMatrix a -> Vector a -> Vector a
- addMatrix :: (Num a, Unbox a) => Matrix a -> Matrix a -> Matrix a
- addVec :: (Num a, Unbox a) => Vector a -> Vector a -> Vector a
- lsqMatrix :: (Num a, Unbox a) => SparseMatrix a -> Matrix a
- lsqSolveDist :: (Fractional a, Unbox a) => SparseMatrix (a, a) -> Vector (a, a) -> Vector a
- decompLDL :: (Fractional a, Unbox a) => Matrix a -> Matrix a
- lsqSolve :: (Fractional a, Unbox a) => SparseMatrix a -> Vector a -> Vector a
- solveTriDiagonal :: (Unbox a, Fractional a) => (a, a, a) -> Vector (a, a, a, a) -> Vector a
- solveCyclicTriD :: (Unbox a, Fractional a) => Vector (a, a, a, a) -> Vector a
Documentation
quadraticRoot :: Double -> Double -> Double -> [Double] Source #
quadraticRoot a b c
find the real roots of the quadratic equation
a x^2 + b x + c = 0
. It will return one, two or zero roots.
cubicRootNorm :: Double -> Double -> Double -> [Double] Source #
Find real roots from the normalized cubic equation.
solveLinear2x2 :: (Eq a, Fractional a) => a -> a -> a -> a -> a -> a -> Maybe (a, a) Source #
solveLinear2x2 a b c d e f
solves the linear equation with two variables (x and y) and two systems:
a x + b y + c = 0 d x + e y + f = 0
Returns Nothing
if no solution is found.
:: Unbox a | |
=> Vector Int | The column index of the first element of each row. Should be ascending in order. |
-> Matrix a | The adjacent coefficients in each row |
-> SparseMatrix a | A sparse matrix. |
data SparseMatrix a Source #
sparseMulT :: (Num a, Unbox a) => Vector a -> SparseMatrix a -> Vector a Source #
Multiply the vector by the transpose of the sparse matrix.
sparseMul :: (Num a, Unbox a) => SparseMatrix a -> Vector a -> Vector a Source #
Sparse matrix * vector multiplication.
:: (Num a, Unbox a) | |
=> SparseMatrix a | The input system. |
-> Matrix a | The resulting symmetric matrix as a sparse matrix. The first element of each row is the element on the diagonal. |
Given a rectangular matrix M, calculate the symmetric square matrix MᵀM which can be used to find a least squares solution to the overconstrained system.
:: (Fractional a, Unbox a) | |
=> SparseMatrix (a, a) | sparse matrix |
-> Vector (a, a) | Right hand side vector. |
-> Vector a | Solution vector |
lsqSolveDist rowStart M y
Find a least squares solution of the distance between the points.
decompLDL :: (Fractional a, Unbox a) => Matrix a -> Matrix a Source #
LDL* decomposition of the sparse hermitian matrix. The first element of each row is the diagonal component of the D matrix. The following elements are the elements next to the diagonal in the L* matrix (the diagonal components in L* are 1). For efficiency it mutates the matrix inplace.
:: (Fractional a, Unbox a) | |
=> SparseMatrix a | sparse matrix |
-> Vector a | Right hand side vector. |
-> Vector a | Solution vector |
lsqSolve rowStart M y
Find a least squares solution x to the
system xM = y.
solveTriDiagonal :: (Unbox a, Fractional a) => (a, a, a) -> Vector (a, a, a, a) -> Vector a Source #
solve a tridiagonal system. see metafont the program: ¶ 283
solveCyclicTriD :: (Unbox a, Fractional a) => Vector (a, a, a, a) -> Vector a Source #
solve a cyclic tridiagonal system. see metafont the program: ¶ 286