module Hadolint.Rule.DL3046 (rule) where

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

rule :: Rule 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
"DL3046"
    severity :: DLSeverity
severity = DLSeverity
DLWarningC
    message :: Text
message = Text
"`useradd` without flag `-l` and high UID will result in excessively large Image."

    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 ((Command -> Bool) -> ParsedShell -> Bool
Shell.noCommands Command -> Bool
forgotFlagL) Arguments ParsedShell
args
    check Instruction ParsedShell
_ = Bool
True

    forgotFlagL :: Command -> Bool
forgotFlagL Command
cmd = Command -> Bool
isUseradd Command
cmd Bool -> Bool -> Bool
&& (Bool -> Bool
not (Command -> Bool
hasLFlag Command
cmd) Bool -> Bool -> Bool
&& Command -> Bool
hasUFlag Command
cmd Bool -> Bool -> Bool
&& Command -> Bool
hasLongUID Command
cmd)
    isUseradd :: Command -> Bool
isUseradd (Shell.Command Text
name [CmdPart]
_ [CmdPart]
_) = Text
name Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"useradd"
    hasLFlag :: Command -> Bool
hasLFlag = [Text] -> Command -> Bool
Shell.hasAnyFlag [Text
"l", Text
"no-log-init"]
    hasUFlag :: Command -> Bool
hasUFlag = [Text] -> Command -> Bool
Shell.hasAnyFlag [Text
"u", Text
"uid"]
    hasLongUID :: Command -> Bool
hasLongUID Command
cmd = (Text -> Bool) -> [Text] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
5) (Int -> Bool) -> (Text -> Int) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Int
Text.length) (Text -> Command -> [Text]
Shell.getFlagArg Text
"u" Command
cmd)
{-# INLINEABLE rule #-}