dockerfile-creator

[ bsd3, library, unclassified ] [ Propose Tags ]

Embedded DSL to create Dockerfiles using Haskell. Please see the README on GitHub at https://github.com/hadolint/dockerfile-creator#readme


[Skip to Readme]

Modules

[Last Documentation]

  • Language
    • Docker
      • Language.Docker.Creator
      • Language.Docker.EDSL
        • Language.Docker.EDSL.Quasi

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 0.1.1.0
Dependencies base (>=4.7 && <5), bytestring (>=0.10), data-default-class, free, language-docker (>=8.1), megaparsec (>=8.0), mtl, template-haskell, text, th-lift, th-lift-instances, time [details]
License BSD-3-Clause
Copyright 2020 José Lorenzo Rodríguez
Author José Loreno Rodríguez
Maintainer jose.zap@gmail.com
Home page https://github.com/hadolint/dockerfile-creator#readme
Bug tracker https://github.com/hadolint/dockerfile-creator/issues
Source repo head: git clone https://github.com/hadolint/dockerfile-creator
Uploaded by lorenzo at 2020-06-02T09:30:07Z
Distributions
Downloads 383 total (9 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs not available [build log]
All reported builds failed as of 2020-06-02 [all 3 reports]

Readme for dockerfile-creator-0.1.0.0

[back to package description]

dockerfile-composer

Build Dockerfiles using Haskell with an embedded DSL.

Pretty-printing files

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

Writing Dockerfiles in Haskell

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedLists #-}
import Language.Docker

main = putDockerfileStr $ do
    from "node"
    run "apt-get update"
    run ["apt-get", "install", "something"]
    -- ...

Using the QuasiQuoter

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes       #-}
import Language.Docker
main = putDockerfileStr $ 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)
import qualified Data.Text.Lazy.IO as L

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 = toDockerfileText $ do
            from ("haskell" `tagged` tag)
            cabalSandboxBuild "mypackage"
        L.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)
import qualified Data.Text.Lazy.IO    as L

main = do
    str <- toDockerfileTextIO $ 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/"
    L.putStr str