Skip to content

Commit c3c59f5

Browse files
committed
Style imports and pragmas with stylish-haskell
1 parent b8624f7 commit c3c59f5

File tree

17 files changed

+335
-244
lines changed

17 files changed

+335
-244
lines changed

Data/HashMap/Internal.hs

Lines changed: 84 additions & 67 deletions
Original file line numberDiff line numberDiff line change
@@ -1,17 +1,17 @@
1-
{-# LANGUAGE CPP #-}
2-
{-# LANGUAGE BangPatterns #-}
3-
{-# LANGUAGE DeriveLift #-}
4-
{-# LANGUAGE LambdaCase #-}
5-
{-# LANGUAGE MagicHash #-}
6-
{-# LANGUAGE PatternGuards #-}
7-
{-# LANGUAGE RoleAnnotations #-}
8-
{-# LANGUAGE ScopedTypeVariables #-}
9-
{-# LANGUAGE StandaloneDeriving #-}
1+
{-# LANGUAGE BangPatterns #-}
2+
{-# LANGUAGE CPP #-}
3+
{-# LANGUAGE DeriveLift #-}
4+
{-# LANGUAGE LambdaCase #-}
5+
{-# LANGUAGE MagicHash #-}
6+
{-# LANGUAGE PatternGuards #-}
7+
{-# LANGUAGE RoleAnnotations #-}
8+
{-# LANGUAGE ScopedTypeVariables #-}
9+
{-# LANGUAGE StandaloneDeriving #-}
1010
{-# LANGUAGE TemplateHaskellQuotes #-}
11-
{-# LANGUAGE TypeFamilies #-}
12-
{-# LANGUAGE UnboxedTuples #-}
13-
{-# LANGUAGE TypeInType #-}
14-
{-# LANGUAGE UnboxedSums #-}
11+
{-# LANGUAGE TypeFamilies #-}
12+
{-# LANGUAGE TypeInType #-}
13+
{-# LANGUAGE UnboxedSums #-}
14+
{-# LANGUAGE UnboxedTuples #-}
1515
{-# OPTIONS_GHC -fno-full-laziness -funbox-strict-fields #-}
1616
{-# OPTIONS_HADDOCK not-home #-}
1717

@@ -140,39 +140,56 @@ module Data.HashMap.Internal
140140
, adjust#
141141
) where
142142

143-
import Data.Semigroup (Semigroup(..), stimesIdempotentMonoid)
144-
import Control.DeepSeq (NFData(rnf))
145-
import Control.Monad.ST (ST, runST)
146-
import Data.Bits ((.&.), (.|.), complement, popCount, unsafeShiftL, unsafeShiftR)
147-
import Data.Data
148-
import qualified Data.Foldable as Foldable
149-
import Data.Bifoldable
150-
import qualified Data.List as L
151-
import GHC.Exts ((==#), build, reallyUnsafePtrEquality#, inline)
152-
import Prelude hiding (filter, foldl, foldr, lookup, map, null, pred)
153-
import Text.Read hiding (step)
154-
155-
import qualified Data.HashMap.Internal.Array as A
156-
import qualified Data.Hashable as H
157-
import Data.Hashable (Hashable)
158-
import Data.HashMap.Internal.List (isPermutationBy, unorderedCompare)
159-
160-
import GHC.Exts (isTrue#)
161-
import qualified GHC.Exts as Exts
162-
143+
import Control.Applicative (Const (..))
144+
import Control.DeepSeq (NFData (..), NFData1 (..), NFData2 (..))
145+
import Control.Monad.ST (ST, runST)
146+
import Data.Bifoldable (Bifoldable (..))
147+
import Data.Bits
148+
( complement
149+
, popCount
150+
, unsafeShiftL
151+
, unsafeShiftR
152+
, (.&.)
153+
, (.|.)
154+
)
155+
import Data.Coerce (coerce)
156+
import Data.Data (Constr, Data (..), DataType)
163157
import Data.Functor.Classes
164-
import GHC.Stack
165-
166-
import qualified Data.Hashable.Lifted as H
167-
168-
import qualified Control.DeepSeq as NF
169-
170-
import GHC.Exts (TYPE, Int (..), Int#)
158+
( Eq1 (..)
159+
, Eq2 (..)
160+
, Ord1 (..)
161+
, Ord2 (..)
162+
, Read1 (..)
163+
, Show1 (..)
164+
, Show2 (..)
165+
)
166+
import Data.Functor.Identity (Identity (..))
167+
import Data.HashMap.Internal.List (isPermutationBy, unorderedCompare)
168+
import Data.Hashable (Hashable)
169+
import Data.Hashable.Lifted (Hashable1, Hashable2)
170+
import Data.Semigroup (Semigroup (..), stimesIdempotentMonoid)
171+
import GHC.Exts (Int (..), Int#, TYPE, (==#))
172+
import GHC.Stack (HasCallStack)
173+
import Prelude hiding
174+
( filter
175+
, foldl
176+
, foldr
177+
, lookup
178+
, map
179+
, null
180+
, pred
181+
)
182+
import Text.Read hiding (step)
171183

172-
import Data.Functor.Identity (Identity (..))
173-
import Control.Applicative (Const (..))
174-
import Data.Coerce (coerce)
175-
import qualified Language.Haskell.TH.Syntax as TH
184+
import qualified Data.Data as Data
185+
import qualified Data.Foldable as Foldable
186+
import qualified Data.Functor.Classes as FC
187+
import qualified Data.HashMap.Internal.Array as A
188+
import qualified Data.Hashable as H
189+
import qualified Data.Hashable.Lifted as H
190+
import qualified Data.List as L
191+
import qualified GHC.Exts as Exts
192+
import qualified Language.Haskell.TH.Syntax as TH
176193

177194
-- | A set of values. A set cannot contain duplicate values.
178195
------------------------------------------------------------------------
@@ -196,11 +213,11 @@ instance (TH.Lift k, TH.Lift v) => TH.Lift (Leaf k v) where
196213
#endif
197214

198215
-- | @since 0.2.14.0
199-
instance NFData k => NF.NFData1 (Leaf k) where
200-
liftRnf rnf2 = NF.liftRnf2 rnf rnf2
216+
instance NFData k => NFData1 (Leaf k) where
217+
liftRnf rnf2 = liftRnf2 rnf rnf2
201218

202219
-- | @since 0.2.14.0
203-
instance NF.NFData2 Leaf where
220+
instance NFData2 Leaf where
204221
liftRnf2 rnf1 rnf2 (L k v) = rnf1 k `seq` rnf2 v
205222

206223
-- Invariant: The length of the 1st argument to 'Full' is
@@ -228,16 +245,16 @@ instance (NFData k, NFData v) => NFData (HashMap k v) where
228245
rnf (Collision _ ary) = rnf ary
229246

230247
-- | @since 0.2.14.0
231-
instance NFData k => NF.NFData1 (HashMap k) where
232-
liftRnf rnf2 = NF.liftRnf2 rnf rnf2
248+
instance NFData k => NFData1 (HashMap k) where
249+
liftRnf rnf2 = liftRnf2 rnf rnf2
233250

234251
-- | @since 0.2.14.0
235-
instance NF.NFData2 HashMap where
252+
instance NFData2 HashMap where
236253
liftRnf2 _ _ Empty = ()
237-
liftRnf2 rnf1 rnf2 (BitmapIndexed _ ary) = NF.liftRnf (NF.liftRnf2 rnf1 rnf2) ary
238-
liftRnf2 rnf1 rnf2 (Leaf _ l) = NF.liftRnf2 rnf1 rnf2 l
239-
liftRnf2 rnf1 rnf2 (Full ary) = NF.liftRnf (NF.liftRnf2 rnf1 rnf2) ary
240-
liftRnf2 rnf1 rnf2 (Collision _ ary) = NF.liftRnf (NF.liftRnf2 rnf1 rnf2) ary
254+
liftRnf2 rnf1 rnf2 (BitmapIndexed _ ary) = liftRnf (liftRnf2 rnf1 rnf2) ary
255+
liftRnf2 rnf1 rnf2 (Leaf _ l) = liftRnf2 rnf1 rnf2 l
256+
liftRnf2 rnf1 rnf2 (Full ary) = liftRnf (liftRnf2 rnf1 rnf2) ary
257+
liftRnf2 rnf1 rnf2 (Collision _ ary) = liftRnf (liftRnf2 rnf1 rnf2) ary
241258

242259
instance Functor (HashMap k) where
243260
fmap = map
@@ -300,26 +317,26 @@ instance (Eq k, Hashable k) => Monoid (HashMap k v) where
300317
instance (Data k, Data v, Eq k, Hashable k) => Data (HashMap k v) where
301318
gfoldl f z m = z fromList `f` toList m
302319
toConstr _ = fromListConstr
303-
gunfold k z c = case constrIndex c of
320+
gunfold k z c = case Data.constrIndex c of
304321
1 -> k (z fromList)
305322
_ -> error "gunfold"
306323
dataTypeOf _ = hashMapDataType
307-
dataCast1 f = gcast1 f
308-
dataCast2 f = gcast2 f
324+
dataCast1 f = Data.gcast1 f
325+
dataCast2 f = Data.gcast2 f
309326

310327
fromListConstr :: Constr
311-
fromListConstr = mkConstr hashMapDataType "fromList" [] Prefix
328+
fromListConstr = Data.mkConstr hashMapDataType "fromList" [] Data.Prefix
312329

313330
hashMapDataType :: DataType
314-
hashMapDataType = mkDataType "Data.HashMap.Internal.HashMap" [fromListConstr]
331+
hashMapDataType = Data.mkDataType "Data.HashMap.Internal.HashMap" [fromListConstr]
315332

316333
type Hash = Word
317334
type Bitmap = Word
318335
type Shift = Int
319336

320337
instance Show2 HashMap where
321338
liftShowsPrec2 spk slk spv slv d m =
322-
showsUnaryWith (liftShowsPrec sp sl) "fromList" d (toList m)
339+
FC.showsUnaryWith (liftShowsPrec sp sl) "fromList" d (toList m)
323340
where
324341
sp = liftShowsPrec2 spk slk spv slv
325342
sl = liftShowList2 spk slk spv slv
@@ -328,8 +345,8 @@ instance Show k => Show1 (HashMap k) where
328345
liftShowsPrec = liftShowsPrec2 showsPrec showList
329346

330347
instance (Eq k, Hashable k, Read k) => Read1 (HashMap k) where
331-
liftReadsPrec rp rl = readsData $
332-
readsUnaryWith (liftReadsPrec rp' rl') "fromList" fromList
348+
liftReadsPrec rp rl = FC.readsData $
349+
FC.readsUnaryWith (liftReadsPrec rp' rl') "fromList" fromList
333350
where
334351
rp' = liftReadsPrec rp rl
335352
rl' = liftReadList rp rl
@@ -484,7 +501,7 @@ equalKeys = go
484501

485502
leafEq (L k1 _) (L k2 _) = k1 == k2
486503

487-
instance H.Hashable2 HashMap where
504+
instance Hashable2 HashMap where
488505
liftHashWithSalt2 hk hv salt hm = go salt (toList' hm [])
489506
where
490507
-- go :: Int -> [HashMap k v] -> Int
@@ -507,7 +524,7 @@ instance H.Hashable2 HashMap where
507524
-- arrayHashesSorted :: Int -> A.Array (Leaf k v) -> [Int]
508525
arrayHashesSorted s = L.sort . L.map (hashLeafWithSalt s) . A.toList
509526

510-
instance (Hashable k) => H.Hashable1 (HashMap k) where
527+
instance (Hashable k) => Hashable1 (HashMap k) where
511528
liftHashWithSalt = H.liftHashWithSalt2 H.hashWithSalt
512529

513530
instance (Hashable k, Hashable v) => Hashable (HashMap k v) where
@@ -1410,7 +1427,7 @@ alterFEager f !k m = (<$> f mv) $ \fres ->
14101427
--
14111428
-- @since 0.2.12
14121429
isSubmapOf :: (Eq k, Hashable k, Eq v) => HashMap k v -> HashMap k v -> Bool
1413-
isSubmapOf = (inline isSubmapOfBy) (==)
1430+
isSubmapOf = (Exts.inline isSubmapOfBy) (==)
14141431
{-# INLINABLE isSubmapOf #-}
14151432

14161433
-- | /O(n*log m)/ Inclusion of maps with value comparison. A map is included in
@@ -2035,7 +2052,7 @@ elems = L.map snd . toList
20352052
-- | /O(n)/ Return a list of this map's elements. The list is
20362053
-- produced lazily. The order of its elements is unspecified.
20372054
toList :: HashMap k v -> [(k, v)]
2038-
toList t = build (\ c z -> foldrWithKey (curry c) z t)
2055+
toList t = Exts.build (\ c z -> foldrWithKey (curry c) z t)
20392056
{-# INLINE toList #-}
20402057

20412058
-- | /O(n)/ Construct a map with the supplied mappings. If the list
@@ -2282,7 +2299,7 @@ fullNodeMask = complement (complement 0 `unsafeShiftL` maxChildren)
22822299
-- | Check if two the two arguments are the same value. N.B. This
22832300
-- function might give false negatives (due to GC moving objects.)
22842301
ptrEq :: a -> a -> Bool
2285-
ptrEq x y = isTrue# (reallyUnsafePtrEquality# x y ==# 1#)
2302+
ptrEq x y = Exts.isTrue# (Exts.reallyUnsafePtrEquality# x y ==# 1#)
22862303
{-# INLINE ptrEq #-}
22872304

22882305
------------------------------------------------------------------------

Data/HashMap/Internal/Array.hs

Lines changed: 42 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,10 @@
1-
{-# LANGUAGE BangPatterns, CPP, MagicHash, Rank2Types, UnboxedTuples, ScopedTypeVariables #-}
1+
{-# LANGUAGE BangPatterns #-}
2+
{-# LANGUAGE CPP #-}
3+
{-# LANGUAGE MagicHash #-}
4+
{-# LANGUAGE Rank2Types #-}
5+
{-# LANGUAGE ScopedTypeVariables #-}
26
{-# LANGUAGE TemplateHaskellQuotes #-}
7+
{-# LANGUAGE UnboxedTuples #-}
38
{-# OPTIONS_GHC -fno-full-laziness -funbox-strict-fields #-}
49
{-# OPTIONS_HADDOCK not-home #-}
510

@@ -74,27 +79,47 @@ module Data.HashMap.Internal.Array
7479
) where
7580

7681
import Control.Applicative (liftA2)
77-
import Control.DeepSeq (NFData (..))
78-
import GHC.Exts(Int(..), reallyUnsafePtrEquality#, tagToEnum#, unsafeCoerce#)
79-
import GHC.ST (ST(..))
80-
import Control.Monad.ST (runST, stToIO)
81-
82-
import Prelude hiding (filter, foldMap, foldr, foldl, length, map, read, traverse, all)
83-
84-
import GHC.Exts (SmallArray#, newSmallArray#, readSmallArray#, writeSmallArray#,
85-
indexSmallArray#, unsafeFreezeSmallArray#, unsafeThawSmallArray#,
86-
SmallMutableArray#, sizeofSmallArray#, copySmallArray#, thawSmallArray#,
87-
sizeofSmallMutableArray#, copySmallMutableArray#, cloneSmallMutableArray#)
82+
import Control.DeepSeq (NFData (..), NFData1 (..))
83+
import Control.Monad ((>=>))
84+
import Control.Monad.ST (runST, stToIO)
85+
import GHC.Exts
86+
( Int (..)
87+
, SmallArray#
88+
, SmallMutableArray#
89+
, cloneSmallMutableArray#
90+
, copySmallArray#
91+
, copySmallMutableArray#
92+
, indexSmallArray#
93+
, newSmallArray#
94+
, readSmallArray#
95+
, reallyUnsafePtrEquality#
96+
, sizeofSmallArray#
97+
, sizeofSmallMutableArray#
98+
, tagToEnum#
99+
, thawSmallArray#
100+
, unsafeCoerce#
101+
, unsafeFreezeSmallArray#
102+
, unsafeThawSmallArray#
103+
, writeSmallArray#
104+
)
105+
import GHC.ST (ST (..))
106+
import Prelude hiding
107+
( all
108+
, filter
109+
, foldMap
110+
, foldl
111+
, foldr
112+
, length
113+
, map
114+
, read
115+
, traverse
116+
)
88117

89118
import qualified Language.Haskell.TH.Syntax as TH
90-
91119
#if defined(ASSERTS)
92120
import qualified Prelude
93121
#endif
94122

95-
import qualified Control.DeepSeq as NF
96-
97-
import Control.Monad ((>=>))
98123

99124
#if defined(ASSERTS)
100125
-- This fugly hack is brought by GHC's apparent reluctance to deal
@@ -172,7 +197,7 @@ rnfArray ary0 = go ary0 n0 0
172197
{-# INLINE rnfArray #-}
173198

174199
-- | @since 0.2.14.0
175-
instance NF.NFData1 Array where
200+
instance NFData1 Array where
176201
liftRnf = liftRnfArray
177202

178203
liftRnfArray :: (a -> ()) -> Array a -> ()

Data/HashMap/Internal/List.hs

Lines changed: 6 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE CPP #-}
12
{-# LANGUAGE ScopedTypeVariables #-}
23
{-# OPTIONS_GHC -fno-full-laziness -funbox-strict-fields #-}
34
{-# OPTIONS_HADDOCK not-home #-}
@@ -25,10 +26,11 @@ module Data.HashMap.Internal.List
2526
, unorderedCompare
2627
) where
2728

29+
import Data.List (sortBy)
2830
import Data.Maybe (fromMaybe)
29-
import Data.List (sortBy)
30-
import Data.Monoid
31-
import Prelude
31+
#if !MIN_VERSION_base(4,11,0)
32+
import Data.Semigroup ((<>))
33+
#endif
3234

3335
-- Note: previous implemenation isPermutation = null (as // bs)
3436
-- was O(n^2) too.
@@ -68,7 +70,7 @@ unorderedCompare c as bs = go (sortBy cmpA as) (sortBy cmpB bs)
6870
go [] [] = EQ
6971
go [] (_ : _) = LT
7072
go (_ : _) [] = GT
71-
go (x : xs) (y : ys) = c x y `mappend` go xs ys
73+
go (x : xs) (y : ys) = c x y <> go xs ys
7274

7375
cmpA a a' = compare (inB a) (inB a')
7476
cmpB b b' = compare (inA b) (inA b')

0 commit comments

Comments
 (0)