| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Converter
Description
Terms
- format- specific encoding of some information. See- Format.
- document-- Textin a specific format, e.g.,- Haskell(- .hs) file.
- document block- consecutive lines of a document.
- Token- a representation of a document block as a- Haskelltype.
- 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- Tokensto a document. Example:- hsFromTokens.
- tag- a marker that affects how- Tokensare 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- TeXtag, 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 DisabledTokenand 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:
- Tokensare in the same order as the corresponding blocks of document.
- Lines inside - Tokensare reversed compared to the document. Example:- Literate Haskelldocument:- 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.
There are several forms of Haskell code blocks in Literate Haskell recognized by GHC.
- Code between - begin{code}and- end{code}tags.- begin{code} a = 42 end{code} begin{code} b = a end{code}- The line starting with begin{code}cannot have other non-space characters afterbegin{code}.
- The indentation of all expressions in code blocks must be the same.
 
- The line starting with 
- Code lines starting with - '> '.- begin{mycode} > a = 42 end{mycode} begin{mycode} > b = a end{mycode}- There must be at least a single empty line before and after each Haskellcode block.
- Any text may surround Haskellcode blocks.
- The indentation of all expressions in code blocks must be the same.
 
- There must be at least a single empty line before and after each 
This library supports only the second form as this form is more versatile.
Moreover, this form does not require writing Markdown tags like '```haskell'.
Such tags will automatically be printed when converting Literate Haskell to Markdown.
Synopsis
- type family Mode a where ...
- type User = 'User
- type Internal = 'Internal
- data Config (a :: Mode') = Config {- _disable :: Mode a
- _enable :: Mode a
- _indent :: Mode a
- _dedent :: Mode a
- _mdHaskellCodeStart :: Mode a
- _mdHaskellCodeEnd :: Mode a
- _texHaskellCodeStart :: Mode a
- _texHaskellCodeEnd :: Mode a
- _texSingleLineCommentStart :: Mode a
- _lhsSingleLineCommentStart :: Mode a
 
- def :: Default a => a
- toConfigInternal :: Config User -> Config Internal
- disable :: forall a. Lens' (Config a) (Mode a)
- enable :: forall a. Lens' (Config a) (Mode a)
- indent :: forall a. Lens' (Config a) (Mode a)
- dedent :: forall a. Lens' (Config a) (Mode a)
- mdHaskellCodeStart :: forall a. Lens' (Config a) (Mode a)
- mdHaskellCodeEnd :: forall a. Lens' (Config a) (Mode a)
- texHaskellCodeStart :: forall a. Lens' (Config a) (Mode a)
- texHaskellCodeEnd :: forall a. Lens' (Config a) (Mode a)
- texSingleLineCommentStart :: forall a. Lens' (Config a) (Mode a)
- lhsSingleLineCommentStart :: forall a. Lens' (Config a) (Mode a)
- (&) :: a -> (a -> b) -> b
- (?~) :: ASetter s t a (Maybe b) -> b -> s -> t
- data Format
- convertTo :: Format -> Format -> Config User -> Text -> Text
- showFormatExtension :: Format -> String
- showFormatName :: Format -> String
- data Token
- type Tokens = [Token]
- selectFromTokens :: Config User -> Format -> Tokens -> Text
- selectToTokens :: Config User -> Format -> Text -> Tokens
- mergeTokens :: Tokens -> Tokens
- stripTokens :: Tokens -> Tokens
- normalizeTokens :: Tokens -> Tokens
- hsFromTokens :: Config User -> Tokens -> Text
- hsFromTokens' :: Config User -> Tokens -> [Text]
- lhsFromTokens :: Config User -> Tokens -> Text
- lhsFromTokens' :: Config User -> Tokens -> [Text]
- mdFromTokens :: Config User -> Tokens -> Text
- mdFromTokens' :: Config User -> Tokens -> [Text]
- texFromTokens :: Config User -> Tokens -> Text
- texFromTokens' :: Config User -> Tokens -> [Text]
- hsToTokens :: Config User -> Text -> Tokens
- lhsToTokens :: Config User -> Text -> Tokens
- mdToTokens :: Config User -> Text -> Tokens
- texToTokens :: Config User -> Text -> Tokens
- mkFromTokens :: (Config User -> Tokens -> [Text]) -> Config User -> Tokens -> Text
- mkToTokens :: (State -> [(Int, Text)] -> [Token] -> [Token]) -> Text -> Tokens
- parseLineToToken :: Config Internal -> Format -> Token -> Text -> Int -> Tokens
- errorExpectedToken :: (Data a1, Show a2, Show a3) => a2 -> a3 -> a1 -> a4
- errorNotEnoughTokens :: Format -> a
- pp :: PrettyPrint a => a -> Pretty String
- exampleNonTexTokens' :: Tokens
- exampleNonTexTokens :: Tokens
- exampleTexTokens :: Tokens
Config
data Config (a :: Mode') Source #
Configuration of tag names.
The default values of Config User are all Nothings.
Inside the library functions, Config User is converted to Config Internal.
The below examples show the names from Config Internal.
>>>pp (def :: Config User)Config { _disable = "LIMA_DISABLE", _enable = "LIMA_ENABLE", _indent = "LIMA_INDENT", _dedent = "LIMA_DEDENT", _mdHaskellCodeStart = "```haskell", _mdHaskellCodeEnd = "```", _texHaskellCodeStart = "\\begin{mycode}", _texHaskellCodeEnd = "\\end{mycode}", _texSingleLineCommentStart = "SINGLE_LINE ", _lhsSingleLineCommentStart = "SINGLE_LINE " }
It's possible to override these names.
>>>pp ((def :: Config User) & disable ?~ "off" & enable ?~ "on" & indent ?~ "indent" & dedent ?~ "dedent")Config { _disable = "off", _enable = "on", _indent = "indent", _dedent = "dedent", _mdHaskellCodeStart = "```haskell", _mdHaskellCodeEnd = "```", _texHaskellCodeStart = "\\begin{mycode}", _texHaskellCodeEnd = "\\end{mycode}", _texSingleLineCommentStart = "SINGLE_LINE ", _lhsSingleLineCommentStart = "SINGLE_LINE " }
Constructors
| Config | |
| Fields 
 | |
Instances
Lenses
microlens
Format
A format of a document.
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
Constructors
| Indent | 
 | 
| Dedent | 
 | 
| Disabled | A block that should be invisible when rendered outside of  
 | 
| HaskellCode | Lines copied verbatim while a parser was in a  | 
| Text | Lines copied verbatim while a parser was in a text block. | 
| Comment | Lines copied verbatim while a parser was in a comment block. | 
| CommentSingleLine | A line of a comment that must be kept on a single-line. E.g., {- FOURMOLU_DISABLE -} from a  | 
Instances
| Data Token Source # | |
| 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 # 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 # | |
| Eq Token Source # | |
| PrettyPrint Tokens Source # | |
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!" :| []}, CommentSingleLine {someLine = "Comment on a single line."}, Text {someLines = "Hello from text," :| []}, Text {someLines = "world!" :| []} ]
>>>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,"]}, CommentSingleLine {someLine = "Comment on a single line."}, Text {someLines = "world!" :| ["","Hello from text,"]} ]
stripTokens :: Tokens -> Tokens Source #
Strip empty lines and leading spaces in Tokens.
- Remove empty lines in Tokens.
- Shift lines in HaskellCodeto 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!" :| []}, CommentSingleLine {someLine = "Comment on a single line."}, Text {someLines = "Hello from text," :| []}, Text {someLines = "world!" :| []} ]
>>>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!" :| []}, CommentSingleLine {someLine = "Comment on a single line."}, Text {someLines = "Hello from text," :| []}, Text {someLines = "world!" :| []} ]
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,"]}, CommentSingleLine {someLine = "Comment on a single line."}, Text {someLines = "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 - Tokensand document blocks when the default- Configvalues are used.- Indent~- '{- LIMA_INDENT N -}'where- Nis an- Int.
- Dedent~- '{- LIMA_DEDENT -}'.
- Disabled~- '{- LIMA_DISABLE -}'and- '{- LIMA_ENABLE -}'and lines between them.- {- LIMA_DISABLE -} disabled {- LIMA_ENABLE -}
- Text~ a multiline comment starting with- '{-\n'and ending with- '\n-}'.- {- line 1 -}
- CommentSingleLine~ a multiline comment on a single line.- {- line -}
- Comment~ a multiline comment starting with- '{- TEXT', where- TEXTis nonempty text, and ending with- \n-}- {- line 1 line 2 -}
- HaskellCode~ other lines.
 
Example
>>>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! -} {- Comment on a single line. -} {- Hello from text, world! -}
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 - Configvalues are used.- Indent~- '% LIMA_INDENT N'(- Nis an- Int).
- Dedent~- '% LIMA_DEDENT'.
- Disabled~ Lines between and including- '% LIMA_DISABLE'and- '% LIMA_ENABLE'.- There must be at least one nonempty line between these tags.
 
- CommentSingleLine~ a line starting with- '% SINGLE_LINE '.- % SINGLE_LINE line 
- Comment~ consecutive lines, either empty or starting with- '% '.- % Hello, % world! % Hello, % user! - At least one line must have nonempty text after '% '
 
- At least one line must have nonempty text after 
- HaskellCode~ consecutive lines starting with- '> '.- > a4 = 4 > a2 = 2 - Inside a Token, code is shifted to the left. SeenormalizeTokens.
- During printing, code is indented according to previous Tokens.
 
- Inside a 
- Text~ other lines.
 
Example
>>>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! % SINGLE_LINE Comment on a single line. Hello from text, world!
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 - Configvalues are used.- Indent~- '<!-- LIMA_INDENT N -->', where- Nis an- Int.
- Dedent~- '<!-- LIMA_DEDENT -->'.
- Disabled~ a multiline comment starting with- '<!-- LIMA_DISABLE\n'and ending with- '\nLIMA_ENABLE -->'.- <!-- LIMA_DISABLE a4 = 4 a2 = 2 LIMA_ENABLE --> 
- CommentSingleLine~ a line starting with- '<!-- 'and ending with- ' -->'.- line -- 
- Comment~ a multiline comment starting with- '<!-- {text}', where- {text}is nonempty text.- <!-- line 1 line 2 --> 
- HaskellCode~ possibly indented block starting with- '```haskell'and ending with- '```'.- ```haskell a4 = 2 ```
- Text~ other lines.
 
Example
>>>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! --> <!-- Comment on a single line. --> Hello from text, world!
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 tokens and document blocks when the default - Configvalues are used.- Indent~- '% LIMA_INDENT N'(- Nis an- Int).
- Dedent~- '% LIMA_DEDENT'.
- Disabled~- '% LIMA_DISABLE'and- '% LIMA_ENABLE'and lines between them.
- CommentSingleLine~ a line starting with- '% SINGLE_LINE '.- % SINGLE_LINE line 
- Comment~ consecutive lines, either empty or starting with- '% '.- % Hello, % world! % Hello, % user! - At least one line must have nonempty text after '% '.
 
- At least one line must have nonempty text after 
- HaskellCode~ lines between possibly indented tags- '\begin{code}'and- '\end{code}'.- Inside a Token, code will be shifted to the left. SeenormalizeTokens.
- When printing the Tokens, code will be indented according to previousTokens.
 
- Inside a 
- Text~ other lines.
 
Example
>>>pp $ texFromTokens def exampleTexTokens% LIMA_INDENT 3 % LIMA_DISABLE % -- What's the answer? % LIMA_ENABLE % LIMA_INDENT 1 % LIMA_INDENT 0 Intermediate results \begin{mycode} a = const 3 b = a 4 \end{mycode} % LIMA_DEDENT \begin{mycode} answer = b * 14 \end{mycode} % Hello from comments, % world! % SINGLE_LINE Comment on a single line.
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
hsToTokens :: Config User -> Text -> Tokens Source #
Convert Tokens to Haskell code.
Inverse of hsFromTokens.
>>>(hsToTokens def $ hsFromTokens def exampleNonTexTokens) == exampleNonTexTokensTrue
lhsToTokens :: Config User -> Text -> Tokens Source #
Convert Tokens to Markdown code.
Inverse of lhsFromTokens.
>>>(lhsToTokens def $ lhsFromTokens def exampleNonTexTokens) == exampleNonTexTokensTrue
mdToTokens :: Config User -> Text -> Tokens Source #
Convert Tokens to Markdown code.
Inverse of mdFromTokens.
>>>(mdToTokens def $ mdFromTokens def exampleNonTexTokens) == exampleNonTexTokensTrue
texToTokens :: Config User -> Text -> Tokens Source #
Convert Tokens to TeX code.
Inverse of texFromTokens.
>>>(texToTokens def $ texFromTokens def exampleTexTokens) == exampleTexTokensTrue
Helpers
parseLineToToken :: Config Internal -> Format -> Token -> Text -> Int -> Tokens Source #
Parse a single line to a token.
- Merge comments
errorExpectedToken :: (Data a1, Show a2, Show a3) => a2 -> a3 -> a1 -> a4 Source #
Show error with line number for a token.
errorNotEnoughTokens :: Format -> a Source #
pp :: PrettyPrint a => a -> Pretty String Source #
A printing function
It's not meant to be used outside of this library.
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!" :| []}, CommentSingleLine {someLine = "Comment on a single line."}, Text {someLines = "Hello from text," :| []}, Text {someLines = "world!" :| []} ]
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,"]}, CommentSingleLine {someLine = "Comment on a single line."}, Text {someLines = "world!" :| ["","Hello from text,"]} ]
exampleTexTokens :: Tokens Source #
same as exampleNonTexTokens, but with TeX-specific tags that make Haskell code blocks correctly parsable.
>>>pp $ exampleTexTokens[ Indent {n = 3}, Disabled {manyLines = ["-- What's the answer?"]}, Indent {n = 1}, Indent {n = 0}, Text {someLines = "\\begin{mycode}" :| ["","Intermediate results"]}, HaskellCode {manyLines = ["b = a 4","a = const 3"]}, Text {someLines = "\\end{mycode}" :| []}, Dedent, Text {someLines = "\\begin{mycode}" :| []}, HaskellCode {manyLines = ["answer = b * 14"]}, Text {someLines = "\\end{mycode}" :| []}, Comment {someLines = "world!" :| ["","Hello from comments,"]}, CommentSingleLine {someLine = "Comment on a single line."} ]