Skip to content

Commit

Permalink
Enable more hints for HLint. (#489)
Browse files Browse the repository at this point in the history
* Enable `Fuse foldr/map` hint for HLint.
* Enable `Use :` hint for HLint.
* Enable `Use camelCase` hint for HLint.
* Enable `Use concatMap` hint for HLint.
* Enable `Use fmap` hint for HLint.
* Enable `Use maybe` hint for HLint.
* Enable `Use newtype instead of data` hint for HLint.
* Enable `Use replicate` hint for HLint.
* Disable `Use fmap` hint for HLint.
* Update code to satisfy HLint.
  • Loading branch information
chungyc authored Oct 11, 2024
1 parent 0e0028b commit 4df4073
Show file tree
Hide file tree
Showing 6 changed files with 19 additions and 23 deletions.
7 changes: 0 additions & 7 deletions .hlint.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -13,15 +13,8 @@
# Warnings currently triggered by existing code.
- ignore: {name: "Avoid lambda"} # 1 hint
- ignore: {name: "Eta reduce"} # 1 hint
- ignore: {name: "Fuse foldr/map"} # 1 hint
- ignore: {name: "Use :"} # 2 hints
- ignore: {name: "Use <$"} # 1 hint
- ignore: {name: "Use <$>"} # 1 hint
- ignore: {name: "Use ?~"} # 5 hints
- ignore: {name: "Use camelCase"} # 3 hints
- ignore: {name: "Use concatMap"} # 1 hint
- ignore: {name: "Use fmap"} # 10 hints
- ignore: {name: "Use lambda-case"} # 3 hints
- ignore: {name: "Use maybe"} # 1 hint
- ignore: {name: "Use newtype instead of data"} # 1 hint
- ignore: {name: "Use replicate"} # 1 hint
14 changes: 6 additions & 8 deletions proto-lens-protoc/app/Data/ProtoLens/Compiler/Generate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -424,12 +424,11 @@ generatePrisms env oneofInfo =
-- Case deconstruction
@@ lambda [bvar "p__"] (
case' (var "p__") $
[ match [conP (unqual consName) [bvar "p__val"]]
$ var "Prelude.Just" @@ var "p__val"
]
match [conP (unqual consName) [bvar "p__val"]]
(var "Prelude.Just" @@ var "p__val")
-- We want to generate the otherwise case
-- depending on the amount of sum type cases there are
++ otherwiseCase
: otherwiseCase
)
generatePrism :: [RawMatch] -> OneofCase -> [HsDecl']
generatePrism otherwiseCase oneofCase =
Expand Down Expand Up @@ -812,15 +811,14 @@ oneofRecordField env oneofInfo
-- since oneofs don't have a notion of a "default" case.
-- data Foo = Foo { _Foo'bar = Maybe Foo'Bar }
-- type instance Field "maybe'bar" Foo = Maybe Foo'Bar
[LensInstance
LensInstance
{ lensSymbol = "maybe'" <> overloadedName
(oneofFieldName oneofInfo)
, lensFieldType =
var "Prelude.Maybe" @@ var (unqual $ oneofTypeName oneofInfo)
, lensExp = var "Prelude.id"
}
]
++ concat
: concat
-- Generate the same lenses for each sub-field of the oneof
-- as if they were proto2 optional fields.
-- type instance Field "bar" Foo = Bar
Expand Down Expand Up @@ -1089,7 +1087,7 @@ fieldTypeDescriptorExpr = \case
-- instance NFData Bar where
-- rnf = \x -> deepseq (_Bar'foo x) (deepseq (_Bar'bar x) ())
messageRnfExpr :: MessageInfo OccNameStr -> HsExpr'
messageRnfExpr msg = lambda [bvar "x__"] $ foldr (@@) unit (map seqField fieldNames)
messageRnfExpr msg = lambda [bvar "x__"] $ foldr ((@@) . seqField) unit fieldNames
where
fieldNames = messageUnknownFields msg
: map (haskellRecordFieldName . fieldName . plainFieldInfo)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@
-- | Enables pretty-printing Haddock comments along with top-level declarations.
module Data.ProtoLens.Compiler.Generate.Commented where

import Data.Maybe (fromMaybe)
import GHC.SourceGen
#if MIN_VERSION_ghc(9,0,0)
import GHC.Utils.Outputable (Outputable(..), SDoc, (<+>), ($+$), vcat, empty, text)
Expand Down Expand Up @@ -47,8 +46,10 @@ data CommentedModule = CommentedModule

getModuleName :: CommentedModule -> ModuleName
getModuleName m =
fromMaybe (error "getModuleName: No explicit name")
$ fmap unLoc $ hsmodName $ moduleHeader m
maybe
(error "getModuleName: No explicit name")
unLoc
(hsmodName $ moduleHeader m)

instance Outputable CommentedModule where
ppr m =
Expand Down
2 changes: 1 addition & 1 deletion proto-lens-setup/src/Data/ProtoLens/Setup.hs
Original file line number Diff line number Diff line change
Expand Up @@ -240,7 +240,7 @@ generateSources root l files = withSystemTempDirectory "protoc-out" $ \tmpDir ->
-- Generate .hs files for all active components into a single temporary
-- directory.
let activeModules = collectActiveModules l
let allModules = Set.fromList . concat . map snd $ activeModules
let allModules = Set.fromList . concatMap snd $ activeModules
let usedInComponent f = ModuleName.fromString (protoModuleName f)
`Set.member` allModules
generateProtosWithImports (root : importDirs) tmpDir
Expand Down
8 changes: 4 additions & 4 deletions proto-lens-tests/tests/decode_delimited_test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,8 +16,8 @@ import Proto.DecodeDelimited_Fields
import System.IO (openBinaryFile, hClose, IOMode(ReadMode))
import System.IO.Temp (withSystemTempFile)

filename_template :: String
filename_template = "test_decode_delimited"
filenameTemplate :: String
filenameTemplate = "test_decode_delimited"

main :: IO ()
main = testMain
Expand All @@ -28,13 +28,13 @@ main = testMain
foo1 = defMessage & a .~ 42 & b .~ "hello" :: Foo
foo2 = defMessage
& a .~ 43
& b .~ (T.pack . take 300 . repeat $ 'x') :: Foo
& b .~ (T.pack . replicate 300 $ 'x') :: Foo

testWithMessage :: (Eq msg, Show msg, Message msg) => msg -> IO ()
testWithMessage msg =
let bs = runBuilder . buildMessageDelimited $ msg
in
withSystemTempFile filename_template $ \fname h -> do
withSystemTempFile filenameTemplate $ \fname h -> do
B.hPut h bs
hClose h
h' <- openBinaryFile fname ReadMode
Expand Down
4 changes: 4 additions & 0 deletions proto-lens-tests/tests/proto3_optional_test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -117,6 +117,10 @@ instance HasField Foo "maybe'_nonsynth" (Maybe ()) where
fieldOf _ = lens (const Nothing) const
#endif

-- Ignore lint suggestions which test generated type names.
{- HLINT ignore Foo'_tracked -}
{- HLINT ignore Foo'_nonsynth -}

-- We should not generate a data type or constructor for the synthetic oneof.
data Foo'_tracked = Foo'Tracked Int32
#if 0
Expand Down

0 comments on commit 4df4073

Please sign in to comment.