Skip to content

Commit cbec132

Browse files
committed
Hlinting
1 parent 88c244e commit cbec132

25 files changed

+87
-70
lines changed

.travis.yml

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,9 @@ matrix:
4040
- env: BUILD=cabal CABALVER=1.22 GHCVER=7.10.3
4141
compiler: ": #GHC 7.10.3"
4242
addons: {apt: {packages: [cabal-install-1.22,ghc-7.10.3], sources: [hvr-ghc]}}
43+
- env: BUILD=hlint CABALVER=1.24 GHCVER=8.0.2
44+
compiler: ": #GHC 8.0.2"
45+
addons: {apt: {packages: [cabal-install-1.24,ghc-8.0.2], sources: [hvr-ghc]}}
4346

4447
before_install:
4548
- unset CC

Data/Aeson/Encoding/Builder.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -292,7 +292,7 @@ encodeUtf8BuilderEscaped be =
292292
where
293293
iend = off + len
294294

295-
outerLoop !i0 !br@(B.BufferRange op0 ope)
295+
outerLoop !i0 br@(B.BufferRange op0 ope)
296296
| i0 >= iend = k br
297297
| outRemaining > 0 = goPartial (i0 + min outRemaining inpRemaining)
298298
-- TODO: Use a loop with an integrated bound's check if outRemaining

Data/Aeson/TH.hs

Lines changed: 7 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1629,7 +1629,7 @@ buildTypeInstanceFromTys tyConName jc dataCxt varTysOrig isDataFamily = do
16291629
-- instance C (Fam [Char])
16301630
remainingTysOrigSubst :: [Type]
16311631
remainingTysOrigSubst =
1632-
map (substNamesWithKindStar (union droppedKindVarNames kvNames'))
1632+
map (substNamesWithKindStar (droppedKindVarNames `union` kvNames'))
16331633
$ take remainingLength varTysOrig
16341634

16351635
remainingTysOrigSubst' :: [Type]
@@ -2118,7 +2118,7 @@ createKindChain :: Int -> Kind
21182118
createKindChain = go starK
21192119
where
21202120
go :: Kind -> Int -> Kind
2121-
go k !0 = k
2121+
go k 0 = k
21222122
#if MIN_VERSION_template_haskell(2,8,0)
21232123
go k !n = go (AppT (AppT ArrowT StarT) k) (n - 1)
21242124
#else
@@ -2245,7 +2245,7 @@ substNameWithKind :: Name -> Kind -> Type -> Type
22452245
substNameWithKind n k = substKind (M.singleton n k)
22462246

22472247
substNamesWithKindStar :: [Name] -> Type -> Type
2248-
substNamesWithKindStar ns t = foldr' (flip substNameWithKind starK) t ns
2248+
substNamesWithKindStar ns t = foldr' (`substNameWithKind` starK) t ns
22492249

22502250
-------------------------------------------------------------------------------
22512251
-- Error messages
@@ -2394,13 +2394,12 @@ data StarKindStatus = NotKindStar
23942394

23952395
-- | Does a Type have kind * or k (for some kind variable k)?
23962396
canRealizeKindStar :: Type -> StarKindStatus
2397-
canRealizeKindStar t
2398-
| hasKindStar t = KindStar
2399-
| otherwise = case t of
2397+
canRealizeKindStar t = case t of
2398+
_ | hasKindStar t -> KindStar
24002399
#if MIN_VERSION_template_haskell(2,8,0)
2401-
SigT _ (VarT k) -> IsKindVar k
2400+
SigT _ (VarT k) -> IsKindVar k
24022401
#endif
2403-
_ -> NotKindStar
2402+
_ -> NotKindStar
24042403

24052404
-- | Returns 'Just' the kind variable 'Name' of a 'StarKindStatus' if it exists.
24062405
-- Otherwise, returns 'Nothing'.

Data/Aeson/Types/ToJSON.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,3 @@
1-
{-# LANGUAGE BangPatterns #-}
21
{-# LANGUAGE CPP #-}
32
{-# LANGUAGE DataKinds #-}
43
{-# LANGUAGE DefaultSignatures #-}
@@ -132,6 +131,8 @@ import qualified Data.ByteString.Internal as S
132131
import qualified Data.ByteString.Lazy.Internal as L
133132
#endif
134133

134+
{-# ANN module ("HLint: ignore Reduce duplication"::String) #-}
135+
135136
toJSONPair :: (a -> Value) -> (b -> Value) -> (a, b) -> Value
136137
toJSONPair a b = liftToJSON2 a (listValue a) b (listValue b)
137138
{-# INLINE toJSONPair #-}
@@ -2809,8 +2810,8 @@ packChunks :: L.ByteString -> S.ByteString
28092810
packChunks lbs =
28102811
S.unsafeCreate (fromIntegral $ L.length lbs) (copyChunks lbs)
28112812
where
2812-
copyChunks !L.Empty !_pf = return ()
2813-
copyChunks !(L.Chunk (S.PS fpbuf o l) lbs') !pf = do
2813+
copyChunks L.Empty _pf = return ()
2814+
copyChunks (L.Chunk (S.PS fpbuf o l) lbs') pf = do
28142815
withForeignPtr fpbuf $ \pbuf ->
28152816
copyBytes pf (pbuf `plusPtr` o) l
28162817
copyChunks lbs' (pf `plusPtr` l)

HLint.hs

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
module HLint.HLint where
2+
3+
import "hint" HLint.Default
4+
import "hint" HLint.Builtin.All
5+
import "hint" HLint.Dollar
6+
7+
ignore "Avoid lambda"
8+
ignore "Eta reduce"
9+
ignore "Functor law"
10+
ignore "Use >=>"

Makefile

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
lint:
2+
hlint --cpp-include include/ .

benchmarks/AesonCompareAutoInstances.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@ d :: T
4343
d = Record
4444
{ testOne = 1234.56789
4545
, testTwo = True
46-
, testThree = Product "Hello World!" 'a' $
46+
, testThree = Product "Hello World!" 'a'
4747
Record
4848
{ testOne = 9876.54321
4949
, testTwo = False
@@ -80,7 +80,7 @@ d' :: T'
8080
d' = Record'
8181
{ testOne' = 1234.56789
8282
, testTwo' = True
83-
, testThree' = Product' "Hello World!" 'a' $
83+
, testThree' = Product' "Hello World!" 'a'
8484
Record'
8585
{ testOne' = 9876.54321
8686
, testTwo' = False

benchmarks/AesonEncode.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,6 @@ import Prelude ()
77
import Prelude.Compat
88

99
import Control.DeepSeq
10-
import Control.Exception
1110
import Control.Monad
1211
import Data.Aeson
1312
import Data.Attoparsec.ByteString (IResult(..), parseWith)
@@ -25,7 +24,7 @@ main = do
2524
(c:a) -> (c,a)
2625
[] -> error "Unexpected empty list"
2726
let count = read cnt :: Int
28-
forM_ args $ \arg -> bracket (openFile arg ReadMode) hClose $ \h -> do
27+
forM_ args $ \arg -> withFile arg ReadMode $ \h -> do
2928
putStrLn $ arg ++ ":"
3029
let refill = B.hGet h 16384
3130
result0 <- parseWith refill json =<< refill
@@ -35,7 +34,7 @@ main = do
3534
start <- getCurrentTime
3635
let loop !n r
3736
| n >= count = return ()
38-
| otherwise = {-# SCC "loop" #-} do
37+
| otherwise = {-# SCC "loop" #-}
3938
rnf (encode r) `seq` loop (n+1) r
4039
loop 0 r0
4140
delta <- flip diffUTCTime start `fmap` getCurrentTime

benchmarks/AesonMap.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -97,16 +97,16 @@ value1000 = value 1000
9797
value10000 = value 10000
9898

9999
encodedValue10 :: LBS.ByteString
100-
encodedValue10 = B.encode $ value10
100+
encodedValue10 = B.encode value10
101101

102102
encodedValue100 :: LBS.ByteString
103-
encodedValue100 = B.encode $ value100
103+
encodedValue100 = B.encode value100
104104

105105
encodedValue1000 :: LBS.ByteString
106-
encodedValue1000 = B.encode $ value1000
106+
encodedValue1000 = B.encode value1000
107107

108108
encodedValue10000 :: LBS.ByteString
109-
encodedValue10000 = B.encode $ value10000
109+
encodedValue10000 = B.encode value10000
110110

111111
-------------------------------------------------------------------------------
112112
-- Helpers

benchmarks/AesonParse.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,6 @@ import Prelude ()
88
import Prelude.Compat
99

1010
import "aeson-benchmarks" Data.Aeson
11-
import Control.Exception
1211
import Control.Monad
1312
import Data.Attoparsec.ByteString (IResult(..), parseWith)
1413
import Data.Time.Clock
@@ -21,7 +20,7 @@ main = do
2120
(bs:cnt:args) <- getArgs
2221
let count = read cnt :: Int
2322
blkSize = read bs
24-
forM_ args $ \arg -> bracket (openFile arg ReadMode) hClose $ \h -> do
23+
forM_ args $ \arg -> withFile arg ReadMode $ \h -> do
2524
putStrLn $ arg ++ ":"
2625
start <- getCurrentTime
2726
let loop !good !bad

0 commit comments

Comments
 (0)