eigen-3.3.4.1: Eigen C++ library (linear algebra: matrices, sparse matrices, vectors, numerical solvers).

Safe HaskellNone
LanguageHaskell2010

Data.Eigen.Internal

Contents

Description

This internal module is going to see a lot of refactoring. It is not recommended to import this, as the API is likely to experience heavy change.

Synopsis

Documentation

class (Num a, Cast a b, Cast b a, Storable b, Code b) => Elem a b | a -> b Source #

Instances
Elem Double CDouble Source # 
Instance details

Defined in Data.Eigen.Internal

Elem Float CFloat Source # 
Instance details

Defined in Data.Eigen.Internal

Elem (Complex Double) (CComplex CDouble) Source # 
Instance details

Defined in Data.Eigen.Internal

Elem (Complex Float) (CComplex CFloat) Source # 
Instance details

Defined in Data.Eigen.Internal

class Cast a b where Source #

Minimal complete definition

cast

Methods

cast :: a -> b Source #

Instances
Cast Double CDouble Source # 
Instance details

Defined in Data.Eigen.Internal

Methods

cast :: Double -> CDouble Source #

Cast Float CFloat Source # 
Instance details

Defined in Data.Eigen.Internal

Methods

cast :: Float -> CFloat Source #

Cast Int CInt Source # 
Instance details

Defined in Data.Eigen.Internal

Methods

cast :: Int -> CInt Source #

Cast CInt Int Source # 
Instance details

Defined in Data.Eigen.Internal

Methods

cast :: CInt -> Int Source #

Cast CFloat Float Source # 
Instance details

Defined in Data.Eigen.Internal

Methods

cast :: CFloat -> Float Source #

Cast CDouble Double Source # 
Instance details

Defined in Data.Eigen.Internal

Methods

cast :: CDouble -> Double Source #

Cast (Complex Double) (CComplex CDouble) Source # 
Instance details

Defined in Data.Eigen.Internal

Cast (Complex Float) (CComplex CFloat) Source # 
Instance details

Defined in Data.Eigen.Internal

Cast (CComplex CFloat) (Complex Float) Source # 
Instance details

Defined in Data.Eigen.Internal

Cast (CComplex CDouble) (Complex Double) Source # 
Instance details

Defined in Data.Eigen.Internal

Cast a b => Cast (CTriplet a) (Int, Int, b) Source # 
Instance details

Defined in Data.Eigen.Internal

Methods

cast :: CTriplet a -> (Int, Int, b) Source #

Cast a b => Cast (Int, Int, a) (CTriplet b) Source # 
Instance details

Defined in Data.Eigen.Internal

Methods

cast :: (Int, Int, a) -> CTriplet b Source #

data CComplex a Source #

Complex number for FFI with the same memory layout as std::complex<T>

Constructors

CComplex !a !a 
Instances
Show a => Show (CComplex a) Source # 
Instance details

Defined in Data.Eigen.Internal

Methods

showsPrec :: Int -> CComplex a -> ShowS #

show :: CComplex a -> String #

showList :: [CComplex a] -> ShowS #

Storable a => Storable (CComplex a) Source # 
Instance details

Defined in Data.Eigen.Internal

Methods

sizeOf :: CComplex a -> Int #

alignment :: CComplex a -> Int #

peekElemOff :: Ptr (CComplex a) -> Int -> IO (CComplex a) #

pokeElemOff :: Ptr (CComplex a) -> Int -> CComplex a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (CComplex a) #

pokeByteOff :: Ptr b -> Int -> CComplex a -> IO () #

peek :: Ptr (CComplex a) -> IO (CComplex a) #

poke :: Ptr (CComplex a) -> CComplex a -> IO () #

Code (CComplex CFloat) Source # 
Instance details

Defined in Data.Eigen.Internal

Code (CComplex CDouble) Source # 
Instance details

Defined in Data.Eigen.Internal

Cast (Complex Double) (CComplex CDouble) Source # 
Instance details

Defined in Data.Eigen.Internal

Cast (Complex Float) (CComplex CFloat) Source # 
Instance details

Defined in Data.Eigen.Internal

Cast (CComplex CFloat) (Complex Float) Source # 
Instance details

Defined in Data.Eigen.Internal

Cast (CComplex CDouble) (Complex Double) Source # 
Instance details

Defined in Data.Eigen.Internal

Elem (Complex Double) (CComplex CDouble) Source # 
Instance details

Defined in Data.Eigen.Internal

Elem (Complex Float) (CComplex CFloat) Source # 
Instance details

Defined in Data.Eigen.Internal

data CTriplet a Source #

Constructors

CTriplet !CInt !CInt !a 
Instances
Show a => Show (CTriplet a) Source # 
Instance details

Defined in Data.Eigen.Internal

Methods

showsPrec :: Int -> CTriplet a -> ShowS #

show :: CTriplet a -> String #

showList :: [CTriplet a] -> ShowS #

Storable a => Storable (CTriplet a) Source # 
Instance details

Defined in Data.Eigen.Internal

Methods

sizeOf :: CTriplet a -> Int #

alignment :: CTriplet a -> Int #

peekElemOff :: Ptr (CTriplet a) -> Int -> IO (CTriplet a) #

pokeElemOff :: Ptr (CTriplet a) -> Int -> CTriplet a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (CTriplet a) #

pokeByteOff :: Ptr b -> Int -> CTriplet a -> IO () #

peek :: Ptr (CTriplet a) -> IO (CTriplet a) #

poke :: Ptr (CTriplet a) -> CTriplet a -> IO () #

Cast a b => Cast (CTriplet a) (Int, Int, b) Source # 
Instance details

Defined in Data.Eigen.Internal

Methods

cast :: CTriplet a -> (Int, Int, b) Source #

Cast a b => Cast (Int, Int, a) (CTriplet b) Source # 
Instance details

Defined in Data.Eigen.Internal

Methods

cast :: (Int, Int, a) -> CTriplet b Source #

data CSolver a b Source #

type CSolverPtr a b = Ptr (CSolver a b) Source #

performIO :: IO a -> a Source #

free :: Ptr a -> IO () Source #

class Code a where Source #

Minimal complete definition

code

Methods

code :: a -> CInt Source #

Instances
Code CFloat Source # 
Instance details

Defined in Data.Eigen.Internal

Methods

code :: CFloat -> CInt Source #

Code CDouble Source # 
Instance details

Defined in Data.Eigen.Internal

Methods

code :: CDouble -> CInt Source #

Code SparseQR Source # 
Instance details

Defined in Data.Eigen.SparseLA

Methods

code :: SparseQR -> CInt Source #

Code SparseLU Source # 
Instance details

Defined in Data.Eigen.SparseLA

Methods

code :: SparseLU -> CInt Source #

Code BiCGSTAB Source # 
Instance details

Defined in Data.Eigen.SparseLA

Methods

code :: BiCGSTAB -> CInt Source #

Code ConjugateGradient Source # 
Instance details

Defined in Data.Eigen.SparseLA

Code (CComplex CFloat) Source # 
Instance details

Defined in Data.Eigen.Internal

Code (CComplex CDouble) Source # 
Instance details

Defined in Data.Eigen.Internal

newtype MagicCode Source #

Constructors

MagicCode CInt 
Instances
Eq MagicCode Source # 
Instance details

Defined in Data.Eigen.Internal

Binary MagicCode Source # 
Instance details

Defined in Data.Eigen.Internal

random :: forall b. Code b => Ptr b -> CInt -> CInt -> IO CString Source #

identity :: forall b. Code b => Ptr b -> CInt -> CInt -> IO CString Source #

c_add :: CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

add :: forall b. Code b => Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

c_sub :: CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

sub :: forall b. Code b => Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

c_mul :: CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

mul :: forall b. Code b => Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

c_diagonal :: CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

diagonal :: forall b. Code b => Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

c_transpose :: CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

transpose :: forall b. Code b => Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

c_inverse :: CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

inverse :: forall b. Code b => Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

c_adjoint :: CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

adjoint :: forall b. Code b => Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

c_conjugate :: CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

conjugate :: forall b. Code b => Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

normalize :: forall b. Code b => Ptr b -> CInt -> CInt -> IO CString Source #

c_sum :: CInt -> Ptr b -> Ptr b -> CInt -> CInt -> IO CString Source #

sum :: forall b. Code b => Ptr b -> Ptr b -> CInt -> CInt -> IO CString Source #

c_prod :: CInt -> Ptr b -> Ptr b -> CInt -> CInt -> IO CString Source #

prod :: forall b. Code b => Ptr b -> Ptr b -> CInt -> CInt -> IO CString Source #

c_mean :: CInt -> Ptr b -> Ptr b -> CInt -> CInt -> IO CString Source #

mean :: forall b. Code b => Ptr b -> Ptr b -> CInt -> CInt -> IO CString Source #

c_norm :: CInt -> Ptr b -> Ptr b -> CInt -> CInt -> IO CString Source #

norm :: forall b. Code b => Ptr b -> Ptr b -> CInt -> CInt -> IO CString Source #

c_trace :: CInt -> Ptr b -> Ptr b -> CInt -> CInt -> IO CString Source #

trace :: forall b. Code b => Ptr b -> Ptr b -> CInt -> CInt -> IO CString Source #

squaredNorm :: forall b. Code b => Ptr b -> Ptr b -> CInt -> CInt -> IO CString Source #

c_blueNorm :: CInt -> Ptr b -> Ptr b -> CInt -> CInt -> IO CString Source #

blueNorm :: forall b. Code b => Ptr b -> Ptr b -> CInt -> CInt -> IO CString Source #

c_hypotNorm :: CInt -> Ptr b -> Ptr b -> CInt -> CInt -> IO CString Source #

hypotNorm :: forall b. Code b => Ptr b -> Ptr b -> CInt -> CInt -> IO CString Source #

determinant :: forall b. Code b => Ptr b -> Ptr b -> CInt -> CInt -> IO CString Source #

c_rank :: CInt -> CInt -> Ptr CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

rank :: forall b. Code b => CInt -> Ptr CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

c_image :: CInt -> CInt -> Ptr (Ptr b) -> Ptr CInt -> Ptr CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

image :: forall b. Code b => CInt -> Ptr (Ptr b) -> Ptr CInt -> Ptr CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

c_kernel :: CInt -> CInt -> Ptr (Ptr b) -> Ptr CInt -> Ptr CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

kernel :: forall b. Code b => CInt -> Ptr (Ptr b) -> Ptr CInt -> Ptr CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

c_solve :: CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

solve :: forall b. Code b => CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

c_relativeError :: CInt -> Ptr b -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

relativeError :: forall b. Code b => Ptr b -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString Source #

sparse_new :: forall a b. Code b => CInt -> CInt -> Ptr (CSparseMatrixPtr a b) -> IO CString Source #

sparse_fromList :: forall a b. Code b => CInt -> CInt -> Ptr (CTriplet b) -> CInt -> Ptr (CSparseMatrixPtr a b) -> IO CString Source #

sparse_toList :: forall a b. Code b => CSparseMatrixPtr a b -> Ptr (CTriplet b) -> CInt -> IO CString Source #

sparse_free :: forall a b. Code b => CSparseMatrixPtr a b -> IO CString Source #

sparse_prunedRef :: forall a b. Code b => CSparseMatrixPtr a b -> Ptr b -> Ptr (CSparseMatrixPtr a b) -> IO CString Source #

sparse_scale :: forall a b. Code b => CSparseMatrixPtr a b -> Ptr b -> Ptr (CSparseMatrixPtr a b) -> IO CString Source #

sparse_coeff :: forall a b. Code b => CSparseMatrixPtr a b -> CInt -> CInt -> Ptr b -> IO CString Source #

sparse_coeffRef :: forall a b. Code b => CSparseMatrixPtr a b -> CInt -> CInt -> Ptr (Ptr b) -> IO CString Source #

sparse_cols :: forall a b. Code b => CSparseMatrixPtr a b -> Ptr CInt -> IO CString Source #

sparse_rows :: forall a b. Code b => CSparseMatrixPtr a b -> Ptr CInt -> IO CString Source #

sparse_norm :: forall a b. Code b => CSparseMatrixPtr a b -> Ptr b -> IO CString Source #

sparse_squaredNorm :: forall a b. Code b => CSparseMatrixPtr a b -> Ptr b -> IO CString Source #

sparse_blueNorm :: forall a b. Code b => CSparseMatrixPtr a b -> Ptr b -> IO CString Source #

sparse_block :: forall a b. Code b => CSparseMatrixPtr a b -> CInt -> CInt -> CInt -> CInt -> Ptr (CSparseMatrixPtr a b) -> IO CString Source #

sparse_fromMatrix :: forall a b. Code b => Ptr b -> CInt -> CInt -> Ptr (CSparseMatrixPtr a b) -> IO CString Source #

sparse_toMatrix :: forall a b. Code b => CSparseMatrixPtr a b -> Ptr b -> CInt -> CInt -> IO CString Source #

sparse_values :: forall a b. Code b => CSparseMatrixPtr a b -> Ptr CInt -> Ptr (Ptr b) -> IO CString Source #

sparse_innerNNZs :: forall a b. Code b => CSparseMatrixPtr a b -> Ptr CInt -> Ptr (Ptr CInt) -> IO CString Source #

sparse_reserve :: forall a b. Code b => CSparseMatrixPtr a b -> CInt -> IO CString Source #

sparse_resize :: forall a b. Code b => CSparseMatrixPtr a b -> CInt -> CInt -> IO CString Source #

sparse_la_newSolver :: forall s a b. (Code s, Code b) => s -> Ptr (CSolverPtr a b) -> IO CString Source #

sparse_la_freeSolver :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> IO CString Source #

sparse_la_factorize :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> CSparseMatrixPtr a b -> IO CString Source #

sparse_la_analyzePattern :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> CSparseMatrixPtr a b -> IO CString Source #

sparse_la_compute :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> CSparseMatrixPtr a b -> IO CString Source #

sparse_la_tolerance :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> Ptr CDouble -> IO CString Source #

sparse_la_setTolerance :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> CDouble -> IO CString Source #

sparse_la_maxIterations :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> Ptr CInt -> IO CString Source #

sparse_la_setMaxIterations :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> CInt -> IO CString Source #

sparse_la_info :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> Ptr CInt -> IO CString Source #

sparse_la_error :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> Ptr CDouble -> IO CString Source #

sparse_la_iterations :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> Ptr CInt -> IO CString Source #

sparse_la_solve :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString Source #

sparse_la_matrixQ :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString Source #

sparse_la_matrixR :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString Source #

sparse_la_setPivotThreshold :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> CDouble -> IO CString Source #

sparse_la_rank :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> Ptr CInt -> IO CString Source #

sparse_la_matrixL :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString Source #

sparse_la_matrixU :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString Source #

sparse_la_setSymmetric :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> CInt -> IO CString Source #

sparse_la_determinant :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> Ptr b -> IO CString Source #

sparse_la_logAbsDeterminant :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> Ptr b -> IO CString Source #

sparse_la_absDeterminant :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> Ptr b -> IO CString Source #

sparse_la_signDeterminant :: forall s a b. (Code s, Code b) => s -> CSolverPtr a b -> Ptr b -> IO CString Source #

Orphan instances

Storable a => Binary (Vector a) Source # 
Instance details

Methods

put :: Vector a -> Put #

get :: Get (Vector a) #

putList :: [Vector a] -> Put #