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

[ development, gpl, library ] [ Propose Tags ]

All functions for parsing, printing and writting Dockerfiles are exported through Language.Docker. For more fine-grained operations look for specific modules that implement a certain functionality. See the GitHub project for the source-code and examples.


[Skip to Readme]

Downloads

Note: This package has metadata revisions in the cabal description newer than included in the tarball. To unpack the package including the revisions, use 'cabal get'.

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 1.0.0, 2.0.0, 2.0.1, 3.0.0, 3.0.1, 4.0.0, 4.0.1, 5.0.0, 5.0.1, 6.0.0, 6.0.1, 6.0.2, 6.0.3, 6.0.4, 7.0.0, 8.0.0, 8.0.1, 8.0.2, 8.1.0, 8.1.1, 9.0.0, 9.0.1, 9.1.0, 9.1.1, 9.1.2, 9.1.3, 9.2.0, 9.3.0, 10.0.0, 10.0.1, 10.0.2, 10.1.0, 10.1.1, 10.1.2, 10.2.0, 10.3.0, 10.4.0, 10.4.1, 10.4.2, 10.4.3, 11.0.0, 12.0.0, 12.1.0
Dependencies aeson, base (>=4.9 && <4.11), bytestring (>=0.10), directory, filepath, free, Glob, mtl, parsec (>=3.1), pretty, semigroups, split (>=0.2), template-haskell, text, th-lift, th-lift-instances, time, transformers, unordered-containers, yaml [details]
License GPL-3.0-only
Copyright Lukas Martinelli, Copyright (c) 2016, Pedro Tacla Yamada, Copyright (c) 2016, José Lorenzo Rodríguez, Copyright (c) 2017
Author Lukas Martinelli, Pedro Tacla Yamada, José Lorenzo Rodríguez
Maintainer me@lukasmartinelli.ch, lorenzo@seatgeek.com
Revised Revision 1 made by HerbertValerioRiedel at 2018-08-23T22:12:56Z
Category Development
Home page https://github.com/hadolint/language-docker#readme
Bug tracker https://github.com/hadolint/language-docker/issues
Source repo head: git clone https://github.com/hadolint/language-docker
Uploaded by lorenzo at 2018-03-12T03:43:43Z
Distributions Fedora:11.0.0, LTSHaskell:12.1.0, NixOS:12.1.0, openSUSE:11.0.0
Reverse Dependencies 3 direct, 0 indirect [details]
Downloads 22815 total (133 in the last 30 days)
Rating 2.0 (votes: 1) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2018-03-12 [all 1 reports]

Readme for language-docker-3.0.0

[back to package description]

Build Status Hackage GPL-3 licensed

haskell-language-docker

Dockerfile parser, pretty-printer and embedded DSL

Provides de ability to parse docker files, a pretty-printer and EDSL for writting Dockerfiles in Haskell.

Parsing files

import Language.Docker
main = do
    ef <- parseFile "./Dockerfile"
    print ef

Parsing strings

import Language.Docker
main = do
    c <- readFile "./Dockerfile"
    print (parseString c)

Pretty-printing files

import Language.Docker
main = do
    Right d <- parseFile "./Dockerfile"
    putStr (prettyPrint d)

Writing Dockerfiles in Haskell

{-# LANGUAGE OverloadedStrings #-}
import Language.Docker
main = putStr $ toDockerfileStr $ do
    from "node"
    run "apt-get update"
    runArgs ["apt-get", "install", "something"]
    -- ...

Using the QuasiQuoter

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes       #-}
import Language.Docker
main = putStr $ toDockerfileStr $ do
    from "node"
    run "apt-get update"
    [edockerfile|
    RUN apt-get update
    CMD node something.js
    |]
    -- ...

Templating Dockerfiles in Haskell

{-# LANGUAGE FlexibleContexts  #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedLists #-}
import Control.Monad
import Language.Docker
import Data.String (fromString)

tags = ["7.8", "7.10", "8"]
cabalSandboxBuild packageName = do
    let cabalFile = packageName ++ ".cabal"
    run "cabal sandbox init"
    run "cabal update"
    add [fromString cabalFile] (fromString $ "/app/" ++ cabalFile)
    run "cabal install --only-dep -j"
    add "." "/app/"
    run "cabal build"
main =
    forM_ tags $ \tag -> do
        let df = toDockerfileStr $ do
            from ("haskell" `tagged` tag)
            cabalSandboxBuild "mypackage"
        writeFile ("./examples/templating-" ++ tag ++ ".dockerfile") df

Using IO in the DSL

By default the DSL runs in the Identity monad. By running in IO we can support more features like file globbing:

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedLists #-}
import           Language.Docker
import qualified System.Directory     as Directory
import qualified System.FilePath      as FilePath
import qualified System.FilePath.Glob as Glob
import Data.List.NonEmpty (fromList)

main = do
    str <- toDockerfileStrIO $ do
        fs <- liftIO $ do
            cwd <- Directory.getCurrentDirectory
            fs <- Glob.glob "./test/*.hs"
	    let relativeFiles = map (FilePath.makeRelative cwd) fs
            return (fromList relativeFiles)
        from "ubuntu"
	copy $ (toSources fs) `to` "/app/"
    putStr str