| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Language.Dockerfile
Contents
- Parsing Dockerfiles (
Language.Dockerfile.SyntaxandLanguage.Dockerfile.Parser) - Pretty-printing Dockerfiles (
Language.Dockerfile.PrettyPrint) - Writting Dockerfiles (
Language.Dockerfile.EDSL) - QuasiQuoter (
Language.Dockerfile.EDSL.Quasi) - Types (
Language.Dockerfile.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 :: String -> String -> EBaseImage
 - untagged :: String -> EBaseImage
 - digested :: String -> ByteString -> EBaseImage
 - add :: forall m. MonadFree EInstruction m => Source -> Destination -> 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 :: forall m. MonadFree EInstruction m => Source -> Destination -> m ()
 - run :: MonadFree EInstruction m => String -> m ()
 - runArgs :: forall m. MonadFree EInstruction m => Arguments -> m ()
 - cmd :: MonadFree EInstruction m => String -> m ()
 - cmdArgs :: forall m. MonadFree EInstruction m => Arguments -> m ()
 - workdir :: forall m. MonadFree EInstruction m => Directory -> m ()
 - expose :: forall m. MonadFree EInstruction m => Ports -> m ()
 - ports :: [Integer] -> Ports
 - port :: Integer -> Ports
 - volume :: forall m. MonadFree EInstruction m => String -> m ()
 - entrypoint :: MonadFree EInstruction m => String -> 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 -> 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
 - data InstructionPos = InstructionPos Instruction Filename Linenumber
 - data BaseImage
 - type Image = String
 - type Tag = String
 - data Ports
 - type Directory = String
 - type Source = String
 - type Destination = String
 - type Arguments = [String]
 - type Pairs = [(String, String)]
 - type Filename = String
 - type Linenumber = Int
 - data ParseError :: *
 - instruction :: InstructionPos -> Instruction
 - instructionPos :: Instruction -> InstructionPos
 - sourcename :: InstructionPos -> Filename
 
Parsing Dockerfiles (Language.Dockerfile.Syntax and Language.Dockerfile.Parser)
type Dockerfile = [InstructionPos] Source #
Type of the Dockerfile AST
parseFile :: String -> IO (Either ParseError Dockerfile) Source #
Pretty-printing Dockerfiles (Language.Dockerfile.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.Dockerfile.EDSL)
toDockerfileStr :: EDockerfileM a -> String Source #
runs the Dockerfile EDSL and returns a String using
 PrettyPrint
import           Language.Dockerfile
main :: IO ()
main = writeFile "something.dockerfile" $ toDockerfileStr $ do
    from (tagged "fpco/stack-build" "lts-6.9")
    add "." "applanguage-dockerfile"
    workdir "applanguage-dockerfile"
    run (words "stack build --test --only-dependencies")
    cmd (words "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
untagged :: String -> EBaseImage Source #
digested :: String -> ByteString -> EBaseImage Source #
Syntax
add :: forall m. MonadFree EInstruction m => Source -> Destination -> m () Source #
stopSignal :: forall m. MonadFree EInstruction m => String -> m () Source #
copy :: forall m. MonadFree EInstruction m => Source -> Destination -> m () Source #
entrypoint :: MonadFree EInstruction m => String -> m () Source #
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 #
Constructors
| EUntaggedImage String | |
| ETaggedImage String String | |
| EDigestedImage String ByteString | 
Instances
QuasiQuoter (Language.Dockerfile.EDSL.Quasi)
Types (Language.Dockerfile.Syntax)
data Instruction Source #
All commands available in Dockerfiles
Constructors
Instances
data InstructionPos Source #
Instruction with additional location information required for creating
 good check messages
Constructors
| InstructionPos Instruction Filename Linenumber | 
Instances
Constructors
| UntaggedImage Image | |
| TaggedImage Image Tag | |
| DigestedImage Image ByteString | 
type Destination = String Source #
type Linenumber = Int Source #
Re-exports from parsec
data ParseError :: * #
The abstract data type ParseError represents parse errors. It
 provides the source position (SourcePos) of the error
 and a list of error messages (Message). A ParseError
 can be returned by the function parse. ParseError is an
 instance of the Show and Eq classes.
Instances
Instruction and InstructionPos helpers
sourcename :: InstructionPos -> Filename Source #