{-# LINE 1 "Data/Eigen/Internal.hsc" #-}
{-# OPTIONS_HADDOCK hide #-}
{-# LINE 2 "Data/Eigen/Internal.hsc" #-}

{-# LANGUAGE CPP #-} 
{-# LANGUAGE EmptyDataDecls  #-}
{-# LANGUAGE FlexibleInstances  #-}
{-# LANGUAGE ForeignFunctionInterface  #-}
{-# LANGUAGE FunctionalDependencies  #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables  #-}

module Data.Eigen.Internal where

import Foreign.Ptr
import Foreign.ForeignPtr
import Foreign.Storable
import Foreign.C.Types
import Foreign.C.String
import Control.Monad

{-# LINE 20 "Data/Eigen/Internal.hsc" #-}

{-# LINE 23 "Data/Eigen/Internal.hsc" #-}
import System.IO.Unsafe
import Data.Complex
import Data.IORef
import Data.Bits
import qualified Data.Vector.Storable as VS
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL
import qualified Data.ByteString.Internal as BSI

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

instance Elem Float CFloat where
instance Elem Double CDouble where
instance Elem (Complex Float) (CComplex CFloat) where
instance Elem (Complex Double) (CComplex CDouble) where

class Cast a b where
    cast :: a -> b

-- | Complex number for FFI with the same memory layout as std::complex\<T\>
data CComplex a = CComplex !a !a

instance Storable a => Storable (CComplex a) where
    sizeOf _ = sizeOf (undefined :: a) * 2
    alignment _ = alignment (undefined :: a)
    poke p (CComplex x y) = do
        pokeElemOff (castPtr p) 0 x
        pokeElemOff (castPtr p) 1 y
    peek p = CComplex
        <$> peekElemOff (castPtr p) 0
        <*> peekElemOff (castPtr p) 1

data CTriplet a = CTriplet !CInt !CInt !a

instance Storable a => Storable (CTriplet a) where
    sizeOf _ = sizeOf (undefined :: a) + sizeOf (undefined :: CInt) * 2
    alignment _ = alignment (undefined :: CInt)
    poke p (CTriplet row col val) = do
        pokeElemOff (castPtr p) 0 row
        pokeElemOff (castPtr p) 1 col
        pokeByteOff p (sizeOf (undefined :: CInt) * 2) val
    peek p = CTriplet
        <$> peekElemOff (castPtr p) 0
        <*> peekElemOff (castPtr p) 1
        <*> peekByteOff p (sizeOf (undefined :: CInt) * 2)

instance Cast CInt Int where; cast = fromIntegral
instance Cast Int CInt where; cast = fromIntegral
instance Cast CFloat Float where; cast (CFloat x) = x
instance Cast Float CFloat where; cast = CFloat
instance Cast CDouble Double where; cast (CDouble x) = x
instance Cast Double CDouble where; cast = CDouble
instance Cast (CComplex CFloat) (Complex Float) where; cast (CComplex x y) = cast x :+ cast y
instance Cast (Complex Float) (CComplex CFloat) where; cast (x :+ y) = CComplex (cast x) (cast y)
instance Cast (CComplex CDouble) (Complex Double) where; cast (CComplex x y) = cast x :+ cast y
instance Cast (Complex Double) (CComplex CDouble) where; cast (x :+ y) = CComplex (cast x) (cast y)

intSize :: Int
intSize = sizeOf (undefined :: CInt)

encodeInt :: CInt -> BS.ByteString
encodeInt x = BSI.unsafeCreate (sizeOf x) $ (`poke` x) . castPtr

decodeInt :: BS.ByteString -> CInt
decodeInt (BSI.PS fp fo fs)
    | fs == sizeOf x = x
    | otherwise = error "decodeInt: wrong buffer size"
    where x = performIO $ withForeignPtr fp $ peek . (`plusPtr` fo)

data CSparseMatrix a b
type CSparseMatrixPtr a b = Ptr (CSparseMatrix a b)

data CSolver a b
type CSolverPtr a b = Ptr (CSolver a b)

performIO :: IO a -> a
performIO = unsafeDupablePerformIO

plusForeignPtr :: ForeignPtr a -> Int -> ForeignPtr b
plusForeignPtr fp fo = castForeignPtr fp' where
    vs :: VS.Vector CChar
    vs = VS.unsafeFromForeignPtr (castForeignPtr fp) fo 0
    (fp', _) = VS.unsafeToForeignPtr0 vs

foreign import ccall "eigen-proxy.h free" c_freeString :: CString -> IO ()

call :: IO CString -> IO ()
call func = func >>= \c_str -> when (c_str /= nullPtr) $
    peekCString c_str >>= \str -> c_freeString c_str >> fail str

foreign import ccall "eigen-proxy.h free" free :: Ptr a -> IO ()

foreign import ccall "eigen-proxy.h eigen_setNbThreads" c_setNbThreads :: CInt -> IO ()
foreign import ccall "eigen-proxy.h eigen_getNbThreads" c_getNbThreads :: IO CInt

class Code a where; code :: a -> CInt
instance Code CFloat where; code _ = 0
instance Code CDouble where; code _ = 1
instance Code (CComplex CFloat) where; code _ = 2
instance Code (CComplex CDouble) where; code _ = 3

magicCode :: Code a => a -> CInt
magicCode x = code x `xor` 0x45696730


{-# LINE 128 "Data/Eigen/Internal.hsc" #-}

foreign import ccall "eigen_random" c_random :: CInt -> Ptr b -> CInt -> CInt -> IO CString
random :: forall b . Code b => Ptr b -> CInt -> CInt -> IO CString
random = c_random (code (undefined :: b))
{-# LINE 130 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_identity" c_identity :: CInt -> Ptr b -> CInt -> CInt -> IO CString
identity :: forall b . Code b => Ptr b -> CInt -> CInt -> IO CString
identity = c_identity (code (undefined :: b))
{-# LINE 131 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_add" c_add :: CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString
add :: forall b . Code b => Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString
add = c_add (code (undefined :: b))
{-# LINE 132 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sub" c_sub :: CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString
sub :: forall b . Code b => Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString
sub = c_sub (code (undefined :: b))
{-# LINE 133 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_mul" c_mul :: CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString
mul :: forall b . Code b => Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString
mul = c_mul (code (undefined :: b))
{-# LINE 134 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_diagonal" c_diagonal :: CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString
diagonal :: forall b . Code b => Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString
diagonal = c_diagonal (code (undefined :: b))
{-# LINE 135 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_transpose" c_transpose :: CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString
transpose :: forall b . Code b => Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString
transpose = c_transpose (code (undefined :: b))
{-# LINE 136 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_inverse" c_inverse :: CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString
inverse :: forall b . Code b => Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString
inverse = c_inverse (code (undefined :: b))
{-# LINE 137 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_adjoint" c_adjoint :: CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString
adjoint :: forall b . Code b => Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString
adjoint = c_adjoint (code (undefined :: b))
{-# LINE 138 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_conjugate" c_conjugate :: CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString
conjugate :: forall b . Code b => Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString
conjugate = c_conjugate (code (undefined :: b))
{-# LINE 139 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_normalize" c_normalize :: CInt -> Ptr b -> CInt -> CInt -> IO CString
normalize :: forall b . Code b => Ptr b -> CInt -> CInt -> IO CString
normalize = c_normalize (code (undefined :: b))
{-# LINE 140 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sum" c_sum :: CInt -> Ptr b -> Ptr b -> CInt -> CInt -> IO CString
sum :: forall b . Code b => Ptr b -> Ptr b -> CInt -> CInt -> IO CString
sum = c_sum (code (undefined :: b))
{-# LINE 141 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_prod" c_prod :: CInt -> Ptr b -> Ptr b -> CInt -> CInt -> IO CString
prod :: forall b . Code b => Ptr b -> Ptr b -> CInt -> CInt -> IO CString
prod = c_prod (code (undefined :: b))
{-# LINE 142 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_mean" c_mean :: CInt -> Ptr b -> Ptr b -> CInt -> CInt -> IO CString
mean :: forall b . Code b => Ptr b -> Ptr b -> CInt -> CInt -> IO CString
mean = c_mean (code (undefined :: b))
{-# LINE 143 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_norm" c_norm :: CInt -> Ptr b -> Ptr b -> CInt -> CInt -> IO CString
norm :: forall b . Code b => Ptr b -> Ptr b -> CInt -> CInt -> IO CString
norm = c_norm (code (undefined :: b))
{-# LINE 144 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_trace" c_trace :: CInt -> Ptr b -> Ptr b -> CInt -> CInt -> IO CString
trace :: forall b . Code b => Ptr b -> Ptr b -> CInt -> CInt -> IO CString
trace = c_trace (code (undefined :: b))
{-# LINE 145 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_squaredNorm" c_squaredNorm :: CInt -> Ptr b -> Ptr b -> CInt -> CInt -> IO CString
squaredNorm :: forall b . Code b => Ptr b -> Ptr b -> CInt -> CInt -> IO CString
squaredNorm = c_squaredNorm (code (undefined :: b))
{-# LINE 146 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_blueNorm" c_blueNorm :: CInt -> Ptr b -> Ptr b -> CInt -> CInt -> IO CString
blueNorm :: forall b . Code b => Ptr b -> Ptr b -> CInt -> CInt -> IO CString
blueNorm = c_blueNorm (code (undefined :: b))
{-# LINE 147 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_hypotNorm" c_hypotNorm :: CInt -> Ptr b -> Ptr b -> CInt -> CInt -> IO CString
hypotNorm :: forall b . Code b => Ptr b -> Ptr b -> CInt -> CInt -> IO CString
hypotNorm = c_hypotNorm (code (undefined :: b))
{-# LINE 148 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_determinant" c_determinant :: CInt -> Ptr b -> Ptr b -> CInt -> CInt -> IO CString
determinant :: forall b . Code b => Ptr b -> Ptr b -> CInt -> CInt -> IO CString
determinant = c_determinant (code (undefined :: b))
{-# LINE 149 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_rank" c_rank :: CInt -> CInt -> Ptr CInt -> Ptr b -> CInt -> CInt -> IO CString
rank :: forall b . Code b => CInt -> Ptr CInt -> Ptr b -> CInt -> CInt -> IO CString
rank = c_rank (code (undefined :: b))
{-# LINE 150 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_image" c_image :: CInt -> CInt -> Ptr (Ptr b) -> Ptr CInt -> Ptr CInt -> Ptr b -> CInt -> CInt -> IO CString
image :: forall b . Code b => CInt -> Ptr (Ptr b) -> Ptr CInt -> Ptr CInt -> Ptr b -> CInt -> CInt -> IO CString
image = c_image (code (undefined :: b))
{-# LINE 151 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_kernel" c_kernel :: CInt -> CInt -> Ptr (Ptr b) -> Ptr CInt -> Ptr CInt -> Ptr b -> CInt -> CInt -> IO CString
kernel :: forall b . Code b => CInt -> Ptr (Ptr b) -> Ptr CInt -> Ptr CInt -> Ptr b -> CInt -> CInt -> IO CString
kernel = c_kernel (code (undefined :: b))
{-# LINE 152 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_solve" c_solve :: CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString
solve :: forall b . Code b => CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString
solve = c_solve (code (undefined :: b))
{-# LINE 153 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_relativeError" c_relativeError :: CInt -> Ptr b -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString
relativeError :: forall b . Code b => Ptr b -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> Ptr b -> CInt -> CInt -> IO CString
relativeError = c_relativeError (code (undefined :: b))
{-# LINE 154 "Data/Eigen/Internal.hsc" #-}


{-# LINE 156 "Data/Eigen/Internal.hsc" #-}

foreign import ccall "eigen_sparse_fromList" c_sparse_fromList :: CInt -> CInt -> CInt -> Ptr (CTriplet b) -> CInt -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_fromList :: forall a b . Code b => CInt -> CInt -> Ptr (CTriplet b) -> CInt -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_fromList = c_sparse_fromList (code (undefined :: b))
{-# LINE 158 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_toList" c_sparse_toList :: CInt -> CSparseMatrixPtr a b -> Ptr (CTriplet b) -> CInt -> IO CString
sparse_toList :: forall a b . Code b => CSparseMatrixPtr a b -> Ptr (CTriplet b) -> CInt -> IO CString
sparse_toList = c_sparse_toList (code (undefined :: b))
{-# LINE 159 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_free" c_sparse_free :: CInt -> CSparseMatrixPtr a b -> IO CString
sparse_free :: forall a b . Code b => CSparseMatrixPtr a b -> IO CString
sparse_free = c_sparse_free (code (undefined :: b))
{-# LINE 160 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_makeCompressed" c_sparse_makeCompressed :: CInt -> CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_makeCompressed :: forall a b . Code b => CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_makeCompressed = c_sparse_makeCompressed (code (undefined :: b))
{-# LINE 161 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_uncompress" c_sparse_uncompress :: CInt -> CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_uncompress :: forall a b . Code b => CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_uncompress = c_sparse_uncompress (code (undefined :: b))
{-# LINE 162 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_isCompressed" c_sparse_isCompressed :: CInt -> CSparseMatrixPtr a b -> Ptr CInt -> IO CString
sparse_isCompressed :: forall a b . Code b => CSparseMatrixPtr a b -> Ptr CInt -> IO CString
sparse_isCompressed = c_sparse_isCompressed (code (undefined :: b))
{-# LINE 163 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_transpose" c_sparse_transpose :: CInt -> CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_transpose :: forall a b . Code b => CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_transpose = c_sparse_transpose (code (undefined :: b))
{-# LINE 164 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_adjoint" c_sparse_adjoint :: CInt -> CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_adjoint :: forall a b . Code b => CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_adjoint = c_sparse_adjoint (code (undefined :: b))
{-# LINE 165 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_pruned" c_sparse_pruned :: CInt -> CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_pruned :: forall a b . Code b => CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_pruned = c_sparse_pruned (code (undefined :: b))
{-# LINE 166 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_prunedRef" c_sparse_prunedRef :: CInt -> CSparseMatrixPtr a b -> Ptr b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_prunedRef :: forall a b . Code b => CSparseMatrixPtr a b -> Ptr b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_prunedRef = c_sparse_prunedRef (code (undefined :: b))
{-# LINE 167 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_scale" c_sparse_scale :: CInt -> CSparseMatrixPtr a b -> Ptr b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_scale :: forall a b . Code b => CSparseMatrixPtr a b -> Ptr b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_scale = c_sparse_scale (code (undefined :: b))
{-# LINE 168 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_diagonal" c_sparse_diagonal :: CInt -> CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_diagonal :: forall a b . Code b => CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_diagonal = c_sparse_diagonal (code (undefined :: b))
{-# LINE 169 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_nonZeros" c_sparse_nonZeros :: CInt -> CSparseMatrixPtr a b -> Ptr CInt -> IO CString
sparse_nonZeros :: forall a b . Code b => CSparseMatrixPtr a b -> Ptr CInt -> IO CString
sparse_nonZeros = c_sparse_nonZeros (code (undefined :: b))
{-# LINE 170 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_innerSize" c_sparse_innerSize :: CInt -> CSparseMatrixPtr a b -> Ptr CInt -> IO CString
sparse_innerSize :: forall a b . Code b => CSparseMatrixPtr a b -> Ptr CInt -> IO CString
sparse_innerSize = c_sparse_innerSize (code (undefined :: b))
{-# LINE 171 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_outerSize" c_sparse_outerSize :: CInt -> CSparseMatrixPtr a b -> Ptr CInt -> IO CString
sparse_outerSize :: forall a b . Code b => CSparseMatrixPtr a b -> Ptr CInt -> IO CString
sparse_outerSize = c_sparse_outerSize (code (undefined :: b))
{-# LINE 172 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_coeff" c_sparse_coeff :: CInt -> CSparseMatrixPtr a b -> CInt -> CInt -> Ptr b -> IO CString
sparse_coeff :: forall a b . Code b => CSparseMatrixPtr a b -> CInt -> CInt -> Ptr b -> IO CString
sparse_coeff = c_sparse_coeff (code (undefined :: b))
{-# LINE 173 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_cols" c_sparse_cols :: CInt -> CSparseMatrixPtr a b -> Ptr CInt -> IO CString
sparse_cols :: forall a b . Code b => CSparseMatrixPtr a b -> Ptr CInt -> IO CString
sparse_cols = c_sparse_cols (code (undefined :: b))
{-# LINE 174 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_rows" c_sparse_rows :: CInt -> CSparseMatrixPtr a b -> Ptr CInt -> IO CString
sparse_rows :: forall a b . Code b => CSparseMatrixPtr a b -> Ptr CInt -> IO CString
sparse_rows = c_sparse_rows (code (undefined :: b))
{-# LINE 175 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_norm" c_sparse_norm :: CInt -> CSparseMatrixPtr a b -> Ptr b -> IO CString
sparse_norm :: forall a b . Code b => CSparseMatrixPtr a b -> Ptr b -> IO CString
sparse_norm = c_sparse_norm (code (undefined :: b))
{-# LINE 176 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_squaredNorm" c_sparse_squaredNorm :: CInt -> CSparseMatrixPtr a b -> Ptr b -> IO CString
sparse_squaredNorm :: forall a b . Code b => CSparseMatrixPtr a b -> Ptr b -> IO CString
sparse_squaredNorm = c_sparse_squaredNorm (code (undefined :: b))
{-# LINE 177 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_blueNorm" c_sparse_blueNorm :: CInt -> CSparseMatrixPtr a b -> Ptr b -> IO CString
sparse_blueNorm :: forall a b . Code b => CSparseMatrixPtr a b -> Ptr b -> IO CString
sparse_blueNorm = c_sparse_blueNorm (code (undefined :: b))
{-# LINE 178 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_add" c_sparse_add :: CInt -> CSparseMatrixPtr a b -> CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_add :: forall a b . Code b => CSparseMatrixPtr a b -> CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_add = c_sparse_add (code (undefined :: b))
{-# LINE 179 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_sub" c_sparse_sub :: CInt -> CSparseMatrixPtr a b -> CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_sub :: forall a b . Code b => CSparseMatrixPtr a b -> CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_sub = c_sparse_sub (code (undefined :: b))
{-# LINE 180 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_mul" c_sparse_mul :: CInt -> CSparseMatrixPtr a b -> CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_mul :: forall a b . Code b => CSparseMatrixPtr a b -> CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_mul = c_sparse_mul (code (undefined :: b))
{-# LINE 181 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_block" c_sparse_block :: CInt -> CSparseMatrixPtr a b -> CInt -> CInt -> CInt -> CInt -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_block :: forall a b . Code b => CSparseMatrixPtr a b -> CInt -> CInt -> CInt -> CInt -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_block = c_sparse_block (code (undefined :: b))
{-# LINE 182 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_fromMatrix" c_sparse_fromMatrix :: CInt -> Ptr b -> CInt -> CInt -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_fromMatrix :: forall a b . Code b => Ptr b -> CInt -> CInt -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_fromMatrix = c_sparse_fromMatrix (code (undefined :: b))
{-# LINE 183 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_toMatrix" c_sparse_toMatrix :: CInt -> CSparseMatrixPtr a b -> Ptr b -> CInt -> CInt -> IO CString
sparse_toMatrix :: forall a b . Code b => CSparseMatrixPtr a b -> Ptr b -> CInt -> CInt -> IO CString
sparse_toMatrix = c_sparse_toMatrix (code (undefined :: b))
{-# LINE 184 "Data/Eigen/Internal.hsc" #-}


{-# LINE 186 "Data/Eigen/Internal.hsc" #-}

foreign import ccall "eigen_sparse_la_newSolver" c_sparse_la_newSolver :: CInt -> CInt -> Ptr (CSolverPtr a b) -> IO CString
sparse_la_newSolver :: forall s a b . (Code s, Code b) => s -> Ptr (CSolverPtr a b) -> IO CString
sparse_la_newSolver s = c_sparse_la_newSolver (code (undefined :: b)) (code s)
{-# LINE 188 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_freeSolver" c_sparse_la_freeSolver :: CInt -> CInt -> CSolverPtr a b -> IO CString
sparse_la_freeSolver :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> IO CString
sparse_la_freeSolver s = c_sparse_la_freeSolver (code (undefined :: b)) (code s)
{-# LINE 189 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_factorize" c_sparse_la_factorize :: CInt -> CInt -> CSolverPtr a b -> CSparseMatrixPtr a b -> IO CString
sparse_la_factorize :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> CSparseMatrixPtr a b -> IO CString
sparse_la_factorize s = c_sparse_la_factorize (code (undefined :: b)) (code s)
{-# LINE 190 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_analyzePattern" c_sparse_la_analyzePattern :: CInt -> CInt -> CSolverPtr a b -> CSparseMatrixPtr a b -> IO CString
sparse_la_analyzePattern :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> CSparseMatrixPtr a b -> IO CString
sparse_la_analyzePattern s = c_sparse_la_analyzePattern (code (undefined :: b)) (code s)
{-# LINE 191 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_compute" c_sparse_la_compute :: CInt -> CInt -> CSolverPtr a b -> CSparseMatrixPtr a b -> IO CString
sparse_la_compute :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> CSparseMatrixPtr a b -> IO CString
sparse_la_compute s = c_sparse_la_compute (code (undefined :: b)) (code s)
{-# LINE 192 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_tolerance" c_sparse_la_tolerance :: CInt -> CInt -> CSolverPtr a b -> Ptr CDouble -> IO CString
sparse_la_tolerance :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> Ptr CDouble -> IO CString
sparse_la_tolerance s = c_sparse_la_tolerance (code (undefined :: b)) (code s)
{-# LINE 193 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_setTolerance" c_sparse_la_setTolerance :: CInt -> CInt -> CSolverPtr a b -> CDouble -> IO CString
sparse_la_setTolerance :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> CDouble -> IO CString
sparse_la_setTolerance s = c_sparse_la_setTolerance (code (undefined :: b)) (code s)
{-# LINE 194 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_maxIterations" c_sparse_la_maxIterations :: CInt -> CInt -> CSolverPtr a b -> Ptr CInt -> IO CString
sparse_la_maxIterations :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> Ptr CInt -> IO CString
sparse_la_maxIterations s = c_sparse_la_maxIterations (code (undefined :: b)) (code s)
{-# LINE 195 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_setMaxIterations" c_sparse_la_setMaxIterations :: CInt -> CInt -> CSolverPtr a b -> CInt -> IO CString
sparse_la_setMaxIterations :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> CInt -> IO CString
sparse_la_setMaxIterations s = c_sparse_la_setMaxIterations (code (undefined :: b)) (code s)
{-# LINE 196 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_info" c_sparse_la_info :: CInt -> CInt -> CSolverPtr a b -> Ptr CInt -> IO CString
sparse_la_info :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> Ptr CInt -> IO CString
sparse_la_info s = c_sparse_la_info (code (undefined :: b)) (code s)
{-# LINE 197 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_error" c_sparse_la_error :: CInt -> CInt -> CSolverPtr a b -> Ptr CDouble -> IO CString
sparse_la_error :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> Ptr CDouble -> IO CString
sparse_la_error s = c_sparse_la_error (code (undefined :: b)) (code s)
{-# LINE 198 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_iterations" c_sparse_la_iterations :: CInt -> CInt -> CSolverPtr a b -> Ptr CInt -> IO CString
sparse_la_iterations :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> Ptr CInt -> IO CString
sparse_la_iterations s = c_sparse_la_iterations (code (undefined :: b)) (code s)
{-# LINE 199 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_solve" c_sparse_la_solve :: CInt -> CInt -> CSolverPtr a b -> CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_la_solve :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_la_solve s = c_sparse_la_solve (code (undefined :: b)) (code s)
{-# LINE 200 "Data/Eigen/Internal.hsc" #-}
-- #api3 sparse_la_solveWithGuess,     "CSolverPtr a b -> CSparseMatrixPtr a b -> CSparseMatrixPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString"
foreign import ccall "eigen_sparse_la_matrixQ" c_sparse_la_matrixQ :: CInt -> CInt -> CSolverPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_la_matrixQ :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_la_matrixQ s = c_sparse_la_matrixQ (code (undefined :: b)) (code s)
{-# LINE 202 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_matrixR" c_sparse_la_matrixR :: CInt -> CInt -> CSolverPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_la_matrixR :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_la_matrixR s = c_sparse_la_matrixR (code (undefined :: b)) (code s)
{-# LINE 203 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_setPivotThreshold" c_sparse_la_setPivotThreshold :: CInt -> CInt -> CSolverPtr a b -> CDouble -> IO CString
sparse_la_setPivotThreshold :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> CDouble -> IO CString
sparse_la_setPivotThreshold s = c_sparse_la_setPivotThreshold (code (undefined :: b)) (code s)
{-# LINE 204 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_rank" c_sparse_la_rank :: CInt -> CInt -> CSolverPtr a b -> Ptr CInt -> IO CString
sparse_la_rank :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> Ptr CInt -> IO CString
sparse_la_rank s = c_sparse_la_rank (code (undefined :: b)) (code s)
{-# LINE 205 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_matrixL" c_sparse_la_matrixL :: CInt -> CInt -> CSolverPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_la_matrixL :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_la_matrixL s = c_sparse_la_matrixL (code (undefined :: b)) (code s)
{-# LINE 206 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_matrixU" c_sparse_la_matrixU :: CInt -> CInt -> CSolverPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_la_matrixU :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> Ptr (CSparseMatrixPtr a b) -> IO CString
sparse_la_matrixU s = c_sparse_la_matrixU (code (undefined :: b)) (code s)
{-# LINE 207 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_setSymmetric" c_sparse_la_setSymmetric :: CInt -> CInt -> CSolverPtr a b -> CInt -> IO CString
sparse_la_setSymmetric :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> CInt -> IO CString
sparse_la_setSymmetric s = c_sparse_la_setSymmetric (code (undefined :: b)) (code s)
{-# LINE 208 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_simplicialFactorize" c_sparse_la_simplicialFactorize :: CInt -> CInt -> CSolverPtr a b -> CSparseMatrixPtr a b -> IO CString
sparse_la_simplicialFactorize :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> CSparseMatrixPtr a b -> IO CString
sparse_la_simplicialFactorize s = c_sparse_la_simplicialFactorize (code (undefined :: b)) (code s)
{-# LINE 209 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_determinant" c_sparse_la_determinant :: CInt -> CInt -> CSolverPtr a b -> Ptr b -> IO CString
sparse_la_determinant :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> Ptr b -> IO CString
sparse_la_determinant s = c_sparse_la_determinant (code (undefined :: b)) (code s)
{-# LINE 210 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_logAbsDeterminant" c_sparse_la_logAbsDeterminant :: CInt -> CInt -> CSolverPtr a b -> Ptr b -> IO CString
sparse_la_logAbsDeterminant :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> Ptr b -> IO CString
sparse_la_logAbsDeterminant s = c_sparse_la_logAbsDeterminant (code (undefined :: b)) (code s)
{-# LINE 211 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_absDeterminant" c_sparse_la_absDeterminant :: CInt -> CInt -> CSolverPtr a b -> Ptr b -> IO CString
sparse_la_absDeterminant :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> Ptr b -> IO CString
sparse_la_absDeterminant s = c_sparse_la_absDeterminant (code (undefined :: b)) (code s)
{-# LINE 212 "Data/Eigen/Internal.hsc" #-}
foreign import ccall "eigen_sparse_la_signDeterminant" c_sparse_la_signDeterminant :: CInt -> CInt -> CSolverPtr a b -> Ptr b -> IO CString
sparse_la_signDeterminant :: forall s a b . (Code s, Code b) => s -> CSolverPtr a b -> Ptr b -> IO CString
sparse_la_signDeterminant s = c_sparse_la_signDeterminant (code (undefined :: b)) (code s)
{-# LINE 213 "Data/Eigen/Internal.hsc" #-}


openStream :: BSL.ByteString -> IO (IORef BSL.ByteString)
openStream = newIORef

readStream :: IORef BSL.ByteString -> Int -> IO BS.ByteString
readStream ref size = readIORef ref >>= \a ->
    let (b,c) = BSL.splitAt (fromIntegral size) a
    in if BSL.length b /= fromIntegral size
        then fail "readStream: stream exhausted"
        else do
            writeIORef ref c
            return . BS.concat . BSL.toChunks $ b

closeStream :: IORef BSL.ByteString -> IO ()
closeStream ref = BSL.null <$> readIORef ref >>= (`unless` fail "closeStream: stream underrun")

readInt :: IORef BSL.ByteString -> IO CInt
readInt st = decodeInt <$> readStream st intSize