module Hadolint.Rule.DL3055 (rule) where

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


rule :: LabelSchema -> Rule args
rule :: forall args. LabelSchema -> Rule args
rule LabelSchema
labelschema = forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$
  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall args. Text -> Rule args
labelIsNotGitHashRule (forall k a. Map k a -> [k]
Map.keys (forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter (forall a. Eq a => a -> a -> Bool
== LabelType
GitHash) LabelSchema
labelschema))
{-# INLINEABLE rule #-}

labelIsNotGitHashRule :: LabelName -> Rule args
labelIsNotGitHashRule :: forall args. Text -> Rule args
labelIsNotGitHashRule Text
label = forall args.
RuleCode
-> DLSeverity -> Text -> (Instruction args -> Bool) -> Rule args
simpleRule RuleCode
code DLSeverity
severity Text
message forall {args}. Instruction args -> Bool
check
  where
    code :: RuleCode
code = RuleCode
"DL3055"
    severity :: DLSeverity
severity = DLSeverity
DLWarningC
    message :: Text
message = Text
"Label `" forall a. Semigroup a => a -> a -> a
<> Text
label forall a. Semigroup a => a -> a -> a
<> Text
"` is not a valid git hash."
    check :: Instruction args -> Bool
check (Label Pairs
ls) = forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall a b. (a -> b) -> a -> b
$ Text -> Pairs -> Pairs
getBadHashLabels Text
label Pairs
ls
    check Instruction args
_ = Bool
True

getBadHashLabels :: LabelName -> Pairs -> Pairs
getBadHashLabels :: Text -> Pairs -> Pairs
getBadHashLabels Text
lbl Pairs
prs = [(Text
l, Text
v) | (Text
l, Text
v) <- Pairs
prs, Text
l forall a. Eq a => a -> a -> Bool
== Text
lbl, Text -> Bool
isBadHash Text
v]

isBadHash :: Text.Text -> Bool
isBadHash :: Text -> Bool
isBadHash Text
h = (Char -> Bool) -> Text -> Bool
Text.any (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` String
validHash) Text
h
            Bool -> Bool -> Bool
|| (Text -> Int
Text.length Text
h forall a. Eq a => a -> a -> Bool
/= Int
40 Bool -> Bool -> Bool
&& Text -> Int
Text.length Text
h forall a. Eq a => a -> a -> Bool
/= Int
7)

validHash :: String
validHash :: String
validHash = [Char
'0'..Char
'9'] forall a. [a] -> [a] -> [a]
++ [Char
'a'..Char
'f']