module Text.LaTeX.Packages.TikZ.Simple (
tikz
, Figure (..)
, Point
, TikZColor (..)
, Color (..)
, Word8
, pathImage
, 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
type Point = (Double,Double)
data Figure =
Line [Point]
| Polygon [Point]
| PolygonFilled [Point]
| Rectangle Point Double Double
| RectangleFilled Point Double Double
| Circle Point Double
| CircleFilled Point Double
| Ellipse Point Double Double
| EllipseFilled Point Double Double
| Text Point LaTeX
| Colored TikZColor Figure
| LineWidth Measure Figure
| Scale Double Figure
| Rotate Double Figure
| Figures [Figure]
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 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
x) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
forall a. Floating a => a
pi
figuretikz :: Figure -> TikZ
figuretikz :: Figure -> TikZ
figuretikz (Line []) = TikZ
emptytikz
figuretikz (Line (Point
p:[Point]
ps)) = TPath -> TikZ
T.draw (TPath -> TikZ) -> TPath -> TikZ
forall a b. (a -> b) -> a -> b
$ (TPath -> Point -> TPath) -> TPath -> [Point] -> TPath
forall b a. (b -> a -> b) -> 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 (TPoint -> TPath) -> TPoint -> TPath
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 (TPath -> TikZ) -> TPath -> TikZ
forall a b. (a -> b) -> a -> b
$ TPath -> TPath
T.Cycle (TPath -> TPath) -> TPath -> TPath
forall a b. (a -> b) -> a -> b
$ (TPath -> Point -> TPath) -> TPath -> [Point] -> TPath
forall b a. (b -> a -> b) -> 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 (TPoint -> TPath) -> TPoint -> TPath
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 (TPath -> TikZ) -> TPath -> TikZ
forall a b. (a -> b) -> a -> b
$ TPath -> TPath
T.Cycle (TPath -> TPath) -> TPath -> TPath
forall a b. (a -> b) -> a -> b
$ (TPath -> Point -> TPath) -> TPath -> [Point] -> TPath
forall b a. (b -> a -> b) -> 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 (TPoint -> TPath) -> TPoint -> TPath
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 (TPath -> TikZ) -> TPath -> TikZ
forall a b. (a -> b) -> a -> b
$ TPath -> TPoint -> TPath
T.Rectangle (TPoint -> TPath
T.Start (TPoint -> TPath) -> TPoint -> TPath
forall a b. (a -> b) -> a -> b
$ Point -> TPoint
castpoint Point
p) (TPoint -> TPath) -> TPoint -> TPath
forall a b. (a -> b) -> a -> b
$ TPoint -> TPoint
T.relPoint (TPoint -> TPoint) -> TPoint -> TPoint
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 (TPath -> TikZ) -> TPath -> TikZ
forall a b. (a -> b) -> a -> b
$ TPath -> TPoint -> TPath
T.Rectangle (TPoint -> TPath
T.Start (TPoint -> TPath) -> TPoint -> TPath
forall a b. (a -> b) -> a -> b
$ Point -> TPoint
castpoint Point
p) (TPoint -> TPath) -> TPoint -> TPath
forall a b. (a -> b) -> a -> b
$ TPoint -> TPoint
T.relPoint (TPoint -> TPoint) -> TPoint -> TPoint
forall a b. (a -> b) -> a -> b
$ Point -> TPoint
castpoint (Double
w,-Double
h)
figuretikz (Circle Point
p Double
r) = TPath -> TikZ
T.draw (TPath -> TikZ) -> TPath -> TikZ
forall a b. (a -> b) -> a -> b
$ TPath -> Double -> TPath
T.Circle (TPoint -> TPath
T.Start (TPoint -> TPath) -> TPoint -> TPath
forall a b. (a -> b) -> a -> b
$ Point -> TPoint
castpoint Point
p) Double
r
figuretikz (CircleFilled Point
p Double
r) = TPath -> TikZ
T.fill (TPath -> TikZ) -> TPath -> TikZ
forall a b. (a -> b) -> a -> b
$ TPath -> Double -> TPath
T.Circle (TPoint -> TPath
T.Start (TPoint -> TPath) -> TPoint -> TPath
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 (TPath -> TikZ) -> TPath -> TikZ
forall a b. (a -> b) -> a -> b
$ TPath -> Double -> Double -> TPath
T.Ellipse (TPoint -> TPath
T.Start (TPoint -> TPath) -> TPoint -> TPath
forall a b. (a -> b) -> a -> b
$ Point -> TPoint
castpoint Point
p) (Double
r1Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
2) (Double
r2Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
2)
figuretikz (EllipseFilled Point
p Double
r1 Double
r2) = TPath -> TikZ
T.fill (TPath -> TikZ) -> TPath -> TikZ
forall a b. (a -> b) -> a -> b
$ TPath -> Double -> Double -> TPath
T.Ellipse (TPoint -> TPath
T.Start (TPoint -> TPath) -> TPoint -> TPath
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 (TPath -> TikZ) -> TPath -> TikZ
forall a b. (a -> b) -> a -> b
$ TPath -> LaTeX -> TPath
T.Node (TPoint -> TPath
T.Start (TPoint -> TPath) -> TPoint -> TPath
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] (TikZ -> TikZ) -> TikZ -> TikZ
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] (TikZ -> TikZ) -> TikZ -> TikZ
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] (TikZ -> TikZ) -> TikZ -> TikZ
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 (Double -> Parameter) -> Double -> Parameter
forall a b. (a -> b) -> a -> b
$ Double -> Double
radiansToDegrees Double
a] (TikZ -> TikZ) -> TikZ -> TikZ
forall a b. (a -> b) -> a -> b
$ Figure -> TikZ
figuretikz Figure
f
figuretikz (Figures [Figure]
fs) = (Figure -> TikZ -> TikZ) -> TikZ -> [Figure] -> TikZ
forall a b. (a -> b -> b) -> b -> [a] -> b
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
pathImage :: Double
-> (Double,Double)
-> (Double -> Point)
-> Figure
pathImage :: Double -> Point -> (Double -> Point) -> Figure
pathImage Double
eps (Double
a,Double
b) Double -> Point
f = [Point] -> Figure
Line ([Point] -> Figure) -> [Point] -> Figure
forall a b. (a -> b) -> a -> b
$ Double -> [Point]
listFrom Double
a
where
listFrom :: Double -> [Point]
listFrom Double
x =
if Double
x Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= Double
b then [Double -> Point
f Double
b]
else Double -> Point
f Double
x Point -> [Point] -> [Point]
forall a. a -> [a] -> [a]
: Double -> [Point]
listFrom (Double
xDouble -> Double -> Double
forall a. Num a => a -> a -> a
+Double
eps)