diagrams-input-0.1.3: Parse raster and SVG files for diagrams
Copyright(c) 2015 Tillmann Vogt <tillk.vogt@googlemail.com>
LicenseBSD3
Maintainerdiagrams-discuss@googlegroups.com
Stabilitystable
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Diagrams.SVG.Tree

Description

 
Synopsis

Tree data type

data Tag b n Source #

A tree structure is needed to handle refences to parts of the tree itself. The <defs>-section contains shapes that can be refered to, but the SVG standard allows to refer to every tag in the SVG-file.

Constructors

Leaf 

Fields

  • Id
     
  • (ViewBox n -> Path V2 n)
     
  • ((HashMaps b n, ViewBox n) -> Diagram b)

    A leaf consists of

    • An Id
    • A path so that this leaf can be used to clip some other part of a tree
    • A diagram (Another option would have been to apply a function to the upper path)
Reference 

Fields

  • Id
     
  • Id
     
  • (ViewBox n -> Path V2 n)
     
  • ((HashMaps b n, ViewBox n) -> Diagram b -> Diagram b)

    A reference (<use>-tag) consists of:

    • An Id
    • A reference to an Id
    • A viewbox so that percentages are relative to this viewbox
    • Transformations applied to the reference
SubTree 

Fields

  • Bool
     
  • Id
     
  • (Double, Double)
     
  • (Maybe (ViewBox n))
     
  • (Maybe PreserveAR)
     
  • (HashMaps b n -> Diagram b -> Diagram b)
     
  • [Tag b n]

    A subtree consists of:

    • A Bool: Are we in a section that will be rendered directly (not in a <defs>-section)
    • An Id of subdiagram
    • A viewbox so that percentages are relative to this viewbox
    • Aspect Ratio
    • A transformation or application of a style to a subdiagram
    • A list of subtrees
StyleTag [(Text, [(Text, Text)])]

A tag that contains CSS styles with selectors and attributes

FontTag (FontData b n) 
Grad Id (Gr n)

A gradient

Stop (HashMaps b n -> [GradientStop n])

We need to make this part of this data structure because Gradient tags can also contain description tags

Instances

Instances details
Show (Tag b n) Source # 
Instance details

Defined in Diagrams.SVG.Tree

Methods

showsPrec :: Int -> Tag b n -> ShowS #

show :: Tag b n -> String #

showList :: [Tag b n] -> ShowS #

Extract data from the tree

nodes :: Maybe (ViewBox n) -> (Nodelist b n, CSSlist, Gradlist n, Fontlist b n) -> Tag b n -> (Nodelist b n, CSSlist, Gradlist n, Fontlist b n) Source #

Generate elements that can be referenced by their ID. The tree nodes are splitted into 4 groups of lists of (ID,value)-pairs):

  • Nodes that contain elements that can be transformed to a diagram
  • CSS classes with corresponding (attribute,value)-pairs, from the defs-tag
  • Gradients
  • Fonts

type Attrs = [(Text, Text)] Source #

type NodesMap b n = HashMap Text (Tag b n) Source #

data AlignSVG Source #

Constructors

AlignXY Place Place

alignment in x and y direction

data MeetOrSlice Source #

Constructors

Meet 
Slice 

type Place Source #

Arguments

 = Double

A value between 0 and 1, where 0 is the minimal value and 1 the maximal value

type ViewBox n = (n, n, n, n) Source #

data PresentationAttributes Source #

Constructors

PA 

Fields

expandGradMap :: GradientsMap n -> GradientsMap n Source #

Gradients contain references to include attributes/stops from other gradients. expandGradMap expands the gradient with these attributes and stops

insertRefs :: (V b ~ V2, N b ~ n, RealFloat n, Place ~ n) => (HashMaps b n, ViewBox n) -> Tag b n -> Diagram b Source #

Evaluate the tree into a diagram by inserting xlink:href references from nodes and gradients, applying clipping and passing the viewbox to the leafs

preserveAspectRatio :: (V a ~ V2, N a ~ Place, Fractional (N a), Transformable a, Alignable a, HasOrigin a, Additive (V a), R2 (V a)) => Place -> Place -> Place -> Place -> PreserveAR -> a -> a Source #

preserveAspectRatio is needed to fit an image into a frame that has a different aspect ratio than the image (e.g. 16:10 against 4:3). SVG embeds images the same way: http://www.w3.org/TR/SVG11/coords.html#PreserveAspectRatioAttribute

import Graphics.SVGFonts

portrait preserveAR width height = stroke (readSVGFile preserveAR width height "portrait.svg") # showOrigin
text' t = stroke (textSVG' $ TextOpts t lin INSIDE_H KERN False 1 1 ) # fc back # lc black # fillRule EvenOdd
portraitMeet1 x y = (text' "PAR (AlignXY " ++ show x ++ " " show y ++ ") Meet") ===
                    (portrait (PAR (AlignXY x y) Meet) 200 100 <> rect 200 100)
portraitMeet2 x y = (text' "PAR (AlignXY " ++ show x ++ " " show y ++ ") Meet") ===
                    (portrait (PAR (AlignXY x y) Meet) 100 200 <> rect 100 200)
portraitSlice1 x y = (text' "PAR (AlignXY " ++ show x ++ " " show y ++ ") Slice") ===
                     (portrait (PAR (AlignXY x y) Slice) 100 200 <> rect 100 200)
portraitSlice2 x y = (text' "PAR (AlignXY " ++ show x ++ " " show y ++ ") Slice") ===
                     (portrait (PAR (AlignXY x y) Slice) 200 100 <> rect 200 100)
meetX = (text' "meet") === (portraitMeet1 0 0 ||| portraitMeet1 0.5 0 ||| portraitMeet1 1 0)
meetY = (text' "meet") === (portraitMeet2 0 0 ||| portraitMeet2 0 0.5 ||| portraitMeet2 0 1)
sliceX = (text' "slice") === (portraitSlice1 0 0 ||| portraitSlice1 0.5 0 ||| portraitSlice1 1 0)
sliceY = (text' "slice") === (portraitSlice2 0 0 ||| portraitSlice2 0 0.5 ||| portraitSlice2 0 1)
im = (text' "Image to fit") === (portrait (PAR (AlignXY 0 0) Meet) 123 456)
viewport1 = (text' "Viewport1") === (rect 200 100)
viewport2 = (text' "Viewport2") === (rect 100 200)
imageAndViewports = im === viewport1 === viewport2

par = imageAndViewports ||| ( ( meetX ||| meetY) === ( sliceX ||| sliceY) )

preserveAspectRatio :: Width -> Height -> Width -> Height -> PreserveAR -> Diagram b -> Diagram b

data FontContent b n Source #

Data from the subtags

Constructors

FF (FontFace n) 
GG (Glyph b n) 
KK (Kern n) 

data Glyph b n Source #

data KernDir Source #

Constructors

HKern 
VKern 

type SvgGlyphs n = HashMap Text (Maybe Text, n, Maybe Text) Source #

\[ (unicode, (glyph_name, horiz_advance, ds)) \]

data Kern n Source #

Constructors

Kern 

Fields