Copyright | (c) 2012 diagrams-lib team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | None |
Language | Haskell2010 |
Tools for dynamically building diagrams, for e.g. creating preprocessors to interpret diagrams code embedded in documents.
- data BuildOpts b v n = BuildOpts {
- backendToken :: b
- vectorToken :: v n
- _backendOpts :: Options b v n
- _snippets :: [String]
- _pragmas :: [String]
- _imports :: [String]
- _decideRegen :: Hash -> IO (Maybe (Options b v n -> Options b v n))
- _diaExpr :: String
- _postProcess :: QDiagram b v n Any -> QDiagram b v n Any
- mkBuildOpts :: b -> v n -> Options b v n -> BuildOpts b v n
- backendOpts :: Lens' (BuildOpts b v n) (Options b v n)
- snippets :: Lens' (BuildOpts b v n) [String]
- pragmas :: Lens' (BuildOpts b v n) [String]
- imports :: Lens' (BuildOpts b v n) [String]
- decideRegen :: Lens' (BuildOpts b v n) (Hash -> IO (Maybe (Options b v n -> Options b v n)))
- diaExpr :: Lens' (BuildOpts b v n) String
- postProcess :: Lens' (BuildOpts b v n) (QDiagram b v n Any -> QDiagram b v n Any)
- alwaysRegenerate :: Hash -> IO (Maybe (a -> a))
- hashedRegenerate :: (String -> a -> a) -> FilePath -> Hash -> IO (Maybe (a -> a))
- hashToHexStr :: Hash -> String
- buildDiagram :: (Typeable b, Data (v n), Data n, Metric v, HasLinearMap v, Typeable v, OrderedField n, Backend b v n, Hashable (Options b v n)) => BuildOpts b v n -> IO (BuildResult b v n)
- data BuildResult b v n
- ppInterpError :: InterpreterError -> String
- setDiagramImports :: MonadInterpreter m => String -> [String] -> m ()
- interpretDiagram :: forall b v n. (Typeable b, Typeable v, HasLinearMap v, Data (v n), Data n, Metric v, OrderedField n, Backend b v n) => BuildOpts b v n -> FilePath -> IO (Either InterpreterError (Result b v n))
- data Build = Build {}
- defaultBuildOpts :: Build
Building diagrams
Options
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"
BuildOpts | |
|
mkBuildOpts :: b -> v n -> Options b v n -> BuildOpts b v n Source
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 n) (Options b v n) Source
Backend-specific options to use.
snippets :: Lens' (BuildOpts b v n) [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 n) [String] Source
Extra LANGUAGE
pragmas to use (NoMonomorphismRestriction
is automatically enabled.)
imports :: Lens' (BuildOpts b v n) [String] Source
Additional module imports (note that Diagrams.Prelude is automatically imported).
decideRegen :: Lens' (BuildOpts b v n) (Hash -> IO (Maybe (Options b v n -> Options b v n))) 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 n) String Source
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
or IO (Diagram b)
.
postProcess :: Lens' (BuildOpts b v n) (QDiagram b v n Any -> QDiagram b v n Any) 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.
:: (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.)
hashToHexStr :: Hash -> String Source
Building
buildDiagram :: (Typeable b, Data (v n), Data n, Metric v, HasLinearMap v, Typeable v, OrderedField n, Backend b v n, Hashable (Options b v n)) => BuildOpts b v n -> IO (BuildResult b v n) 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 n Source
Potential results of a dynamic diagram building operation.
ParseErr String | Parsing of the code failed. |
InterpErr InterpreterError | Interpreting the code
failed. See |
Skipped Hash | This diagram did not need to be regenerated; includes the hash. |
OK Hash (Result b v n) | A successful build, yielding the hash and a backend-specific result. |
ppInterpError :: InterpreterError -> String Source
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.
:: MonadInterpreter m | |
=> String | Filename of the module containing the diagrams |
-> [String] | Additional necessary imports. |
-> m () |
Set up the module to be interpreted, in the context of the necessary imports.
interpretDiagram :: forall b v n. (Typeable b, Typeable v, HasLinearMap v, Data (v n), Data n, Metric v, OrderedField n, Backend b v n) => BuildOpts b v n -> FilePath -> IO (Either InterpreterError (Result b v n)) 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 n
or IO (Diagram b v n)
.
Tools for creating standalone builder executables
Record of command-line options.
defaultBuildOpts :: Build Source
Default command-line options record.