{-# LANGUAGE OverloadedStrings, CPP #-}
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 Int -> TPoint -> ShowS
[TPoint] -> ShowS
TPoint -> String
(Int -> TPoint -> ShowS)
-> (TPoint -> String) -> ([TPoint] -> ShowS) -> Show TPoint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TPoint -> ShowS
showsPrec :: Int -> TPoint -> ShowS
$cshow :: TPoint -> String
show :: TPoint -> String
$cshowList :: [TPoint] -> ShowS
showList :: [TPoint] -> ShowS
Show
instance Render TPoint where
render :: TPoint -> Text
render (DimPoint Measure
x Measure
y) = Text
"(" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Measure] -> Text
forall a. Render a => [a] -> Text
renderCommas [Measure
x,Measure
y] Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
render (XYPoint Double
x Double
y) = Text
"(" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Double] -> Text
forall a. Render a => [a] -> Text
renderCommas [Double
x,Double
y] Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
render (XYZPoint Double
x Double
y Double
z) = Text
"(" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Double] -> Text
forall a. Render a => [a] -> Text
renderCommas [Double
x,Double
y,Double
z] Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
render (RelPoint TPoint
p) = Text
"++" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> TPoint -> Text
forall a. Render a => a -> Text
render TPoint
p
render (RelPoint_ TPoint
p) = Text
"+" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> TPoint -> Text
forall a. Render a => a -> Text
render TPoint
p
pointAt :: Measure -> Measure -> TPoint
pointAt :: Measure -> Measure -> TPoint
pointAt = Measure -> Measure -> TPoint
DimPoint
pointAtXY :: Double -> Double -> TPoint
pointAtXY :: Double -> Double -> TPoint
pointAtXY = Double -> Double -> TPoint
XYPoint
pointAtXYZ :: Double -> Double -> Double -> TPoint
pointAtXYZ :: Double -> Double -> Double -> TPoint
pointAtXYZ = Double -> Double -> Double -> TPoint
XYZPoint
relPoint :: TPoint -> TPoint
relPoint :: TPoint -> TPoint
relPoint (RelPoint TPoint
x) = TPoint -> TPoint
RelPoint TPoint
x
relPoint (RelPoint_ TPoint
x) = TPoint -> TPoint
RelPoint TPoint
x
relPoint TPoint
p = TPoint -> TPoint
RelPoint TPoint
p
relPoint_ :: TPoint -> TPoint
relPoint_ :: TPoint -> TPoint
relPoint_ (RelPoint TPoint
x) = TPoint -> TPoint
RelPoint_ TPoint
x
relPoint_ (RelPoint_ TPoint
x) = TPoint -> TPoint
RelPoint_ TPoint
x
relPoint_ TPoint
p = TPoint -> TPoint
RelPoint_ TPoint
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 Int -> TPath -> ShowS
[TPath] -> ShowS
TPath -> String
(Int -> TPath -> ShowS)
-> (TPath -> String) -> ([TPath] -> ShowS) -> Show TPath
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TPath -> ShowS
showsPrec :: Int -> TPath -> ShowS
$cshow :: TPath -> String
show :: TPath -> String
$cshowList :: [TPath] -> ShowS
showList :: [TPath] -> ShowS
Show
newtype GridOption =
GridStep Step
deriving Int -> GridOption -> ShowS
[GridOption] -> ShowS
GridOption -> String
(Int -> GridOption -> ShowS)
-> (GridOption -> String)
-> ([GridOption] -> ShowS)
-> Show GridOption
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GridOption -> ShowS
showsPrec :: Int -> GridOption -> ShowS
$cshow :: GridOption -> String
show :: GridOption -> String
$cshowList :: [GridOption] -> ShowS
showList :: [GridOption] -> ShowS
Show
data Step =
DimStep Measure
| XYStep Double
| PointStep TPoint
deriving Int -> Step -> ShowS
[Step] -> ShowS
Step -> String
(Int -> Step -> ShowS)
-> (Step -> String) -> ([Step] -> ShowS) -> Show Step
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Step -> ShowS
showsPrec :: Int -> Step -> ShowS
$cshow :: Step -> String
show :: Step -> String
$cshowList :: [Step] -> ShowS
showList :: [Step] -> ShowS
Show
instance Render TPath where
render :: TPath -> Text
render (Start TPoint
p) = TPoint -> Text
forall a. Render a => a -> Text
render TPoint
p
render (Cycle TPath
p) = TPath -> Text
forall a. Render a => a -> Text
render TPath
p Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" -- cycle"
render (Line TPath
p1 TPoint
p2) = TPath -> Text
forall a. Render a => a -> Text
render TPath
p1 Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" -- " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> TPoint -> Text
forall a. Render a => a -> Text
render TPoint
p2
render (Rectangle TPath
p1 TPoint
p2) = TPath -> Text
forall a. Render a => a -> Text
render TPath
p1 Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" rectangle " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> TPoint -> Text
forall a. Render a => a -> Text
render TPoint
p2
render (Circle TPath
p Double
r) = TPath -> Text
forall a. Render a => a -> Text
render TPath
p Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" circle (" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Double -> Text
forall a. Render a => a -> Text
render Double
r Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
render (Ellipse TPath
p Double
r1 Double
r2) = TPath -> Text
forall a. Render a => a -> Text
render TPath
p Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" ellipse (" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Double -> Text
forall a. Render a => a -> Text
render Double
r1 Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" and " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Double -> Text
forall a. Render a => a -> Text
render Double
r2 Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
render (Grid TPath
p1 [] TPoint
p2) = TPath -> Text
forall a. Render a => a -> Text
render TPath
p1 Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" grid " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> TPoint -> Text
forall a. Render a => a -> Text
render TPoint
p2
render (Grid TPath
p1 [GridOption]
xs TPoint
p2) = TPath -> Text
forall a. Render a => a -> Text
render TPath
p1 Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" grid " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [GridOption] -> Text
forall a. Render a => a -> Text
render [GridOption]
xs Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> TPoint -> Text
forall a. Render a => a -> Text
render TPoint
p2
render (Node TPath
p LaTeX
l) = TPath -> Text
forall a. Render a => a -> Text
render TPath
p Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" node[transform shape] " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> LaTeX -> Text
forall a. Render a => a -> Text
render (LaTeX -> LaTeX
TeXBraces LaTeX
l)
instance Render GridOption where
render :: GridOption -> Text
render (GridStep Step
s) = Text
"step=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Step -> Text
forall a. Render a => a -> Text
render Step
s
instance Render Step where
render :: Step -> Text
render (DimStep Measure
m) = Measure -> Text
forall a. Render a => a -> Text
render Measure
m
render (XYStep Double
q) = Double -> Text
forall a. Render a => a -> Text
render Double
q
render (PointStep TPoint
p) = TPoint -> Text
forall a. Render a => a -> Text
render TPoint
p
startingPoint :: TPath -> TPoint
startingPoint :: TPath -> TPoint
startingPoint (Start TPoint
p) = TPoint
p
startingPoint (Cycle TPath
x) = TPath -> TPoint
startingPoint TPath
x
startingPoint (Line TPath
x TPoint
_) = TPath -> TPoint
startingPoint TPath
x
startingPoint (Rectangle TPath
x TPoint
_) = TPath -> TPoint
startingPoint TPath
x
startingPoint (Circle TPath
x Double
_) = TPath -> TPoint
startingPoint TPath
x
startingPoint (Ellipse TPath
x Double
_ Double
_) = TPath -> TPoint
startingPoint TPath
x
startingPoint (Grid TPath
x [GridOption]
_ TPoint
_) = TPath -> TPoint
startingPoint TPath
x
startingPoint (Node TPath
x LaTeX
_) = TPath -> TPoint
startingPoint TPath
x
lastPoint :: TPath -> TPoint
lastPoint :: TPath -> TPoint
lastPoint (Start TPoint
p) = TPoint
p
lastPoint (Cycle TPath
x) = TPath -> TPoint
startingPoint TPath
x
lastPoint (Line TPath
_ TPoint
p) = TPoint
p
lastPoint (Rectangle TPath
_ TPoint
p) = TPoint
p
lastPoint (Circle TPath
x Double
_) = TPath -> TPoint
lastPoint TPath
x
lastPoint (Ellipse TPath
x Double
_ Double
_) = TPath -> TPoint
lastPoint TPath
x
lastPoint (Grid TPath
_ [GridOption]
_ TPoint
p) = TPoint
p
lastPoint (Node TPath
x LaTeX
_) = TPath -> TPoint
lastPoint TPath
x
(->-) :: TPath -> TPoint -> TPath
->- :: TPath -> TPoint -> TPath
(->-) = TPath -> TPoint -> TPath
Line
data TikZColor =
BasicColor Color
| RGBColor Word8 Word8 Word8
deriving Int -> TikZColor -> ShowS
[TikZColor] -> ShowS
TikZColor -> String
(Int -> TikZColor -> ShowS)
-> (TikZColor -> String)
-> ([TikZColor] -> ShowS)
-> Show TikZColor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TikZColor -> ShowS
showsPrec :: Int -> TikZColor -> ShowS
$cshow :: TikZColor -> String
show :: TikZColor -> String
$cshowList :: [TikZColor] -> ShowS
showList :: [TikZColor] -> ShowS
Show
instance Render TikZColor where
render :: TikZColor -> Text
render (BasicColor Color
c) = Color -> Text
forall a. Render a => a -> Text
render Color
c
render (RGBColor Word8
r Word8
g Word8
b) = Text
"{rgb,255:red," Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Word8 -> Text
forall a. Render a => a -> Text
render Word8
r Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
";green," Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Word8 -> Text
forall a. Render a => a -> Text
render Word8
g Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
";blue," Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Word8 -> Text
forall a. Render a => a -> Text
render Word8
b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}"
data Parameter =
TWidth Measure
| TColor TikZColor
| TScale Double
| TRotate Double
deriving Int -> Parameter -> ShowS
[Parameter] -> ShowS
Parameter -> String
(Int -> Parameter -> ShowS)
-> (Parameter -> String)
-> ([Parameter] -> ShowS)
-> Show Parameter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Parameter -> ShowS
showsPrec :: Int -> Parameter -> ShowS
$cshow :: Parameter -> String
show :: Parameter -> String
$cshowList :: [Parameter] -> ShowS
showList :: [Parameter] -> ShowS
Show
renderPair :: Render a => Text -> a -> Text
renderPair :: forall a. Render a => Text -> a -> Text
renderPair Text
x a
y = Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> a -> Text
forall a. Render a => a -> Text
render a
y
instance Render Parameter where
render :: Parameter -> Text
render (TWidth Measure
m) = Text -> Measure -> Text
forall a. Render a => Text -> a -> Text
renderPair Text
"line width" Measure
m
render (TColor TikZColor
c) = Text -> TikZColor -> Text
forall a. Render a => Text -> a -> Text
renderPair Text
"color" TikZColor
c
render (TScale Double
q) = Text -> Double -> Text
forall a. Render a => Text -> a -> Text
renderPair Text
"scale" Double
q
render (TRotate Double
a) = Text -> Double -> Text
forall a. Render a => Text -> a -> Text
renderPair Text
"rotate" Double
a
data TikZ =
PathAction [ActionType] TPath
| Scope [Parameter] TikZ
| TikZSeq (S.Seq TikZ)
deriving Int -> TikZ -> ShowS
[TikZ] -> ShowS
TikZ -> String
(Int -> TikZ -> ShowS)
-> (TikZ -> String) -> ([TikZ] -> ShowS) -> Show TikZ
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TikZ -> ShowS
showsPrec :: Int -> TikZ -> ShowS
$cshow :: TikZ -> String
show :: TikZ -> String
$cshowList :: [TikZ] -> ShowS
showList :: [TikZ] -> ShowS
Show
data ActionType = Draw | Fill | Clip | Shade deriving Int -> ActionType -> ShowS
[ActionType] -> ShowS
ActionType -> String
(Int -> ActionType -> ShowS)
-> (ActionType -> String)
-> ([ActionType] -> ShowS)
-> Show ActionType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ActionType -> ShowS
showsPrec :: Int -> ActionType -> ShowS
$cshow :: ActionType -> String
show :: ActionType -> String
$cshowList :: [ActionType] -> ShowS
showList :: [ActionType] -> ShowS
Show
emptytikz :: TikZ
emptytikz :: TikZ
emptytikz = Seq TikZ -> TikZ
TikZSeq Seq TikZ
forall a. Monoid a => a
mempty
instance Render TikZ where
render :: TikZ -> Text
render (PathAction [ActionType]
ts TPath
p) = Text
"\\path" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [ActionType] -> Text
forall a. Render a => a -> Text
render [ActionType]
ts Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> TPath -> Text
forall a. Render a => a -> Text
render TPath
p Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" ; "
render (Scope [Parameter]
ps TikZ
t) = Text
"\\begin{scope}" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Parameter] -> Text
forall a. Render a => a -> Text
render [Parameter]
ps Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> TikZ -> Text
forall a. Render a => a -> Text
render TikZ
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\\end{scope}"
render (TikZSeq Seq TikZ
ts) = (TikZ -> Text) -> Seq TikZ -> Text
forall m a. Monoid m => (a -> m) -> Seq a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap TikZ -> Text
forall a. Render a => a -> Text
render Seq TikZ
ts
instance Render ActionType where
render :: ActionType -> Text
render ActionType
Draw = Text
"draw"
render ActionType
Fill = Text
"fill"
render ActionType
Clip = Text
"clip"
render ActionType
Shade = Text
"shade"
path :: [ActionType] -> TPath -> TikZ
path :: [ActionType] -> TPath -> TikZ
path = [ActionType] -> TPath -> TikZ
PathAction
scope :: [Parameter] -> TikZ -> TikZ
scope :: [Parameter] -> TikZ -> TikZ
scope = [Parameter] -> TikZ -> TikZ
Scope
(->>) :: TikZ -> TikZ -> TikZ
(TikZSeq Seq TikZ
s1) ->> :: TikZ -> TikZ -> TikZ
->> (TikZSeq Seq TikZ
s2) = Seq TikZ -> TikZ
TikZSeq (Seq TikZ
s1 Seq TikZ -> Seq TikZ -> Seq TikZ
forall a. Semigroup a => a -> a -> a
<> Seq TikZ
s2)
(TikZSeq Seq TikZ
s) ->> TikZ
a = Seq TikZ -> TikZ
TikZSeq (Seq TikZ -> TikZ) -> Seq TikZ -> TikZ
forall a b. (a -> b) -> a -> b
$ Seq TikZ
s Seq TikZ -> TikZ -> Seq TikZ
forall a. Seq a -> a -> Seq a
S.|> TikZ
a
TikZ
a ->> (TikZSeq Seq TikZ
s) = Seq TikZ -> TikZ
TikZSeq (Seq TikZ -> TikZ) -> Seq TikZ -> TikZ
forall a b. (a -> b) -> a -> b
$ TikZ
a TikZ -> Seq TikZ -> Seq TikZ
forall a. a -> Seq a -> Seq a
S.<| Seq TikZ
s
TikZ
a ->> TikZ
b = Seq TikZ -> TikZ
TikZSeq (Seq TikZ -> TikZ) -> Seq TikZ -> TikZ
forall a b. (a -> b) -> a -> b
$ TikZ
a TikZ -> Seq TikZ -> Seq TikZ
forall a. a -> Seq a -> Seq a
S.<| TikZ -> Seq TikZ
forall a. a -> Seq a
S.singleton TikZ
b
draw :: TPath -> TikZ
draw :: TPath -> TikZ
draw = [ActionType] -> TPath -> TikZ
path [ActionType
Draw]
fill :: TPath -> TikZ
fill :: TPath -> TikZ
fill = [ActionType] -> TPath -> TikZ
path [ActionType
Fill]
clip :: TPath -> TikZ
clip :: TPath -> TikZ
clip = [ActionType] -> TPath -> TikZ
path [ActionType
Clip]
shade :: TPath -> TikZ
shade :: TPath -> TikZ
shade = [ActionType] -> TPath -> TikZ
path [ActionType
Shade]
filldraw :: TPath -> TikZ
filldraw :: TPath -> TikZ
filldraw = [ActionType] -> TPath -> TikZ
path [ActionType
Fill,ActionType
Draw]
shadedraw :: TPath -> TikZ
shadedraw :: TPath -> TikZ
shadedraw = [ActionType] -> TPath -> TikZ
path [ActionType
Shade,ActionType
Draw]