{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RoleAnnotations #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
-- |
-- Module:
--   Data.AppendMap
-- Description:
--   Instances and convenience functions for 'Data.Map.Monoidal'. We use
--   monoidal-containers to take advantage of its better monoid instance.
--   'Data.Map' has @mappend = union@, which is left-biased.  'MonoidalMap'
--   has @mappend = unionWith mappend@ instead.
module Data.AppendMap
  ( module Data.AppendMap
  , module Data.Map.Monoidal
  ) where

import Prelude hiding (null)

import Data.Coerce
import Data.Default
import Data.Map (Map)
#if MIN_VERSION_containers(0,5,11)
import qualified Data.Map.Internal.Debug as Map (showTree, showTreeWith)
#else
import qualified Data.Map as Map (showTree, showTreeWith)
#endif
import qualified Data.Witherable as W
import Data.Map.Monoidal
import qualified Data.Map.Monoidal as MonoidalMap


{-# DEPRECATED AppendMap "Use 'MonoidalMap' instead" #-}
-- | AppendMap is a synonym for 'Data.Map.Monoidal.MonoidalMap'
type AppendMap = MonoidalMap

{-# DEPRECATED _unAppendMap "Use 'getMonoidalMap' instead" #-}
-- | A synonym for 'getMonoidalMap'
_unAppendMap :: MonoidalMap k v -> Map k v
_unAppendMap :: MonoidalMap k v -> Map k v
_unAppendMap = MonoidalMap k v -> Map k v
forall k a. MonoidalMap k a -> Map k a
getMonoidalMap

-- | Pattern synonym for 'MonoidalMap'
pattern AppendMap :: Map k v -> MonoidalMap k v
pattern $bAppendMap :: Map k v -> MonoidalMap k v
$mAppendMap :: forall r k v.
MonoidalMap k v -> (Map k v -> r) -> (Void# -> r) -> r
AppendMap m = MonoidalMap m

#if !MIN_VERSION_witherable(0,3,2)
instance W.Filterable (MonoidalMap k) where
  mapMaybe :: (a -> Maybe b) -> MonoidalMap k a -> MonoidalMap k b
mapMaybe = (a -> Maybe b) -> MonoidalMap k a -> MonoidalMap k b
forall k a b. (a -> Maybe b) -> MonoidalMap k a -> MonoidalMap k b
MonoidalMap.mapMaybe
#endif

-- | Deletes a key, returning 'Nothing' if the result is empty.
nonEmptyDelete :: Ord k => k -> MonoidalMap k a -> Maybe (MonoidalMap k a)
nonEmptyDelete :: k -> MonoidalMap k a -> Maybe (MonoidalMap k a)
nonEmptyDelete k :: k
k vs :: MonoidalMap k a
vs =
  let deleted :: MonoidalMap k a
deleted = k -> MonoidalMap k a -> MonoidalMap k a
forall k a. Ord k => k -> MonoidalMap k a -> MonoidalMap k a
delete k
k MonoidalMap k a
vs
  in if MonoidalMap k a -> Bool
forall k a. MonoidalMap k a -> Bool
null MonoidalMap k a
deleted
       then Maybe (MonoidalMap k a)
forall a. Maybe a
Nothing
       else MonoidalMap k a -> Maybe (MonoidalMap k a)
forall a. a -> Maybe a
Just MonoidalMap k a
deleted

-- | Like 'mapMaybe' but indicates whether the resulting container is empty
mapMaybeNoNull :: (a -> Maybe b)
               -> MonoidalMap token a
               -> Maybe (MonoidalMap token b)
mapMaybeNoNull :: (a -> Maybe b)
-> MonoidalMap token a -> Maybe (MonoidalMap token b)
mapMaybeNoNull f :: a -> Maybe b
f as :: MonoidalMap token a
as =
  let bs :: MonoidalMap token b
bs = (a -> Maybe b) -> MonoidalMap token a -> MonoidalMap token b
forall k a b. (a -> Maybe b) -> MonoidalMap k a -> MonoidalMap k b
mapMaybe a -> Maybe b
f MonoidalMap token a
as
  in if MonoidalMap token b -> Bool
forall k a. MonoidalMap k a -> Bool
null MonoidalMap token b
bs
       then Maybe (MonoidalMap token b)
forall a. Maybe a
Nothing
       else MonoidalMap token b -> Maybe (MonoidalMap token b)
forall a. a -> Maybe a
Just MonoidalMap token b
bs

-- TODO: Move instances to `Data.Patch`
-- | Displays a 'MonoidalMap' as a tree. See 'Data.Map.Lazy.showTree' for details.
showTree :: forall k a. (Show k, Show a) => MonoidalMap k a -> String
showTree :: MonoidalMap k a -> String
showTree = (Map k a -> String) -> MonoidalMap k a -> String
forall a b. Coercible a b => a -> b
coerce (Map k a -> String
forall k a. (Show k, Show a) => Map k a -> String
Map.showTree :: Map k a -> String)

-- | Displays a 'MonoidalMap' as a tree, using the supplied function to convert nodes to string.
showTreeWith :: forall k a. (k -> a -> String) -> Bool -> Bool -> MonoidalMap k a -> String
showTreeWith :: (k -> a -> String) -> Bool -> Bool -> MonoidalMap k a -> String
showTreeWith = ((k -> a -> String) -> Bool -> Bool -> Map k a -> String)
-> (k -> a -> String) -> Bool -> Bool -> MonoidalMap k a -> String
forall a b. Coercible a b => a -> b
coerce ((k -> a -> String) -> Bool -> Bool -> Map k a -> String
forall k a. (k -> a -> String) -> Bool -> Bool -> Map k a -> String
Map.showTreeWith :: (k -> a -> String) -> Bool -> Bool -> Map k a -> String)

instance Default (MonoidalMap k a) where
  def :: MonoidalMap k a
def = MonoidalMap k a
forall k a. MonoidalMap k a
empty