-- | -- Module : Case.Hashable.Cuckoo -- Copyright : (c) OleksandrZhabenko 2021 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- A library that can be used as a @case ... of@ constuction analogue for the Hashable keys. -- For the large lists is expected to be more time efficient than CaseBi.Arr.getBFst' analogue. -- If you plan to use it together with the former one, please, use qualified import to avoid names ambiguity. {-# LANGUAGE MagicHash, UnboxedTuples #-} module Case.Hashable.Cuckoo ( getBFstL' ) where import qualified Data.HashTable.ST.Cuckoo as C import qualified Data.HashTable.Class as H (fromList) import GHC.ST import GHC.Magic (runRW# ) import Data.Maybe (fromMaybe) import Data.Hashable (Hashable(..)) getBFstL' :: (Eq k, Hashable k) => v -> [(k, v)] -> k -> v getBFstL' def pairs key = fromMaybe def ((\(ST st_rep) -> case runRW# st_rep of (# _, a #) -> a) . -- Actually is rewritten from the GHC.ST.runST to remove the forall constraint lookup2 pairs $ key) lookup2 pairs key = H.fromList pairs >>= \ht -> C.lookup ht key {-# INLINE lookup2 #-}