predicate-typed-0.7.4.4: Predicates, Refinement types and Dsl
Safe HaskellNone
LanguageHaskell2010

Predicate.Data.Bits

Description

promoted bit manipulation functions

Synopsis

Documentation

data p .&. q infixl 7 Source #

bitwise and similar to .&.

>>> pz @(344 .&. 123) ()
Val 88

Instances

Instances details
(P p a, P q a, Show (PP p a), PP p a ~ PP q a, Bits (PP p a)) => P (p .&. q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (p .&. q) a Source #

Methods

eval :: MonadEval m => proxy (p .&. q) -> POpts -> a -> m (TT (PP (p .&. q) a)) Source #

Show (p .&. q) Source # 
Instance details

Defined in Predicate.Data.Bits

Methods

showsPrec :: Int -> (p .&. q) -> ShowS #

show :: (p .&. q) -> String #

showList :: [p .&. q] -> ShowS #

type PP (p .&. q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Bits

type PP (p .&. q :: Type) a = PP p a

data p .|. q infixl 5 Source #

bitwise or similar to .|.

>>> pz @(344 .|. 123) ()
Val 379
>>> pz @(Fst .|. Snd) (124,33)
Val 125

Instances

Instances details
(P p a, P q a, Show (PP p a), PP p a ~ PP q a, Bits (PP p a)) => P (p .|. q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (p .|. q) a Source #

Methods

eval :: MonadEval m => proxy (p .|. q) -> POpts -> a -> m (TT (PP (p .|. q) a)) Source #

Show (p .|. q) Source # 
Instance details

Defined in Predicate.Data.Bits

Methods

showsPrec :: Int -> (p .|. q) -> ShowS #

show :: (p .|. q) -> String #

showList :: [p .|. q] -> ShowS #

type PP (p .|. q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Bits

type PP (p .|. q :: Type) a = PP p a

data p .^. q infixl 5 Source #

bitwise xor similar to xor

>>> pz @(344 .^. 123) ()
Val 291

Instances

Instances details
(P p a, P q a, Show (PP p a), PP p a ~ PP q a, Bits (PP p a)) => P (p .^. q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (p .^. q) a Source #

Methods

eval :: MonadEval m => proxy (p .^. q) -> POpts -> a -> m (TT (PP (p .^. q) a)) Source #

Show (p .^. q) Source # 
Instance details

Defined in Predicate.Data.Bits

Methods

showsPrec :: Int -> (p .^. q) -> ShowS #

show :: (p .^. q) -> String #

showList :: [p .^. q] -> ShowS #

type PP (p .^. q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Bits

type PP (p .^. q :: Type) a = PP p a

data BitShift p q Source #

shift by p using q: similar to flipped version of shift

>>> pz @(BitShift 1 7) ()
Val 14
>>> pz @(BitShift 1 Id) 123
Val 246

Instances

Instances details
P (BitShiftT p q) x => P (BitShift p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (BitShift p q) x Source #

Methods

eval :: MonadEval m => proxy (BitShift p q) -> POpts -> x -> m (TT (PP (BitShift p q) x)) Source #

Show (BitShift p q) Source # 
Instance details

Defined in Predicate.Data.Bits

Methods

showsPrec :: Int -> BitShift p q -> ShowS #

show :: BitShift p q -> String #

showList :: [BitShift p q] -> ShowS #

type PP (BitShift p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

type PP (BitShift p q :: Type) x

data BitShiftL p q Source #

shift left by p using q: similar to flipped version of shiftL

>>> pz @(BitShiftL 1 Id) 123
Val 246

Instances

Instances details
P (BitShiftLT p q) x => P (BitShiftL p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (BitShiftL p q) x Source #

Methods

eval :: MonadEval m => proxy (BitShiftL p q) -> POpts -> x -> m (TT (PP (BitShiftL p q) x)) Source #

Show (BitShiftL p q) Source # 
Instance details

Defined in Predicate.Data.Bits

Methods

showsPrec :: Int -> BitShiftL p q -> ShowS #

show :: BitShiftL p q -> String #

showList :: [BitShiftL p q] -> ShowS #

type PP (BitShiftL p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

type PP (BitShiftL p q :: Type) x

data BitShiftR p q Source #

shift right by p using q: similar to flipped version of shiftR

>>> pz @(BitShiftR 1 Id) 123
Val 61

Instances

Instances details
P (BitShiftRT p q) x => P (BitShiftR p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (BitShiftR p q) x Source #

Methods

eval :: MonadEval m => proxy (BitShiftR p q) -> POpts -> x -> m (TT (PP (BitShiftR p q) x)) Source #

Show (BitShiftR p q) Source # 
Instance details

Defined in Predicate.Data.Bits

Methods

showsPrec :: Int -> BitShiftR p q -> ShowS #

show :: BitShiftR p q -> String #

showList :: [BitShiftR p q] -> ShowS #

type PP (BitShiftR p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

type PP (BitShiftR p q :: Type) x

data BitRotate p q Source #

rotate by p using q: similar to flipped version of rotate

>>> pz @(BitRotate 2 Id) 7
Val 28

Instances

Instances details
P (BitRotateT p q) x => P (BitRotate p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (BitRotate p q) x Source #

Methods

eval :: MonadEval m => proxy (BitRotate p q) -> POpts -> x -> m (TT (PP (BitRotate p q) x)) Source #

Show (BitRotate p q) Source # 
Instance details

Defined in Predicate.Data.Bits

Methods

showsPrec :: Int -> BitRotate p q -> ShowS #

show :: BitRotate p q -> String #

showList :: [BitRotate p q] -> ShowS #

type PP (BitRotate p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

type PP (BitRotate p q :: Type) x

data BitRotateL p q Source #

rotate left by p using q: similar to flipped version of rotateL

>>> pz @(BitRotateL 2 Id) 7
Val 28

Instances

Instances details
P (BitRotateLT p q) x => P (BitRotateL p q :: Type) x Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Predicate.Data.Bits

type PP (BitRotateL p q :: Type) x

data BitRotateR p q Source #

rotate right by p using q: similar to flipped version of rotateR

>>> pz @(BitRotateR 2 Id) 7
Val 1

Instances

Instances details
P (BitRotateRT p q) x => P (BitRotateR p q :: Type) x Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Predicate.Data.Bits

type PP (BitRotateR p q :: Type) x

data BitSet p q Source #

set the bit at p using q: similar to flipped version of setBit

>>> pz @(BitSet 0 Id) 8
Val 9

Instances

Instances details
P (BitSetT p q) x => P (BitSet p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (BitSet p q) x Source #

Methods

eval :: MonadEval m => proxy (BitSet p q) -> POpts -> x -> m (TT (PP (BitSet p q) x)) Source #

Show (BitSet p q) Source # 
Instance details

Defined in Predicate.Data.Bits

Methods

showsPrec :: Int -> BitSet p q -> ShowS #

show :: BitSet p q -> String #

showList :: [BitSet p q] -> ShowS #

type PP (BitSet p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

type PP (BitSet p q :: Type) x

data BitComplement p q Source #

complement the bit at p using q: similar to flipped version of complementBit

>>> pz @(BitComplement 1 Id) 7
Val 5

Instances

Instances details
P (BitComplementT p q) x => P (BitComplement p q :: Type) x Source # 
Instance details

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 # 
Instance details

Defined in Predicate.Data.Bits

type PP (BitComplement p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

type PP (BitComplement p q :: Type) x

data BitClear p q Source #

clear the bit at p using q: similar to flipped version of clearBit

>>> pz @(BitClear 2 Id) 7
Val 3

Instances

Instances details
P (BitClearT p q) x => P (BitClear p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (BitClear p q) x Source #

Methods

eval :: MonadEval m => proxy (BitClear p q) -> POpts -> x -> m (TT (PP (BitClear p q) x)) Source #

Show (BitClear p q) Source # 
Instance details

Defined in Predicate.Data.Bits

Methods

showsPrec :: Int -> BitClear p q -> ShowS #

show :: BitClear p q -> String #

showList :: [BitClear p q] -> ShowS #

type PP (BitClear p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

type PP (BitClear p q :: Type) x

data PopCount p Source #

count number of bits at p: similar to popCount

>>> pz @(PopCount Id) 7
Val 3
>>> pz @(PopCount Id) 8
Val 1
>>> pz @(PopCount Id) (-7)
Val (-3)

Instances

Instances details
(P p a, Show (PP p a), Bits (PP p a)) => P (PopCount p :: Type) a Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (PopCount p) a Source #

Methods

eval :: MonadEval m => proxy (PopCount p) -> POpts -> a -> m (TT (PP (PopCount p) a)) Source #

Show (PopCount p) Source # 
Instance details

Defined in Predicate.Data.Bits

Methods

showsPrec :: Int -> PopCount p -> ShowS #

show :: PopCount p -> String #

showList :: [PopCount p] -> ShowS #

type PP (PopCount p :: Type) a Source # 
Instance details

Defined in Predicate.Data.Bits

type PP (PopCount p :: Type) a = Int

data TestBit p q Source #

test the bit at p using q: similar to flipped version of testBit

>>> pz @(TestBit 2 Id) 7
Val True
>>> pz @(TestBit 2 Id) 8
Val False

Instances

Instances details
(P p a, P q a, Show (PP q a), Bits (PP q a), Integral (PP p a)) => P (TestBit p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (TestBit p q) a Source #

Methods

eval :: MonadEval m => proxy (TestBit p q) -> POpts -> a -> m (TT (PP (TestBit p q) a)) Source #

Show (TestBit p q) Source # 
Instance details

Defined in Predicate.Data.Bits

Methods

showsPrec :: Int -> TestBit p q -> ShowS #

show :: TestBit p q -> String #

showList :: [TestBit p q] -> ShowS #

type PP (TestBit p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Bits

type PP (TestBit p q :: Type) a = Bool

data Bit t p Source #

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) 0
Val 1
>>> pz @(Bit Int Id) 3
Val 8

Instances

Instances details
(P p a, Show t, Bits t, Integral (PP p a)) => P (Bit t p :: Type) a Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (Bit t p) a Source #

Methods

eval :: MonadEval m => proxy (Bit t p) -> POpts -> a -> m (TT (PP (Bit t p) a)) Source #

Show (Bit t p) Source # 
Instance details

Defined in Predicate.Data.Bits

Methods

showsPrec :: Int -> Bit t p -> ShowS #

show :: Bit t p -> String #

showList :: [Bit t p] -> ShowS #

type PP (Bit t p :: Type) a Source # 
Instance details

Defined in Predicate.Data.Bits

type PP (Bit t p :: Type) a = t

data ZeroBits t Source #

create a Bits for type @t with all bits set to zero: similar to zeroBits

>>> pz @(ZeroBits Int) ()
Val 0

Instances

Instances details
(Show t, Bits t) => P (ZeroBits t :: Type) a Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (ZeroBits t) a Source #

Methods

eval :: MonadEval m => proxy (ZeroBits t) -> POpts -> a -> m (TT (PP (ZeroBits t) a)) Source #

Show (ZeroBits t) Source # 
Instance details

Defined in Predicate.Data.Bits

Methods

showsPrec :: Int -> ZeroBits t -> ShowS #

show :: ZeroBits t -> String #

showList :: [ZeroBits t] -> ShowS #

type PP (ZeroBits t :: Type) a Source # 
Instance details

Defined in Predicate.Data.Bits

type PP (ZeroBits t :: Type) a = t