Safe Haskell | None |
---|---|
Language | Haskell2010 |
- Parsing Dockerfiles (
Language.Docker.Syntax
andLanguage.Docker.Parser
) - Pretty-printing Dockerfiles (
Language.Docker.PrettyPrint
) - Writting Dockerfiles (
Language.Docker.EDSL
) - QuasiQuoter (
Language.Docker.EDSL.Quasi
) - Types (
Language.Docker.Syntax
) - Re-exports from
parsec
- Instruction and InstructionPos helpers
- type Dockerfile = [InstructionPos]
- parseString :: String -> Either ParseError Dockerfile
- parseFile :: String -> IO (Either ParseError Dockerfile)
- prettyPrint :: Dockerfile -> String
- prettyPrintInstructionPos :: InstructionPos -> String
- toDockerfileStr :: EDockerfileM a -> String
- toDockerfile :: EDockerfileM a -> Dockerfile
- toDockerfileStrIO :: MonadIO m => EDockerfileTM m t -> m String
- toDockerfileIO :: MonadIO m => EDockerfileTM m t -> m Dockerfile
- runDockerfileIO :: MonadIO m => EDockerfileTM m t -> m (t, Dockerfile)
- runDockerfileStrIO :: MonadIO m => EDockerfileTM m t -> m (t, String)
- liftIO :: MonadIO m => forall a. IO a -> m a
- from :: forall m. MonadFree EInstruction m => EBaseImage -> m ()
- tagged :: Image -> String -> EBaseImage
- untagged :: String -> EBaseImage
- digested :: Image -> ByteString -> EBaseImage
- aliased :: EBaseImage -> String -> EBaseImage
- add :: MonadFree EInstruction m => NonEmpty SourcePath -> TargetPath -> m ()
- user :: forall m. MonadFree EInstruction m => String -> m ()
- label :: forall m. MonadFree EInstruction m => Pairs -> m ()
- stopSignal :: forall m. MonadFree EInstruction m => String -> m ()
- copy :: MonadFree EInstruction m => CopyArgs -> m ()
- copyFromStage :: MonadFree EInstruction m => CopySource -> NonEmpty SourcePath -> TargetPath -> m ()
- to :: NonEmpty SourcePath -> TargetPath -> CopyArgs
- fromStage :: CopyArgs -> CopySource -> CopyArgs
- ownedBy :: CopyArgs -> Chown -> CopyArgs
- toSources :: NonEmpty String -> NonEmpty SourcePath
- toTarget :: String -> TargetPath
- run :: MonadFree EInstruction m => Arguments -> m ()
- runArgs :: forall m. MonadFree EInstruction m => Arguments -> m ()
- cmd :: MonadFree EInstruction m => Arguments -> m ()
- cmdArgs :: forall m. MonadFree EInstruction m => Arguments -> m ()
- healthcheck :: forall m. MonadFree EInstruction m => Check -> m ()
- check :: Arguments -> Check
- interval :: Check -> Integer -> Check
- timeout :: Check -> Integer -> Check
- startPeriod :: Check -> Integer -> Check
- retries :: Check -> Integer -> Check
- workdir :: forall m. MonadFree EInstruction m => Directory -> m ()
- expose :: forall m. MonadFree EInstruction m => Ports -> m ()
- ports :: [Port] -> Ports
- tcpPort :: Integer -> Port
- udpPort :: Integer -> Port
- variablePort :: String -> Port
- portRange :: Integer -> Integer -> Port
- udpPortRange :: Integer -> Integer -> Port
- volume :: forall m. MonadFree EInstruction m => String -> m ()
- entrypoint :: MonadFree EInstruction m => Arguments -> m ()
- entrypointArgs :: forall m. MonadFree EInstruction m => Arguments -> m ()
- maintainer :: forall m. MonadFree EInstruction m => String -> m ()
- env :: forall m. MonadFree EInstruction m => Pairs -> m ()
- arg :: forall m. MonadFree EInstruction m => String -> Maybe String -> m ()
- comment :: forall m. MonadFree EInstruction m => String -> m ()
- onBuild :: MonadFree EInstruction m => EDockerfileM a -> m ()
- onBuildRaw :: forall m. MonadFree EInstruction m => Instruction -> m ()
- embed :: forall m. MonadFree EInstruction m => [InstructionPos] -> m ()
- edockerfile :: QuasiQuoter
- type EDockerfileM = Free EInstruction
- type EDockerfileTM = FreeT EInstruction
- data EBaseImage
- dockerfile :: QuasiQuoter
- data Instruction
- = From BaseImage
- | Add AddArgs
- | User String
- | Label Pairs
- | Stopsignal String
- | Copy CopyArgs
- | Run Arguments
- | Cmd Arguments
- | Shell Arguments
- | Workdir Directory
- | Expose Ports
- | Volume String
- | Entrypoint Arguments
- | Maintainer String
- | Env Pairs
- | Arg String (Maybe String)
- | Healthcheck Check
- | Comment String
- | OnBuild Instruction
- data InstructionPos = InstructionPos {}
- data BaseImage
- newtype SourcePath = SourcePath {}
- newtype TargetPath = TargetPath {}
- data Chown
- data CopySource
- data CopyArgs = CopyArgs {}
- data AddArgs = AddArgs {}
- data Check
- data CheckArgs = CheckArgs {}
- data Image = Image {}
- newtype Registry = Registry String
- newtype ImageAlias = ImageAlias {}
- type Tag = String
- data Ports
- type Directory = String
- data Arguments
- type Pairs = [(String, String)]
- type Filename = String
- type Linenumber = Int
- data ParseError :: *
- instructionPos :: Instruction -> InstructionPos
Documentation
type Dockerfile = [InstructionPos] Source #
Type of the Dockerfile AST
Parsing Dockerfiles (Language.Docker.Syntax
and Language.Docker.Parser
)
parseFile :: String -> IO (Either ParseError Dockerfile) Source #
Pretty-printing Dockerfiles (Language.Docker.PrettyPrint
)
prettyPrint :: Dockerfile -> String Source #
Pretty print a Dockerfile
to a String
prettyPrintInstructionPos :: InstructionPos -> String Source #
Pretty print a InstructionPos
to a String
Writting Dockerfiles (Language.Docker.EDSL
)
toDockerfileStr :: EDockerfileM a -> String Source #
runs the Dockerfile EDSL and returns a String
using
PrettyPrint
import Language.Docker main :: IO () main = writeFile "something.dockerfile" $ toDockerfileStr $ do from (tagged "fpco/stack-build" "lts-6.9") add ["."] "applanguage-docker" workdir "applanguage-docker" run "stack build --test --only-dependencies" cmd "stack test"
toDockerfile :: EDockerfileM a -> Dockerfile Source #
Runs the Dockerfile EDSL and returns a Dockerfile
you can pretty print
or manipulate
toDockerfileStrIO :: MonadIO m => EDockerfileTM m t -> m String Source #
A version of toDockerfileStr
which allows IO actions
toDockerfileIO :: MonadIO m => EDockerfileTM m t -> m Dockerfile Source #
A version of toDockerfile
which allows IO actions
runDockerfileIO :: MonadIO m => EDockerfileTM m t -> m (t, Dockerfile) Source #
Just runs the EDSL's writer monad
runDockerfileStrIO :: MonadIO m => EDockerfileTM m t -> m (t, String) Source #
Runs the EDSL's writer monad and pretty-prints the result
from :: forall m. MonadFree EInstruction m => EBaseImage -> m () Source #
Constructing base images
tagged :: Image -> String -> 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"
untagged :: String -> 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"
digested :: Image -> ByteString -> EBaseImage Source #
aliased :: EBaseImage -> String -> 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"
Syntax
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"] "."
stopSignal :: forall m. MonadFree EInstruction m => String -> m () Source #
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"] "."
to :: NonEmpty SourcePath -> TargetPath -> CopyArgs Source #
toSources :: NonEmpty String -> 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 :: String -> TargetPath Source #
Converts a String 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)
run :: MonadFree EInstruction m => Arguments -> m () Source #
Create a RUN instruction with the given arguments.
run "apt-get install wget"
cmd :: MonadFree EInstruction m => Arguments -> m () Source #
Create a CMD instruction with the given arguments.
cmd "my-program --some-flag"
healthcheck :: forall m. MonadFree EInstruction m => Check -> m () Source #
variablePort :: String -> Port Source #
entrypoint :: MonadFree EInstruction m => Arguments -> m () Source #
Create an ENTRYPOINT instruction with the given arguments.
entrypoint "usrlocalbinprogram --some-flag"
entrypointArgs :: forall m. MonadFree EInstruction m => Arguments -> m () Source #
maintainer :: forall m. MonadFree EInstruction m => String -> m () 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"
onBuildRaw :: forall m. MonadFree EInstruction m => Instruction -> m () Source #
embed :: forall m. MonadFree EInstruction m => [InstructionPos] -> m () Source #
edockerfile :: QuasiQuoter Source #
Quasiquoter for embedding dockerfiles on the EDSL
putStr $ toDockerfile
$ do
from "node"
run "apt-get update"
[edockerfile|
RUN apt-get update
CMD node something.js
|]
Support types for the EDSL
type EDockerfileM = Free EInstruction Source #
The type of Identity
based EDSL blocks
type EDockerfileTM = FreeT EInstruction Source #
The type of free monad EDSL blocks
data EBaseImage Source #
QuasiQuoter (Language.Docker.EDSL.Quasi
)
Types (Language.Docker.Syntax
)
data Instruction Source #
All commands available in Dockerfiles
data InstructionPos Source #
Instruction
with additional location information required for creating
good check messages
newtype SourcePath Source #
newtype TargetPath Source #
data CopySource Source #
newtype ImageAlias Source #
type Linenumber = Int Source #
Re-exports from parsec
data ParseError :: * #