module Hadolint.Rule.DL1001 (rule) where

import Hadolint.Pragma
import Hadolint.Rule
import Hadolint.Shell (ParsedShell)
import Language.Docker.Syntax


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
forall args. Instruction args -> Bool
check
  where
    code :: RuleCode
code = RuleCode
"DL1001"
    severity :: DLSeverity
severity = DLSeverity
DLIgnoreC
    message :: Text
message = Text
"Please refrain from using inline igore pragmas \
              \ `# hadolint ignore=DLxxxx`."
    check :: Instruction args -> Bool
check (Comment Text
com) =
      case Text -> Maybe [Text]
parseIgnorePragma Text
com of
        Just [Text]
_ -> Bool
False
        Maybe [Text]
_ -> Bool
True
    check Instruction args
_ = Bool
True
{-# INLINEABLE rule #-}