-- | A simple interface to create Ti/k/Z graphics. Just build pictures using
--   the 'Figure' data constructors, and get the Ti/k/Z script using the function
--   'figuretikz'. Use the function 'tikzpicture' to insert the Ti/k/Z 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.
--
--   <<docfiles/tikz/tikzsimple.png>>
--
-- > 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
-- >     ]
--
module Text.LaTeX.Packages.TikZ.Simple (
   -- TikZ package
   tikz
   -- * Figures
 , Figure (..)
 , Point
 , TikZColor (..)
 , Color (..)
 , Word8
   -- * Additional functions
 , pathImage
   -- * Figure scripting
 , figuretikz
 , (T.->>)
 , tikzpicture
   ) where

import Text.LaTeX.Base.Syntax (LaTeX)
import Text.LaTeX.Base.Types (Measure)
import Text.LaTeX.Packages.TikZ
           ( TikZ, TikZColor, Color, Word8
           , tikzpicture, emptytikz, tikz )
import qualified Text.LaTeX.Packages.TikZ as T

-- | A point in the plane.
type Point = (Double,Double)

-- | A figure in the plane.
data Figure =
   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.

castpoint :: Point -> T.TPoint
castpoint :: Point -> TPoint
castpoint (Double
x,Double
y) = Double -> Double -> TPoint
T.pointAtXY Double
x Double
y

radiansToDegrees :: Double -> Double
radiansToDegrees :: Double -> Double
radiansToDegrees Double
x = (Double
180 forall a. Num a => a -> a -> a
* Double
x) forall a. Fractional a => a -> a -> a
/ forall a. Floating a => a
pi

-- | Translate a 'Figure' to a 'TikZ' script.
figuretikz :: Figure -> TikZ
figuretikz :: Figure -> TikZ
figuretikz (Line []) = TikZ
emptytikz
figuretikz (Line (Point
p:[Point]
ps)) = TPath -> TikZ
T.draw forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (\TPath
y Point
x -> TPath
y TPath -> TPoint -> TPath
T.->- Point -> TPoint
castpoint Point
x) (TPoint -> TPath
T.Start forall a b. (a -> b) -> a -> b
$ Point -> TPoint
castpoint Point
p) [Point]
ps
figuretikz (Polygon []) = TikZ
emptytikz
figuretikz (Polygon (Point
p:[Point]
ps)) = TPath -> TikZ
T.draw forall a b. (a -> b) -> a -> b
$ TPath -> TPath
T.Cycle forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (\TPath
y Point
x -> TPath
y TPath -> TPoint -> TPath
T.->- Point -> TPoint
castpoint Point
x) (TPoint -> TPath
T.Start forall a b. (a -> b) -> a -> b
$ Point -> TPoint
castpoint Point
p) [Point]
ps
figuretikz (PolygonFilled []) = TikZ
emptytikz
figuretikz (PolygonFilled (Point
p:[Point]
ps)) = TPath -> TikZ
T.fill forall a b. (a -> b) -> a -> b
$ TPath -> TPath
T.Cycle forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (\TPath
y Point
x -> TPath
y TPath -> TPoint -> TPath
T.->- Point -> TPoint
castpoint Point
x) (TPoint -> TPath
T.Start forall a b. (a -> b) -> a -> b
$ Point -> TPoint
castpoint Point
p) [Point]
ps
figuretikz (Rectangle Point
p Double
w Double
h) = TPath -> TikZ
T.draw forall a b. (a -> b) -> a -> b
$ TPath -> TPoint -> TPath
T.Rectangle (TPoint -> TPath
T.Start forall a b. (a -> b) -> a -> b
$ Point -> TPoint
castpoint Point
p) forall a b. (a -> b) -> a -> b
$ TPoint -> TPoint
T.relPoint forall a b. (a -> b) -> a -> b
$ Point -> TPoint
castpoint (Double
w,-Double
h)
figuretikz (RectangleFilled Point
p Double
w Double
h) = TPath -> TikZ
T.fill forall a b. (a -> b) -> a -> b
$ TPath -> TPoint -> TPath
T.Rectangle (TPoint -> TPath
T.Start forall a b. (a -> b) -> a -> b
$ Point -> TPoint
castpoint Point
p) forall a b. (a -> b) -> a -> b
$ TPoint -> TPoint
T.relPoint forall a b. (a -> b) -> a -> b
$ Point -> TPoint
castpoint (Double
w,-Double
h)
figuretikz (Circle Point
p Double
r) = TPath -> TikZ
T.draw forall a b. (a -> b) -> a -> b
$ TPath -> Double -> TPath
T.Circle (TPoint -> TPath
T.Start forall a b. (a -> b) -> a -> b
$ Point -> TPoint
castpoint Point
p) Double
r
figuretikz (CircleFilled Point
p Double
r) = TPath -> TikZ
T.fill forall a b. (a -> b) -> a -> b
$ TPath -> Double -> TPath
T.Circle (TPoint -> TPath
T.Start forall a b. (a -> b) -> a -> b
$ Point -> TPoint
castpoint Point
p) Double
r
figuretikz (Ellipse Point
p Double
r1 Double
r2) = TPath -> TikZ
T.draw forall a b. (a -> b) -> a -> b
$ TPath -> Double -> Double -> TPath
T.Ellipse (TPoint -> TPath
T.Start forall a b. (a -> b) -> a -> b
$ Point -> TPoint
castpoint Point
p) (Double
r1forall a. Fractional a => a -> a -> a
/Double
2) (Double
r2forall a. Fractional a => a -> a -> a
/Double
2)
figuretikz (EllipseFilled Point
p Double
r1 Double
r2) = TPath -> TikZ
T.fill forall a b. (a -> b) -> a -> b
$ TPath -> Double -> Double -> TPath
T.Ellipse (TPoint -> TPath
T.Start forall a b. (a -> b) -> a -> b
$ Point -> TPoint
castpoint Point
p) Double
r1 Double
r2
figuretikz (Text Point
p LaTeX
l) = TPath -> TikZ
T.draw forall a b. (a -> b) -> a -> b
$ TPath -> LaTeX -> TPath
T.Node (TPoint -> TPath
T.Start forall a b. (a -> b) -> a -> b
$ Point -> TPoint
castpoint Point
p) LaTeX
l
figuretikz (Colored TikZColor
c Figure
f) = [Parameter] -> TikZ -> TikZ
T.scope [TikZColor -> Parameter
T.TColor TikZColor
c] forall a b. (a -> b) -> a -> b
$ Figure -> TikZ
figuretikz Figure
f
figuretikz (LineWidth Measure
m Figure
f) = [Parameter] -> TikZ -> TikZ
T.scope [Measure -> Parameter
T.TWidth Measure
m] forall a b. (a -> b) -> a -> b
$ Figure -> TikZ
figuretikz Figure
f
figuretikz (Scale Double
q Figure
f) = [Parameter] -> TikZ -> TikZ
T.scope [Double -> Parameter
T.TScale Double
q] forall a b. (a -> b) -> a -> b
$ Figure -> TikZ
figuretikz Figure
f
figuretikz (Rotate Double
a Figure
f) = [Parameter] -> TikZ -> TikZ
T.scope [Double -> Parameter
T.TRotate forall a b. (a -> b) -> a -> b
$ Double -> Double
radiansToDegrees Double
a] forall a b. (a -> b) -> a -> b
$ Figure -> TikZ
figuretikz Figure
f
figuretikz (Figures [Figure]
fs) = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\Figure
x TikZ
y -> Figure -> TikZ
figuretikz Figure
x TikZ -> TikZ -> TikZ
T.->> TikZ
y) TikZ
emptytikz [Figure]
fs

-- | 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 &#949;, the points
--   in the spline will be /f(a)/, /f(a+/&#949;/)/, /f(a+2/&#949;/)/, and so on, until reaching /f(b)/.
--   The smaller is &#949;, the closer is the figure to the original image.
--
--   Here is an example with a logarithmic spiral.
--
--   <<docfiles/tikz/spiral.png>>
--
-- > 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
--
pathImage :: Double -- ^ Precision argument, &#949;.
          -> (Double,Double) -- ^ Interval, /(a,b)/.
          -> (Double -> Point) -- ^ Path function, /f/.
          -> Figure -- ^ Output figure.
pathImage :: Double -> Point -> (Double -> Point) -> Figure
pathImage Double
eps (Double
a,Double
b) Double -> Point
f = [Point] -> Figure
Line forall a b. (a -> b) -> a -> b
$ Double -> [Point]
listFrom Double
a
  where
   listFrom :: Double -> [Point]
listFrom Double
x =
     if Double
x forall a. Ord a => a -> a -> Bool
>= Double
b then [Double -> Point
f Double
b]
               else Double -> Point
f Double
x forall a. a -> [a] -> [a]
: Double -> [Point]
listFrom (Double
xforall a. Num a => a -> a -> a
+Double
eps)