module StmContainers.Map
(
Map,
new,
newIO,
null,
size,
focus,
lookup,
insert,
delete,
reset,
unfoldlM,
listT,
)
where
import StmContainers.Prelude hiding (insert, delete, lookup, alter, foldM, toList, empty, null)
import qualified StmHamt.Hamt as A
import qualified Focus as B
import qualified DeferredFolds.UnfoldlM as C
newtype Map key value =
Map (A.Hamt (Product2 key value))
{-# INLINABLE new #-}
new :: STM (Map key value)
new =
Map <$> A.new
{-# INLINABLE newIO #-}
newIO :: IO (Map key value)
newIO =
Map <$> A.newIO
{-# INLINABLE null #-}
null :: Map key value -> STM Bool
null (Map hamt) =
A.null hamt
{-# INLINABLE size #-}
size :: Map key value -> STM Int
size =
C.foldlM' (\ x _ -> return (succ x)) 0 . unfoldlM
{-# INLINE focus #-}
focus :: (Eq key, Hashable key) => B.Focus value STM result -> key -> Map key value -> STM result
focus valueFocus key (Map hamt) =
A.focus rowFocus (\(Product2 key _) -> key) key hamt
where
rowFocus =
B.mappingInput (\value -> Product2 key value) (\(Product2 _ value) -> value) valueFocus
{-# INLINABLE lookup #-}
lookup :: (Eq key, Hashable key) => key -> Map key value -> STM (Maybe value)
lookup key =
focus B.lookup key
{-# INLINE insert #-}
insert :: (Eq key, Hashable key) => value -> key -> Map key value -> STM ()
insert value key (Map hamt) =
void (A.insert (\(Product2 key _) -> key) (Product2 key value) hamt)
{-# INLINABLE delete #-}
delete :: (Eq key, Hashable key) => key -> Map key value -> STM ()
delete key =
focus B.delete key
{-# INLINABLE reset #-}
reset :: Map key value -> STM ()
reset (Map hamt) =
A.reset hamt
{-# INLINABLE unfoldlM #-}
unfoldlM :: Map key value -> UnfoldlM STM (key, value)
unfoldlM (Map hamt) =
fmap (\ (Product2 k v) -> (k, v)) (A.unfoldlM hamt)
{-# INLINE listT #-}
listT :: Map key value -> ListT STM (key, value)
listT (Map hamt) =
fmap (\ (Product2 k v) -> (k, v)) (A.listT hamt)