diagrams-haddock-0.4.0.3: Preprocessor for embedding diagrams in Haddock documentation

Copyright(c) 2013 diagrams-haddock team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.Haddock

Contents

Description

Include inline diagrams code in Haddock documentation! For example, here is a green circle:

which was literally produced by this code:

greenCircle = circle 1
            # fc green # pad 1.1

For a much better example of the use of diagrams-haddock, see the diagrams-contrib package: http://hackage.haskell.org/package/diagrams%2Dcontrib.

For complete documentation and examples, see https://github.com/diagrams/diagrams-haddock/blob/master/README.md.

Synopsis

Diagram URLs

Haddock supports inline links to images with the syntax <<URL>>. To indicate an image which should be automatically generated from some diagrams code, we use the special syntax <<URL#diagram=name&key1=val1&key2=val2&...>>. The point is that everything following the # will be ignored by browsers, but we can use it to indicate to diagrams-haddock the name of the diagram to be rendered along with options such as size.

data DiagramURL Source #

An abstract representation of inline Haddock image URLs with diagrams tags, like <<URL#diagram=name&width=100>>.

Instances
Eq DiagramURL Source # 
Instance details

Defined in Diagrams.Haddock

Show DiagramURL Source # 
Instance details

Defined in Diagrams.Haddock

displayDiagramURL :: DiagramURL -> String Source #

Display a diagram URL in the format <<URL#diagram=name&key=val&...>>.

parseDiagramURL :: Parser DiagramURL Source #

Parse things of the form <<URL#diagram=name&key=val&...>>. The URL is optional (the #, however, is required).

parseKeyValPair :: Parser (String, String) Source #

Parse a key/value pair of the form &key=val.

maybeParseDiagramURL :: Parser (Either Char DiagramURL) Source #

Parse a diagram URL or a single character which is not the start of a diagram URL.

parseDiagramURLs :: Parser [Either String DiagramURL] Source #

Decompose a string into a parsed form with explicitly represented diagram URLs interspersed with other content.

displayDiagramURLs :: [Either String DiagramURL] -> String Source #

Serialize a parsed comment with diagram URLs back into a String.

Comments

A few miscellaneous functions for dealing with comments.

getDiagramNames :: Comment -> Set String Source #

Get the names of all diagrams referenced from diagram URLs in the given comment.

coalesceComments :: [Comment] -> [(String, Int)] Source #

Given a series of comments, return a list of their contents, coalescing blocks of adjacent single-line comments into one String. Each string will be paired with the number of the line on which it begins.

Code blocks

A code block represents some portion of a comment set off by bird tracks. We also collect a list of the names bound in each code block, in order to decide which code blocks contain expressions representing diagrams that are to be rendered.

data CodeBlock Source #

A CodeBlock represents a portion of a comment which is a valid code block (set off by > bird tracks). It also caches the list of bindings present in the code block.

Instances
Eq CodeBlock Source # 
Instance details

Defined in Diagrams.Haddock

Show CodeBlock Source # 
Instance details

Defined in Diagrams.Haddock

makeCodeBlock :: FilePath -> (String, Int) -> CollectErrors (Maybe CodeBlock) Source #

Given a String representing a code block, i.e. valid Haskell code with any bird tracks already stripped off, along with its beginning line number (and the name of the file from which it was taken), attempt to parse it, extract the list of bindings present, and construct a CodeBlock value.

collectBindings :: Module l -> Set String Source #

Collect the list of names bound in a module.

extractCodeBlocks :: FilePath -> (String, Int) -> CollectErrors [CodeBlock] Source #

From a String representing a comment (along with its beginning line number, and the name of the file it came from, for error reporting purposes), extract all the code blocks (consecutive lines beginning with bird tracks), and error messages for code blocks that fail to parse.

parseCodeBlocks :: FilePath -> String -> CollectErrors (Maybe ([CodeBlock], Set String)) Source #

Take the contents of a Haskell source file (and the name of the file, for error reporting purposes), and extract all the code blocks, as well as the referenced diagram names.

transitiveClosure :: String -> [CodeBlock] -> [CodeBlock] Source #

Given an identifier and a list of CodeBlocks, filter the list of CodeBlocks to the transitive closure of the "depends-on" relation, i.e. only blocks which bind identifiers referenced in blocks ultimately needed by the block which defines the desired identifier.

Diagram compilation

This section contains all the functions which actually interface with diagrams-builder in order to compile diagrams referenced from URLs.

compileDiagram Source #

Arguments

:: Bool

True = quiet

-> Bool

True = generate data URIs

-> FilePath

cache directory

-> FilePath

output directory

-> FilePath

file being processed

-> Set String

diagrams referenced from URLs

-> [CodeBlock] 
-> DiagramURL 
-> WriterT [String] IO (DiagramURL, Bool) 

Given a directory for cached diagrams and a directory for outputting final diagrams, and all the relevant code blocks, compile the diagram referenced by a single URL, returning a new URL updated to point to the location of the generated diagram. Also return a Bool indicating whether the URL changed.

In particular, the diagram will be output to outDir/name.svg, where outDir is the second argument to compileDiagram, and name is the name of the diagram. The updated URL will also refer to outDir/name.svg, under the assumption that outDir will be copied into the Haddock output directory. (For information on how to make this copying happen, see the README: https://github.com/diagrams/diagrams-haddock/blob/master/README.md.) If for some reason you would like this scheme to be more flexible/configurable, feel free to file a feature request.

compileDiagrams Source #

Arguments

:: Bool

True = quiet

-> Bool

True = generate data URIs

-> FilePath

cache directory

-> FilePath

output directory

-> FilePath

file being processed

-> Set String

diagram names referenced from URLs

-> [CodeBlock] 
-> [Either String DiagramURL] 
-> WriterT [String] IO ([Either String DiagramURL], Bool) 

Compile all the diagrams referenced in an entire module.

processHaddockDiagrams Source #

Arguments

:: Bool

quiet

-> Bool

generate data URIs?

-> FilePath

cache directory

-> FilePath

output directory

-> FilePath

file to be processed

-> IO [String] 

Read a file, compile all the referenced diagrams, and update all the diagram URLs to refer to the proper image files. Note, this overwrites the file, so it's recommended to only do this on files that are under version control, so you can compare the two versions and roll back if processHaddockDiagrams does something horrible.

Returns a list of warnings and/or errors.

processHaddockDiagrams' Source #

Arguments

:: CpphsOptions

Options for cpphs

-> Bool

quiet

-> Bool

generate data URIs?

-> FilePath

cache directory

-> FilePath

output directory

-> FilePath

file to be processed

-> IO [String] 

Version of processHaddockDiagrams that takes options for cpphs.

Utilities

showParseFailure :: SrcLoc -> String -> String Source #

Pretty-print a parse failure at a particular location.

newtype CollectErrors a Source #

A simple monad for collecting a list of error messages. There is no facility for failing as such---in this model one simply generates an error message and moves on.

Constructors

CE 

Fields

Instances
Monad CollectErrors Source # 
Instance details

Defined in Diagrams.Haddock

Functor CollectErrors Source # 
Instance details

Defined in Diagrams.Haddock

Methods

fmap :: (a -> b) -> CollectErrors a -> CollectErrors b #

(<$) :: a -> CollectErrors b -> CollectErrors a #

Applicative CollectErrors Source # 
Instance details

Defined in Diagrams.Haddock

MonadWriter [String] CollectErrors Source # 
Instance details

Defined in Diagrams.Haddock

failWith :: String -> CollectErrors (Maybe a) Source #

Generate an error message and fail (by returning Nothing).

runCE :: CollectErrors a -> (a, [String]) Source #

Run a CollectErrors computation, resulting in a value of type a along with the collection of generated error messages.