module Graphics.PDF.Shading(
PDFShading(..)
, paintWithShading
, applyShading
) where
import Graphics.PDF.Draw
import Graphics.PDF.LowLevel.Types
import Control.Monad.State(gets)
import Graphics.PDF.Shapes(setAsClipPath)
import Control.Monad.Writer
import Graphics.PDF.LowLevel.Serializer
applyShading :: PDFShading -> Draw ()
applyShading :: PDFShading -> Draw ()
applyShading PDFShading
shade = do
Map PDFShading String
shadingMap <- forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets DrawState -> Map PDFShading String
shadings
(String
newName,Map PDFShading String
newMap) <- forall a.
(Ord a, PdfResourceObject a) =>
String -> a -> Map a String -> Draw (String, Map a String)
setResource String
"Shading" PDFShading
shade Map PDFShading String
shadingMap
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modifyStrict forall a b. (a -> b) -> a -> b
$ \DrawState
s -> DrawState
s { shadings :: Map PDFShading String
shadings = Map PDFShading String
newMap }
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$ [ forall s a. SerializeValue s a => a -> s
serialize String
"\n/"
, forall s a. SerializeValue s a => a -> s
serialize String
newName
, forall s a. SerializeValue s a => a -> s
serialize String
" sh"
]
paintWithShading :: PDFShading
-> Draw a
-> Draw ()
paintWithShading :: forall a. PDFShading -> Draw a -> Draw ()
paintWithShading PDFShading
shade Draw a
d = do
forall a. Draw a -> Draw a
withNewContext forall a b. (a -> b) -> a -> b
$ do
a
_ <- Draw a
d
Draw ()
setAsClipPath
PDFShading -> Draw ()
applyShading PDFShading
shade