bin-0.1.1: Bin: binary natural numbers.
Safe HaskellSafe
LanguageHaskell2010

Data.Wrd

Description

Fixed-Wrdth (unsigned) integers.

Synopsis

Documentation

data Wrd (n :: Nat) where Source #

Fixed-width unsigned integers, Wrds for short.

The number is thought to be stored in big-endian format, i.e. most-significant bit first. (as in binary literals).

Constructors

WE :: Wrd 'Z 
W0 :: Wrd n -> Wrd ('S n) 
W1 :: Wrd n -> Wrd ('S n) 

Instances

Instances details
SNatI n => Bounded (Wrd n) Source # 
Instance details

Defined in Data.Wrd

Methods

minBound :: Wrd n #

maxBound :: Wrd n #

Eq (Wrd n) Source # 
Instance details

Defined in Data.Wrd

Methods

(==) :: Wrd n -> Wrd n -> Bool #

(/=) :: Wrd n -> Wrd n -> Bool #

SNatI n => Num (Wrd n) Source # 
Instance details

Defined in Data.Wrd

Methods

(+) :: Wrd n -> Wrd n -> Wrd n #

(-) :: Wrd n -> Wrd n -> Wrd n #

(*) :: Wrd n -> Wrd n -> Wrd n #

negate :: Wrd n -> Wrd n #

abs :: Wrd n -> Wrd n #

signum :: Wrd n -> Wrd n #

fromInteger :: Integer -> Wrd n #

Ord (Wrd n) Source # 
Instance details

Defined in Data.Wrd

Methods

compare :: Wrd n -> Wrd n -> Ordering #

(<) :: Wrd n -> Wrd n -> Bool #

(<=) :: Wrd n -> Wrd n -> Bool #

(>) :: Wrd n -> Wrd n -> Bool #

(>=) :: Wrd n -> Wrd n -> Bool #

max :: Wrd n -> Wrd n -> Wrd n #

min :: Wrd n -> Wrd n -> Wrd n #

Show (Wrd n) Source #

Wrd is printed as a binary literal.

>>> let i = W1 $ W0 $ W1 $ W0 WE
>>> i
0b1010
>>> explicitShow i
"W1 $ W0 $ W1 $ W0 WE"

At the time being, there is no Num instance.

Instance details

Defined in Data.Wrd

Methods

showsPrec :: Int -> Wrd n -> ShowS #

show :: Wrd n -> String #

showList :: [Wrd n] -> ShowS #

SNatI n => Function (Wrd n) Source # 
Instance details

Defined in Data.Wrd

Methods

function :: (Wrd n -> b) -> Wrd n :-> b #

SNatI n => Arbitrary (Wrd n) Source # 
Instance details

Defined in Data.Wrd

Methods

arbitrary :: Gen (Wrd n) #

shrink :: Wrd n -> [Wrd n] #

CoArbitrary (Wrd n) Source # 
Instance details

Defined in Data.Wrd

Methods

coarbitrary :: Wrd n -> Gen b -> Gen b #

SNatI n => Bits (Wrd n) Source #
>>> let u = W0 $ W0 $ W1 $ W1 WE
>>> let v = W0 $ W1 $ W0 $ W1 WE
>>> (u, v)
(0b0011,0b0101)
>>> (complement u, complement v)
(0b1100,0b1010)
>>> (u .&. v, u .|. v, u `xor` v)
(0b0001,0b0111,0b0110)
>>> (shiftR v 1, shiftL v 1)
(0b0010,0b1010)
>>> (rotateR u 1, rotateL u 3)
(0b1001,0b1001)
>>> popCount u
2
Instance details

Defined in Data.Wrd

Methods

(.&.) :: Wrd n -> Wrd n -> Wrd n #

(.|.) :: Wrd n -> Wrd n -> Wrd n #

xor :: Wrd n -> Wrd n -> Wrd n #

complement :: Wrd n -> Wrd n #

shift :: Wrd n -> Int -> Wrd n #

rotate :: Wrd n -> Int -> Wrd n #

zeroBits :: Wrd n #

bit :: Int -> Wrd n #

setBit :: Wrd n -> Int -> Wrd n #

clearBit :: Wrd n -> Int -> Wrd n #

complementBit :: Wrd n -> Int -> Wrd n #

testBit :: Wrd n -> Int -> Bool #

bitSizeMaybe :: Wrd n -> Maybe Int #

bitSize :: Wrd n -> Int #

isSigned :: Wrd n -> Bool #

shiftL :: Wrd n -> Int -> Wrd n #

unsafeShiftL :: Wrd n -> Int -> Wrd n #

shiftR :: Wrd n -> Int -> Wrd n #

unsafeShiftR :: Wrd n -> Int -> Wrd n #

rotateL :: Wrd n -> Int -> Wrd n #

rotateR :: Wrd n -> Int -> Wrd n #

popCount :: Wrd n -> Int #

SNatI n => FiniteBits (Wrd n) Source # 
Instance details

Defined in Data.Wrd

NFData (Wrd n) Source # 
Instance details

Defined in Data.Wrd

Methods

rnf :: Wrd n -> () #

Hashable (Wrd n) Source # 
Instance details

Defined in Data.Wrd

Methods

hashWithSalt :: Int -> Wrd n -> Int #

hash :: Wrd n -> Int #

Showing

explicitShow :: Wrd n -> String Source #

show displaying a structure of Wrd n

>>> explicitShow WE
"WE"
>>> explicitShow $ W0 WE
"W0 WE"
>>> explicitShow $ W1 $ W0 $ W1 $ W0 WE
"W1 $ W0 $ W1 $ W0 WE"

explicitShowsPrec :: Int -> Wrd n -> ShowS Source #

showsPrec displaying a structure of Wrd n.

>>> explicitShowsPrec 0 (W0 WE) ""
"W0 WE"
>>> explicitShowsPrec 1 (W0 WE) ""
"(W0 WE)"

Conversions

toNatural :: Wrd n -> Natural Source #

Convert to Natural number

>>> let u = W0 $ W1 $ W1 $ W1 $ W0 $ W1 $ W0 WE
>>> u
0b0111010
>>> toNatural u
58
>>> map toNatural (universe :: [Wrd N.Nat3])
[0,1,2,3,4,5,6,7]

Universe

universe :: forall n. SNatI n => [Wrd n] Source #

All values, i.e. universe of Wrd .

>>> universe :: [Wrd 'Z]
[WE]
>>> universe :: [Wrd N.Nat3]
[0b000,0b001,0b010,0b011,0b100,0b101,0b110,0b111]

Bits

We have implementation of some Bits members, which doesn't need SNatI constraint.

xor :: Wrd n -> Wrd n -> Wrd n Source #

(.&.) :: Wrd n -> Wrd n -> Wrd n Source #

(.|.) :: Wrd n -> Wrd n -> Wrd n Source #

shiftR :: Wrd n -> Int -> Wrd n Source #

shiftL :: Wrd n -> Int -> Wrd n Source #

rotateL :: Wrd n -> Int -> Wrd n Source #

rotateR :: Wrd n -> Int -> Wrd n Source #

setBit :: Wrd n -> Int -> Wrd n Source #

clearBit :: Wrd n -> Int -> Wrd n Source #

testBit :: Wrd n -> Int -> Bool Source #

Extras

shiftL1 :: Wrd n -> Wrd n Source #

shiftR1 :: Wrd n -> Wrd n Source #

rotateL1 :: Wrd n -> Wrd n Source #

rotateR1 :: Wrd n -> Wrd n Source #