module Hadolint.Rule.DL3028 (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 = Rule ParsedShell
dl3028 forall a. Semigroup a => a -> a -> a
<> forall args. Rule args -> Rule args
onbuild Rule ParsedShell
dl3028
{-# INLINEABLE rule #-}

dl3028 :: Rule ParsedShell
dl3028 :: Rule ParsedShell
dl3028 = 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
"DL3028"
    severity :: DLSeverity
severity = DLSeverity
DLWarningC
    message :: Text
message =
      Text
"Pin versions in gem install. Instead of `gem install <gem>` use `gem \
      \install <gem>:<version>`"

    check :: Instruction ParsedShell -> Bool
check (Run (RunArgs Arguments ParsedShell
args RunFlags
_)) = forall a b. (a -> b) -> Arguments a -> b
foldArguments (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Text -> Bool
versionFixed forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsedShell -> [Text]
gems) Arguments ParsedShell
args
    check Instruction ParsedShell
_ = Bool
True

    versionFixed :: Text -> Bool
versionFixed Text
package = Text
":" Text -> Text -> Bool
`Text.isInfixOf` Text
package
{-# INLINEABLE dl3028 #-}

gems :: Shell.ParsedShell -> [Text.Text]
gems :: ParsedShell -> [Text]
gems ParsedShell
shell =
  [ Text
arg
    | Command
cmd <- ParsedShell -> [Command]
Shell.presentCommands ParsedShell
shell,
      Text -> [Text] -> Command -> Bool
Shell.cmdHasArgs Text
"gem" [Text
"install", Text
"i"] Command
cmd,
      Bool -> Bool
not (Text -> [Text] -> Command -> Bool
Shell.cmdHasArgs Text
"gem" [Text
"-v"] Command
cmd),
      Bool -> Bool
not (Text -> [Text] -> Command -> Bool
Shell.cmdHasArgs Text
"gem" [Text
"--version"] Command
cmd),
      Bool -> Bool
not (Text -> Text -> Command -> Bool
Shell.cmdHasPrefixArg Text
"gem" Text
"--version=" Command
cmd),
      Text
arg <- Command -> [Text]
Shell.getArgsNoFlags Command
cmd,
      Text
arg forall a. Eq a => a -> a -> Bool
/= Text
"install",
      Text
arg forall a. Eq a => a -> a -> Bool
/= Text
"i",
      Text
arg forall a. Eq a => a -> a -> Bool
/= Text
"--"
  ]