module Reanimate.Builtin.TernaryPlot
( ACoord
, BCoord
, CCoord
, ternaryPlot
, toCartesianCoords
, toOffsetCartesianCoords
, fromCartesianCoords
) where
import Codec.Picture
import Graphics.SvgTree (Tree)
import Reanimate.Raster
import Reanimate.Svg
type ACoord = Double
type BCoord = Double
type CCoord = Double
ternaryPlot :: Int
-> (ACoord -> BCoord -> CCoord -> PixelRGBA8)
-> Tree
ternaryPlot density fn =
scaleToWidth stdWidth $
translate (-cX) (-cY) $
scaleToWidth 1 $
flipYAxis $
translate (fromIntegral density/2) (-fromIntegral height/2) $
embedImage $ generateImage gen density height
where
stdWidth = 5
(cX, cY) = toCartesianCoords (1/3) (1/3)
height = round (fromIntegral density * (sqrt 3 / 2) :: Double)
gen x y =
let
x' = (fromIntegral x / fromIntegral density)
y' = (fromIntegral y / fromIntegral density)
aCoord = (x'*2-bCoord)/2
bCoord = y' / (sqrt 3 / 2)
cCoord = 1 - aCoord - bCoord
in if aCoord + bCoord > 1 || aCoord < 0 || bCoord < 0 || cCoord < 0
then PixelRGBA8 0 0 0 0
else fn aCoord bCoord cCoord
toCartesianCoords :: ACoord -> BCoord -> (Double, Double)
toCartesianCoords a b = (x, y)
where
x = (a+2*b)/2
y = (sqrt 3 / 2) * a
toOffsetCartesianCoords :: ACoord -> BCoord -> (Double, Double)
toOffsetCartesianCoords a b =
(tx-zx, ty-zy)
where
(zx,zy) = toCartesianCoords (1/3) (1/3)
(tx,ty) = toCartesianCoords a b
fromCartesianCoords :: Double -> Double -> (ACoord, BCoord, CCoord)
fromCartesianCoords x y = (a,b,1-a-b)
where
a = (x*2-b)/2
b = y / (sqrt 3 / 2)