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

Diagrams.SVG.ReadSVG

Description

 
Synopsis

Main functions

readSVGFile :: (V b ~ V2, N b ~ n, RealFloat n, Renderable (Path V2 n) b, Renderable (DImage n Embedded) b, Typeable b, Typeable n, Show n, Read n, n ~ Place, Renderable (Text n) b) => FilePath -> IO (Either String (Diagram b)) Source #

Main library function

{-# LANGUAGE OverloadedStrings #-}

module Main where
import Diagrams.SVG.ReadSVG
import Diagrams.Prelude
import Diagrams.Backend.SVG.CmdLine
import System.Environment
import Filesystem.Path.CurrentOS
import Diagrams.SVG.Attributes (PreserveAR(..), AlignSVG(..), Place(..), MeetOrSlice(..))

main = do
   diagramFromSVG :: Either String (Diagram B) <- readSVGFile "svgs/web.svg"
   case diagramFromSVG of
     Left msg      -> error $ "readSVGFile returned: " <> msg
     Right diagram -> mainWith $ diagram

readSVGLBS :: (V b ~ V2, N b ~ n, RealFloat n, Renderable (Path V2 n) b, Renderable (DImage n Embedded) b, Typeable b, Typeable n, Show n, Read n, n ~ Place, Renderable (Text n) b, MonadThrow m) => ByteString -> m (Diagram b) Source #

Read SVG from a Lazy ByteString and turn it into a diagram.

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

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

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

data AlignSVG Source #

Constructors

AlignXY Place Place

alignment in x and y direction

type Place Source #

Arguments

 = Double

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

data MeetOrSlice Source #

Constructors

Meet 
Slice 

class (V b ~ V2, N b ~ n, RealFloat n, Renderable (Path V2 n) b, Typeable n, Typeable b, Show n, Renderable (DImage n Embedded) b) => InputConstraints b n Source #

Instances

Instances details
(V b ~ V2, N b ~ n, RealFloat n, Renderable (Path V2 n) b, Typeable n, Typeable b, Show n, Renderable (DImage n Embedded) b) => InputConstraints b n Source # 
Instance details

Defined in Diagrams.SVG.ReadSVG

Parsing of basic structure tags

parseUse :: (MonadThrow m, V b ~ V2, N b ~ n, RealFloat n, Typeable n) => forall o. ConduitT Event o m (Maybe (Tag b n)) Source #

parseSwitch :: (MonadThrow m, V b ~ V2, N b ~ n, RealFloat n) => forall o. ConduitT Event o m (Maybe (Tag b n)) Source #

parseDesc :: forall {m :: Type -> Type} {b} {o} {n}. (MonadThrow m, Metric (V b), Floating (N b), Ord (N b)) => ConduitT Event o m (Maybe (Tag b n)) Source #

Parse <desc>, see http://www.w3.org/TR/SVG/struct.html#DescriptionAndTitleElements parseDesc :: (MonadThrow m, Metric (V b), RealFloat (N b)) => forall o. ConduitT Event o m (Maybe (Tag b n))

parseTitle :: forall {m :: Type -> Type} {b} {o} {n}. (MonadThrow m, Metric (V b), Floating (N b), Ord (N b)) => ConduitT Event o m (Maybe (Tag b n)) Source #

Parsing of basic shape tags

Parsing of Gradient tags

parseLinearGradient :: (MonadThrow m, V b ~ V2, N b ~ n, RealFloat n) => forall o. ConduitT Event o m (Maybe (Tag b n)) Source #

Parse <linearGradient>, see http://www.w3.org/TR/SVG/pservers.html#LinearGradientElement example: <linearGradient id=SVGID_2_ gradientUnits="userSpaceOnUse" x1="68.2461" y1="197.6797" x2="52.6936" y2="237.5337" gradientTransform="matrix(1 0 0 -1 -22.5352 286.4424)">

parseSet :: forall {m :: Type -> Type} {b} {o} {n}. (MonadThrow m, Metric (V b), Floating (N b), Ord (N b)) => ConduitT Event o m (Maybe (Tag b n)) Source #

Parsing of other tags

parseFilter :: forall {m :: Type -> Type} {b} {o} {n}. (MonadThrow m, Metric (V b), Floating (N b), Ord (N b)) => ConduitT Event o m (Maybe (Tag b n)) Source #

Parsing data uri in image

dataUriToImage :: (Metric (V b), Ord n, RealFloat n, N b ~ n, V2 ~ V b, Renderable (DImage n Embedded) b, Typeable b, Typeable n) => Maybe Text -> n -> n -> Diagram b Source #

Convert base64 encoded data in image to a Diagram b with JuicyPixels input: "data:image/png;base64,..."