HaTeX-3.17.1.0: The Haskell LaTeX library.

Safe HaskellSafe
LanguageHaskell2010

Text.LaTeX.Packages.TikZ.Simple

Contents

Description

A simple interface to create TikZ graphics. Just build pictures using the Figure data constructors, and get the TikZ script using the function figuretikz. Use the function tikzpicture to insert the TikZ script in the LaTeX document. And do not forget to import the tikz package in the preamble.

Please, note that this module is not intended to be imported in the same module than Text.LaTeX.Packages.TikZ. This module is itself a self-contained alternative of that module. If you still want to use both modules, please, use qualified imports to avoid name clashes.

In the Examples directory of the source distribution, the file tikzsimple.hs contains a complete example of usage of this module with several pictures. Below you can see a picture along with the code it came from.

myFigure :: Figure
myFigure = Scale 2 $ Figures
  [ RectangleFilled (0,0) 1 1
  , Colored (BasicColor Green) $ RectangleFilled (-1,1) 1 1
  , Colored (BasicColor Red)   $ RectangleFilled ( 0,2) 1 1
  , Colored (BasicColor Blue)  $ RectangleFilled ( 1,1) 1 1
    ]

Synopsis

Documentation

tikz :: PackageName Source #

Import the tikz package to use the functions exported by this module. For example, adding this line to your document preamble:

usepackage [] tikz

Figures

data Figure Source #

A figure in the plane.

Constructors

Line [Point]

Line along a list of points.

Polygon [Point]

Line along a list of points, but the last point will be joined with the first one.

PolygonFilled [Point]

Same as Polygon, but the inner side will be filled with color.

Rectangle Point Double Double

Rectangle with top-right corner at the given point and width and height given by the other parameters.

RectangleFilled Point Double Double

Same as Rectangle, but filled with color.

Circle Point Double

Circle centered at the given point with the given radius.

CircleFilled Point Double

As in Circle, but it will be filled with some color.

Ellipse Point Double Double

Ellipse centered at the given point with width and height given by the other parameters.

EllipseFilled Point Double Double

Same as Ellipse, but filled with some color.

Text Point LaTeX

Insert some LaTeX code, centered at the given Point. The text should not be very complex to fit nicely in the picture.

Colored TikZColor Figure

Color for the given Figure.

LineWidth Measure Figure

Line width for the given Figure.

Scale Double Figure

Scaling of the given Figure by a factor.

Rotate Double Figure

Rotate a Figure by a given angle (in radians).

Figures [Figure]

A figure composed by a list of figures.

type Point = (Double, Double) Source #

A point in the plane.

data TikZColor Source #

Color models accepted by TikZ.

data Color Source #

Basic colors.

Constructors

Red 
Green 
Blue 
Yellow 
Cyan 
Magenta 
Black 
White 

Instances

data Word8 :: * #

8-bit unsigned integer type

Instances

Bounded Word8 
Enum Word8 
Eq Word8 

Methods

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

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

Integral Word8 
Num Word8 
Ord Word8 

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 
Real Word8 

Methods

toRational :: Word8 -> Rational #

Show Word8 

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Ix Word8 
Lift Word8 

Methods

lift :: Word8 -> Q Exp #

Arbitrary Word8 

Methods

arbitrary :: Gen Word8 #

shrink :: Word8 -> [Word8] #

CoArbitrary Word8 

Methods

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

Bits Word8 
FiniteBits Word8 
Random Word8 

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 #

Pretty Word8 

Methods

pretty :: Word8 -> Doc e #

prettyList :: [Word8] -> Doc e #

Render Word8 Source # 

Methods

render :: Word8 -> Text Source #

Additional functions

pathImage Source #

Arguments

:: Double

Precision argument, ε.

-> (Double, Double)

Interval, (a,b).

-> (Double -> Point)

Path function, f.

-> Figure

Output figure.

The figure of a path. A path (in this context) means a function from an interval to the plane. The image of such a function is what this function returns as a Figure. An additional argument is needed to set the precision of the curve.

The actual implementation builds a spline of degree one joining different points of the image. Given that the interval is (a,b) and the precision argument is ε, the points in the spline will be f(a), f(a+ε), f(a+2ε), and so on, until reaching f(b). The smaller is ε, the closer is the figure to the original image.

Here is an example with a logarithmic spiral.

spiral :: Figure
spiral = LineWidth (Pt 2) $
    pathImage 0.01 (0,4) $
      \t -> ( a * exp t * cos (b*t)
            , a * exp t * sin (b*t)
              )
  where
    a = 0.1 ; b = 4

Figure scripting

figuretikz :: Figure -> TikZ Source #

Translate a Figure to a TikZ script.

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

Sequence two TikZ scripts.

tikzpicture :: LaTeXC l => TikZ -> l Source #

Transform a TikZ script to a LaTeX block.