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

Data.HTree.Existential

Description

Existential types and helpers to work with existentials HLists and HTrees

Synopsis

existential data types

data Some (g :: l -> Type) where Source #

a Some type that takes an arity one type constructor, this is for completeness

Constructors

MkSome :: forall {l} (g :: l -> Type) (k :: l). g k -> Some g 

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 (k :: l). Show (g k)) => Show (Some g) Source # 
Instance details

Defined in Data.HTree.Existential

Methods

showsPrec :: Int -> Some g -> ShowS #

show :: Some g -> String #

showList :: [Some g] -> ShowS #

(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)) #

data Some2 (g :: k -> l -> Type) (f :: k) where Source #

a Some type that take an arity two type constructor, this is necessary so that we avoid using composition on the type level or having visible parameters to the type synonyms

Constructors

MkSome2 :: forall {k} {l} (g :: k -> l -> Type) (f :: k) (k1 :: l). g f k1 -> Some2 g f 

Instances

Instances details
(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 (k1 :: l). Show (g f k1)) => Show (Some2 g f) Source # 
Instance details

Defined in Data.HTree.Existential

Methods

showsPrec :: Int -> Some2 g f -> ShowS #

show :: Some2 g f -> String #

showList :: [Some2 g f] -> ShowS #

existential type synonyms

type ETree = Some2 (HTree :: (k -> Type) -> TyTree k -> Type) Source #

HTree but the type level tree is existential

type EList = Some2 (HList :: (k -> Type) -> [k] -> Type) Source #

HList but the type level list is existential

working with existential HTrees/HLists functions

with :: Some g -> (forall (m :: l). g m -> r) -> r Source #

take some existentai arity one type constructor and a function that takes the non-existential one and returns some r and return an r

with2 :: forall {k} {l} g (f :: k) r. Some2 g f -> (forall (m :: l). g f m -> r) -> r Source #

take some existential arity two type constructor and a function that takes the non-existential one and returns some r and return an r

withSomeHTree :: forall {k} (f :: k -> Type) r. ETree f -> (forall (t :: TyTree k). HTree f t -> r) -> r Source #

with2 specialized to HTrees

withSomeHList :: forall {k} (f :: k -> Type) r. EList f -> (forall (xs :: [k]). HList f xs -> r) -> r Source #

with2 specialized to HLists

hcFoldEHList :: (forall (x :: k). c x => f x -> y -> y) -> y -> EList (Has c f) -> y Source #

fold over existential hlists

hcFoldMapEHTree :: forall {k} c f y. Semigroup y => (forall (a :: k). c a => f a -> y) -> ETree (Has c f) -> y Source #

fold over existential htrees

useful functors to work with existential type-level structures

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 #

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

working with Has

withProves :: Some (Has c f) -> (forall (a :: l). c a => f a -> r) -> r Source #

destruct Some, destruct Has

prodHas :: forall {l} (c1 :: l -> Constraint) (c2 :: l -> Constraint) (f :: l -> Type). Some (Has c1 (Has c2 f)) -> Some (Has (Both c1 c2) f) Source #

condens the Has constraints in an existential

flipHas :: forall {l} (c1 :: l -> Constraint) (c2 :: l -> Constraint) (f :: l -> Type). Some (Has c1 (Has c2 f)) -> Some (Has c2 (Has c1 f)) Source #

flip the constraints in an existential