Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type EDockerfileM = Free EInstruction
- type EDockerfileTM = FreeT EInstruction
- type EInstructionM = Free EInstruction
- type EInstructionTM = FreeT EInstruction
- embed :: forall m. MonadFree EInstruction m => [InstructionPos Text] -> m ()
- onBuildRaw :: forall m. MonadFree EInstruction m => Instruction Text -> m ()
- healthcheck :: forall m. MonadFree EInstruction m => Check Text -> m ()
- comment :: forall m. MonadFree EInstruction m => Text -> m ()
- arg :: forall m. MonadFree EInstruction m => Text -> Maybe Text -> m ()
- env :: forall m. MonadFree EInstruction m => Pairs -> m ()
- maintainer :: forall m. MonadFree EInstruction m => Text -> m ()
- entrypointArgs :: forall m. MonadFree EInstruction m => Arguments Text -> m ()
- volume :: forall m. MonadFree EInstruction m => Text -> m ()
- expose :: forall m. MonadFree EInstruction m => Ports -> m ()
- workdir :: forall m. MonadFree EInstruction m => Directory -> m ()
- shell :: forall m. MonadFree EInstruction m => Arguments Text -> m ()
- cmdArgs :: forall m. MonadFree EInstruction m => Arguments Text -> m ()
- runArgs :: forall m. MonadFree EInstruction m => Arguments Text -> RunFlags -> m ()
- copyArgs :: forall m. MonadFree EInstruction m => NonEmpty SourcePath -> TargetPath -> Chown -> Chmod -> CopySource -> m ()
- stopSignal :: forall m. MonadFree EInstruction m => Text -> m ()
- label :: forall m. MonadFree EInstruction m => Pairs -> m ()
- user :: forall m. MonadFree EInstruction m => Text -> m ()
- addArgs :: forall m. MonadFree EInstruction m => NonEmpty SourcePath -> TargetPath -> Chown -> Chmod -> m ()
- from :: forall m. MonadFree EInstruction m => EBaseImage -> m ()
- runDockerWriter :: MonadWriter [Instruction Text] m => EDockerfileM a -> m a
- runDockerWriterIO :: (Monad m, MonadTrans t, MonadWriter [Instruction Text] (t m)) => EDockerfileTM m a -> t m a
- runDef :: MonadWriter [t] m => (t1 -> t) -> t1 -> m b -> m b
- runDef2 :: MonadWriter [t] m => (t1 -> t2 -> t) -> t1 -> t2 -> m b -> m b
- runD :: MonadWriter [Instruction Text] m => EInstruction (m b) -> m b
- instructionPos :: Instruction args -> InstructionPos args
- toDockerfile :: EDockerfileM a -> Dockerfile
- toDockerfileText :: EDockerfileM a -> Text
- writeDockerFile :: Text -> Dockerfile -> IO ()
- putDockerfileStr :: EDockerfileM a -> IO ()
- untagged :: Text -> EBaseImage
- tagged :: Image -> Tag -> EBaseImage
- digested :: EBaseImage -> Digest -> EBaseImage
- aliased :: EBaseImage -> ImageAlias -> EBaseImage
- run :: MonadFree EInstruction m => Arguments Text -> m ()
- entrypoint :: MonadFree EInstruction m => Arguments Text -> m ()
- cmd :: MonadFree EInstruction m => Arguments Text -> m ()
- copy :: MonadFree EInstruction m => CopyArgs -> m ()
- copyFromStage :: MonadFree EInstruction m => CopySource -> NonEmpty SourcePath -> TargetPath -> m ()
- add :: MonadFree EInstruction m => NonEmpty SourcePath -> TargetPath -> m ()
- toSources :: NonEmpty Text -> NonEmpty SourcePath
- toTarget :: Text -> TargetPath
- fromStage :: CopyArgs -> CopySource -> CopyArgs
- ownedBy :: CopyArgs -> Chown -> CopyArgs
- to :: NonEmpty SourcePath -> TargetPath -> CopyArgs
- ports :: [Port] -> Ports
- tcpPort :: Int -> Port
- udpPort :: Int -> Port
- variablePort :: Text -> Port
- portRange :: Int -> Int -> Port
- udpPortRange :: Int -> Int -> Port
- check :: Arguments args -> Check args
- interval :: Check args -> Integer -> Check args
- timeout :: Check args -> Integer -> Check args
- startPeriod :: Check args -> Integer -> Check args
- retries :: Check args -> Integer -> Check args
- noCheck :: Check args
- onBuild :: MonadFree EInstruction m => EDockerfileM a -> m ()
- toDockerfileIO :: MonadIO m => EDockerfileTM m t -> m Dockerfile
- toDockerfileTextIO :: MonadIO m => EDockerfileTM m t -> m Text
- runDockerfileIO :: MonadIO m => EDockerfileTM m t -> m (t, Dockerfile)
- runDockerfileTextIO :: MonadIO m => EDockerfileTM m t -> m (t, Text)
Documentation
type EDockerfileM = Free EInstruction Source #
The type of Identity
based EDSL blocks
type EDockerfileTM = FreeT EInstruction Source #
The type of free monad EDSL blocks
type EInstructionM = Free EInstruction Source #
type EInstructionTM = FreeT EInstruction Source #
onBuildRaw :: forall m. MonadFree EInstruction m => Instruction Text -> m () Source #
maintainer :: forall m. MonadFree EInstruction m => Text -> m () Source #
copyArgs :: forall m. MonadFree EInstruction m => NonEmpty SourcePath -> TargetPath -> Chown -> Chmod -> CopySource -> m () Source #
stopSignal :: forall m. MonadFree EInstruction m => Text -> m () Source #
addArgs :: forall m. MonadFree EInstruction m => NonEmpty SourcePath -> TargetPath -> Chown -> Chmod -> m () Source #
from :: forall m. MonadFree EInstruction m => EBaseImage -> m () Source #
runDockerWriter :: MonadWriter [Instruction Text] m => EDockerfileM a -> m a Source #
runDockerWriterIO :: (Monad m, MonadTrans t, MonadWriter [Instruction Text] (t m)) => EDockerfileTM m a -> t m a Source #
runDef :: MonadWriter [t] m => (t1 -> t) -> t1 -> m b -> m b Source #
runDef2 :: MonadWriter [t] m => (t1 -> t2 -> t) -> t1 -> t2 -> m b -> m b Source #
runD :: MonadWriter [Instruction Text] m => EInstruction (m b) -> m b Source #
instructionPos :: Instruction args -> InstructionPos args Source #
toDockerfile :: EDockerfileM a -> Dockerfile Source #
Runs the Dockerfile EDSL and returns a Dockerfile
you can pretty print
or manipulate
toDockerfileText :: EDockerfileM a -> Text Source #
runs the Dockerfile EDSL and returns a Lazy
using
PrettyPrint
import Language.Docker main :: IO () main = print $ toDockerfileText $ do from (tagged "fpco/stack-build" "lts-6.9") add ["."] "applanguage-docker" workdir "applanguage-docker" run "stack build --test --only-dependencies" cmd "stack test"
writeDockerFile :: Text -> Dockerfile -> IO () Source #
Writes the dockerfile to the given file path after pretty-printing it
import Language.Docker main :: IO () main = writeDockerFile "build.Dockerfile" $ toDockerfile $ do from (tagged "fpco/stack-build" "lts-6.9") add ["."] "applanguage-docker" workdir "applanguage-docker" run "stack build --test --only-dependencies" cmd "stack test"
putDockerfileStr :: EDockerfileM a -> IO () Source #
Prints the dockerfile to stdout. Mainly used for debugging purposes
import Language.Docker main :: IO () main = putDockerfileStr $ do from (tagged "fpco/stack-build" "lts-6.9") add ["."] "applanguage-docker" workdir "applanguage-docker" run "stack build --test --only-dependencies" cmd "stack test"
untagged :: Text -> EBaseImage Source #
Use a docker image in a FROM instruction without a tag
The following two examples are equivalent
from $ untagged "fpco/stack-build"
Is equivalent to, when having OverloadedStrings:
from "fpco/stack-build"
tagged :: Image -> Tag -> EBaseImage Source #
Use a specific tag for a docker image. This function is meant to be used as an infix operator.
from $ "fpco/stack-build" tagged
"lts-10.3"
digested :: EBaseImage -> Digest -> EBaseImage Source #
Adds a digest checksum so a FROM instruction This function is meant to be used as an infix operator.
from $ "fpco/stack-build" digested
"sha256:abcdef123"
aliased :: EBaseImage -> ImageAlias -> EBaseImage Source #
Alias a FROM instruction to be used as a build stage. This function is meant to be used as an infix operator.
from $ "fpco/stack-build" aliased
"builder"
run :: MonadFree EInstruction m => Arguments Text -> m () Source #
Create a RUN instruction with the given arguments.
run "apt-get install wget"
entrypoint :: MonadFree EInstruction m => Arguments Text -> m () Source #
Create an ENTRYPOINT instruction with the given arguments.
entrypoint "usrlocalbinprogram --some-flag"
cmd :: MonadFree EInstruction m => Arguments Text -> m () Source #
Create a CMD instruction with the given arguments.
cmd "my-program --some-flag"
copyFromStage :: MonadFree EInstruction m => CopySource -> NonEmpty SourcePath -> TargetPath -> m () Source #
Create a COPY instruction from a given build stage.
This is a shorthand version of using copy
with combinators.
copyFromStage "builder" ["foo.js", "bar.js"] "."
add :: MonadFree EInstruction m => NonEmpty SourcePath -> TargetPath -> m () Source #
Create an ADD instruction. This is often used as a shorthand version
of copy when no extra options are needed. Currently there is no way to
pass extra options to ADD, so you are encouraged to use copy
instead.
add ["foo.js", "bar.js"] "."
toSources :: NonEmpty Text -> NonEmpty SourcePath Source #
Converts a NonEmpty list of strings to a NonEmpty list of SourcePath
This is a convenience function when you need to pass a non-static list of
strings that you build somewhere as an argument for copy
or add
someFiles <- glob "*.js"
copy $ (toSources someFiles) to
"."
toTarget :: Text -> TargetPath Source #
Converts a Text into a TargetPath
This is a convenience function when you need to pass a string variable
as an argument for copy
or add
let destination = buildSomePath pwd add ["foo.js"] (toTarget destination)
to :: NonEmpty SourcePath -> TargetPath -> CopyArgs Source #
variablePort :: Text -> Port Source #
onBuild :: MonadFree EInstruction m => EDockerfileM a -> m () Source #
ONBUILD Dockerfile instruction
Each nested instruction gets emitted as a separate ONBUILD
block
toDockerfile
$ do
from "node"
run "apt-get update"
onBuild $ do
run "echo more-stuff"
run "echo here"
toDockerfileIO :: MonadIO m => EDockerfileTM m t -> m Dockerfile Source #
A version of toDockerfile
which allows IO actions
toDockerfileTextIO :: MonadIO m => EDockerfileTM m t -> m Text Source #
A version of toDockerfileText
which allows IO actions
runDockerfileIO :: MonadIO m => EDockerfileTM m t -> m (t, Dockerfile) Source #
Just runs the EDSL's writer monad
runDockerfileTextIO :: MonadIO m => EDockerfileTM m t -> m (t, Text) Source #
Runs the EDSL's writer monad and pretty-prints the result