module Data.TreeMap.Strict where
import Control.Applicative (Applicative(..), Alternative((<|>)))
import Control.DeepSeq (NFData(..))
import Control.Monad (Monad(..))
import Data.Bool
import Data.Data (Data)
import Data.Eq (Eq(..))
import Data.Foldable (Foldable, foldMap)
import Data.Function (($), (.), const, flip, id)
import Data.Functor (Functor(..), (<$>))
import Data.Map.Strict (Map)
import Data.Maybe (Maybe(..), maybe)
import Data.Monoid (Monoid(..))
import Data.NonNull (NonNull, nuncons, toNullable)
import Data.Ord (Ord(..))
import Data.Semigroup (Semigroup(..))
import Data.Sequences (reverse)
import Data.Traversable (Traversable(..))
import Data.Typeable (Typeable)
import Prelude (Int, Num(..), seq)
import Text.Show (Show(..))
import qualified Control.Applicative as App
import qualified Data.List as List
import qualified Data.Map.Strict as Map
import qualified Data.NonNull as NonNull
import qualified Data.Strict.Maybe as Strict
deriving instance Data x => Data (Strict.Maybe x)
deriving instance Typeable Strict.Maybe
instance Semigroup x => Semigroup (Strict.Maybe x) where
Strict.Just x <> Strict.Just y = Strict.Just (x <> y)
x <> Strict.Nothing = x
Strict.Nothing <> y = y
instance Semigroup x => Monoid (Strict.Maybe x) where
mempty = Strict.Nothing
mappend = (<>)
instance NFData x => NFData (Strict.Maybe x) where
rnf Strict.Nothing = ()
rnf (Strict.Just x) = rnf x
instance Applicative Strict.Maybe where
pure = Strict.Just
Strict.Just f <*> Strict.Just x = Strict.Just (f x)
_ <*> _ = Strict.Nothing
instance Alternative Strict.Maybe where
empty = Strict.Nothing
x <|> y = if Strict.isJust x then x else y
newtype TreeMap k x
= TreeMap (Map k (Node k x))
deriving (Data, Eq, Ord, Show, Typeable)
instance (Ord k, Semigroup v) => Semigroup (TreeMap k v) where
(<>) = union (<>)
instance (Ord k, Monoid v) => Monoid (TreeMap k v) where
mempty = empty
mappend = union mappend
instance Ord k => Functor (TreeMap k) where
fmap f (TreeMap m) = TreeMap $ fmap (fmap f) m
instance Ord k => Foldable (TreeMap k) where
foldMap f (TreeMap m) = foldMap (foldMap f) m
instance Ord k => Traversable (TreeMap k) where
traverse f (TreeMap m) = TreeMap <$> traverse (traverse f) m
instance (Ord k, NFData k, NFData x) => NFData (TreeMap k x) where
rnf (TreeMap m) = rnf m
type Path k = NonNull [k]
path :: k -> [k] -> Path k
path = NonNull.ncons
(<|) :: k -> [k] -> Path k
(<|) = path
data Node k x
= Node
{ node_size :: !Int
, node_value :: !(Strict.Maybe x)
, node_descendants :: !(TreeMap k x)
} deriving (Data, Eq, Ord, Show, Typeable)
instance (Ord k, Semigroup v) => Semigroup (Node k v) where
(<>)
Node{node_value=x0, node_descendants=m0}
Node{node_value=x1, node_descendants=m1} =
node (x0 <> x1) (union const m0 m1)
instance (Ord k, Semigroup v) => Monoid (Node k v) where
mempty = node Strict.Nothing (TreeMap mempty)
mappend = (<>)
instance Ord k => Functor (Node k) where
fmap f Node{node_value=x, node_descendants=m, node_size} =
Node
{ node_value = fmap f x
, node_descendants = map f m
, node_size
}
instance Ord k => Foldable (Node k) where
foldMap f Node{node_value=Strict.Nothing, node_descendants=TreeMap m} =
foldMap (foldMap f) m
foldMap f Node{node_value=Strict.Just x, node_descendants=TreeMap m} =
f x `mappend` foldMap (foldMap f) m
instance Ord k => Traversable (Node k) where
traverse f Node{node_value=Strict.Nothing, node_descendants=TreeMap m, node_size} =
Node node_size <$> pure Strict.Nothing <*> (TreeMap <$> traverse (traverse f) m)
traverse f Node{node_value=Strict.Just x, node_descendants=TreeMap m, node_size} =
Node node_size <$> (Strict.Just <$> f x) <*> (TreeMap <$> traverse (traverse f) m)
instance (Ord k, NFData k, NFData x) => NFData (Node k x) where
rnf (Node s v d) = rnf s `seq` rnf v `seq` rnf d
node :: Strict.Maybe x -> TreeMap k x -> Node k x
node node_value node_descendants =
Node
{ node_value
, node_size =
size node_descendants +
Strict.maybe 0 (const 1) node_value
, node_descendants
}
nodeEmpty :: Node k x
nodeEmpty = node Strict.Nothing empty
nodeLookup :: Ord k => [k] -> Node k x -> Strict.Maybe (Node k x)
nodeLookup [] n = Strict.Just n
nodeLookup (k:ks) Node{node_descendants=TreeMap m} =
maybe Strict.Nothing (nodeLookup ks) $
Map.lookup k m
empty :: TreeMap k x
empty = TreeMap Map.empty
singleton :: Ord k => Path k -> x -> TreeMap k x
singleton ks x = insert const ks x empty
leaf :: x -> Node k x
leaf x = node (Strict.Just x) empty
insert :: Ord k => (x -> x -> x) -> Path k -> x -> TreeMap k x -> TreeMap k x
insert merge p x (TreeMap m) =
TreeMap $
case nuncons p of
(k, Nothing) ->
Map.insertWith (\_ Node{..} -> node
(Strict.maybe (Strict.Just x) (Strict.Just . merge x) node_value)
node_descendants)
k (leaf x) m
(k, Just p') ->
Map.insertWith (\_ Node{..} -> node node_value $
insert merge p' x node_descendants)
k (node Strict.Nothing (insert merge p' x empty)) m
fromList :: Ord k => (x -> x -> x) -> [(Path k, x)] -> TreeMap k x
fromList merge = List.foldl' (\acc (p,x) -> insert merge p x acc) empty
fromMap :: Ord k => Map (Path k) x -> TreeMap k x
fromMap = go . Map.toList
where
go :: Ord k => [(Path k,x)] -> TreeMap k x
go m =
TreeMap $ Map.fromAscListWith
(\Node{node_value=vn, node_descendants=mn}
Node{node_value=vo, node_descendants=mo} ->
node (vn <|> vo) $ union const mn mo) $
(<$> m) $ \(p,x) ->
let (p0,mps) = nuncons p in
case mps of
Nothing -> (p0,node (Strict.Just x) empty)
Just ps -> (p0,node Strict.Nothing $ go [(ps,x)])
nodes :: TreeMap k x -> Map k (Node k x)
nodes (TreeMap m) = m
null :: TreeMap k x -> Bool
null m = size m == 0
size :: TreeMap k x -> Int
size = Map.foldr ((+) . node_size) 0 . nodes
lookup :: Ord k => Path k -> TreeMap k x -> Strict.Maybe x
lookup p (TreeMap m) =
maybe Strict.Nothing nod_val $ Map.lookup k m
where
(k, mp') = nuncons p
nod_val =
case mp' of
Nothing -> node_value
Just p' -> lookup p' . node_descendants
lookupAlong :: Ord k => Path k -> TreeMap k x -> [x]
lookupAlong p (TreeMap tm) =
go (toNullable p) tm
where
go :: Ord k => [k] -> Map k (Node k x) -> [x]
go [] _m = []
go (k:ks) m =
case Map.lookup k m of
Nothing -> []
Just nod ->
Strict.maybe id (:) (node_value nod) $
go ks $ nodes (node_descendants nod)
lookupNode :: Ord k => Path k -> TreeMap k x -> Maybe (Node k x)
lookupNode p (TreeMap m) =
case nuncons p of
(k, Nothing) -> Map.lookup k m
(k, Just p') -> Map.lookup k m >>= lookupNode p' . node_descendants
union :: Ord k => (x -> x -> x) -> TreeMap k x -> TreeMap k x -> TreeMap k x
union merge (TreeMap tm0) (TreeMap tm1) =
TreeMap $
Map.unionWith
(\Node{node_value=x0, node_descendants=m0}
Node{node_value=x1, node_descendants=m1} ->
node (Strict.maybe x1 (\x0' -> Strict.maybe (Strict.Just x0') (Strict.Just . merge x0') x1) x0)
(union merge m0 m1))
tm0 tm1
unions :: Ord k => (x -> x -> x) -> [TreeMap k x] -> TreeMap k x
unions merge = List.foldl' (union merge) empty
map :: Ord k => (x -> y) -> TreeMap k x -> TreeMap k y
map f =
TreeMap .
Map.map
(\n@Node{node_value=x, node_descendants=m} ->
n{ node_value = fmap f x
, node_descendants = map f m
}) .
nodes
mapMonotonic :: (Ord k, Ord l) => (k -> l) -> (x -> y) -> TreeMap k x -> TreeMap l y
mapMonotonic fk fx =
TreeMap .
Map.mapKeysMonotonic fk .
Map.map
(\n@Node{node_value=x, node_descendants=m} ->
n{ node_value = fmap fx x
, node_descendants = mapMonotonic fk fx m
}) .
nodes
mapByDepthFirst :: Ord k => (TreeMap k y -> Strict.Maybe x -> y) -> TreeMap k x -> TreeMap k y
mapByDepthFirst f =
TreeMap .
Map.map
(\Node{node_value, node_descendants} ->
let m = mapByDepthFirst f node_descendants in
node (Strict.Just $ f m node_value) m) .
nodes
alterl_path :: Ord k => (Strict.Maybe x -> Strict.Maybe x) -> Path k -> TreeMap k x -> TreeMap k x
alterl_path fct =
go fct . toNullable
where
go :: Ord k
=> (Strict.Maybe x -> Strict.Maybe x) -> [k]
-> TreeMap k x -> TreeMap k x
go _f [] m = m
go f (k:p) (TreeMap m) =
TreeMap $
Map.alter
(\c ->
let (cv, cm) =
case c of
Just Node{node_value=v, node_descendants=d} -> (v, d)
Nothing -> (Strict.Nothing, empty) in
let fx = f cv in
let gm = go f p cm in
case (fx, size gm) of
(Strict.Nothing, 0) -> Nothing
(_, s) -> Just
Node
{ node_value = fx
, node_descendants = gm
, node_size = s + 1
}
) k m
foldlWithPath :: Ord k => (a -> Path k -> x -> a) -> a -> TreeMap k x -> a
foldlWithPath =
foldp []
where
foldp :: Ord k
=> [k] -> (a -> Path k -> x -> a)
-> a -> TreeMap k x -> a
foldp p fct a (TreeMap m) =
Map.foldlWithKey
(\acc k Node{..} ->
let acc' = Strict.maybe acc (fct acc (reverse $ path k p)) node_value in
foldp (k:p) fct acc' node_descendants) a m
foldlWithPathAndNode :: Ord k => (a -> Node k x -> Path k -> x -> a) -> a -> TreeMap k x -> a
foldlWithPathAndNode =
foldp []
where
foldp :: Ord k
=> [k] -> (a -> Node k x -> Path k -> x -> a)
-> a -> TreeMap k x -> a
foldp p fct a (TreeMap m) =
Map.foldlWithKey
(\acc k n@Node{..} ->
let acc' = Strict.maybe acc (fct acc n (reverse $ path k p)) node_value in
foldp (k:p) fct acc' node_descendants) a m
foldrWithPath :: Ord k => (Path k -> x -> a -> a) -> a -> TreeMap k x -> a
foldrWithPath =
foldp []
where
foldp :: Ord k
=> [k] -> (Path k -> x -> a -> a)
-> a -> TreeMap k x -> a
foldp p fct a (TreeMap m) =
Map.foldrWithKey
(\k Node{..} acc ->
let acc' = foldp (k:p) fct acc node_descendants in
Strict.maybe acc' (\x -> fct (reverse $ path k p) x acc') node_value) a m
foldrWithPathAndNode :: Ord k => (Node k x -> Path k -> x -> a -> a) -> a -> TreeMap k x -> a
foldrWithPathAndNode =
foldp []
where
foldp :: Ord k
=> [k] -> (Node k x -> Path k -> x -> a -> a)
-> a -> TreeMap k x -> a
foldp p fct a (TreeMap m) =
Map.foldrWithKey
(\k n@Node{..} acc ->
let acc' = foldp (k:p) fct acc node_descendants in
Strict.maybe acc' (\x -> fct n (reverse $ path k p) x acc') node_value) a m
foldlPath :: Ord k => (Path k -> x -> a -> a) -> Path k -> TreeMap k x -> a -> a
foldlPath fct =
go fct [] . toNullable
where
go :: Ord k
=> (Path k -> x -> a -> a) -> [k] -> [k]
-> TreeMap k x -> a -> a
go _f _ [] _t a = a
go f p (k:n) (TreeMap t) a =
case Map.lookup k t of
Nothing -> a
Just Node{..} ->
case node_value of
Strict.Nothing -> go f (k:p) n node_descendants a
Strict.Just x -> go f (k:p) n node_descendants (f (reverse $ path k p) x a)
foldrPath :: Ord k => (Path k -> x -> a -> a) -> Path k -> TreeMap k x -> a -> a
foldrPath fct =
go fct [] . toNullable
where
go :: Ord k
=> (Path k -> x -> a -> a) -> [k] -> [k]
-> TreeMap k x -> a -> a
go _f _ [] _t a = a
go f p (k:n) (TreeMap t) a =
case Map.lookup k t of
Nothing -> a
Just Node{..} ->
case node_value of
Strict.Nothing -> go f (k:p) n node_descendants a
Strict.Just x -> f (reverse $ path k p) x $ go f (k:p) n node_descendants a
flatten :: Ord k => (x -> y) -> TreeMap k x -> Map (Path k) y
flatten = flattenWithPath . const
flattenWithPath :: Ord k => (Path k -> x -> y) -> TreeMap k x -> Map (Path k) y
flattenWithPath =
flat_map []
where
flat_map :: Ord k
=> [k] -> (Path k -> x -> y)
-> TreeMap k x
-> Map (Path k) y
flat_map p f (TreeMap m) =
Map.unions $
Map.mapKeysMonotonic (reverse . flip path p) (
Map.mapMaybeWithKey (\k Node{node_value} ->
case node_value of
Strict.Nothing -> Nothing
Strict.Just x -> Just $ f (reverse $ path k p) x) m
) :
Map.foldrWithKey
(\k -> (:) . flat_map (k:p) f . node_descendants)
[] m
filter :: Ord k => (x -> Bool) -> TreeMap k x -> TreeMap k x
filter f =
mapMaybeWithPath
(\_p x -> if f x then Strict.Just x else Strict.Nothing)
filterWithPath :: Ord k => (Path k -> x -> Bool) -> TreeMap k x -> TreeMap k x
filterWithPath f =
mapMaybeWithPath
(\p x -> if f p x then Strict.Just x else Strict.Nothing)
filterWithPathAndNode :: Ord k => (Node k x -> Path k -> x -> Bool) -> TreeMap k x -> TreeMap k x
filterWithPathAndNode f =
mapMaybeWithPathAndNode
(\n p x -> if f n p x then Strict.Just x else Strict.Nothing)
mapMaybe :: Ord k => (x -> Strict.Maybe y) -> TreeMap k x -> TreeMap k y
mapMaybe = mapMaybeWithPath . const
mapMaybeWithPath :: Ord k => (Path k -> x -> Strict.Maybe y) -> TreeMap k x -> TreeMap k y
mapMaybeWithPath = mapMaybeWithPathAndNode . const
mapMaybeWithPathAndNode :: Ord k => (Node k x -> Path k -> x -> Strict.Maybe y) -> TreeMap k x -> TreeMap k y
mapMaybeWithPathAndNode =
go []
where
go :: Ord k
=> [k] -> (Node k x -> Path k -> x -> Strict.Maybe y)
-> TreeMap k x
-> TreeMap k y
go p test (TreeMap m) =
TreeMap $
Map.mapMaybeWithKey
(\k nod@Node{node_value=v, node_descendants=ns} ->
let node_descendants = go (k:p) test ns in
let node_size = size node_descendants in
case v of
Strict.Just x ->
let node_value = test nod (reverse $ path k p) x in
case node_value of
Strict.Nothing | null node_descendants -> Nothing
Strict.Nothing -> Just Node{node_value, node_descendants, node_size=1 + node_size}
Strict.Just _ -> Just Node{node_value, node_descendants, node_size}
_ ->
if null node_descendants
then Nothing
else Just Node{node_value=Strict.Nothing, node_descendants, node_size}
) m
(\\) :: Ord k => TreeMap k x -> TreeMap k y -> TreeMap k x
(\\) = intersection const
intersection ::
Ord k =>
(Strict.Maybe x -> Strict.Maybe y -> Strict.Maybe z) ->
TreeMap k x -> TreeMap k y -> TreeMap k z
intersection merge (TreeMap x) (TreeMap y) =
TreeMap $
Map.intersectionWith
(\xn yn ->
node (node_value xn `merge` node_value yn) $
intersection merge
(node_descendants xn)
(node_descendants yn))
x y