language-docker-2.0.0: Dockerfile parser, pretty-printer and embedded DSL

Safe HaskellNone
LanguageHaskell2010

Language.Docker

Contents

Synopsis

Documentation

type Dockerfile = [InstructionPos] Source #

Type of the Dockerfile AST

Parsing Dockerfiles (Language.Docker.Syntax and Language.Docker.Parser)

Pretty-printing Dockerfiles (Language.Docker.PrettyPrint)

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 (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

liftIO :: MonadIO m => forall a. IO a -> m a #

Lift a computation from the IO monad.

from :: forall m. MonadFree EInstruction m => EBaseImage -> m () Source #

Constructing base images

Syntax

user :: forall m. MonadFree EInstruction m => String -> m () Source #

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

stopSignal :: forall m. MonadFree EInstruction m => String -> m () Source #

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

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

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

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

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

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

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

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

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

comment :: 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"

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

QuasiQuoter (Language.Docker.EDSL.Quasi)

Types (Language.Docker.Syntax)

data Chown Source #

Constructors

Chown String 
NoChown 

Instances

Eq Chown Source # 

Methods

(==) :: Chown -> Chown -> Bool #

(/=) :: Chown -> Chown -> Bool #

Ord Chown Source # 

Methods

compare :: Chown -> Chown -> Ordering #

(<) :: Chown -> Chown -> Bool #

(<=) :: Chown -> Chown -> Bool #

(>) :: Chown -> Chown -> Bool #

(>=) :: Chown -> Chown -> Bool #

max :: Chown -> Chown -> Chown #

min :: Chown -> Chown -> Chown #

Show Chown Source # 

Methods

showsPrec :: Int -> Chown -> ShowS #

show :: Chown -> String #

showList :: [Chown] -> ShowS #

data Check Source #

Constructors

Check CheckArgs 
NoCheck 

Instances

Eq Check Source # 

Methods

(==) :: Check -> Check -> Bool #

(/=) :: Check -> Check -> Bool #

Ord Check Source # 

Methods

compare :: Check -> Check -> Ordering #

(<) :: Check -> Check -> Bool #

(<=) :: Check -> Check -> Bool #

(>) :: Check -> Check -> Bool #

(>=) :: Check -> Check -> Bool #

max :: Check -> Check -> Check #

min :: Check -> Check -> Check #

Show Check Source # 

Methods

showsPrec :: Int -> Check -> ShowS #

show :: Check -> String #

showList :: [Check] -> ShowS #

data Ports Source #

Instances

IsList Ports Source # 

Associated Types

type Item Ports :: * #

Eq Ports Source # 

Methods

(==) :: Ports -> Ports -> Bool #

(/=) :: Ports -> Ports -> Bool #

Ord Ports Source # 

Methods

compare :: Ports -> Ports -> Ordering #

(<) :: Ports -> Ports -> Bool #

(<=) :: Ports -> Ports -> Bool #

(>) :: Ports -> Ports -> Bool #

(>=) :: Ports -> Ports -> Bool #

max :: Ports -> Ports -> Ports #

min :: Ports -> Ports -> Ports #

Show Ports Source # 

Methods

showsPrec :: Int -> Ports -> ShowS #

show :: Ports -> String #

showList :: [Ports] -> ShowS #

type Item Ports Source # 
type Item Ports = Port

type Pairs = [(String, String)] 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.

Instruction and InstructionPos helpers