module Text.LaTeX.Packages.TikZ.Syntax (
TPoint
, pointAt , pointAtXY , pointAtXYZ
, relPoint , relPoint_
, TPath (..)
, GridOption (..)
, Step (..)
, startingPoint
, lastPoint
, (->-)
, Parameter (..)
, TikZColor (..)
, Color (..)
, Word8
, TikZ
, emptytikz
, path
, scope
, ActionType (..)
, (->>)
, draw , fill , clip , shade
, filldraw , shadedraw
) where
import Text.LaTeX.Base.Types
import Text.LaTeX.Base.Render
import Text.LaTeX.Base.Syntax
import Text.LaTeX.Packages.Color
import qualified Data.Sequence as S
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid
import Data.Foldable (foldMap)
#endif
data TPoint =
DimPoint Measure Measure
| XYPoint Double Double
| XYZPoint Double Double Double
| RelPoint TPoint
| RelPoint_ TPoint
deriving Show
instance Render TPoint where
render (DimPoint x y) = "(" <> renderCommas [x,y] <> ")"
render (XYPoint x y) = "(" <> renderCommas [x,y] <> ")"
render (XYZPoint x y z) = "(" <> renderCommas [x,y,z] <> ")"
render (RelPoint p) = "++" <> render p
render (RelPoint_ p) = "+" <> render p
pointAt :: Measure -> Measure -> TPoint
pointAt = DimPoint
pointAtXY :: Double -> Double -> TPoint
pointAtXY = XYPoint
pointAtXYZ :: Double -> Double -> Double -> TPoint
pointAtXYZ = XYZPoint
relPoint :: TPoint -> TPoint
relPoint (RelPoint x) = RelPoint x
relPoint (RelPoint_ x) = RelPoint x
relPoint p = RelPoint p
relPoint_ :: TPoint -> TPoint
relPoint_ (RelPoint x) = RelPoint_ x
relPoint_ (RelPoint_ x) = RelPoint_ x
relPoint_ p = RelPoint_ p
data TPath =
Start TPoint
| Cycle TPath
| Line TPath TPoint
| Rectangle TPath TPoint
| Circle TPath Double
| Ellipse TPath Double Double
| Grid TPath [GridOption] TPoint
| Node TPath LaTeX
deriving Show
data GridOption =
GridStep Step
deriving Show
data Step =
DimStep Measure
| XYStep Double
| PointStep TPoint
deriving Show
instance Render TPath where
render (Start p) = render p
render (Cycle p) = render p <> " -- cycle"
render (Line p1 p2) = render p1 <> " -- " <> render p2
render (Rectangle p1 p2) = render p1 <> " rectangle " <> render p2
render (Circle p r) = render p <> " circle (" <> render r <> ")"
render (Ellipse p r1 r2) = render p <> " ellipse (" <> render r1 <> " and " <> render r2 <> ")"
render (Grid p1 [] p2) = render p1 <> " grid " <> render p2
render (Grid p1 xs p2) = render p1 <> " grid " <> render xs <> " " <> render p2
render (Node p l) = render p <> " node[transform shape] " <> render (TeXBraces l)
instance Render GridOption where
render (GridStep s) = "step=" <> render s
instance Render Step where
render (DimStep m) = render m
render (XYStep q) = render q
render (PointStep p) = render p
startingPoint :: TPath -> TPoint
startingPoint (Start p) = p
startingPoint (Cycle x) = startingPoint x
startingPoint (Line x _) = startingPoint x
startingPoint (Rectangle x _) = startingPoint x
startingPoint (Circle x _) = startingPoint x
startingPoint (Ellipse x _ _) = startingPoint x
startingPoint (Grid x _ _) = startingPoint x
startingPoint (Node x _) = startingPoint x
lastPoint :: TPath -> TPoint
lastPoint (Start p) = p
lastPoint (Cycle x) = startingPoint x
lastPoint (Line _ p) = p
lastPoint (Rectangle _ p) = p
lastPoint (Circle x _) = lastPoint x
lastPoint (Ellipse x _ _) = lastPoint x
lastPoint (Grid _ _ p) = p
lastPoint (Node x _) = lastPoint x
(->-) :: TPath -> TPoint -> TPath
(->-) = Line
data TikZColor =
BasicColor Color
| RGBColor Word8 Word8 Word8
deriving Show
instance Render TikZColor where
render (BasicColor c) = render c
render (RGBColor r g b) = "{rgb,255:red," <> render r <> ";green," <> render g <> ";blue," <> render b <> "}"
data Parameter =
TWidth Measure
| TColor TikZColor
| TScale Double
| TRotate Double
deriving Show
renderPair :: Render a => Text -> a -> Text
renderPair x y = x <> "=" <> render y
instance Render Parameter where
render (TWidth m) = renderPair "line width" m
render (TColor c) = renderPair "color" c
render (TScale q) = renderPair "scale" q
render (TRotate a) = renderPair "rotate" a
data TikZ =
PathAction [ActionType] TPath
| Scope [Parameter] TikZ
| TikZSeq (S.Seq TikZ)
deriving Show
data ActionType = Draw | Fill | Clip | Shade deriving Show
emptytikz :: TikZ
emptytikz = TikZSeq mempty
instance Render TikZ where
render (PathAction ts p) = "\\path" <> render ts <> " " <> render p <> " ; "
render (Scope ps t) = "\\begin{scope}" <> render ps <> render t <> "\\end{scope}"
render (TikZSeq ts) = foldMap render ts
instance Render ActionType where
render Draw = "draw"
render Fill = "fill"
render Clip = "clip"
render Shade = "shade"
path :: [ActionType] -> TPath -> TikZ
path = PathAction
scope :: [Parameter] -> TikZ -> TikZ
scope = Scope
(->>) :: TikZ -> TikZ -> TikZ
(TikZSeq s1) ->> (TikZSeq s2) = TikZSeq (s1 <> s2)
(TikZSeq s) ->> a = TikZSeq $ s S.|> a
a ->> (TikZSeq s) = TikZSeq $ a S.<| s
a ->> b = TikZSeq $ a S.<| S.singleton b
draw :: TPath -> TikZ
draw = path [Draw]
fill :: TPath -> TikZ
fill = path [Fill]
clip :: TPath -> TikZ
clip = path [Clip]
shade :: TPath -> TikZ
shade = path [Shade]
filldraw :: TPath -> TikZ
filldraw = path [Fill,Draw]
shadedraw :: TPath -> TikZ
shadedraw = path [Shade,Draw]