module Hadolint.Rule.DL3021 (rule) where

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

rule :: Rule args
rule :: Rule args
rule = RuleCode
-> DLSeverity -> Text -> (Instruction args -> Bool) -> Rule args
forall args.
RuleCode
-> DLSeverity -> Text -> (Instruction args -> Bool) -> Rule args
simpleRule RuleCode
code DLSeverity
severity Text
message Instruction args -> Bool
forall args. Instruction args -> Bool
check
  where
    code :: RuleCode
code = RuleCode
"DL3021"
    severity :: DLSeverity
severity = DLSeverity
DLErrorC
    message :: Text
message = Text
"COPY with more than 2 arguments requires the last argument to end with /"

    check :: Instruction args -> Bool
check (Copy (CopyArgs NonEmpty SourcePath
sources TargetPath
t Chown
_ Chmod
_ CopySource
_))
      | NonEmpty SourcePath -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length NonEmpty SourcePath
sources Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 = TargetPath -> Bool
endsWithSlash TargetPath
t
      | Bool
otherwise = Bool
True
    check Instruction args
_ = Bool
True
{-# INLINEABLE rule #-}

endsWithSlash :: TargetPath -> Bool
endsWithSlash :: TargetPath -> Bool
endsWithSlash (TargetPath Text
t) =
  Bool -> Bool
not (Text -> Bool
Text.null Text
t) Bool -> Bool -> Bool
&& (Text -> Char
Text.last (Text -> Char) -> (Text -> Text) -> Text -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
dropQuotes) Text
t Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'/'