module Diagrams.Backend.SVG
( SVG(..)
, B
, Options(..), sizeSpec, svgDefinitions, idPrefix, svgAttributes, generateDoctype
, SVGFloat
, renderSVG
, renderSVG'
, renderPretty
, renderPretty'
, loadImageSVG
) where
import Codec.Picture
import Codec.Picture.Types (dynamicMap)
#if __GLASGOW_HASKELL__ < 710
import Data.Foldable as F (foldMap)
#endif
import qualified Data.Text as T
import Data.Text.Lazy.IO as LT
import Data.Tree
import System.FilePath
import Control.Monad.Reader
import Control.Monad.State
import Data.Char
import Data.Typeable
import Data.Hashable (Hashable (), hashWithSalt)
import qualified Data.ByteString as SBS
import qualified Data.ByteString.Lazy as BS
import Control.Lens hiding (transform, ( # ))
import Diagrams.Core.Compile
import Diagrams.Core.Types (Annotation (..))
import Diagrams.Prelude hiding (Attribute, size, view, local)
import Diagrams.TwoD.Adjust (adjustDia2D)
import Diagrams.TwoD.Attributes (splitTextureFills)
import Diagrams.TwoD.Path (Clip (Clip))
import Diagrams.TwoD.Text
import Graphics.Svg hiding ((<>))
import Graphics.Rendering.SVG (SVGFloat)
import qualified Graphics.Rendering.SVG as R
data SVG = SVG
deriving (Show, Typeable)
type B = SVG
type instance V SVG = V2
type instance N SVG = Double
data Environment n = Environment
{ _style :: Style V2 n
, __pre :: T.Text
}
makeLenses ''Environment
data SvgRenderState = SvgRenderState
{ _clipPathId :: Int
, _fillGradId :: Int
, _lineGradId :: Int
}
makeLenses ''SvgRenderState
initialEnvironment :: SVGFloat n => T.Text -> Environment n
initialEnvironment = Environment (mempty # recommendFillColor transparent)
initialSvgRenderState :: SvgRenderState
initialSvgRenderState = SvgRenderState 0 0 1
type SvgRenderM n = ReaderT (Environment n) (State SvgRenderState) Element
runRenderM :: SVGFloat n => T.Text -> SvgRenderM n -> Element
runRenderM o s = flip evalState initialSvgRenderState
$ runReaderT s (initialEnvironment o)
instance Monoid (Render SVG V2 n) where
mempty = R $ return mempty
R r1 `mappend` R r2_ = R $ do
svg1 <- r1
svg2 <- r2_
return (svg1 `mappend` svg2)
renderSvgWithClipping :: forall n. SVGFloat n
=> T.Text
-> Element
-> Style V2 n
-> SvgRenderM n
renderSvgWithClipping prefix svg s =
case op Clip <$> getAttr s of
Nothing -> return svg
Just paths -> renderClips paths
where
renderClips :: [Path V2 n] -> SvgRenderM n
renderClips [] = return svg
renderClips (p:ps) = do
clipPathId += 1
ident <- use clipPathId
R.renderClip p prefix ident <$> renderClips ps
fillTextureDefs :: SVGFloat n => Style v n -> SvgRenderM n
fillTextureDefs s = do
ident <- use fillGradId
fillGradId += 2
return $ R.renderFillTextureDefs ident s
lineTextureDefs :: SVGFloat n => Style v n -> SvgRenderM n
lineTextureDefs s = do
ident <- use lineGradId
lineGradId += 2
return $ R.renderLineTextureDefs ident s
instance SVGFloat n => Backend SVG V2 n where
newtype Render SVG V2 n = R (SvgRenderM n)
type Result SVG V2 n = Element
data Options SVG V2 n = SVGOptions
{ _size :: SizeSpec V2 n
, _svgDefinitions :: Maybe Element
, _idPrefix :: T.Text
, _svgAttributes :: [Attribute]
, _generateDoctype :: Bool
}
renderRTree :: SVG -> Options SVG V2 n -> RTree SVG V2 n Annotation -> Result SVG V2 n
renderRTree _ opts rt = runRenderM (opts ^.idPrefix) svgOutput
where
svgOutput = do
let R r = rtree (splitTextureFills rt)
V2 w h = specToSize 100 (opts^.sizeSpec)
svg <- r
return $ R.svgHeader w h (opts^.svgDefinitions)
(opts^.svgAttributes)
(opts^.generateDoctype) svg
adjustDia c opts d = ( sz, t <> reflectionY, d' ) where
(sz, t, d') = adjustDia2D sizeSpec c opts (d # reflectY)
rtree :: SVGFloat n => RTree SVG V2 n Annotation -> Render SVG V2 n
rtree (Node n rs) = case n of
RPrim p -> render SVG p
RStyle sty -> R $ local (over style (<> sty)) r
RAnnot (OpacityGroup o) -> R $ g_ [Opacity_ <<- toText o] <$> r
RAnnot (Href uri) -> R $ a_ [XlinkHref_ <<- T.pack uri] <$> r
_ -> R r
where
R r = foldMap rtree rs
sizeSpec :: Lens' (Options SVG V2 n) (SizeSpec V2 n)
sizeSpec f opts = f (_size opts) <&> \s -> opts { _size = s }
svgDefinitions :: Lens' (Options SVG V2 n) (Maybe Element)
svgDefinitions f opts =
f (_svgDefinitions opts) <&> \ds -> opts { _svgDefinitions = ds }
idPrefix :: Lens' (Options SVG V2 n) T.Text
idPrefix f opts = f (_idPrefix opts) <&> \i -> opts { _idPrefix = i }
svgAttributes :: Lens' (Options SVG V2 n) [Attribute]
svgAttributes f opts =
f (_svgAttributes opts) <&> \ds -> opts { _svgAttributes = ds }
generateDoctype :: Lens' (Options SVG V2 n) Bool
generateDoctype f opts =
f (_generateDoctype opts) <&> \ds -> opts { _generateDoctype = ds }
attributedRender :: SVGFloat n => Element -> SvgRenderM n
attributedRender svg = do
SvgRenderState _idClip idFill idLine <- get
Environment sty preT <- ask
clippedSvg <- renderSvgWithClipping preT svg sty
lineGradDefs <- lineTextureDefs sty
fillGradDefs <- fillTextureDefs sty
return $ do
let gDefs = mappend fillGradDefs lineGradDefs
gDefs `mappend` g_ (R.renderStyles idFill idLine sty) clippedSvg
instance SVGFloat n => Renderable (Path V2 n) SVG where
render _ = R . attributedRender . R.renderPath
instance SVGFloat n => Renderable (Text n) SVG where
render _ = R . attributedRender . R.renderText
instance SVGFloat n => Renderable (DImage n Embedded) SVG where
render _ = R . return . R.renderDImageEmb
renderSVG :: SVGFloat n => FilePath -> SizeSpec V2 n -> QDiagram SVG V2 n Any -> IO ()
renderSVG outFile spec = renderSVG' outFile (SVGOptions spec Nothing (mkPrefix outFile) [] True)
renderPretty :: SVGFloat n => FilePath -> SizeSpec V2 n -> QDiagram SVG V2 n Any -> IO ()
renderPretty outFile spec = renderPretty' outFile (SVGOptions spec Nothing (mkPrefix outFile)[] True)
mkPrefix :: FilePath -> T.Text
mkPrefix = T.filter isAlpha . T.pack . takeBaseName
renderSVG' :: SVGFloat n => FilePath -> Options SVG V2 n -> QDiagram SVG V2 n Any -> IO ()
renderSVG' outFile opts = BS.writeFile outFile . renderBS . renderDia SVG opts
renderPretty' :: SVGFloat n => FilePath -> Options SVG V2 n -> QDiagram SVG V2 n Any -> IO ()
renderPretty' outFile opts = LT.writeFile outFile . prettyText . renderDia SVG opts
data Img = Img !Char !BS.ByteString deriving Typeable
loadImageSVG :: SVGFloat n => FilePath -> IO (QDiagram SVG V2 n Any)
loadImageSVG fp = do
raw <- SBS.readFile fp
dyn <- eIO $ decodeImage raw
let dat = BS.fromChunks [raw]
let pic t d = return $ image (DImage (ImageNative (Img t d))
(dynamicMap imageWidth dyn)
(dynamicMap imageHeight dyn) mempty)
if | pngHeader `SBS.isPrefixOf` raw -> pic 'P' dat
| jpgHeader `SBS.isPrefixOf` raw -> pic 'J' dat
| otherwise -> case dyn of
(ImageYCbCr8 _) -> pic 'J' dat
_ -> pic 'P' =<< eIO (encodeDynamicPng dyn)
where pngHeader :: SBS.ByteString
pngHeader = SBS.pack [137, 80, 78, 71, 13, 10, 26, 10]
jpgHeader :: SBS.ByteString
jpgHeader = SBS.pack [0xFF, 0xD8]
eIO :: Either String a -> IO a
eIO = either fail return
instance SVGFloat n => Renderable (DImage n (Native Img)) SVG where
render _ di@(DImage (ImageNative (Img t d)) _ _ _) = R $ do
mime <- case t of
'J' -> return "image/jpeg"
'P' -> return "image/png"
_ -> fail "Unknown mime type while rendering image"
return $ R.renderDImage di $ R.dataUri mime d
instance Hashable n => Hashable (Options SVG V2 n) where
hashWithSalt s (SVGOptions sz defs ia sa gd) =
s `hashWithSalt`
sz `hashWithSalt`
ds `hashWithSalt`
ia `hashWithSalt`
sa `hashWithSalt`
gd
where ds = fmap renderBS defs