hgmp-0.1.1: Haskell interface to GMP

Safe HaskellNone
LanguageHaskell2010

Numeric.GMP.Types

Description

GMP types.

Synopsis

Documentation

data MPZ Source #

mpz_t

Constructors

MPZ 

Fields

Instances

Storable MPZ Source # 

Methods

sizeOf :: MPZ -> Int #

alignment :: MPZ -> Int #

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

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

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

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

peek :: Ptr MPZ -> IO MPZ #

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

data MPQ Source #

mpq_t

Constructors

MPQ 

Fields

Instances

Storable MPQ Source # 

Methods

sizeOf :: MPQ -> Int #

alignment :: MPQ -> Int #

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

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

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

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

peek :: Ptr MPQ -> IO MPQ #

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

mpq_numref :: Ptr MPQ -> Ptr MPZ Source #

Get pointers to numerator and denominator (these are macros in the C API).

mpq_denref :: Ptr MPQ -> Ptr MPZ Source #

Get pointers to numerator and denominator (these are macros in the C API).

data MPF Source #

mpf_t

Constructors

MPF 

Fields

Instances

Storable MPF Source # 

Methods

sizeOf :: MPF -> Int #

alignment :: MPF -> Int #

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

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

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

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

peek :: Ptr MPF -> IO MPF #

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

newtype MPLimb Source #

mp_limb_t

Constructors

MPLimb Word64 

Instances

Bounded MPLimb Source # 
Enum MPLimb Source # 
Eq MPLimb Source # 

Methods

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

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

Integral MPLimb Source # 
Data MPLimb Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MPLimb -> c MPLimb #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MPLimb #

toConstr :: MPLimb -> Constr #

dataTypeOf :: MPLimb -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MPLimb) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MPLimb) #

gmapT :: (forall b. Data b => b -> b) -> MPLimb -> MPLimb #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MPLimb -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MPLimb -> r #

gmapQ :: (forall d. Data d => d -> u) -> MPLimb -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MPLimb -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MPLimb -> m MPLimb #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MPLimb -> m MPLimb #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MPLimb -> m MPLimb #

Num MPLimb Source # 
Ord MPLimb Source # 
Read MPLimb Source # 
Real MPLimb Source # 
Show MPLimb Source # 
Ix MPLimb Source # 
Storable MPLimb Source # 
Bits MPLimb Source # 
FiniteBits MPLimb Source # 

newtype MPLimbSigned Source #

mp_limb_signed_t

Constructors

MPLimbSigned Int64 

Instances

Bounded MPLimbSigned Source # 
Enum MPLimbSigned Source # 
Eq MPLimbSigned Source # 
Integral MPLimbSigned Source # 
Data MPLimbSigned Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MPLimbSigned -> c MPLimbSigned #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MPLimbSigned #

toConstr :: MPLimbSigned -> Constr #

dataTypeOf :: MPLimbSigned -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MPLimbSigned) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MPLimbSigned) #

gmapT :: (forall b. Data b => b -> b) -> MPLimbSigned -> MPLimbSigned #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MPLimbSigned -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MPLimbSigned -> r #

gmapQ :: (forall d. Data d => d -> u) -> MPLimbSigned -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MPLimbSigned -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MPLimbSigned -> m MPLimbSigned #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MPLimbSigned -> m MPLimbSigned #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MPLimbSigned -> m MPLimbSigned #

Num MPLimbSigned Source # 
Ord MPLimbSigned Source # 
Read MPLimbSigned Source # 
Real MPLimbSigned Source # 
Show MPLimbSigned Source # 
Ix MPLimbSigned Source # 
Storable MPLimbSigned Source # 
Bits MPLimbSigned Source # 
FiniteBits MPLimbSigned Source # 

newtype MPSize Source #

mp_size_t

Constructors

MPSize Int64 

Instances

Bounded MPSize Source # 
Enum MPSize Source # 
Eq MPSize Source # 

Methods

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

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

Integral MPSize Source # 
Data MPSize Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MPSize -> c MPSize #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MPSize #

toConstr :: MPSize -> Constr #

dataTypeOf :: MPSize -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MPSize) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MPSize) #

gmapT :: (forall b. Data b => b -> b) -> MPSize -> MPSize #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MPSize -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MPSize -> r #

gmapQ :: (forall d. Data d => d -> u) -> MPSize -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MPSize -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MPSize -> m MPSize #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MPSize -> m MPSize #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MPSize -> m MPSize #

Num MPSize Source # 
Ord MPSize Source # 
Read MPSize Source # 
Real MPSize Source # 
Show MPSize Source # 
Ix MPSize Source # 
Storable MPSize Source # 
Bits MPSize Source # 
FiniteBits MPSize Source # 

newtype MPExp Source #

mp_exp_t

Constructors

MPExp Int64 

Instances

Bounded MPExp Source # 
Enum MPExp Source # 
Eq MPExp Source # 

Methods

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

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

Integral MPExp Source # 
Data MPExp Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MPExp -> c MPExp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MPExp #

toConstr :: MPExp -> Constr #

dataTypeOf :: MPExp -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MPExp) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MPExp) #

gmapT :: (forall b. Data b => b -> b) -> MPExp -> MPExp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MPExp -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MPExp -> r #

gmapQ :: (forall d. Data d => d -> u) -> MPExp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MPExp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MPExp -> m MPExp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MPExp -> m MPExp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MPExp -> m MPExp #

Num MPExp Source # 
Ord MPExp Source # 

Methods

compare :: MPExp -> MPExp -> Ordering #

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

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

(>) :: MPExp -> MPExp -> Bool #

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

max :: MPExp -> MPExp -> MPExp #

min :: MPExp -> MPExp -> MPExp #

Read MPExp Source # 
Real MPExp Source # 

Methods

toRational :: MPExp -> Rational #

Show MPExp Source # 

Methods

showsPrec :: Int -> MPExp -> ShowS #

show :: MPExp -> String #

showList :: [MPExp] -> ShowS #

Ix MPExp Source # 
Storable MPExp Source # 

Methods

sizeOf :: MPExp -> Int #

alignment :: MPExp -> Int #

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

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

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

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

peek :: Ptr MPExp -> IO MPExp #

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

Bits MPExp Source # 
FiniteBits MPExp Source # 

newtype MPBitCnt Source #

mp_bitcnt_t

Constructors

MPBitCnt Word64 

Instances

Bounded MPBitCnt Source # 
Enum MPBitCnt Source # 
Eq MPBitCnt Source # 
Integral MPBitCnt Source # 
Data MPBitCnt Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MPBitCnt -> c MPBitCnt #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MPBitCnt #

toConstr :: MPBitCnt -> Constr #

dataTypeOf :: MPBitCnt -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MPBitCnt) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MPBitCnt) #

gmapT :: (forall b. Data b => b -> b) -> MPBitCnt -> MPBitCnt #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MPBitCnt -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MPBitCnt -> r #

gmapQ :: (forall d. Data d => d -> u) -> MPBitCnt -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MPBitCnt -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MPBitCnt -> m MPBitCnt #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MPBitCnt -> m MPBitCnt #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MPBitCnt -> m MPBitCnt #

Num MPBitCnt Source # 
Ord MPBitCnt Source # 
Read MPBitCnt Source # 
Real MPBitCnt Source # 
Show MPBitCnt Source # 
Ix MPBitCnt Source # 
Storable MPBitCnt Source # 
Bits MPBitCnt Source # 
FiniteBits MPBitCnt Source # 

newtype GMPRandAlg Source #

gmp_randalg_t

Constructors

GMPRandAlg Word32 

Instances

Bounded GMPRandAlg Source # 
Enum GMPRandAlg Source # 
Eq GMPRandAlg Source # 
Integral GMPRandAlg Source # 
Data GMPRandAlg Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GMPRandAlg -> c GMPRandAlg #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GMPRandAlg #

toConstr :: GMPRandAlg -> Constr #

dataTypeOf :: GMPRandAlg -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GMPRandAlg) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GMPRandAlg) #

gmapT :: (forall b. Data b => b -> b) -> GMPRandAlg -> GMPRandAlg #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GMPRandAlg -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GMPRandAlg -> r #

gmapQ :: (forall d. Data d => d -> u) -> GMPRandAlg -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GMPRandAlg -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GMPRandAlg -> m GMPRandAlg #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GMPRandAlg -> m GMPRandAlg #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GMPRandAlg -> m GMPRandAlg #

Num GMPRandAlg Source # 
Ord GMPRandAlg Source # 
Read GMPRandAlg Source # 
Real GMPRandAlg Source # 
Show GMPRandAlg Source # 
Ix GMPRandAlg Source # 
Storable GMPRandAlg Source # 
Bits GMPRandAlg Source # 
FiniteBits GMPRandAlg Source #