module Hadolint.Rule.DL3019 (rule) where

import Hadolint.Rule
import Hadolint.Shell (ParsedShell)
import Language.Docker.Syntax
import qualified Data.Set as Set
import qualified Data.Text as Text
import qualified Hadolint.Shell as Shell


rule :: Rule ParsedShell
rule :: Rule ParsedShell
rule = Rule ParsedShell
dl3019 Rule ParsedShell -> Rule ParsedShell -> Rule ParsedShell
forall a. Semigroup a => a -> a -> a
<> Rule ParsedShell -> Rule ParsedShell
forall args. Rule args -> Rule args
onbuild Rule ParsedShell
dl3019
{-# INLINEABLE rule #-}

dl3019 :: Rule ParsedShell
dl3019 :: Rule ParsedShell
dl3019 = 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
check
  where
    code :: RuleCode
code = RuleCode
"DL3019"
    severity :: DLSeverity
severity = DLSeverity
DLInfoC
    message :: Text
message =
      Text
"Use the `--no-cache` switch to avoid the need to use `--update` and \
      \remove `/var/cache/apk/*` when done installing packages"
    check :: Instruction ParsedShell -> Bool
check (Run (RunArgs Arguments ParsedShell
args RunFlags
flags)) = RunFlags -> Bool
hasCacheMount RunFlags
flags
      Bool -> Bool -> Bool
|| (ParsedShell -> Bool) -> Arguments ParsedShell -> Bool
forall a b. (a -> b) -> Arguments a -> b
foldArguments ((Command -> Bool) -> ParsedShell -> Bool
Shell.noCommands Command -> Bool
forgotCacheOption) Arguments ParsedShell
args
    check Instruction ParsedShell
_ = Bool
True
{-# INLINEABLE dl3019 #-}

hasCacheMount :: RunFlags -> Bool
hasCacheMount :: RunFlags -> Bool
hasCacheMount RunFlags { Set RunMount
$sel:mount:RunFlags :: RunFlags -> Set RunMount
mount :: Set RunMount
mount } =
  Bool -> Bool
not (Set RunMount -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (Set RunMount -> Bool) -> Set RunMount -> Bool
forall a b. (a -> b) -> a -> b
$ (RunMount -> Bool) -> Set RunMount -> Set RunMount
forall a. (a -> Bool) -> Set a -> Set a
Set.filter RunMount -> Bool
isCacheMount Set RunMount
mount)

isCacheMount :: RunMount -> Bool
isCacheMount :: RunMount -> Bool
isCacheMount (CacheMount CacheOpts { $sel:cTarget:CacheOpts :: CacheOpts -> TargetPath
cTarget = TargetPath
t })= TargetPath -> Bool
isVarCacheApk TargetPath
t
isCacheMount RunMount
_ = Bool
False

isVarCacheApk :: TargetPath -> Bool
isVarCacheApk :: TargetPath -> Bool
isVarCacheApk TargetPath { $sel:unTargetPath:TargetPath :: TargetPath -> Text
unTargetPath = Text
p }
  = (Char -> Bool) -> Text -> Text
Text.dropWhileEnd (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'/') Text
p Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"/var/cache/apk"

forgotCacheOption :: Shell.Command -> Bool
forgotCacheOption :: Command -> Bool
forgotCacheOption Command
cmd = Text -> [Text] -> Command -> Bool
Shell.cmdHasArgs Text
"apk" [Text
"add"] Command
cmd
  Bool -> Bool -> Bool
&& Bool -> Bool
not (Text -> Command -> Bool
Shell.hasFlag Text
"no-cache" Command
cmd)