diagrams-builder-0.5.0.6: hint-based build service for the diagrams graphics EDSL.

Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone

Diagrams.Builder

Contents

Description

Tools for dynamically building diagrams, for e.g. creating preprocessors to interpret diagrams code embedded in documents.

Synopsis

Building diagrams

Options

data BuildOpts b v Source

Options to control the behavior of buildDiagram. Create one with mkBuildOpts followed by using the provided lenses to override more fields; for example,

   mkBuildOpts SVG zeroV (Options ...)
     & imports .~ ["Foo.Bar", "Baz.Quux"]
     & diaExpr .~ "square 6 # fc green"

Constructors

BuildOpts 

Fields

backendToken :: b

Backend token

vectorToken :: v

Dummy vector argument to fix the vector space type

_backendOpts :: Options b v
 
_snippets :: [String]
 
_pragmas :: [String]
 
_imports :: [String]
 
_decideRegen :: Hash -> IO (Maybe (Options b v -> Options b v))
 
_diaExpr :: String
 
_postProcess :: Diagram b v -> Diagram b v
 

mkBuildOpts :: b -> v -> Options b v -> BuildOpts b vSource

Create a BuildOpts record with default options:

  • no snippets
  • no pragmas
  • no imports
  • always regenerate
  • the diagram expression circle 1
  • no postprocessing

backendOpts :: Lens' (BuildOpts b v) (Options b v)Source

Backend-specific options to use.

snippets :: Lens' (BuildOpts b v) [String]Source

Source code snippets. Each should be a syntactically valid Haskell module. They will be combined intelligently, i.e. not just pasted together textually but combining pragmas, imports, etc. separately.

pragmas :: Lens' (BuildOpts b v) [String]Source

Extra LANGUAGE pragmas to use (NoMonomorphismRestriction is automatically enabled.)

imports :: Lens' (BuildOpts b v) [String]Source

Additional module imports (note that Diagrams.Prelude is automatically imported).

decideRegen :: Lens' (BuildOpts b v) (Hash -> IO (Maybe (Options b v -> Options b v)))Source

A function to decide whether a particular diagram needs to be regenerated. It will be passed a hash of the final assembled source for the diagram (but with the module name set to Main instead of something auto-generated, so that hashing the source will produce consistent results across runs), plus any options, local imports, and other things which could affect the result of rendering. It can return some information (such as a hash of the source) via the x result, which will be passed through to the result of buildDiagram. More importantly, it decides whether the diagram should be built: a result of Just means the diagram should be built; Nothing means it should not. In the case that it should be built, it returns a function for updating the rendering options. This could be used, e.g., to request a filename based on a hash of the source.

Two standard decision functions are provided for convenience: alwaysRegenerate returns no extra information and always decides to regenerate the diagram; hashedRegenerate creates a hash of the diagram source and looks for a file with that name in a given directory.

diaExpr :: Lens' (BuildOpts b v) StringSource

The diagram expression to interpret. All the given import sand snippets will be in scope, with the given LANGUAGE pragmas enabled. The expression may have either of the types Diagram b v or IO (Diagram b v).

postProcess :: Lens' (BuildOpts b v) (Diagram b v -> Diagram b v)Source

A function to apply to the interpreted diagram prior to rendering. For example, you might wish to apply pad 1.1 . centerXY. This is preferred over directly modifying the string expression to be interpreted, since it gives better typechecking, and works no matter whether the expression represents a diagram or an IO action.

Regeneration decision functions and hashing

alwaysRegenerate :: Hash -> IO (Maybe (a -> a))Source

Convenience function suitable to be given as the final argument to buildDiagram. It implements the simple policy of always rebuilding every diagram.

hashedRegenerateSource

Arguments

:: (String -> a -> a)

A function for computing an update to rendering options, given a new base filename computed from a hash of the diagram source.

-> FilePath

The directory in which to look for generated files

-> Hash

The hash

-> IO (Maybe (a -> a)) 

Convenience function suitable to be given as the final argument to buildDiagram. It works by converting the hash value to a zero-padded hexadecimal string and looking in the specified directory for any file whose base name is equal to the hash. If there is such a file, it specifies that the diagram should not be rebuilt. Otherwise, it specifies that the diagram should be rebuilt, and uses the provided function to update the rendering options based on the generated hash string. (Most likely, one would want to set the requested output file to the hash followed by some extension.)

Building

buildDiagram :: (Typeable b, Typeable v, InnerSpace v, OrderedField (Scalar v), Backend b v, Hashable (Options b v)) => BuildOpts b v -> IO (BuildResult b v)Source

Build a diagram by writing the given source code to a temporary module and interpreting the given expression, which can be of type Diagram b v or IO (Diagram b v). Can return either a parse error if the source does not parse, an interpreter error, or the final result.

data BuildResult b v Source

Potential results of a dynamic diagram building operation.

Constructors

ParseErr String

Parsing of the code failed.

InterpErr InterpreterError

Interpreting the code failed. See ppInterpError.

Skipped Hash

This diagram did not need to be regenerated; includes the hash.

OK Hash (Result b v)

A successful build, yielding the hash and a backend-specific result.

ppInterpError :: InterpreterError -> StringSource

Pretty-print an InterpreterError.

Interpreting diagrams

These functions constitute the internals of diagrams-builder. End users should not usually need to call them directly; use buildDiagram instead.

setDiagramImportsSource

Arguments

:: MonadInterpreter m 
=> String

Filename of the module containing the diagrams

-> [String]

Additional necessary imports. Prelude, Diagrams.Prelude, Diagrams.Core.Types, and Data.Monoid are included by default.

-> m () 

Set up the module to be interpreted, in the context of the necessary imports.

interpretDiagram :: forall b v. (Typeable b, Typeable v, InnerSpace v, OrderedField (Scalar v), Backend b v) => BuildOpts b v -> FilePath -> IO (Either InterpreterError (Result b v))Source

Interpret a diagram expression based on the contents of a given source file, using some backend to produce a result. The expression can be of type Diagram b v or IO (Diagram b v).

Tools for creating standalone builder executables

data Build Source

Record of command-line options.

Constructors

Build 

Instances

defaultBuildOpts :: BuildSource

Default command-line options record.