Safe Haskell | None |
---|---|
Language | Haskell2010 |
Fixed-Wrd
th (unsigned) integers.
Synopsis
- data Wrd (n :: Nat) where
- explicitShow :: Wrd n -> String
- explicitShowsPrec :: Int -> Wrd n -> ShowS
- toNatural :: Wrd n -> Natural
- universe :: forall n. SNatI n => [Wrd n]
- xor :: Wrd n -> Wrd n -> Wrd n
- (.&.) :: Wrd n -> Wrd n -> Wrd n
- (.|.) :: Wrd n -> Wrd n -> Wrd n
- complement :: Wrd n -> Wrd n
- complement2 :: Wrd n -> Wrd n
- shiftR :: Wrd n -> Int -> Wrd n
- shiftL :: Wrd n -> Int -> Wrd n
- rotateL :: Wrd n -> Int -> Wrd n
- rotateR :: Wrd n -> Int -> Wrd n
- popCount :: Wrd n -> Int
- setBit :: Wrd n -> Int -> Wrd n
- clearBit :: Wrd n -> Int -> Wrd n
- complementBit :: Wrd n -> Int -> Wrd n
- testBit :: Wrd n -> Int -> Bool
- shiftL1 :: Wrd n -> Wrd n
- shiftR1 :: Wrd n -> Wrd n
- rotateL1 :: Wrd n -> Wrd n
- rotateR1 :: Wrd n -> Wrd n
Documentation
data Wrd (n :: Nat) where Source #
Fixed-width unsigned integers, Wrd
s for short.
The number is thought to be stored in big-endian format, i.e. most-significant bit first. (as in binary literals).
Instances
SNatI n => Bounded (Wrd n) Source # | |
Eq (Wrd n) Source # | |
SNatI n => Num (Wrd n) Source # | |
Ord (Wrd n) Source # | |
Show (Wrd n) Source # |
At the time being, there is no |
SNatI n => Function (Wrd n) Source # | |
SNatI n => Arbitrary (Wrd n) Source # | |
CoArbitrary (Wrd n) Source # | |
SNatI n => Bits (Wrd n) Source # |
|
Defined in Data.Wrd (.&.) :: 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 # 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 # 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 # | |
SNatI n => FiniteBits (Wrd n) Source # | |
Defined in Data.Wrd finiteBitSize :: Wrd n -> Int # countLeadingZeros :: Wrd n -> Int # countTrailingZeros :: Wrd n -> Int # | |
NFData (Wrd n) Source # | |
Hashable (Wrd n) Source # | |
Showing
explicitShow :: Wrd n -> String Source #
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.
complement :: Wrd n -> Wrd n Source #
complement2 :: Wrd n -> Wrd n Source #
complement2
w =complement
w + 1