Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- (|>) :: a -> (a -> b) -> b
- data DLSeverity
- withSeverity :: (DLSeverity -> Parser a) -> Node Pos -> Parser a
- readEitherSeverity :: Text -> Either String DLSeverity
- readMaybeSeverity :: Text -> Maybe DLSeverity
- newtype RuleCode = RuleCode {
- unRuleCode :: Text
- data CheckFailure = CheckFailure {
- code :: RuleCode
- severity :: DLSeverity
- message :: Text
- line :: Linenumber
- type Failures = Seq CheckFailure
- data State a = State {}
- type LabelName = Text
- data LabelType
- readEitherLabelType :: Text -> Either Text LabelType
- withLabelType :: (LabelType -> Parser a) -> Node Pos -> Parser a
- type LabelSchema = Map LabelName LabelType
- withLineNumber :: (Linenumber -> t1 -> Instruction args -> t2) -> t1 -> InstructionPos args -> t2
- addFail :: CheckFailure -> State a -> State a
- emptyState :: a -> State a
- simpleState :: State ()
- modify :: (a -> a) -> State a -> State a
- replaceWith :: a -> State a -> State a
- type Rule args = Fold (InstructionPos args) Failures
- simpleRule :: RuleCode -> DLSeverity -> Text -> (Instruction args -> Bool) -> Rule args
- customRule :: (Linenumber -> State a -> Instruction args -> State a) -> State a -> Rule args
- veryCustomRule :: (Linenumber -> State a -> Instruction args -> State a) -> State a -> (State a -> Failures) -> Rule args
- foldArguments :: (a -> b) -> Arguments a -> b
- aliasMustBe :: (Text -> Bool) -> Instruction a -> Bool
- archiveFileFormatExtensions :: [Text]
- dropQuotes :: Text -> Text
- onbuild :: Rule args -> Rule args
Documentation
data DLSeverity Source #
Instances
withSeverity :: (DLSeverity -> Parser a) -> Node Pos -> Parser a Source #
readMaybeSeverity :: Text -> Maybe DLSeverity Source #
data CheckFailure Source #
CheckFailure | |
|
Instances
Show CheckFailure Source # | |
Defined in Hadolint.Rule showsPrec :: Int -> CheckFailure -> ShowS # show :: CheckFailure -> String # showList :: [CheckFailure] -> ShowS # | |
Eq CheckFailure Source # | |
Defined in Hadolint.Rule (==) :: CheckFailure -> CheckFailure -> Bool # (/=) :: CheckFailure -> CheckFailure -> Bool # | |
Ord CheckFailure Source # | |
Defined in Hadolint.Rule compare :: CheckFailure -> CheckFailure -> Ordering # (<) :: CheckFailure -> CheckFailure -> Bool # (<=) :: CheckFailure -> CheckFailure -> Bool # (>) :: CheckFailure -> CheckFailure -> Bool # (>=) :: CheckFailure -> CheckFailure -> Bool # max :: CheckFailure -> CheckFailure -> CheckFailure # min :: CheckFailure -> CheckFailure -> CheckFailure # |
type Failures = Seq CheckFailure Source #
withLineNumber :: (Linenumber -> t1 -> Instruction args -> t2) -> t1 -> InstructionPos args -> t2 Source #
emptyState :: a -> State a Source #
simpleState :: State () Source #
replaceWith :: a -> State a -> State a Source #
:: 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.
:: (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.
dropQuotes :: Text -> Text Source #