htree-0.1.1.0: An implemementation of a heterogeneous rosetree
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.HTree.Tree

Description

implements a heterogeneous tree (HTree) indexed by a homogeneous type level tree (TyTree)

Synopsis

type level tree

data TyTree k where Source #

a type level rose-tree that is only intended to store something of a certain kind, e.g. Type

Constructors

TyNode :: forall a. a -> TyForest a -> TyTree a infixr 4 

Instances

Instances details
HasField' strat typ t => Decide strat 'False typ ('TyNode typ' (t ': ts')) Source # 
Instance details

Defined in Data.HTree.Labeled

Methods

evidence' :: forall {proxy :: forall k. k -> Type}. proxy strat -> proxy 'False -> Path typ ('TyNode typ' (t ': ts')) Source #

HasField' strat typ ('TyNode typ' ts) => Decide strat 'True typ ('TyNode typ' (t' ': ts)) Source # 
Instance details

Defined in Data.HTree.Labeled

Methods

evidence' :: forall {proxy :: forall k. k -> Type}. proxy strat -> proxy 'True -> Path typ ('TyNode typ' (t' ': ts)) Source #

HasField' 'BFS typ ('TyNode typ (t ': ts)) Source # 
Instance details

Defined in Data.HTree.Labeled

Methods

evidence :: proxy 'BFS -> Path typ ('TyNode typ (t ': ts)) Source #

HasField' 'BFS typ ('TyNode typ ('[] :: [TyTree Type])) Source # 
Instance details

Defined in Data.HTree.Labeled

Methods

evidence :: proxy 'BFS -> Path typ ('TyNode typ '[]) Source #

Decide 'BFS (AnyElem typ ts) typ ('TyNode typ' (t ': ts)) => HasField' 'BFS typ ('TyNode typ' (t ': ts)) Source # 
Instance details

Defined in Data.HTree.Labeled

Methods

evidence :: proxy 'BFS -> Path typ ('TyNode typ' (t ': ts)) Source #

HasField' 'DFS typ ('TyNode typ (t ': ts)) Source # 
Instance details

Defined in Data.HTree.Labeled

Methods

evidence :: proxy 'DFS -> Path typ ('TyNode typ (t ': ts)) Source #

HasField' 'DFS typ ('TyNode typ ('[] :: [TyTree Type])) Source # 
Instance details

Defined in Data.HTree.Labeled

Methods

evidence :: proxy 'DFS -> Path typ ('TyNode typ '[]) Source #

Decide 'DFS (Not (Elem typ t)) typ ('TyNode typ' (t ': ts)) => HasField' 'DFS typ ('TyNode typ' (t ': ts)) Source # 
Instance details

Defined in Data.HTree.Labeled

Methods

evidence :: proxy 'DFS -> Path typ ('TyNode typ' (t ': ts)) Source #

(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 Eq) f) -> ETree (Has (Both Typeable Eq) f) -> Bool #

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

type TyForest a = [TyTree a] Source #

a forest of TyTrees

heterogeneous tree

data HTree f t where Source #

a heterogeneous rose tree indexed by a TyTree

Constructors

HNode :: forall f a ts. f a -> HForest f ts -> HTree f ('TyNode a ts) infixr 4 

Bundled Patterns

pattern HLeaf :: forall f a. forall. f a -> HTree f ('TyNode a '[])

a pattern synonym for the leaf of an HTree

Instances

Instances details
(HasField' 'BFS (Labeled l typ) t, Functor f) => HasField (l :: k) (HTree f t) (f typ) Source # 
Instance details

Defined in Data.HTree.Labeled

Methods

getField :: HTree f t -> f typ #

(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 Eq) f) -> ETree (Has (Both Typeable Eq) f) -> Bool #

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

(Show (f a2), Show (HForest f t)) => Show (HTree f ('TyNode a2 t)) Source # 
Instance details

Defined in Data.HTree.Tree

Methods

showsPrec :: Int -> HTree f ('TyNode a2 t) -> ShowS #

show :: HTree f ('TyNode a2 t) -> String #

showList :: [HTree f ('TyNode a2 t)] -> ShowS #

(Eq (f a2), Eq (HForest f t)) => Eq (HTree f ('TyNode a2 t)) Source # 
Instance details

Defined in Data.HTree.Tree

Methods

(==) :: HTree f ('TyNode a2 t) -> HTree f ('TyNode a2 t) -> Bool #

(/=) :: HTree f ('TyNode a2 t) -> HTree f ('TyNode a2 t) -> Bool #

type HForest f ts = HList (HTree f) ts Source #

A forest of heterogeneous rose trees

mapping

value level

hmap :: forall {k} (f :: k -> Type) (g :: k -> Type) (t :: TyTree k). (forall a. f a -> g a) -> HTree f t -> HTree g t Source #

map a function over an HTree

hcmap :: forall {k} (c :: k -> Constraint) (f :: k -> Type) (g :: k -> Type) (t :: TyTree k). AllTree c t => (forall a. c a => f a -> g a) -> HTree f t -> HTree g t Source #

map a function with a constraint over an HTree

type level

type family TreeMap f t where ... Source #

map a functor over a TyTree

Equations

TreeMap f ('TyNode x '[]) = 'TyNode (f x) '[] 
TreeMap f ('TyNode x xs) = 'TyNode (f x) (ForestMap f xs) 

type family ForestMap f t where ... Source #

map a functor over a TyForest

Equations

ForestMap _ '[] = '[] 
ForestMap f (n : ns) = TreeMap f n : ForestMap f ns 

traversing

htraverse :: forall {k} (h :: Type -> Type) (f :: k -> Type) (g :: k -> Type) (t :: TyTree k). Applicative h => (forall a. f a -> h (g a)) -> HTree f t -> h (HTree g t) Source #

traverse a structure with a function

hctraverse :: forall {k} (c :: k -> Constraint) (h :: Type -> Type) (f :: k -> Type) (g :: k -> Type) (t :: TyTree k). (AllTree c t, Applicative h) => (forall a. c a => f a -> h (g a)) -> HTree f t -> h (HTree g t) Source #

traverse a structure such that a constraint holds; this is the workhorse of mapping and traversing

folding

value level

hFoldMap :: forall {k} (f :: k -> Type) (t :: TyTree k) (b :: Type). Semigroup b => (forall a. f a -> b) -> HTree f t -> b Source #

monoidally folds down a tree to a single value, this is similar to foldMap

hcFoldMap :: forall {k} (c :: k -> Constraint) (f :: k -> Type) (t :: TyTree k) (b :: Type). (AllTree c t, Semigroup b) => (forall a. c a => f a -> b) -> HTree f t -> b Source #

monoidally folds down a tree to a single value using a constraint on the element in the wrapping functor, this is similar to foldMap

hFlatten :: forall {k} (f :: k -> Type) (t :: TyTree k). HTree f t -> HList f (FlattenTree t) Source #

flatten a heterogeneous tree down to a heterogeneous list

type level

type family FlattenTree t where ... Source #

a type family that flattens a tree down to a list

Equations

FlattenTree ('TyNode x xs) = x : FlattenForest xs 

type family FlattenForest f where ... Source #

a type family that flattens a forest down to a list

Equations

FlattenForest '[] = '[] 
FlattenForest (x : xs) = FlattenTree x ++ FlattenForest xs 

paths into the htree and things you can do with those

data Path k t where Source #

provides evidence that an element is in the tree by providing a path to the element

Constructors

Here :: forall a ts. Path a ('TyNode a ts) 
Deeper :: forall a b t ts. Path a t -> Path a ('TyNode b (t : ts)) 
Farther :: forall a b t ts. Path a ('TyNode b ts) -> Path a ('TyNode b (t : ts)) 

Instances

Instances details
Show (Path typ t) Source # 
Instance details

Defined in Data.HTree.Tree

Methods

showsPrec :: Int -> Path typ t -> ShowS #

show :: Path typ t -> String #

showList :: [Path typ t] -> ShowS #

Eq (Path typ t) Source # 
Instance details

Defined in Data.HTree.Tree

Methods

(==) :: Path typ t -> Path typ t -> Bool #

(/=) :: Path typ t -> Path typ t -> Bool #

replaceAt :: Path typ t -> f typ -> HTree f t -> HTree f t Source #

replace an element at a certain path.

helpful constraints

type family AllTree c ts where ... Source #

a constraint holds for all elements in the tree

Equations

AllTree c ('TyNode x ts) = (c x, AllForest c ts) 

class AllTree c ts => AllTreeC c ts Source #

constraint synonym for AllTree

Instances

Instances details
AllTree c ts => AllTreeC (c :: k -> Constraint) (ts :: TyTree k) Source # 
Instance details

Defined in Data.HTree.Tree

type family AllForest c t where ... Source #

a constraint holds for all elements in the forest

Equations

AllForest c xs = All (AllTreeC c) xs 

helpers for witnessing the constraints

allTopHTree :: forall f t. HTree f t -> Dict (AllTree Top t) Source #

witnesses that for any HTree the constraint AllTree Top always holds

allTopHForest :: forall f t. HForest f t -> Dict (AllForest Top t) Source #

witnesses that for any HForest the constraint AllForest Top always holds