{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE RecordWildCards #-}
module Reanimate.Scene.Object where
import Control.Lens
import Control.Monad (forM_, void)
import Control.Monad.State (State, execState)
import Data.Monoid (Last (getLast))
import Graphics.SvgTree (Number (..), Tree, pattern None, strokeWidth, toUserUnit)
import Linear.V2 (R1 (_x), R2 (_y), V2 (..))
import Linear.Vector (Additive (lerp), (^*))
import Reanimate.Animation
import Reanimate.Constants (defaultDPI, defaultStrokeWidth)
import Reanimate.Ease (Signal, curveS, fromToS)
import Reanimate.Effect (applyE, fadeLineOutE, overEnding)
import Reanimate.Math.Balloon (balloon)
import Reanimate.Morph.Common (morph)
import Reanimate.Morph.Linear (linear)
import Reanimate.Svg
import Reanimate.Scene.Core (Scene, fork, scene, wait)
import Reanimate.Scene.Sprite (Sprite, newSprite, newSpriteA', play, spriteModify, unVar)
import Reanimate.Scene.Var (Var, modifyVar, newVar, readVar, tweenVar)
class Renderable a where
toSVG :: a -> SVG
instance Renderable Tree where
toSVG :: Tree -> Tree
toSVG = Tree -> Tree
forall a. a -> a
id
data Object s a = Object
{ Object s a -> Sprite s
objectSprite :: Sprite s,
Object s a -> Var s (ObjectData a)
objectData :: Var s (ObjectData a)
}
data ObjectData a = ObjectData
{ ObjectData a -> V2 Double
_oTranslate :: V2 Double,
ObjectData a -> a
_oValueRef :: a,
ObjectData a -> Tree
_oSVG :: SVG,
ObjectData a -> Tree -> Tree
_oContext :: SVG -> SVG,
ObjectData a -> (Double, Double, Double, Double)
_oMargin :: (Double, Double, Double, Double),
ObjectData a -> (Double, Double, Double, Double)
_oBB :: (Double, Double, Double, Double),
ObjectData a -> Double
_oOpacity :: Double,
ObjectData a -> Bool
_oShown :: Bool,
ObjectData a -> Int
_oZIndex :: Int,
ObjectData a -> Signal
_oEasing :: Signal,
ObjectData a -> Double
_oScale :: Double,
ObjectData a -> V2 Double
_oScaleOrigin :: V2 Double
}
oTranslate :: Lens' (ObjectData a) (V2 Double)
oTranslate :: (V2 Double -> f (V2 Double)) -> ObjectData a -> f (ObjectData a)
oTranslate = (ObjectData a -> V2 Double)
-> (ObjectData a -> V2 Double -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) (V2 Double) (V2 Double)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ObjectData a -> V2 Double
forall a. ObjectData a -> V2 Double
_oTranslate ((ObjectData a -> V2 Double -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) (V2 Double) (V2 Double))
-> (ObjectData a -> V2 Double -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) (V2 Double) (V2 Double)
forall a b. (a -> b) -> a -> b
$ \ObjectData a
obj V2 Double
val -> ObjectData a
obj {_oTranslate :: V2 Double
_oTranslate = V2 Double
val}
oTranslateX :: Lens' (ObjectData a) Double
oTranslateX :: (Double -> f Double) -> ObjectData a -> f (ObjectData a)
oTranslateX = (V2 Double -> f (V2 Double)) -> ObjectData a -> f (ObjectData a)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate ((V2 Double -> f (V2 Double)) -> ObjectData a -> f (ObjectData a))
-> ((Double -> f Double) -> V2 Double -> f (V2 Double))
-> (Double -> f Double)
-> ObjectData a
-> f (ObjectData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> f Double) -> V2 Double -> f (V2 Double)
forall (t :: * -> *) a. R1 t => Lens' (t a) a
_x
oTranslateY :: Lens' (ObjectData a) Double
oTranslateY :: (Double -> f Double) -> ObjectData a -> f (ObjectData a)
oTranslateY = (V2 Double -> f (V2 Double)) -> ObjectData a -> f (ObjectData a)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate ((V2 Double -> f (V2 Double)) -> ObjectData a -> f (ObjectData a))
-> ((Double -> f Double) -> V2 Double -> f (V2 Double))
-> (Double -> f Double)
-> ObjectData a
-> f (ObjectData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> f Double) -> V2 Double -> f (V2 Double)
forall (t :: * -> *) a. R2 t => Lens' (t a) a
_y
oSVG :: Getter (ObjectData a) SVG
oSVG :: (Tree -> f Tree) -> ObjectData a -> f (ObjectData a)
oSVG = (ObjectData a -> Tree)
-> (Tree -> f Tree) -> ObjectData a -> f (ObjectData a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ObjectData a -> Tree
forall a. ObjectData a -> Tree
_oSVG
oContext :: Lens' (ObjectData a) (SVG -> SVG)
oContext :: ((Tree -> Tree) -> f (Tree -> Tree))
-> ObjectData a -> f (ObjectData a)
oContext = (ObjectData a -> Tree -> Tree)
-> (ObjectData a -> (Tree -> Tree) -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) (Tree -> Tree) (Tree -> Tree)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ObjectData a -> Tree -> Tree
forall a. ObjectData a -> Tree -> Tree
_oContext ((ObjectData a -> (Tree -> Tree) -> ObjectData a)
-> Lens
(ObjectData a) (ObjectData a) (Tree -> Tree) (Tree -> Tree))
-> (ObjectData a -> (Tree -> Tree) -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) (Tree -> Tree) (Tree -> Tree)
forall a b. (a -> b) -> a -> b
$ \ObjectData a
obj Tree -> Tree
val -> ObjectData a
obj {_oContext :: Tree -> Tree
_oContext = Tree -> Tree
val}
oMargin :: Lens' (ObjectData a) (Double, Double, Double, Double)
oMargin :: ((Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> ObjectData a -> f (ObjectData a)
oMargin = (ObjectData a -> (Double, Double, Double, Double))
-> (ObjectData a
-> (Double, Double, Double, Double) -> ObjectData a)
-> Lens
(ObjectData a)
(ObjectData a)
(Double, Double, Double, Double)
(Double, Double, Double, Double)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ObjectData a -> (Double, Double, Double, Double)
forall a. ObjectData a -> (Double, Double, Double, Double)
_oMargin ((ObjectData a -> (Double, Double, Double, Double) -> ObjectData a)
-> Lens
(ObjectData a)
(ObjectData a)
(Double, Double, Double, Double)
(Double, Double, Double, Double))
-> (ObjectData a
-> (Double, Double, Double, Double) -> ObjectData a)
-> Lens
(ObjectData a)
(ObjectData a)
(Double, Double, Double, Double)
(Double, Double, Double, Double)
forall a b. (a -> b) -> a -> b
$ \ObjectData a
obj (Double, Double, Double, Double)
val -> ObjectData a
obj {_oMargin :: (Double, Double, Double, Double)
_oMargin = (Double, Double, Double, Double)
val}
oBB :: Getter (ObjectData a) (Double, Double, Double, Double)
oBB :: ((Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> ObjectData a -> f (ObjectData a)
oBB = (ObjectData a -> (Double, Double, Double, Double))
-> ((Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> ObjectData a
-> f (ObjectData a)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ObjectData a -> (Double, Double, Double, Double)
forall a. ObjectData a -> (Double, Double, Double, Double)
_oBB
oOpacity :: Lens' (ObjectData a) Double
oOpacity :: (Double -> f Double) -> ObjectData a -> f (ObjectData a)
oOpacity = (ObjectData a -> Double)
-> (ObjectData a -> Double -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) Double Double
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ObjectData a -> Double
forall a. ObjectData a -> Double
_oOpacity ((ObjectData a -> Double -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) Double Double)
-> (ObjectData a -> Double -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) Double Double
forall a b. (a -> b) -> a -> b
$ \ObjectData a
obj Double
val -> ObjectData a
obj {_oOpacity :: Double
_oOpacity = Double
val}
oShown :: Lens' (ObjectData a) Bool
oShown :: (Bool -> f Bool) -> ObjectData a -> f (ObjectData a)
oShown = (ObjectData a -> Bool)
-> (ObjectData a -> Bool -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) Bool Bool
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ObjectData a -> Bool
forall a. ObjectData a -> Bool
_oShown ((ObjectData a -> Bool -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) Bool Bool)
-> (ObjectData a -> Bool -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) Bool Bool
forall a b. (a -> b) -> a -> b
$ \ObjectData a
obj Bool
val -> ObjectData a
obj {_oShown :: Bool
_oShown = Bool
val}
oZIndex :: Lens' (ObjectData a) Int
oZIndex :: (Int -> f Int) -> ObjectData a -> f (ObjectData a)
oZIndex = (ObjectData a -> Int)
-> (ObjectData a -> Int -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) Int Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ObjectData a -> Int
forall a. ObjectData a -> Int
_oZIndex ((ObjectData a -> Int -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) Int Int)
-> (ObjectData a -> Int -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) Int Int
forall a b. (a -> b) -> a -> b
$ \ObjectData a
obj Int
val -> ObjectData a
obj {_oZIndex :: Int
_oZIndex = Int
val}
oEasing :: Lens' (ObjectData a) Signal
oEasing :: (Signal -> f Signal) -> ObjectData a -> f (ObjectData a)
oEasing = (ObjectData a -> Signal)
-> (ObjectData a -> Signal -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) Signal Signal
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ObjectData a -> Signal
forall a. ObjectData a -> Signal
_oEasing ((ObjectData a -> Signal -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) Signal Signal)
-> (ObjectData a -> Signal -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) Signal Signal
forall a b. (a -> b) -> a -> b
$ \ObjectData a
obj Signal
val -> ObjectData a
obj {_oEasing :: Signal
_oEasing = Signal
val}
oScale :: Lens' (ObjectData a) Double
oScale :: (Double -> f Double) -> ObjectData a -> f (ObjectData a)
oScale = (ObjectData a -> Double)
-> (ObjectData a -> Double -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) Double Double
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ObjectData a -> Double
forall a. ObjectData a -> Double
_oScale ((ObjectData a -> Double -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) Double Double)
-> (ObjectData a -> Double -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) Double Double
forall a b. (a -> b) -> a -> b
$ \ObjectData a
obj Double
val -> ObjectData a -> ObjectData a
forall a. ObjectData a -> ObjectData a
oComputeBB ObjectData a
obj {_oScale :: Double
_oScale = Double
val}
oScaleOrigin :: Lens' (ObjectData a) (V2 Double)
oScaleOrigin :: (V2 Double -> f (V2 Double)) -> ObjectData a -> f (ObjectData a)
oScaleOrigin = (ObjectData a -> V2 Double)
-> (ObjectData a -> V2 Double -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) (V2 Double) (V2 Double)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ObjectData a -> V2 Double
forall a. ObjectData a -> V2 Double
_oScaleOrigin ((ObjectData a -> V2 Double -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) (V2 Double) (V2 Double))
-> (ObjectData a -> V2 Double -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) (V2 Double) (V2 Double)
forall a b. (a -> b) -> a -> b
$ \ObjectData a
obj V2 Double
val -> ObjectData a -> ObjectData a
forall a. ObjectData a -> ObjectData a
oComputeBB ObjectData a
obj {_oScaleOrigin :: V2 Double
_oScaleOrigin = V2 Double
val}
oValue :: Renderable a => Lens' (ObjectData a) a
oValue :: Lens' (ObjectData a) a
oValue = (ObjectData a -> a)
-> (ObjectData a -> a -> ObjectData a) -> Lens' (ObjectData a) a
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ObjectData a -> a
forall a. ObjectData a -> a
_oValueRef ((ObjectData a -> a -> ObjectData a) -> Lens' (ObjectData a) a)
-> (ObjectData a -> a -> ObjectData a) -> Lens' (ObjectData a) a
forall a b. (a -> b) -> a -> b
$ \ObjectData a
obj a
newVal ->
let svg :: Tree
svg = a -> Tree
forall a. Renderable a => a -> Tree
toSVG a
newVal
in ObjectData a -> ObjectData a
forall a. ObjectData a -> ObjectData a
oComputeBB
ObjectData a
obj
{ _oValueRef :: a
_oValueRef = a
newVal,
_oSVG :: Tree
_oSVG = Tree
svg
}
oComputeBB :: ObjectData a -> ObjectData a
oComputeBB :: ObjectData a -> ObjectData a
oComputeBB ObjectData a
obj =
ObjectData a
obj
{ _oBB :: (Double, Double, Double, Double)
_oBB = Tree -> (Double, Double, Double, Double)
boundingBox (Tree -> (Double, Double, Double, Double))
-> Tree -> (Double, Double, Double, Double)
forall a b. (a -> b) -> a -> b
$ ObjectData a -> Tree -> Tree
forall a. ObjectData a -> Tree -> Tree
oScaleApply ObjectData a
obj (ObjectData a -> Tree
forall a. ObjectData a -> Tree
_oSVG ObjectData a
obj)
}
oTopY :: Lens' (ObjectData a) Double
oTopY :: (Double -> f Double) -> ObjectData a -> f (ObjectData a)
oTopY = (ObjectData a -> Double)
-> (ObjectData a -> Double -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) Double Double
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ObjectData a -> Double
forall a. ObjectData a -> Double
getter ObjectData a -> Double -> ObjectData a
forall a. ObjectData a -> Double -> ObjectData a
setter
where
getter :: ObjectData a -> Double
getter ObjectData a
obj =
let top :: Double
top = ObjectData a
obj ObjectData a -> Getting Double (ObjectData a) Double -> Double
forall s a. s -> Getting a s a -> a
^. Getting Double (ObjectData a) Double
forall a. Lens' (ObjectData a) Double
oMarginTop
miny :: Double
miny = ObjectData a
obj ObjectData a -> Getting Double (ObjectData a) Double -> Double
forall s a. s -> Getting a s a -> a
^. Getting Double (ObjectData a) Double
forall a. Getter (ObjectData a) Double
oBBMinY
h :: Double
h = ObjectData a
obj ObjectData a -> Getting Double (ObjectData a) Double -> Double
forall s a. s -> Getting a s a -> a
^. Getting Double (ObjectData a) Double
forall a. Getter (ObjectData a) Double
oBBHeight
dy :: Double
dy = ObjectData a
obj ObjectData a -> Getting Double (ObjectData a) Double -> Double
forall s a. s -> Getting a s a -> a
^. (V2 Double -> Const Double (V2 Double))
-> ObjectData a -> Const Double (ObjectData a)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate ((V2 Double -> Const Double (V2 Double))
-> ObjectData a -> Const Double (ObjectData a))
-> ((Double -> Const Double Double)
-> V2 Double -> Const Double (V2 Double))
-> Getting Double (ObjectData a) Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Const Double Double)
-> V2 Double -> Const Double (V2 Double)
forall s t a b. Field2 s t a b => Lens s t a b
_2
in Double
dy Double -> Signal
forall a. Num a => a -> a -> a
+ Double
miny Double -> Signal
forall a. Num a => a -> a -> a
+ Double
h Double -> Signal
forall a. Num a => a -> a -> a
+ Double
top
setter :: ObjectData a -> Double -> ObjectData a
setter ObjectData a
obj Double
val =
ObjectData a
obj ObjectData a -> (ObjectData a -> ObjectData a) -> ObjectData a
forall a b. a -> (a -> b) -> b
& ((V2 Double -> Identity (V2 Double))
-> ObjectData a -> Identity (ObjectData a)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate ((V2 Double -> Identity (V2 Double))
-> ObjectData a -> Identity (ObjectData a))
-> ((Double -> Identity Double)
-> V2 Double -> Identity (V2 Double))
-> (Double -> Identity Double)
-> ObjectData a
-> Identity (ObjectData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Identity Double) -> V2 Double -> Identity (V2 Double)
forall s t a b. Field2 s t a b => Lens s t a b
_2) ((Double -> Identity Double)
-> ObjectData a -> Identity (ObjectData a))
-> Double -> ObjectData a -> ObjectData a
forall a s t. Num a => ASetter s t a a -> a -> s -> t
+~ Double
val Double -> Signal
forall a. Num a => a -> a -> a
- ObjectData a -> Double
forall a. ObjectData a -> Double
getter ObjectData a
obj
oBottomY :: Lens' (ObjectData a) Double
oBottomY :: (Double -> f Double) -> ObjectData a -> f (ObjectData a)
oBottomY = (ObjectData a -> Double)
-> (ObjectData a -> Double -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) Double Double
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ObjectData a -> Double
forall a. ObjectData a -> Double
getter ObjectData a -> Double -> ObjectData a
forall a. ObjectData a -> Double -> ObjectData a
setter
where
getter :: ObjectData a -> Double
getter ObjectData a
obj =
let bot :: Double
bot = ObjectData a
obj ObjectData a -> Getting Double (ObjectData a) Double -> Double
forall s a. s -> Getting a s a -> a
^. Getting Double (ObjectData a) Double
forall a. Lens' (ObjectData a) Double
oMarginBottom
miny :: Double
miny = ObjectData a
obj ObjectData a -> Getting Double (ObjectData a) Double -> Double
forall s a. s -> Getting a s a -> a
^. Getting Double (ObjectData a) Double
forall a. Getter (ObjectData a) Double
oBBMinY
dy :: Double
dy = ObjectData a
obj ObjectData a -> Getting Double (ObjectData a) Double -> Double
forall s a. s -> Getting a s a -> a
^. (V2 Double -> Const Double (V2 Double))
-> ObjectData a -> Const Double (ObjectData a)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate ((V2 Double -> Const Double (V2 Double))
-> ObjectData a -> Const Double (ObjectData a))
-> ((Double -> Const Double Double)
-> V2 Double -> Const Double (V2 Double))
-> Getting Double (ObjectData a) Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Const Double Double)
-> V2 Double -> Const Double (V2 Double)
forall s t a b. Field2 s t a b => Lens s t a b
_2
in Double
dy Double -> Signal
forall a. Num a => a -> a -> a
+ Double
miny Double -> Signal
forall a. Num a => a -> a -> a
- Double
bot
setter :: ObjectData a -> Double -> ObjectData a
setter ObjectData a
obj Double
val =
ObjectData a
obj ObjectData a -> (ObjectData a -> ObjectData a) -> ObjectData a
forall a b. a -> (a -> b) -> b
& ((V2 Double -> Identity (V2 Double))
-> ObjectData a -> Identity (ObjectData a)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate ((V2 Double -> Identity (V2 Double))
-> ObjectData a -> Identity (ObjectData a))
-> ((Double -> Identity Double)
-> V2 Double -> Identity (V2 Double))
-> (Double -> Identity Double)
-> ObjectData a
-> Identity (ObjectData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Identity Double) -> V2 Double -> Identity (V2 Double)
forall s t a b. Field2 s t a b => Lens s t a b
_2) ((Double -> Identity Double)
-> ObjectData a -> Identity (ObjectData a))
-> Double -> ObjectData a -> ObjectData a
forall a s t. Num a => ASetter s t a a -> a -> s -> t
+~ Double
val Double -> Signal
forall a. Num a => a -> a -> a
- ObjectData a -> Double
forall a. ObjectData a -> Double
getter ObjectData a
obj
oLeftX :: Lens' (ObjectData a) Double
oLeftX :: (Double -> f Double) -> ObjectData a -> f (ObjectData a)
oLeftX = (ObjectData a -> Double)
-> (ObjectData a -> Double -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) Double Double
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ObjectData a -> Double
forall a. ObjectData a -> Double
getter ObjectData a -> Double -> ObjectData a
forall a. ObjectData a -> Double -> ObjectData a
setter
where
getter :: ObjectData a -> Double
getter ObjectData a
obj =
let left :: Double
left = ObjectData a
obj ObjectData a -> Getting Double (ObjectData a) Double -> Double
forall s a. s -> Getting a s a -> a
^. Getting Double (ObjectData a) Double
forall a. Lens' (ObjectData a) Double
oMarginLeft
minx :: Double
minx = ObjectData a
obj ObjectData a -> Getting Double (ObjectData a) Double -> Double
forall s a. s -> Getting a s a -> a
^. Getting Double (ObjectData a) Double
forall a. Getter (ObjectData a) Double
oBBMinX
dx :: Double
dx = ObjectData a
obj ObjectData a -> Getting Double (ObjectData a) Double -> Double
forall s a. s -> Getting a s a -> a
^. (V2 Double -> Const Double (V2 Double))
-> ObjectData a -> Const Double (ObjectData a)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate ((V2 Double -> Const Double (V2 Double))
-> ObjectData a -> Const Double (ObjectData a))
-> ((Double -> Const Double Double)
-> V2 Double -> Const Double (V2 Double))
-> Getting Double (ObjectData a) Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Const Double Double)
-> V2 Double -> Const Double (V2 Double)
forall s t a b. Field1 s t a b => Lens s t a b
_1
in Double
dx Double -> Signal
forall a. Num a => a -> a -> a
+ Double
minx Double -> Signal
forall a. Num a => a -> a -> a
- Double
left
setter :: ObjectData a -> Double -> ObjectData a
setter ObjectData a
obj Double
val =
ObjectData a
obj ObjectData a -> (ObjectData a -> ObjectData a) -> ObjectData a
forall a b. a -> (a -> b) -> b
& ((V2 Double -> Identity (V2 Double))
-> ObjectData a -> Identity (ObjectData a)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate ((V2 Double -> Identity (V2 Double))
-> ObjectData a -> Identity (ObjectData a))
-> ((Double -> Identity Double)
-> V2 Double -> Identity (V2 Double))
-> (Double -> Identity Double)
-> ObjectData a
-> Identity (ObjectData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Identity Double) -> V2 Double -> Identity (V2 Double)
forall s t a b. Field1 s t a b => Lens s t a b
_1) ((Double -> Identity Double)
-> ObjectData a -> Identity (ObjectData a))
-> Double -> ObjectData a -> ObjectData a
forall a s t. Num a => ASetter s t a a -> a -> s -> t
+~ Double
val Double -> Signal
forall a. Num a => a -> a -> a
- ObjectData a -> Double
forall a. ObjectData a -> Double
getter ObjectData a
obj
oRightX :: Lens' (ObjectData a) Double
oRightX :: (Double -> f Double) -> ObjectData a -> f (ObjectData a)
oRightX = (ObjectData a -> Double)
-> (ObjectData a -> Double -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) Double Double
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ObjectData a -> Double
forall a. ObjectData a -> Double
getter ObjectData a -> Double -> ObjectData a
forall a. ObjectData a -> Double -> ObjectData a
setter
where
getter :: ObjectData a -> Double
getter ObjectData a
obj =
let right :: Double
right = ObjectData a
obj ObjectData a -> Getting Double (ObjectData a) Double -> Double
forall s a. s -> Getting a s a -> a
^. Getting Double (ObjectData a) Double
forall a. Lens' (ObjectData a) Double
oMarginRight
minx :: Double
minx = ObjectData a
obj ObjectData a -> Getting Double (ObjectData a) Double -> Double
forall s a. s -> Getting a s a -> a
^. Getting Double (ObjectData a) Double
forall a. Getter (ObjectData a) Double
oBBMinX
w :: Double
w = ObjectData a
obj ObjectData a -> Getting Double (ObjectData a) Double -> Double
forall s a. s -> Getting a s a -> a
^. Getting Double (ObjectData a) Double
forall a. Getter (ObjectData a) Double
oBBWidth
dx :: Double
dx = ObjectData a
obj ObjectData a -> Getting Double (ObjectData a) Double -> Double
forall s a. s -> Getting a s a -> a
^. (V2 Double -> Const Double (V2 Double))
-> ObjectData a -> Const Double (ObjectData a)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate ((V2 Double -> Const Double (V2 Double))
-> ObjectData a -> Const Double (ObjectData a))
-> ((Double -> Const Double Double)
-> V2 Double -> Const Double (V2 Double))
-> Getting Double (ObjectData a) Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Const Double Double)
-> V2 Double -> Const Double (V2 Double)
forall s t a b. Field1 s t a b => Lens s t a b
_1
in Double
dx Double -> Signal
forall a. Num a => a -> a -> a
+ Double
minx Double -> Signal
forall a. Num a => a -> a -> a
+ Double
w Double -> Signal
forall a. Num a => a -> a -> a
+ Double
right
setter :: ObjectData a -> Double -> ObjectData a
setter ObjectData a
obj Double
val =
ObjectData a
obj ObjectData a -> (ObjectData a -> ObjectData a) -> ObjectData a
forall a b. a -> (a -> b) -> b
& ((V2 Double -> Identity (V2 Double))
-> ObjectData a -> Identity (ObjectData a)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate ((V2 Double -> Identity (V2 Double))
-> ObjectData a -> Identity (ObjectData a))
-> ((Double -> Identity Double)
-> V2 Double -> Identity (V2 Double))
-> (Double -> Identity Double)
-> ObjectData a
-> Identity (ObjectData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Identity Double) -> V2 Double -> Identity (V2 Double)
forall s t a b. Field1 s t a b => Lens s t a b
_1) ((Double -> Identity Double)
-> ObjectData a -> Identity (ObjectData a))
-> Double -> ObjectData a -> ObjectData a
forall a s t. Num a => ASetter s t a a -> a -> s -> t
+~ Double
val Double -> Signal
forall a. Num a => a -> a -> a
- ObjectData a -> Double
forall a. ObjectData a -> Double
getter ObjectData a
obj
oCenterXY :: Lens' (ObjectData a) (V2 Double)
oCenterXY :: (V2 Double -> f (V2 Double)) -> ObjectData a -> f (ObjectData a)
oCenterXY = (ObjectData a -> V2 Double)
-> (ObjectData a -> V2 Double -> ObjectData a)
-> Lens (ObjectData a) (ObjectData a) (V2 Double) (V2 Double)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ObjectData a -> V2 Double
forall a. ObjectData a -> V2 Double
getter ObjectData a -> V2 Double -> ObjectData a
forall a. ObjectData a -> V2 Double -> ObjectData a
setter
where
getter :: ObjectData a -> V2 Double
getter ObjectData a
obj =
let minx :: Double
minx = ObjectData a
obj ObjectData a -> Getting Double (ObjectData a) Double -> Double
forall s a. s -> Getting a s a -> a
^. Getting Double (ObjectData a) Double
forall a. Getter (ObjectData a) Double
oBBMinX
miny :: Double
miny = ObjectData a
obj ObjectData a -> Getting Double (ObjectData a) Double -> Double
forall s a. s -> Getting a s a -> a
^. Getting Double (ObjectData a) Double
forall a. Getter (ObjectData a) Double
oBBMinY
w :: Double
w = ObjectData a
obj ObjectData a -> Getting Double (ObjectData a) Double -> Double
forall s a. s -> Getting a s a -> a
^. Getting Double (ObjectData a) Double
forall a. Getter (ObjectData a) Double
oBBWidth
h :: Double
h = ObjectData a
obj ObjectData a -> Getting Double (ObjectData a) Double -> Double
forall s a. s -> Getting a s a -> a
^. Getting Double (ObjectData a) Double
forall a. Getter (ObjectData a) Double
oBBHeight
V2 Double
dx Double
dy = ObjectData a
obj ObjectData a
-> Getting (V2 Double) (ObjectData a) (V2 Double) -> V2 Double
forall s a. s -> Getting a s a -> a
^. Getting (V2 Double) (ObjectData a) (V2 Double)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate
in Double -> Double -> V2 Double
forall a. a -> a -> V2 a
V2 (Double
dx Double -> Signal
forall a. Num a => a -> a -> a
+ Double
minx Double -> Signal
forall a. Num a => a -> a -> a
+ Double
w Double -> Signal
forall a. Fractional a => a -> a -> a
/ Double
2) (Double
dy Double -> Signal
forall a. Num a => a -> a -> a
+ Double
miny Double -> Signal
forall a. Num a => a -> a -> a
+ Double
h Double -> Signal
forall a. Fractional a => a -> a -> a
/ Double
2)
setter :: ObjectData a -> V2 Double -> ObjectData a
setter ObjectData a
obj (V2 Double
dx Double
dy) =
let V2 Double
x Double
y = ObjectData a -> V2 Double
forall a. ObjectData a -> V2 Double
getter ObjectData a
obj
in ObjectData a
obj ObjectData a -> (ObjectData a -> ObjectData a) -> ObjectData a
forall a b. a -> (a -> b) -> b
& ((V2 Double -> Identity (V2 Double))
-> ObjectData a -> Identity (ObjectData a)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate ((V2 Double -> Identity (V2 Double))
-> ObjectData a -> Identity (ObjectData a))
-> ((Double -> Identity Double)
-> V2 Double -> Identity (V2 Double))
-> (Double -> Identity Double)
-> ObjectData a
-> Identity (ObjectData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Identity Double) -> V2 Double -> Identity (V2 Double)
forall s t a b. Field1 s t a b => Lens s t a b
_1) ((Double -> Identity Double)
-> ObjectData a -> Identity (ObjectData a))
-> Double -> ObjectData a -> ObjectData a
forall a s t. Num a => ASetter s t a a -> a -> s -> t
+~ Double
dx Double -> Signal
forall a. Num a => a -> a -> a
- Double
x
ObjectData a -> (ObjectData a -> ObjectData a) -> ObjectData a
forall a b. a -> (a -> b) -> b
& ((V2 Double -> Identity (V2 Double))
-> ObjectData a -> Identity (ObjectData a)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate ((V2 Double -> Identity (V2 Double))
-> ObjectData a -> Identity (ObjectData a))
-> ((Double -> Identity Double)
-> V2 Double -> Identity (V2 Double))
-> (Double -> Identity Double)
-> ObjectData a
-> Identity (ObjectData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Identity Double) -> V2 Double -> Identity (V2 Double)
forall s t a b. Field2 s t a b => Lens s t a b
_2) ((Double -> Identity Double)
-> ObjectData a -> Identity (ObjectData a))
-> Double -> ObjectData a -> ObjectData a
forall a s t. Num a => ASetter s t a a -> a -> s -> t
+~ Double
dy Double -> Signal
forall a. Num a => a -> a -> a
- Double
y
oCenterX :: Lens' (ObjectData a) Double
oCenterX :: (Double -> f Double) -> ObjectData a -> f (ObjectData a)
oCenterX = (V2 Double -> f (V2 Double)) -> ObjectData a -> f (ObjectData a)
forall a. Lens' (ObjectData a) (V2 Double)
oCenterXY ((V2 Double -> f (V2 Double)) -> ObjectData a -> f (ObjectData a))
-> ((Double -> f Double) -> V2 Double -> f (V2 Double))
-> (Double -> f Double)
-> ObjectData a
-> f (ObjectData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> f Double) -> V2 Double -> f (V2 Double)
forall (t :: * -> *) a. R1 t => Lens' (t a) a
_x
oCenterY :: Lens' (ObjectData a) Double
oCenterY :: (Double -> f Double) -> ObjectData a -> f (ObjectData a)
oCenterY = (V2 Double -> f (V2 Double)) -> ObjectData a -> f (ObjectData a)
forall a. Lens' (ObjectData a) (V2 Double)
oCenterXY ((V2 Double -> f (V2 Double)) -> ObjectData a -> f (ObjectData a))
-> ((Double -> f Double) -> V2 Double -> f (V2 Double))
-> (Double -> f Double)
-> ObjectData a
-> f (ObjectData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> f Double) -> V2 Double -> f (V2 Double)
forall (t :: * -> *) a. R2 t => Lens' (t a) a
_y
oMarginTop :: Lens' (ObjectData a) Double
oMarginTop :: (Double -> f Double) -> ObjectData a -> f (ObjectData a)
oMarginTop = ((Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> ObjectData a -> f (ObjectData a)
forall a. Lens' (ObjectData a) (Double, Double, Double, Double)
oMargin (((Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> ObjectData a -> f (ObjectData a))
-> ((Double -> f Double)
-> (Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> (Double -> f Double)
-> ObjectData a
-> f (ObjectData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> f Double)
-> (Double, Double, Double, Double)
-> f (Double, Double, Double, Double)
forall s t a b. Field1 s t a b => Lens s t a b
_1
oMarginRight :: Lens' (ObjectData a) Double
oMarginRight :: (Double -> f Double) -> ObjectData a -> f (ObjectData a)
oMarginRight = ((Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> ObjectData a -> f (ObjectData a)
forall a. Lens' (ObjectData a) (Double, Double, Double, Double)
oMargin (((Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> ObjectData a -> f (ObjectData a))
-> ((Double -> f Double)
-> (Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> (Double -> f Double)
-> ObjectData a
-> f (ObjectData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> f Double)
-> (Double, Double, Double, Double)
-> f (Double, Double, Double, Double)
forall s t a b. Field2 s t a b => Lens s t a b
_2
oMarginBottom :: Lens' (ObjectData a) Double
oMarginBottom :: (Double -> f Double) -> ObjectData a -> f (ObjectData a)
oMarginBottom = ((Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> ObjectData a -> f (ObjectData a)
forall a. Lens' (ObjectData a) (Double, Double, Double, Double)
oMargin (((Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> ObjectData a -> f (ObjectData a))
-> ((Double -> f Double)
-> (Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> (Double -> f Double)
-> ObjectData a
-> f (ObjectData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> f Double)
-> (Double, Double, Double, Double)
-> f (Double, Double, Double, Double)
forall s t a b. Field3 s t a b => Lens s t a b
_3
oMarginLeft :: Lens' (ObjectData a) Double
oMarginLeft :: (Double -> f Double) -> ObjectData a -> f (ObjectData a)
oMarginLeft = ((Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> ObjectData a -> f (ObjectData a)
forall a. Lens' (ObjectData a) (Double, Double, Double, Double)
oMargin (((Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> ObjectData a -> f (ObjectData a))
-> ((Double -> f Double)
-> (Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> (Double -> f Double)
-> ObjectData a
-> f (ObjectData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> f Double)
-> (Double, Double, Double, Double)
-> f (Double, Double, Double, Double)
forall s t a b. Field4 s t a b => Lens s t a b
_4
oBBMinX :: Getter (ObjectData a) Double
oBBMinX :: (Double -> f Double) -> ObjectData a -> f (ObjectData a)
oBBMinX = ((Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> ObjectData a -> f (ObjectData a)
forall a. Getter (ObjectData a) (Double, Double, Double, Double)
oBB (((Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> ObjectData a -> f (ObjectData a))
-> ((Double -> f Double)
-> (Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> (Double -> f Double)
-> ObjectData a
-> f (ObjectData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> f Double)
-> (Double, Double, Double, Double)
-> f (Double, Double, Double, Double)
forall s t a b. Field1 s t a b => Lens s t a b
_1
oBBMinY :: Getter (ObjectData a) Double
oBBMinY :: (Double -> f Double) -> ObjectData a -> f (ObjectData a)
oBBMinY = ((Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> ObjectData a -> f (ObjectData a)
forall a. Getter (ObjectData a) (Double, Double, Double, Double)
oBB (((Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> ObjectData a -> f (ObjectData a))
-> ((Double -> f Double)
-> (Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> (Double -> f Double)
-> ObjectData a
-> f (ObjectData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> f Double)
-> (Double, Double, Double, Double)
-> f (Double, Double, Double, Double)
forall s t a b. Field2 s t a b => Lens s t a b
_2
oBBWidth :: Getter (ObjectData a) Double
oBBWidth :: (Double -> f Double) -> ObjectData a -> f (ObjectData a)
oBBWidth = ((Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> ObjectData a -> f (ObjectData a)
forall a. Getter (ObjectData a) (Double, Double, Double, Double)
oBB (((Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> ObjectData a -> f (ObjectData a))
-> ((Double -> f Double)
-> (Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> (Double -> f Double)
-> ObjectData a
-> f (ObjectData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> f Double)
-> (Double, Double, Double, Double)
-> f (Double, Double, Double, Double)
forall s t a b. Field3 s t a b => Lens s t a b
_3
oBBHeight :: Getter (ObjectData a) Double
oBBHeight :: (Double -> f Double) -> ObjectData a -> f (ObjectData a)
oBBHeight = ((Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> ObjectData a -> f (ObjectData a)
forall a. Getter (ObjectData a) (Double, Double, Double, Double)
oBB (((Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> ObjectData a -> f (ObjectData a))
-> ((Double -> f Double)
-> (Double, Double, Double, Double)
-> f (Double, Double, Double, Double))
-> (Double -> f Double)
-> ObjectData a
-> f (ObjectData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> f Double)
-> (Double, Double, Double, Double)
-> f (Double, Double, Double, Double)
forall s t a b. Field4 s t a b => Lens s t a b
_4
oModify :: Object s a -> (ObjectData a -> ObjectData a) -> Scene s ()
oModify :: Object s a -> (ObjectData a -> ObjectData a) -> Scene s ()
oModify Object s a
o = Var s (ObjectData a)
-> (ObjectData a -> ObjectData a) -> Scene s ()
forall s a. Var s a -> (a -> a) -> Scene s ()
modifyVar (Object s a -> Var s (ObjectData a)
forall s a. Object s a -> Var s (ObjectData a)
objectData Object s a
o)
oModifyS :: Object s a -> State (ObjectData a) b -> Scene s ()
oModifyS :: Object s a -> State (ObjectData a) b -> Scene s ()
oModifyS Object s a
o = Object s a -> (ObjectData a -> ObjectData a) -> Scene s ()
forall s a.
Object s a -> (ObjectData a -> ObjectData a) -> Scene s ()
oModify Object s a
o ((ObjectData a -> ObjectData a) -> Scene s ())
-> (State (ObjectData a) b -> ObjectData a -> ObjectData a)
-> State (ObjectData a) b
-> Scene s ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. State (ObjectData a) b -> ObjectData a -> ObjectData a
forall s a. State s a -> s -> s
execState
oRead :: Object s a -> Getting b (ObjectData a) b -> Scene s b
oRead :: Object s a -> Getting b (ObjectData a) b -> Scene s b
oRead Object s a
o Getting b (ObjectData a) b
l = Getting b (ObjectData a) b -> ObjectData a -> b
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting b (ObjectData a) b
l (ObjectData a -> b) -> Scene s (ObjectData a) -> Scene s b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Var s (ObjectData a) -> Scene s (ObjectData a)
forall s a. Var s a -> Scene s a
readVar (Object s a -> Var s (ObjectData a)
forall s a. Object s a -> Var s (ObjectData a)
objectData Object s a
o)
oTween :: Object s a -> Duration -> (Double -> ObjectData a -> ObjectData a) -> Scene s ()
oTween :: Object s a
-> Double -> (Double -> ObjectData a -> ObjectData a) -> Scene s ()
oTween Object s a
o Double
d Double -> ObjectData a -> ObjectData a
fn = do
Signal
ease <- Object s a
-> Getting Signal (ObjectData a) Signal -> Scene s Signal
forall s a b. Object s a -> Getting b (ObjectData a) b -> Scene s b
oRead Object s a
o Getting Signal (ObjectData a) Signal
forall a. Lens' (ObjectData a) Signal
oEasing
Var s (ObjectData a)
-> Double -> (ObjectData a -> Double -> ObjectData a) -> Scene s ()
forall s a. Var s a -> Double -> (a -> Double -> a) -> Scene s ()
tweenVar (Object s a -> Var s (ObjectData a)
forall s a. Object s a -> Var s (ObjectData a)
objectData Object s a
o) Double
d (\ObjectData a
v Double
t -> Double -> ObjectData a -> ObjectData a
fn (Signal
ease Double
t) ObjectData a
v)
oTweenS :: Object s a -> Duration -> (Double -> State (ObjectData a) b) -> Scene s ()
oTweenS :: Object s a
-> Double -> (Double -> State (ObjectData a) b) -> Scene s ()
oTweenS Object s a
o Double
d Double -> State (ObjectData a) b
fn = Object s a
-> Double -> (Double -> ObjectData a -> ObjectData a) -> Scene s ()
forall s a.
Object s a
-> Double -> (Double -> ObjectData a -> ObjectData a) -> Scene s ()
oTween Object s a
o Double
d (State (ObjectData a) b -> ObjectData a -> ObjectData a
forall s a. State s a -> s -> s
execState (State (ObjectData a) b -> ObjectData a -> ObjectData a)
-> (Double -> State (ObjectData a) b)
-> Double
-> ObjectData a
-> ObjectData a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> State (ObjectData a) b
fn)
oTweenV :: Renderable a => Object s a -> Duration -> (Double -> a -> a) -> Scene s ()
oTweenV :: Object s a -> Double -> (Double -> a -> a) -> Scene s ()
oTweenV Object s a
o Double
d Double -> a -> a
fn = Object s a
-> Double -> (Double -> ObjectData a -> ObjectData a) -> Scene s ()
forall s a.
Object s a
-> Double -> (Double -> ObjectData a -> ObjectData a) -> Scene s ()
oTween Object s a
o Double
d (\Double
t -> (a -> Identity a) -> ObjectData a -> Identity (ObjectData a)
forall a. Renderable a => Lens' (ObjectData a) a
oValue ((a -> Identity a) -> ObjectData a -> Identity (ObjectData a))
-> (a -> a) -> ObjectData a -> ObjectData a
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Double -> a -> a
fn Double
t)
oTweenVS :: Renderable a => Object s a -> Duration -> (Double -> State a b) -> Scene s ()
oTweenVS :: Object s a -> Double -> (Double -> State a b) -> Scene s ()
oTweenVS Object s a
o Double
d Double -> State a b
fn = Object s a
-> Double -> (Double -> ObjectData a -> ObjectData a) -> Scene s ()
forall s a.
Object s a
-> Double -> (Double -> ObjectData a -> ObjectData a) -> Scene s ()
oTween Object s a
o Double
d (\Double
t -> (a -> Identity a) -> ObjectData a -> Identity (ObjectData a)
forall a. Renderable a => Lens' (ObjectData a) a
oValue ((a -> Identity a) -> ObjectData a -> Identity (ObjectData a))
-> (a -> a) -> ObjectData a -> ObjectData a
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ State a b -> a -> a
forall s a. State s a -> s -> s
execState (Double -> State a b
fn Double
t))
oNew :: Renderable a => a -> Scene s (Object s a)
oNew :: a -> Scene s (Object s a)
oNew = a -> Scene s (Object s a)
forall a s. Renderable a => a -> Scene s (Object s a)
newObject
newObject :: Renderable a => a -> Scene s (Object s a)
newObject :: a -> Scene s (Object s a)
newObject a
val = do
Var s (ObjectData a)
ref <-
ObjectData a -> Scene s (Var s (ObjectData a))
forall a s. a -> Scene s (Var s a)
newVar
ObjectData :: forall a.
V2 Double
-> a
-> Tree
-> (Tree -> Tree)
-> (Double, Double, Double, Double)
-> (Double, Double, Double, Double)
-> Double
-> Bool
-> Int
-> Signal
-> Double
-> V2 Double
-> ObjectData a
ObjectData
{ _oTranslate :: V2 Double
_oTranslate = Double -> Double -> V2 Double
forall a. a -> a -> V2 a
V2 Double
0 Double
0,
_oValueRef :: a
_oValueRef = a
val,
_oSVG :: Tree
_oSVG = Tree
svg,
_oContext :: Tree -> Tree
_oContext = Tree -> Tree
forall a. a -> a
id,
_oMargin :: (Double, Double, Double, Double)
_oMargin = (Double
0.5, Double
0.5, Double
0.5, Double
0.5),
_oBB :: (Double, Double, Double, Double)
_oBB = Tree -> (Double, Double, Double, Double)
boundingBox Tree
svg,
_oOpacity :: Double
_oOpacity = Double
1,
_oShown :: Bool
_oShown = Bool
False,
_oZIndex :: Int
_oZIndex = Int
1,
_oEasing :: Signal
_oEasing = Double -> Signal
curveS Double
2,
_oScale :: Double
_oScale = Double
1,
_oScaleOrigin :: V2 Double
_oScaleOrigin = Double -> Double -> V2 Double
forall a. a -> a -> V2 a
V2 Double
0 Double
0
}
Sprite s
sprite <- Frame s Tree -> Scene s (Sprite s)
forall s. Frame s Tree -> Scene s (Sprite s)
newSprite (Frame s Tree -> Scene s (Sprite s))
-> Frame s Tree -> Scene s (Sprite s)
forall a b. (a -> b) -> a -> b
$ do
~obj :: ObjectData a
obj@ObjectData {a
Bool
Double
Int
(Double, Double, Double, Double)
V2 Double
Tree
Signal
Tree -> Tree
_oScaleOrigin :: V2 Double
_oScale :: Double
_oEasing :: Signal
_oZIndex :: Int
_oShown :: Bool
_oOpacity :: Double
_oBB :: (Double, Double, Double, Double)
_oMargin :: (Double, Double, Double, Double)
_oContext :: Tree -> Tree
_oSVG :: Tree
_oValueRef :: a
_oTranslate :: V2 Double
_oScaleOrigin :: forall a. ObjectData a -> V2 Double
_oScale :: forall a. ObjectData a -> Double
_oEasing :: forall a. ObjectData a -> Signal
_oZIndex :: forall a. ObjectData a -> Int
_oShown :: forall a. ObjectData a -> Bool
_oOpacity :: forall a. ObjectData a -> Double
_oBB :: forall a. ObjectData a -> (Double, Double, Double, Double)
_oMargin :: forall a. ObjectData a -> (Double, Double, Double, Double)
_oContext :: forall a. ObjectData a -> Tree -> Tree
_oSVG :: forall a. ObjectData a -> Tree
_oValueRef :: forall a. ObjectData a -> a
_oTranslate :: forall a. ObjectData a -> V2 Double
..} <- Var s (ObjectData a) -> Frame s (ObjectData a)
forall s a. Var s a -> Frame s a
unVar Var s (ObjectData a)
ref
pure $
if Bool
_oShown
then
(Double -> Double -> Tree -> Tree) -> V2 Double -> Tree -> Tree
forall a b. (a -> a -> b) -> V2 a -> b
uncurryV2 Double -> Double -> Tree -> Tree
translate V2 Double
_oTranslate (Tree -> Tree) -> Tree -> Tree
forall a b. (a -> b) -> a -> b
$
ObjectData a -> Tree -> Tree
forall a. ObjectData a -> Tree -> Tree
oScaleApply ObjectData a
obj (Tree -> Tree) -> Tree -> Tree
forall a b. (a -> b) -> a -> b
$
Double -> Tree -> Tree
withGroupOpacity Double
_oOpacity (Tree -> Tree) -> Tree -> Tree
forall a b. (a -> b) -> a -> b
$
[Tree] -> Tree
mkGroup [Tree -> Tree
_oContext Tree
_oSVG]
else Tree
None
Sprite s -> Frame s ((Tree, Int) -> (Tree, Int)) -> Scene s ()
forall s.
Sprite s -> Frame s ((Tree, Int) -> (Tree, Int)) -> Scene s ()
spriteModify Sprite s
sprite (Frame s ((Tree, Int) -> (Tree, Int)) -> Scene s ())
-> Frame s ((Tree, Int) -> (Tree, Int)) -> Scene s ()
forall a b. (a -> b) -> a -> b
$ do
~ObjectData {_oZIndex :: forall a. ObjectData a -> Int
_oZIndex = Int
z} <- Var s (ObjectData a) -> Frame s (ObjectData a)
forall s a. Var s a -> Frame s a
unVar Var s (ObjectData a)
ref
pure $ \(Tree
img, Int
_) -> (Tree
img, Int
z)
return
Object :: forall s a. Sprite s -> Var s (ObjectData a) -> Object s a
Object
{ objectSprite :: Sprite s
objectSprite = Sprite s
sprite,
objectData :: Var s (ObjectData a)
objectData = Var s (ObjectData a)
ref
}
where
svg :: Tree
svg = a -> Tree
forall a. Renderable a => a -> Tree
toSVG a
val
oScaleApply :: ObjectData a -> (SVG -> SVG)
oScaleApply :: ObjectData a -> Tree -> Tree
oScaleApply ObjectData {a
Bool
Double
Int
(Double, Double, Double, Double)
V2 Double
Tree
Signal
Tree -> Tree
_oScaleOrigin :: V2 Double
_oScale :: Double
_oEasing :: Signal
_oZIndex :: Int
_oShown :: Bool
_oOpacity :: Double
_oBB :: (Double, Double, Double, Double)
_oMargin :: (Double, Double, Double, Double)
_oContext :: Tree -> Tree
_oSVG :: Tree
_oValueRef :: a
_oTranslate :: V2 Double
_oScaleOrigin :: forall a. ObjectData a -> V2 Double
_oScale :: forall a. ObjectData a -> Double
_oEasing :: forall a. ObjectData a -> Signal
_oZIndex :: forall a. ObjectData a -> Int
_oShown :: forall a. ObjectData a -> Bool
_oOpacity :: forall a. ObjectData a -> Double
_oBB :: forall a. ObjectData a -> (Double, Double, Double, Double)
_oMargin :: forall a. ObjectData a -> (Double, Double, Double, Double)
_oContext :: forall a. ObjectData a -> Tree -> Tree
_oSVG :: forall a. ObjectData a -> Tree
_oValueRef :: forall a. ObjectData a -> a
_oTranslate :: forall a. ObjectData a -> V2 Double
..} =
(Double -> Double -> Tree -> Tree) -> V2 Double -> Tree -> Tree
forall a b. (a -> a -> b) -> V2 a -> b
uncurryV2 Double -> Double -> Tree -> Tree
translate (V2 Double -> V2 Double
forall a. Num a => a -> a
negate V2 Double
_oScaleOrigin)
(Tree -> Tree) -> (Tree -> Tree) -> Tree -> Tree
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Tree -> Tree
scale Double
_oScale
(Tree -> Tree) -> (Tree -> Tree) -> Tree -> Tree
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Double -> Tree -> Tree) -> V2 Double -> Tree -> Tree
forall a b. (a -> a -> b) -> V2 a -> b
uncurryV2 Double -> Double -> Tree -> Tree
translate V2 Double
_oScaleOrigin
uncurryV2 :: (a -> a -> b) -> V2 a -> b
uncurryV2 :: (a -> a -> b) -> V2 a -> b
uncurryV2 a -> a -> b
fn (V2 a
a a
b) = a -> a -> b
fn a
a a
b
oShow :: Object s a -> Scene s ()
oShow :: Object s a -> Scene s ()
oShow Object s a
o = Object s a -> (ObjectData a -> ObjectData a) -> Scene s ()
forall s a.
Object s a -> (ObjectData a -> ObjectData a) -> Scene s ()
oModify Object s a
o ((ObjectData a -> ObjectData a) -> Scene s ())
-> (ObjectData a -> ObjectData a) -> Scene s ()
forall a b. (a -> b) -> a -> b
$ (Bool -> Identity Bool) -> ObjectData a -> Identity (ObjectData a)
forall a. Lens' (ObjectData a) Bool
oShown ((Bool -> Identity Bool)
-> ObjectData a -> Identity (ObjectData a))
-> Bool -> ObjectData a -> ObjectData a
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
True
oHide :: Object s a -> Scene s ()
oHide :: Object s a -> Scene s ()
oHide Object s a
o = Object s a -> (ObjectData a -> ObjectData a) -> Scene s ()
forall s a.
Object s a -> (ObjectData a -> ObjectData a) -> Scene s ()
oModify Object s a
o ((ObjectData a -> ObjectData a) -> Scene s ())
-> (ObjectData a -> ObjectData a) -> Scene s ()
forall a b. (a -> b) -> a -> b
$ (Bool -> Identity Bool) -> ObjectData a -> Identity (ObjectData a)
forall a. Lens' (ObjectData a) Bool
oShown ((Bool -> Identity Bool)
-> ObjectData a -> Identity (ObjectData a))
-> Bool -> ObjectData a -> ObjectData a
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
False
oShowWith :: Object s a -> (SVG -> Animation) -> Scene s ()
oShowWith :: Object s a -> (Tree -> Animation) -> Scene s ()
oShowWith Object s a
o Tree -> Animation
fn = do
Object s a -> (ObjectData a -> ObjectData a) -> Scene s ()
forall s a.
Object s a -> (ObjectData a -> ObjectData a) -> Scene s ()
oModify Object s a
o ((ObjectData a -> ObjectData a) -> Scene s ())
-> (ObjectData a -> ObjectData a) -> Scene s ()
forall a b. (a -> b) -> a -> b
$ (Bool -> Identity Bool) -> ObjectData a -> Identity (ObjectData a)
forall a. Lens' (ObjectData a) Bool
oShown ((Bool -> Identity Bool)
-> ObjectData a -> Identity (ObjectData a))
-> Bool -> ObjectData a -> ObjectData a
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
True
Tree
initSVG <- Object s a -> Getting Tree (ObjectData a) Tree -> Scene s Tree
forall s a b. Object s a -> Getting b (ObjectData a) b -> Scene s b
oRead Object s a
o Getting Tree (ObjectData a) Tree
forall a. Getter (ObjectData a) Tree
oSVG
let ani :: Animation
ani = Tree -> Animation
fn Tree
initSVG
Object s a
-> Double -> (Double -> ObjectData a -> ObjectData a) -> Scene s ()
forall s a.
Object s a
-> Double -> (Double -> ObjectData a -> ObjectData a) -> Scene s ()
oTween Object s a
o (Animation -> Double
duration Animation
ani) ((Double -> ObjectData a -> ObjectData a) -> Scene s ())
-> (Double -> ObjectData a -> ObjectData a) -> Scene s ()
forall a b. (a -> b) -> a -> b
$ \Double
t ObjectData a
obj ->
ObjectData a
obj {_oSVG :: Tree
_oSVG = Sync -> Animation -> Double -> Double -> Tree
getAnimationFrame Sync
SyncStretch Animation
ani Double
t Double
1}
Object s a -> (ObjectData a -> ObjectData a) -> Scene s ()
forall s a.
Object s a -> (ObjectData a -> ObjectData a) -> Scene s ()
oModify Object s a
o ((ObjectData a -> ObjectData a) -> Scene s ())
-> (ObjectData a -> ObjectData a) -> Scene s ()
forall a b. (a -> b) -> a -> b
$ \ObjectData a
obj -> ObjectData a
obj {_oSVG :: Tree
_oSVG = Tree
initSVG}
oHideWith :: Object s a -> (SVG -> Animation) -> Scene s ()
oHideWith :: Object s a -> (Tree -> Animation) -> Scene s ()
oHideWith Object s a
o Tree -> Animation
fn = do
Tree
initSVG <- Object s a -> Getting Tree (ObjectData a) Tree -> Scene s Tree
forall s a b. Object s a -> Getting b (ObjectData a) b -> Scene s b
oRead Object s a
o Getting Tree (ObjectData a) Tree
forall a. Getter (ObjectData a) Tree
oSVG
let ani :: Animation
ani = Tree -> Animation
fn Tree
initSVG
Object s a
-> Double -> (Double -> ObjectData a -> ObjectData a) -> Scene s ()
forall s a.
Object s a
-> Double -> (Double -> ObjectData a -> ObjectData a) -> Scene s ()
oTween Object s a
o (Animation -> Double
duration Animation
ani) ((Double -> ObjectData a -> ObjectData a) -> Scene s ())
-> (Double -> ObjectData a -> ObjectData a) -> Scene s ()
forall a b. (a -> b) -> a -> b
$ \Double
t ObjectData a
obj ->
ObjectData a
obj {_oSVG :: Tree
_oSVG = Sync -> Animation -> Double -> Double -> Tree
getAnimationFrame Sync
SyncStretch Animation
ani Double
t Double
1}
Object s a -> (ObjectData a -> ObjectData a) -> Scene s ()
forall s a.
Object s a -> (ObjectData a -> ObjectData a) -> Scene s ()
oModify Object s a
o ((ObjectData a -> ObjectData a) -> Scene s ())
-> (ObjectData a -> ObjectData a) -> Scene s ()
forall a b. (a -> b) -> a -> b
$ \ObjectData a
obj -> ObjectData a
obj {_oSVG :: Tree
_oSVG = Tree
initSVG}
Object s a -> (ObjectData a -> ObjectData a) -> Scene s ()
forall s a.
Object s a -> (ObjectData a -> ObjectData a) -> Scene s ()
oModify Object s a
o ((ObjectData a -> ObjectData a) -> Scene s ())
-> (ObjectData a -> ObjectData a) -> Scene s ()
forall a b. (a -> b) -> a -> b
$ (Bool -> Identity Bool) -> ObjectData a -> Identity (ObjectData a)
forall a. Lens' (ObjectData a) Bool
oShown ((Bool -> Identity Bool)
-> ObjectData a -> Identity (ObjectData a))
-> Bool -> ObjectData a -> ObjectData a
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
False
oFadeIn :: SVG -> Animation
oFadeIn :: Tree -> Animation
oFadeIn Tree
svg = (Double -> Tree) -> Animation
animate ((Double -> Tree) -> Animation) -> (Double -> Tree) -> Animation
forall a b. (a -> b) -> a -> b
$ \Double
t -> Double -> Tree -> Tree
withGroupOpacity Double
t Tree
svg
oFadeOut :: SVG -> Animation
oFadeOut :: Tree -> Animation
oFadeOut = Animation -> Animation
reverseA (Animation -> Animation)
-> (Tree -> Animation) -> Tree -> Animation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tree -> Animation
oFadeIn
oGrow :: SVG -> Animation
oGrow :: Tree -> Animation
oGrow Tree
svg = (Double -> Tree) -> Animation
animate ((Double -> Tree) -> Animation) -> (Double -> Tree) -> Animation
forall a b. (a -> b) -> a -> b
$ \Double
t -> Double -> Tree -> Tree
scale Double
t Tree
svg
oShrink :: SVG -> Animation
oShrink :: Tree -> Animation
oShrink = Animation -> Animation
reverseA (Animation -> Animation)
-> (Tree -> Animation) -> Tree -> Animation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tree -> Animation
oGrow
type Origin = (Double, Double)
svgOrigin :: SVG -> Origin -> (Double, Double)
svgOrigin :: Tree -> Origin -> Origin
svgOrigin Tree
svg (Double
originX, Double
originY) =
case Tree -> (Double, Double, Double, Double)
boundingBox Tree
svg of
(Double
polyX, Double
polyY, Double
polyWidth, Double
polyHeight) ->
( Double
polyX Double -> Signal
forall a. Num a => a -> a -> a
+ Double
polyWidth Double -> Signal
forall a. Num a => a -> a -> a
* Double
originX,
Double
polyY Double -> Signal
forall a. Num a => a -> a -> a
+ Double
polyHeight Double -> Signal
forall a. Num a => a -> a -> a
* Double
originY
)
oScaleIn :: SVG -> Animation
oScaleIn :: Tree -> Animation
oScaleIn = Signal -> Origin -> Tree -> Animation
oScaleIn' (Double -> Signal
curveS Double
2) (Double
0.5, Double
1)
oScaleIn' :: Signal -> Origin -> SVG -> Animation
oScaleIn' :: Signal -> Origin -> Tree -> Animation
oScaleIn' Signal
easing Origin
origin = Double -> (Tree -> Animation) -> Tree -> Animation
oStagger' Double
0.05 ((Tree -> Animation) -> Tree -> Animation)
-> (Tree -> Animation) -> Tree -> Animation
forall a b. (a -> b) -> a -> b
$ \Tree
svg ->
let (Double
cx, Double
cy) = Tree -> Origin -> Origin
svgOrigin Tree
svg Origin
origin
in Signal -> Animation -> Animation
signalA Signal
easing (Animation -> Animation) -> Animation -> Animation
forall a b. (a -> b) -> a -> b
$
Double -> (Double -> Tree) -> Animation
mkAnimation Double
0.3 ((Double -> Tree) -> Animation) -> (Double -> Tree) -> Animation
forall a b. (a -> b) -> a -> b
$ \Double
t ->
Double -> Double -> Tree -> Tree
translate Double
cx Double
cy (Tree -> Tree) -> Tree -> Tree
forall a b. (a -> b) -> a -> b
$
Double -> Tree -> Tree
scale Double
t (Tree -> Tree) -> Tree -> Tree
forall a b. (a -> b) -> a -> b
$
Double -> Double -> Tree -> Tree
translate
(- Double
cx)
(- Double
cy)
Tree
svg
oScaleOut :: SVG -> Animation
oScaleOut :: Tree -> Animation
oScaleOut = Animation -> Animation
reverseA (Animation -> Animation)
-> (Tree -> Animation) -> Tree -> Animation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> (Tree -> Animation) -> Tree -> Animation
oStaggerRev' Double
0.05 (Signal -> Origin -> Tree -> Animation
oScaleIn' (Double -> Signal
curveS Double
2) (Double
0.5, Double
0))
oScaleOut' :: Signal -> Origin -> SVG -> Animation
oScaleOut' :: Signal -> Origin -> Tree -> Animation
oScaleOut' Signal
easing Origin
origin = Animation -> Animation
reverseA (Animation -> Animation)
-> (Tree -> Animation) -> Tree -> Animation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> (Tree -> Animation) -> Tree -> Animation
oStaggerRev' Double
0.05 (Signal -> Origin -> Tree -> Animation
oScaleIn' Signal
easing Origin
origin)
oSim :: (SVG -> Animation) -> SVG -> Animation
oSim :: (Tree -> Animation) -> Tree -> Animation
oSim = Double -> (Tree -> Animation) -> Tree -> Animation
oStagger' Double
0
oStagger :: (SVG -> Animation) -> SVG -> Animation
oStagger :: (Tree -> Animation) -> Tree -> Animation
oStagger = Double -> (Tree -> Animation) -> Tree -> Animation
oStagger' Double
0.2
oStaggerRev :: (SVG -> Animation) -> SVG -> Animation
oStaggerRev :: (Tree -> Animation) -> Tree -> Animation
oStaggerRev = Double -> (Tree -> Animation) -> Tree -> Animation
oStaggerRev' Double
0.2
oStagger' :: Duration -> (SVG -> Animation) -> SVG -> Animation
oStagger' :: Double -> (Tree -> Animation) -> Tree -> Animation
oStagger' Double
staggerDelay Tree -> Animation
fn Tree
svg = (forall s. Scene s ()) -> Animation
forall a. (forall s. Scene s a) -> Animation
scene ((forall s. Scene s ()) -> Animation)
-> (forall s. Scene s ()) -> Animation
forall a b. (a -> b) -> a -> b
$
[(Tree -> Tree, DrawAttributes, Tree)]
-> ((Tree -> Tree, DrawAttributes, Tree) -> Scene s ())
-> Scene s ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (Tree -> [(Tree -> Tree, DrawAttributes, Tree)]
svgGlyphs Tree
svg) (((Tree -> Tree, DrawAttributes, Tree) -> Scene s ())
-> Scene s ())
-> ((Tree -> Tree, DrawAttributes, Tree) -> Scene s ())
-> Scene s ()
forall a b. (a -> b) -> a -> b
$ \(Tree -> Tree
ctx, DrawAttributes
_attr, Tree
node) -> do
Scene s (Sprite s) -> Scene s ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Scene s (Sprite s) -> Scene s ())
-> Scene s (Sprite s) -> Scene s ()
forall a b. (a -> b) -> a -> b
$ Scene s (Sprite s) -> Scene s (Sprite s)
forall s a. Scene s a -> Scene s a
fork (Scene s (Sprite s) -> Scene s (Sprite s))
-> Scene s (Sprite s) -> Scene s (Sprite s)
forall a b. (a -> b) -> a -> b
$ Sync -> Animation -> Scene s (Sprite s)
forall s. Sync -> Animation -> Scene s (Sprite s)
newSpriteA' Sync
SyncFreeze (Tree -> Animation
fn (Tree -> Animation) -> Tree -> Animation
forall a b. (a -> b) -> a -> b
$ Tree -> Tree
ctx Tree
node)
Double -> Scene s ()
forall s. Double -> Scene s ()
wait Double
staggerDelay
oStaggerRev' :: Duration -> (SVG -> Animation) -> SVG -> Animation
oStaggerRev' :: Double -> (Tree -> Animation) -> Tree -> Animation
oStaggerRev' Double
staggerDelay Tree -> Animation
fn Tree
svg = (forall s. Scene s ()) -> Animation
forall a. (forall s. Scene s a) -> Animation
scene ((forall s. Scene s ()) -> Animation)
-> (forall s. Scene s ()) -> Animation
forall a b. (a -> b) -> a -> b
$
[(Tree -> Tree, DrawAttributes, Tree)]
-> ((Tree -> Tree, DrawAttributes, Tree) -> Scene s ())
-> Scene s ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ ([(Tree -> Tree, DrawAttributes, Tree)]
-> [(Tree -> Tree, DrawAttributes, Tree)]
forall a. [a] -> [a]
reverse ([(Tree -> Tree, DrawAttributes, Tree)]
-> [(Tree -> Tree, DrawAttributes, Tree)])
-> [(Tree -> Tree, DrawAttributes, Tree)]
-> [(Tree -> Tree, DrawAttributes, Tree)]
forall a b. (a -> b) -> a -> b
$ Tree -> [(Tree -> Tree, DrawAttributes, Tree)]
svgGlyphs Tree
svg) (((Tree -> Tree, DrawAttributes, Tree) -> Scene s ())
-> Scene s ())
-> ((Tree -> Tree, DrawAttributes, Tree) -> Scene s ())
-> Scene s ()
forall a b. (a -> b) -> a -> b
$ \(Tree -> Tree
ctx, DrawAttributes
_attr, Tree
node) -> do
Scene s (Sprite s) -> Scene s ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Scene s (Sprite s) -> Scene s ())
-> Scene s (Sprite s) -> Scene s ()
forall a b. (a -> b) -> a -> b
$ Scene s (Sprite s) -> Scene s (Sprite s)
forall s a. Scene s a -> Scene s a
fork (Scene s (Sprite s) -> Scene s (Sprite s))
-> Scene s (Sprite s) -> Scene s (Sprite s)
forall a b. (a -> b) -> a -> b
$ Sync -> Animation -> Scene s (Sprite s)
forall s. Sync -> Animation -> Scene s (Sprite s)
newSpriteA' Sync
SyncFreeze (Tree -> Animation
fn (Tree -> Animation) -> Tree -> Animation
forall a b. (a -> b) -> a -> b
$ Tree -> Tree
ctx Tree
node)
Double -> Scene s ()
forall s. Double -> Scene s ()
wait Double
staggerDelay
oDraw :: SVG -> Animation
oDraw :: Tree -> Animation
oDraw = (Tree -> Animation) -> Tree -> Animation
oStagger ((Tree -> Animation) -> Tree -> Animation)
-> (Tree -> Animation) -> Tree -> Animation
forall a b. (a -> b) -> a -> b
$ \Tree
svg -> (forall s. Scene s ()) -> Animation
forall a. (forall s. Scene s a) -> Animation
scene ((forall s. Scene s ()) -> Animation)
-> (forall s. Scene s ()) -> Animation
forall a b. (a -> b) -> a -> b
$
[(Tree -> Tree, DrawAttributes, Tree)]
-> ((Tree -> Tree, DrawAttributes, Tree) -> Scene s (Sprite s))
-> Scene s ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (Tree -> [(Tree -> Tree, DrawAttributes, Tree)]
svgGlyphs (Tree -> [(Tree -> Tree, DrawAttributes, Tree)])
-> Tree -> [(Tree -> Tree, DrawAttributes, Tree)]
forall a b. (a -> b) -> a -> b
$ Tree -> Tree
pathify Tree
svg) (((Tree -> Tree, DrawAttributes, Tree) -> Scene s (Sprite s))
-> Scene s ())
-> ((Tree -> Tree, DrawAttributes, Tree) -> Scene s (Sprite s))
-> Scene s ()
forall a b. (a -> b) -> a -> b
$ \(Tree -> Tree
ctx, DrawAttributes
attr, Tree
node) -> do
let sWidth :: Double
sWidth =
case Int -> Number -> Number
toUserUnit Int
defaultDPI (Number -> Number) -> Maybe Number -> Maybe Number
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Last Number -> Maybe Number
forall a. Last a -> Maybe a
getLast (DrawAttributes
attr DrawAttributes
-> Getting (Last Number) DrawAttributes (Last Number)
-> Last Number
forall s a. s -> Getting a s a -> a
^. Getting (Last Number) DrawAttributes (Last Number)
forall c. HasDrawAttributes c => Lens' c (Last Number)
strokeWidth) of
Just (Num Double
d) -> Double -> Signal
forall a. Ord a => a -> a -> a
max Double
defaultStrokeWidth Double
d
Maybe Number
_ -> Double
defaultStrokeWidth
Animation -> Scene s ()
forall s. Animation -> Scene s ()
play (Animation -> Scene s ()) -> Animation -> Scene s ()
forall a b. (a -> b) -> a -> b
$
(Tree -> Tree) -> Animation -> Animation
mapA Tree -> Tree
ctx (Animation -> Animation) -> Animation -> Animation
forall a b. (a -> b) -> a -> b
$
(Double -> Double -> Tree -> Tree) -> Animation -> Animation
applyE (Double
-> (Double -> Double -> Tree -> Tree)
-> Double
-> Double
-> Tree
-> Tree
overEnding Double
fillDur ((Double -> Double -> Tree -> Tree)
-> Double -> Double -> Tree -> Tree)
-> (Double -> Double -> Tree -> Tree)
-> Double
-> Double
-> Tree
-> Tree
forall a b. (a -> b) -> a -> b
$ Double -> Double -> Double -> Tree -> Tree
fadeLineOutE Double
sWidth) (Animation -> Animation) -> Animation -> Animation
forall a b. (a -> b) -> a -> b
$
(Double -> Tree) -> Animation
animate ((Double -> Tree) -> Animation) -> (Double -> Tree) -> Animation
forall a b. (a -> b) -> a -> b
$ \Double
t ->
Double -> Tree -> Tree
withStrokeWidth Double
sWidth (Tree -> Tree) -> Tree -> Tree
forall a b. (a -> b) -> a -> b
$
[Tree] -> Tree
mkGroup
[Double -> Tree -> Tree
withFillOpacity Double
0 (Tree -> Tree) -> Tree -> Tree
forall a b. (a -> b) -> a -> b
$ Double -> Tree -> Tree
partialSvg Double
t Tree
node]
Double -> Scene s ()
forall s. Double -> Scene s ()
wait (- Double
fillDur)
Sync -> Animation -> Scene s (Sprite s)
forall s. Sync -> Animation -> Scene s (Sprite s)
newSpriteA' Sync
SyncFreeze (Animation -> Scene s (Sprite s))
-> Animation -> Scene s (Sprite s)
forall a b. (a -> b) -> a -> b
$
Double -> (Double -> Tree) -> Animation
mkAnimation Double
fillDur ((Double -> Tree) -> Animation) -> (Double -> Tree) -> Animation
forall a b. (a -> b) -> a -> b
$ \Double
t ->
Double -> Tree -> Tree
withGroupOpacity Double
t (Tree -> Tree) -> Tree -> Tree
forall a b. (a -> b) -> a -> b
$
[Tree] -> Tree
mkGroup [Tree -> Tree
ctx Tree
node]
where
fillDur :: Double
fillDur = Double
0.3
_oBalloon :: SVG -> Animation
_oBalloon :: Tree -> Animation
_oBalloon = (Double -> Tree) -> Animation
animate ((Double -> Tree) -> Animation)
-> (Tree -> Double -> Tree) -> Tree -> Animation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tree -> Double -> Tree
balloon
oTransform :: Object s a -> Object s b -> Duration -> Scene s ()
oTransform :: Object s a -> Object s b -> Double -> Scene s ()
oTransform Object s a
src Object s b
dst Double
d = do
Tree
srcSvg <- Object s a -> Getting Tree (ObjectData a) Tree -> Scene s Tree
forall s a b. Object s a -> Getting b (ObjectData a) b -> Scene s b
oRead Object s a
src Getting Tree (ObjectData a) Tree
forall a. Getter (ObjectData a) Tree
oSVG
Tree -> Tree
srcCtx <- Object s a
-> Getting (Tree -> Tree) (ObjectData a) (Tree -> Tree)
-> Scene s (Tree -> Tree)
forall s a b. Object s a -> Getting b (ObjectData a) b -> Scene s b
oRead Object s a
src Getting (Tree -> Tree) (ObjectData a) (Tree -> Tree)
forall a. Lens' (ObjectData a) (Tree -> Tree)
oContext
Signal
srcEase <- Object s a
-> Getting Signal (ObjectData a) Signal -> Scene s Signal
forall s a b. Object s a -> Getting b (ObjectData a) b -> Scene s b
oRead Object s a
src Getting Signal (ObjectData a) Signal
forall a. Lens' (ObjectData a) Signal
oEasing
V2 Double
srcLoc <- Object s a
-> Getting (V2 Double) (ObjectData a) (V2 Double)
-> Scene s (V2 Double)
forall s a b. Object s a -> Getting b (ObjectData a) b -> Scene s b
oRead Object s a
src Getting (V2 Double) (ObjectData a) (V2 Double)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate
Object s a -> (ObjectData a -> ObjectData a) -> Scene s ()
forall s a.
Object s a -> (ObjectData a -> ObjectData a) -> Scene s ()
oModify Object s a
src ((ObjectData a -> ObjectData a) -> Scene s ())
-> (ObjectData a -> ObjectData a) -> Scene s ()
forall a b. (a -> b) -> a -> b
$ (Bool -> Identity Bool) -> ObjectData a -> Identity (ObjectData a)
forall a. Lens' (ObjectData a) Bool
oShown ((Bool -> Identity Bool)
-> ObjectData a -> Identity (ObjectData a))
-> Bool -> ObjectData a -> ObjectData a
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
False
Tree
dstSvg <- Object s b -> Getting Tree (ObjectData b) Tree -> Scene s Tree
forall s a b. Object s a -> Getting b (ObjectData a) b -> Scene s b
oRead Object s b
dst Getting Tree (ObjectData b) Tree
forall a. Getter (ObjectData a) Tree
oSVG
Tree -> Tree
dstCtx <- Object s b
-> Getting (Tree -> Tree) (ObjectData b) (Tree -> Tree)
-> Scene s (Tree -> Tree)
forall s a b. Object s a -> Getting b (ObjectData a) b -> Scene s b
oRead Object s b
dst Getting (Tree -> Tree) (ObjectData b) (Tree -> Tree)
forall a. Lens' (ObjectData a) (Tree -> Tree)
oContext
V2 Double
dstLoc <- Object s b
-> Getting (V2 Double) (ObjectData b) (V2 Double)
-> Scene s (V2 Double)
forall s a b. Object s a -> Getting b (ObjectData a) b -> Scene s b
oRead Object s b
dst Getting (V2 Double) (ObjectData b) (V2 Double)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate
Object s Morph
m <- Morph -> Scene s (Object s Morph)
forall a s. Renderable a => a -> Scene s (Object s a)
newObject (Morph -> Scene s (Object s Morph))
-> Morph -> Scene s (Object s Morph)
forall a b. (a -> b) -> a -> b
$ Double -> Tree -> Tree -> Morph
Morph Double
0 (Tree -> Tree
srcCtx Tree
srcSvg) (Tree -> Tree
dstCtx Tree
dstSvg)
Object s Morph -> State (ObjectData Morph) () -> Scene s ()
forall s a b. Object s a -> State (ObjectData a) b -> Scene s ()
oModifyS Object s Morph
m (State (ObjectData Morph) () -> Scene s ())
-> State (ObjectData Morph) () -> Scene s ()
forall a b. (a -> b) -> a -> b
$ do
(Bool -> Identity Bool)
-> ObjectData Morph -> Identity (ObjectData Morph)
forall a. Lens' (ObjectData a) Bool
oShown ((Bool -> Identity Bool)
-> ObjectData Morph -> Identity (ObjectData Morph))
-> Bool -> State (ObjectData Morph) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bool
True
(Signal -> Identity Signal)
-> ObjectData Morph -> Identity (ObjectData Morph)
forall a. Lens' (ObjectData a) Signal
oEasing ((Signal -> Identity Signal)
-> ObjectData Morph -> Identity (ObjectData Morph))
-> Signal -> State (ObjectData Morph) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Signal
srcEase
(V2 Double -> Identity (V2 Double))
-> ObjectData Morph -> Identity (ObjectData Morph)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate ((V2 Double -> Identity (V2 Double))
-> ObjectData Morph -> Identity (ObjectData Morph))
-> V2 Double -> State (ObjectData Morph) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= V2 Double
srcLoc
Scene s () -> Scene s ()
forall s a. Scene s a -> Scene s a
fork (Scene s () -> Scene s ()) -> Scene s () -> Scene s ()
forall a b. (a -> b) -> a -> b
$ Object s Morph
-> Double
-> (Double -> ObjectData Morph -> ObjectData Morph)
-> Scene s ()
forall s a.
Object s a
-> Double -> (Double -> ObjectData a -> ObjectData a) -> Scene s ()
oTween Object s Morph
m Double
d ((Double -> ObjectData Morph -> ObjectData Morph) -> Scene s ())
-> (Double -> ObjectData Morph -> ObjectData Morph) -> Scene s ()
forall a b. (a -> b) -> a -> b
$ \Double
t -> (V2 Double -> Identity (V2 Double))
-> ObjectData Morph -> Identity (ObjectData Morph)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate ((V2 Double -> Identity (V2 Double))
-> ObjectData Morph -> Identity (ObjectData Morph))
-> (V2 Double -> V2 Double) -> ObjectData Morph -> ObjectData Morph
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Double -> V2 Double -> V2 Double -> V2 Double
forall (f :: * -> *) a.
(Additive f, Num a) =>
a -> f a -> f a -> f a
lerp Double
t V2 Double
dstLoc
Object s Morph
-> Double -> (Double -> Morph -> Morph) -> Scene s ()
forall a s.
Renderable a =>
Object s a -> Double -> (Double -> a -> a) -> Scene s ()
oTweenV Object s Morph
m Double
d ((Double -> Morph -> Morph) -> Scene s ())
-> (Double -> Morph -> Morph) -> Scene s ()
forall a b. (a -> b) -> a -> b
$ \Double
t -> (Double -> Identity Double) -> Morph -> Identity Morph
Lens' Morph Double
morphDelta ((Double -> Identity Double) -> Morph -> Identity Morph)
-> Double -> Morph -> Morph
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
t
Object s Morph
-> (ObjectData Morph -> ObjectData Morph) -> Scene s ()
forall s a.
Object s a -> (ObjectData a -> ObjectData a) -> Scene s ()
oModify Object s Morph
m ((ObjectData Morph -> ObjectData Morph) -> Scene s ())
-> (ObjectData Morph -> ObjectData Morph) -> Scene s ()
forall a b. (a -> b) -> a -> b
$ (Bool -> Identity Bool)
-> ObjectData Morph -> Identity (ObjectData Morph)
forall a. Lens' (ObjectData a) Bool
oShown ((Bool -> Identity Bool)
-> ObjectData Morph -> Identity (ObjectData Morph))
-> Bool -> ObjectData Morph -> ObjectData Morph
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
False
Object s b -> (ObjectData b -> ObjectData b) -> Scene s ()
forall s a.
Object s a -> (ObjectData a -> ObjectData a) -> Scene s ()
oModify Object s b
dst ((ObjectData b -> ObjectData b) -> Scene s ())
-> (ObjectData b -> ObjectData b) -> Scene s ()
forall a b. (a -> b) -> a -> b
$ (Bool -> Identity Bool) -> ObjectData b -> Identity (ObjectData b)
forall a. Lens' (ObjectData a) Bool
oShown ((Bool -> Identity Bool)
-> ObjectData b -> Identity (ObjectData b))
-> Bool -> ObjectData b -> ObjectData b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
True
newtype Circle = Circle {Circle -> Double
_circleRadius :: Double}
circleRadius :: Lens' Circle Double
circleRadius :: (Double -> f Double) -> Circle -> f Circle
circleRadius = (Circle -> Double)
-> (Double -> Circle) -> Iso Circle Circle Double Double
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Circle -> Double
_circleRadius Double -> Circle
Circle
instance Renderable Circle where
toSVG :: Circle -> Tree
toSVG (Circle Double
r) = Double -> Tree
mkCircle Double
r
data Rectangle = Rectangle {Rectangle -> Double
_rectWidth :: Double, Rectangle -> Double
_rectHeight :: Double}
rectWidth :: Lens' Rectangle Double
rectWidth :: (Double -> f Double) -> Rectangle -> f Rectangle
rectWidth = (Rectangle -> Double)
-> (Rectangle -> Double -> Rectangle)
-> Lens Rectangle Rectangle Double Double
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Rectangle -> Double
_rectWidth ((Rectangle -> Double -> Rectangle)
-> Lens Rectangle Rectangle Double Double)
-> (Rectangle -> Double -> Rectangle)
-> Lens Rectangle Rectangle Double Double
forall a b. (a -> b) -> a -> b
$ \Rectangle
obj Double
val -> Rectangle
obj {_rectWidth :: Double
_rectWidth = Double
val}
rectHeight :: Lens' Rectangle Double
rectHeight :: (Double -> f Double) -> Rectangle -> f Rectangle
rectHeight = (Rectangle -> Double)
-> (Rectangle -> Double -> Rectangle)
-> Lens Rectangle Rectangle Double Double
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Rectangle -> Double
_rectHeight ((Rectangle -> Double -> Rectangle)
-> Lens Rectangle Rectangle Double Double)
-> (Rectangle -> Double -> Rectangle)
-> Lens Rectangle Rectangle Double Double
forall a b. (a -> b) -> a -> b
$ \Rectangle
obj Double
val -> Rectangle
obj {_rectHeight :: Double
_rectHeight = Double
val}
instance Renderable Rectangle where
toSVG :: Rectangle -> Tree
toSVG (Rectangle Double
w Double
h) = Double -> Double -> Tree
mkRect Double
w Double
h
data Morph = Morph {Morph -> Double
_morphDelta :: Double, Morph -> Tree
_morphSrc :: SVG, Morph -> Tree
_morphDst :: SVG}
morphDelta :: Lens' Morph Double
morphDelta :: (Double -> f Double) -> Morph -> f Morph
morphDelta = (Morph -> Double)
-> (Morph -> Double -> Morph) -> Lens' Morph Double
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Morph -> Double
_morphDelta ((Morph -> Double -> Morph) -> Lens' Morph Double)
-> (Morph -> Double -> Morph) -> Lens' Morph Double
forall a b. (a -> b) -> a -> b
$ \Morph
obj Double
val -> Morph
obj {_morphDelta :: Double
_morphDelta = Double
val}
morphSrc :: Lens' Morph SVG
morphSrc :: (Tree -> f Tree) -> Morph -> f Morph
morphSrc = (Morph -> Tree)
-> (Morph -> Tree -> Morph) -> Lens Morph Morph Tree Tree
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Morph -> Tree
_morphSrc ((Morph -> Tree -> Morph) -> Lens Morph Morph Tree Tree)
-> (Morph -> Tree -> Morph) -> Lens Morph Morph Tree Tree
forall a b. (a -> b) -> a -> b
$ \Morph
obj Tree
val -> Morph
obj {_morphSrc :: Tree
_morphSrc = Tree
val}
morphDst :: Lens' Morph SVG
morphDst :: (Tree -> f Tree) -> Morph -> f Morph
morphDst = (Morph -> Tree)
-> (Morph -> Tree -> Morph) -> Lens Morph Morph Tree Tree
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Morph -> Tree
_morphDst ((Morph -> Tree -> Morph) -> Lens Morph Morph Tree Tree)
-> (Morph -> Tree -> Morph) -> Lens Morph Morph Tree Tree
forall a b. (a -> b) -> a -> b
$ \Morph
obj Tree
val -> Morph
obj {_morphDst :: Tree
_morphDst = Tree
val}
instance Renderable Morph where
toSVG :: Morph -> Tree
toSVG (Morph Double
t Tree
src Tree
dst) = Morph -> Tree -> Tree -> Double -> Tree
morph Morph
linear Tree
src Tree
dst Double
t
data Camera = Camera
instance Renderable Camera where
toSVG :: Camera -> Tree
toSVG Camera
Camera = Tree
None
cameraAttach :: Object s Camera -> Object s a -> Scene s ()
cameraAttach :: Object s Camera -> Object s a -> Scene s ()
cameraAttach Object s Camera
cam Object s a
obj =
Sprite s -> Frame s ((Tree, Int) -> (Tree, Int)) -> Scene s ()
forall s.
Sprite s -> Frame s ((Tree, Int) -> (Tree, Int)) -> Scene s ()
spriteModify (Object s a -> Sprite s
forall s a. Object s a -> Sprite s
objectSprite Object s a
obj) (Frame s ((Tree, Int) -> (Tree, Int)) -> Scene s ())
-> Frame s ((Tree, Int) -> (Tree, Int)) -> Scene s ()
forall a b. (a -> b) -> a -> b
$ do
ObjectData Camera
camData <- Var s (ObjectData Camera) -> Frame s (ObjectData Camera)
forall s a. Var s a -> Frame s a
unVar (Object s Camera -> Var s (ObjectData Camera)
forall s a. Object s a -> Var s (ObjectData a)
objectData Object s Camera
cam)
return $ \(Tree
svg, Int
zindex) ->
let V2 Double
x Double
y = ObjectData Camera
camData ObjectData Camera
-> Getting (V2 Double) (ObjectData Camera) (V2 Double) -> V2 Double
forall s a. s -> Getting a s a -> a
^. Getting (V2 Double) (ObjectData Camera) (V2 Double)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate
ctx :: Tree -> Tree
ctx =
Double -> Double -> Tree -> Tree
translate (- Double
x) (- Double
y)
(Tree -> Tree) -> (Tree -> Tree) -> Tree -> Tree
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Double -> Tree -> Tree) -> V2 Double -> Tree -> Tree
forall a b. (a -> a -> b) -> V2 a -> b
uncurryV2 Double -> Double -> Tree -> Tree
translate (ObjectData Camera
camData ObjectData Camera
-> Getting (V2 Double) (ObjectData Camera) (V2 Double) -> V2 Double
forall s a. s -> Getting a s a -> a
^. Getting (V2 Double) (ObjectData Camera) (V2 Double)
forall a. Lens' (ObjectData a) (V2 Double)
oScaleOrigin)
(Tree -> Tree) -> (Tree -> Tree) -> Tree -> Tree
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Tree -> Tree
scale (ObjectData Camera
camData ObjectData Camera
-> Getting Double (ObjectData Camera) Double -> Double
forall s a. s -> Getting a s a -> a
^. Getting Double (ObjectData Camera) Double
forall a. Lens' (ObjectData a) Double
oScale)
(Tree -> Tree) -> (Tree -> Tree) -> Tree -> Tree
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Double -> Tree -> Tree) -> V2 Double -> Tree -> Tree
forall a b. (a -> a -> b) -> V2 a -> b
uncurryV2 Double -> Double -> Tree -> Tree
translate (V2 Double -> V2 Double
forall a. Num a => a -> a
negate (V2 Double -> V2 Double) -> V2 Double -> V2 Double
forall a b. (a -> b) -> a -> b
$ ObjectData Camera
camData ObjectData Camera
-> Getting (V2 Double) (ObjectData Camera) (V2 Double) -> V2 Double
forall s a. s -> Getting a s a -> a
^. Getting (V2 Double) (ObjectData Camera) (V2 Double)
forall a. Lens' (ObjectData a) (V2 Double)
oScaleOrigin)
in (Tree -> Tree
ctx Tree
svg, Int
zindex)
cameraFocus :: Object s Camera -> V2 Double -> Scene s ()
cameraFocus :: Object s Camera -> V2 Double -> Scene s ()
cameraFocus Object s Camera
cam V2 Double
new = do
V2 Double
origin <- Object s Camera
-> Getting (V2 Double) (ObjectData Camera) (V2 Double)
-> Scene s (V2 Double)
forall s a b. Object s a -> Getting b (ObjectData a) b -> Scene s b
oRead Object s Camera
cam Getting (V2 Double) (ObjectData Camera) (V2 Double)
forall a. Lens' (ObjectData a) (V2 Double)
oScaleOrigin
V2 Double
t <- Object s Camera
-> Getting (V2 Double) (ObjectData Camera) (V2 Double)
-> Scene s (V2 Double)
forall s a b. Object s a -> Getting b (ObjectData a) b -> Scene s b
oRead Object s Camera
cam Getting (V2 Double) (ObjectData Camera) (V2 Double)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate
Double
s <- Object s Camera
-> Getting Double (ObjectData Camera) Double -> Scene s Double
forall s a b. Object s a -> Getting b (ObjectData a) b -> Scene s b
oRead Object s Camera
cam Getting Double (ObjectData Camera) Double
forall a. Lens' (ObjectData a) Double
oScale
let newLocation :: V2 Double
newLocation = V2 Double
new V2 Double -> V2 Double -> V2 Double
forall a. Num a => a -> a -> a
- ((V2 Double
new V2 Double -> V2 Double -> V2 Double
forall a. Num a => a -> a -> a
- V2 Double
origin) V2 Double -> Double -> V2 Double
forall (f :: * -> *) a. (Functor f, Num a) => f a -> a -> f a
^* Double
s V2 Double -> V2 Double -> V2 Double
forall a. Num a => a -> a -> a
+ V2 Double
origin V2 Double -> V2 Double -> V2 Double
forall a. Num a => a -> a -> a
- V2 Double
t)
Object s Camera -> State (ObjectData Camera) () -> Scene s ()
forall s a b. Object s a -> State (ObjectData a) b -> Scene s ()
oModifyS Object s Camera
cam (State (ObjectData Camera) () -> Scene s ())
-> State (ObjectData Camera) () -> Scene s ()
forall a b. (a -> b) -> a -> b
$ do
(V2 Double -> Identity (V2 Double))
-> ObjectData Camera -> Identity (ObjectData Camera)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate ((V2 Double -> Identity (V2 Double))
-> ObjectData Camera -> Identity (ObjectData Camera))
-> V2 Double -> State (ObjectData Camera) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= V2 Double
newLocation
(V2 Double -> Identity (V2 Double))
-> ObjectData Camera -> Identity (ObjectData Camera)
forall a. Lens' (ObjectData a) (V2 Double)
oScaleOrigin ((V2 Double -> Identity (V2 Double))
-> ObjectData Camera -> Identity (ObjectData Camera))
-> V2 Double -> State (ObjectData Camera) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= V2 Double
new
cameraSetZoom :: Object s Camera -> Double -> Scene s ()
cameraSetZoom :: Object s Camera -> Double -> Scene s ()
cameraSetZoom Object s Camera
cam Double
s =
Object s Camera -> State (ObjectData Camera) () -> Scene s ()
forall s a b. Object s a -> State (ObjectData a) b -> Scene s ()
oModifyS Object s Camera
cam (State (ObjectData Camera) () -> Scene s ())
-> State (ObjectData Camera) () -> Scene s ()
forall a b. (a -> b) -> a -> b
$
(Double -> Identity Double)
-> ObjectData Camera -> Identity (ObjectData Camera)
forall a. Lens' (ObjectData a) Double
oScale ((Double -> Identity Double)
-> ObjectData Camera -> Identity (ObjectData Camera))
-> Double -> State (ObjectData Camera) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Double
s
cameraZoom :: Object s Camera -> Duration -> Double -> Scene s ()
cameraZoom :: Object s Camera -> Double -> Double -> Scene s ()
cameraZoom Object s Camera
cam Double
d Double
s =
Object s Camera
-> Double -> (Double -> State (ObjectData Camera) ()) -> Scene s ()
forall s a b.
Object s a
-> Double -> (Double -> State (ObjectData a) b) -> Scene s ()
oTweenS Object s Camera
cam Double
d ((Double -> State (ObjectData Camera) ()) -> Scene s ())
-> (Double -> State (ObjectData Camera) ()) -> Scene s ()
forall a b. (a -> b) -> a -> b
$ \Double
t ->
(Double -> Identity Double)
-> ObjectData Camera -> Identity (ObjectData Camera)
forall a. Lens' (ObjectData a) Double
oScale ((Double -> Identity Double)
-> ObjectData Camera -> Identity (ObjectData Camera))
-> Signal -> State (ObjectData Camera) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= \Double
v -> Double -> Double -> Signal
fromToS Double
v Double
s Double
t
cameraSetPan :: Object s Camera -> V2 Double -> Scene s ()
cameraSetPan :: Object s Camera -> V2 Double -> Scene s ()
cameraSetPan Object s Camera
cam V2 Double
location =
Object s Camera -> State (ObjectData Camera) () -> Scene s ()
forall s a b. Object s a -> State (ObjectData a) b -> Scene s ()
oModifyS Object s Camera
cam (State (ObjectData Camera) () -> Scene s ())
-> State (ObjectData Camera) () -> Scene s ()
forall a b. (a -> b) -> a -> b
$
(V2 Double -> Identity (V2 Double))
-> ObjectData Camera -> Identity (ObjectData Camera)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate ((V2 Double -> Identity (V2 Double))
-> ObjectData Camera -> Identity (ObjectData Camera))
-> V2 Double -> State (ObjectData Camera) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= V2 Double
location
cameraPan :: Object s Camera -> Duration -> V2 Double -> Scene s ()
cameraPan :: Object s Camera -> Double -> V2 Double -> Scene s ()
cameraPan Object s Camera
cam Double
d V2 Double
pos =
Object s Camera
-> Double -> (Double -> State (ObjectData Camera) ()) -> Scene s ()
forall s a b.
Object s a
-> Double -> (Double -> State (ObjectData a) b) -> Scene s ()
oTweenS Object s Camera
cam Double
d ((Double -> State (ObjectData Camera) ()) -> Scene s ())
-> (Double -> State (ObjectData Camera) ()) -> Scene s ()
forall a b. (a -> b) -> a -> b
$ \Double
t ->
(V2 Double -> Identity (V2 Double))
-> ObjectData Camera -> Identity (ObjectData Camera)
forall a. Lens' (ObjectData a) (V2 Double)
oTranslate ((V2 Double -> Identity (V2 Double))
-> ObjectData Camera -> Identity (ObjectData Camera))
-> (V2 Double -> V2 Double) -> State (ObjectData Camera) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= Double -> V2 Double -> V2 Double -> V2 Double
forall (f :: * -> *) a.
(Additive f, Num a) =>
a -> f a -> f a -> f a
lerp Double
t V2 Double
pos