module Diagrams.Backend.PGF.Render
( PGF (..)
, Options (..)
, Render (..)
, surface
, sizeSpec
, readable
, standalone
, escapeString
) where
import Control.Monad (when)
import Data.ByteString.Builder
import qualified Data.Foldable as F (foldMap)
import Data.Functor
import Data.Hashable (Hashable (..))
import Data.Tree (Tree (Node))
import Diagrams.Core.Types
import Diagrams.Prelude hiding ((<~))
import Diagrams.Backend.PGF.Hbox (Hbox (..))
import Diagrams.Backend.PGF.Surface (Surface)
import Diagrams.TwoD.Adjust (adjustDia2D)
import Diagrams.TwoD.Path
import Diagrams.TwoD.Text (Text (..), TextAlignment (..), getFontSize,
getFontSlant, getFontWeight)
import Data.Typeable
import qualified Graphics.Rendering.PGF as P
import Prelude
data PGF = PGF
deriving (Show, Typeable)
type instance V PGF = V2
type instance N PGF = Double
instance TypeableFloat n => Backend PGF V2 n where
newtype Render PGF V2 n = R (P.Render n)
type Result PGF V2 n = Builder
data Options PGF V2 n = PGFOptions
{ _surface :: Surface
, _sizeSpec :: SizeSpec V2 n
, _readable :: Bool
, _standalone :: Bool
}
renderRTree _ ops (toRender -> R r) =
P.renderWith (ops^.surface) (ops^.readable) (ops^.standalone) bounds r
where
bounds = specToSize 100 (ops^.sizeSpec)
adjustDia = adjustDia2D sizeSpec
toRender :: TypeableFloat n => RTree PGF V2 n Annotation -> Render PGF V2 n
toRender (Node n rs) = case n of
RPrim p -> render PGF p
RStyle sty' -> R $ do
sty <- P.style <<<>= sty'
clips <- use (P.style . _clip)
clip clips r <* (P.style .= sty)
RAnnot (OpacityGroup x) -> R $ P.opacityGroup x r
_ -> R r
where R r = F.foldMap toRender rs
instance Fractional n => Default (Options PGF V2 n) where
def = PGFOptions
{ _surface = def
, _sizeSpec = absolute
, _readable = True
, _standalone = False
}
instance Monoid (Render PGF V2 n) where
mempty = R $ return ()
R ra `mappend` R rb = R $ ra >> rb
surface :: Lens' (Options PGF V2 n) Surface
surface = lens _surface (\o s -> o {_surface = s})
standalone :: Lens' (Options PGF V2 n) Bool
standalone = lens _standalone (\o s -> o {_standalone = s})
sizeSpec :: Lens' (Options PGF V2 n) (SizeSpec V2 n)
sizeSpec = lens _sizeSpec (\o s -> o {_sizeSpec = s})
readable :: Lens' (Options PGF V2 n) Bool
readable = lens _readable (\o b -> o {_readable = b})
(<~) :: AttributeClass a => (b -> P.Render n) -> (a -> b) -> P.Render n
renderF <~ getF = do
s <- uses P.style (fmap getF . getAttr)
maybe (return ()) renderF s
infixr 2 <~
fade :: Color c => Getting (Endo (Endo Double)) (Style V2 n) Double -> c -> P.RenderM n (AlphaColour Double)
fade g c = use P.style <&> \s ->
dissolve (productOf (_opacity <> g) s) (toAlphaColour c)
setFillTexture :: RealFloat n => Path V2 n -> Texture n -> P.Render n
setFillTexture p t = case t of
SC (SomeColor c) -> fade _fillOpacity c >>= P.setFillColor
LG g -> P.linearGradient p g
RG g -> P.radialGradient p g
setLineTexture :: RealFloat n => Texture n -> P.Render n
setLineTexture (SC (SomeColor c)) = fade _strokeOpacity c >>= P.setLineColor
setLineTexture _ = return ()
clip :: TypeableFloat n => [Path V2 n] -> P.Render n -> P.Render n
clip paths r = go paths
where
go [] = r
go (p:ps) = P.scope $ P.path p >> P.clip >> go ps
escapeString :: String -> String
escapeString = concatMap escapeChar
where
escapeChar ch = case ch of
'$' -> "\\$"
'%' -> "\\letterpercent{}"
'&' -> "\\&"
'#' -> "\\#"
'_' -> "\\_"
'{' -> "$\\{$"
'}' -> "$\\}$"
'\\'-> "$\\backslash{}$"
'~' -> "\\~{}"
'^' -> "\\^{}"
'[' -> "{[}"
']' -> "{]}"
x -> [x]
instance TypeableFloat n => Renderable (Path V2 n) PGF where
render _ path = R . P.scope $ do
let canFill = noneOf (_head . located) isLine path
doFill <- if canFill
then do
mFillTexture <- preuse (P.style . _fillTexture)
case mFillTexture of
Nothing -> return False
Just t -> do
setFillTexture path t
P.setFillRule <~ getFillRule
return (has _SC t)
else return False
w <- use (P.style . _lineWidthU . non 0)
let doStroke = w > 0.0001
when doStroke $ do
P.setLineWidth w
setLineTexture <~ getLineTexture
P.setLineJoin <~ getLineJoin
P.setLineCap <~ getLineCap
P.setDash <~ getDashing
P.path path
P.usePath doFill doStroke
instance TypeableFloat n => Renderable (Text n) PGF where
render _ (Text tt txtAlign str) = R . P.scope $ do
setFillTexture mempty <~ getFillTexture
P.applyTransform tt
(P.applyScale . (/8)) <~ getFontSize
P.renderText (P.setTextAlign txtAlign) $ do
P.setFontWeight <~ getFontWeight
P.setFontSlant <~ getFontSlant
P.rawString str
instance TypeableFloat n => Renderable (Hbox n) PGF where
render _ (Hbox tt str) = R . P.scope $ do
P.applyTransform tt
P.renderText (P.setTextAlign BaselineText) (P.rawString str)
instance RealFloat n => Renderable (DImage n External) PGF where
render _ = R . P.image
instance RealFloat n => Renderable (DImage n Embedded) PGF where
render _ = R . P.embeddedImage
instance Hashable n => Hashable (Options PGF V2 n) where
hashWithSalt s (PGFOptions sf sz rd st)
= s `hashWithSalt`
sf `hashWithSalt`
sz `hashWithSalt`
rd `hashWithSalt`
st