Skip to content

Commit 6547038

Browse files
authored
Add definitions for stimes (#340)
Also remove unused `LambdaCase` extension. Resolves part of #307.
1 parent 6910660 commit 6547038

File tree

3 files changed

+6
-7
lines changed

3 files changed

+6
-7
lines changed

Data/HashMap/Internal.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -142,9 +142,7 @@ module Data.HashMap.Internal
142142
, adjust#
143143
) where
144144

145-
#if !MIN_VERSION_base(4,11,0)
146-
import Data.Semigroup (Semigroup((<>)))
147-
#endif
145+
import Data.Semigroup (Semigroup(..), stimesIdempotentMonoid)
148146
import Control.DeepSeq (NFData(rnf))
149147
import Control.Monad.ST (ST, runST)
150148
import Data.Bits ((.&.), (.|.), complement, popCount, unsafeShiftL, unsafeShiftR)
@@ -296,6 +294,8 @@ instance Bifoldable HashMap where
296294
instance (Eq k, Hashable k) => Semigroup (HashMap k v) where
297295
(<>) = union
298296
{-# INLINE (<>) #-}
297+
stimes = stimesIdempotentMonoid
298+
{-# INLINE stimes #-}
299299

300300
-- | 'mempty' = 'empty'
301301
--

Data/HashMap/Internal/Strict.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
11
{-# LANGUAGE BangPatterns, CPP, PatternGuards, MagicHash, UnboxedTuples #-}
2-
{-# LANGUAGE LambdaCase #-}
32
{-# LANGUAGE Trustworthy #-}
43
{-# OPTIONS_HADDOCK not-home #-}
54

Data/HashSet/Internal.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -97,9 +97,7 @@ import Data.HashMap.Internal
9797
( HashMap, foldMapWithKey, foldlWithKey, foldrWithKey
9898
, equalKeys, equalKeys1)
9999
import Data.Hashable (Hashable(hashWithSalt))
100-
#if !MIN_VERSION_base(4,11,0)
101-
import Data.Semigroup (Semigroup(..))
102-
#endif
100+
import Data.Semigroup (Semigroup(..), stimesIdempotentMonoid)
103101
import GHC.Exts (build)
104102
import qualified GHC.Exts as Exts
105103
import Prelude hiding (filter, foldr, foldl, map, null)
@@ -200,6 +198,8 @@ instance Foldable.Foldable HashSet where
200198
instance (Hashable a, Eq a) => Semigroup (HashSet a) where
201199
(<>) = union
202200
{-# INLINE (<>) #-}
201+
stimes = stimesIdempotentMonoid
202+
{-# INLINE stimes #-}
203203

204204
-- | 'mempty' = 'empty'
205205
--

0 commit comments

Comments
 (0)