HaTeX-3.22.0.0: The Haskell LaTeX library.

Safe HaskellSafe
LanguageHaskell2010

Text.LaTeX.Packages.TikZ.Syntax

Contents

Description

This module defines the syntax of a TikZ script.

To generate a TikZ 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.

Synopsis

Points

data TPoint Source #

A point in TikZ.

Instances
Show TPoint Source # 
Instance details

Defined in Text.LaTeX.Packages.TikZ.Syntax

Render TPoint Source # 
Instance details

Defined in Text.LaTeX.Packages.TikZ.Syntax

Methods

render :: TPoint -> Text Source #

pointAt :: Measure -> Measure -> TPoint Source #

Point using Measures for coordinantes.

pointAtXY :: Double -> Double -> TPoint Source #

Point using numbers as coordinates.

pointAtXYZ :: Double -> Double -> Double -> TPoint Source #

Three-dimensional point.

relPoint :: TPoint -> TPoint Source #

Makes a point relative to the previous.

Paths

Types

data TPath Source #

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.

Constructors

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.

Instances
Show TPath Source # 
Instance details

Defined in Text.LaTeX.Packages.TikZ.Syntax

Methods

showsPrec :: Int -> TPath -> ShowS #

show :: TPath -> String #

showList :: [TPath] -> ShowS #

Render TPath Source # 
Instance details

Defined in Text.LaTeX.Packages.TikZ.Syntax

Methods

render :: TPath -> Text Source #

newtype GridOption Source #

Constructors

GridStep Step 

data Step Source #

Instances
Show Step Source # 
Instance details

Defined in Text.LaTeX.Packages.TikZ.Syntax

Methods

showsPrec :: Int -> Step -> ShowS #

show :: Step -> String #

showList :: [Step] -> ShowS #

Render Step Source # 
Instance details

Defined in Text.LaTeX.Packages.TikZ.Syntax

Methods

render :: Step -> Text Source #

Critical points

startingPoint :: TPath -> TPoint Source #

Calculate the starting point of a TPath.

lastPoint :: TPath -> TPoint Source #

Calculate the last point of a TPath.

Functions

(->-) :: TPath -> TPoint -> TPath Source #

Alias of Line.

Parameters

data Parameter Source #

Parameters to use in a scope to change how things are rendered within that scope.

Constructors

TWidth Measure 
TColor TikZColor 
TScale Double 
TRotate Double

Angle is in degrees.

Instances
Show Parameter Source # 
Instance details

Defined in Text.LaTeX.Packages.TikZ.Syntax

Render Parameter Source # 
Instance details

Defined in Text.LaTeX.Packages.TikZ.Syntax

data TikZColor Source #

Color models accepted by TikZ.

Instances
Show TikZColor Source # 
Instance details

Defined in Text.LaTeX.Packages.TikZ.Syntax

Render TikZColor Source # 
Instance details

Defined in Text.LaTeX.Packages.TikZ.Syntax

data Color Source #

Basic colors.

Constructors

Red 
Green 
Blue 
Yellow 
Cyan 
Magenta 
Black 
White 
Instances
Show Color Source # 
Instance details

Defined in Text.LaTeX.Packages.Color

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Render Color Source # 
Instance details

Defined in Text.LaTeX.Packages.Color

Methods

render :: Color -> Text Source #

data Word8 #

8-bit unsigned integer type

Instances
Bounded Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

(==) :: Word8 -> Word8 -> Bool #

(/=) :: Word8 -> Word8 -> Bool #

Integral Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Data Word8

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word8 -> c Word8 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word8 #

toConstr :: Word8 -> Constr #

dataTypeOf :: Word8 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word8) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word8) #

gmapT :: (forall b. Data b => b -> b) -> Word8 -> Word8 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word8 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word8 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word8 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word8 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 #

Num Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

compare :: Word8 -> Word8 -> Ordering #

(<) :: Word8 -> Word8 -> Bool #

(<=) :: Word8 -> Word8 -> Bool #

(>) :: Word8 -> Word8 -> Bool #

(>=) :: Word8 -> Word8 -> Bool #

max :: Word8 -> Word8 -> Word8 #

min :: Word8 -> Word8 -> Word8 #

Read Word8

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

toRational :: Word8 -> Rational #

Show Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Ix Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Lift Word8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word8 -> Q Exp #

Function Word8 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Word8 -> b) -> Word8 :-> b #

Arbitrary Word8 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Word8 #

shrink :: Word8 -> [Word8] #

CoArbitrary Word8 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

coarbitrary :: Word8 -> Gen b -> Gen b #

Bits Word8

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word8

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

Hashable Word8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word8 -> Int #

hash :: Word8 -> Int #

Pretty Word8 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Word8 -> Doc ann #

prettyList :: [Word8] -> Doc ann #

Random Word8 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word8, Word8) -> g -> (Word8, g) #

random :: RandomGen g => g -> (Word8, g) #

randomRs :: RandomGen g => (Word8, Word8) -> g -> [Word8] #

randoms :: RandomGen g => g -> [Word8] #

randomRIO :: (Word8, Word8) -> IO Word8 #

randomIO :: IO Word8 #

Render Word8 Source # 
Instance details

Defined in Text.LaTeX.Base.Render

Methods

render :: Word8 -> Text Source #

TikZ

data TikZ Source #

A TikZ script.

Instances
Show TikZ Source # 
Instance details

Defined in Text.LaTeX.Packages.TikZ.Syntax

Methods

showsPrec :: Int -> TikZ -> ShowS #

show :: TikZ -> String #

showList :: [TikZ] -> ShowS #

Render TikZ Source # 
Instance details

Defined in Text.LaTeX.Packages.TikZ.Syntax

Methods

render :: TikZ -> Text Source #

emptytikz :: TikZ Source #

Just an empty script.

path :: [ActionType] -> TPath -> TikZ Source #

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.

scope :: [Parameter] -> TikZ -> TikZ Source #

Applies a scope to a TikZ script.

data ActionType Source #

Different types of actions that can be performed with a TPath. See path for more information.

Constructors

Draw 
Fill 
Clip 
Shade 

(->>) :: TikZ -> TikZ -> TikZ Source #

Sequence two TikZ scripts.

Sugar

draw :: TPath -> TikZ Source #

Equivalent to path [Draw].

fill :: TPath -> TikZ Source #

Equivalent to path [Fill].

clip :: TPath -> TikZ Source #

Equivalent to path [Clip].

shade :: TPath -> TikZ Source #

Equivalent to path [Shade].

filldraw :: TPath -> TikZ Source #

Equivalent to path [Fill,Draw].

shadedraw :: TPath -> TikZ Source #

Equivalent to path [Shade,Draw].