module Hadolint.Rule.DL3001 (rule) where

import qualified Data.Set as Set
import Hadolint.Rule
import qualified Hadolint.Shell as Shell
import Language.Docker.Syntax (Instruction (..), RunArgs (..))

rule :: Rule Shell.ParsedShell
rule :: Rule ParsedShell
rule = RuleCode
-> DLSeverity
-> Text
-> (Instruction ParsedShell -> Bool)
-> Rule ParsedShell
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
"DL3001"
    severity :: DLSeverity
severity = DLSeverity
DLInfoC
    message :: Text
message =
      Text
"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 :: Instruction ParsedShell -> Bool
check (Run (RunArgs Arguments ParsedShell
args RunFlags
_)) = (ParsedShell -> Bool) -> Arguments ParsedShell -> Bool
forall a b. (a -> b) -> Arguments a -> b
foldArguments ParsedShell -> Bool
hasInvalid Arguments ParsedShell
args
    check Instruction ParsedShell
_ = Bool
True

    hasInvalid :: ParsedShell -> Bool
hasInvalid ParsedShell
args = [Text] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text
arg | Text
arg <- ParsedShell -> [Text]
Shell.findCommandNames ParsedShell
args, Text -> Set Text -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member Text
arg Set Text
invalidCmds]
    invalidCmds :: Set Text
invalidCmds =
      [Text] -> Set Text
forall a. Ord a => [a] -> Set a
Set.fromList
        [ Text
"free",
          Text
"kill",
          Text
"mount",
          Text
"ps",
          Text
"service",
          Text
"shutdown",
          Text
"ssh",
          Text
"top",
          Text
"vim"
        ]
{-# INLINEABLE rule #-}