fplll-0.1.0.0: Haskell bindings to <https://fplll.github.io/fplll/ fplll>

Safe HaskellNone
LanguageHaskell2010

Math.Lattices.Fplll.Internal

Synopsis

Documentation

newtype LLLMethod Source #

Constructors

LLLMethod CInt 
Instances
Eq LLLMethod Source # 
Instance details

Defined in Math.Lattices.Fplll.Internal

Methods

(==) :: LLLMethod -> LLLMethod -> Bool

(/=) :: LLLMethod -> LLLMethod -> Bool

Ord LLLMethod Source # 
Instance details

Defined in Math.Lattices.Fplll.Internal

Methods

compare :: LLLMethod -> LLLMethod -> Ordering

(<) :: LLLMethod -> LLLMethod -> Bool

(<=) :: LLLMethod -> LLLMethod -> Bool

(>) :: LLLMethod -> LLLMethod -> Bool

(>=) :: LLLMethod -> LLLMethod -> Bool

max :: LLLMethod -> LLLMethod -> LLLMethod

min :: LLLMethod -> LLLMethod -> LLLMethod

Show LLLMethod 
Instance details

Defined in Math.Lattices.Fplll.Types

Methods

showsPrec :: Int -> LLLMethod -> ShowS

show :: LLLMethod -> String

showList :: [LLLMethod] -> ShowS

Storable LLLMethod Source # 
Instance details

Defined in Math.Lattices.Fplll.Internal

Methods

sizeOf :: LLLMethod -> Int

alignment :: LLLMethod -> Int

peekElemOff :: Ptr LLLMethod -> Int -> IO LLLMethod

pokeElemOff :: Ptr LLLMethod -> Int -> LLLMethod -> IO ()

peekByteOff :: Ptr b -> Int -> IO LLLMethod

pokeByteOff :: Ptr b -> Int -> LLLMethod -> IO ()

peek :: Ptr LLLMethod -> IO LLLMethod

poke :: Ptr LLLMethod -> LLLMethod -> IO ()

newtype FloatType Source #

Constructors

FloatType CInt 
Instances
Eq FloatType Source # 
Instance details

Defined in Math.Lattices.Fplll.Internal

Methods

(==) :: FloatType -> FloatType -> Bool

(/=) :: FloatType -> FloatType -> Bool

Ord FloatType Source # 
Instance details

Defined in Math.Lattices.Fplll.Internal

Methods

compare :: FloatType -> FloatType -> Ordering

(<) :: FloatType -> FloatType -> Bool

(<=) :: FloatType -> FloatType -> Bool

(>) :: FloatType -> FloatType -> Bool

(>=) :: FloatType -> FloatType -> Bool

max :: FloatType -> FloatType -> FloatType

min :: FloatType -> FloatType -> FloatType

Show FloatType 
Instance details

Defined in Math.Lattices.Fplll.Types

Methods

showsPrec :: Int -> FloatType -> ShowS

show :: FloatType -> String

showList :: [FloatType] -> ShowS

Storable FloatType Source # 
Instance details

Defined in Math.Lattices.Fplll.Internal

Methods

sizeOf :: FloatType -> Int

alignment :: FloatType -> Int

peekElemOff :: Ptr FloatType -> Int -> IO FloatType

pokeElemOff :: Ptr FloatType -> Int -> FloatType -> IO ()

peekByteOff :: Ptr b -> Int -> IO FloatType

pokeByteOff :: Ptr b -> Int -> FloatType -> IO ()

peek :: Ptr FloatType -> IO FloatType

poke :: Ptr FloatType -> FloatType -> IO ()

newtype RedStatus Source #

Constructors

RedStatus CInt 
Instances
Eq RedStatus Source # 
Instance details

Defined in Math.Lattices.Fplll.Internal

Methods

(==) :: RedStatus -> RedStatus -> Bool

(/=) :: RedStatus -> RedStatus -> Bool

Ord RedStatus Source # 
Instance details

Defined in Math.Lattices.Fplll.Internal

Methods

compare :: RedStatus -> RedStatus -> Ordering

(<) :: RedStatus -> RedStatus -> Bool

(<=) :: RedStatus -> RedStatus -> Bool

(>) :: RedStatus -> RedStatus -> Bool

(>=) :: RedStatus -> RedStatus -> Bool

max :: RedStatus -> RedStatus -> RedStatus

min :: RedStatus -> RedStatus -> RedStatus

Show RedStatus 
Instance details

Defined in Math.Lattices.Fplll.Types

Methods

showsPrec :: Int -> RedStatus -> ShowS

show :: RedStatus -> String

showList :: [RedStatus] -> ShowS

Storable RedStatus Source # 
Instance details

Defined in Math.Lattices.Fplll.Internal

Methods

sizeOf :: RedStatus -> Int

alignment :: RedStatus -> Int

peekElemOff :: Ptr RedStatus -> Int -> IO RedStatus

pokeElemOff :: Ptr RedStatus -> Int -> RedStatus -> IO ()

peekByteOff :: Ptr b -> Int -> IO RedStatus

pokeByteOff :: Ptr b -> Int -> RedStatus -> IO ()

peek :: Ptr RedStatus -> IO RedStatus

poke :: Ptr RedStatus -> RedStatus -> IO ()

newtype LLLFlags Source #

Flags controlling LLL reduction. Can be combined using \/.

Constructors

LLLFlags CInt 
Instances
Eq LLLFlags Source # 
Instance details

Defined in Math.Lattices.Fplll.Internal

Methods

(==) :: LLLFlags -> LLLFlags -> Bool

(/=) :: LLLFlags -> LLLFlags -> Bool

Ord LLLFlags Source # 
Instance details

Defined in Math.Lattices.Fplll.Internal

Methods

compare :: LLLFlags -> LLLFlags -> Ordering

(<) :: LLLFlags -> LLLFlags -> Bool

(<=) :: LLLFlags -> LLLFlags -> Bool

(>) :: LLLFlags -> LLLFlags -> Bool

(>=) :: LLLFlags -> LLLFlags -> Bool

max :: LLLFlags -> LLLFlags -> LLLFlags

min :: LLLFlags -> LLLFlags -> LLLFlags

Show LLLFlags 
Instance details

Defined in Math.Lattices.Fplll.Types

Methods

showsPrec :: Int -> LLLFlags -> ShowS

show :: LLLFlags -> String

showList :: [LLLFlags] -> ShowS

Storable LLLFlags Source # 
Instance details

Defined in Math.Lattices.Fplll.Internal

Methods

sizeOf :: LLLFlags -> Int

alignment :: LLLFlags -> Int

peekElemOff :: Ptr LLLFlags -> Int -> IO LLLFlags

pokeElemOff :: Ptr LLLFlags -> Int -> LLLFlags -> IO ()

peekByteOff :: Ptr b -> Int -> IO LLLFlags

pokeByteOff :: Ptr b -> Int -> LLLFlags -> IO ()

peek :: Ptr LLLFlags -> IO LLLFlags

poke :: Ptr LLLFlags -> LLLFlags -> IO ()

BoundedJoinSemiLattice LLLFlags 
Instance details

Defined in Math.Lattices.Fplll.Types

Methods

bottom :: LLLFlags

BoundedLattice LLLFlags 
Instance details

Defined in Math.Lattices.Fplll.Types

BoundedMeetSemiLattice LLLFlags 
Instance details

Defined in Math.Lattices.Fplll.Types

Methods

top :: LLLFlags

JoinSemiLattice LLLFlags 
Instance details

Defined in Math.Lattices.Fplll.Types

Lattice LLLFlags 
Instance details

Defined in Math.Lattices.Fplll.Types

MeetSemiLattice LLLFlags 
Instance details

Defined in Math.Lattices.Fplll.Types

BiHeytingAlgebra LLLFlags 
Instance details

Defined in Math.Lattices.Fplll.Types

BooleanAlgebra LLLFlags 
Instance details

Defined in Math.Lattices.Fplll.Types

CoHeytingAlgebra LLLFlags 
Instance details

Defined in Math.Lattices.Fplll.Types

DistributiveLattice LLLFlags 
Instance details

Defined in Math.Lattices.Fplll.Types

HeytingAlgebra LLLFlags 
Instance details

Defined in Math.Lattices.Fplll.Types

LowerBoundedDistributiveLattice LLLFlags 
Instance details

Defined in Math.Lattices.Fplll.Types

LowerBoundedLattice LLLFlags 
Instance details

Defined in Math.Lattices.Fplll.Types

SemiCoHeytingAlgebra LLLFlags 
Instance details

Defined in Math.Lattices.Fplll.Types

SemiHeytingAlgebra LLLFlags 
Instance details

Defined in Math.Lattices.Fplll.Types

UpperBoundedDistributiveLattice LLLFlags 
Instance details

Defined in Math.Lattices.Fplll.Types

UpperBoundedLattice LLLFlags 
Instance details

Defined in Math.Lattices.Fplll.Types

allocaMpz :: Int -> (Ptr MPZ -> IO a) -> IO a Source #

peekBasis :: Int -> Int -> Ptr MPZ -> IO [[Integer]] Source #

pokeBasis :: Int -> Int -> Ptr MPZ -> [[Integer]] -> IO () Source #

allocaAndPokeBasis :: [[Integer]] -> (Int -> Int -> Ptr MPZ -> IO a) -> IO a Source #

allEqual :: Eq a => [a] -> Bool Source #

c_lllDefaultDelta :: Ptr CDouble Source #

c_lllDefaultEta :: Ptr CDouble Source #

c_lmWrapper :: Ptr CInt Source #

c_lmProved :: Ptr CInt Source #

c_lmHeuristic :: Ptr CInt Source #

c_lmFast :: Ptr CInt Source #

c_lllMethodStr :: Ptr (Ptr CString) Source #

c_lllVerbose :: Ptr CInt Source #

c_lllEarlyRed :: Ptr CInt Source #

c_lllSiegel :: Ptr CInt Source #

c_lllDefault :: Ptr CInt Source #

c_ftDefault :: Ptr CInt Source #

c_ftDouble :: Ptr CInt Source #

c_ftLongDouble :: Ptr CInt Source #

c_ftDpe :: Ptr CInt Source #

c_ftDD :: Ptr CInt Source #

c_ftQD :: Ptr CInt Source #

c_ftMpfr :: Ptr CInt Source #

c_floatTypeStr :: Ptr (Ptr CString) Source #

c_redSuccess :: Ptr CInt Source #

c_redStatusStr :: Ptr (Ptr CString) Source #

c_lll_reduction :: CInt -> CInt -> Ptr MPZ -> CDouble -> CDouble -> LLLMethod -> FloatType -> CInt -> LLLFlags -> IO RedStatus Source #

c_lll_reduction_u_id :: CInt -> CInt -> Ptr MPZ -> Ptr MPZ -> CDouble -> CDouble -> LLLMethod -> FloatType -> CInt -> LLLFlags -> IO RedStatus Source #

c_lll_reduction_uinv_id :: CInt -> CInt -> Ptr MPZ -> Ptr MPZ -> Ptr MPZ -> CDouble -> CDouble -> LLLMethod -> FloatType -> CInt -> LLLFlags -> IO RedStatus Source #