module Hadolint.Rule.DL3029 (rule) where

import qualified Data.Text as Text
import Hadolint.Rule
import Language.Docker.Syntax

rule :: Rule args
rule :: forall args. Rule args
rule = forall args.
RuleCode
-> DLSeverity -> Text -> (Instruction args -> Bool) -> Rule args
simpleRule RuleCode
code DLSeverity
severity Text
message forall {args}. Instruction args -> Bool
check
  where
    code :: RuleCode
code = RuleCode
"DL3029"
    severity :: DLSeverity
severity = DLSeverity
DLWarningC
    message :: Text
message = Text
"Do not use --platform flag with FROM"

    check :: Instruction args -> Bool
check (From BaseImage {$sel:platform:BaseImage :: BaseImage -> Maybe Text
platform = Just Text
p}) = Text
"BUILDPLATFORM" Text -> Text -> Bool
`Text.isInfixOf` Text
p Bool -> Bool -> Bool
|| Text
"TARGETPLATFORM" Text -> Text -> Bool
`Text.isInfixOf` Text
p
    check Instruction args
_ = Bool
True
{-# INLINEABLE rule #-}