Skip to content

Commit

Permalink
Add definitions for stimes (#340)
Browse files Browse the repository at this point in the history
Also remove unused `LambdaCase` extension.

Resolves part of #307.
  • Loading branch information
konsumlamm authored Jan 6, 2022
1 parent 6910660 commit 6547038
Show file tree
Hide file tree
Showing 3 changed files with 6 additions and 7 deletions.
6 changes: 3 additions & 3 deletions Data/HashMap/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -142,9 +142,7 @@ module Data.HashMap.Internal
, adjust#
) where

#if !MIN_VERSION_base(4,11,0)
import Data.Semigroup (Semigroup((<>)))
#endif
import Data.Semigroup (Semigroup(..), stimesIdempotentMonoid)
import Control.DeepSeq (NFData(rnf))
import Control.Monad.ST (ST, runST)
import Data.Bits ((.&.), (.|.), complement, popCount, unsafeShiftL, unsafeShiftR)
Expand Down Expand Up @@ -296,6 +294,8 @@ instance Bifoldable HashMap where
instance (Eq k, Hashable k) => Semigroup (HashMap k v) where
(<>) = union
{-# INLINE (<>) #-}
stimes = stimesIdempotentMonoid
{-# INLINE stimes #-}

-- | 'mempty' = 'empty'
--
Expand Down
1 change: 0 additions & 1 deletion Data/HashMap/Internal/Strict.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# LANGUAGE BangPatterns, CPP, PatternGuards, MagicHash, UnboxedTuples #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE Trustworthy #-}
{-# OPTIONS_HADDOCK not-home #-}

Expand Down
6 changes: 3 additions & 3 deletions Data/HashSet/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -97,9 +97,7 @@ import Data.HashMap.Internal
( HashMap, foldMapWithKey, foldlWithKey, foldrWithKey
, equalKeys, equalKeys1)
import Data.Hashable (Hashable(hashWithSalt))
#if !MIN_VERSION_base(4,11,0)
import Data.Semigroup (Semigroup(..))
#endif
import Data.Semigroup (Semigroup(..), stimesIdempotentMonoid)
import GHC.Exts (build)
import qualified GHC.Exts as Exts
import Prelude hiding (filter, foldr, foldl, map, null)
Expand Down Expand Up @@ -200,6 +198,8 @@ instance Foldable.Foldable HashSet where
instance (Hashable a, Eq a) => Semigroup (HashSet a) where
(<>) = union
{-# INLINE (<>) #-}
stimes = stimesIdempotentMonoid
{-# INLINE stimes #-}

-- | 'mempty' = 'empty'
--
Expand Down

0 comments on commit 6547038

Please sign in to comment.