Skip to content

Commit 3ed23a4

Browse files
committed
Bump to hlint 3
1 parent 25f202b commit 3ed23a4

File tree

3 files changed

+3
-3
lines changed

3 files changed

+3
-3
lines changed

src/Data/Functor/Misc.hs

-1
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,6 @@
66
{-# LANGUAGE GADTs #-}
77
{-# LANGUAGE LambdaCase #-}
88
{-# LANGUAGE MultiParamTypeClasses #-}
9-
{-# LANGUAGE PatternSynonyms #-}
109
{-# LANGUAGE PolyKinds #-}
1110
{-# LANGUAGE RankNTypes #-}
1211
{-# LANGUAGE ScopedTypeVariables #-}

src/Data/Patch/IntMap.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -59,7 +59,7 @@ mapIntMapPatchWithKey f (PatchIntMap m) = PatchIntMap $ IntMap.mapWithKey (\ k m
5959
-- | Map an effectful function @Int -> a -> f b@ over all @a@s in the given @'PatchIntMap' a@
6060
-- (that is, all inserts/updates), producing a @f (PatchIntMap b)@.
6161
traverseIntMapPatchWithKey :: Applicative f => (Int -> a -> f b) -> PatchIntMap a -> f (PatchIntMap b)
62-
traverseIntMapPatchWithKey f (PatchIntMap m) = PatchIntMap <$> IntMap.traverseWithKey (\k mv -> traverse (f k) mv) m
62+
traverseIntMapPatchWithKey f (PatchIntMap m) = PatchIntMap <$> IntMap.traverseWithKey (traverse . f) m
6363

6464
-- | Extract all @a@s inserted/updated by the given @'PatchIntMap' a@.
6565
patchIntMapNewElements :: PatchIntMap a -> [a]

test/hlint.hs

+2-1
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
module Main where
22

33
import Control.Monad
4-
import Language.Haskell.HLint3 (hlint)
4+
import Language.Haskell.HLint (hlint)
55
import System.Directory
66
import System.Exit (exitFailure, exitSuccess)
77
import System.FilePath
@@ -23,6 +23,7 @@ main = do
2323
, "--ignore=Reduce duplication"
2424
, "--cpp-define=USE_TEMPLATE_HASKELL"
2525
, "--ignore=Use tuple-section"
26+
, "--ignore=Unused LANGUAGE pragma" -- hlint3 falsely believes that TypeOperators is not needed
2627
]
2728
recurseInto = and <$> sequence
2829
[ fileType ==? Directory

0 commit comments

Comments
 (0)