{-# LANGUAGE NoImplicitPrelude #-}
module Salak.Trie(
Trie(..)
, empty
, singleton
, Salak.Trie.null
, member
, lookup
, subTrie
, subTries
, insert
, modify
, modify'
, update
, alter
, Salak.Trie.toList
, fromList
, filter
, unionWith
, unionWith'
) where
import Control.Applicative (pure, (<*>))
import Data.Bool
import qualified Data.DList as D
import Data.Eq
import Data.Foldable (Foldable (..))
import Data.Function
import Data.Functor
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HM
import Data.List (concat, intercalate, map, (++))
import Data.Maybe
import Data.Traversable
import Data.Tuple (uncurry)
import Salak.Internal.Key
import Text.Show (Show (..))
data Trie v = Trie
{ tvar :: !(Maybe v)
, tmap :: !(HashMap Key (Trie v))
} deriving (Eq, Functor)
instance Show v => Show (Trie v) where
{-# INLINE show #-}
show t = intercalate "\n" $ map (\(k,v)-> show k ++ ":" ++ show v) $ Salak.Trie.toList t
instance Foldable Trie where
{-# INLINE foldr #-}
foldr f b Trie{..} = foldr (flip (foldr f)) (go tvar) tmap
where
{-# INLINE go #-}
go (Just x) = f x b
go _ = b
instance Traversable Trie where
{-# INLINE traverse #-}
traverse f Trie{..} = Trie <$> go tvar <*> traverse (traverse f) tmap
where
{-# INLINE go #-}
go (Just x) = Just <$> f x
go _ = pure Nothing
{-# INLINE singleton #-}
singleton :: v -> Trie v
singleton v = Trie (Just v) HM.empty
{-# INLINE empty #-}
empty :: Trie v
empty = Trie Nothing HM.empty
{-# INLINE null #-}
null :: Trie v -> Bool
null (Trie Nothing e) = HM.null e
null _ = False
{-# INLINE member #-}
member :: Eq v => Keys -> Trie v -> Bool
member k t = isJust (lookup k t)
{-# INLINE subTrie #-}
subTrie :: Key -> Trie v -> Trie v
subTrie key = fromMaybe empty . HM.lookup key . tmap
{-# INLINE subTries #-}
subTries :: Keys -> Trie v -> Trie v
subTries = flip (foldl' (flip subTrie)) . toKeyList
{-# INLINE lookup #-}
lookup :: Eq v => Keys -> Trie v -> Maybe v
lookup keys = tvar . subTries keys
{-# INLINE insert #-}
insert :: Eq v => Keys -> v -> Trie v -> Trie v
insert ks v = alter (const $ Just v) ks
{-# INLINE modify #-}
modify :: Eq v => Key -> (Trie v -> Trie v) -> Trie v -> Trie v
modify k f (Trie v m) = Trie v $ HM.alter (convert . f . fromMaybe empty) k m
{-# INLINE convert #-}
convert :: Eq v => Trie v -> Maybe (Trie v)
convert x = if x == empty then Nothing else Just x
{-# INLINE modify' #-}
modify' :: Eq v => (Trie v -> Trie v) -> Keys -> Trie v -> Trie v
modify' f = foldr modify f . toKeyList
{-# INLINE update #-}
update :: Eq v => (Maybe v -> Maybe v) -> Trie v -> Trie v
update = flip alter mempty
{-# INLINE alter #-}
alter :: Eq v => (Maybe v -> Maybe v) -> Keys -> Trie v -> Trie v
alter f = modify' (\(Trie a b) -> Trie (f a) b)
toList :: Trie v -> [(Keys, v)]
toList = go D.empty
where
{-# INLINE go #-}
go p (Trie (Just v) m) = (Keys p, v) : g2 p m
go p (Trie _ m) = g2 p m
{-# INLINE g2 #-}
g2 p m = concat $ g3 p <$> HM.toList m
{-# INLINE g3 #-}
g3 p (k,t) = go (D.snoc p k) t
{-# INLINE fromList #-}
fromList :: Eq v => [(Keys, v)] -> Trie v
fromList = foldr (uncurry insert) empty
{-# INLINE filter #-}
filter :: Eq v => (v -> Bool) -> Trie v -> Trie v
filter f (Trie v m) = if ok v then Trie v go else Trie Nothing go
where
{-# INLINE ok #-}
ok (Just x) = f x
ok _ = False
{-# INLINE go #-}
go = HM.mapMaybe (convert . filter f) m
{-# INLINE unionWith #-}
unionWith :: Eq v => (Maybe v -> Maybe v -> Maybe v) -> Trie v -> Trie v -> Trie v
unionWith f (Trie v1 m1) (Trie v2 m2) = Trie (f v1 v2) $ HM.unionWith (unionWith f) m1 m2
{-# INLINE unionWith' #-}
unionWith' :: (Maybe v -> Maybe v -> Maybe v3) -> Trie v -> Trie v -> Trie v3
unionWith' f (Trie v1 m1) (Trie v2 m2) = Trie (f v1 v2) $ foldr go HM.empty $ HM.keys $ HM.union m1 m2
where
{-# INLINE go #-}
go k =
let x1 = fromMaybe empty $ HM.lookup k m1
x2 = fromMaybe empty $ HM.lookup k m2
in HM.insert k (unionWith' f x1 x2)