{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
module CHR.Data.Lookup.Types
(
Lookup(..)
, LookupApply(..)
, alterDefault
)
where
import qualified Data.Set as Set
import Control.Arrow
import Prelude hiding (lookup, map)
import qualified Data.List as List
class Lookup c k v | c -> k, c -> v where
lookup :: k -> c -> Maybe v
fromList :: [(k,v)] -> c
toList :: c -> [(k,v)]
null :: c -> Bool
size :: c -> Int
alter :: (Maybe v -> Maybe v) -> k -> c -> c
singleton :: k -> v -> c
empty :: c
insertWith :: (v -> v -> v) -> k -> v -> c -> c
insert :: k -> v -> c -> c
unionWith :: (v -> v -> v) -> c -> c -> c
union :: c -> c -> c
unionsWith :: (v -> v -> v) -> [c] -> c
unions :: [c] -> c
delete :: k -> c -> c
keys :: c -> [k]
keysSet :: Ord k => c -> Set.Set k
elems :: c -> [v]
map :: (v -> v) -> c -> c
singleton k v = fromList [(k,v)]
empty = fromList []
insertWith f k v c = alter (Just . maybe v (f v)) k c
insert = insertWith const
unionWith f c1 c2 = foldr (uncurry $ insertWith f) c2 $ toList c1
union = unionWith const
unionsWith f [] = empty
unionsWith f l = foldr1 (unionWith f) l
unions = unionsWith const
delete = alter (const Nothing)
keys = List.map fst . toList
keysSet = Set.fromList . keys
elems = List.map snd . toList
map f = fromList . List.map (second f) . toList
null c = size c == 0
alterDefault :: Lookup c k v => (Maybe v -> Maybe v) -> k -> c -> c
alterDefault f k c = case f $ lookup k c of
Just v -> insert k v c
_ -> delete k c
class LookupApply l1 l2 where
apply :: l1 -> l2 -> l2