parameterized-utils-2.1.10.0: Classes and data structures for working with data-kind indexed types
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Parameterized.BoolRepr

Contents

Synopsis

Documentation

type family (a :: Bool) && (b :: Bool) :: Bool where ... #

Equations

'False && a = 'False 
'True && a = a 
a && 'False = 'False 
a && 'True = a 
a && a = a 

type family (a :: Bool) || (b :: Bool) :: Bool where ... #

Equations

'False || a = a 
'True || a = 'True 
a || 'False = a 
a || 'True = 'True 
a || a = a 

type family If (cond :: Bool) (tru :: k) (fls :: k) :: k where ... #

Equations

If 'True (tru :: k) (fls :: k) = tru 
If 'False (tru :: k) (fls :: k) = fls 

type family Not (a :: Bool) = (res :: Bool) | res -> a where ... #

Equations

Not 'False = 'True 
Not 'True = 'False 

data BoolRepr (b :: Bool) where Source #

A Boolean flag

Constructors

FalseRepr :: BoolRepr 'False 
TrueRepr :: BoolRepr 'True 

Instances

Instances details
TestEquality BoolRepr Source # 
Instance details

Defined in Data.Parameterized.BoolRepr

Methods

testEquality :: forall (a :: Bool) (b :: Bool). BoolRepr a -> BoolRepr b -> Maybe (a :~: b) #

EqF BoolRepr Source # 
Instance details

Defined in Data.Parameterized.BoolRepr

Methods

eqF :: forall (a :: Bool). BoolRepr a -> BoolRepr a -> Bool Source #

HashableF BoolRepr Source # 
Instance details

Defined in Data.Parameterized.BoolRepr

Methods

hashWithSaltF :: forall (tp :: Bool). Int -> BoolRepr tp -> Int Source #

hashF :: forall (tp :: Bool). BoolRepr tp -> Int Source #

OrdF BoolRepr Source # 
Instance details

Defined in Data.Parameterized.BoolRepr

Methods

compareF :: forall (x :: Bool) (y :: Bool). BoolRepr x -> BoolRepr y -> OrderingF x y Source #

leqF :: forall (x :: Bool) (y :: Bool). BoolRepr x -> BoolRepr y -> Bool Source #

ltF :: forall (x :: Bool) (y :: Bool). BoolRepr x -> BoolRepr y -> Bool Source #

geqF :: forall (x :: Bool) (y :: Bool). BoolRepr x -> BoolRepr y -> Bool Source #

gtF :: forall (x :: Bool) (y :: Bool). BoolRepr x -> BoolRepr y -> Bool Source #

ShowF BoolRepr Source # 
Instance details

Defined in Data.Parameterized.BoolRepr

Methods

withShow :: forall p q (tp :: Bool) a. p BoolRepr -> q tp -> (Show (BoolRepr tp) => a) -> a Source #

showF :: forall (tp :: Bool). BoolRepr tp -> String Source #

showsPrecF :: forall (tp :: Bool). Int -> BoolRepr tp -> String -> String Source #

DecidableEq BoolRepr Source # 
Instance details

Defined in Data.Parameterized.BoolRepr

Methods

decEq :: forall (a :: Bool) (b :: Bool). BoolRepr a -> BoolRepr b -> Either (a :~: b) ((a :~: b) -> Void) Source #

IsRepr BoolRepr Source # 
Instance details

Defined in Data.Parameterized.WithRepr

Methods

withRepr :: forall (a :: Bool) r. BoolRepr a -> (KnownRepr BoolRepr a => r) -> r Source #

KnownRepr BoolRepr 'False Source # 
Instance details

Defined in Data.Parameterized.BoolRepr

Methods

knownRepr :: BoolRepr 'False Source #

KnownRepr BoolRepr 'True Source # 
Instance details

Defined in Data.Parameterized.BoolRepr

Methods

knownRepr :: BoolRepr 'True Source #

Show (BoolRepr m) Source # 
Instance details

Defined in Data.Parameterized.BoolRepr

Methods

showsPrec :: Int -> BoolRepr m -> ShowS

show :: BoolRepr m -> String

showList :: [BoolRepr m] -> ShowS

Eq (BoolRepr m) Source # 
Instance details

Defined in Data.Parameterized.BoolRepr

Methods

(==) :: BoolRepr m -> BoolRepr m -> Bool

(/=) :: BoolRepr m -> BoolRepr m -> Bool

Hashable (BoolRepr n) Source # 
Instance details

Defined in Data.Parameterized.BoolRepr

Methods

hashWithSalt :: Int -> BoolRepr n -> Int #

hash :: BoolRepr n -> Int #

PolyEq (BoolRepr m) (BoolRepr n) Source # 
Instance details

Defined in Data.Parameterized.BoolRepr

Methods

polyEqF :: BoolRepr m -> BoolRepr n -> Maybe (BoolRepr m :~: BoolRepr n) Source #

polyEq :: BoolRepr m -> BoolRepr n -> Bool Source #

ifRepr :: forall (a :: Bool) (b :: Bool) (c :: Bool). BoolRepr a -> BoolRepr b -> BoolRepr c -> BoolRepr (If a b c) Source #

conditional

notRepr :: forall (b :: Bool). BoolRepr b -> BoolRepr (Not b) Source #

negation

(%&&) :: forall (a :: Bool) (b :: Bool). BoolRepr a -> BoolRepr b -> BoolRepr (a && b) infixr 3 Source #

Conjunction

(%||) :: forall (a :: Bool) (b :: Bool). BoolRepr a -> BoolRepr b -> BoolRepr (a || b) infixr 2 Source #

Disjunction

Re-exports

class TestEquality (f :: k -> Type) where #

Methods

testEquality :: forall (a :: k) (b :: k). f a -> f b -> Maybe (a :~: b) #

Instances

Instances details
TestEquality SNat 
Instance details

Defined in GHC.TypeNats

Methods

testEquality :: forall (a :: Nat) (b :: Nat). SNat a -> SNat b -> Maybe (a :~: b) #

TestEquality NatRepr Source # 
Instance details

Defined in Data.Parameterized.NatRepr.Internal

Methods

testEquality :: forall (a :: Nat) (b :: Nat). NatRepr a -> NatRepr b -> Maybe (a :~: b) #

TestEquality PeanoRepr Source # 
Instance details

Defined in Data.Parameterized.Peano

Methods

testEquality :: forall (a :: Peano) (b :: Peano). PeanoRepr a -> PeanoRepr b -> Maybe (a :~: b) #

TestEquality BoolRepr Source # 
Instance details

Defined in Data.Parameterized.BoolRepr

Methods

testEquality :: forall (a :: Bool) (b :: Bool). BoolRepr a -> BoolRepr b -> Maybe (a :~: b) #

TestEquality SChar 
Instance details

Defined in GHC.TypeLits

Methods

testEquality :: forall (a :: Char) (b :: Char). SChar a -> SChar b -> Maybe (a :~: b) #

TestEquality SSymbol 
Instance details

Defined in GHC.TypeLits

Methods

testEquality :: forall (a :: Symbol) (b :: Symbol). SSymbol a -> SSymbol b -> Maybe (a :~: b) #

TestEquality SymbolRepr Source # 
Instance details

Defined in Data.Parameterized.SymbolRepr

Methods

testEquality :: forall (a :: Symbol) (b :: Symbol). SymbolRepr a -> SymbolRepr b -> Maybe (a :~: b) #

TestEquality (TypeRep :: k -> Type) 
Instance details

Defined in Data.Typeable.Internal

Methods

testEquality :: forall (a :: k) (b :: k). TypeRep a -> TypeRep b -> Maybe (a :~: b) #

TestEquality (Nonce :: k -> Type) Source # 
Instance details

Defined in Data.Parameterized.Nonce.Unsafe

Methods

testEquality :: forall (a :: k) (b :: k). Nonce a -> Nonce b -> Maybe (a :~: b) #

TestEquality ((:~:) a :: k -> Type) 
Instance details

Defined in Data.Type.Equality

Methods

testEquality :: forall (a0 :: k) (b :: k). (a :~: a0) -> (a :~: b) -> Maybe (a0 :~: b) #

TestEquality (Index ctx :: k -> Type) Source # 
Instance details

Defined in Data.Parameterized.Context.Unsafe

Methods

testEquality :: forall (a :: k) (b :: k). Index ctx a -> Index ctx b -> Maybe (a :~: b) #

TestEquality (Index l :: k -> Type) Source # 
Instance details

Defined in Data.Parameterized.List

Methods

testEquality :: forall (a :: k) (b :: k). Index l a -> Index l b -> Maybe (a :~: b) #

TestEquality (Nonce s :: k -> Type) Source # 
Instance details

Defined in Data.Parameterized.Nonce

Methods

testEquality :: forall (a :: k) (b :: k). Nonce s a -> Nonce s b -> Maybe (a :~: b) #

TestEquality ((:~~:) a :: k -> Type) 
Instance details

Defined in Data.Type.Equality

Methods

testEquality :: forall (a0 :: k) (b :: k). (a :~~: a0) -> (a :~~: b) -> Maybe (a0 :~: b) #

TestEquality f => TestEquality (Compose f g :: k2 -> Type) 
Instance details

Defined in Data.Functor.Compose

Methods

testEquality :: forall (a :: k2) (b :: k2). Compose f g a -> Compose f g b -> Maybe (a :~: b) #

TestEquality f => TestEquality (Assignment f :: Ctx k -> Type) Source # 
Instance details

Defined in Data.Parameterized.Context.Unsafe

Methods

testEquality :: forall (a :: Ctx k) (b :: Ctx k). Assignment f a -> Assignment f b -> Maybe (a :~: b) #

TestEquality f => TestEquality (List f :: [k] -> Type) Source # 
Instance details

Defined in Data.Parameterized.List

Methods

testEquality :: forall (a :: [k]) (b :: [k]). List f a -> List f b -> Maybe (a :~: b) #

(TestEquality f, TestEquality g) => TestEquality (PairRepr f g :: (k1, k2) -> Type) Source # 
Instance details

Defined in Data.Parameterized.DataKind

Methods

testEquality :: forall (a :: (k1, k2)) (b :: (k1, k2)). PairRepr f g a -> PairRepr f g b -> Maybe (a :~: b) #

data (a :: k) :~: (b :: k) where #

Constructors

Refl :: forall {k} (a :: k). a :~: a 

Instances

Instances details
Category ((:~:) :: k -> k -> Type) 
Instance details

Defined in Control.Category

Methods

id :: forall (a :: k). a :~: a

(.) :: forall (b :: k) (c :: k) (a :: k). (b :~: c) -> (a :~: b) -> a :~: c

TestCoercion ((:~:) a :: k -> Type) 
Instance details

Defined in Data.Type.Coercion

Methods

testCoercion :: forall (a0 :: k) (b :: k). (a :~: a0) -> (a :~: b) -> Maybe (Coercion a0 b)

TestEquality ((:~:) a :: k -> Type) 
Instance details

Defined in Data.Type.Equality

Methods

testEquality :: forall (a0 :: k) (b :: k). (a :~: a0) -> (a :~: b) -> Maybe (a0 :~: b) #

NFData2 ((:~:) :: Type -> Type -> Type) 
Instance details

Defined in Control.DeepSeq

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> (a :~: b) -> ()

NFData1 ((:~:) a) 
Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a0 -> ()) -> (a :~: a0) -> ()

(a ~ b, Data a) => Data (a :~: b) 
Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a :~: b) -> c (a :~: b)

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a :~: b)

toConstr :: (a :~: b) -> Constr

dataTypeOf :: (a :~: b) -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (a :~: b))

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (a :~: b))

gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a :~: b) -> a :~: b

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a :~: b) -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a :~: b) -> r

gmapQ :: (forall d. Data d => d -> u) -> (a :~: b) -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> (a :~: b) -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b)

a ~ b => Bounded (a :~: b) 
Instance details

Defined in Data.Type.Equality

Methods

minBound :: a :~: b

maxBound :: a :~: b

a ~ b => Enum (a :~: b) 
Instance details

Defined in Data.Type.Equality

Methods

succ :: (a :~: b) -> a :~: b

pred :: (a :~: b) -> a :~: b

toEnum :: Int -> a :~: b

fromEnum :: (a :~: b) -> Int

enumFrom :: (a :~: b) -> [a :~: b]

enumFromThen :: (a :~: b) -> (a :~: b) -> [a :~: b]

enumFromTo :: (a :~: b) -> (a :~: b) -> [a :~: b]

enumFromThenTo :: (a :~: b) -> (a :~: b) -> (a :~: b) -> [a :~: b]

a ~ b => Read (a :~: b) 
Instance details

Defined in Data.Type.Equality

Methods

readsPrec :: Int -> ReadS (a :~: b)

readList :: ReadS [a :~: b]

readPrec :: ReadPrec (a :~: b)

readListPrec :: ReadPrec [a :~: b]

Show (a :~: b) 
Instance details

Defined in Data.Type.Equality

Methods

showsPrec :: Int -> (a :~: b) -> ShowS

show :: (a :~: b) -> String

showList :: [a :~: b] -> ShowS

NFData (a :~: b) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: (a :~: b) -> ()

Eq (a :~: b) 
Instance details

Defined in Data.Type.Equality

Methods

(==) :: (a :~: b) -> (a :~: b) -> Bool

(/=) :: (a :~: b) -> (a :~: b) -> Bool

Ord (a :~: b) 
Instance details

Defined in Data.Type.Equality

Methods

compare :: (a :~: b) -> (a :~: b) -> Ordering

(<) :: (a :~: b) -> (a :~: b) -> Bool

(<=) :: (a :~: b) -> (a :~: b) -> Bool

(>) :: (a :~: b) -> (a :~: b) -> Bool

(>=) :: (a :~: b) -> (a :~: b) -> Bool

max :: (a :~: b) -> (a :~: b) -> a :~: b

min :: (a :~: b) -> (a :~: b) -> a :~: b

HasDict (a ~ b) (a :~: b) 
Instance details

Defined in Data.Constraint

Methods

evidence :: (a :~: b) -> Dict (a ~ b)

data Some (f :: k -> Type) Source #

Instances

Instances details
OrdC (Some :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Parameterized.ClassesC

Methods

compareC :: (forall (x :: k) (y :: k). f x -> g y -> OrderingF x y) -> Some f -> Some g -> Ordering Source #

TestEqualityC (Some :: (k -> Type) -> Type) Source #

This instance demonstrates where the above class is useful: namely, in types with existential quantification.

Instance details

Defined in Data.Parameterized.ClassesC

Methods

testEqualityC :: (forall (x :: k) (y :: k). f x -> f y -> Maybe (x :~: y)) -> Some f -> Some f -> Bool Source #

FoldableF (Some :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Parameterized.Some

Methods

foldMapF :: Monoid m => (forall (s :: k). e s -> m) -> Some e -> m Source #

foldrF :: (forall (s :: k). e s -> b -> b) -> b -> Some e -> b Source #

foldlF :: (forall (s :: k). b -> e s -> b) -> b -> Some e -> b Source #

foldrF' :: (forall (s :: k). e s -> b -> b) -> b -> Some e -> b Source #

foldlF' :: (forall (s :: k). b -> e s -> b) -> b -> Some e -> b Source #

toListF :: (forall (tp :: k). f tp -> a) -> Some f -> [a] Source #

FunctorF (Some :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Parameterized.Some

Methods

fmapF :: (forall (x :: k). f x -> g x) -> Some f -> Some g Source #

TraversableF (Some :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Parameterized.Some

Methods

traverseF :: Applicative m => (forall (s :: k). e s -> m (f s)) -> Some e -> m (Some f) Source #

ShowF f => Show (Some f) Source # 
Instance details

Defined in Data.Parameterized.Some

Methods

showsPrec :: Int -> Some f -> ShowS

show :: Some f -> String

showList :: [Some f] -> ShowS

TestEquality f => Eq (Some f) Source # 
Instance details

Defined in Data.Parameterized.Some

Methods

(==) :: Some f -> Some f -> Bool

(/=) :: Some f -> Some f -> Bool

OrdF f => Ord (Some f) Source # 
Instance details

Defined in Data.Parameterized.Some

Methods

compare :: Some f -> Some f -> Ordering

(<) :: Some f -> Some f -> Bool

(<=) :: Some f -> Some f -> Bool

(>) :: Some f -> Some f -> Bool

(>=) :: Some f -> Some f -> Bool

max :: Some f -> Some f -> Some f

min :: Some f -> Some f -> Some f

(HashableF f, TestEquality f) => Hashable (Some f) Source # 
Instance details

Defined in Data.Parameterized.Some

Methods

hashWithSalt :: Int -> Some f -> Int #

hash :: Some f -> Int #