accelerate-bignum-0.3.0.0: Fixed-length large integer arithmetic for Accelerate
Copyright[2016..2020] Trevor L. McDonell
LicenseBSD3
MaintainerTrevor L. McDonell <trevor.mcdonell@gmail.com>
Stabilityexperimental
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Data.Array.Accelerate.Data.BigInt

Contents

Description

Fixed length signed integer types

Synopsis

Documentation

Internals

data BigInt hi lo Source #

Large integers of fixed size represented as separate (signed) high and (unsigned) low words.

Constructors

I2 !hi !lo 

Instances

Instances details
FromIntegral Int Int512 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int Int256 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int Int224 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int Int192 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int Int160 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int Int128 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int Int96 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Methods

fromIntegral :: Exp Int -> Exp Int96 #

FromIntegral Int32 Int512 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int32 Int256 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int32 Int224 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int32 Int192 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int32 Int160 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int32 Int128 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int32 Int96 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int64 Int512 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int64 Int256 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int64 Int224 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int64 Int192 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int64 Int160 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int64 Int128 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int64 Int96 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word Int512 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word Int256 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word Int224 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word Int192 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word Int160 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word Int128 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word Int96 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word32 Int512 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word32 Int256 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word32 Int224 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word32 Int192 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word32 Int160 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word32 Int128 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word32 Int96 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word64 Int512 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word64 Int256 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word64 Int224 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word64 Int192 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word64 Int160 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word64 Int128 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word64 Int96 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word512 Int512 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word256 Int256 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word224 Int224 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word192 Int192 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word160 Int160 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word128 Int128 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Word96 Int96 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int512 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int512 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int512 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int512 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int512 Word512 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int512 Int512 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int256 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int256 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int256 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int256 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int256 Word256 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int256 Int256 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int224 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int224 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int224 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int224 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int224 Word224 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int224 Int224 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int192 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int192 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int192 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int192 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int192 Word192 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int192 Int192 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int160 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int160 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int160 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int160 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int160 Word160 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int160 Int160 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int128 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int128 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int128 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int128 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int128 Word128 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int128 Int128 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int96 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int96 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int96 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int96 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int96 Word96 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

FromIntegral Int96 Int96 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

ToFloating Int512 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

ToFloating Int512 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

ToFloating Int512 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Methods

toFloating :: Exp Int512 -> Exp Half #

ToFloating Int256 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

ToFloating Int256 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

ToFloating Int256 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Methods

toFloating :: Exp Int256 -> Exp Half #

ToFloating Int224 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

ToFloating Int224 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

ToFloating Int224 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Methods

toFloating :: Exp Int224 -> Exp Half #

ToFloating Int192 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

ToFloating Int192 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

ToFloating Int192 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Methods

toFloating :: Exp Int192 -> Exp Half #

ToFloating Int160 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

ToFloating Int160 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

ToFloating Int160 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Methods

toFloating :: Exp Int160 -> Exp Half #

ToFloating Int128 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

ToFloating Int128 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

ToFloating Int128 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Methods

toFloating :: Exp Int128 -> Exp Half #

ToFloating Int96 Double Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

ToFloating Int96 Float Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Methods

toFloating :: Exp Int96 -> Exp Float #

ToFloating Int96 Half Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Methods

toFloating :: Exp Int96 -> Exp Half #

(Lift Exp a, Lift Exp b, Elt (Plain a), Elt (Plain b)) => Lift Exp (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Elt

Associated Types

type Plain (BigInt a b) #

Methods

lift :: BigInt a b -> Exp (Plain (BigInt a b)) #

(Elt a, Elt b) => Unlift Exp (BigInt (Exp a) (Exp b)) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Elt

Methods

unlift :: Exp (Plain (BigInt (Exp a) (Exp b))) -> BigInt (Exp a) (Exp b) #

(Bounded a, Bounded b, Elt (BigInt a b)) => Bounded (Exp (BigInt a b)) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Methods

minBound :: Exp (BigInt a b) #

maxBound :: Exp (BigInt a b) #

Enum (Exp Int512) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Enum (Exp Int256) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Enum (Exp Int224) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Enum (Exp Int192) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Enum (Exp Int160) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Enum (Exp Int128) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Enum (Exp Int96) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

(Integral a, Integral b, Num (BigInt a b), Eq (BigWord (Unsigned a) b), Integral (BigWord (Unsigned a) b), Num2 (Exp (BigInt a b)), Num2 (Exp (BigWord (Unsigned a) b)), BigIntCtx a b, Enum (BigInt a b)) => Integral (Exp (BigInt a b)) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Methods

quot :: Exp (BigInt a b) -> Exp (BigInt a b) -> Exp (BigInt a b) #

rem :: Exp (BigInt a b) -> Exp (BigInt a b) -> Exp (BigInt a b) #

div :: Exp (BigInt a b) -> Exp (BigInt a b) -> Exp (BigInt a b) #

mod :: Exp (BigInt a b) -> Exp (BigInt a b) -> Exp (BigInt a b) #

quotRem :: Exp (BigInt a b) -> Exp (BigInt a b) -> (Exp (BigInt a b), Exp (BigInt a b)) #

divMod :: Exp (BigInt a b) -> Exp (BigInt a b) -> (Exp (BigInt a b), Exp (BigInt a b)) #

toInteger :: Exp (BigInt a b) -> Integer #

(Num a, Ord a, Num b, Ord b, Bounded b, Num2 (Exp (BigInt a b)), Num2 (Exp (BigWord (Unsigned a) b)), Num (BigWord (Unsigned a) b), Num (BigInt a b), BigIntCtx a b) => Num (Exp (BigInt a b)) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Methods

(+) :: Exp (BigInt a b) -> Exp (BigInt a b) -> Exp (BigInt a b) #

(-) :: Exp (BigInt a b) -> Exp (BigInt a b) -> Exp (BigInt a b) #

(*) :: Exp (BigInt a b) -> Exp (BigInt a b) -> Exp (BigInt a b) #

negate :: Exp (BigInt a b) -> Exp (BigInt a b) #

abs :: Exp (BigInt a b) -> Exp (BigInt a b) #

signum :: Exp (BigInt a b) -> Exp (BigInt a b) #

fromInteger :: Integer -> Exp (BigInt a b) #

(Ord a, Num a, Num2 (Exp a), Ord (BigInt a b), Num (BigInt a b), Bits (BigInt a b), Bounded (BigWord (Unsigned a) b), Num (BigWord (Unsigned a) b), Num2 (Exp (BigWord (Unsigned a) b)), Elt (Unsigned a), Exp (Unsigned a) ~ Unsigned (Exp a), BigIntCtx a b) => Num2 (Exp (BigInt a b)) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Associated Types

type Signed (Exp (BigInt a b)) Source #

type Unsigned (Exp (BigInt a b)) Source #

Methods

signed :: Exp (BigInt a b) -> Signed (Exp (BigInt a b)) Source #

unsigned :: Exp (BigInt a b) -> Unsigned (Exp (BigInt a b)) Source #

addWithCarry :: Exp (BigInt a b) -> Exp (BigInt a b) -> (Exp (BigInt a b), Unsigned (Exp (BigInt a b))) Source #

mulWithCarry :: Exp (BigInt a b) -> Exp (BigInt a b) -> (Exp (BigInt a b), Unsigned (Exp (BigInt a b))) Source #

(Bounded a, Bounded b) => Bounded (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.BigInt

Methods

minBound :: BigInt a b #

maxBound :: BigInt a b #

(Enum a, Num a, Eq a, Enum b, Num b, Eq b, Bounded b) => Enum (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.BigInt

Methods

succ :: BigInt a b -> BigInt a b #

pred :: BigInt a b -> BigInt a b #

toEnum :: Int -> BigInt a b #

fromEnum :: BigInt a b -> Int #

enumFrom :: BigInt a b -> [BigInt a b] #

enumFromThen :: BigInt a b -> BigInt a b -> [BigInt a b] #

enumFromTo :: BigInt a b -> BigInt a b -> [BigInt a b] #

enumFromThenTo :: BigInt a b -> BigInt a b -> BigInt a b -> [BigInt a b] #

(Eq a, Eq b) => Eq (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.BigInt

Methods

(==) :: BigInt a b -> BigInt a b -> Bool #

(/=) :: BigInt a b -> BigInt a b -> Bool #

(Integral a, Integral b, Bounded b, Integral (BigWord (Unsigned a) b), Num2 (BigInt a b), Num2 (BigWord (Unsigned a) b), BigIntCtx a b) => Integral (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.BigInt

Methods

quot :: BigInt a b -> BigInt a b -> BigInt a b #

rem :: BigInt a b -> BigInt a b -> BigInt a b #

div :: BigInt a b -> BigInt a b -> BigInt a b #

mod :: BigInt a b -> BigInt a b -> BigInt a b #

quotRem :: BigInt a b -> BigInt a b -> (BigInt a b, BigInt a b) #

divMod :: BigInt a b -> BigInt a b -> (BigInt a b, BigInt a b) #

toInteger :: BigInt a b -> Integer #

(Integral a, Ord a, Integral b, Ord b, Bounded b, Ord (BigInt a b), Num (BigInt a b), Num2 (BigInt a b), Num (BigWord (Unsigned a) b), Num2 (BigWord (Unsigned a) b), BigIntCtx a b) => Num (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.BigInt

Methods

(+) :: BigInt a b -> BigInt a b -> BigInt a b #

(-) :: BigInt a b -> BigInt a b -> BigInt a b #

(*) :: BigInt a b -> BigInt a b -> BigInt a b #

negate :: BigInt a b -> BigInt a b #

abs :: BigInt a b -> BigInt a b #

signum :: BigInt a b -> BigInt a b #

fromInteger :: Integer -> BigInt a b #

(Ord a, Ord b) => Ord (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.BigInt

Methods

compare :: BigInt a b -> BigInt a b -> Ordering #

(<) :: BigInt a b -> BigInt a b -> Bool #

(<=) :: BigInt a b -> BigInt a b -> Bool #

(>) :: BigInt a b -> BigInt a b -> Bool #

(>=) :: BigInt a b -> BigInt a b -> Bool #

max :: BigInt a b -> BigInt a b -> BigInt a b #

min :: BigInt a b -> BigInt a b -> BigInt a b #

(Integral (BigInt a b), Num (BigInt a b), Ord (BigInt a b)) => Real (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.BigInt

Methods

toRational :: BigInt a b -> Rational #

Integral (BigInt a b) => Show (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.BigInt

Methods

showsPrec :: Int -> BigInt a b -> ShowS #

show :: BigInt a b -> String #

showList :: [BigInt a b] -> ShowS #

Generic (BigInt hi lo) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.BigInt

Associated Types

type Rep (BigInt hi lo) :: Type -> Type #

Methods

from :: BigInt hi lo -> Rep (BigInt hi lo) x #

to :: Rep (BigInt hi lo) x -> BigInt hi lo #

(FiniteBits a, Integral a, FromIntegral a b, FromIntegral a (Signed b), FiniteBits b, Integral b, FromIntegral b a, Bits (Signed b), Integral (Signed b), FromIntegral (Signed b) b, Num2 (Exp (BigInt a b)), Num2 (Exp (BigWord (Unsigned a) b)), Bits (BigWord (Unsigned a) b), FiniteBits (BigInt a b), BigIntCtx a b) => Bits (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Methods

(.&.) :: Exp (BigInt a b) -> Exp (BigInt a b) -> Exp (BigInt a b) #

(.|.) :: Exp (BigInt a b) -> Exp (BigInt a b) -> Exp (BigInt a b) #

xor :: Exp (BigInt a b) -> Exp (BigInt a b) -> Exp (BigInt a b) #

complement :: Exp (BigInt a b) -> Exp (BigInt a b) #

shift :: Exp (BigInt a b) -> Exp Int -> Exp (BigInt a b) #

rotate :: Exp (BigInt a b) -> Exp Int -> Exp (BigInt a b) #

zeroBits :: Exp (BigInt a b) #

bit :: Exp Int -> Exp (BigInt a b) #

setBit :: Exp (BigInt a b) -> Exp Int -> Exp (BigInt a b) #

clearBit :: Exp (BigInt a b) -> Exp Int -> Exp (BigInt a b) #

complementBit :: Exp (BigInt a b) -> Exp Int -> Exp (BigInt a b) #

testBit :: Exp (BigInt a b) -> Exp Int -> Exp Bool #

isSigned :: Exp (BigInt a b) -> Exp Bool #

shiftL :: Exp (BigInt a b) -> Exp Int -> Exp (BigInt a b) #

unsafeShiftL :: Exp (BigInt a b) -> Exp Int -> Exp (BigInt a b) #

shiftR :: Exp (BigInt a b) -> Exp Int -> Exp (BigInt a b) #

unsafeShiftR :: Exp (BigInt a b) -> Exp Int -> Exp (BigInt a b) #

rotateL :: Exp (BigInt a b) -> Exp Int -> Exp (BigInt a b) #

rotateR :: Exp (BigInt a b) -> Exp Int -> Exp (BigInt a b) #

popCount :: Exp (BigInt a b) -> Exp Int #

(FiniteBits a, FiniteBits b, Bits (BigInt a b), Num2 (Exp (BigInt a b)), FiniteBits (BigWord (Unsigned a) b), BigIntCtx a b) => FiniteBits (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

(Ord a, Ord b, Elt (BigInt a b)) => Ord (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Methods

(<) :: Exp (BigInt a b) -> Exp (BigInt a b) -> Exp Bool #

(>) :: Exp (BigInt a b) -> Exp (BigInt a b) -> Exp Bool #

(<=) :: Exp (BigInt a b) -> Exp (BigInt a b) -> Exp Bool #

(>=) :: Exp (BigInt a b) -> Exp (BigInt a b) -> Exp Bool #

min :: Exp (BigInt a b) -> Exp (BigInt a b) -> Exp (BigInt a b) #

max :: Exp (BigInt a b) -> Exp (BigInt a b) -> Exp (BigInt a b) #

compare :: Exp (BigInt a b) -> Exp (BigInt a b) -> Exp Ordering #

(Eq a, Eq b, Elt (BigInt a b)) => Eq (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Methods

(==) :: Exp (BigInt a b) -> Exp (BigInt a b) -> Exp Bool #

(/=) :: Exp (BigInt a b) -> Exp (BigInt a b) -> Exp Bool #

(Elt a, Elt b) => Elt (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Elt

Associated Types

type EltR (BigInt a b)

Methods

eltR :: TypeR (EltR (BigInt a b))

tagsR :: [TagR (EltR (BigInt a b))]

fromElt :: BigInt a b -> EltR (BigInt a b)

toElt :: EltR (BigInt a b) -> BigInt a b

(FiniteBits a, Integral a, FiniteBits b, Integral b, FiniteBits (BigInt a b), Num2 (BigInt a b), Num2 (BigWord (Unsigned a) b), Bits (BigWord (Unsigned a) b), Integral (Signed b), Bits (Signed b), BigIntCtx a b) => Bits (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.BigInt

Methods

(.&.) :: BigInt a b -> BigInt a b -> BigInt a b #

(.|.) :: BigInt a b -> BigInt a b -> BigInt a b #

xor :: BigInt a b -> BigInt a b -> BigInt a b #

complement :: BigInt a b -> BigInt a b #

shift :: BigInt a b -> Int -> BigInt a b #

rotate :: BigInt a b -> Int -> BigInt a b #

zeroBits :: BigInt a b #

bit :: Int -> BigInt a b #

setBit :: BigInt a b -> Int -> BigInt a b #

clearBit :: BigInt a b -> Int -> BigInt a b #

complementBit :: BigInt a b -> Int -> BigInt a b #

testBit :: BigInt a b -> Int -> Bool #

bitSizeMaybe :: BigInt a b -> Maybe Int #

bitSize :: BigInt a b -> Int #

isSigned :: BigInt a b -> Bool #

shiftL :: BigInt a b -> Int -> BigInt a b #

unsafeShiftL :: BigInt a b -> Int -> BigInt a b #

shiftR :: BigInt a b -> Int -> BigInt a b #

unsafeShiftR :: BigInt a b -> Int -> BigInt a b #

rotateL :: BigInt a b -> Int -> BigInt a b #

rotateR :: BigInt a b -> Int -> BigInt a b #

popCount :: BigInt a b -> Int #

(FiniteBits a, FiniteBits b, Bits (BigInt a b), Num2 (BigInt a b), FiniteBits (BigWord (Unsigned a) b), BigIntCtx a b) => FiniteBits (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.BigInt

(Ord a, Num a, Num2 a, Num (BigInt a b), Ord (BigInt a b), Num2 (BigInt a b), Bits (BigInt a b), Num (BigWord (Unsigned a) b), Num2 (BigWord (Unsigned a) b), Bounded (BigWord (Unsigned a) b), BigIntCtx a b, Unsigned (Unsigned a) ~ Unsigned a) => Num2 (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.BigInt

Associated Types

type Signed (BigInt a b) Source #

type Unsigned (BigInt a b) Source #

Methods

signed :: BigInt a b -> Signed (BigInt a b) Source #

unsigned :: BigInt a b -> Unsigned (BigInt a b) Source #

addWithCarry :: BigInt a b -> BigInt a b -> (BigInt a b, Unsigned (BigInt a b)) Source #

mulWithCarry :: BigInt a b -> BigInt a b -> (BigInt a b, Unsigned (BigInt a b)) Source #

type Signed (Exp (BigInt a b)) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

type Signed (Exp (BigInt a b)) = Exp (BigInt a b)
type Unsigned (Exp (BigInt a b)) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

type Unsigned (Exp (BigInt a b)) = Exp (BigWord (Unsigned a) b)
type Rep (BigInt hi lo) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.BigInt

type Rep (BigInt hi lo) = D1 ('MetaData "BigInt" "Data.Array.Accelerate.Internal.BigInt" "accelerate-bignum-0.3.0.0-4G6rF62D4Q3KyuXU6S7NMs" 'False) (C1 ('MetaCons "I2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 hi) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 lo)))
type EltR (BigInt a b) 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Elt

type EltR (BigInt a b) = GEltR () (Rep (BigInt a b))
type Plain (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Elt

type Plain (BigInt a b) = BigInt (Plain a) (Plain b)
type Signed (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.BigInt

type Signed (BigInt a b) = BigInt (Signed a) b
type Unsigned (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.BigInt

type Unsigned (BigInt a b) = BigWord (Unsigned a) b

class Num2 w where Source #

Addition and multiplication with carry

Associated Types

type Signed w Source #

type Unsigned w Source #

Methods

signed :: w -> Signed w Source #

unsigned :: w -> Unsigned w Source #

addWithCarry :: w -> w -> (w, Unsigned w) Source #

mulWithCarry :: w -> w -> (w, Unsigned w) Source #

Instances

Instances details
Num2 Int8 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Num2

Associated Types

type Signed Int8 Source #

type Unsigned Int8 Source #

Num2 Int16 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Num2

Associated Types

type Signed Int16 Source #

type Unsigned Int16 Source #

Num2 Int32 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Num2

Associated Types

type Signed Int32 Source #

type Unsigned Int32 Source #

Num2 Int64 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Num2

Associated Types

type Signed Int64 Source #

type Unsigned Int64 Source #

Num2 Word8 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Num2

Associated Types

type Signed Word8 Source #

type Unsigned Word8 Source #

Num2 Word16 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Num2

Associated Types

type Signed Word16 Source #

type Unsigned Word16 Source #

Num2 Word32 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Num2

Associated Types

type Signed Word32 Source #

type Unsigned Word32 Source #

Num2 Word64 Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Num2

Associated Types

type Signed Word64 Source #

type Unsigned Word64 Source #

Num2 (Exp Int8) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Associated Types

type Signed (Exp Int8) Source #

type Unsigned (Exp Int8) Source #

Num2 (Exp Int16) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Associated Types

type Signed (Exp Int16) Source #

type Unsigned (Exp Int16) Source #

Num2 (Exp Int32) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Associated Types

type Signed (Exp Int32) Source #

type Unsigned (Exp Int32) Source #

Num2 (Exp Int64) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Associated Types

type Signed (Exp Int64) Source #

type Unsigned (Exp Int64) Source #

Num2 (Exp Word8) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Associated Types

type Signed (Exp Word8) Source #

type Unsigned (Exp Word8) Source #

Num2 (Exp Word16) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Associated Types

type Signed (Exp Word16) Source #

type Unsigned (Exp Word16) Source #

Num2 (Exp Word32) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Associated Types

type Signed (Exp Word32) Source #

type Unsigned (Exp Word32) Source #

Num2 (Exp Word64) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Associated Types

type Signed (Exp Word64) Source #

type Unsigned (Exp Word64) Source #

(Ord a, Num a, Num2 (Exp a), Ord (BigInt a b), Num (BigInt a b), Bits (BigInt a b), Bounded (BigWord (Unsigned a) b), Num (BigWord (Unsigned a) b), Num2 (Exp (BigWord (Unsigned a) b)), Elt (Unsigned a), Exp (Unsigned a) ~ Unsigned (Exp a), BigIntCtx a b) => Num2 (Exp (BigInt a b)) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Associated Types

type Signed (Exp (BigInt a b)) Source #

type Unsigned (Exp (BigInt a b)) Source #

Methods

signed :: Exp (BigInt a b) -> Signed (Exp (BigInt a b)) Source #

unsigned :: Exp (BigInt a b) -> Unsigned (Exp (BigInt a b)) Source #

addWithCarry :: Exp (BigInt a b) -> Exp (BigInt a b) -> (Exp (BigInt a b), Unsigned (Exp (BigInt a b))) Source #

mulWithCarry :: Exp (BigInt a b) -> Exp (BigInt a b) -> (Exp (BigInt a b), Unsigned (Exp (BigInt a b))) Source #

(Integral a, FiniteBits a, FromIntegral a b, Num2 (Exp a), Integral b, FiniteBits b, FromIntegral b a, Num2 (Exp b), Elt (Signed a), Elt (BigInt (Signed a) b), Exp (Signed a) ~ Signed (Exp a), BigWordCtx a b) => Num2 (Exp (BigWord a b)) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.Orphans.Base

Associated Types

type Signed (Exp (BigWord a b)) Source #

type Unsigned (Exp (BigWord a b)) Source #

Methods

signed :: Exp (BigWord a b) -> Signed (Exp (BigWord a b)) Source #

unsigned :: Exp (BigWord a b) -> Unsigned (Exp (BigWord a b)) Source #

addWithCarry :: Exp (BigWord a b) -> Exp (BigWord a b) -> (Exp (BigWord a b), Unsigned (Exp (BigWord a b))) Source #

mulWithCarry :: Exp (BigWord a b) -> Exp (BigWord a b) -> (Exp (BigWord a b), Unsigned (Exp (BigWord a b))) Source #

(Ord a, Num a, Num2 a, Num (BigInt a b), Ord (BigInt a b), Num2 (BigInt a b), Bits (BigInt a b), Num (BigWord (Unsigned a) b), Num2 (BigWord (Unsigned a) b), Bounded (BigWord (Unsigned a) b), BigIntCtx a b, Unsigned (Unsigned a) ~ Unsigned a) => Num2 (BigInt a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.BigInt

Associated Types

type Signed (BigInt a b) Source #

type Unsigned (BigInt a b) Source #

Methods

signed :: BigInt a b -> Signed (BigInt a b) Source #

unsigned :: BigInt a b -> Unsigned (BigInt a b) Source #

addWithCarry :: BigInt a b -> BigInt a b -> (BigInt a b, Unsigned (BigInt a b)) Source #

mulWithCarry :: BigInt a b -> BigInt a b -> (BigInt a b, Unsigned (BigInt a b)) Source #

(Integral a, FiniteBits a, Num2 a, Integral b, FiniteBits b, Num2 b, BigWordCtx a b) => Num2 (BigWord a b) Source # 
Instance details

Defined in Data.Array.Accelerate.Internal.BigWord

Associated Types

type Signed (BigWord a b) Source #

type Unsigned (BigWord a b) Source #

Methods

signed :: BigWord a b -> Signed (BigWord a b) Source #

unsigned :: BigWord a b -> Unsigned (BigWord a b) Source #

addWithCarry :: BigWord a b -> BigWord a b -> (BigWord a b, Unsigned (BigWord a b)) Source #

mulWithCarry :: BigWord a b -> BigWord a b -> (BigWord a b, Unsigned (BigWord a b)) Source #