module Buffet.Assemble.ConditionInstructions ( Configuration(..) , get ) where import qualified Buffet.Assemble.InsertOptionArgInstructionUnlessPresent as InsertOptionArgInstructionUnlessPresent import qualified Buffet.Ir.Ir as Ir import qualified Data.Text as T import qualified Language.Docker as Docker hiding (sourcePaths) import qualified Language.Docker.Syntax as Syntax import Prelude (Eq, Ord, Show, ($), (.), (<>), fmap, mconcat, pure) data Configuration = Configuration { Configuration -> Text copyDummySourcePath :: T.Text , Configuration -> Option option :: Ir.Option } deriving (Configuration -> Configuration -> Bool (Configuration -> Configuration -> Bool) -> (Configuration -> Configuration -> Bool) -> Eq Configuration forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Configuration -> Configuration -> Bool $c/= :: Configuration -> Configuration -> Bool == :: Configuration -> Configuration -> Bool $c== :: Configuration -> Configuration -> Bool Eq, Eq Configuration Eq Configuration -> (Configuration -> Configuration -> Ordering) -> (Configuration -> Configuration -> Bool) -> (Configuration -> Configuration -> Bool) -> (Configuration -> Configuration -> Bool) -> (Configuration -> Configuration -> Bool) -> (Configuration -> Configuration -> Configuration) -> (Configuration -> Configuration -> Configuration) -> Ord Configuration Configuration -> Configuration -> Bool Configuration -> Configuration -> Ordering Configuration -> Configuration -> Configuration forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: Configuration -> Configuration -> Configuration $cmin :: Configuration -> Configuration -> Configuration max :: Configuration -> Configuration -> Configuration $cmax :: Configuration -> Configuration -> Configuration >= :: Configuration -> Configuration -> Bool $c>= :: Configuration -> Configuration -> Bool > :: Configuration -> Configuration -> Bool $c> :: Configuration -> Configuration -> Bool <= :: Configuration -> Configuration -> Bool $c<= :: Configuration -> Configuration -> Bool < :: Configuration -> Configuration -> Bool $c< :: Configuration -> Configuration -> Bool compare :: Configuration -> Configuration -> Ordering $ccompare :: Configuration -> Configuration -> Ordering $cp1Ord :: Eq Configuration Ord, Int -> Configuration -> ShowS [Configuration] -> ShowS Configuration -> String (Int -> Configuration -> ShowS) -> (Configuration -> String) -> ([Configuration] -> ShowS) -> Show Configuration forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Configuration] -> ShowS $cshowList :: [Configuration] -> ShowS show :: Configuration -> String $cshow :: Configuration -> String showsPrec :: Int -> Configuration -> ShowS $cshowsPrec :: Int -> Configuration -> ShowS Show) get :: Configuration -> Ir.DockerfilePart -> Ir.DockerfilePart get :: Configuration -> DockerfilePart -> DockerfilePart get Configuration configuration = (Instruction Text -> Instruction Text) -> DockerfilePart -> DockerfilePart forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (Configuration -> Instruction Text -> Instruction Text conditionInstruction Configuration configuration) (DockerfilePart -> DockerfilePart) -> (DockerfilePart -> DockerfilePart) -> DockerfilePart -> DockerfilePart forall b c a. (b -> c) -> (a -> b) -> a -> c . Option -> DockerfilePart -> DockerfilePart InsertOptionArgInstructionUnlessPresent.get Option option' where option' :: Option option' = Configuration -> Option option Configuration configuration conditionInstruction :: Configuration -> Docker.Instruction T.Text -> Docker.Instruction T.Text conditionInstruction :: Configuration -> Instruction Text -> Instruction Text conditionInstruction Configuration configuration = Instruction Text -> Instruction Text condition where condition :: Instruction Text -> Instruction Text condition (Docker.Copy CopyArgs arguments) = Configuration -> CopyArgs -> Instruction Text conditionCopyInstruction Configuration configuration CopyArgs arguments condition (Docker.Run (Syntax.RunArgs (Syntax.ArgumentsText Text command) RunFlags flags)) = Configuration -> Text -> RunFlags -> Instruction Text conditionRunInstruction Configuration configuration Text command RunFlags flags condition Instruction Text instruction = Instruction Text instruction conditionCopyInstruction :: Configuration -> Docker.CopyArgs -> Docker.Instruction T.Text conditionCopyInstruction :: Configuration -> CopyArgs -> Instruction Text conditionCopyInstruction Configuration buffet CopyArgs arguments = CopyArgs -> Instruction Text forall args. CopyArgs -> Instruction args Docker.Copy CopyArgs arguments {$sel:sourcePaths:CopyArgs :: NonEmpty SourcePath Docker.sourcePaths = NonEmpty SourcePath sources} where sources :: NonEmpty SourcePath sources = (SourcePath -> SourcePath) -> NonEmpty SourcePath -> NonEmpty SourcePath forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap SourcePath -> SourcePath makePattern NonEmpty SourcePath originalSources NonEmpty SourcePath -> NonEmpty SourcePath -> NonEmpty SourcePath forall a. Semigroup a => a -> a -> a <> SourcePath -> NonEmpty SourcePath forall (f :: * -> *) a. Applicative f => a -> f a pure SourcePath dummy makePattern :: SourcePath -> SourcePath makePattern SourcePath path = SourcePath :: Text -> SourcePath Docker.SourcePath {$sel:unSourcePath:SourcePath :: Text Docker.unSourcePath = Text -> Char -> Text T.snoc (SourcePath -> Text Docker.unSourcePath SourcePath path) Char '*'} originalSources :: NonEmpty SourcePath originalSources = CopyArgs -> NonEmpty SourcePath Docker.sourcePaths CopyArgs arguments dummy :: SourcePath dummy = SourcePath :: Text -> SourcePath Docker.SourcePath {$sel:unSourcePath:SourcePath :: Text Docker.unSourcePath = Configuration -> Text copyDummySourcePath Configuration buffet} conditionRunInstruction :: Configuration -> T.Text -> Syntax.RunFlags -> Docker.Instruction T.Text conditionRunInstruction :: Configuration -> Text -> RunFlags -> Instruction Text conditionRunInstruction Configuration configuration Text thenPart = RunArgs Text -> Instruction Text forall args. RunArgs args -> Instruction args Docker.Run (RunArgs Text -> Instruction Text) -> (RunFlags -> RunArgs Text) -> RunFlags -> Instruction Text forall b c a. (b -> c) -> (a -> b) -> a -> c . Arguments Text -> RunFlags -> RunArgs Text forall args. Arguments args -> RunFlags -> RunArgs args Syntax.RunArgs (Text -> Arguments Text forall args. args -> Arguments args Syntax.ArgumentsText Text command) where command :: Text command = [Text] -> Text forall a. Monoid a => [a] -> a mconcat [ String -> Text T.pack String "if [ -n \"${" , Option -> Text Ir.option (Option -> Text) -> Option -> Text forall a b. (a -> b) -> a -> b $ Configuration -> Option option Configuration configuration , String -> Text T.pack String "}\" ]; then " , Text thenPart , String -> Text T.pack String "; fi" ]