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 = id
  valueOf = id
instance Ord o => Indexable (o,a) o a where
  indexOf = fst
  valueOf = snd
instance Ord o => Indexable (o,a,b) o (a,b) where
  indexOf (o,_,_) = o
  valueOf (_,a,b) = (a,b)
instance Ord o => Indexable (o,a,b,c) o (a,b,c) where
  indexOf (o,_,_,_) = o
  valueOf (_,a,b,c) = (a,b,c)
instance Ord o => Indexable (o,a,b,c,d) o (a,b,c,d) where
  indexOf (o,_,_,_,_) = o
  valueOf (_,a,b,c,d) = (a,b,c,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
  valueOf (o,a,b,c,d,e) = (a,b,c,d,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 = bstInsert
  anyBstRemove = bstRemove
  anyBstMax = bstMax
  anyBstMin =  bstMin
  anyBstLookup = bstLookup
  anyBstEmpty = EmptyBST
  anyBstHead = bstHead
  anyBstInorder = bstInorder
instance None (BST a) where
  none = EmptyBST
data BST a = EmptyBST | BST a !(BST a) !(BST a)
bstInsert :: Indexable i o v => i -> BST i -> BST i
bstInsert i EmptyBST = BST i EmptyBST EmptyBST
bstInsert i (BST a l r)
  | indexOf i < indexOf a = BST a (bstInsert i l) r
  | indexOf i > indexOf a = BST a l (bstInsert i r)
  | otherwise = BST i l r
bstRemove :: Indexable i o v => o -> BST i -> BST i
bstRemove o EmptyBST = EmptyBST
bstRemove o (BST a EmptyBST r) | indexOf a == o = r
bstRemove o (BST a l EmptyBST) | indexOf a == o = l
bstRemove o (BST a l r)
  | indexOf a < o = BST a (bstRemove o l) r
  | indexOf a > o = BST a l (bstRemove o r)
  | otherwise = let (Just m) = bstMax l in BST m (bstRemove (indexOf m) l) r
bstMax :: BST i -> Maybe i
bstMax EmptyBST = Nothing
bstMax (BST a _ EmptyBST) = Just a
bstMax (BST _ _ r) = bstMax r
bstMin :: BST i -> Maybe i
bstMin EmptyBST = Nothing
bstMin (BST a EmptyBST _) = Just a
bstMin (BST _ l _) = bstMin l
bstLookup :: Indexable i o v => o -> BST i -> Maybe v
bstLookup _ EmptyBST = Nothing
bstLookup o (BST a l r)
  | o == indexOf a = Just $ valueOf a
  | o < indexOf a = bstLookup o l
  | o > indexOf a = bstLookup o r
bstContains :: Indexable i o v => o -> BST i -> Bool
bstContains o = isJust . bstLookup o
bstHead :: Indexable i o v => BST i -> Maybe i
bstHead EmptyBST = Nothing
bstHead (BST a _ _) = Just a
bstInorder :: Indexable i o v => BST i -> [i]
bstInorder EmptyBST = []
bstInorder (BST a l r) = bstInorder l ++ [a] ++ bstInorder r