----------------------------------------------------------- -- | -- Module : Control.Imperative.Hash -- Copyright : (C) 2015, Yu Fukuzawa -- License : BSD3 -- Maintainer : minpou.primer@email.com -- Stability : experimental -- Portability : portable -- ----------------------------------------------------------- {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} module Control.Imperative.Hash ( -- $doc -- * Types HashTable , MonadHash , HashKey -- * Operations , new , newSized , delete , fromList , toList ) where import Control.Imperative.Hash.Class import Control.Imperative.Internal import Control.Monad (liftM) import Control.Monad.Base -- $doc -- A mutable hashtable. -- -- There are two basic operation exported from the "Control.Imperative" module. -- -- [@ref@] /O(1)/. lookup the value of a hashtable at the given key. -- [@assign@] /O(1)/. insert the value at the given key. newtype HashTable m k v = H (HashEntity m k v) instance (HashKey k, MHash m) => Indexable (HashTable m k v) where type Element (HashTable m k v) = Ref m v type IndexType (HashTable m k v) = k (H h) ! k = Ref { get = unsafeLookupHash h k , set = insertHash h k } {-# INLINE (!) #-} -- | Useful constraint synonym for hashtable operations. type MonadHash m = (MonadBase (BaseEff m) m, MHash (BaseEff m)) -- | /O(1)/. Create an empty hashtable with a given size. new :: MonadHash m => m (HashTable (BaseEff m) k v) new = newSized 2 {-# INLINE new #-} -- | /O(1)/. Create an empty hashtable with a given size. newSized :: MonadHash m => Int -- initial size -> m (HashTable (BaseEff m) k v) newSized size = liftBase $ liftM H $ newSizedHash size {-# INLINE newSized #-} -- | /O(n)/ worst case, /O(1)/ amortized. Delete key-value mapping in a hashtable. delete :: (HashKey k, MonadHash m) => HashTable (BaseEff m) k v -> k -> m () delete (H h) k = liftBase $ deleteHash h k {-# INLINE delete #-} -- | /O(n)/. Create a hashtable from an associative list. fromList :: (HashKey k, MonadHash m) => [(k, v)] -> m (HashTable (BaseEff m) k v) fromList as = liftBase $ liftM H $ fromListHash as {-# INLINE fromList #-} -- | /O(n)/. Convert the hashtable to a nested associative list. toList :: (HashKey k, MonadHash m) => HashTable (BaseEff m) k v -> m [(k, v)] toList (H h) = liftBase $ toListHash h {-# INLINE toList #-}