type-safe-avl-1.0.0.1: Type safe BST and AVL trees
Copyright(c) Nicolás Rodríguez 2021
LicenseGPL-3
MaintainerNicolás Rodríguez
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe
LanguageHaskell2010

Data.Tree.AVL.Extern.Insert

Description

Implementation of the insertion algorithm over ITree trees for externalist AVL trees.

Synopsis

Documentation

class Insertable (x :: Nat) (a :: Type) (t :: Tree) where Source #

This type class provides the functionality to insert a node with key x and value type a in a tree t without checking any structural invariant (key ordering or height balance). The insertion is defined at the value level and the type level, and is performed as if the tree is an AVL; the verification of the AVL restrictions is performed after the insertion.

Associated Types

type Insert (x :: Nat) (a :: Type) (t :: Tree) :: Tree Source #

Methods

insert :: Node x a -> ITree t -> ITree (Insert x a t) Source #

Insert a new node. If the key is already present in the tree, update the value.

Instances

Instances details
Show a => Insertable x a 'EmptyTree Source # 
Instance details

Defined in Data.Tree.AVL.Extern.Insert

Associated Types

type Insert x a 'EmptyTree :: Tree Source #

Methods

insert :: Node x a -> ITree 'EmptyTree -> ITree (Insert x a 'EmptyTree) Source #

(o ~ CmpNat x n, Insertable' x a ('ForkTree l (Node n a1) r) o) => Insertable x a ('ForkTree l (Node n a1) r) Source # 
Instance details

Defined in Data.Tree.AVL.Extern.Insert

Associated Types

type Insert x a ('ForkTree l (Node n a1) r) :: Tree Source #

Methods

insert :: Node x a -> ITree ('ForkTree l (Node n a1) r) -> ITree (Insert x a ('ForkTree l (Node n a1) r)) Source #

class Insertable' (x :: Nat) (a :: Type) (t :: Tree) (o :: Ordering) Source #

This type class provides the functionality to insert a node with key x and value type a in a non empty tree t without checking any structural invariant (key ordering or height balance). It's only used by the Insertable 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 insertion.

Minimal complete definition

insert'

Associated Types

type Insert' (x :: Nat) (a :: Type) (t :: Tree) (o :: Ordering) :: Tree Source #

Instances

Instances details
(r ~ 'ForkTree rl (Node rn rna) rr, o ~ CmpNat x rn, Insertable' x a r o, Balanceable ('ForkTree l (Node n a1) (Insert' x a r o))) => Insertable' x a ('ForkTree l (Node n a1) ('ForkTree rl (Node rn rna) rr)) 'GT Source # 
Instance details

Defined in Data.Tree.AVL.Extern.Insert

Associated Types

type Insert' x a ('ForkTree l (Node n a1) ('ForkTree rl (Node rn rna) rr)) 'GT :: Tree Source #

Methods

insert' :: Node x a -> ITree ('ForkTree l (Node n a1) ('ForkTree rl (Node rn rna) rr)) -> Proxy 'GT -> ITree (Insert' x a ('ForkTree l (Node n a1) ('ForkTree rl (Node rn rna) rr)) 'GT)

(Show a, Balanceable ('ForkTree l (Node n a1) ('ForkTree 'EmptyTree (Node x a) 'EmptyTree))) => Insertable' x a ('ForkTree l (Node n a1) 'EmptyTree) 'GT Source # 
Instance details

Defined in Data.Tree.AVL.Extern.Insert

Associated Types

type Insert' x a ('ForkTree l (Node n a1) 'EmptyTree) 'GT :: Tree Source #

Methods

insert' :: Node x a -> ITree ('ForkTree l (Node n a1) 'EmptyTree) -> Proxy 'GT -> ITree (Insert' x a ('ForkTree l (Node n a1) 'EmptyTree) 'GT)

(l ~ 'ForkTree ll (Node ln lna) lr, o ~ CmpNat x ln, Insertable' x a l o, Balanceable ('ForkTree (Insert' x a l o) (Node n a1) r)) => Insertable' x a ('ForkTree ('ForkTree ll (Node ln lna) lr) (Node n a1) r) 'LT Source # 
Instance details

Defined in Data.Tree.AVL.Extern.Insert

Associated Types

type Insert' x a ('ForkTree ('ForkTree ll (Node ln lna) lr) (Node n a1) r) 'LT :: Tree Source #

Methods

insert' :: Node x a -> ITree ('ForkTree ('ForkTree ll (Node ln lna) lr) (Node n a1) r) -> Proxy 'LT -> ITree (Insert' x a ('ForkTree ('ForkTree ll (Node ln lna) lr) (Node n a1) r) 'LT)

(Show a, Balanceable ('ForkTree ('ForkTree 'EmptyTree (Node x a) 'EmptyTree) (Node n a1) r)) => Insertable' x a ('ForkTree 'EmptyTree (Node n a1) r) 'LT Source # 
Instance details

Defined in Data.Tree.AVL.Extern.Insert

Associated Types

type Insert' x a ('ForkTree 'EmptyTree (Node n a1) r) 'LT :: Tree Source #

Methods

insert' :: Node x a -> ITree ('ForkTree 'EmptyTree (Node n a1) r) -> Proxy 'LT -> ITree (Insert' x a ('ForkTree 'EmptyTree (Node n a1) r) 'LT)

Show a => Insertable' x a ('ForkTree l (Node n a1) r) 'EQ Source # 
Instance details

Defined in Data.Tree.AVL.Extern.Insert

Associated Types

type Insert' x a ('ForkTree l (Node n a1) r) 'EQ :: Tree Source #

Methods

insert' :: Node x a -> ITree ('ForkTree l (Node n a1) r) -> Proxy 'EQ -> ITree (Insert' x a ('ForkTree l (Node n a1) r) 'EQ)