{-# LANGUAGE NamedFieldPuns #-}
module Hadolint.Rules where
import Control.Arrow ((&&&))
import Data.List
(dropWhile, isInfixOf, isPrefixOf, isSuffixOf, mapAccumL)
import Data.List.NonEmpty (toList)
import Data.List.Split (splitOneOf)
import Hadolint.Bash
import Language.Docker.Syntax
import qualified Data.Set as Set
import qualified ShellCheck.Interface
import ShellCheck.Interface (Severity(..))
import qualified Text.Parsec as Parsec
import Text.Parsec ((<|>))
data Metadata = Metadata
{ code :: String
, severity :: Severity
, message :: String
} deriving (Eq)
data RuleCheck = RuleCheck
{ metadata :: Metadata
, filename :: Filename
, linenumber :: Linenumber
, success :: Bool
} deriving (Eq)
instance Ord RuleCheck where
a `compare` b = linenumber a `compare` linenumber b
link :: Metadata -> String
link (Metadata code _ _)
| "SC" `isPrefixOf` code = "https://github.com/koalaman/shellcheck/wiki/" ++ code
| "DL" `isPrefixOf` code = "https://github.com/hadolint/hadolint/wiki/" ++ code
| otherwise = "https://github.com/hadolint/hadolint"
type Rule = Dockerfile -> [RuleCheck]
mapInstructions ::
Metadata -> (state -> Linenumber -> Instruction -> (state, Bool)) -> state -> Rule
mapInstructions metadata f initialState dockerfile =
let (_, results) = mapAccumL applyRule initialState dockerfile
in results
where
applyRule state (InstructionPos i source linenumber) =
let (newState, res) = f state linenumber i
in (newState, RuleCheck metadata source linenumber res)
instructionRule :: String -> Severity -> String -> (Instruction -> Bool) -> Rule
instructionRule code severity message check =
instructionRuleLine code severity message (const check)
instructionRuleLine :: String -> Severity -> String -> (Linenumber -> Instruction -> Bool) -> Rule
instructionRuleLine code severity message check =
instructionRuleState code severity message checkAndDropState ()
where
checkAndDropState state line instr = (state, check line instr)
instructionRuleState ::
String
-> Severity
-> String
-> (state -> Linenumber -> Instruction -> (state, Bool))
-> state
-> Rule
instructionRuleState code severity message = mapInstructions (Metadata code severity message)
withState :: a -> b -> (a, b)
withState st res = (st, res)
analyze :: [Rule] -> Dockerfile -> [RuleCheck]
analyze list dockerfile = filter failed $ concat [r dockerfile | r <- list]
where
failed RuleCheck {metadata = Metadata {code}, linenumber, success} =
not success && not (wasIgnored code linenumber)
wasIgnored c ln = not $ null [line | (line, codes) <- allIgnores, line == ln, c `elem` codes]
allIgnores = ignored dockerfile
ignored :: Dockerfile -> [(Linenumber, [String])]
ignored dockerfile =
[(l + 1, ignores) | (l, Just ignores) <- map (lineNumber &&& extractIgnored) dockerfile]
where
extractIgnored = ignoreFromInstruction . instruction
ignoreFromInstruction (Comment comment) = either (const Nothing) Just (parseComment comment)
ignoreFromInstruction _ = Nothing
parseComment :: String -> Either Parsec.ParseError [String]
parseComment = Parsec.parse commentParser ""
commentParser =
Parsec.skipMany space >>
Parsec.string "hadolint" >>
Parsec.skipMany1 space >>
Parsec.string "ignore=" >>
Parsec.skipMany space >>
Parsec.sepBy1 ruleName (Parsec.many space >> Parsec.char ',' >> Parsec.many space)
space = Parsec.char ' ' <|> Parsec.char '\t'
ruleName = Parsec.many1 (Parsec.choice $ map Parsec.char "DLSC0123456789")
rules :: [Rule]
rules =
[ absoluteWorkdir
, shellcheckBash
, invalidCmd
, copyInsteadAdd
, copyEndingSlash
, copyFromExists
, copyFromAnother
, fromAliasUnique
, noRootUser
, noCd
, noSudo
, noAptGetUpgrade
, noApkUpgrade
, noLatestTag
, noUntagged
, aptGetVersionPinned
, aptGetCleanup
, apkAddVersionPinned
, apkAddNoCache
, useAdd
, pipVersionPinned
, npmVersionPinned
, invalidPort
, aptGetNoRecommends
, aptGetYes
, wgetOrCurl
, hasNoMaintainer
, multipleCmds
, multipleEntrypoints
, useShell
]
commentMetadata :: ShellCheck.Interface.Comment -> Metadata
commentMetadata (ShellCheck.Interface.Comment severity code message) =
Metadata ("SC" ++ show code) severity message
shellcheckBash :: Dockerfile -> [RuleCheck]
shellcheckBash = concatMap check
where
check (InstructionPos (Run (Arguments args)) source linenumber) =
rmDup [RuleCheck m source linenumber False | m <- convert args]
check _ = []
convert args = [commentMetadata c | c <- shellcheck $ unwords args]
rmDup :: [RuleCheck] -> [RuleCheck]
rmDup [] = []
rmDup (x:xs) = x : rmDup (filter (\y -> metadata x /= metadata y) xs)
bashCommands :: [String] -> [[String]]
bashCommands = splitOneOf [";", "|", "&&"]
allFromImages :: Dockerfile -> [(Linenumber, BaseImage)]
allFromImages dockerfile = [(l, f) | (l, From f) <- instr]
where
instr = fmap (lineNumber &&& instruction) dockerfile
allAliasedImages :: Dockerfile -> [(Linenumber, ImageAlias)]
allAliasedImages dockerfile =
[(l, alias) | (l, Just alias) <- map extractAlias (allFromImages dockerfile)]
where
extractAlias (l, f) = (l, fromAlias f)
allImageNames :: Dockerfile -> [(Linenumber, String)]
allImageNames dockerfile = [(l, fromName baseImage) | (l, baseImage) <- allFromImages dockerfile]
previouslyDefinedAliases :: Linenumber -> Dockerfile -> [String]
previouslyDefinedAliases line dockerfile =
[i | (l, ImageAlias i) <- allAliasedImages dockerfile, l < line]
aliasMustBe :: (String -> Bool) -> Instruction -> Bool
aliasMustBe predicate fromInstr =
case fromInstr of
From (UntaggedImage _ (Just (ImageAlias alias))) -> predicate alias
From (TaggedImage _ _ (Just (ImageAlias alias))) -> predicate alias
From (DigestedImage _ _ (Just (ImageAlias alias))) -> predicate alias
_ -> True
fromName :: BaseImage -> String
fromName (UntaggedImage Image {imageName} _) = imageName
fromName (TaggedImage Image {imageName} _ _) = imageName
fromName (DigestedImage Image {imageName} _ _) = imageName
fromAlias :: BaseImage -> Maybe ImageAlias
fromAlias (UntaggedImage _ alias) = alias
fromAlias (TaggedImage _ _ alias) = alias
fromAlias (DigestedImage _ _ alias) = alias
absoluteWorkdir :: Rule
absoluteWorkdir = instructionRule code severity message check
where
code = "DL3000"
severity = ErrorC
message = "Use absolute WORKDIR"
check (Workdir ('$':_)) = True
check (Workdir ('/':_)) = True
check (Workdir _) = False
check _ = True
hasNoMaintainer :: Rule
hasNoMaintainer = instructionRule code severity message check
where
code = "DL4000"
severity = ErrorC
message = "MAINTAINER is deprecated"
check (Maintainer _) = False
check _ = True
usingProgram :: String -> [String] -> Bool
usingProgram prog args = or [True | cmd:_ <- bashCommands args, cmd == prog]
multipleCmds :: Rule
multipleCmds = instructionRuleState code severity message check Nothing
where
code = "DL4003"
severity = WarningC
message =
"Multiple `CMD` instructions found. If you list more than one `CMD` then only the last \
\`CMD` will take effect"
check Nothing line (Cmd _) = withState (Just line) True
check (Just l) _ (Cmd _) = withState (Just l) False
check st _ _ = withState st True
multipleEntrypoints :: Rule
multipleEntrypoints = instructionRuleState code severity message check Nothing
where
code = "DL4004"
severity = ErrorC
message =
"Multiple `ENTRYPOINT` instructions found. If you list more than one `ENTRYPOINT` then \
\only the last `ENTRYPOINT` will take effect"
check Nothing line (Entrypoint _) = withState (Just line) True
check (Just l) _ (Entrypoint _) = withState (Just l) False
check st _ _ = withState st True
wgetOrCurl :: Rule
wgetOrCurl = instructionRuleState code severity message check Set.empty
where
code = "DL4001"
severity = WarningC
message = "Either use Wget or Curl but not both"
check state _ (Run (Arguments args)) = detectDoubleUsage state args
check state _ _ = withState state True
detectDoubleUsage state args =
let newArgs = extractCommands args
newState = Set.union state newArgs
in withState newState (Set.size newState < 2)
extractCommands args = Set.fromList [w | w <- args, w == "curl" || w == "wget"]
invalidCmd :: Rule
invalidCmd = instructionRule code severity message check
where
code = "DL3001"
severity = InfoC
message =
"For some bash commands it makes no sense running them in a Docker container like `ssh`, \
\`vim`, `shutdown`, `service`, `ps`, `free`, `top`, `kill`, `mount`, `ifconfig`"
check (Run (Arguments (arg:_))) = arg `notElem` invalidCmds
check _ = True
invalidCmds = ["ssh", "vim", "shutdown", "service", "ps", "free", "top", "kill", "mount"]
noRootUser :: Rule
noRootUser = instructionRule code severity message check
where
code = "DL3002"
severity = WarningC
message = "Do not switch to root USER"
check (User user) =
not (isPrefixOf "root:" user || isPrefixOf "0:" user || user == "root" || user == "0")
check _ = True
noCd :: Rule
noCd = instructionRule code severity message check
where
code = "DL3003"
severity = WarningC
message = "Use WORKDIR to switch to a directory"
check (Run (Arguments args)) = not $ usingProgram "cd" args
check _ = True
noSudo :: Rule
noSudo = instructionRule code severity message check
where
code = "DL3004"
severity = ErrorC
message =
"Do not use sudo as it leads to unpredictable behavior. Use a tool like gosu to enforce \
\root"
check (Run (Arguments args)) = not $ usingProgram "sudo" args
check _ = True
noAptGetUpgrade :: Rule
noAptGetUpgrade = instructionRule code severity message check
where
code = "DL3005"
severity = ErrorC
message = "Do not use apt-get upgrade or dist-upgrade"
check (Run (Arguments args)) = not $ isInfixOf ["apt-get", "upgrade"] args
check _ = True
noUntagged :: Rule
noUntagged dockerfile = instructionRuleLine code severity message check dockerfile
where
code = "DL3006"
severity = WarningC
message = "Always tag the version of an image explicitly"
check _ (From (UntaggedImage (Image _ "scratch") _)) = True
check line (From (UntaggedImage (Image _ i) _)) =
i `elem` previouslyDefinedAliases line dockerfile
check _ _ = True
noLatestTag :: Rule
noLatestTag = instructionRule code severity message check
where
code = "DL3007"
severity = WarningC
message =
"Using latest is prone to errors if the image will ever update. Pin the version explicitly \
\to a release tag"
check (From (TaggedImage _ tag _)) = tag /= "latest"
check _ = True
aptGetVersionPinned :: Rule
aptGetVersionPinned = instructionRule code severity message check
where
code = "DL3008"
severity = WarningC
message =
"Pin versions in apt get install. Instead of `apt-get install <package>` use `apt-get \
\install <package>=<version>`"
check (Run (Arguments args)) = and [versionFixed p | p <- aptGetPackages args]
check _ = True
versionFixed package = "=" `isInfixOf` package
aptGetPackages :: [String] -> [String]
aptGetPackages args =
concat
[ filter noOption (dropOptionsWithArg ["-t", "--target-release"] cmd)
| cmd <- bashCommands args
, isAptGetInstall cmd
]
where
noOption arg = arg `notElem` ["apt-get", "install"] && not ("-" `isPrefixOf` arg)
aptGetCleanup :: Rule
aptGetCleanup dockerfile = instructionRuleState code severity message check Nothing dockerfile
where
code = "DL3009"
severity = InfoC
message = "Delete the apt-get lists after installing something"
check _ line f@(From _) = withState (Just (line, f)) True
check st@(Just (line, From baseimage)) _ (Run (Arguments args))
| not (hasUpdate args) || not (imageIsUsed line baseimage) = withState st True
| otherwise = withState st (hasCleanup args)
check st _ _ = withState st True
hasCleanup cmd = ["rm", "-rf", "/var/lib/apt/lists/*"] `isInfixOf` cmd
hasUpdate cmd = ["apt-get", "update"] `isInfixOf` cmd
imageIsUsed line baseimage = isLastImage line baseimage || imageIsUsedLater line baseimage
isLastImage line baseimage =
case reverse (allFromImages dockerfile) of
lst:_ -> (line, baseimage) == lst
_ -> True
imageIsUsedLater line baseimage =
case fromAlias baseimage of
Nothing -> True
Just (ImageAlias alias) ->
alias `elem` [i | (l, i) <- allImageNames dockerfile, l > line]
dropOptionsWithArg :: [String] -> [String] -> [String]
dropOptionsWithArg _ [] = []
dropOptionsWithArg os (x:xs)
| x `elem` os = dropOptionsWithArg os (drop 1 xs)
| otherwise = x : dropOptionsWithArg os xs
noApkUpgrade :: Rule
noApkUpgrade = instructionRule code severity message check
where
code = "DL3017"
severity = ErrorC
message = "Do not use apk upgrade"
check (Run (Arguments args)) = not $ isInfixOf ["apk", "upgrade"] args
check _ = True
isApkAdd :: [String] -> Bool
isApkAdd cmd = ["apk"] `isInfixOf` cmd && ["add"] `isInfixOf` cmd
apkAddVersionPinned :: Rule
apkAddVersionPinned = instructionRule code severity message check
where
code = "DL3018"
severity = WarningC
message =
"Pin versions in apk add. Instead of `apk add <package>` use `apk add <package>=<version>`"
check (Run (Arguments args)) = and [versionFixed p | p <- apkAddPackages args]
check _ = True
versionFixed package = "=" `isInfixOf` package
apkAddPackages :: [String] -> [String]
apkAddPackages args =
concat
[ filter noOption (dropOptionsWithArg ["-t", "--virtual"] cmd)
| cmd <- bashCommands args
, isApkAdd cmd
]
where
noOption arg = arg `notElem` options && not ("--" `isPrefixOf` arg)
options = ["apk", "add", "-q", "-p", "-v", "-f", "-t"]
apkAddNoCache :: Rule
apkAddNoCache = instructionRule code severity message check
where
code = "DL3019"
severity = InfoC
message =
"Use the `--no-cache` switch to avoid the need to use `--update` and remove \
\`/var/cache/apk/*` when done installing packages"
check (Run (Arguments args)) = not (isApkAdd args) || hasNoCacheOption args
check _ = True
hasNoCacheOption cmd = ["--no-cache"] `isInfixOf` cmd
useAdd :: Rule
useAdd = instructionRule code severity message check
where
code = "DL3010"
severity = InfoC
message = "Use ADD for extracting archives into an image"
check (Copy (CopyArgs srcs _ _ _)) =
and
[ not (format `isSuffixOf` src)
| SourcePath src <- toList srcs
, format <- archiveFormats
]
check _ = True
archiveFormats = [".tar", ".gz", ".bz2", "xz"]
invalidPort :: Rule
invalidPort = instructionRule code severity message check
where
code = "DL3011"
severity = ErrorC
message = "Valid UNIX ports range from 0 to 65535"
check (Expose (Ports ports)) =
and [p <= 65535 | Port p _ <- ports] &&
and [l <= 65535 && m <= 65535 | PortRange l m _ <- ports]
check _ = True
pipVersionPinned :: Rule
pipVersionPinned = instructionRule code severity message check
where
code = "DL3013"
severity = WarningC
message =
"Pin versions in pip. Instead of `pip install <package>` use `pip install \
\<package>==<version>`"
check (Run (Arguments args)) = not (isPipInstall args) || all versionFixed (packages args)
check _ = True
isPipInstall :: [String] -> Bool
isPipInstall cmd =
case getInstallArgs cmd of
Nothing -> False
Just args -> not (["-r"] `isInfixOf` args || ["."] `isInfixOf` args)
packages cmd =
case getInstallArgs cmd of
Nothing -> []
Just args -> findPackages args
getInstallArgs = stripInstallPrefix isInstallCommand
isInstallCommand ('p':'i':'p':_) = True
isInstallCommand _ = False
versionFixed package = hasVersionSymbol package || isVersionedGit package
isVersionedGit package = "git+http" `isInfixOf` package && "@" `isInfixOf` package
versionSymbols = ["==", ">=", "<=", ">", "<", "!="]
hasVersionSymbol package = or [s `isInfixOf` package | s <- versionSymbols]
findPackages :: [String] -> [String]
findPackages = takeWhile (not . isEnd) . dropWhile isFlag
where
isEnd word = isFlag word || word `elem` ["&&", "||", ";", "|"]
isFlag ('-':_) = True
isFlag _ = False
stripInstallPrefix :: (String -> Bool) -> [String] -> Maybe [String]
stripInstallPrefix isCommand args =
if ["install"] `isPrefixOf` dropUntilInstall
then dropUntilInstall |> drop 1 |> Just
else Nothing
where
dropUntilInstall =
args |>
dropWhile (not . isCommand) |>
drop 1 |>
dropWhile (/= "install")
a |> f = f a
npmVersionPinned :: Rule
npmVersionPinned = instructionRule code severity message check
where
code = "DL3016"
severity = WarningC
message =
"Pin versions in npm. Instead of `npm install <package>` use `npm install \
\<package>@<version>`"
check (Run (Arguments args)) = all versionFixed (packages args)
check _ = True
packages cmd =
case getInstallArgs cmd of
Nothing -> []
Just args -> findPackages args
getInstallArgs = stripInstallPrefix (== "npm")
versionFixed package =
if hasGitPrefix package
then isVersionedGit package
else hasVersionSymbol package
gitPrefixes = ["git://", "git+ssh://", "git+http://", "git+https://"]
hasGitPrefix package = or [p `isPrefixOf` package | p <- gitPrefixes]
isVersionedGit package = "#" `isInfixOf` package
hasVersionSymbol package = "@" `isInfixOf` dropScope package
where
dropScope pkg =
if "@" `isPrefixOf` pkg
then dropWhile ('/' <) pkg
else pkg
isAptGetInstall :: [String] -> Bool
isAptGetInstall cmd = ["apt-get"] `isInfixOf` cmd && ["install"] `isInfixOf` cmd
aptGetYes :: Rule
aptGetYes = instructionRule code severity message check
where
code = "DL3014"
severity = WarningC
message = "Use the `-y` switch to avoid manual input `apt-get -y install <package>`"
check (Run (Arguments args)) = not (isAptGetInstall args) || hasYesOption args
check _ = True
hasYesOption cmd =
["-y"] `isInfixOf` cmd ||
["--yes"] `isInfixOf` cmd || ["-qq"] `isInfixOf` cmd || startsWithYesFlag cmd
startsWithYesFlag cmd = True `elem` ["-y" `isInfixOf` arg | arg <- cmd]
aptGetNoRecommends :: Rule
aptGetNoRecommends = instructionRule code severity message check
where
code = "DL3015"
severity = InfoC
message = "Avoid additional packages by specifying `--no-install-recommends`"
check (Run (Arguments args)) = not (isAptGetInstall args) || hasNoRecommendsOption args
check _ = True
hasNoRecommendsOption cmd = ["--no-install-recommends"] `isInfixOf` cmd
isArchive :: String -> Bool
isArchive path =
True `elem`
[ ftype `isSuffixOf` path
| ftype <-
[ ".tar"
, ".gz"
, ".bz2"
, ".xz"
, ".zip"
, ".tgz"
, ".tb2"
, ".tbz"
, ".tbz2"
, ".lz"
, ".lzma"
, ".tlz"
, ".txz"
, ".Z"
, ".tZ"
]
]
isUrl :: String -> Bool
isUrl path = True `elem` [proto `isPrefixOf` path | proto <- ["https://", "http://"]]
copyInsteadAdd :: Rule
copyInsteadAdd = instructionRule code severity message check
where
code = "DL3020"
severity = ErrorC
message = "Use COPY instead of ADD for files and folders"
check (Add (AddArgs srcs _ _)) =
and [isArchive src || isUrl src | SourcePath src <- toList srcs]
check _ = True
copyEndingSlash :: Rule
copyEndingSlash = instructionRule code severity message check
where
code = "DL3021"
severity = ErrorC
message = "COPY with more than 2 arguments requires the last argument to end with /"
check (Copy (CopyArgs sources t _ _))
| length sources > 1 = endsWithSlash t
| otherwise = True
check _ = True
endsWithSlash (TargetPath t) = last t == '/'
copyFromExists :: Rule
copyFromExists dockerfile = instructionRuleLine code severity message check dockerfile
where
code = "DL3022"
severity = WarningC
message = "COPY --from should reference a previously defined FROM alias"
check l (Copy (CopyArgs _ _ _ (CopySource s))) = s `elem` previouslyDefinedAliases l dockerfile
check _ _ = True
copyFromAnother :: Rule
copyFromAnother = instructionRuleState code severity message check Nothing
where
code = "DL3023"
severity = ErrorC
message = "COPY --from should reference a previously defined FROM alias"
check _ _ f@(From _) = withState (Just f) True
check st@(Just fromInstr) _ (Copy (CopyArgs _ _ _ (CopySource stageName))) =
withState st (aliasMustBe (/= stageName) fromInstr)
check state _ _ = withState state True
fromAliasUnique :: Rule
fromAliasUnique dockerfile = instructionRuleLine code severity message check dockerfile
where
code = "DL3024"
severity = ErrorC
message = "FROM aliases (stage names) must be unique"
check line = aliasMustBe (not . alreadyTaken line)
alreadyTaken line alias = alias `elem` previouslyDefinedAliases line dockerfile
useShell :: Rule
useShell = instructionRule code severity message check
where
code = "DL4005"
severity = WarningC
message = "Use SHELL to change the default shell"
check (Run (Arguments args)) = not $ any shellSymlink (bashCommands args)
check _ = True
shellSymlink args = usingProgram "ln" args && isInfixOf ["/bin/sh"] args