{-# LANGUAGE NamedFieldPuns #-}

module Hadolint.Lint where

import qualified Control.Concurrent.Async as Async
import Control.Parallel.Strategies (parListChunk, rseq, using)
import qualified Data.List.NonEmpty as NonEmpty
import Data.Text (Text)
import GHC.Conc (numCapabilities)
import qualified Hadolint.Formatter.Checkstyle as Checkstyle
import qualified Hadolint.Formatter.Codacy as Codacy
import qualified Hadolint.Formatter.Codeclimate as Codeclimate
import qualified Hadolint.Formatter.Format as Format
import qualified Hadolint.Formatter.Json as Json
import qualified Hadolint.Formatter.TTY as TTY
import qualified Hadolint.Rules as Rules
import qualified Language.Docker as Docker
import Language.Docker.Parser (DockerfileError, Error)
import Language.Docker.Syntax (Dockerfile)


type ErrorRule = Text
type WarningRule = Text
type InfoRule = Text
type StyleRule = Text
type IgnoreRule = Text

type TrustedRegistry = Text

data LintOptions = LintOptions
  { LintOptions -> [ErrorRule]
errorRules :: [ErrorRule],
    LintOptions -> [ErrorRule]
warningRules :: [WarningRule],
    LintOptions -> [ErrorRule]
infoRules :: [InfoRule],
    LintOptions -> [ErrorRule]
styleRules :: [StyleRule],
    LintOptions -> [ErrorRule]
ignoreRules :: [IgnoreRule],
    LintOptions -> RulesConfig
rulesConfig :: Rules.RulesConfig
  }
  deriving (Int -> LintOptions -> ShowS
[LintOptions] -> ShowS
LintOptions -> String
(Int -> LintOptions -> ShowS)
-> (LintOptions -> String)
-> ([LintOptions] -> ShowS)
-> Show LintOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LintOptions] -> ShowS
$cshowList :: [LintOptions] -> ShowS
show :: LintOptions -> String
$cshow :: LintOptions -> String
showsPrec :: Int -> LintOptions -> ShowS
$cshowsPrec :: Int -> LintOptions -> ShowS
Show)

data OutputFormat
  = Json
  | TTY
  | CodeclimateJson
  | GitlabCodeclimateJson
  | Checkstyle
  | Codacy
  deriving (Int -> OutputFormat -> ShowS
[OutputFormat] -> ShowS
OutputFormat -> String
(Int -> OutputFormat -> ShowS)
-> (OutputFormat -> String)
-> ([OutputFormat] -> ShowS)
-> Show OutputFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OutputFormat] -> ShowS
$cshowList :: [OutputFormat] -> ShowS
show :: OutputFormat -> String
$cshow :: OutputFormat -> String
showsPrec :: Int -> OutputFormat -> ShowS
$cshowsPrec :: Int -> OutputFormat -> ShowS
Show, OutputFormat -> OutputFormat -> Bool
(OutputFormat -> OutputFormat -> Bool)
-> (OutputFormat -> OutputFormat -> Bool) -> Eq OutputFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OutputFormat -> OutputFormat -> Bool
$c/= :: OutputFormat -> OutputFormat -> Bool
== :: OutputFormat -> OutputFormat -> Bool
$c== :: OutputFormat -> OutputFormat -> Bool
Eq)

printResults :: OutputFormat -> Bool -> Format.Result Text DockerfileError -> IO ()
printResults :: OutputFormat -> Bool -> Result ErrorRule DockerfileError -> IO ()
printResults OutputFormat
format Bool
nocolor Result ErrorRule DockerfileError
allResults =
  case OutputFormat
format of
    OutputFormat
TTY -> Result ErrorRule DockerfileError -> Bool -> IO ()
forall s e.
(VisualStream s, TraversableStream s, ShowErrorComponent e) =>
Result s e -> Bool -> IO ()
TTY.printResult Result ErrorRule DockerfileError
allResults Bool
nocolor
    OutputFormat
Json -> Result ErrorRule DockerfileError -> IO ()
forall s e.
(VisualStream s, TraversableStream s, ShowErrorComponent e) =>
Result s e -> IO ()
Json.printResult Result ErrorRule DockerfileError
allResults
    OutputFormat
Checkstyle -> Result ErrorRule DockerfileError -> IO ()
forall s e.
(VisualStream s, TraversableStream s, ShowErrorComponent e) =>
Result s e -> IO ()
Checkstyle.printResult Result ErrorRule DockerfileError
allResults
    OutputFormat
CodeclimateJson -> Result ErrorRule DockerfileError -> IO ()
forall s e.
(VisualStream s, TraversableStream s, ShowErrorComponent e) =>
Result s e -> IO ()
Codeclimate.printResult Result ErrorRule DockerfileError
allResults
    OutputFormat
GitlabCodeclimateJson -> Result ErrorRule DockerfileError -> IO ()
forall s e.
(VisualStream s, TraversableStream s, ShowErrorComponent e) =>
Result s e -> IO ()
Codeclimate.printGitlabResult Result ErrorRule DockerfileError
allResults
    OutputFormat
Codacy -> Result ErrorRule DockerfileError -> IO ()
forall s e.
(VisualStream s, TraversableStream s, ShowErrorComponent e) =>
Result s e -> IO ()
Codacy.printResult Result ErrorRule DockerfileError
allResults

shallSkipErrorStatus:: OutputFormat -> Bool
shallSkipErrorStatus :: OutputFormat -> Bool
shallSkipErrorStatus OutputFormat
format  = OutputFormat
format OutputFormat -> [OutputFormat] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [OutputFormat
CodeclimateJson, OutputFormat
Codacy]

-- | Performs the process of parsing the dockerfile and analyzing it with all the applicable
-- rules, depending on the list of ignored rules.
-- Depending on the preferred printing format, it will output the results to stdout
lint :: LintOptions -> NonEmpty.NonEmpty String -> IO (Format.Result Text DockerfileError)
lint :: LintOptions
-> NonEmpty String -> IO (Result ErrorRule DockerfileError)
lint
  LintOptions
    { errorRules :: LintOptions -> [ErrorRule]
errorRules = [ErrorRule]
errorList,
      warningRules :: LintOptions -> [ErrorRule]
warningRules = [ErrorRule]
warningList,
      infoRules :: LintOptions -> [ErrorRule]
infoRules = [ErrorRule]
infoList,
      styleRules :: LintOptions -> [ErrorRule]
styleRules = [ErrorRule]
styleList,
      ignoreRules :: LintOptions -> [ErrorRule]
ignoreRules = [ErrorRule]
ignoreList,
      RulesConfig
rulesConfig :: RulesConfig
rulesConfig :: LintOptions -> RulesConfig
rulesConfig
    }
  NonEmpty String
dFiles = do
    [Either Error Dockerfile]
parsedFiles <- (String -> IO (Either Error Dockerfile))
-> [String] -> IO [Either Error Dockerfile]
forall (t :: * -> *) a b.
Traversable t =>
(a -> IO b) -> t a -> IO (t b)
Async.mapConcurrently String -> IO (Either Error Dockerfile)
parseFile (NonEmpty String -> [String]
forall a. NonEmpty a -> [a]
NonEmpty.toList NonEmpty String
dFiles)
    let results :: [Result ErrorRule DockerfileError]
results = [Either Error Dockerfile] -> [Result ErrorRule DockerfileError]
forall s e.
[Either (ParseErrorBundle s e) Dockerfile] -> [Result s e]
lintAll [Either Error Dockerfile]
parsedFiles [Result ErrorRule DockerfileError]
-> Strategy [Result ErrorRule DockerfileError]
-> [Result ErrorRule DockerfileError]
forall a. a -> Strategy a -> a
`using` Int
-> Strategy (Result ErrorRule DockerfileError)
-> Strategy [Result ErrorRule DockerfileError]
forall a. Int -> Strategy a -> Strategy [a]
parListChunk (Int -> Int -> Int
forall a. Integral a => a -> a -> a
div Int
numCapabilities Int
2) Strategy (Result ErrorRule DockerfileError)
forall a. Strategy a
rseq
    Result ErrorRule DockerfileError
-> IO (Result ErrorRule DockerfileError)
forall (m :: * -> *) a. Monad m => a -> m a
return (Result ErrorRule DockerfileError
 -> IO (Result ErrorRule DockerfileError))
-> Result ErrorRule DockerfileError
-> IO (Result ErrorRule DockerfileError)
forall a b. (a -> b) -> a -> b
$ [Result ErrorRule DockerfileError]
-> Result ErrorRule DockerfileError
forall a. Monoid a => [a] -> a
mconcat [Result ErrorRule DockerfileError]
results
    where
      parseFile :: String -> IO (Either Error Dockerfile)
      parseFile :: String -> IO (Either Error Dockerfile)
parseFile String
"-" = IO (Either Error Dockerfile)
Docker.parseStdin
      parseFile String
s = String -> IO (Either Error Dockerfile)
Docker.parseFile String
s

      lintAll :: [Either (ParseErrorBundle s e) Dockerfile] -> [Result s e]
lintAll = (Either (ParseErrorBundle s e) Dockerfile -> Result s e)
-> [Either (ParseErrorBundle s e) Dockerfile] -> [Result s e]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Either (ParseErrorBundle s e) Dockerfile -> Result s e
forall s e. Either (ParseErrorBundle s e) Dockerfile -> Result s e
lintDockerfile

      lintDockerfile :: Either (ParseErrorBundle s e) Dockerfile -> Result s e
lintDockerfile = Either (ParseErrorBundle s e) Dockerfile -> Result s e
forall s e. Either (ParseErrorBundle s e) Dockerfile -> Result s e
processedFile
        where
          processedFile :: Either (ParseErrorBundle s e) Dockerfile -> Result s e
processedFile = Either (ParseErrorBundle s e) [RuleCheck] -> Result s e
forall s e. Either (ParseErrorBundle s e) [RuleCheck] -> Result s e
Format.toResult (Either (ParseErrorBundle s e) [RuleCheck] -> Result s e)
-> (Either (ParseErrorBundle s e) Dockerfile
    -> Either (ParseErrorBundle s e) [RuleCheck])
-> Either (ParseErrorBundle s e) Dockerfile
-> Result s e
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Dockerfile -> [RuleCheck])
-> Either (ParseErrorBundle s e) Dockerfile
-> Either (ParseErrorBundle s e) [RuleCheck]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Dockerfile -> [RuleCheck]
processRules
          processRules :: Dockerfile -> [RuleCheck]
processRules Dockerfile
fileLines =
            (RuleCheck -> Bool) -> [RuleCheck] -> [RuleCheck]
forall a. (a -> Bool) -> [a] -> [a]
filter RuleCheck -> Bool
ignoredRules ([RuleCheck] -> [RuleCheck]) -> [RuleCheck] -> [RuleCheck]
forall a b. (a -> b) -> a -> b
$
              (RuleCheck -> RuleCheck) -> [RuleCheck] -> [RuleCheck]
forall a b. (a -> b) -> [a] -> [b]
map
                ( DLSeverity -> [ErrorRule] -> RuleCheck -> RuleCheck
forall (t :: * -> *).
Foldable t =>
DLSeverity -> t ErrorRule -> RuleCheck -> RuleCheck
makeSeverity DLSeverity
Rules.DLErrorC [ErrorRule]
errorList
                (RuleCheck -> RuleCheck)
-> (RuleCheck -> RuleCheck) -> RuleCheck -> RuleCheck
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DLSeverity -> [ErrorRule] -> RuleCheck -> RuleCheck
forall (t :: * -> *).
Foldable t =>
DLSeverity -> t ErrorRule -> RuleCheck -> RuleCheck
makeSeverity DLSeverity
Rules.DLWarningC [ErrorRule]
warningList
                (RuleCheck -> RuleCheck)
-> (RuleCheck -> RuleCheck) -> RuleCheck -> RuleCheck
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DLSeverity -> [ErrorRule] -> RuleCheck -> RuleCheck
forall (t :: * -> *).
Foldable t =>
DLSeverity -> t ErrorRule -> RuleCheck -> RuleCheck
makeSeverity DLSeverity
Rules.DLInfoC [ErrorRule]
infoList
                (RuleCheck -> RuleCheck)
-> (RuleCheck -> RuleCheck) -> RuleCheck -> RuleCheck
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DLSeverity -> [ErrorRule] -> RuleCheck -> RuleCheck
forall (t :: * -> *).
Foldable t =>
DLSeverity -> t ErrorRule -> RuleCheck -> RuleCheck
makeSeverity DLSeverity
Rules.DLStyleC [ErrorRule]
styleList
                )
                ([RuleCheck] -> [RuleCheck]) -> [RuleCheck] -> [RuleCheck]
forall a b. (a -> b) -> a -> b
$ RulesConfig -> Dockerfile -> [RuleCheck]
analyzeAll RulesConfig
rulesConfig Dockerfile
fileLines

          ignoredRules :: RuleCheck -> Bool
ignoredRules = [ErrorRule] -> RuleCheck -> Bool
ignoreFilter [ErrorRule]
ignoreList

          makeSeverity :: DLSeverity -> t ErrorRule -> RuleCheck -> RuleCheck
makeSeverity DLSeverity
s t ErrorRule
rules rule :: RuleCheck
rule@(Rules.RuleCheck (Rules.Metadata ErrorRule
code DLSeverity
_ ErrorRule
message) ErrorRule
filename Int
linenumber Bool
success) =
            if ErrorRule
code ErrorRule -> t ErrorRule -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` t ErrorRule
rules
              then Metadata -> ErrorRule -> Int -> Bool -> RuleCheck
Rules.RuleCheck (ErrorRule -> DLSeverity -> ErrorRule -> Metadata
Rules.Metadata ErrorRule
code DLSeverity
s ErrorRule
message) ErrorRule
filename Int
linenumber Bool
success
              else RuleCheck
rule

          ignoreFilter :: [IgnoreRule] -> Rules.RuleCheck -> Bool
          ignoreFilter :: [ErrorRule] -> RuleCheck -> Bool
ignoreFilter [ErrorRule]
rules (Rules.RuleCheck (Rules.Metadata ErrorRule
code DLSeverity
severity ErrorRule
_) ErrorRule
_ Int
_ Bool
_) =
            ErrorRule
code ErrorRule -> [ErrorRule] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [ErrorRule]
rules Bool -> Bool -> Bool
&& DLSeverity
severity DLSeverity -> DLSeverity -> Bool
forall a. Eq a => a -> a -> Bool
/= DLSeverity
Rules.DLIgnoreC

-- | Returns the result of applying all the rules to the given dockerfile
analyzeAll :: Rules.RulesConfig -> Dockerfile -> [Rules.RuleCheck]
analyzeAll :: RulesConfig -> Dockerfile -> [RuleCheck]
analyzeAll RulesConfig
config = [Rule] -> Dockerfile -> [RuleCheck]
Rules.analyze ([Rule]
Rules.rules [Rule] -> [Rule] -> [Rule]
forall a. [a] -> [a] -> [a]
++ RulesConfig -> [Rule]
Rules.optionalRules RulesConfig
config)

-- | Helper to analyze AST quickly in GHCI
analyzeEither :: Rules.RulesConfig -> Either t Dockerfile -> [Rules.RuleCheck]
analyzeEither :: RulesConfig -> Either t Dockerfile -> [RuleCheck]
analyzeEither RulesConfig
_ (Left t
_) = []
analyzeEither RulesConfig
config (Right Dockerfile
dockerFile) = RulesConfig -> Dockerfile -> [RuleCheck]
analyzeAll RulesConfig
config Dockerfile
dockerFile