fcf-containers-0.3.0: Data structures and algorithms for first-class-families
Copyright(c) gspia 2020-
LicenseBSD
Maintainergspia
Safe HaskellSafe
LanguageHaskell2010

Fcf.Data.Tree

Description

Fcf.Data.Tree

Tree provides an interface which is similar to the that given by the container-package. If a method is missing here that you need, please do open up an issue or better, make a PR.

This module provides it's own but (almost) identical definitions of Tree and Forest. The reason for not using the definitions given in the containers is that since nothing else is needed from containers, we are able to have less dependencies.

Many of the examples are from containers-package.

Synopsis

Documentation

>>> import qualified GHC.TypeLits as TL
>>> import           Fcf.Data.Nat

data Tree a Source #

Same as in containers, except not used for any term-level computation in this module.

Constructors

Node a [Tree a] 

Instances

Instances details
type Eval (FoldTree f ('Node a3 (x ': xs)) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.Tree

type Eval (FoldTree f ('Node a3 (x ': xs)) :: a2 -> Type) = Eval (f a3 (Eval (Map (FoldTree f) (x ': xs))))
type Eval (FoldTree f ('Node a3 ('[] :: [Tree a1])) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.Tree

type Eval (FoldTree f ('Node a3 ('[] :: [Tree a1])) :: a2 -> Type) = Eval (f a3 ('[] :: [a2]))
type Eval (GetForest ('Node _1 f) :: [Tree a] -> Type) Source # 
Instance details

Defined in Fcf.Data.Tree

type Eval (GetForest ('Node _1 f) :: [Tree a] -> Type) = f
type Eval (GetForests ts :: [Tree a] -> Type) Source # 
Instance details

Defined in Fcf.Data.Tree

type Eval (GetForests ts :: [Tree a] -> Type) = Eval (ConcatMap (GetForest :: Tree a -> [Tree a] -> Type) ts)
type Eval (SubFLevels (t ': ts) :: Maybe ([a], [Tree a]) -> Type) Source # 
Instance details

Defined in Fcf.Data.Tree

type Eval (SubFLevels (t ': ts) :: Maybe ([a], [Tree a]) -> Type) = 'Just '(Eval (GetRoots (t ': ts)), Eval (GetForests (t ': ts)))
type Eval (SubFLevels ('[] :: [Tree a]) :: Maybe ([a], [Tree a]) -> Type) Source # 
Instance details

Defined in Fcf.Data.Tree

type Eval (SubFLevels ('[] :: [Tree a]) :: Maybe ([a], [Tree a]) -> Type) = 'Nothing :: Maybe ([a], [Tree a])
type Eval (TreeToFix ('Node a2 (b ': bs)) :: Fix (TreeF a1) -> Type) Source # 
Instance details

Defined in Fcf.Alg.Tree

type Eval (TreeToFix ('Node a2 (b ': bs)) :: Fix (TreeF a1) -> Type) = 'Fix ('NodeF a2 (Eval (Map (TreeToFix :: Tree a1 -> Fix (TreeF a1) -> Type) (b ': bs))))
type Eval (TreeToFix ('Node a2 ('[] :: [Tree a1])) :: Fix (TreeF a1) -> Type) Source # 
Instance details

Defined in Fcf.Alg.Tree

type Eval (TreeToFix ('Node a2 ('[] :: [Tree a1])) :: Fix (TreeF a1) -> Type) = 'Fix ('NodeF a2 ('[] :: [Fix (TreeF a1)]))
type Eval (UnfoldForest f bs :: Forest a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.Tree

type Eval (UnfoldForest f bs :: Forest a2 -> Type) = Eval (Map (UnfoldTree f) bs)
type Eval (UnfoldTree f b2 :: Tree a -> Type) Source # 
Instance details

Defined in Fcf.Data.Tree

type Eval (UnfoldTree f b2 :: Tree a -> Type) = 'Node (Eval ((Fst :: (a, [b1]) -> a -> Type) =<< f b2)) (Eval (UnfoldForest f (Eval ((Snd :: (a, [b1]) -> [b1] -> Type) =<< f b2))))

type Forest a = [Tree a] Source #

Same as in containers, except not used for any term-level computation in this module.

data FoldTree :: (a -> [b] -> Exp b) -> Tree a -> Exp b Source #

Fold a type-level Tree.

Instances

Instances details
type Eval (FoldTree f ('Node a3 (x ': xs)) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.Tree

type Eval (FoldTree f ('Node a3 (x ': xs)) :: a2 -> Type) = Eval (f a3 (Eval (Map (FoldTree f) (x ': xs))))
type Eval (FoldTree f ('Node a3 ('[] :: [Tree a1])) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.Tree

type Eval (FoldTree f ('Node a3 ('[] :: [Tree a1])) :: a2 -> Type) = Eval (f a3 ('[] :: [a2]))

data UnfoldTree :: (b -> Exp (a, [b])) -> b -> Exp (Tree a) Source #

Unfold for a Tree.

Example

Expand
>>> data BuildNode :: Nat -> Exp (Nat,[Nat])
>>> :{
  type instance Eval (BuildNode x) =
      If (Eval ((2 TL.* x TL.+ 1) >= 8))
          '(x, '[])
          '(x, '[2 TL.* x, (2 TL.* x) TL.+ 1 ])
:}
>>> :kind! Eval (UnfoldTree BuildNode 1)
Eval (UnfoldTree BuildNode 1) :: Tree Nat
= 'Node
    1
    '[ 'Node 2 '[ 'Node 4 '[], 'Node 5 '[]],
       'Node 3 '[ 'Node 6 '[], 'Node 7 '[]]]

Instances

Instances details
type Eval (UnfoldTree f b2 :: Tree a -> Type) Source # 
Instance details

Defined in Fcf.Data.Tree

type Eval (UnfoldTree f b2 :: Tree a -> Type) = 'Node (Eval ((Fst :: (a, [b1]) -> a -> Type) =<< f b2)) (Eval (UnfoldForest f (Eval ((Snd :: (a, [b1]) -> [b1] -> Type) =<< f b2))))

data UnfoldForest :: (b -> Exp (a, [b])) -> [b] -> Exp (Forest a) Source #

Unfold for a Forest.

Instances

Instances details
type Eval (UnfoldForest f bs :: Forest a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.Tree

type Eval (UnfoldForest f bs :: Forest a2 -> Type) = Eval (Map (UnfoldTree f) bs)

data Flatten :: Tree a -> Exp [a] Source #

Flatten a Tree.

Example

Expand
>>> :kind! Eval (Flatten ('Node 1 '[ 'Node 2 '[ 'Node 3 '[ 'Node 4 '[]]], 'Node 5 '[ 'Node 6 '[]]]))
Eval (Flatten ('Node 1 '[ 'Node 2 '[ 'Node 3 '[ 'Node 4 '[]]], 'Node 5 '[ 'Node 6 '[]]])) :: [Nat]
= '[1, 2, 3, 4, 5, 6]

Instances

Instances details
type Eval (Flatten ('Node a fs) :: [b] -> Type) Source # 
Instance details

Defined in Fcf.Data.Tree

type Eval (Flatten ('Node a fs) :: [b] -> Type) = a ': Eval (ConcatMap (Flatten :: Tree b -> [b] -> Type) fs)

data GetRoot :: Tree a -> Exp a Source #

Get the root node from a Tree.

Instances

Instances details
type Eval (GetRoot ('Node a2 _1) :: a1 -> Type) Source # 
Instance details

Defined in Fcf.Data.Tree

type Eval (GetRoot ('Node a2 _1) :: a1 -> Type) = a2

data GetForest :: Tree a -> Exp [Tree a] Source #

Get the forest from a Tree.

Instances

Instances details
type Eval (GetForest ('Node _1 f) :: [Tree a] -> Type) Source # 
Instance details

Defined in Fcf.Data.Tree

type Eval (GetForest ('Node _1 f) :: [Tree a] -> Type) = f

data GetRoots :: [Tree a] -> Exp [a] Source #

Get the root nodes from a list of Trees.

Instances

Instances details
type Eval (GetRoots trs :: [b] -> Type) Source # 
Instance details

Defined in Fcf.Data.Tree

type Eval (GetRoots trs :: [b] -> Type) = Eval (Map (GetRoot :: Tree b -> b -> Type) trs)

data GetForests :: [Tree a] -> Exp [Tree a] Source #

Get the forests from a list of Trees.

Instances

Instances details
type Eval (GetForests ts :: [Tree a] -> Type) Source # 
Instance details

Defined in Fcf.Data.Tree

type Eval (GetForests ts :: [Tree a] -> Type) = Eval (ConcatMap (GetForest :: Tree a -> [Tree a] -> Type) ts)

data SubFLevels :: [Tree a] -> Exp (Maybe ([a], [Tree a])) Source #

Instances

Instances details
type Eval (SubFLevels (t ': ts) :: Maybe ([a], [Tree a]) -> Type) Source # 
Instance details

Defined in Fcf.Data.Tree

type Eval (SubFLevels (t ': ts) :: Maybe ([a], [Tree a]) -> Type) = 'Just '(Eval (GetRoots (t ': ts)), Eval (GetForests (t ': ts)))
type Eval (SubFLevels ('[] :: [Tree a]) :: Maybe ([a], [Tree a]) -> Type) Source # 
Instance details

Defined in Fcf.Data.Tree

type Eval (SubFLevels ('[] :: [Tree a]) :: Maybe ([a], [Tree a]) -> Type) = 'Nothing :: Maybe ([a], [Tree a])

data Levels :: Tree a -> Exp [[a]] Source #

Get the levels from a Tree.

Example

Expand
>>> :kind! Eval (Levels ('Node 1 '[ 'Node 2 '[ 'Node 3 '[ 'Node 4 '[]]], 'Node 5 '[ 'Node 6 '[]]]))
Eval (Levels ('Node 1 '[ 'Node 2 '[ 'Node 3 '[ 'Node 4 '[]]], 'Node 5 '[ 'Node 6 '[]]])) :: [[Nat]]
= '[ '[1], '[2, 5], '[3, 6], '[4]]

Instances

Instances details
type Eval (Levels tr :: [[a]] -> Type) Source # 
Instance details

Defined in Fcf.Data.Tree

type Eval (Levels tr :: [[a]] -> Type) = Eval (Unfoldr (SubFLevels :: [Tree a] -> Maybe ([a], [Tree a]) -> Type) '[tr])