Skip to content

Commit

Permalink
fix: Cleanup some hlint warnings.
Browse files Browse the repository at this point in the history
  • Loading branch information
iphydf committed Dec 18, 2023
1 parent de55692 commit ed2ba7e
Show file tree
Hide file tree
Showing 10 changed files with 11 additions and 16 deletions.
2 changes: 0 additions & 2 deletions src/Language/Cimple/Ast.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,8 @@
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE StrictData #-}
module Language.Cimple.Ast
( AssignOp (..)
, BinaryOp (..)
Expand Down
3 changes: 1 addition & 2 deletions src/Language/Cimple/DescribeAst.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE StrictData #-}
module Language.Cimple.DescribeAst
( HasLocation (..)
, describeLexeme
Expand Down Expand Up @@ -34,7 +33,7 @@ describeNode node = case unFix node of
PreprocIf{} -> "#if/#endif block"
PreprocIfdef{} -> "#ifdef/#endif block"
PreprocIfndef{} -> "#ifndef/#endif block"
_ -> show $ (const ellipsis) <$> unFix node
_ -> show $ ellipsis <$ unFix node
where
ellipsis :: String
ellipsis = "..."
Expand Down
1 change: 0 additions & 1 deletion src/Language/Cimple/Diagnostics.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE StrictData #-}
module Language.Cimple.Diagnostics
( Diagnostics
, HasDiagnostics (..)
Expand Down
3 changes: 1 addition & 2 deletions src/Language/Cimple/Flatten.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,6 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeOperators #-}
module Language.Cimple.Flatten (lexemes) where

Expand Down Expand Up @@ -81,7 +80,7 @@ instance GenConcatsFlatten (Fix (CommentF a)) a where
gconcatsFlatten (Fix (DocRParen x)) = gconcatsFlatten x
gconcatsFlatten (Fix (DocSee r x)) = r : gconcatsFlatten x
gconcatsFlatten (Fix (DocSentence x p)) = gconcatsFlatten x ++ [p]
gconcatsFlatten (Fix (DocULItem i x)) = concat [gconcatsFlatten i, gconcatsFlatten x]
gconcatsFlatten (Fix (DocULItem i x)) = gconcatsFlatten i ++ gconcatsFlatten x
gconcatsFlatten (Fix (DocWord x)) = [x]

instance GenConcatsFlatten t a => GenConcats (Rec0 t) a where
Expand Down
3 changes: 1 addition & 2 deletions src/Language/Cimple/IO.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# LANGUAGE Strict #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE Strict #-}
module Language.Cimple.IO
( parseExpr
, parseFile
Expand Down
1 change: 0 additions & 1 deletion src/Language/Cimple/MapAst.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,6 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
module Language.Cimple.MapAst
( mapAst
Expand Down
7 changes: 5 additions & 2 deletions src/Language/Cimple/Pretty.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
{-# OPTIONS_GHC -Wno-missing-signatures #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# HLINT ignore "Functor law" #-}
{-# HLINT ignore "Use <$" #-}
module Language.Cimple.Pretty
( plain
, render
Expand Down Expand Up @@ -275,8 +277,9 @@ ppVerbatimComment =
ppCommentInfo :: Comment (Lexeme Text) -> Doc
ppCommentInfo = foldFix go
where
ppBody = vcat . zipWith (<>) ( repeat (dullyellow (text " * " )))
ppIndented = vcat . zipWith (<>) (empty : repeat (dullyellow (text " * ")))
commentStart t = repeat (dullyellow (text t))
ppBody = vcat . zipWith (<>) ( commentStart " * " )
ppIndented = vcat . zipWith (<>) (empty : commentStart " * ")
ppRef = underline . cyan . ppLexeme
ppAttr = maybe empty (blue . ppLexeme)

Expand Down
3 changes: 1 addition & 2 deletions src/Language/Cimple/SemCheck/Includes.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# LANGUAGE Strict #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE Strict #-}
module Language.Cimple.SemCheck.Includes
( collectIncludes
, normaliseIncludes
Expand Down
1 change: 0 additions & 1 deletion src/Language/Cimple/TraverseAst.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,6 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
module Language.Cimple.TraverseAst
( traverseAst
Expand Down
3 changes: 2 additions & 1 deletion tools/count-tokens.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# LANGUAGE Strict #-}
module Main (main) where

import Data.Bifunctor (bimap)
import qualified Data.ByteString.Lazy as LBS
import qualified Data.Text as Text
import Data.Time.Clock (diffUTCTime, getCurrentTime)
Expand All @@ -27,7 +28,7 @@ processFile source = do
Right ok -> return ok

processFiles :: [FilePath] -> IO (Int, Int)
processFiles = fmap ((\(a, b) -> (sum a, sum b)) . unzip) . mapM processFile
processFiles = fmap (bimap sum sum . unzip) . mapM processFile

main :: IO ()
main = do
Expand Down

0 comments on commit ed2ba7e

Please sign in to comment.