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

Safe HaskellNone
LanguageHaskell2010

Math.Lattices.Fplll.Types

Contents

Synopsis

Documentation

data LLLMethod Source #

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 ()

lmWrapper :: LLLMethod Source #

Automatically select the LLL implementation.

lmProved :: LLLMethod Source #

Use a slower method that has proven precision.

lmHeuristic :: LLLMethod Source #

Use the heuristic method.

lmFast :: LLLMethod Source #

Use the fast but less precise LLL method.

data FloatType Source #

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 ()

ftDefault :: FloatType Source #

Automatically select floating point type.

ftDouble :: FloatType Source #

Use double precision.

ftLongDouble :: FloatType Source #

Use the long double type.

ftDpe :: FloatType Source #

Use DPE (Double Plus Exponent) floating point representation, which can represent values with extra large exponents.

ftDD :: FloatType Source #

Use double-double arithmetic, where each value is represented as the sum of two double values, representing the most and least significant bits, respectively.

ftQD :: FloatType Source #

Use quad-double arithmetic. Values are represented as the sum of four doubles.

ftMpfr :: FloatType Source #

Use MPFR for arbitrary precision arithmetic.

data LLLFlags Source #

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

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

lllDefault :: LLLFlags Source #

Default options, i.e. no flags.

data RedStatus Source #

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 ()

redSuccess :: RedStatus Source #

Algorithm returned successfully. In some cases a RedStatus is only returned in case of an error, such as with lllReduce, in which case this value will never be returned.

Orphan instances

Show LLLFlags Source # 
Instance details

Methods

showsPrec :: Int -> LLLFlags -> ShowS

show :: LLLFlags -> String

showList :: [LLLFlags] -> ShowS

Show RedStatus Source # 
Instance details

Methods

showsPrec :: Int -> RedStatus -> ShowS

show :: RedStatus -> String

showList :: [RedStatus] -> ShowS

Show FloatType Source # 
Instance details

Methods

showsPrec :: Int -> FloatType -> ShowS

show :: FloatType -> String

showList :: [FloatType] -> ShowS

Show LLLMethod Source # 
Instance details

Methods

showsPrec :: Int -> LLLMethod -> ShowS

show :: LLLMethod -> String

showList :: [LLLMethod] -> ShowS

BoundedJoinSemiLattice LLLFlags Source # 
Instance details

Methods

bottom :: LLLFlags

BoundedLattice LLLFlags Source # 
Instance details

BoundedMeetSemiLattice LLLFlags Source # 
Instance details

Methods

top :: LLLFlags

JoinSemiLattice LLLFlags Source # 
Instance details

Lattice LLLFlags Source # 
Instance details

MeetSemiLattice LLLFlags Source # 
Instance details

BiHeytingAlgebra LLLFlags Source # 
Instance details

BooleanAlgebra LLLFlags Source # 
Instance details

CoHeytingAlgebra LLLFlags Source # 
Instance details

DistributiveLattice LLLFlags Source # 
Instance details

HeytingAlgebra LLLFlags Source # 
Instance details

LowerBoundedDistributiveLattice LLLFlags Source # 
Instance details

LowerBoundedLattice LLLFlags Source # 
Instance details

SemiCoHeytingAlgebra LLLFlags Source # 
Instance details

SemiHeytingAlgebra LLLFlags Source # 
Instance details

UpperBoundedDistributiveLattice LLLFlags Source # 
Instance details

UpperBoundedLattice LLLFlags Source # 
Instance details