{-# LANGUAGE OverloadedStrings, CPP #-}

-- | This module defines the syntax of a Ti/k/Z script.
--
-- To generate a Ti/k/Z script, first create a 'TPath' using
-- data constructors, or alternatively, use a 'PathBuilder'
-- from the "Text.LaTeX.Packages.TikZ.PathBuilder" module.
--
-- Once a 'TPath' is created, use 'path' to render a picture
-- from it. Use 'scope' to apply some parameters to your picture,
-- such line width or color.
module Text.LaTeX.Packages.TikZ.Syntax (
    -- * Points
    TPoint
  , pointAt , pointAtXY , pointAtXYZ
  , relPoint , relPoint_
    -- * Paths
    -- ** Types
  , TPath (..)
  , GridOption (..)
  , Step (..)
    -- ** Critical points
  , startingPoint
  , lastPoint
    -- ** Functions
  , (->-)
    -- * Parameters
  , Parameter (..)
  , TikZColor (..)
  , Color (..)
  , Word8
    -- * TikZ
  , TikZ
  , emptytikz
  , path
  , scope
  , ActionType (..)
  , (->>)
    -- * Sugar
  , 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

-- POINTS

-- | A point in Ti/k/Z.
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
showList :: [TPoint] -> ShowS
$cshowList :: [TPoint] -> ShowS
show :: TPoint -> String
$cshow :: TPoint -> String
showsPrec :: Int -> TPoint -> ShowS
$cshowsPrec :: Int -> 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

-- | Point using 'Measure's for coordinantes.
pointAt :: Measure -> Measure -> TPoint
pointAt :: Measure -> Measure -> TPoint
pointAt = Measure -> Measure -> TPoint
DimPoint

-- | Point using numbers as coordinates.
pointAtXY :: Double -> Double -> TPoint
pointAtXY :: Double -> Double -> TPoint
pointAtXY = Double -> Double -> TPoint
XYPoint

-- | Three-dimensional point.
pointAtXYZ :: Double -> Double -> Double -> TPoint
pointAtXYZ :: Double -> Double -> Double -> TPoint
pointAtXYZ = Double -> Double -> Double -> TPoint
XYZPoint

-- | Makes a point relative to the previous.
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

-- PATHS

-- | Type for TikZ paths. Every 'TPath' has two fundamental points: the /starting point/
--   and the /last point/.
--   The starting point is set using the 'Start' constructor.
--   The last point then is modified by the other constructors.
--   Below a explanation of each one of them.
--   Note that both starting point and last point may coincide.
--   You can use the functions 'startingPoint' and 'lastPoint' to calculate them.
--   After creating a 'TPath', use 'path' to do something useful with it.
data TPath =
    Start TPoint -- ^ Let @y = Start p@.
                 --
                 -- /Operation:/ Set the starting point of a path.
                 --
                 -- /Last point:/ The last point of @y@ is @p@.
  | Cycle TPath  -- ^ Let @y = Cycle x@.
                 --
                 -- /Operation:/ Close a path with a line from the last point of @x@ to
                 -- the starting point of @x@.
                 --
                 -- /Last point:/ The last point of @y@ is the starting point of @x@.
  | Line TPath TPoint -- ^ Let @y = Line x p@.
                      --
                      -- /Operation:/ Extend the current path from the last point of @x@
                      -- in a straight line to @p@.
                      --
                      -- /Last point:/ The last point of @y@ is @p@.
  | Rectangle TPath TPoint -- ^ Let @y = Rectangle x p@.
                           --
                           -- /Operation:/ Define a rectangle using the last point of
                           -- @x@ as one corner and @p@ as the another corner.
                           --
                           -- /Last point:/ The last point of @y@ is @p@.
  | Circle TPath Double -- ^ Let @y = Circle x r@.
                        --
                        -- /Operation:/ Define a circle with center at the last point
                        -- of x and radius @r@.
                        --
                        -- /Last point:/ The last point of @y@ is the same as the last
                        -- point of @x@.
  | Ellipse TPath Double Double -- ^ Let @y = Ellipse x r1 r2@.
                                --
                                -- /Operation:/ Define a ellipse with center at the last
                                -- point of @x@, width the double of @r1@ and height
                                -- the double of @r2@.
                                --
                                -- /Last point:/ The last point of @y@ is the same as the
                                -- last point of @x@.
  | Grid TPath [GridOption] TPoint
  | Node TPath LaTeX -- ^ Let @y = Node x l@.
                     --
                     -- /Operation:/ Set a text centered at the last point of @x@.
                     --
                     -- /Last point:/ The last point of @y@ is the same as the last
                     -- point of @x@.
    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
showList :: [TPath] -> ShowS
$cshowList :: [TPath] -> ShowS
show :: TPath -> String
$cshow :: TPath -> String
showsPrec :: Int -> TPath -> ShowS
$cshowsPrec :: Int -> 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
showList :: [GridOption] -> ShowS
$cshowList :: [GridOption] -> ShowS
show :: GridOption -> String
$cshow :: GridOption -> String
showsPrec :: Int -> GridOption -> ShowS
$cshowsPrec :: Int -> 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
showList :: [Step] -> ShowS
$cshowList :: [Step] -> ShowS
show :: Step -> String
$cshow :: Step -> String
showsPrec :: Int -> Step -> ShowS
$cshowsPrec :: Int -> 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

-- Starting and Last points

-- | Calculate the starting point of a 'TPath'.
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

-- | Calculate the last point of a 'TPath'.
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

-- Path builders

-- | Alias of 'Line'.
(->-) :: TPath -> TPoint -> TPath
->- :: TPath -> TPoint -> TPath
(->-) = TPath -> TPoint -> TPath
Line

-- Parameters

-- | Color models accepted by Ti/k/Z.
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
showList :: [TikZColor] -> ShowS
$cshowList :: [TikZColor] -> ShowS
show :: TikZColor -> String
$cshow :: TikZColor -> String
showsPrec :: Int -> TikZColor -> ShowS
$cshowsPrec :: Int -> 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
"}"

-- | Parameters to use in a 'scope' to change how things
--   are rendered within that scope.
data Parameter =
   TWidth Measure
 | TColor TikZColor
 | TScale Double
 | TRotate Double -- ^ Angle is in degrees.
     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
showList :: [Parameter] -> ShowS
$cshowList :: [Parameter] -> ShowS
show :: Parameter -> String
$cshow :: Parameter -> String
showsPrec :: Int -> Parameter -> ShowS
$cshowsPrec :: Int -> Parameter -> ShowS
Show

renderPair :: Render a => Text -> a -> Text
renderPair :: 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

-- TikZ

-- | A Ti/k/Z script.
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
showList :: [TikZ] -> ShowS
$cshowList :: [TikZ] -> ShowS
show :: TikZ -> String
$cshow :: TikZ -> String
showsPrec :: Int -> TikZ -> ShowS
$cshowsPrec :: Int -> TikZ -> ShowS
Show

-- | Different types of actions that can be performed
--   with a 'TPath'. See 'path' for more information.
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
showList :: [ActionType] -> ShowS
$cshowList :: [ActionType] -> ShowS
show :: ActionType -> String
$cshow :: ActionType -> String
showsPrec :: Int -> ActionType -> ShowS
$cshowsPrec :: Int -> ActionType -> ShowS
Show

-- | Just an empty script.
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 (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"

-- | A path can be used in different ways.
--
-- * 'Draw': Just draw the path.
--
-- * 'Fill': Fill the area inside the path.
--
-- * 'Clip': Clean everything outside the path.
--
-- * 'Shade': Shade the area inside the path.
--
--   It is possible to stack different effects in the list.
--
--   Example of usage:
--
-- > path [Draw] $ Start (pointAtXY 0 0) ->- pointAtXY 1 1
--
--   Most common usages are exported as functions. See
--   'draw', 'fill', 'clip', 'shade', 'filldraw' and
--   'shadedraw'.
path :: [ActionType] -> TPath -> TikZ
path :: [ActionType] -> TPath -> TikZ
path = [ActionType] -> TPath -> TikZ
PathAction

-- | Applies a scope to a Ti/k/Z script.
scope :: [Parameter] -> TikZ -> TikZ
scope :: [Parameter] -> TikZ -> TikZ
scope = [Parameter] -> TikZ -> TikZ
Scope

-- | Sequence two Ti/k/Z scripts.
(->>) :: 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

-- SUGAR

-- | Equivalent to @path [Draw]@.
draw :: TPath -> TikZ
draw :: TPath -> TikZ
draw = [ActionType] -> TPath -> TikZ
path [ActionType
Draw]

-- | Equivalent to @path [Fill]@.
fill :: TPath -> TikZ
fill :: TPath -> TikZ
fill = [ActionType] -> TPath -> TikZ
path [ActionType
Fill]

-- | Equivalent to @path [Clip]@.
clip :: TPath -> TikZ
clip :: TPath -> TikZ
clip = [ActionType] -> TPath -> TikZ
path [ActionType
Clip]

-- | Equivalent to @path [Shade]@.
shade :: TPath -> TikZ
shade :: TPath -> TikZ
shade = [ActionType] -> TPath -> TikZ
path [ActionType
Shade]

-- | Equivalent to @path [Fill,Draw]@.
filldraw :: TPath -> TikZ
filldraw :: TPath -> TikZ
filldraw = [ActionType] -> TPath -> TikZ
path [ActionType
Fill,ActionType
Draw]

-- | Equivalent to @path [Shade,Draw]@.
shadedraw :: TPath -> TikZ
shadedraw :: TPath -> TikZ
shadedraw = [ActionType] -> TPath -> TikZ
path [ActionType
Shade,ActionType
Draw]