{-# LANGUAGE ForeignFunctionInterface #-} module Numeric.Jalla.Foreign.LAPACKE --(CblasOrder (..), -- CblasTranspose (..), -- CblasUplo (..), -- CblasDiag (..), -- CblasSide (..), -- CblasIndex) where import C2HS import Foreign.C.Types import Foreign.Ptr import Numeric.Jalla.Types import Data.Complex #define LAPACK_NAME_PATTERN_MC 1 #define LAPACK_COMPLEX_STRUCTURE 1 #include #include #include castComplexToPtr :: Ptr (Complex CFloat) -> Ptr a castComplexToPtr = castPtr castZomplexToPtr :: Ptr (Complex CDouble) -> Ptr a castZomplexToPtr = castPtr castChar = toEnum . fromEnum withSingleCharPtr :: Ptr CChar -> (Char -> IO a) -> IO a withSingleCharPtr pc act = peek pc >>= \c -> act (toEnum (fromEnum c)) withSingleChar :: Char -> (Ptr CChar -> IO a) -> IO a withSingleChar c act = alloca $ \pc -> poke pc (toEnum (fromEnum c)) >> act pc {# fun unsafe LAPACKE_cgbbrd as cgbbrd {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgbbrd as dgbbrd {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgbbrd as sgbbrd {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgbbrd as zgbbrd {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgebrd as cgebrd {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgebrd as dgebrd {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgebrd as sgebrd {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgebrd as zgebrd {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgebak as cgebak {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgebak as dgebak {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgebak as sgebak {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgebak as zgebak {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgebal as cgebal {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgebal as dgebal {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgebal as sgebal {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgebal as zgebal {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cggbak as cggbak {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dggbak as dggbak {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sggbak as sggbak {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zggbak as zggbak {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cggbal as cggbal {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dggbal as dggbal {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sggbal as sggbal {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zggbal as zggbal {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgbcon as cgbcon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgbcon as dgbcon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgbcon as sgbcon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgbcon as zgbcon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpbcon as cpbcon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpbcon as dpbcon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spbcon as spbcon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpbcon as zpbcon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctbcon as ctbcon {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtbcon as dtbcon {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_stbcon as stbcon {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztbcon as ztbcon {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgecon as cgecon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgecon as dgecon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgecon as sgecon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgecon as zgecon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_checon as checon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhecon as zhecon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpocon as cpocon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpocon as dpocon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spocon as spocon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpocon as zpocon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chpcon as chpcon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CInt', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhpcon as zhpcon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CInt', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cppcon as cppcon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dppcon as dppcon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sppcon as sppcon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zppcon as zppcon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cspcon as cspcon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CInt', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dspcon as dspcon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CInt', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sspcon as sspcon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CInt', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zspcon as zspcon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CInt', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctpcon as ctpcon {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtpcon as dtpcon {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_stpcon as stpcon {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztpcon as ztpcon {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctrcon as ctrcon {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtrcon as dtrcon {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_strcon as strcon {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztrcon as ztrcon {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgtcon as cgtcon {castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CInt', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgtcon as dgtcon {castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CInt', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgtcon as sgtcon {castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CInt', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgtcon as zgtcon {castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CInt', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cptcon as cptcon {fromIntegral `Int', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dptcon as dptcon {fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sptcon as sptcon {fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zptcon as zptcon {fromIntegral `Int', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_csycon as csycon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsycon as dsycon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssycon as ssycon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zsycon as zsycon {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chbev as chbev {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhbev as zhbev {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsbev as dsbev {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssbev as ssbev {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chbevd as chbevd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhbevd as zhbevd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsbevd as dsbevd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssbevd as ssbevd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgbequ as cgbequ {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgbequ as dgbequ {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgbequ as sgbequ {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgbequ as zgbequ {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chbevx as chbevx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CInt', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhbevx as zhbevx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CInt', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpbequ as cpbequ {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpbequ as dpbequ {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spbequ as spbequ {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpbequ as zpbequ {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsbevx as dsbevx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssbevx as ssbevx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgeev as cgeev {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgeev as dgeev {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgeev as sgeev {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgeev as zgeev {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cheev as cheev {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zheev as zheev {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cheevd as cheevd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zheevd as zheevd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cheevr as cheevr {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CInt', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zheevr as zheevr {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CInt', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgeequ as cgeequ {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgeequ as dgeequ {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgeequ as sgeequ {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgeequ as zgeequ {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgeevx as cgeevx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgeevx as dgeevx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgeevx as sgeevx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgeevx as zgeevx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cheevx as cheevx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CInt', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zheevx as zheevx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CInt', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cggev as cggev {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dggev as dggev {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sggev as sggev {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zggev as zggev {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctgevc as ctgevc {fromIntegral `Int', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtgevc as dtgevc {fromIntegral `Int', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctgexc as ctgexc {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtgexc as dtgexc {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_stgevc as stgevc {fromIntegral `Int', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_stgexc as stgexc {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztgevc as ztgevc {fromIntegral `Int', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztgexc as ztgexc {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zcgesv as zcgesv {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cggevx as cggevx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dggevx as dggevx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sggevx as sggevx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zggevx as zggevx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chgeqz as chgeqz {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dhgeqz as dhgeqz {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_shgeqz as shgeqz {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhgeqz as zhgeqz {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsgesv as dsgesv {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpoequ as cpoequ {fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpoequ as dpoequ {fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spoequ as spoequ {fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpoequ as zpoequ {fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chpev as chpev {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhpev as zhpev {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dspev as dspev {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sspev as sspev {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chpevd as chpevd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhpevd as zhpevd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dspevd as dspevd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sspevd as sspevd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chpevx as chpevx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CInt', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhpevx as zhpevx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CInt', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cppequ as cppequ {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dppequ as dppequ {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sppequ as sppequ {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zppequ as zppequ {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dspevx as dspevx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sspevx as sspevx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctrevc as ctrevc {fromIntegral `Int', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtrevc as dtrevc {fromIntegral `Int', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctrexc as ctrexc {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtrexc as dtrexc {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_strevc as strevc {fromIntegral `Int', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_strexc as strexc {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztrevc as ztrevc {fromIntegral `Int', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztrexc as ztrexc {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chsein as chsein {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dhsein as dhsein {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_shsein as shsein {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhsein as zhsein {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chseqr as chseqr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dhseqr as dhseqr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_shseqr as shseqr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhseqr as zhseqr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dstev as dstev {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sstev as sstev {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cstedc as cstedc {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dstedc as dstedc {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sstedc as sstedc {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zstedc as zstedc {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dstevd as dstevd {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sstevd as sstevd {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsterf as dsterf {fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssterf as ssterf {fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cstein as cstein {fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CInt', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dstein as dstein {fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CInt', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sstein as sstein {fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CInt', id `Ptr CInt', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zstein as zstein {fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CInt', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpteqr as cpteqr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpteqr as dpteqr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spteqr as spteqr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpteqr as zpteqr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cstegr as cstegr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CInt', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dstegr as dstegr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cstemr as cstemr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dstemr as dstemr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_csteqr as csteqr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsteqr as dsteqr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dstevr as dstevr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sstegr as sstegr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sstemr as sstemr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zstegr as zstegr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CInt', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssteqr as ssteqr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zstemr as zstemr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sstevr as sstevr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zsteqr as zsteqr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dstevx as dstevx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sstevx as sstevx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dstebz as dstebz {castChar `CChar', castChar `CChar', fromIntegral `Int', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CInt', id `Ptr CInt', id `Ptr CDouble', id `Ptr CInt', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sstebz as sstebz {castChar `CChar', castChar `CChar', fromIntegral `Int', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CInt', id `Ptr CInt', id `Ptr CFloat', id `Ptr CInt', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsyev as dsyev {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssyev as ssyev {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsyevd as dsyevd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssyevd as ssyevd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsyevr as dsyevr {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssyevr as ssyevr {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsyevx as dsyevx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssyevx as ssyevx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgbequb as cgbequb {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgbequb as dgbequb {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgbequb as sgbequb {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgbequb as zgbequb {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgeequb as cgeequb {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgeequb as dgeequb {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgeequb as sgeequb {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgeequb as zgeequb {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cheequb as cheequb {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zheequb as zheequb {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpoequb as cpoequb {fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpoequb as dpoequb {fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spoequb as spoequb {fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpoequb as zpoequb {fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_csyequb as csyequb {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsyequb as dsyequb {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssyequb as ssyequb {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zsyequb as zsyequb {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chbgv as chbgv {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhbgv as zhbgv {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsbgv as dsbgv {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssbgv as ssbgv {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chbgvd as chbgvd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhbgvd as zhbgvd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsbgvd as dsbgvd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssbgvd as ssbgvd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chbgst as chbgst {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhbgst as zhbgst {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chbgvx as chbgvx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CInt', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhbgvx as zhbgvx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CInt', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsbgst as dsbgst {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssbgst as ssbgst {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsbgvx as dsbgvx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssbgvx as ssbgvx {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chegv as chegv {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhegv as zhegv {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chegvd as chegvd {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhegvd as zhegvd {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chegst as chegst {fromIntegral `Int', fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhegst as zhegst {fromIntegral `Int', fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chegvx as chegvx {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CInt', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhegvx as zhegvx {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CInt', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cggglm as cggglm {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dggglm as dggglm {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sggglm as sggglm {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zggglm as zggglm {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cungql as cungql {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zungql as zungql {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cunglq as cunglq {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cungrq as cungrq {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zunglq as zunglq {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zungrq as zungrq {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cungbr as cungbr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cunghr as cunghr {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cungqr as cungqr {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cungtr as cungtr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zungbr as zungbr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zunghr as zunghr {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zungqr as zungqr {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zungtr as zungtr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chpgv as chpgv {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhpgv as zhpgv {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dspgv as dspgv {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sspgv as sspgv {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chpgvd as chpgvd {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhpgvd as zhpgvd {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dspgvd as dspgvd {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sspgvd as sspgvd {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chpgst as chpgst {fromIntegral `Int', fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhpgst as zhpgst {fromIntegral `Int', fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chpgvx as chpgvx {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CInt', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhpgvx as zhpgvx {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CInt', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dopgtr as dopgtr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sopgtr as sopgtr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cupgtr as cupgtr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dspgst as dspgst {fromIntegral `Int', fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sspgst as sspgst {fromIntegral `Int', fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zupgtr as zupgtr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dspgvx as dspgvx {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sspgvx as sspgvx {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dorgql as dorgql {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sorgql as sorgql {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dorglq as dorglq {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dorgrq as dorgrq {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sorglq as sorglq {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sorgrq as sorgrq {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dorgbr as dorgbr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dorghr as dorghr {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dorgqr as dorgqr {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sorgbr as sorgbr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dorgtr as dorgtr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sorghr as sorghr {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sorgqr as sorgqr {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sorgtr as sorgtr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsygv as dsygv {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssygv as ssygv {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsygvd as dsygvd {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssygvd as ssygvd {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsygst as dsygst {fromIntegral `Int', fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssygst as ssygst {fromIntegral `Int', fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsygvx as dsygvx {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `CDouble', id `CDouble', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssygvx as ssygvx {fromIntegral `Int', fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `CFloat', id `CFloat', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgehrd as cgehrd {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgehrd as dgehrd {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgehrd as sgehrd {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgehrd as zgehrd {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgghrd as cgghrd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgghrd as dgghrd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgghrd as sgghrd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgghrd as zgghrd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgejsv as dgejsv {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgejsv as sgejsv {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgels as cgels {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgels as dgels {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgels as sgels {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgels as zgels {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgelsd as cgelsd {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `CFloat', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgelsd as dgelsd {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `CDouble', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgelsd as sgelsd {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `CFloat', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgelsd as zgelsd {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `CDouble', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgelqf as cgelqf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgelqf as dgelqf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgelqf as sgelqf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgelqf as zgelqf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgelss as cgelss {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `CFloat', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgelss as dgelss {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `CDouble', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgelss as sgelss {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `CFloat', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgelss as zgelss {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `CDouble', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgelsy as cgelsy {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', id `CFloat', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgelsy as dgelsy {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `CDouble', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgelsy as sgelsy {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `CFloat', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgelsy as zgelsy {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', id `CDouble', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgglse as cgglse {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgglse as dgglse {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgglse as sgglse {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgglse as zgglse {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cunmql as cunmql {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zunmql as zunmql {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cunmlq as cunmlq {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cunmrq as cunmrq {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zunmlq as zunmlq {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zunmrq as zunmrq {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cunmbr as cunmbr {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cunmhr as cunmhr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cunmqr as cunmqr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cunmtr as cunmtr {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zunmbr as zunmbr {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zunmhr as zunmhr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zunmqr as zunmqr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zunmtr as zunmtr {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cunmrz as cunmrz {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zunmrz as zunmrz {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dopmtr as dopmtr {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sopmtr as sopmtr {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cupmtr as cupmtr {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zupmtr as zupmtr {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dormql as dormql {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sormql as sormql {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dormlq as dormlq {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dormrq as dormrq {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sormlq as sormlq {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sormrq as sormrq {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dormbr as dormbr {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dormhr as dormhr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dormqr as dormqr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sormbr as sormbr {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dormtr as dormtr {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sormhr as sormhr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sormqr as sormqr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sormtr as sormtr {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dormrz as dormrz {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sormrz as sormrz {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zcposv as zcposv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsposv as dsposv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgeqp3 as cgeqp3 {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgeqp3 as dgeqp3 {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgeqp3 as sgeqp3 {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgeqp3 as zgeqp3 {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgeqlf as cgeqlf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgeqlf as dgeqlf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgeqpf as cgeqpf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgeqpf as dgeqpf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgeqrf as cgeqrf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgeqrf as dgeqrf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgeqlf as sgeqlf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgeqpf as sgeqpf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgeqrf as sgeqrf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgeqlf as zgeqlf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgeqpf as zgeqpf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgeqrf as zgeqrf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cggqrf as cggqrf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dggqrf as dggqrf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sggqrf as sggqrf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zggqrf as zggqrf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgeqrfp as cgeqrfp {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgeqrfp as dgeqrfp {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgeqrfp as sgeqrfp {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgeqrfp as zgeqrfp {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgbrfs as cgbrfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgbrfs as dgbrfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgbrfs as sgbrfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgbrfs as zgbrfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpbrfs as cpbrfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpbrfs as dpbrfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spbrfs as spbrfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpbrfs as zpbrfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctbrfs as ctbrfs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtbrfs as dtbrfs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_stbrfs as stbrfs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztbrfs as ztbrfs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgerqf as cgerqf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgerqf as dgerqf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgerqf as sgerqf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgerqf as zgerqf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgerfs as cgerfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgerfs as dgerfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgerfs as sgerfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgerfs as zgerfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cherfs as cherfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zherfs as zherfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chfrk as chfrk {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `CFloat', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhfrk as zhfrk {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `CDouble', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsfrk as dsfrk {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CDouble', fromIntegral `Int', id `CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssfrk as ssfrk {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CFloat', fromIntegral `Int', id `CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cggrqf as cggrqf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dggrqf as dggrqf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sggrqf as sggrqf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zggrqf as zggrqf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cporfs as cporfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dporfs as dporfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sporfs as sporfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zporfs as zporfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chprfs as chprfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhprfs as zhprfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpprfs as cpprfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpprfs as dpprfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spprfs as spprfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpprfs as zpprfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_csprfs as csprfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsprfs as dsprfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssprfs as ssprfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CInt', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zsprfs as zsprfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctprfs as ctprfs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtprfs as dtprfs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_stprfs as stprfs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztprfs as ztprfs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctrrfs as ctrrfs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtrrfs as dtrrfs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_strrfs as strrfs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztrrfs as ztrrfs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgtrfs as cgtrfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgtrfs as dgtrfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgtrfs as sgtrfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CInt', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgtrfs as zgtrfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cptrfs as cptrfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dptrfs as dptrfs {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sptrfs as sptrfs {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zptrfs as zptrfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_csyrfs as csyrfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsyrfs as dsyrfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssyrfs as ssyrfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zsyrfs as zsyrfs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctzrzf as ctzrzf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtzrzf as dtzrzf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_stzrzf as stzrzf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztzrzf as ztzrzf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgbsv as cgbsv {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgbsv as dgbsv {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgbsv as sgbsv {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgbsv as zgbsv {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpbsv as cpbsv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpbsv as dpbsv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spbsv as spbsv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpbsv as zpbsv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpbstf as cpbstf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpbstf as dpbstf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spbstf as spbstf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpbstf as zpbstf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgbsvx as cgbsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', withSingleChar* `Char', id `Ptr CFloat', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgbsvx as dgbsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', withSingleChar* `Char', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgbsvx as sgbsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', withSingleChar* `Char', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgbsvx as zgbsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', withSingleChar* `Char', id `Ptr CDouble', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpbsvx as cpbsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', withSingleChar* `Char', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpbsvx as dpbsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', withSingleChar* `Char', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spbsvx as spbsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', withSingleChar* `Char', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpbsvx as zpbsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', withSingleChar* `Char', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dbdsdc as dbdsdc {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sbdsdc as sbdsdc {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cbdsqr as cbdsqr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dbdsqr as dbdsqr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sbdsqr as sbdsqr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zbdsqr as zbdsqr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgesv as cgesv {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgesv as dgesv {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgesv as sgesv {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgesv as zgesv {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chesv as chesv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhesv as zhesv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgesdd as cgesdd {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgesdd as dgesdd {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgesdd as sgesdd {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgesvd as cgesvd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgesvd as dgesvd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgesdd as zgesdd {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgesvd as sgesvd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgesvd as zgesvd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgesvj as dgesvj {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgesvj as sgesvj {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgesvx as cgesvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', withSingleChar* `Char', id `Ptr CFloat', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgesvx as dgesvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', withSingleChar* `Char', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgesvx as sgesvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', withSingleChar* `Char', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgesvx as zgesvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', withSingleChar* `Char', id `Ptr CDouble', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chesvx as chesvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhesvx as zhesvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtfsm as dtfsm {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_stfsm as stfsm {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cggsvd as cggsvd {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dggsvd as dggsvd {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sggsvd as sggsvd {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zggsvd as zggsvd {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctgsja as ctgsja {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `CFloat', id `CFloat', id `Ptr CFloat', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtgsja as dtgsja {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `CDouble', id `CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctgsna as ctgsna {fromIntegral `Int', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtgsna as dtgsna {fromIntegral `Int', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_stgsja as stgsja {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `CFloat', id `CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_stgsna as stgsna {fromIntegral `Int', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztgsja as ztgsja {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `CDouble', id `CDouble', id `Ptr CDouble', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztgsna as ztgsna {fromIntegral `Int', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cggsvp as cggsvp {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `CFloat', id `CFloat', id `Ptr CInt', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dggsvp as dggsvp {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `CDouble', id `CDouble', id `Ptr CInt', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sggsvp as sggsvp {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `CFloat', id `CFloat', id `Ptr CInt', id `Ptr CInt', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zggsvp as zggsvp {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `CDouble', id `CDouble', id `Ptr CInt', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctgsyl as ctgsyl {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtgsyl as dtgsyl {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_stgsyl as stgsyl {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztgsyl as ztgsyl {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctgsen as ctgsen {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtgsen as dtgsen {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_stgsen as stgsen {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztgsen as ztgsen {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CInt', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ddisna as ddisna {castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sdisna as sdisna {castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cposv as cposv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dposv as dposv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sposv as sposv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zposv as zposv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chpsv as chpsv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cposvx as cposvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', withSingleChar* `Char', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dposvx as dposvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', withSingleChar* `Char', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sposvx as sposvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', withSingleChar* `Char', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhpsv as zhpsv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zposvx as zposvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', withSingleChar* `Char', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cppsv as cppsv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dppsv as dppsv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sppsv as sppsv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zppsv as zppsv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cspsv as cspsv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dspsv as dspsv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sspsv as sspsv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CInt', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zspsv as zspsv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chpsvx as chpsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhpsvx as zhpsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cppsvx as cppsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', withSingleChar* `Char', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dppsvx as dppsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', withSingleChar* `Char', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sppsvx as sppsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', withSingleChar* `Char', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zppsvx as zppsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', withSingleChar* `Char', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cspsvx as cspsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dspsvx as dspsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sspsvx as sspsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CInt', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zspsvx as zspsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctrsna as ctrsna {fromIntegral `Int', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtrsna as dtrsna {fromIntegral `Int', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_strsna as strsna {fromIntegral `Int', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztrsna as ztrsna {fromIntegral `Int', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctrsyl as ctrsyl {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtrsyl as dtrsyl {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_strsyl as strsyl {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztrsyl as ztrsyl {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctrsen as ctrsen {fromIntegral `Int', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtrsen as dtrsen {fromIntegral `Int', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_strsen as strsen {fromIntegral `Int', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CInt', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztrsen as ztrsen {fromIntegral `Int', castChar `CChar', castChar `CChar', id `Ptr CInt', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CInt', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgtsv as cgtsv {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgtsv as dgtsv {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgtsv as sgtsv {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgtsv as zgtsv {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cptsv as cptsv {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dptsv as dptsv {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sptsv as sptsv {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zptsv as zptsv {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgtsvx as cgtsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgtsvx as dgtsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgtsvx as sgtsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CInt', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgtsvx as zgtsvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cptsvx as cptsvx {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dptsvx as dptsvx {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sptsvx as sptsvx {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zptsvx as zptsvx {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_csysv as csysv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsysv as dsysv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssysv as ssysv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zsysv as zsysv {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_csysvx as csysvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsysvx as dsysvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssysvx as ssysvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zsysvx as zsysvx {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chbtrd as chbtrd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhbtrd as zhbtrd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgbtrf as cgbtrf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgbtrf as dgbtrf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgbtrf as sgbtrf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgbtrf as zgbtrf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpbtrf as cpbtrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpbtrf as dpbtrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spbtrf as spbtrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpbtrf as zpbtrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsbtrd as dsbtrd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssbtrd as ssbtrd {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgbtrs as cgbtrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgbtrs as dgbtrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgbtrs as sgbtrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgbtrs as zgbtrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpbtrs as cpbtrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpbtrs as dpbtrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spbtrs as spbtrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpbtrs as zpbtrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctbtrs as ctbtrs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtbtrs as dtbtrs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_stbtrs as stbtrs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztbtrs as ztbtrs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chetrd as chetrd {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhetrd as zhetrd {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgetrf as cgetrf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgetrf as dgetrf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgetrf as sgetrf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgetrf as zgetrf {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chetrf as chetrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhetrf as zhetrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgetri as cgetri {fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgetri as dgetri {fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgetri as sgetri {fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgetri as zgetri {fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chetri as chetri {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhetri as zhetri {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgetrs as cgetrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgetrs as dgetrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgetrs as sgetrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgetrs as zgetrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chetrs as chetrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhetrs as zhetrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpftrf as cpftrf {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpftrf as dpftrf {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spftrf as spftrf {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpftrf as zpftrf {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpftri as cpftri {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpftri as dpftri {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spftri as spftri {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpftri as zpftri {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctftri as ctftri {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtftri as dtftri {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_stftri as stftri {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztftri as ztftri {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpftrs as cpftrs {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpftrs as dpftrs {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spftrs as spftrs {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpftrs as zpftrs {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctfttp as ctfttp {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtfttp as dtfttp {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_stfttp as stfttp {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztfttp as ztfttp {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctfttr as ctfttr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtfttr as dtfttr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_stfttr as stfttr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztfttr as ztfttr {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpotrf as cpotrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpotrf as dpotrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spotrf as spotrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpotrf as zpotrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpotri as cpotri {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpotri as dpotri {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spotri as spotri {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpotri as zpotri {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpotrs as cpotrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpotrs as dpotrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spotrs as spotrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpotrs as zpotrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chptrd as chptrd {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CFloat', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhptrd as zhptrd {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CDouble', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chptrf as chptrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhptrf as zhptrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chptri as chptri {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhptri as zhptri {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpptrf as cpptrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpptrf as dpptrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spptrf as spptrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpptrf as zpptrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsptrd as dsptrd {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssptrd as ssptrd {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpptri as cpptri {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_csptrf as csptrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpptri as dpptri {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsptrf as dsptrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spptri as spptri {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssptrf as ssptrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpptri as zpptri {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zsptrf as zsptrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctpttf as ctpttf {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtpttf as dtpttf {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_stpttf as stpttf {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztpttf as ztpttf {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_chptrs as chptrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zhptrs as zhptrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_csptri as csptri {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsptri as dsptri {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssptri as ssptri {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zsptri as zsptri {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctptri as ctptri {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtptri as dtptri {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_stptri as stptri {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztptri as ztptri {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpptrs as cpptrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpptrs as dpptrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spptrs as spptrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpptrs as zpptrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_csptrs as csptrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsptrs as dsptrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctpttr as ctpttr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtpttr as dtpttr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssptrs as ssptrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CInt', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_stpttr as stpttr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zsptrs as zsptrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztpttr as ztpttr {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctptrs as ctptrs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtptrs as dtptrs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_stptrs as stptrs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztptrs as ztptrs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctrttf as ctrttf {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtrttf as dtrttf {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_strttf as strttf {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztrttf as ztrttf {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctrtri as ctrtri {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtrtri as dtrtri {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_strtri as strtri {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztrtri as ztrtri {fromIntegral `Int', castChar `CChar', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctrttp as ctrttp {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtrttp as dtrttp {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_strttp as strttp {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztrttp as ztrttp {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ctrtrs as ctrtrs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dtrtrs as dtrtrs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_strtrs as strtrs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ztrtrs as ztrtrs {fromIntegral `Int', castChar `CChar', castChar `CChar', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpstrf as cpstrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpstrf as dpstrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spstrf as spstrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpstrf as zpstrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', id `Ptr CInt', id `CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgttrf as cgttrf {fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgttrf as dgttrf {fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgttrf as sgttrf {fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgttrf as zgttrf {fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpttrf as cpttrf {fromIntegral `Int', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpttrf as dpttrf {fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spttrf as spttrf {fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpttrf as zpttrf {fromIntegral `Int', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cgttrs as cgttrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dgttrs as dgttrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_sgttrs as sgttrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CInt', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zgttrs as zgttrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_cpttrs as cpttrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', castComplexToPtr `Ptr (Complex CFloat)', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dpttrs as dpttrs {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_spttrs as spttrs {fromIntegral `Int', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zpttrs as zpttrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', castZomplexToPtr `Ptr (Complex CDouble)', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsytrd as dsytrd {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CDouble', id `Ptr CDouble', id `Ptr CDouble'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssytrd as ssytrd {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CFloat', id `Ptr CFloat', id `Ptr CFloat'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_csytrf as csytrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsytrf as dsytrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssytrf as ssytrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zsytrf as zsytrf {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_csytri as csytri {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsytri as dsytri {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssytri as ssytri {fromIntegral `Int', castChar `CChar', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zsytri as zsytri {fromIntegral `Int', castChar `CChar', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_csytrs as csytrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int', id `Ptr CInt', castComplexToPtr `Ptr (Complex CFloat)', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_dsytrs as dsytrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CDouble', fromIntegral `Int', id `Ptr CInt', id `Ptr CDouble', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_ssytrs as ssytrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', id `Ptr CFloat', fromIntegral `Int', id `Ptr CInt', id `Ptr CFloat', fromIntegral `Int'} -> `Int' fromIntegral #} {# fun unsafe LAPACKE_zsytrs as zsytrs {fromIntegral `Int', castChar `CChar', fromIntegral `Int', fromIntegral `Int', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int', id `Ptr CInt', castZomplexToPtr `Ptr (Complex CDouble)', fromIntegral `Int'} -> `Int' fromIntegral #}