mirror of
https://github.com/koalaman/shellcheck
synced 2025-08-20 05:13:49 -07:00
feat(formatter): add codeclimate formatter
This commit is contained in:
parent
20d11c1c33
commit
747b55239d
4 changed files with 143 additions and 0 deletions
|
@ -7,6 +7,7 @@
|
||||||
- SC2332: Warn about `[ ! -o opt ]` being unconditionally true in Bash.
|
- SC2332: Warn about `[ ! -o opt ]` being unconditionally true in Bash.
|
||||||
- SC3062: Warn about bashism `[ -o opt ]`.
|
- SC3062: Warn about bashism `[ -o opt ]`.
|
||||||
- Precompiled binaries for Linux riscv64 (linux.riscv64)
|
- Precompiled binaries for Linux riscv64 (linux.riscv64)
|
||||||
|
- Codeclimate: New Codeclimate formatter for GitLab Pipelines.
|
||||||
### Changed
|
### Changed
|
||||||
- SC2002 about Useless Use Of Cat is now disabled by default. It can be
|
- SC2002 about Useless Use Of Cat is now disabled by default. It can be
|
||||||
re-enabled with `--enable=useless-use-of-cat` or equivalent directive.
|
re-enabled with `--enable=useless-use-of-cat` or equivalent directive.
|
||||||
|
|
|
@ -89,6 +89,7 @@ library
|
||||||
ShellCheck.Formatter.GCC
|
ShellCheck.Formatter.GCC
|
||||||
ShellCheck.Formatter.JSON
|
ShellCheck.Formatter.JSON
|
||||||
ShellCheck.Formatter.JSON1
|
ShellCheck.Formatter.JSON1
|
||||||
|
ShellCheck.Formatter.Codeclimate
|
||||||
ShellCheck.Formatter.TTY
|
ShellCheck.Formatter.TTY
|
||||||
ShellCheck.Formatter.Quiet
|
ShellCheck.Formatter.Quiet
|
||||||
ShellCheck.Interface
|
ShellCheck.Interface
|
||||||
|
|
|
@ -29,6 +29,7 @@ import qualified ShellCheck.Formatter.Diff
|
||||||
import qualified ShellCheck.Formatter.GCC
|
import qualified ShellCheck.Formatter.GCC
|
||||||
import qualified ShellCheck.Formatter.JSON
|
import qualified ShellCheck.Formatter.JSON
|
||||||
import qualified ShellCheck.Formatter.JSON1
|
import qualified ShellCheck.Formatter.JSON1
|
||||||
|
import qualified ShellCheck.Formatter.Codeclimate
|
||||||
import qualified ShellCheck.Formatter.TTY
|
import qualified ShellCheck.Formatter.TTY
|
||||||
import qualified ShellCheck.Formatter.Quiet
|
import qualified ShellCheck.Formatter.Quiet
|
||||||
|
|
||||||
|
@ -155,6 +156,7 @@ formats options = Map.fromList [
|
||||||
("gcc", ShellCheck.Formatter.GCC.format),
|
("gcc", ShellCheck.Formatter.GCC.format),
|
||||||
("json", ShellCheck.Formatter.JSON.format),
|
("json", ShellCheck.Formatter.JSON.format),
|
||||||
("json1", ShellCheck.Formatter.JSON1.format),
|
("json1", ShellCheck.Formatter.JSON1.format),
|
||||||
|
("codeclimate", ShellCheck.Formatter.Codeclimate.format),
|
||||||
("tty", ShellCheck.Formatter.TTY.format options),
|
("tty", ShellCheck.Formatter.TTY.format options),
|
||||||
("quiet", ShellCheck.Formatter.Quiet.format options)
|
("quiet", ShellCheck.Formatter.Quiet.format options)
|
||||||
]
|
]
|
||||||
|
|
139
src/ShellCheck/Formatter/Codeclimate.hs
Normal file
139
src/ShellCheck/Formatter/Codeclimate.hs
Normal file
|
@ -0,0 +1,139 @@
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
module ShellCheck.Formatter.Codeclimate (format) where
|
||||||
|
|
||||||
|
import ShellCheck.Interface
|
||||||
|
import ShellCheck.Formatter.Format
|
||||||
|
|
||||||
|
import Control.DeepSeq (deepseq)
|
||||||
|
import Data.Aeson
|
||||||
|
import Data.IORef
|
||||||
|
import System.IO (hPutStrLn, stderr)
|
||||||
|
import qualified Data.ByteString.Lazy.Char8 as BL
|
||||||
|
import qualified Data.List.NonEmpty as NE
|
||||||
|
import qualified Data.ByteString.Char8 as BS
|
||||||
|
|
||||||
|
format :: IO Formatter
|
||||||
|
format = do
|
||||||
|
ref <- newIORef []
|
||||||
|
return Formatter
|
||||||
|
{ header = return ()
|
||||||
|
, onResult = collectResult ref
|
||||||
|
, onFailure = outputError
|
||||||
|
, footer = finish ref
|
||||||
|
}
|
||||||
|
|
||||||
|
data CCIssue = CCIssue
|
||||||
|
{ description :: String
|
||||||
|
, check_name :: String
|
||||||
|
, fingerprint :: String
|
||||||
|
, severity :: String
|
||||||
|
, location :: CCLocation
|
||||||
|
}
|
||||||
|
|
||||||
|
data CCLocation = CCLocation
|
||||||
|
{ path :: String
|
||||||
|
, positions :: CCPositions
|
||||||
|
}
|
||||||
|
|
||||||
|
data CCPositions = CCPositions
|
||||||
|
{ begin :: CCPosition
|
||||||
|
, end :: CCPosition
|
||||||
|
}
|
||||||
|
|
||||||
|
data CCPosition = CCPosition
|
||||||
|
{ line :: Integer
|
||||||
|
, column :: Integer
|
||||||
|
}
|
||||||
|
|
||||||
|
-- ToJSON instances
|
||||||
|
instance ToJSON CCIssue where
|
||||||
|
toJSON issue = object
|
||||||
|
[ "type" .= ("issue" :: String)
|
||||||
|
, "description" .= description issue
|
||||||
|
, "check_name" .= check_name issue
|
||||||
|
, "fingerprint" .= fingerprint issue
|
||||||
|
, "severity" .= severity issue
|
||||||
|
, "location" .= location issue
|
||||||
|
]
|
||||||
|
toEncoding issue = pairs
|
||||||
|
( "type" .= ("issue" :: String)
|
||||||
|
<> "description" .= description issue
|
||||||
|
<> "check_name" .= check_name issue
|
||||||
|
<> "fingerprint" .= fingerprint issue
|
||||||
|
<> "severity" .= severity issue
|
||||||
|
<> "location" .= location issue
|
||||||
|
)
|
||||||
|
|
||||||
|
instance ToJSON CCLocation where
|
||||||
|
toJSON loc = object
|
||||||
|
[ "path" .= path loc
|
||||||
|
, "positions" .= positions loc
|
||||||
|
]
|
||||||
|
|
||||||
|
instance ToJSON CCPositions where
|
||||||
|
toJSON pos = object
|
||||||
|
[ "begin" .= begin pos
|
||||||
|
, "end" .= end pos
|
||||||
|
]
|
||||||
|
|
||||||
|
instance ToJSON CCPosition where
|
||||||
|
toJSON p = object
|
||||||
|
[ "line" .= line p
|
||||||
|
, "column" .= column p
|
||||||
|
]
|
||||||
|
|
||||||
|
-- Mapping ShellCheck PositionedComment -> CCIssue
|
||||||
|
toCCIssue :: PositionedComment -> CCIssue
|
||||||
|
toCCIssue pc =
|
||||||
|
let start = pcStartPos pc
|
||||||
|
endPos = pcEndPos pc
|
||||||
|
filePath = posFile start
|
||||||
|
lineNum = posLine start
|
||||||
|
endLineNum = posLine endPos
|
||||||
|
columnNum = posColumn start
|
||||||
|
endColumnNum = posColumn endPos
|
||||||
|
c = pcComment pc
|
||||||
|
codeNum = cCode c
|
||||||
|
msg = cMessage c
|
||||||
|
desc = msg
|
||||||
|
checkName = "SC" ++ show codeNum
|
||||||
|
fingerprint = filePath ++ ":" ++ show lineNum ++ ":" ++ show codeNum
|
||||||
|
sevText = severityText pc
|
||||||
|
severityCC = mapSeverity sevText
|
||||||
|
in CCIssue
|
||||||
|
{ description = desc
|
||||||
|
, check_name = checkName
|
||||||
|
, fingerprint = fingerprint
|
||||||
|
, severity = severityCC
|
||||||
|
, location = CCLocation filePath (CCPositions (CCPosition lineNum columnNum) (CCPosition endLineNum endColumnNum))
|
||||||
|
}
|
||||||
|
|
||||||
|
-- ShellCheck severity levels to Code Climate levels
|
||||||
|
mapSeverity :: String -> String
|
||||||
|
mapSeverity "error" = "critical"
|
||||||
|
mapSeverity "warning" = "major"
|
||||||
|
mapSeverity "info" = "minor"
|
||||||
|
mapSeverity "style" = "info"
|
||||||
|
mapSeverity _ = "minor"
|
||||||
|
|
||||||
|
outputError :: FilePath -> String -> IO ()
|
||||||
|
outputError file msg = hPutStrLn stderr $ file ++ ": " ++ msg
|
||||||
|
|
||||||
|
collectResult ref cr sys = mapM_ f groups
|
||||||
|
where
|
||||||
|
commentsAll = crComments cr
|
||||||
|
groups = NE.groupWith sourceFile commentsAll
|
||||||
|
f :: NE.NonEmpty PositionedComment -> IO ()
|
||||||
|
f group = do
|
||||||
|
let filename = sourceFile (NE.head group)
|
||||||
|
result <- siReadFile sys (Just True) filename
|
||||||
|
let contents = either (const "") id result
|
||||||
|
let comments' = makeNonVirtual commentsAll contents
|
||||||
|
deepseq comments' $ modifyIORef ref (\x -> comments' ++ x)
|
||||||
|
|
||||||
|
finish :: IORef [PositionedComment] -> IO ()
|
||||||
|
finish ref = do
|
||||||
|
pcs <- readIORef ref
|
||||||
|
let issues = map toCCIssue pcs
|
||||||
|
BL.putStrLn $ encode issues
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue