Copyright | (c) gspia 2020- |
---|---|
License | BSD |
Maintainer | gspia |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Fcf.Data.Bitree
Binary trees
Synopsis
- data Tree a
- data FoldTree :: (a -> [b] -> Exp b) -> Tree a -> Exp b
- data CountSizeHelp :: Nat -> [Nat] -> Exp Nat
- type ExampleTree1 = 'Leaf 1
- type ExampleTree2 = 'Node ('Leaf 2) 1 ('Leaf 3)
- type ExampleTree3 = 'Node ('Node ('Leaf 4) 2 ('Leaf 5)) 1 ('Node ('Leaf 6) 3 ('Leaf 7))
- type ExampleTree4 = 'Node ('Node ('Leaf 4) 2 ('Leaf 5)) 1 ('Leaf 3)
- data Flatten :: Tree a -> Exp [a]
- data GetRoot :: Tree a -> Exp a
- data GetRoots :: [Tree a] -> Exp [a]
Documentation
>>>
import qualified GHC.TypeLits as TL
>>>
import Fcf.Data.Nat
Binary tree type.
data FoldTree :: (a -> [b] -> Exp b) -> Tree a -> Exp b Source #
Fold a type-level Tree
.
data CountSizeHelp :: Nat -> [Nat] -> Exp Nat Source #
Instances
type Eval (CountSizeHelp tr '[n1, n2] :: Nat -> Type) Source # | |
Defined in Fcf.Data.Bitree | |
type Eval (CountSizeHelp tr ('[] :: [Nat]) :: Nat -> Type) Source # | |
Defined in Fcf.Data.Bitree |
type ExampleTree1 = 'Leaf 1 Source #
data Flatten :: Tree a -> Exp [a] Source #
Flatten a Tree
.