module Hadolint.Process (run, RulesConfig (..)) where

import qualified Control.Foldl as Foldl
import qualified Data.IntMap.Strict as SMap
import qualified Data.Sequence as Seq
import qualified Data.Set as Set
import qualified Data.Text as Text
import qualified Hadolint.Ignore
import Hadolint.Rule (CheckFailure (..), Failures, Rule, RuleCode)
import qualified Hadolint.Rule as Rule
import qualified Hadolint.Rule.DL3000
import qualified Hadolint.Rule.DL3001
import qualified Hadolint.Rule.DL3002
import qualified Hadolint.Rule.DL3003
import qualified Hadolint.Rule.DL3004
import qualified Hadolint.Rule.DL3005
import qualified Hadolint.Rule.DL3006
import qualified Hadolint.Rule.DL3007
import qualified Hadolint.Rule.DL3008
import qualified Hadolint.Rule.DL3009
import qualified Hadolint.Rule.DL3010
import qualified Hadolint.Rule.DL3011
import qualified Hadolint.Rule.DL3012
import qualified Hadolint.Rule.DL3013
import qualified Hadolint.Rule.DL3014
import qualified Hadolint.Rule.DL3015
import qualified Hadolint.Rule.DL3016
import qualified Hadolint.Rule.DL3018
import qualified Hadolint.Rule.DL3019
import qualified Hadolint.Rule.DL3020
import qualified Hadolint.Rule.DL3021
import qualified Hadolint.Rule.DL3022
import qualified Hadolint.Rule.DL3023
import qualified Hadolint.Rule.DL3024
import qualified Hadolint.Rule.DL3025
import qualified Hadolint.Rule.DL3026
import qualified Hadolint.Rule.DL3027
import qualified Hadolint.Rule.DL3028
import qualified Hadolint.Rule.DL3029
import qualified Hadolint.Rule.DL3030
import qualified Hadolint.Rule.DL3032
import qualified Hadolint.Rule.DL3033
import qualified Hadolint.Rule.DL3034
import qualified Hadolint.Rule.DL3035
import qualified Hadolint.Rule.DL3036
import qualified Hadolint.Rule.DL3037
import qualified Hadolint.Rule.DL3038
import qualified Hadolint.Rule.DL3040
import qualified Hadolint.Rule.DL3041
import qualified Hadolint.Rule.DL3042
import qualified Hadolint.Rule.DL3043
import qualified Hadolint.Rule.DL3044
import qualified Hadolint.Rule.DL3045
import qualified Hadolint.Rule.DL3046
import qualified Hadolint.Rule.DL3047
import qualified Hadolint.Rule.DL3048
import qualified Hadolint.Rule.DL3049
import qualified Hadolint.Rule.DL3050
import qualified Hadolint.Rule.DL3051
import qualified Hadolint.Rule.DL3052
import qualified Hadolint.Rule.DL3053
import qualified Hadolint.Rule.DL3054
import qualified Hadolint.Rule.DL3055
import qualified Hadolint.Rule.DL3056
import qualified Hadolint.Rule.DL3057
import qualified Hadolint.Rule.DL3058
import qualified Hadolint.Rule.DL3059
import qualified Hadolint.Rule.DL3060
import qualified Hadolint.Rule.DL4000
import qualified Hadolint.Rule.DL4001
import qualified Hadolint.Rule.DL4003
import qualified Hadolint.Rule.DL4004
import qualified Hadolint.Rule.DL4005
import qualified Hadolint.Rule.DL4006
import qualified Hadolint.Rule.Shellcheck
import qualified Hadolint.Shell as Shell
import Language.Docker.Syntax


-- | Contains the required parameters for optional rules
data RulesConfig = RulesConfig
  { -- | The docker registries that are allowed in FROM
    RulesConfig -> Set Registry
allowedRegistries :: Set.Set Registry,
    RulesConfig -> LabelSchema
labelSchema :: Rule.LabelSchema,
    RulesConfig -> Bool
strictLabels :: Bool
  }
  deriving (Int -> RulesConfig -> ShowS
[RulesConfig] -> ShowS
RulesConfig -> String
(Int -> RulesConfig -> ShowS)
-> (RulesConfig -> String)
-> ([RulesConfig] -> ShowS)
-> Show RulesConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RulesConfig] -> ShowS
$cshowList :: [RulesConfig] -> ShowS
show :: RulesConfig -> String
$cshow :: RulesConfig -> String
showsPrec :: Int -> RulesConfig -> ShowS
$cshowsPrec :: Int -> RulesConfig -> ShowS
Show, RulesConfig -> RulesConfig -> Bool
(RulesConfig -> RulesConfig -> Bool)
-> (RulesConfig -> RulesConfig -> Bool) -> Eq RulesConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RulesConfig -> RulesConfig -> Bool
$c/= :: RulesConfig -> RulesConfig -> Bool
== :: RulesConfig -> RulesConfig -> Bool
$c== :: RulesConfig -> RulesConfig -> Bool
Eq)

instance Semigroup RulesConfig where
  RulesConfig Set Registry
a1 LabelSchema
a2 Bool
a3 <> :: RulesConfig -> RulesConfig -> RulesConfig
<> RulesConfig Set Registry
b1 LabelSchema
b2 Bool
b3 =
    Set Registry -> LabelSchema -> Bool -> RulesConfig
RulesConfig
      (Set Registry
a1 Set Registry -> Set Registry -> Set Registry
forall a. Semigroup a => a -> a -> a
<> Set Registry
b1)
      (LabelSchema
a2 LabelSchema -> LabelSchema -> LabelSchema
forall a. Semigroup a => a -> a -> a
<> LabelSchema
b2)
      (Bool
a3 Bool -> Bool -> Bool
|| Bool
b3)

instance Monoid RulesConfig where
  mempty :: RulesConfig
mempty = Set Registry -> LabelSchema -> Bool -> RulesConfig
RulesConfig Set Registry
forall a. Monoid a => a
mempty LabelSchema
forall a. Monoid a => a
mempty Bool
False

data AnalisisResult = AnalisisResult
  { -- | The set of ignored rules per line
    AnalisisResult -> IntMap (Set RuleCode)
ignored :: SMap.IntMap (Set.Set RuleCode),
    -- | A set of failures collected for reach rule
    AnalisisResult -> Failures
failed :: Failures
  }

run :: RulesConfig -> [InstructionPos Text.Text] -> Failures
run :: RulesConfig -> [InstructionPos Text] -> Failures
run RulesConfig
config [InstructionPos Text]
dockerfile = (CheckFailure -> Bool) -> Failures -> Failures
forall a. (a -> Bool) -> Seq a -> Seq a
Seq.filter CheckFailure -> Bool
shouldKeep Failures
failed
  where
    AnalisisResult {IntMap (Set RuleCode)
Failures
ignored :: IntMap (Set RuleCode)
failed :: Failures
failed :: AnalisisResult -> Failures
ignored :: AnalisisResult -> IntMap (Set RuleCode)
..} = Fold (InstructionPos Text) AnalisisResult
-> [InstructionPos Text] -> AnalisisResult
forall (f :: * -> *) a b. Foldable f => Fold a b -> f a -> b
Foldl.fold (RulesConfig -> Fold (InstructionPos Text) AnalisisResult
analyze RulesConfig
config) [InstructionPos Text]
dockerfile

    shouldKeep :: CheckFailure -> Bool
shouldKeep CheckFailure {Int
line :: CheckFailure -> Int
line :: Int
line, RuleCode
code :: CheckFailure -> RuleCode
code :: RuleCode
code} =
      Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
/= do
        Set RuleCode
ignoreList <- Int -> IntMap (Set RuleCode) -> Maybe (Set RuleCode)
forall a. Int -> IntMap a -> Maybe a
SMap.lookup Int
line IntMap (Set RuleCode)
ignored
        Bool -> Maybe Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Maybe Bool) -> Bool -> Maybe Bool
forall a b. (a -> b) -> a -> b
$ RuleCode
code RuleCode -> Set RuleCode -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set RuleCode
ignoreList

analyze :: RulesConfig -> Foldl.Fold (InstructionPos Text.Text) AnalisisResult
analyze :: RulesConfig -> Fold (InstructionPos Text) AnalisisResult
analyze RulesConfig
config =
  IntMap (Set RuleCode) -> Failures -> AnalisisResult
AnalisisResult
    (IntMap (Set RuleCode) -> Failures -> AnalisisResult)
-> Fold (InstructionPos Text) (IntMap (Set RuleCode))
-> Fold (InstructionPos Text) (Failures -> AnalisisResult)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Fold (InstructionPos Text) (IntMap (Set RuleCode))
Hadolint.Ignore.ignored
    Fold (InstructionPos Text) (Failures -> AnalisisResult)
-> Fold (InstructionPos Text) Failures
-> Fold (InstructionPos Text) AnalisisResult
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (InstructionPos Text -> InstructionPos ParsedShell)
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos Text) Failures
forall a b r. (a -> b) -> Fold b r -> Fold a r
Foldl.premap InstructionPos Text -> InstructionPos ParsedShell
parseShell (RulesConfig -> Fold (InstructionPos ParsedShell) Failures
failures RulesConfig
config Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> RulesConfig -> Fold (InstructionPos ParsedShell) Failures
onBuildFailures RulesConfig
config)

parseShell :: InstructionPos Text.Text -> InstructionPos Shell.ParsedShell
parseShell :: InstructionPos Text -> InstructionPos ParsedShell
parseShell = (Text -> ParsedShell)
-> InstructionPos Text -> InstructionPos ParsedShell
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ParsedShell
Shell.parseShell

onBuildFailures :: RulesConfig -> Rule Shell.ParsedShell
onBuildFailures :: RulesConfig -> Fold (InstructionPos ParsedShell) Failures
onBuildFailures RulesConfig
config =
  (InstructionPos ParsedShell -> Bool)
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a r. (a -> Bool) -> Fold a r -> Fold a r
Foldl.prefilter
    InstructionPos ParsedShell -> Bool
forall args. InstructionPos args -> Bool
isOnBuild
    ((InstructionPos ParsedShell -> InstructionPos ParsedShell)
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a b r. (a -> b) -> Fold b r -> Fold a r
Foldl.premap InstructionPos ParsedShell -> InstructionPos ParsedShell
forall args. InstructionPos args -> InstructionPos args
unwrapOnbuild (RulesConfig -> Fold (InstructionPos ParsedShell) Failures
failures RulesConfig
config))
  where
    isOnBuild :: InstructionPos args -> Bool
isOnBuild InstructionPos {$sel:instruction:InstructionPos :: forall args. InstructionPos args -> Instruction args
instruction = OnBuild {}} = Bool
True
    isOnBuild InstructionPos args
_ = Bool
False

    unwrapOnbuild :: InstructionPos args -> InstructionPos args
unwrapOnbuild inst :: InstructionPos args
inst@InstructionPos {$sel:instruction:InstructionPos :: forall args. InstructionPos args -> Instruction args
instruction = OnBuild Instruction args
i} = InstructionPos args
inst {$sel:instruction:InstructionPos :: Instruction args
instruction = Instruction args
i}
    unwrapOnbuild InstructionPos args
inst = InstructionPos args
inst

failures :: RulesConfig -> Rule Shell.ParsedShell
failures :: RulesConfig -> Fold (InstructionPos ParsedShell) Failures
failures RulesConfig {Set Registry
allowedRegistries :: Set Registry
allowedRegistries :: RulesConfig -> Set Registry
allowedRegistries, LabelSchema
labelSchema :: LabelSchema
labelSchema :: RulesConfig -> LabelSchema
labelSchema, Bool
strictLabels :: Bool
strictLabels :: RulesConfig -> Bool
strictLabels} =
  Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL3000.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3001.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL3002.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3003.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3004.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3005.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL3006.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL3007.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3008.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3009.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL3010.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL3011.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL3012.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3013.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3014.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3015.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3016.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3018.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3019.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL3020.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL3021.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL3022.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL3023.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL3024.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL3025.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Set Registry -> Fold (InstructionPos ParsedShell) Failures
forall args. Set Registry -> Rule args
Hadolint.Rule.DL3026.rule Set Registry
allowedRegistries
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3027.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3028.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL3029.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3030.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3032.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3033.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3034.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3035.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3036.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3037.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3038.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3040.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3041.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3042.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL3043.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL3044.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL3045.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3046.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3047.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL3048.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> LabelSchema -> Fold (InstructionPos ParsedShell) Failures
forall args. LabelSchema -> Rule args
Hadolint.Rule.DL3049.rule LabelSchema
labelSchema
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> LabelSchema -> Bool -> Fold (InstructionPos ParsedShell) Failures
forall args. LabelSchema -> Bool -> Rule args
Hadolint.Rule.DL3050.rule LabelSchema
labelSchema Bool
strictLabels
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> LabelSchema -> Fold (InstructionPos ParsedShell) Failures
forall args. LabelSchema -> Rule args
Hadolint.Rule.DL3051.rule LabelSchema
labelSchema
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> LabelSchema -> Fold (InstructionPos ParsedShell) Failures
forall args. LabelSchema -> Rule args
Hadolint.Rule.DL3052.rule LabelSchema
labelSchema
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> LabelSchema -> Fold (InstructionPos ParsedShell) Failures
forall args. LabelSchema -> Rule args
Hadolint.Rule.DL3053.rule LabelSchema
labelSchema
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> LabelSchema -> Fold (InstructionPos ParsedShell) Failures
forall args. LabelSchema -> Rule args
Hadolint.Rule.DL3054.rule LabelSchema
labelSchema
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> LabelSchema -> Fold (InstructionPos ParsedShell) Failures
forall args. LabelSchema -> Rule args
Hadolint.Rule.DL3055.rule LabelSchema
labelSchema
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> LabelSchema -> Fold (InstructionPos ParsedShell) Failures
forall args. LabelSchema -> Rule args
Hadolint.Rule.DL3056.rule LabelSchema
labelSchema
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL3057.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> LabelSchema -> Fold (InstructionPos ParsedShell) Failures
forall args. LabelSchema -> Rule args
Hadolint.Rule.DL3058.rule LabelSchema
labelSchema
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL3059.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL3060.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL4000.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL4001.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL4003.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
forall args. Rule args
Hadolint.Rule.DL4004.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL4005.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.DL4006.rule
    Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
-> Fold (InstructionPos ParsedShell) Failures
forall a. Semigroup a => a -> a -> a
<> Fold (InstructionPos ParsedShell) Failures
Hadolint.Rule.Shellcheck.rule