Skip to content

Commit c975d91

Browse files
committed
hlint fixes
1 parent bdcc924 commit c975d91

File tree

4 files changed

+22
-26
lines changed

4 files changed

+22
-26
lines changed

RegistryProcessor/src/DeclarationParser.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@ parseDeclaration = do
2323
return (typeSpec, length pointers + a)
2424

2525
optionalConst :: ReadP ()
26-
optionalConst = option' () (token "const" >> return ())
26+
optionalConst = option' () (void (token "const"))
2727

2828
parseTypeSpecifier :: ReadP String
2929
parseTypeSpecifier = choice' [

RegistryProcessor/src/Main.hs

Lines changed: 11 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -111,7 +111,7 @@ printGroups api registry = do
111111
-- is very naive about what is the canonical name and what is an alias.
112112
CM.forM_ es $ \e -> do
113113
let same = L.sort [ f | f <- es, enumValue e == enumValue f ]
114-
CM.when (e == head same) $ do
114+
CM.when (e == head same) $
115115
hRender h $ Comment ("* " ++ linkToToken e ++
116116
(case tail same of
117117
[] -> ""
@@ -274,7 +274,7 @@ extensionModules api registry =
274274
]
275275
where suppProfs = latestProfiles api
276276
isProfileDependent mods = any (`S.member` allProfileNames) (mentionedProfileNames mods)
277-
mentionedProfileNames mods = DM.catMaybes . map modificationProfile $ mods
277+
mentionedProfileNames = DM.mapMaybe modificationProfile
278278
allProfileNames = S.fromList . DM.catMaybes $ suppProfs
279279

280280
-- We only consider non-empty supported extensions/modifications for the given API.
@@ -283,7 +283,7 @@ supportedExtensions api registry =
283283
[ nameAndMods
284284
| ext <- extensions registry
285285
, api `supports` extensionSupported ext
286-
, nameAndMods@(_,(_:_)) <- [nameAndModifications ext] ]
286+
, nameAndMods@(_, _:_) <- [nameAndModifications ext] ]
287287
where nameAndModifications :: Extension -> (ExtensionName, [Modification])
288288
nameAndModifications e =
289289
(extensionName e,
@@ -351,11 +351,11 @@ printExtensionSupport extModules = do
351351
extString = joinWords [ extensionNameAPI extName
352352
, extensionNameCategory extName
353353
, extensionNameName extName ]
354-
SI.hPutStrLn h $ ""
354+
SI.hPutStrLn h ""
355355
hRender h $ Comment ("| Is the " ++ extensionHyperlink extName ++ " extension supported?")
356356
SI.hPutStrLn h $ predNameMonad ++ " :: MonadIO m => m Bool"
357357
SI.hPutStrLn h $ predNameMonad ++ " = getExtensions >>= (return . member " ++ show extString ++ ")"
358-
SI.hPutStrLn h $ ""
358+
SI.hPutStrLn h ""
359359
hRender h $ Comment ("| Is the " ++ extensionHyperlink extName ++ " extension supported?")
360360
hRender h $ Comment "Note that in the presence of multiple contexts with different capabilities,"
361361
hRender h $ Comment ("this might be wrong. Use '" ++ predNameMonad ++ "' in those cases instead.")
@@ -374,7 +374,7 @@ capitalize :: String -> String
374374
capitalize str = C.toUpper (head str) : map C.toLower (tail str)
375375

376376
separate :: (a -> String) -> [a] -> String
377-
separate f = L.intercalate ",\n" . map (" " ++) . map f
377+
separate f = L.intercalate ",\n" . map ((" " ++) . f)
378378

379379
-- Note that we handle features just like extensions.
380380
printExtension :: [String] -> Maybe ExtensionName -> ExtensionParts -> IO ()
@@ -429,7 +429,7 @@ printTopLevel api extModules = do
429429
profToReExport = profileToReExport api
430430
lastComp = featureName (latestVersion api) profToReExport
431431
moduleNames = [ moduleNameFor [c] | c <- [ lastComp, "GetProcAddress" ] ++ mangledCategories ]
432-
cmnt = [ Comment (L.intercalate " "
432+
cmnt = [ Comment (unwords
433433
[ "A convenience module, combining the latest"
434434
, apiName api
435435
, maybe "version" (\p -> unProfileName p ++ " profile") profToReExport
@@ -543,7 +543,7 @@ interfaceElementsFor mbProfile modifications =
543543
op Remove = S.delete
544544

545545
lookup' :: (Ord k, Show k) => k -> M.Map k a -> a
546-
lookup' k m = M.findWithDefault (error ("unknown name " ++ show k)) k m
546+
lookup' k = M.findWithDefault (error ("unknown name " ++ show k)) k
547547

548548
matches :: Eq a => a -> Maybe a -> Bool
549549
_ `matches` Nothing = True
@@ -561,22 +561,20 @@ showCommand api registry sigMap c =
561561
showString (P.render cmnt) .
562562

563563
showString (name ++ "\n") .
564-
showString (" :: MonadIO m\n") .
564+
showString " :: MonadIO m\n" .
565565
showString (" => " ++ signature True) .
566566
showString (name ++ args ++ " = liftIO $ " ++ dyn_name ++ " " ++ ptr_name ++ args ++ "\n\n") .
567567

568568
showString ("{-# NOINLINE " ++ ptr_name ++ " #-}\n") .
569569
showString (ptr_name ++ " :: FunPtr (" ++ compactSignature ++ ")\n") .
570-
showString (ptr_name ++ " = unsafePerformIO $ getCommand " ++ str_name ++ "\n") .
571-
572-
id $ ""
570+
showString (ptr_name ++ " = unsafePerformIO $ getCommand " ++ str_name ++ "\n") $ ""
573571

574572
where name = signatureElementName (resultType c)
575573
dyn_name = lookup' compactSignature sigMap
576574
ptr_name = "ptr_" ++ name
577575
str_name = show name
578576
compactSignature = signature False
579-
signature withComment = showSignatureFromCommand registry c withComment
577+
signature = showSignatureFromCommand registry c
580578
urls = M.findWithDefault [] (api, CommandName name) manPageURLs
581579
links = L.intercalate " or " (map renderURL urls)
582580
cmnt = case concat (man ++ ve ++ al) of

RegistryProcessor/src/MangledRegistry.hs

Lines changed: 6 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -101,7 +101,7 @@ toType t = Type {
101101
typeAPI = API `fmap` R.typeAPI t,
102102
typeRequires = R.TypeName `fmap` R.typeRequires t }
103103

104-
data Group = Group {
104+
newtype Group = Group {
105105
groupEnums :: [EnumName]
106106
} deriving (Eq, Ord, Show)
107107

@@ -157,17 +157,15 @@ toCommand c = Command {
157157
-- Make sure that we don't reference pointers to structs, they are mapped to
158158
-- 'Ptr a' etc., anyway (glCreateSyncFromCLeventARB is an exmaple for this).
159159
filter (not . ("struct " `L.isPrefixOf`) . R.unTypeName) $
160-
DM.catMaybes $
161-
map (R.protoPtype . R.paramProto) $
162-
(pr : ps),
160+
DM.mapMaybe (R.protoPtype . R.paramProto) (pr : ps),
163161
vecEquiv = (CommandName . R.unName) `fmap` R.commandVecEquiv c,
164162
alias = (CommandName . R.unName) `fmap` R.commandAlias c }
165163
where pr = R.Param { R.paramLen = Nothing, R.paramProto = R.commandProto c }
166164
ps = R.commandParams c
167165
varSupply = map (R.TypeName . showIntUsingDigits ['a' .. 'z']) [0 ..]
168166
(resTy:paramTys) = snd $ L.mapAccumL toSignatureElement varSupply (pr : ps)
169167

170-
showIntUsingDigits :: [Char] -> Int -> String
168+
showIntUsingDigits :: String -> Int -> String
171169
showIntUsingDigits ds x = N.showIntAtBase (length ds) (ds !!) x ""
172170

173171
commandName :: Command -> CommandName
@@ -196,14 +194,14 @@ toSignatureElement varSupply param =
196194
either error (\(b,n) ->
197195
renameIf (b == "()" && n > 0)
198196
varSupply
199-
(SignatureElement {
197+
SignatureElement {
200198
arrayLength = R.paramLen param,
201199
belongsToGroup = GroupName `fmap` R.protoGroup proto,
202200
numPointer = n,
203201
baseType = R.TypeName b,
204-
signatureElementName = R.protoName proto})) $
202+
signatureElementName = R.protoName proto}) $
205203
D.parse $
206-
L.intercalate " " $
204+
unwords $
207205
map ($ proto) [
208206
R.protoText1,
209207
maybe "" R.unTypeName . R.protoPtype,

RegistryProcessor/src/Registry.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,7 @@ import Data.Maybe ( maybeToList )
3838
import Text.XML.HXT.Core
3939

4040
parseRegistry :: String -> Either String Registry
41-
parseRegistry = head . (runLA $
41+
parseRegistry = head . runLA (
4242
xreadDoc >>>
4343
neg isXmlPi >>>
4444
removeAllWhiteSpace >>>
@@ -242,7 +242,7 @@ data Commands = Commands {
242242

243243
xpCommands :: PU Commands
244244
xpCommands =
245-
xpWrap (\(a,b) -> Commands a b
245+
xpWrap (uncurry Commands
246246
,\(Commands a b) -> (a,b)) $
247247
xpElem "commands" $
248248
xpPair
@@ -275,7 +275,7 @@ xpCommandTail :: PU (Maybe Name, Maybe Name, [GLX])
275275
xpCommandTail =
276276
xpWrapEither (\xs -> do a <- check "alias" [x | AliasElement x <- xs]
277277
b <- check "vecequiv" [x | VecEquivElement x <- xs]
278-
c <- return [x | GLXElement x <- xs]
278+
let c = [x | GLXElement x <- xs]
279279
return (a,b,c)
280280
,\(a,b,c) -> map AliasElement (maybeToList a) ++
281281
map VecEquivElement (maybeToList b) ++
@@ -472,7 +472,7 @@ xpInterfaceElement = xpAlt (fromEnum . interfaceElementKind) pus
472472
, xpIE InterfaceElementEnum "enum"
473473
, xpIE InterfaceElementCommand "command" ]
474474
xpIE ty el =
475-
xpWrap (\(a,b) -> InterfaceElement ty a b
475+
xpWrap (uncurry (InterfaceElement ty)
476476
,\(InterfaceElement _ a b) -> (a,b)) $
477477
xpElem el $
478478
xpPair

0 commit comments

Comments
 (0)