Safe Haskell | None |
---|---|
Language | Haskell98 |
The backend to render charts with the diagrams library.
- runBackend :: (Backend b V2 (N b), Renderable (Path V2 (N b)) b, TypeableFloat (N b), Metric (V b)) => DEnv (N b) -> BackendProgram a -> (QDiagram b V2 (N b) Any, a)
- runBackendR :: (Backend b V2 (N b), Renderable (Path V2 (N b)) b, TypeableFloat (N b), Metric (V b)) => DEnv (N b) -> Renderable a -> (QDiagram b V2 (N b) Any, PickFn a)
- runBackendWithGlyphs :: (Backend b V2 (N b), Renderable (Path V2 (N b)) b, Renderable (Text (N b)) b, TypeableFloat (N b), Metric (V b)) => DEnv (N b) -> BackendProgram a -> (QDiagram b V2 (N b) Any, a, Map (String, FontSlant, FontWeight) (Set String))
- defaultEnv :: (Read n, RealFloat n) => AlignmentFns -> n -> n -> IO (DEnv n)
- createEnv :: (Read n, RealFloat n) => AlignmentFns -> n -> n -> FontSelector n -> DEnv n
- data DEnv n = DEnv {
- envAlignmentFns :: AlignmentFns
- envFontStyle :: FontStyle
- envSelectFont :: FontSelector n
- envOutputSize :: (n, n)
- envUsedGlyphs :: Map (String, FontSlant, FontWeight) (Set String)
- data FileFormat
- = EPS
- | SVG
- | SVG_EMBEDDED
- data FileOptions = FileOptions {
- _fo_size :: (Double, Double)
- _fo_format :: FileFormat
- _fo_fonts :: IO (FontSelector Double)
- fo_size :: Lens' FileOptions (Double, Double)
- fo_format :: Lens' FileOptions FileFormat
- fo_fonts :: Lens' FileOptions (IO (FontSelector Double))
- renderableToFile :: FileOptions -> FilePath -> Renderable a -> IO (PickFn a)
- toFile :: (Default r, ToRenderable r) => FileOptions -> FilePath -> EC r () -> IO ()
- cBackendToFile :: FileOptions -> BackendProgram a -> FilePath -> IO a
- loadSansSerifFonts :: forall n. (RealFloat n, Read n) => IO (FontSelector n)
- loadCommonFonts :: forall n. (RealFloat n, Read n) => IO (FontSelector n)
- type FontSelector n = FontStyle -> PreparedFont n
Documentation
:: (Backend b V2 (N b), Renderable (Path V2 (N b)) b, TypeableFloat (N b), Metric (V b)) | |
=> DEnv (N b) | Environment to start rendering with. |
-> BackendProgram a | Chart render code. |
-> (QDiagram b V2 (N b) Any, a) | The diagram. |
Run this backends renderer.
:: (Backend b V2 (N b), Renderable (Path V2 (N b)) b, TypeableFloat (N b), Metric (V b)) | |
=> DEnv (N b) | Environment to start rendering with. |
-> Renderable a | Chart render code. |
-> (QDiagram b V2 (N b) Any, PickFn a) | The diagram. |
Run this backends renderer.
:: (Backend b V2 (N b), Renderable (Path V2 (N b)) b, Renderable (Text (N b)) b, TypeableFloat (N b), Metric (V b)) | |
=> DEnv (N b) | Environment to start rendering with. |
-> BackendProgram a | Chart render code. |
-> (QDiagram b V2 (N b) Any, a, Map (String, FontSlant, FontWeight) (Set String)) |
Run this backends renderer.
:: (Read n, RealFloat n) | |
=> AlignmentFns | Alignment functions to use. |
-> n | The output image width in backend coordinates. |
-> n | The output image height in backend coordinates. |
-> IO (DEnv n) |
Produce a default environment with just the sans-serif fonts.
:: (Read n, RealFloat n) | |
=> AlignmentFns | Alignment functions to use. |
-> n | The output image width in backend coordinates. |
-> n | The output image height in backend coordinates. |
-> FontSelector n | |
-> DEnv n |
Produce an environment with a custom set of fonts. The defult fonts are still loaded as fall back.
The diagrams backend environement.
DEnv | |
|
File Output Functons
data FileFormat Source #
The file output format: EPS -> Embedded Postscript SVG -> SVG with text rendered as stroked paths SVG -> SVG with embedded font information and text rendered as text operations
data FileOptions Source #
FileOptions | |
|
fo_fonts :: Lens' FileOptions (IO (FontSelector Double)) Source #
renderableToFile :: FileOptions -> FilePath -> Renderable a -> IO (PickFn a) Source #
Generate an image file for the given renderable, at the specified path. Size, format,
and text rendering mode are all set through the FileOptions
parameter.
toFile :: (Default r, ToRenderable r) => FileOptions -> FilePath -> EC r () -> IO () Source #
Generate an image file from from the state content of an EC
computation. The state may have any type that is an instance of
ToRenderable
cBackendToFile :: FileOptions -> BackendProgram a -> FilePath -> IO a Source #
Generate an image file for the given drawing instructions, at the specified path. Size and
format are set through the FileOptions
parameter.
Fonts
loadSansSerifFonts :: forall n. (RealFloat n, Read n) => IO (FontSelector n) Source #
Load sans-serif fonts only
loadCommonFonts :: forall n. (RealFloat n, Read n) => IO (FontSelector n) Source #
Load serif, sans-serif and monospace fonts.
type FontSelector n = FontStyle -> PreparedFont n Source #