Copyright | (c) Nicolás Rodríguez 2021 |
---|---|
License | GPL-3 |
Maintainer | Nicolás Rodríguez |
Stability | experimental |
Portability | POSIX |
Safe Haskell | Safe |
Language | Haskell2010 |
Implementation of the deletion algorithm over ITree trees for externalist BST trees.
Synopsis
- class Maxable (t :: Tree) where
- class MaxKeyDeletable (t :: Tree) where
- type MaxKeyDelete (t :: Tree) :: Tree
- maxKeyDelete :: t ~ 'ForkTree l (Node n a1) r => ITree t -> ITree (MaxKeyDelete t)
- class Deletable (x :: Nat) (t :: Tree) where
- class Deletable' (x :: Nat) (t :: Tree) (o :: Ordering) where
Documentation
class Maxable (t :: Tree) where Source #
This type class provides the functionality to get the key, type and value of the node with maximum key value
in a tree t
without checking any structural invariant (key ordering).
The lookup is defined at the value level and the type level, and is performed
as if the tree is a BST
.
Since the keys are only kept at the type level, there's no value level getter of the maximum key.
Instances
Maxable ('ForkTree rl (Node rn ra) rr) => Maxable ('ForkTree l (Node n a1) ('ForkTree rl (Node rn ra) rr)) Source # | |
Maxable ('ForkTree l (Node n a1) 'EmptyTree) Source # | |
class MaxKeyDeletable (t :: Tree) where Source #
This type class provides the functionality to delete the node with maximum key value
in a tree t
without checking any structural invariant (key ordering).
The deletion is defined at the value level and the type level, and is performed
as if the tree is a BST
; the verification of the BST
restrictions is performed after the deletion.
type MaxKeyDelete (t :: Tree) :: Tree Source #
maxKeyDelete :: t ~ 'ForkTree l (Node n a1) r => ITree t -> ITree (MaxKeyDelete t) Source #
Instances
MaxKeyDeletable 'EmptyTree Source # | |
Defined in Data.Tree.BST.Extern.Delete type MaxKeyDelete 'EmptyTree :: Tree Source # | |
MaxKeyDeletable ('ForkTree rl (Node rn ra) rr) => MaxKeyDeletable ('ForkTree l (Node n a1) ('ForkTree rl (Node rn ra) rr)) Source # | |
Defined in Data.Tree.BST.Extern.Delete maxKeyDelete :: forall (l0 :: Tree) (n0 :: Nat) a10 (r :: Tree). 'ForkTree l (Node n a1) ('ForkTree rl (Node rn ra) rr) ~ 'ForkTree l0 (Node n0 a10) r => ITree ('ForkTree l (Node n a1) ('ForkTree rl (Node rn ra) rr)) -> ITree (MaxKeyDelete ('ForkTree l (Node n a1) ('ForkTree rl (Node rn ra) rr))) Source # | |
MaxKeyDeletable ('ForkTree l (Node n a1) 'EmptyTree) Source # | |
Defined in Data.Tree.BST.Extern.Delete |
class Deletable (x :: Nat) (t :: Tree) where Source #
This type class provides the functionality to delete the node with key x
in a tree t
without checking any structural invariant (key ordering).
The deletion is defined at the value level and the type level, and is performed
as if the tree is a BST
; the key ordering is verified after the deletion.
delete :: Proxy x -> ITree t -> ITree (Delete x t) Source #
Delete the node with the given key. If the key is not in the tree, return the same tree.
class Deletable' (x :: Nat) (t :: Tree) (o :: Ordering) where Source #
This type class provides the functionality to delete a node with key x
in a non empty tree t
without checking any structural invariant (key ordering).
It's only used by the Deletable
type class and it has one extra parameter o
,
which is the type level comparison of x
with the key value of the root node.
The o
parameter guides the deletion.
Instances
(o ~ CmpNat x rn, Deletable' x ('ForkTree rl (Node rn ra) rr) o) => Deletable' x ('ForkTree l (Node n a1) ('ForkTree rl (Node rn ra) rr)) 'GT Source # | |
Defined in Data.Tree.BST.Extern.Delete | |
Deletable' x ('ForkTree l (Node n a1) 'EmptyTree) 'GT Source # | |
(o ~ CmpNat x ln, Deletable' x ('ForkTree ll (Node ln la) lr) o) => Deletable' x ('ForkTree ('ForkTree ll (Node ln la) lr) (Node n a1) r) 'LT Source # | |
Defined in Data.Tree.BST.Extern.Delete | |
Deletable' x ('ForkTree 'EmptyTree (Node n a1) r) 'LT Source # | |
(l ~ 'ForkTree ll (Node ln la) lr, Show (MaxValue l), MaxKeyDeletable l, Maxable l) => Deletable' x ('ForkTree ('ForkTree ll (Node ln la) lr) (Node n a1) ('ForkTree rl (Node rn ra) rr)) 'EQ Source # | |
Deletable' x ('ForkTree ('ForkTree ll (Node ln la) lr) (Node n a1) 'EmptyTree) 'EQ Source # | |
Deletable' x ('ForkTree 'EmptyTree (Node n a1) ('ForkTree rl (Node rn ra) rr)) 'EQ Source # | |
Deletable' x ('ForkTree 'EmptyTree (Node n a1) 'EmptyTree) 'EQ Source # | |