Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype FMPZ = FMPZ {}
- newtype SLong = SLong {}
- data FMPZMat
- fmpz_mat_init :: Ptr FMPZMat -> SLong -> SLong -> IO ()
- fmpz_mat_set :: Ptr FMPZMat -> Ptr FMPZMat -> IO ()
- fmpz_mat_entry :: Ptr FMPZMat -> SLong -> SLong -> IO (Ptr FMPZ)
- fmpz_set_si :: Ptr FMPZ -> SLong -> IO ()
- fmpz_get_si :: Ptr FMPZ -> IO SLong
- fmpz_mat_clear :: Ptr FMPZMat -> IO ()
- fmpz_mat_print_pretty :: Ptr FMPZMat -> IO ()
- fmpz_mat_mul :: Ptr FMPZMat -> Ptr FMPZMat -> Ptr FMPZMat -> IO ()
- fmpz_mat_window_init :: Ptr FMPZMat -> Ptr FMPZMat -> SLong -> SLong -> SLong -> SLong -> IO ()
- fmpz_mat_window_clear :: Ptr FMPZMat -> IO ()
- fmpz_mat_rref :: Ptr FMPZMat -> Ptr FMPZ -> Ptr FMPZMat -> IO SLong
- fmpz_mat_inv :: Ptr FMPZMat -> Ptr FMPZ -> Ptr FMPZMat -> IO CInt
- fmpz_mat_hnf :: Ptr FMPZMat -> Ptr FMPZMat -> IO ()
- fmpz_mat_rank :: Ptr FMPZMat -> IO SLong
- rref :: Matrix Double -> (Matrix Double, Int, Int)
- hnf :: Matrix Double -> Matrix Double
- inv :: Matrix Double -> Maybe (Matrix Double, Int)
- withMatrix :: Matrix Double -> ((SLong, SLong, Ptr FMPZMat) -> IO b) -> IO b
- withBlankMatrix :: SLong -> SLong -> (Ptr FMPZMat -> IO b) -> IO b
- withWindow :: Ptr FMPZMat -> SLong -> SLong -> SLong -> SLong -> (Ptr FMPZMat -> IO b) -> IO b
- flintToHMatrix :: SLong -> SLong -> Ptr FMPZMat -> IO (Matrix Double)
- pokeM :: Ptr FMPZMat -> SLong -> SLong -> SLong -> IO ()
- peekM :: Ptr FMPZMat -> SLong -> SLong -> IO SLong
- copyMatrix :: Ptr FMPZMat -> Ptr FMPZMat -> SLong -> SLong -> SLong -> SLong -> IO ()
- normHNF :: Matrix Double -> (Matrix Double, [Int])
- normHNF' :: Matrix Double -> (Matrix Double, [Int])
- normhnf :: (SLong, SLong, Ptr FMPZMat) -> IO (Matrix Double, [SLong])
- elemrowscale :: Ptr FMPZMat -> SLong -> SLong -> IO [(SLong, SLong)]
- elemrowadds :: Ptr FMPZMat -> SLong -> SLong -> [(SLong, SLong)] -> IO ()
Documentation
Units of measure extension to Fortran: Flint backend components
Some notes on the Flint library to aid comprehension of the original C and this interface:
- They use a
typedef TYPE TYPE_t[1]
convention to do call-by-reference without an explicit pointer. It appears to be an unmentioned convention borrowed from related library & depedency GMP, explained in a GMP doc page: https://gmplib.org/manual/Parameter-Conventions . Any time one of these is a function parameter, it is correct to use 'Ptr a' in Haskell. - Flint extensively uses two typedefs
ulong
andslong
, which are "long integers" in unsigned and signed representations respectively. However, the story is more complicated in cross-platform contexts, because 64-bit Linux'slong
s are 64 bits (8 bytes), while 64-bit Windows kept them at 32 bits (4 bytes). That type isCLong
in Haskell, and it doesn't match up with Flint'sslong
, so we roll our own newtypes instead. (See the definition for further explanation.)
typedef slong fmpz
GHC's generalized newtype deriving handles deriving all the instances we require for us.
Instances
Storable FMPZ Source # | |
Enum FMPZ Source # | |
Num FMPZ Source # | |
Integral FMPZ Source # | |
Real FMPZ Source # | |
Defined in Camfort.Specification.Units.InferenceBackendFlint toRational :: FMPZ -> Rational # | |
Eq FMPZ Source # | |
Ord FMPZ Source # | |
Flint's long signed integer type slong
(= GMP's mp_limb_signed_t
).
As described in their Portability doc page
https://flintlib.org/doc/portability.html , this replaces long
(long signed
integer). Importantly, it is *always* 64-bits, regardless of platform. long
on Windows is usually 32-bits (whether on a 32-bit or 64-bit install), and
you're meant to use long long
instead.
We tie the typedef to Haskell's Int64
, since that should be the appropriate
size for any regular platform. Better would be to do some CPP or hsc2hs magic
to check the size of an slong
and use the appropriate Haskell signed
integer type.
GHC's generalized newtype deriving handles deriving all the instances we require for us.
Instances
Storable SLong Source # | |
Enum SLong Source # | |
Num SLong Source # | |
Integral SLong Source # | |
Real SLong Source # | |
Defined in Camfort.Specification.Units.InferenceBackendFlint toRational :: SLong -> Rational # | |
Eq SLong Source # | |
Ord SLong Source # | |
Instances
Storable FMPZMat Source # | |
fmpz_mat_window_init :: Ptr FMPZMat -> Ptr FMPZMat -> SLong -> SLong -> SLong -> SLong -> IO () Source #