diagrams-cairo-1.4: Cairo backend for diagrams drawing EDSL

Copyright(c) 2011 Diagrams-cairo team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.Backend.Cairo.Internal

Description

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.

Synopsis

Documentation

data Cairo Source #

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.

Constructors

Cairo 

Instances

Eq Cairo Source # 

Methods

(==) :: Cairo -> Cairo -> Bool #

(/=) :: Cairo -> Cairo -> Bool #

Ord Cairo Source # 

Methods

compare :: Cairo -> Cairo -> Ordering #

(<) :: Cairo -> Cairo -> Bool #

(<=) :: Cairo -> Cairo -> Bool #

(>) :: Cairo -> Cairo -> Bool #

(>=) :: Cairo -> Cairo -> Bool #

max :: Cairo -> Cairo -> Cairo #

min :: Cairo -> Cairo -> Cairo #

Read Cairo Source # 
Show Cairo Source # 

Methods

showsPrec :: Int -> Cairo -> ShowS #

show :: Cairo -> String #

showList :: [Cairo] -> ShowS #

Backend Cairo V2 Double Source # 

Associated Types

data Render Cairo (V2 :: * -> *) Double :: * #

type Result Cairo (V2 :: * -> *) Double :: * #

data Options Cairo (V2 :: * -> *) Double :: * #

Renderable (Text Double) Cairo Source # 

Methods

render :: Cairo -> Text Double -> Render Cairo (V (Text Double)) (N (Text Double)) #

Renderable (DImage Double External) Cairo Source # 

Methods

render :: Cairo -> DImage Double External -> Render Cairo (V (DImage Double External)) (N (DImage Double External)) #

Renderable (DImage Double Embedded) Cairo Source # 

Methods

render :: Cairo -> DImage Double Embedded -> Render Cairo (V (DImage Double Embedded)) (N (DImage Double Embedded)) #

Renderable (Trail V2 Double) Cairo Source # 

Methods

render :: Cairo -> Trail V2 Double -> Render Cairo (V (Trail V2 Double)) (N (Trail V2 Double)) #

Renderable (Path V2 Double) Cairo Source # 

Methods

render :: Cairo -> Path V2 Double -> Render Cairo (V (Path V2 Double)) (N (Path V2 Double)) #

Show (Options Cairo V2 Double) Source # 
Monoid (Render Cairo V2 Double) Source # 
Hashable (Options Cairo V2 Double) Source # 
Renderable (Segment Closed V2 Double) Cairo Source # 

Methods

render :: Cairo -> Segment Closed V2 Double -> Render Cairo (V (Segment Closed V2 Double)) (N (Segment Closed V2 Double)) #

type V Cairo Source # 
type V Cairo = V2
type N Cairo Source # 
type N Cairo = Double
data Options Cairo V2 Double Source # 
type Result Cairo V2 Double Source # 
type Result Cairo V2 Double = (IO (), Render ())
data Render Cairo V2 Double Source # 
data Render Cairo V2 Double = C (RenderM ())
type MainOpts [(String, QDiagram Cairo V2 Double Any)] 
type MainOpts [(String, QDiagram Cairo V2 Double Any)] = (MainOpts (QDiagram Cairo V2 Double Any), DiagramMultiOpts)
type MainOpts [(QDiagram Cairo V2 Double Any, GifDelay)] 
type MainOpts [(QDiagram Cairo V2 Double Any, GifDelay)] = (DiagramOpts, GifOpts)
type MainOpts (Animation Cairo V2 Double) 
type MainOpts (Animation Cairo V2 Double) = ((DiagramOpts, DiagramAnimOpts), DiagramLoopOpts)
type MainOpts (QDiagram Cairo V2 Double Any) 
type MainOpts (QDiagram Cairo V2 Double Any) = (DiagramOpts, DiagramLoopOpts)

type B = Cairo Source #

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.

Constructors

PNG

Portable Network Graphics output.

PS

PostScript output

PDF

Portable Document Format output.

SVG

Scalable Vector Graphics output.

RenderOnly

Don't output any file; the returned IO () action will do nothing, but the Render () action can be used (e.g. to draw to a Gtk window; see the diagrams-gtk package).

Instances

Bounded OutputType Source # 
Enum OutputType Source # 
Eq OutputType Source # 
Ord OutputType Source # 
Read OutputType Source # 
Show OutputType Source # 
Generic OutputType Source # 

Associated Types

type Rep OutputType :: * -> * #

Hashable OutputType Source # 
type Rep OutputType Source # 
type Rep OutputType = D1 (MetaData "OutputType" "Diagrams.Backend.Cairo.Internal" "diagrams-cairo-1.4-8DmweMRzTytCBBbaWTzoP7" False) ((:+:) ((:+:) (C1 (MetaCons "PNG" PrefixI False) U1) (C1 (MetaCons "PS" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PDF" PrefixI False) U1) ((:+:) (C1 (MetaCons "SVG" PrefixI False) U1) (C1 (MetaCons "RenderOnly" PrefixI False) U1))))

data CairoState Source #

Custom state tracked in the RenderM monad.

Constructors

CairoState 

Fields

  • _accumStyle :: Style V2 Double

    The current accumulated style.

  • _ignoreFill :: Bool

    Whether or not we saw any lines in the most recent path (as opposed to loops). If we did, we should ignore any fill attribute. diagrams-lib separates lines and loops into separate path primitives so we don't have to worry about seeing them together in the same path.

Instances

Default CairoState Source # 

Methods

def :: CairoState

type RenderM a = StateStackT CairoState Render a Source #

The custom monad in which intermediate drawing options take place; Render is cairo's own rendering monad.

liftC :: Render a -> RenderM a Source #

runRenderM :: RenderM a -> Render a Source #

save :: RenderM () Source #

Push the current context onto a stack.

restore :: RenderM () Source #

Restore the context from a stack.

cairoSizeSpec :: Lens' (Options Cairo V2 Double) (SizeSpec V2 Double) Source #

renderC :: (Renderable a Cairo, V a ~ V2, N a ~ Double) => 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 Double -> 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.

fromFontSlant :: FontSlant -> FontStyle Source #

fromFontWeight :: FontWeight -> Weight Source #

cairoTransf :: T2 Double -> Render () Source #

Multiply the current transformation matrix by the given 2D transformation.

fromLineCap :: LineCap -> LineCap Source #

fromLineJoin :: LineJoin -> LineJoin Source #

fromFillRule :: FillRule -> FillRule Source #

cairoPath :: Path V2 Double -> RenderM () Source #

addStop :: MonadIO m => Pattern -> GradientStop Double -> m () Source #

cairoSpreadMethod :: SpreadMethod -> Extend Source #

setTexture :: Maybe (Texture Double) -> RenderM () Source #

if' :: Monad m => (a -> m ()) -> Maybe a -> m () Source #

layoutStyledText :: Style V2 Double -> Text Double -> Render PangoLayout Source #