#!/usr/bin/env stack -- stack runghc --package reanimate {-# LANGUAGE DataKinds #-} {-# LANGUAGE OverloadedStrings #-} module Main(main) where import Algorithms.Geometry.PolygonTriangulation.Triangulate (triangulate') import Control.Lens import Control.Monad import qualified Data.CircularSeq as C import qualified Data.Geometry as Geo import Data.Geometry.PlanarSubdivision (PolygonFaceData (..)) import qualified Data.Geometry.Point as Geo import qualified Data.Geometry.Polygon as Geo import qualified Data.PlaneGraph as Geo import Data.Proxy import Graphics.SvgTree.Types import Linear.V2 import Reanimate import Reanimate.Builtin.Documentation import Reanimate.PolyShape import Data.Ext import Data.List import qualified Data.Vector as V scaleP n = lowerTransformations . scale n env = addStatic (mkBackground "white") . mapA (withFillOpacity 0 . withStrokeColor "black" . withStrokeWidth (defaultStrokeWidth*0.1)) main :: IO () main = reanimate $ env $ scene $ do let --svg = scaleP 4 $ center $ latex "$F=ma$" svg = scaleP 4 $ center $ latex "$\\infty$" withHoles :: [PolyShapeWithHoles] withHoles = plGroupShapes . unionPolyShapes $ svgToPolyShapes svg hpoly = map toPoly withHoles rects :: [[RPoint]] rects = concatMap decomposeP hpoly -- newSpriteSVG_ $ scaleP 4 $ center $ latex "$F=ma$" forM_ rects $ \rect -> do newSpriteSVG_ $ mkLinePathClosed [ (x, y) | V2 x y <- rect ] wait (1/60) wait 1 -- map (decomposePolygon . plPolygonify 1 . mergePolyShapeHoles) $ plGroupShapes $ unionPolyShapes $ svgToPolyShapes $ latex "I" toPoly :: PolyShapeWithHoles -> Geo.Polygon Geo.Multi () Double toPoly (PolyShapeWithHoles outer holes) = Geo.MultiPolygon (toSeq outer) (map (Geo.SimplePolygon . toSeq) holes) where tol = 0.001 toSeq p = C.fromList $ [ Geo.Point2 x y :+ () | V2 x y <- init $ plPolygonify tol p ] decomposeP :: Geo.Polygon Geo.Multi () Double -> [[RPoint]] decomposeP poly = [ [ V2 x y | v <- V.toList (Geo.boundaryVertices f pg) , let Geo.Point2 x y = pg^.Geo.vertexDataOf v . Geo.location ] | (f, Inside) <- V.toList (Geo.internalFaces pg) ] where pg = triangulate' Proxy poly