| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Predicate.Data.Bits
Description
promoted bit manipulation functions
Documentation
data p .&. q infixl 7 Source #
bitwise and similar to .&.
>>>pz @(344 .&. 123) ()Val 88
data p .^. q infixl 5 Source #
bitwise xor similar to xor
>>>pz @(344 .^. 123) ()Val 291
shift by p using q: similar to flipped version of shift
>>>pz @(BitShift 1 7) ()Val 14
>>>pz @(BitShift 1 Id) 123Val 246
shift left by p using q: similar to flipped version of shiftL
>>>pz @(BitShiftL 1 Id) 123Val 246
shift right by p using q: similar to flipped version of shiftR
>>>pz @(BitShiftR 1 Id) 123Val 61
rotate by p using q: similar to flipped version of rotate
>>>pz @(BitRotate 2 Id) 7Val 28
data BitRotateL p q Source #
rotate left by p using q: similar to flipped version of rotateL
>>>pz @(BitRotateL 2 Id) 7Val 28
Instances
| P (BitRotateLT p q) x => P (BitRotateL p q :: Type) x Source # | |
Defined in Predicate.Data.Bits Associated Types type PP (BitRotateL p q) x Source # Methods eval :: MonadEval m => proxy (BitRotateL p q) -> POpts -> x -> m (TT (PP (BitRotateL p q) x)) Source # | |
| Show (BitRotateL p q) Source # | |
Defined in Predicate.Data.Bits Methods showsPrec :: Int -> BitRotateL p q -> ShowS # show :: BitRotateL p q -> String # showList :: [BitRotateL p q] -> ShowS # | |
| type PP (BitRotateL p q :: Type) x Source # | |
Defined in Predicate.Data.Bits | |
data BitRotateR p q Source #
rotate right by p using q: similar to flipped version of rotateR
>>>pz @(BitRotateR 2 Id) 7Val 1
Instances
| P (BitRotateRT p q) x => P (BitRotateR p q :: Type) x Source # | |
Defined in Predicate.Data.Bits Associated Types type PP (BitRotateR p q) x Source # Methods eval :: MonadEval m => proxy (BitRotateR p q) -> POpts -> x -> m (TT (PP (BitRotateR p q) x)) Source # | |
| Show (BitRotateR p q) Source # | |
Defined in Predicate.Data.Bits Methods showsPrec :: Int -> BitRotateR p q -> ShowS # show :: BitRotateR p q -> String # showList :: [BitRotateR p q] -> ShowS # | |
| type PP (BitRotateR p q :: Type) x Source # | |
Defined in Predicate.Data.Bits | |
set the bit at p using q: similar to flipped version of setBit
>>>pz @(BitSet 0 Id) 8Val 9
data BitComplement p q Source #
complement the bit at p using q: similar to flipped version of complementBit
>>>pz @(BitComplement 1 Id) 7Val 5
Instances
| P (BitComplementT p q) x => P (BitComplement p q :: Type) x Source # | |
Defined in Predicate.Data.Bits Associated Types type PP (BitComplement p q) x Source # Methods eval :: MonadEval m => proxy (BitComplement p q) -> POpts -> x -> m (TT (PP (BitComplement p q) x)) Source # | |
| Show (BitComplement p q) Source # | |
Defined in Predicate.Data.Bits Methods showsPrec :: Int -> BitComplement p q -> ShowS # show :: BitComplement p q -> String # showList :: [BitComplement p q] -> ShowS # | |
| type PP (BitComplement p q :: Type) x Source # | |
Defined in Predicate.Data.Bits | |
clear the bit at p using q: similar to flipped version of clearBit
>>>pz @(BitClear 2 Id) 7Val 3
count number of bits at p: similar to popCount
>>>pz @(PopCount Id) 7Val 3
>>>pz @(PopCount Id) 8Val 1
>>>pz @(PopCount Id) (-7)Val (-3)
test the bit at p using q: similar to flipped version of testBit
>>>pz @(TestBit 2 Id) 7Val True
>>>pz @(TestBit 2 Id) 8Val False
create a Bits for type t with the bit at p@ and all the others set to zero: similar to bit
>>>pz @(Bit Int Id) 0Val 1
>>>pz @(Bit Int Id) 3Val 8