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

Safe HaskellNone
LanguageHaskell2010

Eigen.Internal

Contents

Description

Internal module to Eigen. Here we define all foreign function calls, and some typeclasses integral to the public and private interfaces of the library.

Synopsis

Documentation

data Row (r :: Nat) Source #

Like Proxy, but specialised to Nat.

Constructors

Row 

data Col (c :: Nat) Source #

Like Proxy, but specialised to Nat.

Constructors

Col 

natToInt :: forall n. KnownNat n => Int Source #

Used internally. Given a KnownNat constraint, turn the type-level Nat into an Int.

class Cast (a :: Type) where Source #

Cast to and from a C-FFI type Cast is a closed typeclass with an associated injective type family. It is closed in the sense that we provide only four types with instances for it; and intend for eigen to only be used with those four types. The injectivity of the type family is then useful for avoiding MPTCs. Cast has two functions; toC and fromC, where toC goes from a Haskell type to its associated C type for internal use, with the C FFI, and fromC goes from the associated C type to the Haskell type.

Minimal complete definition

toC, fromC

Associated Types

type C a = (result :: Type) | result -> a Source #

Methods

toC :: a -> C a Source #

fromC :: C a -> a Source #

Instances
Cast Double Source # 
Instance details

Defined in Eigen.Internal

Associated Types

type C Double = (result :: Type) Source #

Cast Float Source # 
Instance details

Defined in Eigen.Internal

Associated Types

type C Float = (result :: Type) Source #

Cast Int Source # 
Instance details

Defined in Eigen.Internal

Associated Types

type C Int = (result :: Type) Source #

Methods

toC :: Int -> C Int Source #

fromC :: C Int -> Int Source #

Cast a => Cast (Complex a) Source # 
Instance details

Defined in Eigen.Internal

Associated Types

type C (Complex a) = (result :: Type) Source #

Methods

toC :: Complex a -> C (Complex a) Source #

fromC :: C (Complex a) -> Complex a Source #

Cast a => Cast (Int, Int, a) Source #

WARNING! toC is lossy for any Int greater than (maxBound :: Int32)!

Instance details

Defined in Eigen.Internal

Associated Types

type C (Int, Int, a) = (result :: Type) Source #

Methods

toC :: (Int, Int, a) -> C (Int, Int, a) Source #

fromC :: C (Int, Int, a) -> (Int, Int, a) 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 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 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 Eigen.Internal

Code (CComplex CDouble) Source # 
Instance details

Defined in Eigen.Internal

data CTriplet a where Source #

FIXME: Doc

Constructors

CTriplet :: Cast a => !CInt -> !CInt -> !(C a) -> CTriplet a 
Instances
(Show a, Show (C a)) => Show (CTriplet a) Source # 
Instance details

Defined in Eigen.Internal

Methods

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

show :: CTriplet a -> String #

showList :: [CTriplet a] -> ShowS #

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

Defined in 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 () #

class (Num a, Cast a, Storable a, Storable (C a), Code (C a)) => Elem a Source #

Elem is a closed typeclass that encompasses the properties eigen expects its values to possess, and simplifies the external API quite a bit.

Instances
Elem Double Source # 
Instance details

Defined in Eigen.Internal

Elem Float Source # 
Instance details

Defined in Eigen.Internal

Elem (Complex Double) Source # 
Instance details

Defined in Eigen.Internal

Elem (Complex Float) Source # 
Instance details

Defined in Eigen.Internal

class Code a where Source #

Encode a C Type as a CInt

Hack used in FFI wrapper functions when constructing FFI calls

Minimal complete definition

code

Methods

code :: a -> CInt Source #

Instances
Code CFloat Source # 
Instance details

Defined in Eigen.Internal

Methods

code :: CFloat -> CInt Source #

Code CDouble Source # 
Instance details

Defined in Eigen.Internal

Methods

code :: CDouble -> CInt Source #

Code SparseQR Source # 
Instance details

Defined in Eigen.Solver.SparseLA

Methods

code :: SparseQR -> CInt Source #

Code SparseLU Source # 
Instance details

Defined in Eigen.Solver.SparseLA

Methods

code :: SparseLU -> CInt Source #

Code BiCGSTAB Source # 
Instance details

Defined in Eigen.Solver.SparseLA

Methods

code :: BiCGSTAB -> CInt Source #

Code ConjugateGradient Source # 
Instance details

Defined in Eigen.Solver.SparseLA

Code (CComplex CFloat) Source # 
Instance details

Defined in Eigen.Internal

Code (CComplex CDouble) Source # 
Instance details

Defined in Eigen.Internal

newtype MagicCode Source #

Hack used in constructing FFI calls.

Constructors

MagicCode CInt 
Instances
Eq MagicCode Source # 
Instance details

Defined in Eigen.Internal

Binary MagicCode Source # 
Instance details

Defined in Eigen.Internal

magicCode :: Code a => a -> MagicCode Source #

Hack used in constructing FFI calls.

intSize :: Int Source #

Machine size of a CInt.

encodeInt :: CInt -> ByteString Source #

FIXME: Doc

decodeInt :: ByteString -> CInt Source #

FIXME: Doc

data CSparseMatrix a Source #

FIXME: Doc

type CSparseMatrixPtr a = Ptr (CSparseMatrix a) Source #

FIXME: Doc

data CSolver a Source #

FIXME: Doc

type CSolverPtr a = Ptr (CSolver a) Source #

FIXME: Doc

performIO :: IO a -> a Source #

FIXME: replace with unholyPerformIO (?)

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

c_random :: CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

random :: forall a. Code (C a) => Ptr (C a) -> CInt -> CInt -> IO CString Source #

c_identity :: CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

identity :: forall a. Code (C a) => Ptr (C a) -> CInt -> CInt -> IO CString Source #

c_add :: CInt -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

add :: forall a. Code (C a) => Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

c_sub :: CInt -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

sub :: forall a. Code (C a) => Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

c_mul :: CInt -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

c_diagonal :: CInt -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

mul :: forall a. Code (C a) => Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

diagonal :: forall a. Code (C a) => Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

c_transpose :: CInt -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

transpose :: forall a. Code (C a) => Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

c_inverse :: CInt -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

inverse :: forall a. Code (C a) => Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

c_adjoint :: CInt -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

adjoint :: forall a. Code (C a) => Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

c_conjugate :: CInt -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

conjugate :: forall a. Code (C a) => Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

normalize :: forall a. Code (C a) => Ptr (C a) -> CInt -> CInt -> IO CString Source #

c_sum :: CInt -> Ptr (C a) -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

sum :: forall a. Code (C a) => Ptr (C a) -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

c_prod :: CInt -> Ptr (C a) -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

prod :: forall a. Code (C a) => Ptr (C a) -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

c_mean :: CInt -> Ptr (C a) -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

mean :: forall a. Code (C a) => Ptr (C a) -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

c_norm :: CInt -> Ptr (C a) -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

norm :: forall a. Code (C a) => Ptr (C a) -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

c_trace :: CInt -> Ptr (C a) -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

trace :: forall a. Code (C a) => Ptr (C a) -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

c_squaredNorm :: CInt -> Ptr (C a) -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

squaredNorm :: forall a. Code (C a) => Ptr (C a) -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

c_blueNorm :: CInt -> Ptr (C a) -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

blueNorm :: forall a. Code (C a) => Ptr (C a) -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

c_hypotNorm :: CInt -> Ptr (C a) -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

hypotNorm :: forall a. Code (C a) => Ptr (C a) -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

c_determinant :: CInt -> Ptr (C a) -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

determinant :: forall a. Code (C a) => Ptr (C a) -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

c_rank :: CInt -> CInt -> Ptr CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

rank :: forall a. Code (C a) => CInt -> Ptr CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

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

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

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

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

c_solve :: CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

solve :: forall a. Code (C a) => CInt -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

c_relativeError :: CInt -> Ptr (C a) -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

relativeError :: forall a. Code (C a) => Ptr (C a) -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> Ptr (C a) -> CInt -> CInt -> IO CString Source #

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

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

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

sparse_free :: forall a. Code (C a) => CSparseMatrixPtr a -> IO CString Source #

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

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

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

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

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

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

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

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

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

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

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

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

sparse_resize :: forall a. Code (C a) => CSparseMatrixPtr a -> CInt -> CInt -> IO CString Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Orphan instances

Storable a => Binary (Vector a) Source #

Binary instance for Vector

Instance details

Methods

put :: Vector a -> Put #

get :: Get (Vector a) #

putList :: [Vector a] -> Put #