hadolint-2.12.0: Dockerfile Linter JavaScript API
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hadolint.Rule

Synopsis

Documentation

(|>) :: a -> (a -> b) -> b infixl 0 Source #

data DLSeverity Source #

Instances

Instances details
FromYAML DLSeverity Source # 
Instance details

Defined in Hadolint.Rule

Monoid DLSeverity Source # 
Instance details

Defined in Hadolint.Rule

Semigroup DLSeverity Source # 
Instance details

Defined in Hadolint.Rule

Generic DLSeverity Source # 
Instance details

Defined in Hadolint.Rule

Associated Types

type Rep DLSeverity :: Type -> Type #

Show DLSeverity Source # 
Instance details

Defined in Hadolint.Rule

Default DLSeverity Source # 
Instance details

Defined in Hadolint.Rule

Methods

def :: DLSeverity #

NFData DLSeverity Source # 
Instance details

Defined in Hadolint.Rule

Methods

rnf :: DLSeverity -> () #

Eq DLSeverity Source # 
Instance details

Defined in Hadolint.Rule

Ord DLSeverity Source # 
Instance details

Defined in Hadolint.Rule

Pretty DLSeverity Source # 
Instance details

Defined in Hadolint.Rule

Methods

pretty :: DLSeverity -> Doc ann #

prettyList :: [DLSeverity] -> Doc ann #

type Rep DLSeverity Source # 
Instance details

Defined in Hadolint.Rule

type Rep DLSeverity = D1 ('MetaData "DLSeverity" "Hadolint.Rule" "hadolint-2.12.0-H3bsWJqlgXKFKqSMzbhywi" 'False) ((C1 ('MetaCons "DLErrorC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DLWarningC" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DLInfoC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DLStyleC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DLIgnoreC" 'PrefixI 'False) (U1 :: Type -> Type))))

newtype RuleCode Source #

Constructors

RuleCode 

Fields

Instances

Instances details
IsString RuleCode Source # 
Instance details

Defined in Hadolint.Rule

Show RuleCode Source # 
Instance details

Defined in Hadolint.Rule

Eq RuleCode Source # 
Instance details

Defined in Hadolint.Rule

Ord RuleCode Source # 
Instance details

Defined in Hadolint.Rule

Pretty RuleCode Source # 
Instance details

Defined in Hadolint.Rule

Methods

pretty :: RuleCode -> Doc ann #

prettyList :: [RuleCode] -> Doc ann #

data State a Source #

Constructors

State 

Fields

Instances

Instances details
Show a => Show (State a) Source # 
Instance details

Defined in Hadolint.Rule

Methods

showsPrec :: Int -> State a -> ShowS #

show :: State a -> String #

showList :: [State a] -> ShowS #

data LabelType Source #

Constructors

Email 
GitHash 
RawText 
Rfc3339 
SemVer 
Spdx 
Url 

Instances

Instances details
FromYAML LabelType Source # 
Instance details

Defined in Hadolint.Rule

Show LabelType Source # 
Instance details

Defined in Hadolint.Rule

Eq LabelType Source # 
Instance details

Defined in Hadolint.Rule

Pretty LabelType Source # 
Instance details

Defined in Hadolint.Rule

Methods

pretty :: LabelType -> Doc ann #

prettyList :: [LabelType] -> Doc ann #

withLineNumber :: (Linenumber -> t1 -> Instruction args -> t2) -> t1 -> InstructionPos args -> t2 Source #

modify :: (a -> a) -> State a -> State a Source #

replaceWith :: a -> State a -> State a Source #

simpleRule Source #

Arguments

:: RuleCode

rule code

-> DLSeverity

severity for the rule

-> Text

failure message for the rule

-> (Instruction args -> Bool)

step calculation for the rule. Returns True or False for each line in the dockerfile depending on its validity.

-> Rule args 

A simple rule that can be implemented in terms of returning True or False for each instruction If you need to calculate some state to decide upon past information, use customRule

customRule :: (Linenumber -> State a -> Instruction args -> State a) -> State a -> Rule args Source #

A rule that accumulates a State a. The state contains the collection of failed lines and a custom data type that can be used to track properties for the rule. Each step always returns the new State, which offers the ability to both accumulate properties and mark failures for every given instruction.

veryCustomRule Source #

Arguments

:: (Linenumber -> State a -> Instruction args -> State a)

step calculation for the rule. Called for each instruction in the docker file it must return the state after being modified by the rule

-> State a

initial state

-> (State a -> Failures)

done callaback. It is passed the final accumulated state and it should return all failures found by the rule

-> Rule args 

Similarly to customRule, it returns a State a for each step, but it has the ability to run a done callback as the last step of the rule. The done callback can be used to transform the state and mark failures for any arbitrary line in the input. This helper is meant for rules that need to do lookahead. Instead of looking ahead, the state should store the facts and make a decision about them once the input is finished.

foldArguments :: (a -> b) -> Arguments a -> b Source #

aliasMustBe :: (Text -> Bool) -> Instruction a -> Bool Source #

Returns the result of running the check function on the image alias name, if the passed instruction is a FROM instruction with a stage alias. Otherwise, returns True.

onbuild :: Rule args -> Rule args Source #

Unwraps ONBUILD instructions and applies the rule to the content