#!/usr/bin/env stack -- stack runghc --package reanimate {-# LANGUAGE ApplicativeDo #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} module Main (main) where {- FE articles/demos scatter: https://codepen.io/mullany/pen/JmgbRB distortion: https://codepen.io/mullany/pen/BWKePz variable stroke width: https://codepen.io/mullany/pen/qaONQm variable stroke gradient: https://codepen.io/mullany/pen/XXBMJd heart: https://codepen.io/yoksel/pen/MLVjoB elastic stroke: https://codepen.io/yoksel/pen/XJbzrO -} import qualified Data.Text as T import Graphics.SvgTree import Reanimate import NeatInterpolation import Control.Monad main :: IO () main = reanimate $ scene $ do newSpriteSVG_ $ mkBackground "white" hue <- newVar 0 dScale <- newVar 0.2 newSprite $ mkDistortFilter <$> unVar hue <*> unVar dScale newSpriteSVG_ $ parseSvg "" fork $ replicateM_ 5 $ tweenVar hue 1 $ \_v -> fromToS 0 360 tweenVar dScale 1 $ \v -> fromToS v 1.0 tweenVar dScale 1 $ \v -> fromToS v 0.2 tweenVar dScale 1 $ \v -> fromToS v 0.5 tweenVar dScale 1 $ \v -> fromToS v 1.0 tweenVar dScale 1 $ \v -> fromToS v 0.2 -- wait 1 -- hue: 0 -> 360 over 1s -- dScale: 0;20;50;0 over 5s mkDistortFilter :: Double -> Double -> SVG mkDistortFilter hue dScale = parseSvg [text| |] where hue' = T.pack (show hue) dScale' = T.pack (show dScale)