dockerfile-creator-0.1.1.0
Safe HaskellNone
LanguageHaskell2010

Language.Docker.EDSL

Synopsis

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 #

embed :: forall m. MonadFree EInstruction m => [InstructionPos Text] -> m () Source #

onBuildRaw :: forall m. MonadFree EInstruction m => Instruction Text -> m () Source #

healthcheck :: forall m. MonadFree EInstruction m => Check Text -> m () Source #

comment :: forall m. MonadFree EInstruction m => Text -> m () Source #

arg :: forall m. MonadFree EInstruction m => Text -> Maybe Text -> m () Source #

env :: forall m. MonadFree EInstruction m => Pairs -> m () Source #

maintainer :: forall m. MonadFree EInstruction m => Text -> m () Source #

entrypointArgs :: forall m. MonadFree EInstruction m => Arguments Text -> m () Source #

volume :: forall m. MonadFree EInstruction m => Text -> m () Source #

expose :: forall m. MonadFree EInstruction m => Ports -> m () Source #

workdir :: forall m. MonadFree EInstruction m => Directory -> m () Source #

shell :: forall m. MonadFree EInstruction m => Arguments Text -> m () Source #

cmdArgs :: forall m. MonadFree EInstruction m => Arguments Text -> m () Source #

runArgs :: forall m. MonadFree EInstruction m => Arguments Text -> RunFlags -> 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 #

label :: forall m. MonadFree EInstruction m => Pairs -> m () Source #

user :: 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 #

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 #

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"

copy :: MonadFree EInstruction m => CopyArgs -> m () Source #

Create a COPY instruction. This function is meant to be used with the compinators to, fromStage and ownedBy

copy $ ["foo.js", "bar.js"] to "."
copy $ ["some_file"] to "somepath" fromStage "builder"

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)

fromStage :: CopyArgs -> CopySource -> CopyArgs Source #

Adds the --from= option to a COPY instruction.

This function is meant to be used as an infix operator:

copy $ ["foo.js"] to "." fromStage "builder"

ownedBy :: CopyArgs -> Chown -> CopyArgs Source #

Adds the --chown= option to a COPY instruction.

This function is meant to be used as an infix operator:

copy $ ["foo.js"] to "." ownedBy "www-data:www-data"

to :: NonEmpty SourcePath -> TargetPath -> CopyArgs Source #

Usedto join source paths with atarget path as an arguments for copy

This function is meant to be used as an infix operator:

copy $ ["foo.js"] to "." ownedBy

check :: Arguments args -> Check args Source #

interval :: Check args -> Integer -> Check args Source #

timeout :: Check args -> Integer -> Check args Source #

startPeriod :: Check args -> Integer -> Check args Source #

retries :: Check args -> Integer -> Check args 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