module Hadolint.Rule.DL3010 (rule) where

import Data.Foldable (toList)
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
"DL3010"
    severity :: DLSeverity
severity = DLSeverity
DLInfoC
    message :: Text
message = Text
"Use ADD for extracting archives into an image"
    check :: Instruction args -> Bool
check (Copy (CopyArgs NonEmpty SourcePath
srcs TargetPath
_ Chown
_ CopySource
_)) =
      [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and
        [ Bool -> Bool
not (Text
format Text -> Text -> Bool
`Text.isSuffixOf` Text
src)
          | SourcePath Text
src <- NonEmpty SourcePath -> [SourcePath]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NonEmpty SourcePath
srcs,
            Text
format <- [Text]
archiveFormats
        ]
    check Instruction args
_ = Bool
True
    archiveFormats :: [Text]
archiveFormats =
      [ Text
".tar",
        Text
".tar.bz2",
        Text
".tb2",
        Text
".tbz",
        Text
".tbz2",
        Text
".tar.gz",
        Text
".tgz",
        Text
".tpz",
        Text
".tar.lz",
        Text
".tar.lzma",
        Text
".tlz",
        Text
".tar.xz",
        Text
".txz",
        Text
".tar.Z",
        Text
".tZ"
      ]
{-# INLINEABLE rule #-}