language-dockerfile: Dockerfile linter, parser, pretty-printer and embedded DSL

[ development, gpl, library ] [ Propose Tags ]

Forked from hadolint.

All functions for parsing, printing and writting Dockerfiles are exported through Language.Dockerfile. For more fine-grained operations look for specific modules that implement a certain functionality.

There are two flags in this package, which enable building two executables:

  • hadolint Enables building the hadolint executable, though you might prefer to use the hadolint package directly

  • dockerfmt Builds example pretty-printer usage, which reads a Dockerfile and pretty-prints it to stdout

See the GitHub project for the source-code and examples.


[Skip to Readme]

Flags

Manual Flags

NameDescriptionDefault
dockerfmt

Build the dockerfmt executable

Disabled
hadolint

Build the hadolint executable

Disabled

Use -f <flag> to enable a flag, or -f -<flag> to disable that flag. More info

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.2.0, 0.2.3.0, 0.3.0.0, 0.3.1.0, 0.3.2.0, 0.3.3.0, 0.3.4.0, 0.3.5.0, 0.3.6.0
Dependencies base (>=4.8 && <5), bytestring (>=0.10), free, language-dockerfile, mtl, parsec (>=3.1), pretty, ShellCheck, split (>=0.2), template-haskell, th-lift, th-lift-instances [details]
License GPL-3.0-only
Copyright Lukas Martinelli, Copyright (c) 2016, Pedro Tacla Yamada, Copyright (c) 2016
Author Lukas Martinelli, Pedro Tacla Yamada
Maintainer tacla.yamada@gmail.com
Category Development
Home page https://github.com/beijaflor-io/language-dockerfile#readme
Bug tracker https://github.com/beijaflor-io/language-dockerfile/issues
Source repo head: git clone https://github.com/beijaflor-io/language-dockerfile
Uploaded by yamadapc at 2016-08-09T12:59:52Z
Distributions
Reverse Dependencies 1 direct, 0 indirect [details]
Executables hadolint, dockerfmt
Downloads 6276 total (22 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2016-08-09 [all 1 reports]

Readme for language-dockerfile-0.2.3.0

[back to package description]

haskell-language-dockerfile

Dockerfile linter, parser, pretty-printer and embedded DSL, forked from hadolint.

Published on Hackage as language-dockerfile.

It extends hadolint with the pretty-printer and EDSL for writting Dockerfiles in Haskell.

Parsing files

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

Parsing strings

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

Pretty-printing files

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

Writting Dockerfiles in Haskell

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

Using the QuasiQuoter

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes       #-}
import Language.Dockerfile
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 #-}
import Control.Monad
import Language.Dockerfile
tags = ["7.8", "7.10", "8"]
cabalSandboxBuild packageName = do
    let cabalFile = packageName ++ ".cabal"
    run "cabal sandbox init"
    run "cabal update"
    add cabalFile ("/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

License

GPLv3