readme-lhs: See readme.md

[ bsd3, deprecated, development, library, program ] [ Propose Tags ]
Deprecated

See readme.md for description.


[Skip to Readme]

Modules

[Index] [Quick Jump]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 0.2.0, 0.2.1, 0.2.2, 0.3.0, 0.4.0, 0.5.0, 0.6.0, 0.7.0, 0.8.0, 0.8.1
Dependencies base (>=4.7 && <5), containers, pandoc, pandoc-types, protolude, readme-lhs, text [details]
License BSD-3-Clause
Copyright 2016 Tony Day
Author Tony Day
Maintainer tonyday567@gmail.com
Category Development
Home page https://github.com/tonyday567/readme-lhs#readme
Bug tracker https://github.com/tonyday567/readme-lhs/issues
Source repo head: git clone https://github.com/tonyday567/readme-lhs
Uploaded by tonyday567 at 2019-10-24T03:56:11Z
Distributions
Reverse Dependencies 1 direct, 0 indirect [details]
Executables readme-lhs-example
Downloads 3316 total (23 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2019-10-24 [all 1 reports]

Readme for readme-lhs-0.2.2

[back to package description]

readme-lhs Build Status

The language in which we express our ideas has a strong influence on our thought processes. Knuth

ghc options

{-# OPTIONS_GHC -Wall #-}

pragmas

{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleInstances #-}

libraries

import Protolude
import Readme.Lhs

code

main :: IO ()
main = do
  let n = 10
  let answer = product [1..n::Integer]
  void $ runOutput ("example.lhs", LHS) ("readme.md", GitHubMarkdown) $ do
    output "example1" (Fence "Simple example of an output")
Simple example of an output
    output "example2" (Fence (show answer))

10! is equal to:

3628800

As well as fenced output, output can be Text that replaces the {.output} code block

    output "example3" (Replace "Fenced code block was overwritten")

Fenced code block was overwritten

or be native pandoc.

    output "example4" (Native [BulletList [[plain "a"], [plain "bullet"], [plain "list"]]])
  • a
  • bullet
  • list

Output that doesn’t exist is simply cleared.

Fenced code block was overwritten

Technicals

This is an example of mixing literate haskell with markdown, and in using readme-lhs. The file is composed of several elements:

  • literate haskell. Bird-tracks are used, as the alternative lhs method is latex. Pandoc can read this, but defaults to bird tracks when rendering markdown+lhs.

  • markdown. All non bird-tracked lines are considered to be markdown. It’s probably incompatible with haddock. This might be easily fixable.

  • fenced code blocks with an output class, which are used to insert computation results. The fenced code blocks look like:

    ```{.output .example} ```

As it currently stands, ghc cannot read a file with fenced code-blocks that look like:

\```haskell
\```

Given this, a file cannot be both a valid haskell file, and a markdown file that is rendered nicely by github. This would resolve with adoption of the literate markdown ghc proposal.

template

A bare bones stack template is located in other/readme-lhs.hsfiles. It contains what you need to quickly get started with literate programming.

workflow

stack build --test --exec "$(stack path --local-install-root)/bin/readme-lhs-example" --file-watch