numeric-prelude-0.4.4: An experimental alternative hierarchy of numeric type classes
Safe HaskellNone
LanguageHaskell98

Number.GaloisField2p32m5

Description

This number type is intended for tests of functions over fields, where the field elements need constant space. This way we can provide a Storable instance. For Rational this would not be possible.

However, be aware that sums of non-zero elements may yield zero. Thus division is not always defined, where it is for rational numbers.

Synopsis

Documentation

>>> import qualified Number.GaloisField2p32m5 as GF
>>> import qualified Algebra.Laws as Laws
>>> import Test.QuickCheck ((==>))
>>> import NumericPrelude.Numeric
>>> import NumericPrelude.Base
>>> import Prelude ()
>>> 
>>> gf :: GF.T -> GF.T
>>> gf = id

newtype T Source #

Laws.identity (+) zero . gf
Laws.commutative (+) . gf
Laws.associative (+) . gf
Laws.inverse (+) negate zero . gf
\x -> Laws.inverse (+) (x-) (gf x)
Laws.identity (*) one . gf
Laws.commutative (*) . gf
Laws.associative (*) . gf
\y -> gf y /= zero ==> Laws.inverse (*) recip one y
\y x -> gf y /= zero ==> Laws.inverse (*) (x/) x y

Constructors

Cons 

Fields

Instances

Instances details
Eq T Source # 
Instance details

Defined in Number.GaloisField2p32m5

Methods

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

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

Show T Source # 
Instance details

Defined in Number.GaloisField2p32m5

Methods

showsPrec :: Int -> T -> ShowS #

show :: T -> String #

showList :: [T] -> ShowS #

Arbitrary T Source # 
Instance details

Defined in Number.GaloisField2p32m5

Methods

arbitrary :: Gen T #

shrink :: T -> [T] #

Storable T Source # 
Instance details

Defined in Number.GaloisField2p32m5

Methods

sizeOf :: T -> Int #

alignment :: T -> Int #

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

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

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

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

peek :: Ptr T -> IO T #

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

C T Source # 
Instance details

Defined in Number.GaloisField2p32m5

Methods

zero :: T Source #

(+) :: T -> T -> T Source #

(-) :: T -> T -> T Source #

negate :: T -> T Source #

C T Source # 
Instance details

Defined in Number.GaloisField2p32m5

Methods

isZero :: T -> Bool Source #

C T Source # 
Instance details

Defined in Number.GaloisField2p32m5

Methods

(*) :: T -> T -> T Source #

one :: T Source #

fromInteger :: Integer -> T Source #

(^) :: T -> Integer -> T Source #

C T Source # 
Instance details

Defined in Number.GaloisField2p32m5

Methods

(/) :: T -> T -> T Source #

recip :: T -> T Source #

fromRational' :: Rational -> T Source #

(^-) :: T -> Integer -> T Source #

C T T Source # 
Instance details

Defined in Number.GaloisField2p32m5

Methods

(*>) :: T -> T -> T Source #

base :: C a => a Source #

lift2 :: (Word64 -> Word64 -> Word64) -> T -> T -> T Source #

lift2Integer :: (Int64 -> Int64 -> Int64) -> T -> T -> T Source #