module Hadolint.Rule.DL3000 (rule) where

import qualified Data.Char as Char
import qualified Data.Text as Text
import Hadolint.Rule
import Language.Docker.Syntax (Instruction (..))

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
"DL3000"
    severity :: DLSeverity
severity = DLSeverity
DLErrorC
    message :: Text
message = Text
"Use absolute WORKDIR"
    check :: Instruction args -> Bool
check (Workdir Text
loc)
      | Text
"$" Text -> Text -> Bool
`Text.isPrefixOf` (Char -> Bool) -> Text -> Text
Text.dropAround Char -> Bool
dropQuotes Text
loc = Bool
True
      | Text
"/" Text -> Text -> Bool
`Text.isPrefixOf` (Char -> Bool) -> Text -> Text
Text.dropAround Char -> Bool
dropQuotes Text
loc = Bool
True
      | Text -> Bool
isWindowsAbsolute ((Char -> Bool) -> Text -> Text
Text.dropAround Char -> Bool
dropQuotes Text
loc) = Bool
True
      | Bool
otherwise = Bool
False
    check Instruction args
_ = Bool
True
{-# INLINEABLE rule #-}

dropQuotes :: Char -> Bool
dropQuotes :: Char -> Bool
dropQuotes Char
chr
  | Char
chr Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\"' = Bool
True
  | Char
chr Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\'' = Bool
True
  | Bool
otherwise = Bool
False

isWindowsAbsolute :: Text.Text -> Bool
isWindowsAbsolute :: Text -> Bool
isWindowsAbsolute Text
path
  | Char -> Bool
Char.isLetter (Text -> Int -> Char
Text.index Text
path Int
0) Bool -> Bool -> Bool
&& (Char
':' Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Int -> Char
Text.index Text
path Int
1) = Bool
True
  | Bool
otherwise = Bool
False