diff --git a/examples/Pentaflake.lhs b/examples/Pentaflake.lhs index 368eaa0..0e69636 100644 --- a/examples/Pentaflake.lhs +++ b/examples/Pentaflake.lhs @@ -1,36 +1,32 @@ -> {-# LANGUAGE NoMonomorphismRestriction #-} > import Diagrams.Prelude -> import qualified Data.Colour as C > import Diagrams.Backend.SVG.CmdLine We can use the [`colour` library](http://hackage.haskell.org/package/colour) to generate successively lighter shades of blue: -> colors = iterate (C.blend 0.1 white) blue +> colors = iterate (blend 0.1 white) blue An order-0 pentaflake is just a pentagon: -> p = regPoly 5 1 # lw 0 -> -> pentaflake 0 = p +> pentaflake' 0 = pentagon 1 # lw 0 -An [order-n pentaflake](http://mathworld.wolfram.com/Pentaflake.html) is an order-(n-1) pentaflake surrounded by five -more. The `appends` function is useful here for positioning the five -pentaflakes around the central one. +An [order-n pentaflake](http://mathworld.wolfram.com/Pentaflake.html) is +an order-(n-1) pentaflake surrounded by five more. The `appends` +function is useful here for positioning the five pentaflakes around the +central one. -> pentaflake n = appends (p' # fc (colors !! (n-1))) +> pentaflake' n = appends (p' # fc (colors !! (n-1))) > (zip vs (repeat (rotateBy (1/2) p'))) > where vs = take 5 . iterate (rotateBy (1/5)) > . (if odd n then negated else id) $ unitY -> p' = pentaflake (n-1) -> -> pentaflake' n = pentaflake n # fc (colors !! n) +> p' = pentaflake' (n-1) +> +> pentaflake n = pentaflake' n # fc (colors !! n) -An order-4 pentaflake looks nice. Of course there's an exponential +An order-4 pentaflake looks nice. Of course there's an exponential blowup in the number of primitives, so generating higher-order pentaflakes can take a long time! -> example :: Diagram B -> example = pad 1.1 $ pentaflake' 4 +> example = pentaflake 4 > main = defaultMain (pad 1.1 example) diff --git a/src/Diagrams/Backend/SVG.hs b/src/Diagrams/Backend/SVG.hs index e02db02..76a45cf 100644 --- a/src/Diagrams/Backend/SVG.hs +++ b/src/Diagrams/Backend/SVG.hs @@ -129,6 +129,7 @@ import Diagrams.TwoD.Adjust (adjustDia2D) import Diagrams.TwoD.Attributes (splitTextureFills) import Diagrams.TwoD.Path (Clip (Clip)) import Diagrams.TwoD.Text +import Diagrams.Backend.Build -- from lucid-svg import Lucid.Svg @@ -223,6 +224,12 @@ instance SVGFloat n => Backend SVG V2 n where adjustDia c opts d = adjustDia2D sizeSpec c opts (d # reflectY) +instance SVGFloat n => BackendBuild SVG V2 n where + outputSize = sizeSpec + saveDia outFile opts dia = renderToFile outFile build + where + build = renderDia SVG opts dia + toRender :: forall n. SVGFloat n => RTree SVG V2 n Annotation -> Render SVG V2 n toRender = fromRTree . Node (RStyle (mempty # recommendFillColor (transparent :: AlphaColour Double))) diff --git a/src/Diagrams/Backend/SVG/CmdLine.hs b/src/Diagrams/Backend/SVG/CmdLine.hs index e523480..f4e57d5 100644 --- a/src/Diagrams/Backend/SVG/CmdLine.hs +++ b/src/Diagrams/Backend/SVG/CmdLine.hs @@ -73,7 +73,8 @@ module Diagrams.Backend.SVG.CmdLine import Diagrams.Backend.CmdLine import Diagrams.Backend.SVG -import Diagrams.Prelude hiding (height, interval, width, output) +import Diagrams.Prelude hiding (height, interval, + output, width) import Control.Lens hiding (argument) import Options.Applicative hiding ((<>)) @@ -148,7 +149,7 @@ import Data.List.Split -- $ ./MyDiagram -o image.svg -w 400 -- @ -defaultMain :: SVGFloat n => QDiagram SVG V2 n Any -> IO () +defaultMain :: Diagram SVG -> IO () defaultMain = mainWith newtype PrettyOpt = PrettyOpt {isPretty :: Bool} @@ -162,10 +163,11 @@ instance Parseable PrettyOpt where parser = prettyOpt instance SVGFloat n => Mainable (QDiagram SVG V2 n Any) where - type MainOpts (QDiagram SVG V2 n Any) = (DiagramOpts, DiagramLoopOpts, PrettyOpt) - mainRender (opts, loopOpts, pretty) d = do - chooseRender opts pretty d - defaultLoopRender loopOpts + + type MainOpts (QDiagram SVG V2 n Any) = (DiagramOpts, DiagramLoopOpts, PrettyOpt) + mainRender (opts, loopOpts, pretty) d = do + chooseRender opts pretty d + defaultLoopRender loopOpts chooseRender :: SVGFloat n => DiagramOpts -> PrettyOpt -> QDiagram SVG V2 n Any -> IO () chooseRender opts pretty d = @@ -206,3 +208,4 @@ instance SVGFloat n => Mainable [(String,QDiagram SVG V2 n Any)] where = (MainOpts (QDiagram SVG V2 n Any), DiagramMultiOpts) mainRender = defaultMultiMainRender +