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

Fcf.Data.Bitree

Description

Fcf.Data.Bitree

Binary trees

Synopsis

Documentation

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

data Tree a Source #

Binary tree type.

Constructors

Leaf a 
Node (Tree a) a (Tree a) 

Instances

Instances details
Show a => Show (Tree a) Source # 
Instance details

Defined in Fcf.Data.Bitree

Methods

showsPrec :: Int -> Tree a -> ShowS #

show :: Tree a -> String #

showList :: [Tree a] -> ShowS #

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

Fold a type-level Tree.

Instances

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

Defined in Fcf.Data.Bitree

type Eval (FoldTree f ('Node tr1 a3 tr2) :: a2 -> Type) = Eval (f a3 (Eval (Map (FoldTree f) '[tr1, tr2])))
type Eval (FoldTree f ('Leaf a3) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.Bitree

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

data CountSizeHelp :: Nat -> [Nat] -> Exp Nat Source #

Instances

Instances details
type Eval (CountSizeHelp tr '[n1, n2] :: Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.Bitree

type Eval (CountSizeHelp tr '[n1, n2] :: Nat -> Type) = 1 + (n1 + n2)
type Eval (CountSizeHelp tr ('[] :: [Nat]) :: Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.Bitree

type Eval (CountSizeHelp tr ('[] :: [Nat]) :: Nat -> Type) = 1

type ExampleTree2 = 'Node ('Leaf 2) 1 ('Leaf 3) Source #

type ExampleTree3 = 'Node ('Node ('Leaf 4) 2 ('Leaf 5)) 1 ('Node ('Leaf 6) 3 ('Leaf 7)) Source #

type ExampleTree4 = 'Node ('Node ('Leaf 4) 2 ('Leaf 5)) 1 ('Leaf 3) Source #

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

Flatten a Tree.

Example

Instances

Instances details
type Eval (Flatten ('Node tr1 a2 tr2) :: [a1] -> Type) Source # 
Instance details

Defined in Fcf.Data.Bitree

type Eval (Flatten ('Node tr1 a2 tr2) :: [a1] -> Type) = a2 ': Eval (Eval (Flatten tr1) ++ Eval (Flatten tr2))
type Eval (Flatten ('Leaf a) :: [k] -> Type) Source # 
Instance details

Defined in Fcf.Data.Bitree

type Eval (Flatten ('Leaf a) :: [k] -> Type) = '[a]

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

Get the root node from a Tree.

Instances

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

Defined in Fcf.Data.Bitree

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

Defined in Fcf.Data.Bitree

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

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.Bitree

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