Skip to content

Commit e565f10

Browse files
committed
Address some of the PR comments.
1 parent c08c328 commit e565f10

File tree

4 files changed

+10
-10
lines changed

4 files changed

+10
-10
lines changed

Data/HashMap/Internal.hs

Lines changed: 7 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -148,6 +148,9 @@ module Data.HashMap.Internal
148148
, adjust#
149149
) where
150150

151+
import Data.Traversable -- MicroHs needs this since its Prelude does not have Foldable&Traversable.
152+
-- It's harmless for GHC, and putting it first avoid a warning.
153+
151154
import Control.Applicative (Const (..))
152155
import Control.DeepSeq (NFData (..), NFData1 (..), NFData2 (..))
153156
import Control.Monad.ST (ST, runST)
@@ -181,10 +184,6 @@ import qualified Data.List as List
181184
import qualified GHC.Exts as Exts
182185
import qualified Language.Haskell.TH.Syntax as TH
183186

184-
#if defined(__MHS__)
185-
import Data.Traversable
186-
#endif
187-
188187
-- | Convenience function. Compute a hash value for the given value.
189188
hash :: H.Hashable a => a -> Hash
190189
hash = fromIntegral . H.hash
@@ -195,7 +194,7 @@ data Leaf k v = L !k v
195194
instance (NFData k, NFData v) => NFData (Leaf k v) where
196195
rnf (L k v) = rnf k `seq` rnf v
197196

198-
#if !defined(__MHS__)
197+
#if defined(__GLASGOW_HASKELL__)
199198
-- | @since 0.2.17.0
200199
instance (TH.Lift k, TH.Lift v) => TH.Lift (Leaf k v) where
201200
liftTyped (L k v) = [|| L k $! v ||]
@@ -706,7 +705,7 @@ lookupRecordCollision# h k m =
706705
-- this whole thing is always inlined, we don't have to worry about
707706
-- any extra CPS overhead.
708707
lookupCont ::
709-
#if !defined(__MHS__)
708+
#if defined(__GLASGOW_HASKELL__)
710709
forall rep (r :: TYPE rep) k v.
711710
#else
712711
forall r k v.
@@ -2424,7 +2423,7 @@ fromListWithKey f = List.foldl' (\ m (k, v) -> unsafeInsertWithKey (\k' a b -> (
24242423
-- | \(O(n)\) Look up the value associated with the given key in an
24252424
-- array.
24262425
lookupInArrayCont ::
2427-
#if !defined(__MHS__)
2426+
#if defined(__GLASGOW_HASKELL__)
24282427
forall rep (r :: TYPE rep) k v.
24292428
#else
24302429
forall r k v.
@@ -2681,7 +2680,7 @@ otherOfOneOrZero :: Int -> Int
26812680
otherOfOneOrZero i = 1 - i
26822681
{-# INLINE otherOfOneOrZero #-}
26832682

2684-
#if !defined(__MHS__)
2683+
#if defined(__GLASGOW_HASKELL__)
26852684
------------------------------------------------------------------------
26862685
-- IsList instance
26872686
instance (Eq k, Hashable k) => Exts.IsList (HashMap k v) where

Data/HashMap/Internal/Array.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -548,7 +548,7 @@ fromList' n xs0 =
548548
go (!x:xs) mary i = do write mary i x
549549
go xs mary (i+1)
550550

551-
#if !defined(__MHS__)
551+
#if defined(__GLASGOW_HASKELL__)
552552
-- | @since 0.2.17.0
553553
instance TH.Lift a => TH.Lift (Array a) where
554554
liftTyped ar = [|| fromList' arlen arlist ||]

Data/HashMap/Internal/Strict.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
{-# LANGUAGE LambdaCase #-}
44
{-# LANGUAGE MagicHash #-}
55
{-# LANGUAGE PatternGuards #-}
6+
{-# LANGUAGE ScopedTypeVariables #-}
67
{-# LANGUAGE Trustworthy #-}
78
{-# LANGUAGE UnboxedTuples #-}
89
{-# OPTIONS_HADDOCK not-home #-}

Data/HashSet/Internal.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -450,7 +450,7 @@ fromList :: (Eq a, Hashable a) => [a] -> HashSet a
450450
fromList = HashSet . List.foldl' (\ m k -> H.unsafeInsert k () m) H.empty
451451
{-# INLINE fromList #-}
452452

453-
#if !defined(__MHS__)
453+
#if defined(__GLASGOW_HASKELL__)
454454
instance (Eq a, Hashable a) => Exts.IsList (HashSet a) where
455455
type Item (HashSet a) = a
456456
fromList = fromList

0 commit comments

Comments
 (0)