Flint2-0.1.0.5: Haskell bindings for the flint library for number theory
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Number.Flint.Arb.Types

Synopsis

Documentation

data Mag Source #

Data structure containing the CMag pointer

Constructors

Mag !(ForeignPtr CMag) 

Instances

Instances details
Num Mag Source # 
Instance details

Defined in Data.Number.Flint.Arb.Mag.Instances

Methods

(+) :: Mag -> Mag -> Mag #

(-) :: Mag -> Mag -> Mag #

(*) :: Mag -> Mag -> Mag #

negate :: Mag -> Mag #

abs :: Mag -> Mag #

signum :: Mag -> Mag #

fromInteger :: Integer -> Mag #

Fractional Mag Source # 
Instance details

Defined in Data.Number.Flint.Arb.Mag.Instances

Methods

(/) :: Mag -> Mag -> Mag #

recip :: Mag -> Mag #

fromRational :: Rational -> Mag #

Show Mag Source # 
Instance details

Defined in Data.Number.Flint.Arb.Mag.Instances

Methods

showsPrec :: Int -> Mag -> ShowS #

show :: Mag -> String #

showList :: [Mag] -> ShowS #

Eq Mag Source # 
Instance details

Defined in Data.Number.Flint.Arb.Mag.Instances

Methods

(==) :: Mag -> Mag -> Bool #

(/=) :: Mag -> Mag -> Bool #

Ord Mag Source # 
Instance details

Defined in Data.Number.Flint.Arb.Mag.Instances

Methods

compare :: Mag -> Mag -> Ordering #

(<) :: Mag -> Mag -> Bool #

(<=) :: Mag -> Mag -> Bool #

(>) :: Mag -> Mag -> Bool #

(>=) :: Mag -> Mag -> Bool #

max :: Mag -> Mag -> Mag #

min :: Mag -> Mag -> Mag #

data CMag Source #

Constructors

CMag CFmpz CMpLimb 

Instances

Instances details
Storable CMag Source # 
Instance details

Defined in Data.Number.Flint.Arb.Types.FFI

Methods

sizeOf :: CMag -> Int #

alignment :: CMag -> Int #

peekElemOff :: Ptr CMag -> Int -> IO CMag #

pokeElemOff :: Ptr CMag -> Int -> CMag -> IO () #

peekByteOff :: Ptr b -> Int -> IO CMag #

pokeByteOff :: Ptr b -> Int -> CMag -> IO () #

peek :: Ptr CMag -> IO CMag #

poke :: Ptr CMag -> CMag -> IO () #

data Arf Source #

Data structure containing the CArb pointer

Constructors

Arf !(ForeignPtr CArf) 

Instances

Instances details
FlintExpression Arf Source # 
Instance details

Defined in Data.Number.Flint.Calcium.Fexpr.Instances

Methods

toFexpr :: Arf -> IO Fexpr Source #

data CArf Source #

Constructors

CFlint CArf 

Instances

Instances details
Storable CArf Source # 
Instance details

Defined in Data.Number.Flint.Arb.Types.FFI

Methods

sizeOf :: CArf -> Int #

alignment :: CArf -> Int #

peekElemOff :: Ptr CArf -> Int -> IO CArf #

pokeElemOff :: Ptr CArf -> Int -> CArf -> IO () #

peekByteOff :: Ptr b -> Int -> IO CArf #

pokeByteOff :: Ptr b -> Int -> CArf -> IO () #

peek :: Ptr CArf -> IO CArf #

poke :: Ptr CArf -> CArf -> IO () #

newtype ArfRnd Source #

Arf rounding

Constructors

ArfRnd 

Fields

Instances

Instances details
Show ArfRnd Source # 
Instance details

Defined in Data.Number.Flint.Arb.Types.FFI

Eq ArfRnd Source # 
Instance details

Defined in Data.Number.Flint.Arb.Types.FFI

Methods

(==) :: ArfRnd -> ArfRnd -> Bool #

(/=) :: ArfRnd -> ArfRnd -> Bool #

arf_rnd_up :: ArfRnd Source #

Specifies that the result of an operation should be rounded to the nearest representable number in the direction towards zero.

arf_rnd_down :: ArfRnd Source #

Specifies that the result of an operation should be rounded to the nearest representable number in the direction away from zero.

arf_rnd_floor :: ArfRnd Source #

Specifies that the result of an operation should be rounded to the nearest representable number in the direction towards minus infinity.

arf_rnd_ceil :: ArfRnd Source #

Specifies that the result of an operation should be rounded to the nearest representable number in the direction towards plus infinity.

arf_rnd_near :: ArfRnd Source #

Specifies that the result of an operation should be rounded to the nearest representable number, rounding to even if there is a tie between two values.

arf_prec_exact :: ArfRnd Source #

If passed as the precision parameter to a function, indicates that no rounding is to be performed. Warning: use of this value is unsafe in general. It must only be passed as input under the following two conditions:

  • The operation in question can inherently be viewed as an exact operation in \(\mathbb{Z}[\tfrac{1}{2}]\) for all possible inputs, provided that the precision is large enough. Examples include addition, multiplication, conversion from integer types to arbitrary-precision floating-point types, and evaluation of some integer-valued functions.
  • The exact result of the operation will certainly fit in memory. Note that, for example, adding two numbers whose exponents are far apart can easily produce an exact result that is far too large to store in memory.

The typical use case is to work with small integer values, double precision constants, and the like. It is also useful when writing test code. If in doubt, simply try with some convenient high precision instead of using this special value, and check that the result is exact.

data Arb Source #

Data structure containing the CArb pointer

Constructors

Arb !(ForeignPtr CArb) 

Instances

Instances details
Show Arb Source # 
Instance details

Defined in Data.Number.Flint.Arb.Instances

Methods

showsPrec :: Int -> Arb -> ShowS #

show :: Arb -> String #

showList :: [Arb] -> ShowS #

data CArb Source #

Constructors

CArb CMag CArf 

Instances

Instances details
Storable CArb Source # 
Instance details

Defined in Data.Number.Flint.Arb.Types.FFI

Methods

sizeOf :: CArb -> Int #

alignment :: CArb -> Int #

peekElemOff :: Ptr CArb -> Int -> IO CArb #

pokeElemOff :: Ptr CArb -> Int -> CArb -> IO () #

peekByteOff :: Ptr b -> Int -> IO CArb #

pokeByteOff :: Ptr b -> Int -> CArb -> IO () #

peek :: Ptr CArb -> IO CArb #

poke :: Ptr CArb -> CArb -> IO () #

type ArbStrOption = CULong Source #

string options

arb_str_none :: ArbStrOption Source #

Default print option

arb_str_more :: ArbStrOption Source #

If arb_str_more is added to flags, more (possibly incorrect) digits may be printed

arb_str_no_radius :: ArbStrOption Source #

If arb_str_no_radius is added to flags, the radius is not included in the output if at least 1 digit of the midpoint can be printed.

arb_str_condense :: ArbStrOption Source #

By adding a multiple m of arb_str_condense to flags, strings of more than three times m consecutive digits are condensed, only printing the leading and trailing m digits along with brackets indicating the number of digits omitted (useful when computing values to extremely high precision).

data ArbPoly Source #

Data structure containing the CArb pointer

Constructors

ArbPoly !(ForeignPtr CArbPoly) 

Instances

Instances details
Storable CArbPoly Source # 
Instance details

Defined in Data.Number.Flint.Arb.Poly.FFI

IsList ArbPoly Source # 
Instance details

Defined in Data.Number.Flint.Arb.Poly.Instances

Associated Types

type Item ArbPoly #

Show ArbPoly Source # 
Instance details

Defined in Data.Number.Flint.Arb.Poly.Instances

type Item ArbPoly Source # 
Instance details

Defined in Data.Number.Flint.Arb.Poly.Instances