htree-0.2.0.0: a library to build and work with heterogeneous, type level indexed rose trees
Safe HaskellNone
LanguageGHC2021

Data.HTree.Constraint

Description

A couple of types to work with Constraints

Synopsis

proving a constraint

data Has (c :: k -> Constraint) (f :: k -> Type) (k1 :: k) where Source #

a functor useful for proving a constraint for some type

>>> import Data.Functor.Identity
>>> Proves @Eq (Identity (5 :: Int))
Proves (Identity 5)

Constructors

Proves :: forall {k} (c :: k -> Constraint) (k1 :: k) (f :: k -> Type). c k1 => f k1 -> Has c f k1 

Instances

Instances details
Typeable f => Show (Some (Has (Typeable :: l -> Constraint) f)) Source # 
Instance details

Defined in Data.HTree.Existential

Methods

showsPrec :: Int -> Some (Has (Typeable :: l -> Constraint) f) -> ShowS #

show :: Some (Has (Typeable :: l -> Constraint) f) -> String #

showList :: [Some (Has (Typeable :: l -> Constraint) f)] -> ShowS #

(forall x. Eq x => Eq (f x), Typeable f) => Eq (EList (Has (Both (Typeable :: Type -> Constraint) Eq) f)) Source # 
Instance details

Defined in Data.HTree.Existential

Methods

(==) :: EList (Has (Both (Typeable :: Type -> Constraint) Eq) f) -> EList (Has (Both (Typeable :: Type -> Constraint) Eq) f) -> Bool #

(/=) :: EList (Has (Both (Typeable :: Type -> Constraint) Eq) f) -> EList (Has (Both (Typeable :: Type -> Constraint) Eq) f) -> Bool #

Eq (f k2) => Eq (EList (HasIs k2 f)) Source # 
Instance details

Defined in Data.HTree.Existential

Methods

(==) :: EList (HasIs k2 f) -> EList (HasIs k2 f) -> Bool #

(/=) :: EList (HasIs k2 f) -> EList (HasIs k2 f) -> Bool #

(forall x. Eq x => Eq (f x), Typeable f) => Eq (ETree (Has (Both (Typeable :: Type -> Constraint) Eq) f)) Source # 
Instance details

Defined in Data.HTree.Existential

Methods

(==) :: ETree (Has (Both (Typeable :: Type -> Constraint) Eq) f) -> ETree (Has (Both (Typeable :: Type -> Constraint) Eq) f) -> Bool #

(/=) :: ETree (Has (Both (Typeable :: Type -> Constraint) Eq) f) -> ETree (Has (Both (Typeable :: Type -> Constraint) Eq) f) -> Bool #

(forall x. Eq x => Eq (f x), Typeable f) => Eq (Some (Has (Typeable :: Type -> Constraint) (Has Eq f))) Source # 
Instance details

Defined in Data.HTree.Existential

Methods

(==) :: Some (Has (Typeable :: Type -> Constraint) (Has Eq f)) -> Some (Has (Typeable :: Type -> Constraint) (Has Eq f)) -> Bool #

(/=) :: Some (Has (Typeable :: Type -> Constraint) (Has Eq f)) -> Some (Has (Typeable :: Type -> Constraint) (Has Eq f)) -> Bool #

(forall x. Ord x => Ord (f x), Typeable f, Eq (Some (Has (Typeable :: Type -> Constraint) (Has Ord f)))) => Ord (Some (Has (Typeable :: Type -> Constraint) (Has Ord f))) Source # 
Instance details

Defined in Data.HTree.Existential

Methods

compare :: Some (Has (Typeable :: Type -> Constraint) (Has Ord f)) -> Some (Has (Typeable :: Type -> Constraint) (Has Ord f)) -> Ordering #

(<) :: Some (Has (Typeable :: Type -> Constraint) (Has Ord f)) -> Some (Has (Typeable :: Type -> Constraint) (Has Ord f)) -> Bool #

(<=) :: Some (Has (Typeable :: Type -> Constraint) (Has Ord f)) -> Some (Has (Typeable :: Type -> Constraint) (Has Ord f)) -> Bool #

(>) :: Some (Has (Typeable :: Type -> Constraint) (Has Ord f)) -> Some (Has (Typeable :: Type -> Constraint) (Has Ord f)) -> Bool #

(>=) :: Some (Has (Typeable :: Type -> Constraint) (Has Ord f)) -> Some (Has (Typeable :: Type -> Constraint) (Has Ord f)) -> Bool #

max :: Some (Has (Typeable :: Type -> Constraint) (Has Ord f)) -> Some (Has (Typeable :: Type -> Constraint) (Has Ord f)) -> Some (Has (Typeable :: Type -> Constraint) (Has Ord f)) #

min :: Some (Has (Typeable :: Type -> Constraint) (Has Ord f)) -> Some (Has (Typeable :: Type -> Constraint) (Has Ord f)) -> Some (Has (Typeable :: Type -> Constraint) (Has Ord f)) #

Show (f k2) => Show (Has c f k2) Source # 
Instance details

Defined in Data.HTree.Constraint

Methods

showsPrec :: Int -> Has c f k2 -> ShowS #

show :: Has c f k2 -> String #

showList :: [Has c f k2] -> ShowS #

synonyms for proving a constraint

type HasTypeable = Has (Typeable :: k -> Constraint) Source #

Has but specialised to Typeable

type HasIs (k1 :: k) = Has (k ~ k1) Source #

Has but specialised to a constant type, Some (HasIs k f) is isomorphic to f k

helpers to work with constraints

proves :: forall {k} c f (a :: k) r. Has c f a -> (c a => f a -> r) -> r Source #

destruct a Has

class c => Charge c (a :: k) Source #

transform a Constraint in something of kind k -> Constraint to be able to use it in Has

Instances

Instances details
c => Charge c (a :: k) Source # 
Instance details

Defined in Data.HTree.Constraint

Dict

type Dict c = Has (Charge c :: Type -> Constraint) (Proxy :: Type -> Type) () Source #

a Dict witnesses some constraint

pattern Dict :: () => c => Dict c Source #

match on a Dict

functions for working with Dicts

withDict :: Dict c -> (c => r) -> r Source #

destructing a Dict