module Hadolint.Rule.DL3004 (rule) where

import Hadolint.Rule
import Hadolint.Shell (ParsedShell, usingProgram)
import Language.Docker.Syntax (Instruction (..), RunArgs (..))


rule :: Rule ParsedShell
rule :: Rule ParsedShell
rule = Rule ParsedShell
dl3004 forall a. Semigroup a => a -> a -> a
<> forall args. Rule args -> Rule args
onbuild Rule ParsedShell
dl3004
{-# INLINEABLE rule #-}

dl3004 :: Rule ParsedShell
dl3004 :: Rule ParsedShell
dl3004 = forall args.
RuleCode
-> DLSeverity -> Text -> (Instruction args -> Bool) -> Rule args
simpleRule RuleCode
code DLSeverity
severity Text
message Instruction ParsedShell -> Bool
check
  where
    code :: RuleCode
code = RuleCode
"DL3004"
    severity :: DLSeverity
severity = DLSeverity
DLErrorC
    message :: Text
message =
      Text
"Do not use sudo as it leads to unpredictable behavior. Use a tool like\
      \ gosu to enforce root"
    check :: Instruction ParsedShell -> Bool
check (Run (RunArgs Arguments ParsedShell
args RunFlags
_)) = forall a b. (a -> b) -> Arguments a -> b
foldArguments (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ParsedShell -> Bool
usingProgram Text
"sudo") Arguments ParsedShell
args
    check Instruction ParsedShell
_ = Bool
True
{-# INLINEABLE dl3004 #-}