{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FunctionalDependencies, Safe #-}
module Data.Chatty.BST where
import Data.Maybe
import Data.Chatty.None
class Ord o => Indexable i o v | i -> o, i -> v where
indexOf :: i -> o
valueOf :: i -> v
instance Indexable Int Int Int where
indexOf :: Int -> Int
indexOf = Int -> Int
forall a. a -> a
id
valueOf :: Int -> Int
valueOf = Int -> Int
forall a. a -> a
id
instance Ord o => Indexable (o,a) o a where
indexOf :: (o, a) -> o
indexOf = (o, a) -> o
forall a b. (a, b) -> a
fst
valueOf :: (o, a) -> a
valueOf = (o, a) -> a
forall a b. (a, b) -> b
snd
instance Ord o => Indexable (o,a,b) o (a,b) where
indexOf :: (o, a, b) -> o
indexOf (o
o,a
_,b
_) = o
o
valueOf :: (o, a, b) -> (a, b)
valueOf (o
_,a
a,b
b) = (a
a,b
b)
instance Ord o => Indexable (o,a,b,c) o (a,b,c) where
indexOf :: (o, a, b, c) -> o
indexOf (o
o,a
_,b
_,c
_) = o
o
valueOf :: (o, a, b, c) -> (a, b, c)
valueOf (o
_,a
a,b
b,c
c) = (a
a,b
b,c
c)
instance Ord o => Indexable (o,a,b,c,d) o (a,b,c,d) where
indexOf :: (o, a, b, c, d) -> o
indexOf (o
o,a
_,b
_,c
_,d
_) = o
o
valueOf :: (o, a, b, c, d) -> (a, b, c, d)
valueOf (o
_,a
a,b
b,c
c,d
d) = (a
a,b
b,c
c,d
d)
instance Ord o => Indexable (o,a,b,c,d,e) o (a,b,c,d,e) where
indexOf :: (o, a, b, c, d, e) -> o
indexOf (o
o,a
a,b
b,c
c,d
d,e
e) = o
o
valueOf :: (o, a, b, c, d, e) -> (a, b, c, d, e)
valueOf (o
o,a
a,b
b,c
c,d
d,e
e) = (a
a,b
b,c
c,d
d,e
e)
class Indexable i o v => AnyBST t i o v where
anyBstInsert :: i -> t i -> t i
anyBstRemove :: o -> t i -> t i
anyBstMax :: t i -> Maybe i
anyBstMin :: t i -> Maybe i
anyBstLookup :: o -> t i -> Maybe v
anyBstEmpty :: t i
anyBstHead :: t i -> Maybe i
anyBstInorder :: t i -> [i]
instance Indexable i o v => AnyBST BST i o v where
anyBstInsert :: i -> BST i -> BST i
anyBstInsert = i -> BST i -> BST i
forall i o v. Indexable i o v => i -> BST i -> BST i
bstInsert
anyBstRemove :: o -> BST i -> BST i
anyBstRemove = o -> BST i -> BST i
forall i o v. Indexable i o v => o -> BST i -> BST i
bstRemove
anyBstMax :: BST i -> Maybe i
anyBstMax = BST i -> Maybe i
forall i. BST i -> Maybe i
bstMax
anyBstMin :: BST i -> Maybe i
anyBstMin = BST i -> Maybe i
forall i. BST i -> Maybe i
bstMin
anyBstLookup :: o -> BST i -> Maybe v
anyBstLookup = o -> BST i -> Maybe v
forall i o v. Indexable i o v => o -> BST i -> Maybe v
bstLookup
anyBstEmpty :: BST i
anyBstEmpty = BST i
forall a. BST a
EmptyBST
anyBstHead :: BST i -> Maybe i
anyBstHead = BST i -> Maybe i
forall i o v. Indexable i o v => BST i -> Maybe i
bstHead
anyBstInorder :: BST i -> [i]
anyBstInorder = BST i -> [i]
forall i o v. Indexable i o v => BST i -> [i]
bstInorder
instance None (BST a) where
none :: BST a
none = BST a
forall a. BST a
EmptyBST
data BST a = EmptyBST | BST a !(BST a) !(BST a)
bstInsert :: Indexable i o v => i -> BST i -> BST i
bstInsert :: i -> BST i -> BST i
bstInsert i
i BST i
EmptyBST = i -> BST i -> BST i -> BST i
forall a. a -> BST a -> BST a -> BST a
BST i
i BST i
forall a. BST a
EmptyBST BST i
forall a. BST a
EmptyBST
bstInsert i
i (BST i
a BST i
l BST i
r)
| i -> o
forall i o v. Indexable i o v => i -> o
indexOf i
i o -> o -> Bool
forall a. Ord a => a -> a -> Bool
< i -> o
forall i o v. Indexable i o v => i -> o
indexOf i
a = i -> BST i -> BST i -> BST i
forall a. a -> BST a -> BST a -> BST a
BST i
a (i -> BST i -> BST i
forall i o v. Indexable i o v => i -> BST i -> BST i
bstInsert i
i BST i
l) BST i
r
| i -> o
forall i o v. Indexable i o v => i -> o
indexOf i
i o -> o -> Bool
forall a. Ord a => a -> a -> Bool
> i -> o
forall i o v. Indexable i o v => i -> o
indexOf i
a = i -> BST i -> BST i -> BST i
forall a. a -> BST a -> BST a -> BST a
BST i
a BST i
l (i -> BST i -> BST i
forall i o v. Indexable i o v => i -> BST i -> BST i
bstInsert i
i BST i
r)
| Bool
otherwise = i -> BST i -> BST i -> BST i
forall a. a -> BST a -> BST a -> BST a
BST i
i BST i
l BST i
r
bstRemove :: Indexable i o v => o -> BST i -> BST i
bstRemove :: o -> BST i -> BST i
bstRemove o
o BST i
EmptyBST = BST i
forall a. BST a
EmptyBST
bstRemove o
o (BST i
a BST i
EmptyBST BST i
r) | i -> o
forall i o v. Indexable i o v => i -> o
indexOf i
a o -> o -> Bool
forall a. Eq a => a -> a -> Bool
== o
o = BST i
r
bstRemove o
o (BST i
a BST i
l BST i
EmptyBST) | i -> o
forall i o v. Indexable i o v => i -> o
indexOf i
a o -> o -> Bool
forall a. Eq a => a -> a -> Bool
== o
o = BST i
l
bstRemove o
o (BST i
a BST i
l BST i
r)
| i -> o
forall i o v. Indexable i o v => i -> o
indexOf i
a o -> o -> Bool
forall a. Ord a => a -> a -> Bool
< o
o = i -> BST i -> BST i -> BST i
forall a. a -> BST a -> BST a -> BST a
BST i
a (o -> BST i -> BST i
forall i o v. Indexable i o v => o -> BST i -> BST i
bstRemove o
o BST i
l) BST i
r
| i -> o
forall i o v. Indexable i o v => i -> o
indexOf i
a o -> o -> Bool
forall a. Ord a => a -> a -> Bool
> o
o = i -> BST i -> BST i -> BST i
forall a. a -> BST a -> BST a -> BST a
BST i
a BST i
l (o -> BST i -> BST i
forall i o v. Indexable i o v => o -> BST i -> BST i
bstRemove o
o BST i
r)
| Bool
otherwise = let (Just i
m) = BST i -> Maybe i
forall i. BST i -> Maybe i
bstMax BST i
l in i -> BST i -> BST i -> BST i
forall a. a -> BST a -> BST a -> BST a
BST i
m (o -> BST i -> BST i
forall i o v. Indexable i o v => o -> BST i -> BST i
bstRemove (i -> o
forall i o v. Indexable i o v => i -> o
indexOf i
m) BST i
l) BST i
r
bstMax :: BST i -> Maybe i
bstMax :: BST i -> Maybe i
bstMax BST i
EmptyBST = Maybe i
forall a. Maybe a
Nothing
bstMax (BST i
a BST i
_ BST i
EmptyBST) = i -> Maybe i
forall a. a -> Maybe a
Just i
a
bstMax (BST i
_ BST i
_ BST i
r) = BST i -> Maybe i
forall i. BST i -> Maybe i
bstMax BST i
r
bstMin :: BST i -> Maybe i
bstMin :: BST i -> Maybe i
bstMin BST i
EmptyBST = Maybe i
forall a. Maybe a
Nothing
bstMin (BST i
a BST i
EmptyBST BST i
_) = i -> Maybe i
forall a. a -> Maybe a
Just i
a
bstMin (BST i
_ BST i
l BST i
_) = BST i -> Maybe i
forall i. BST i -> Maybe i
bstMin BST i
l
bstLookup :: Indexable i o v => o -> BST i -> Maybe v
bstLookup :: o -> BST i -> Maybe v
bstLookup o
_ BST i
EmptyBST = Maybe v
forall a. Maybe a
Nothing
bstLookup o
o (BST i
a BST i
l BST i
r)
| o
o o -> o -> Bool
forall a. Eq a => a -> a -> Bool
== i -> o
forall i o v. Indexable i o v => i -> o
indexOf i
a = v -> Maybe v
forall a. a -> Maybe a
Just (v -> Maybe v) -> v -> Maybe v
forall a b. (a -> b) -> a -> b
$ i -> v
forall i o v. Indexable i o v => i -> v
valueOf i
a
| o
o o -> o -> Bool
forall a. Ord a => a -> a -> Bool
< i -> o
forall i o v. Indexable i o v => i -> o
indexOf i
a = o -> BST i -> Maybe v
forall i o v. Indexable i o v => o -> BST i -> Maybe v
bstLookup o
o BST i
l
| o
o o -> o -> Bool
forall a. Ord a => a -> a -> Bool
> i -> o
forall i o v. Indexable i o v => i -> o
indexOf i
a = o -> BST i -> Maybe v
forall i o v. Indexable i o v => o -> BST i -> Maybe v
bstLookup o
o BST i
r
bstContains :: Indexable i o v => o -> BST i -> Bool
bstContains :: o -> BST i -> Bool
bstContains o
o = Maybe v -> Bool
forall a. Maybe a -> Bool
isJust (Maybe v -> Bool) -> (BST i -> Maybe v) -> BST i -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> BST i -> Maybe v
forall i o v. Indexable i o v => o -> BST i -> Maybe v
bstLookup o
o
bstHead :: Indexable i o v => BST i -> Maybe i
bstHead :: BST i -> Maybe i
bstHead BST i
EmptyBST = Maybe i
forall a. Maybe a
Nothing
bstHead (BST i
a BST i
_ BST i
_) = i -> Maybe i
forall a. a -> Maybe a
Just i
a
bstInorder :: Indexable i o v => BST i -> [i]
bstInorder :: BST i -> [i]
bstInorder BST i
EmptyBST = []
bstInorder (BST i
a BST i
l BST i
r) = BST i -> [i]
forall i o v. Indexable i o v => BST i -> [i]
bstInorder BST i
l [i] -> [i] -> [i]
forall a. [a] -> [a] -> [a]
++ [i
a] [i] -> [i] -> [i]
forall a. [a] -> [a] -> [a]
++ BST i -> [i]
forall i o v. Indexable i o v => BST i -> [i]
bstInorder BST i
r