lima-0.2.0.0: Convert between Haskell, Markdown, Literate Haskell, TeX
Safe HaskellSafe-Inferred
LanguageHaskell2010

Converter

Description

Terms

  • format - specific encoding of some information. See Format.
  • document - Text in a specific format, e.g., Haskell (.hs) file.
  • document block - consecutive lines of a document.
  • Token - a representation of a document block as a Haskell type.
  • Tokens - a list of Tokens.
  • parser - a function that reads a document line by line and converts it to Tokens. Example: hsToTokens.
  • printer - a function that converts Tokens to a document. Example: hsFromTokens.
  • tag - a marker that affects how Tokens are parsed.

    • Each parser recognizes tags of a specific form.
    • Tags can be represented as a wrapper and a name.

      E.g., in '% LIMA_DISABLE some text', a TeX tag, the wrapper is '% ' and the name is 'LIMA_DISABLE some text'.

    • Parsers recognize the tag names that start with tag names specified in a Config.

      E.g., in the example above, a parser will recognize the _disable tag and will become disabled.

    • When a parser is disabled, it copies lines verbatim into a Disabled Token and doesn't recognize any tags until it finds an _enable tag.

Assumptions

The following assumptions must hold for outputs of parsers and inputs of printers:

  • Tokens are in the same order as the corresponding blocks of document.
  • Lines inside Tokens are reversed compared to the document. Example:

    • Literate Haskell document:

      line 1
      line 2
      
      % line 3
      
      % line 4
      
    • Corresponding Tokens:

      [
        Text {manyLines = ["line2","line 1"]},
        Comment {someLines = "line 4" :| ["", "line 3"]}
      ]
      
  • There are no leading or trailing empty lines inside of Tokens.
Synopsis

Config

type family Mode a b where ... Source #

Calculates the mode for data.

Equations

Mode User b = Maybe b 
Mode Internal b = b 

type User = 'User Source #

Marks data supplied by a user.

type Internal = 'Internal Source #

Marks data for internal usage.

data Config (a :: Mode') Source #

Configuration of tag names.

Here are the default names.

>>> pp (def :: Config User)
Config {
  _disable = Just "LIMA_DISABLE",
  _enable = Just "LIMA_ENABLE",
  _indent = Just "LIMA_INDENT",
  _dedent = Just "LIMA_DEDENT",
  _mdHaskellCodeStart = Just "```haskell",
  _mdHaskellCodeEnd = Just "```",
  _texHaskellCodeStart = Just "\\begin{code}",
  _texHaskellCodeEnd = Just "\\end{code}"
}

It's possible to override these names.

>>> pp ((def :: Config User) & disable ?~ "off" & enable ?~ "on" & indent ?~ "indent" & dedent ?~ "dedent")
Config {
  _disable = Just "off",
  _enable = Just "on",
  _indent = Just "indent",
  _dedent = Just "dedent",
  _mdHaskellCodeStart = Just "```haskell",
  _mdHaskellCodeEnd = Just "```",
  _texHaskellCodeStart = Just "\\begin{code}",
  _texHaskellCodeEnd = Just "\\end{code}"
}

Constructors

Config 

Fields

Instances

Instances details
Generic (Config a) Source # 
Instance details

Defined in Converter

Associated Types

type Rep (Config a) :: Type -> Type #

Methods

from :: Config a -> Rep (Config a) x #

to :: Rep (Config a) x -> Config a #

Show (Config Internal) Source # 
Instance details

Defined in Converter

Show (Config User) Source # 
Instance details

Defined in Converter

Default (Config Internal) Source # 
Instance details

Defined in Converter

Methods

def :: Config Internal #

Default (Config User) Source # 
Instance details

Defined in Converter

Methods

def :: Config User #

Eq (Config User) Source # 
Instance details

Defined in Converter

PrettyPrint (Config User) Source # 
Instance details

Defined in Converter

Methods

pp :: Config User -> Pretty String Source #

type Rep (Config a) Source # 
Instance details

Defined in Converter

def :: Default a => a #

The default value for this type.

toInternalConfig :: Config User -> Config Internal Source #

Convert a user Config to an internal Config with user-supplied values.

fromInternalConfig :: Config Internal -> Config User Source #

Make a user Config with default values from an internal Config.

Lenses

disable :: forall a. Lens' (Config a) (Mode a Text) Source #

enable :: forall a. Lens' (Config a) (Mode a Text) Source #

indent :: forall a. Lens' (Config a) (Mode a Text) Source #

dedent :: forall a. Lens' (Config a) (Mode a Text) Source #

microlens

(&) :: a -> (a -> b) -> b infixl 1 #

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

>>> 5 & (+1) & show
"6"

Since: base-4.8.0.0

(?~) :: ASetter s t a (Maybe b) -> b -> s -> t infixr 4 #

(?~) is a version of (.~) that wraps the value into Just before setting.

l ?~ b = l .~ Just b

It can be useful in combination with at:

>>> Map.empty & at 3 ?~ x
fromList [(3,x)]

Format

data Format Source #

A format of a document.

Constructors

Hs
Haskell
Lhs
Literate Haskell
Md
Markdown
TeX
TeX

convertTo :: Format -> Format -> Config User -> Text -> Text Source #

Compose a function that converts a document in one Format to a document in another Format.

showFormatExtension :: Format -> String Source #

Show a Format as a file extension.

>>> showFormatExtension Lhs
"lhs"

showFormatName :: Format -> String Source #

Show a Format as a full name.

>>> showFormatName Lhs
"Literate Haskell"

Tokens

data Token Source #

Internal representation of a document.

A printer processes a list of Tokens one by one.

A Token can have:

  • Action - how this Token affects the subsequent Tokens.
  • Target - a type of Tokens that are affected by this Token.
  • Range - the nearest Token until which this Token affects the subsequent Tokens.

Constructors

Indent

Fields

Dedent
Disabled

A block that should be invisible when rendered outside of .hs.

Fields

HaskellCode

Lines copied verbatim while a parser was in a Haskell code block.

Fields

Text

Lines copied verbatim while a parser was in a text block.

Comment

Lines copied verbatim while a parser was in a comment block.

Instances

Instances details
Data Token Source # 
Instance details

Defined in Converter

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Token -> c Token #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Token #

toConstr :: Token -> Constr #

dataTypeOf :: Token -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Token) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Token) #

gmapT :: (forall b. Data b => b -> b) -> Token -> Token #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Token -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Token -> r #

gmapQ :: (forall d. Data d => d -> u) -> Token -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Token -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Token -> m Token #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Token -> m Token #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Token -> m Token #

Show Token Source # 
Instance details

Defined in Converter

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Eq Token Source # 
Instance details

Defined in Converter

Methods

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

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

PrettyPrint Tokens Source # 
Instance details

Defined in Converter

Methods

pp :: Tokens -> Pretty String Source #

type Tokens = [Token] Source #

A list of Tokens.

selectFromTokens :: Config User -> Format -> Tokens -> Text Source #

Select a printer function based on a given format.

selectToTokens :: Config User -> Format -> Text -> Tokens Source #

Select a parser function based on a given format.

mergeTokens :: Tokens -> Tokens Source #

Merge specific consecutive Tokens.

>>> pp exampleNonTexTokens'
[
  Indent {n = 3},
  Disabled {manyLines = ["-- What's the answer?"]},
  Indent {n = 1},
  Indent {n = 2},
  Text {someLines = "- Intermediate results" :| []},
  HaskellCode {manyLines = ["   b = a 4","   a = const 3"]},
  Dedent,
  HaskellCode {manyLines = ["answer = b * 14"]},
  Comment {someLines = "Hello from comments," :| []},
  Comment {someLines = "world!" :| []},
  Text {someLines = "world!" :| ["Hello from text,"]},
  Text {someLines = "here!" :| ["And from"]}
]
>>> pp $ mergeTokens exampleNonTexTokens'
[
  Indent {n = 3},
  Disabled {manyLines = ["-- What's the answer?"]},
  Indent {n = 1},
  Indent {n = 2},
  Text {someLines = "- Intermediate results" :| []},
  HaskellCode {manyLines = ["   b = a 4","   a = const 3"]},
  Dedent,
  HaskellCode {manyLines = ["answer = b * 14"]},
  Comment {someLines = "world!" :| ["","Hello from comments,"]},
  Text {someLines = "here!" :| ["And from","","world!","Hello from text,"]}
]

stripTokens :: Tokens -> Tokens Source #

Strip empty lines an leading spaces in Tokens.

  • Remove empty lines in Tokens.
  • Shift lines in HaskellCode to the left by the minimal number of leading spaces in nonempty lines.
>>> pp exampleNonTexTokens'
[
  Indent {n = 3},
  Disabled {manyLines = ["-- What's the answer?"]},
  Indent {n = 1},
  Indent {n = 2},
  Text {someLines = "- Intermediate results" :| []},
  HaskellCode {manyLines = ["   b = a 4","   a = const 3"]},
  Dedent,
  HaskellCode {manyLines = ["answer = b * 14"]},
  Comment {someLines = "Hello from comments," :| []},
  Comment {someLines = "world!" :| []},
  Text {someLines = "world!" :| ["Hello from text,"]},
  Text {someLines = "here!" :| ["And from"]}
]
>>> pp $ stripTokens exampleNonTexTokens'
[
  Indent {n = 3},
  Disabled {manyLines = ["-- What's the answer?"]},
  Indent {n = 1},
  Indent {n = 2},
  Text {someLines = "- Intermediate results" :| []},
  HaskellCode {manyLines = ["b = a 4","a = const 3"]},
  Dedent,
  HaskellCode {manyLines = ["answer = b * 14"]},
  Comment {someLines = "Hello from comments," :| []},
  Comment {someLines = "world!" :| []},
  Text {someLines = "world!" :| ["Hello from text,"]},
  Text {someLines = "here!" :| ["And from"]}
]

normalizeTokens :: Tokens -> Tokens Source #

mergeTokens and stripTokens.

>>> pp $ normalizeTokens exampleNonTexTokens
[
  Indent {n = 3},
  Disabled {manyLines = ["-- What's the answer?"]},
  Indent {n = 1},
  Indent {n = 2},
  Text {someLines = "- Intermediate results" :| []},
  HaskellCode {manyLines = ["b = a 4","a = const 3"]},
  Dedent,
  HaskellCode {manyLines = ["answer = b * 14"]},
  Comment {someLines = "world!" :| ["","Hello from comments,"]},
  Text {someLines = "here!" :| ["And from","","world!","Hello from text,"]}
]

Printers

hsFromTokens :: Config User -> Tokens -> Text Source #

Convert Tokens to Haskell code.

Rules

  • Certain assumptions must hold for inputs.
  • These are the relations between document blocks and tokens when the default Config values are used.

    • '{- LIMA_INDENT N -}' (N is an Int) ~ Indent.
    • '{- LIMA_DEDENT -}' ~ Dedent.
    • Lines between and including '{- LIMA_DISABLE -}' and '{- LIMA_ENABLE -}' ~ Disabled.
    • Multiline comment starting with '{-\n' ~ Text.

      {-
      line 1
      -}
      
      • Consecutive Texts are merged into a single Text.
      • There must be at list one nonempty line inside this comment.
    • Multiline comment starting with '{- ' where text is nonempty text ~ Comment.

      {- line 1
      line 2
      -}
      
    • Other lines ~ HaskellCode.

      a = 42
      

Example

Expand
>>> pp $ hsFromTokens def exampleNonTexTokens
{- LIMA_INDENT 3 -}

{- LIMA_DISABLE -}

-- What's the answer?

{- LIMA_ENABLE -}

{- LIMA_INDENT 1 -}

{- LIMA_INDENT 2 -}

{-
- Intermediate results
-}

a = const 3
b = a 4

{- LIMA_DEDENT -}

answer = b * 14

{- Hello from comments,

world!
-}

{-
Hello from text,
world!

And from
here!
-}

hsFromTokens' :: Config User -> Tokens -> [Text] Source #

Convert Tokens to Haskell code.

Each Token becomes a Text in a list.

These Texts are concatenated in hsFromTokens.

lhsFromTokens :: Config User -> Tokens -> Text Source #

Convert Tokens to Literate Haskell code.

Rules

  • Certain assumptions must hold for inputs.
  • These are the relations between document blocks and tokens when the default Config values are used.

    • '% LIMA_INDENT N' (N is an Int) ~ Indent.
    • '% LIMA_DEDENT' ~ Dedent.
    • Lines between and including '% LIMA_DISABLE' and '% LIMA_ENABLE' ~ Disabled.

      • There must be at least one nonempty line between these tags.
    • Consecutive lines, either empty or starting with '% ' ~ Comment.

      % Hello,
      % world!
      
      % Hello,
      % user!
      
      • At least one line must have nonempty text after '% '
    • Consecutive lines starting with '> ' ~ HaskellCode.

      > a4 = 4
      > a2 = 2
      
    • Other lines ~ Text.

Example

Expand
>>> pp $ lhsFromTokens def exampleNonTexTokens
% LIMA_INDENT 3

% LIMA_DISABLE

% -- What's the answer?

% LIMA_ENABLE

% LIMA_INDENT 1

% LIMA_INDENT 2

- Intermediate results
>   a = const 3
>   b = a 4

% LIMA_DEDENT

> answer = b * 14

% Hello from comments,

% world!

Hello from text,
world!

And from
here!

lhsFromTokens' :: Config User -> Tokens -> [Text] Source #

Convert Tokens to Literate Haskell code.

Each Token becomes a Text in a list.

These Texts are concatenated in lhsFromTokens.

mdFromTokens :: Config User -> Tokens -> Text Source #

Convert Tokens to Markdown code.

Rules

  • Certain assumptions must hold for inputs.
  • These are the relations between document blocks and tokens when the default Config values are used.

    • '<!-- LIMA_INDENT N -->' (N is an Int) ~ Indent
    • '<!-- LIMA_DEDENT -->' ~ Dedent.
    • Multiline comment starting with '<!-- LIMA_DISABLE\n' and ending with '\nLIMA_ENABLE -->' ~ Disabled.

      <!-- LIMA_DISABLE
      a4 = 4
      a2 = 2
      LIMA_ENABLE -->
      
    • Multiline comments starting with '<!-- {text}' where {text} is nonempty text ~ Comment.

      <!-- line 1
      line 2
      -->
      
    • Possibly indented block starting with '```haskell' and ending with '```' ~ HaskellCode.

        ```haskell
          a4 = 2
        ```
      
    • Other lines ~ Text.

      Hello, world!
      

Example

Expand
>>> pp $ mdFromTokens def exampleNonTexTokens
   <!-- LIMA_INDENT 3 -->

<!-- LIMA_DISABLE

-- What's the answer?

LIMA_ENABLE -->

 <!-- LIMA_INDENT 1 -->

  <!-- LIMA_INDENT 2 -->

- Intermediate results

  ```haskell
  a = const 3
  b = a 4
  ```

<!-- LIMA_DEDENT -->

```haskell
answer = b * 14
```

<!-- Hello from comments,

world!
-->

Hello from text,
world!

And from
here!

mdFromTokens' :: Config User -> Tokens -> [Text] Source #

Convert Tokens to Haskell code.

Each Token becomes a Text in a list.

These Texts are concatenated in mdFromTokens.

texFromTokens :: Config User -> Tokens -> Text Source #

Convert Tokens to TeX code.

Rules

  • Certain assumptions must hold for inputs.
  • These are the relations between document blocks and tokens when the default Config values are used.

    • '% LIMA_INDENT N' (N is an Int) ~ Indent
    • '% LIMA_DEDENT' ~ Dedent.
    • Lines between and including '% LIMA_DISABLE' and '% LIMA_ENABLE' ~ Disabled.
    • Consecutive lines, either empty or starting with '% ' ~ Comment.

      % Hello,
      % world!
      
      % Hello,
      % user!
      
      • At least one line must have nonempty text after '% '
    • Lines between possibly indented tags '\begin{code}' and '\end{code}' ~ HaskellCode.
    • Other lines ~ Text.

Example

Expand
>>> pp $ texFromTokens def exampleTexTokens
% LIMA_DISABLE

% -- What's the answer?

% LIMA_ENABLE

% LIMA_INDENT 1

% LIMA_INDENT 2

Intermediate results

\begin{code}
  a = const 3
  b = a 4
\end{code}

% LIMA_DEDENT

\begin{code}
answer = b * 14
\end{code}

% Hello from comments,

% world!

Hello from text,
world!

texFromTokens' :: Config User -> Tokens -> [Text] Source #

Convert Tokens to TeX code.

Each Token becomes a Text in a list.

These Texts are concatenated in texFromTokens.

Parsers

lhsToTokens :: Config User -> Text -> Tokens Source #

Convert Tokens to Markdown code.

Inverse of lhsFromTokens.

>>> (lhsToTokens def $ lhsFromTokens def exampleNonTexTokens) == exampleNonTexTokens
True

hsToTokens :: Config User -> Text -> Tokens Source #

Convert Tokens to Haskell code.

Inverse of hsFromTokens.

>>> (hsToTokens def $ hsFromTokens def exampleNonTexTokens) == exampleNonTexTokens
True

texToTokens :: Config User -> Text -> Tokens Source #

Convert Tokens to TeX code.

Inverse of texFromTokens.

>>> (texToTokens def $ texFromTokens def exampleTexTokens) == exampleTexTokens
True

mdToTokens :: Config User -> Text -> Tokens Source #

Convert Tokens to Markdown code.

Inverse of mdFromTokens.

>>> (mdToTokens def $ mdFromTokens def exampleNonTexTokens) == exampleNonTexTokens
True

Examples

exampleNonTexTokens' :: Tokens Source #

Example non-TeX Tokens. See exampleTexTokens.

When printed to a TeX document, these Tokens can't be correctly parsed. This is because they don't have necessary tags surrounding Haskell code blocks.

>>> pp $ exampleNonTexTokens'
[
  Indent {n = 3},
  Disabled {manyLines = ["-- What's the answer?"]},
  Indent {n = 1},
  Indent {n = 2},
  Text {someLines = "- Intermediate results" :| []},
  HaskellCode {manyLines = ["   b = a 4","   a = const 3"]},
  Dedent,
  HaskellCode {manyLines = ["answer = b * 14"]},
  Comment {someLines = "Hello from comments," :| []},
  Comment {someLines = "world!" :| []},
  Text {someLines = "world!" :| ["Hello from text,"]},
  Text {someLines = "here!" :| ["And from"]}
]

exampleNonTexTokens :: Tokens Source #

Normalized exampleNonTexTokens'.

>>> pp $ exampleNonTexTokens
[
  Indent {n = 3},
  Disabled {manyLines = ["-- What's the answer?"]},
  Indent {n = 1},
  Indent {n = 2},
  Text {someLines = "- Intermediate results" :| []},
  HaskellCode {manyLines = ["b = a 4","a = const 3"]},
  Dedent,
  HaskellCode {manyLines = ["answer = b * 14"]},
  Comment {someLines = "world!" :| ["","Hello from comments,"]},
  Text {someLines = "here!" :| ["And from","","world!","Hello from text,"]}
]

exampleTexTokens :: Tokens Source #

same as exampleNonTexTokens, but with TeX-specific tags that make Haskell code blocks correctly parsable.

>>> pp $ exampleTexTokens
[
  Disabled {manyLines = ["-- What's the answer?"]},
  Indent {n = 1},
  Indent {n = 2},
  Text {someLines = "\\begin{code}" :| ["","Intermediate results"]},
  HaskellCode {manyLines = ["b = a 4","a = const 3"]},
  Text {someLines = "\\end{code}" :| []},
  Dedent,
  Text {someLines = "\\begin{code}" :| []},
  HaskellCode {manyLines = ["answer = b * 14"]},
  Text {someLines = "\\end{code}" :| []},
  Comment {someLines = "world!" :| ["","Hello from comments,"]},
  Text {someLines = "world!" :| ["Hello from text,"]}
]

Helpers

stripEmpties :: [Text] -> [Text] Source #

Remove empty lines from the beginning and the end of a list.

class Show a => PrettyPrint a where Source #

A class for prettyprinting data on multiple lines in haddocks.

It's not meant to be used outside of this library.

Methods

pp :: a -> Pretty String Source #

Instances

Instances details
PrettyPrint Tokens Source # 
Instance details

Defined in Converter

Methods

pp :: Tokens -> Pretty String Source #

PrettyPrint Text Source # 
Instance details

Defined in Converter

Methods

pp :: Text -> Pretty String Source #

PrettyPrint String Source # 
Instance details

Defined in Converter

Methods

pp :: String -> Pretty String Source #

PrettyPrint (Config User) Source # 
Instance details

Defined in Converter

Methods

pp :: Config User -> Pretty String Source #