Maintainer | diagrams-discuss@googlegroups.com |
---|---|
Safe Haskell | None |
This module contains the internal implementation guts of the diagrams cairo backend. If you want to see how the cairo backend works under the hood, you are in the right place (try clicking on the "Source" links). (Guts under the hood, what an awful mixed metaphor.) If you know what you are doing and really want access to the internals of the implementation, you are also in the right place. Otherwise, you should have no need of this module; import Diagrams.Backend.Cairo.CmdLine or Diagrams.Backend.Cairo instead.
The one exception is that this module may have to be imported
sometimes to work around an apparent bug in certain versions of
GHC, which results in a "not in scope" error for CairoOptions
.
The types of all the fromX
functions look funny in the Haddock
output, which displays them like Type -> Type
. In fact they are
all of the form Type -> Graphics.Rendering.Cairo.Type
, i.e.
they convert from a diagrams type to a cairo type of the same name.
- data Cairo = Cairo
- type B = Cairo
- data OutputType
- = PNG
- | PS
- | SVG
- | RenderOnly
- data CairoState = CairoState {
- _accumStyle :: Style R2
- _ignoreFill :: Bool
- ignoreFill :: Lens' CairoState Bool
- accumStyle :: Lens' CairoState (Style R2)
- type RenderM a = StateStackT CairoState Render a
- liftC :: Render a -> RenderM a
- runRenderM :: RenderM a -> Render a
- save :: RenderM ()
- restore :: RenderM ()
- runC :: Render Cairo R2 -> RenderM ()
- renderRTree :: RTree Cairo R2 a -> Render Cairo R2
- cairoFileName :: Lens' (Options Cairo R2) String
- cairoSizeSpec :: Lens' (Options Cairo R2) SizeSpec2D
- cairoOutputType :: Lens' (Options Cairo R2) OutputType
- cairoBypassAdjust :: Lens' (Options Cairo R2) Bool
- renderC :: (Renderable a Cairo, V a ~ R2) => a -> RenderM ()
- getStyleAttrib :: AttributeClass a => (a -> b) -> RenderM (Maybe b)
- cairoStyle :: Style v -> RenderM ()
- fromFontSlant :: FontSlant -> FontSlant
- fromFontWeight :: FontWeight -> FontWeight
- applyOpacity :: Color c => c -> Style v -> AlphaColour Double
- cairoTransf :: T2 -> Render ()
- fromLineCap :: LineCap -> LineCap
- fromLineJoin :: LineJoin -> LineJoin
- fromFillRule :: FillRule -> FillRule
- cairoPath :: Path R2 -> RenderM ()
- setSourceColor :: Maybe (AlphaColour Double) -> RenderM ()
Documentation
This data declaration is simply used as a token to distinguish
the cairo 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.
Eq Cairo | |
Ord Cairo | |
Read Cairo | |
Show Cairo | |
Typeable Cairo | |
Backend Cairo R2 | |
Renderable Text Cairo | |
Renderable Image Cairo | |
Mainable [(String, Diagram Cairo R2)] | |
Renderable (Path R2) Cairo | |
Renderable (Trail R2) Cairo | |
Show (Options Cairo R2) | |
Monoid (Render Cairo R2) | |
Mainable (Diagram Cairo R2) | |
Mainable (Animation Cairo R2) | |
Hashable (Options Cairo R2) | |
Renderable (Segment Closed R2) Cairo |
data OutputType Source
Output types supported by cairo, including four different file
types (PNG, PS, PDF, SVG). If you want to output directly to GTK
windows, see the diagrams-gtk
package.
PNG | Portable Network Graphics output. |
PS | PostScript output |
Portable Document Format output. | |
SVG | Scalable Vector Graphics output. |
RenderOnly | Don't output any file; the returned |
data CairoState Source
Custom state tracked in the RenderM
monad.
CairoState | |
|
type RenderM a = StateStackT CairoState Render aSource
The custom monad in which intermediate drawing options take
place; Render
is cairo's own rendering
monad.
runRenderM :: RenderM a -> Render aSource
renderC :: (Renderable a Cairo, V a ~ R2) => a -> RenderM ()Source
Render an object that the cairo backend knows how to render.
getStyleAttrib :: AttributeClass a => (a -> b) -> RenderM (Maybe b)Source
Get an accumulated style attribute from the render monad state.
cairoStyle :: Style v -> RenderM ()Source
Handle those style attributes for which we can immediately emit cairo instructions as we encounter them in the tree (clip, font size, fill rule, line width, cap, join, and dashing). Other attributes (font face, slant, weight; fill color, stroke color, opacity) must be accumulated.
applyOpacity :: Color c => c -> Style v -> AlphaColour DoubleSource
Apply the opacity from a style to a given color.
cairoTransf :: T2 -> Render ()Source
Multiply the current transformation matrix by the given 2D transformation.
fromLineCap :: LineCap -> LineCapSource
setSourceColor :: Maybe (AlphaColour Double) -> RenderM ()Source