diagrams-rasterific-1.3.1.5: Rasterific backend for diagrams.

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

Diagrams.Backend.Rasterific

Description

A full-featured rendering backend for diagrams using Rasterific, implemented natively in Haskell (making it easy to use on any platform). Can create png, tif, bmp, jpg, and animated GIFs.

To invoke the Rasterific backend, you have three options.

  • You can use the Diagrams.Backend.Rasterific.CmdLine module to create standalone executables which output images when invoked.
  • You can use the renderRasterific function provided by this module, which gives you more flexible programmatic control over when and how images are output (making it easy to, for example, write a single program that outputs multiple images, or one that outputs images dynamically based on user input, and so on).
  • For the most flexibility (e.g. if you want access to the resulting Rasterific value directly in memory without writing it to disk), you can manually invoke the renderDia method from the Backend instance for Rasterific. In particular, renderDia has the generic type
renderDia :: b -> Options b v n -> QDiagram b v n m -> Result b v n

(omitting a few type class constraints). b represents the backend type, v the vector space, n the numeric field, and m the type of monoidal query annotations on the diagram. Options and Result are associated data and type families, respectively, which yield the type of option records and rendering results specific to any particular backend. For b ~ Rasterific, v ~ V2, and n ~ n, we have

data Options Rasterific V2 n = RasterificOptions
       { _size      :: SizeSpec2D n -- ^ The requested size of the output
       }
type family Result Rasterific V2 n = 'Image PixelRGBA8'

So the type of renderDia resolves to

renderDia :: Rasterific -> Options Rasterific V2 n -> QDiagram Rasterific V2 n m -> 'Image PixelRGBA8'

which you could call like renderDia Rasterific (RasterificOptions (mkWidth 250)) myDiagram.

Synopsis

Documentation

data Rasterific Source

This data declaration is simply used as a token to distinguish the Rasterific backend: (1) when calling functions where the type inference engine would otherwise have no way to know which backend you wanted to use, and (2) as an argument to the Backend and Renderable type classes.

Constructors

Rasterific 

data family Options b v n

Backend-specific rendering options.

renderRasterific :: TypeableFloat n => FilePath -> SizeSpec V2 n -> QDiagram Rasterific V2 n Any -> IO () Source

Render a Rasterific diagram to a file with the given size. The format is determined by the extension (.png, .tif, .bmp and .jpg supported. (jpeg quality is 80, use writeJpeg to choose quality).

size :: ((~) (* -> *) (V a) v, (~) * (N a) n, Enveloped a, HasBasis v) => a -> v n

The smallest positive vector that bounds the envelope of an object.

writeJpeg :: Word8 -> FilePath -> Result Rasterific V2 n -> IO () Source

Render a Rasterific diagram to a jpeg file with given quality (between 0 and 100).

texterific :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any Source

Create a primitive text diagram from the given string, with baseline alignment, envelope and trace based on the BoundingBox of the text. Designed to be a replacement for the function text in Diagrams.TwoD.Text.

texterific' :: (TypeableFloat n, Renderable (Text n) b) => FontSlant -> FontWeight -> String -> QDiagram b V2 n Any Source

Create a primitive text diagram from the given FontSlant, FontWeight, and string, with baseline alignment, envelope and trace based on the BoundingBox of the text.