module Reanimate.Animation
  ( Duration
  , Time
  , SVG
  , Animation
  
  , mkAnimation
  , unsafeMkAnimation
  , animate
  , staticFrame
  , pause
  
  , duration
  , frameAt
  
  , seqA
  , andThen
  , parA
  , parLoopA
  , parDropA
  
  , setDuration
  , adjustDuration
  , mapA
  , takeA
  , dropA
  , lastA
  , pauseAtEnd
  , pauseAtBeginning
  , pauseAround
  , repeatA
  , reverseA
  , playThenReverseA
  , signalA
  , freezeAtPercentage
  , addStatic
  
  , getAnimationFrame
  , Sync(..)
  
  , renderTree
  , renderSvg
  ) where
import           Data.Fixed                 (mod')
import           Graphics.SvgTree
import           Graphics.SvgTree.Printer   (ppDocument)
import           Reanimate.Constants        (defaultStrokeWidth)
import           Reanimate.Ease             (Signal, reverseS)
import           Reanimate.Svg.Constructors (mkGroup, scaleXY, withStrokeWidth)
import           Text.XML.Light.Output      (ppElement)
type Duration = Double
type Time = Double
type SVG = Tree
data Animation = Animation Duration (Time -> SVG)
mkAnimation :: Duration -> (Time -> SVG) -> Animation
mkAnimation :: Duration -> (Duration -> SVG) -> Animation
mkAnimation Duration
d Duration -> SVG
f
  | Duration
d Duration -> Duration -> Bool
forall a. Ord a => a -> a -> Bool
> Duration
0     = Duration -> (Duration -> SVG) -> Animation
unsafeMkAnimation Duration
d Duration -> SVG
f
  | Bool
otherwise = [Char] -> Animation
forall a. HasCallStack => [Char] -> a
error ([Char] -> Animation) -> [Char] -> Animation
forall a b. (a -> b) -> a -> b
$ [Char]
"Animation duration (" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Duration -> [Char]
forall a. Show a => a -> [Char]
show Duration
d [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
") is not positive."
unsafeMkAnimation :: Duration -> (Time -> SVG) -> Animation
unsafeMkAnimation :: Duration -> (Duration -> SVG) -> Animation
unsafeMkAnimation = Duration -> (Duration -> SVG) -> Animation
Animation
animate :: (Time -> SVG) -> Animation
animate :: (Duration -> SVG) -> Animation
animate = Duration -> (Duration -> SVG) -> Animation
Animation Duration
1
staticFrame :: Duration -> SVG -> Animation
staticFrame :: Duration -> SVG -> Animation
staticFrame Duration
d SVG
svg = Duration -> (Duration -> SVG) -> Animation
mkAnimation Duration
d (SVG -> Duration -> SVG
forall a b. a -> b -> a
const SVG
svg)
duration :: Animation -> Duration
duration :: Animation -> Duration
duration (Animation Duration
d Duration -> SVG
_) = Duration
d
seqA :: Animation -> Animation -> Animation
seqA :: Animation -> Animation -> Animation
seqA (Animation Duration
d1 Duration -> SVG
f1) (Animation Duration
d2 Duration -> SVG
f2) =
  Duration -> (Duration -> SVG) -> Animation
Animation Duration
totalD ((Duration -> SVG) -> Animation) -> (Duration -> SVG) -> Animation
forall a b. (a -> b) -> a -> b
$ \Duration
t ->
    if Duration
t Duration -> Duration -> Bool
forall a. Ord a => a -> a -> Bool
< Duration
d1Duration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
totalD
      then Duration -> SVG
f1 (Duration
t Duration -> Duration -> Duration
forall a. Num a => a -> a -> a
* Duration
totalDDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d1)
      else Duration -> SVG
f2 ((Duration
tDuration -> Duration -> Duration
forall a. Num a => a -> a -> a
-Duration
d1Duration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
totalD) Duration -> Duration -> Duration
forall a. Num a => a -> a -> a
* Duration
totalDDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d2)
  where
    totalD :: Duration
totalD = Duration
d1Duration -> Duration -> Duration
forall a. Num a => a -> a -> a
+Duration
d2
parA :: Animation -> Animation -> Animation
parA :: Animation -> Animation -> Animation
parA (Animation Duration
d1 Duration -> SVG
f1) (Animation Duration
d2 Duration -> SVG
f2) =
  Duration -> (Duration -> SVG) -> Animation
Animation (Duration -> Duration -> Duration
forall a. Ord a => a -> a -> a
max Duration
d1 Duration
d2) ((Duration -> SVG) -> Animation) -> (Duration -> SVG) -> Animation
forall a b. (a -> b) -> a -> b
$ \Duration
t ->
    let t1 :: Duration
t1 = Duration
t Duration -> Duration -> Duration
forall a. Num a => a -> a -> a
* Duration
totalDDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d1
        t2 :: Duration
t2 = Duration
t Duration -> Duration -> Duration
forall a. Num a => a -> a -> a
* Duration
totalDDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d2 in
    [SVG] -> SVG
mkGroup
    [ Duration -> SVG
f1 (Duration -> Duration -> Duration
forall a. Ord a => a -> a -> a
min Duration
1 Duration
t1)
    , Duration -> SVG
f2 (Duration -> Duration -> Duration
forall a. Ord a => a -> a -> a
min Duration
1 Duration
t2) ]
  where
    totalD :: Duration
totalD = Duration -> Duration -> Duration
forall a. Ord a => a -> a -> a
max Duration
d1 Duration
d2
parLoopA :: Animation -> Animation -> Animation
parLoopA :: Animation -> Animation -> Animation
parLoopA (Animation Duration
d1 Duration -> SVG
f1) (Animation Duration
d2 Duration -> SVG
f2) =
  Duration -> (Duration -> SVG) -> Animation
Animation Duration
totalD ((Duration -> SVG) -> Animation) -> (Duration -> SVG) -> Animation
forall a b. (a -> b) -> a -> b
$ \Duration
t ->
    let t1 :: Duration
t1 = Duration
t Duration -> Duration -> Duration
forall a. Num a => a -> a -> a
* Duration
totalDDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d1
        t2 :: Duration
t2 = Duration
t Duration -> Duration -> Duration
forall a. Num a => a -> a -> a
* Duration
totalDDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d2 in
    [SVG] -> SVG
mkGroup
    [ Duration -> SVG
f1 (Duration
t1 Duration -> Duration -> Duration
forall a. Real a => a -> a -> a
`mod'` Duration
1)
    , Duration -> SVG
f2 (Duration
t2 Duration -> Duration -> Duration
forall a. Real a => a -> a -> a
`mod'` Duration
1) ]
  where
    totalD :: Duration
totalD = Duration -> Duration -> Duration
forall a. Ord a => a -> a -> a
max Duration
d1 Duration
d2
parDropA :: Animation -> Animation -> Animation
parDropA :: Animation -> Animation -> Animation
parDropA (Animation Duration
d1 Duration -> SVG
f1) (Animation Duration
d2 Duration -> SVG
f2) =
  Duration -> (Duration -> SVG) -> Animation
Animation Duration
totalD ((Duration -> SVG) -> Animation) -> (Duration -> SVG) -> Animation
forall a b. (a -> b) -> a -> b
$ \Duration
t ->
    let t1 :: Duration
t1 = Duration
t Duration -> Duration -> Duration
forall a. Num a => a -> a -> a
* Duration
totalDDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d1
        t2 :: Duration
t2 = Duration
t Duration -> Duration -> Duration
forall a. Num a => a -> a -> a
* Duration
totalDDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d2 in
    [SVG] -> SVG
mkGroup
    [ if Duration
t1Duration -> Duration -> Bool
forall a. Ord a => a -> a -> Bool
>Duration
1 then SVG
None else Duration -> SVG
f1 Duration
t1
    , if Duration
t2Duration -> Duration -> Bool
forall a. Ord a => a -> a -> Bool
>Duration
1 then SVG
None else Duration -> SVG
f2 Duration
t2 ]
  where
    totalD :: Duration
totalD = Duration -> Duration -> Duration
forall a. Ord a => a -> a -> a
max Duration
d1 Duration
d2
pause :: Duration -> Animation
pause :: Duration -> Animation
pause Duration
d = Duration -> (Duration -> SVG) -> Animation
mkAnimation Duration
d (SVG -> Duration -> SVG
forall a b. a -> b -> a
const SVG
None)
andThen :: Animation -> Animation -> Animation
andThen :: Animation -> Animation -> Animation
andThen Animation
a Animation
b = Animation
a Animation -> Animation -> Animation
`parA` (Duration -> Animation
pause (Animation -> Duration
duration Animation
a) Animation -> Animation -> Animation
`seqA` Animation
b)
frameAt :: Time -> Animation -> SVG
frameAt :: Duration -> Animation -> SVG
frameAt Duration
t (Animation Duration
d Duration -> SVG
f) = Duration -> SVG
f Duration
t'
  where
    t' :: Duration
t' = Duration -> Duration -> Duration -> Duration
clamp Duration
0 Duration
1 (Duration
tDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d)
renderTree :: SVG -> String
renderTree :: SVG -> [Char]
renderTree SVG
t = [Char] -> (Element -> [Char]) -> Maybe Element -> [Char]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Char]
"" Element -> [Char]
ppElement (Maybe Element -> [Char]) -> Maybe Element -> [Char]
forall a b. (a -> b) -> a -> b
$ SVG -> Maybe Element
xmlOfTree SVG
t
renderSvg :: Maybe Number 
                          
                          
                          
          -> Maybe Number 
                          
          -> SVG          
          -> String       
renderSvg :: Maybe Number -> Maybe Number -> SVG -> [Char]
renderSvg Maybe Number
w Maybe Number
h SVG
t = Document -> [Char]
ppDocument Document
doc
  where
    width :: Duration
width = Duration
16
    height :: Duration
height = Duration
9
    doc :: Document
doc = Document :: Maybe (Duration, Duration, Duration, Duration)
-> Maybe Number
-> Maybe Number
-> [SVG]
-> [Char]
-> [Char]
-> PreserveAspectRatio
-> Document
Document
      { _documentViewBox :: Maybe (Duration, Duration, Duration, Duration)
_documentViewBox = (Duration, Duration, Duration, Duration)
-> Maybe (Duration, Duration, Duration, Duration)
forall a. a -> Maybe a
Just (-Duration
widthDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
2, -Duration
heightDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
2, Duration
width, Duration
height)
      , _documentWidth :: Maybe Number
_documentWidth = Maybe Number
w
      , _documentHeight :: Maybe Number
_documentHeight = Maybe Number
h
      , _documentElements :: [SVG]
_documentElements = [Duration -> SVG -> SVG
withStrokeWidth Duration
defaultStrokeWidth (SVG -> SVG) -> SVG -> SVG
forall a b. (a -> b) -> a -> b
$ Duration -> Duration -> SVG -> SVG
scaleXY Duration
1 (-Duration
1) SVG
t]
      , _documentDescription :: [Char]
_documentDescription = [Char]
""
      , _documentLocation :: [Char]
_documentLocation = [Char]
""
      , _documentAspectRatio :: PreserveAspectRatio
_documentAspectRatio = Bool -> Alignment -> Maybe MeetSlice -> PreserveAspectRatio
PreserveAspectRatio Bool
False Alignment
AlignNone Maybe MeetSlice
forall a. Maybe a
Nothing
      }
mapA :: (SVG -> SVG) -> Animation -> Animation
mapA :: (SVG -> SVG) -> Animation -> Animation
mapA SVG -> SVG
fn (Animation Duration
d Duration -> SVG
f) = Duration -> (Duration -> SVG) -> Animation
Animation Duration
d (SVG -> SVG
fn (SVG -> SVG) -> (Duration -> SVG) -> Duration -> SVG
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Duration -> SVG
f)
pauseAtEnd :: Duration -> Animation -> Animation
pauseAtEnd :: Duration -> Animation -> Animation
pauseAtEnd Duration
t Animation
a
  | Duration
t Duration -> Duration -> Bool
forall a. Eq a => a -> a -> Bool
== Duration
0    = Animation
a
  | Bool
otherwise = Animation
a Animation -> Animation -> Animation
`andThen` Duration -> Animation
pause Duration
t
pauseAtBeginning :: Duration -> Animation -> Animation
pauseAtBeginning :: Duration -> Animation -> Animation
pauseAtBeginning Duration
t Animation
a
  | Duration
t Duration -> Duration -> Bool
forall a. Eq a => a -> a -> Bool
== Duration
0    = Animation
a
  | Bool
otherwise = Duration -> (Duration -> SVG) -> Animation
mkAnimation Duration
t (Duration -> Animation -> Duration -> SVG
freezeFrame Duration
0 Animation
a) Animation -> Animation -> Animation
`seqA` Animation
a
pauseAround :: Duration -> Duration -> Animation -> Animation
pauseAround :: Duration -> Duration -> Animation -> Animation
pauseAround Duration
start Duration
end = Duration -> Animation -> Animation
pauseAtEnd Duration
end (Animation -> Animation)
-> (Animation -> Animation) -> Animation -> Animation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Duration -> Animation -> Animation
pauseAtBeginning Duration
start
freezeFrame :: Time -> Animation -> (Time -> SVG)
freezeFrame :: Duration -> Animation -> Duration -> SVG
freezeFrame Duration
t (Animation Duration
d Duration -> SVG
f) = SVG -> Duration -> SVG
forall a b. a -> b -> a
const (SVG -> Duration -> SVG) -> SVG -> Duration -> SVG
forall a b. (a -> b) -> a -> b
$ Duration -> SVG
f (Duration
tDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d)
adjustDuration :: (Duration -> Duration) -> Animation -> Animation
adjustDuration :: (Duration -> Duration) -> Animation -> Animation
adjustDuration Duration -> Duration
fn (Animation Duration
d Duration -> SVG
gen) = Duration -> (Duration -> SVG) -> Animation
mkAnimation (Duration -> Duration
fn Duration
d) Duration -> SVG
gen
setDuration :: Duration -> Animation -> Animation
setDuration :: Duration -> Animation -> Animation
setDuration Duration
newD = (Duration -> Duration) -> Animation -> Animation
adjustDuration (Duration -> Duration -> Duration
forall a b. a -> b -> a
const Duration
newD)
reverseA :: Animation -> Animation
reverseA :: Animation -> Animation
reverseA = (Duration -> Duration) -> Animation -> Animation
signalA Duration -> Duration
reverseS
playThenReverseA :: Animation -> Animation
playThenReverseA :: Animation -> Animation
playThenReverseA Animation
a = Animation
a Animation -> Animation -> Animation
`seqA` Animation -> Animation
reverseA Animation
a
repeatA :: Double -> Animation -> Animation
repeatA :: Duration -> Animation -> Animation
repeatA Duration
n (Animation Duration
d Duration -> SVG
f) = Duration -> (Duration -> SVG) -> Animation
mkAnimation (Duration
dDuration -> Duration -> Duration
forall a. Num a => a -> a -> a
*Duration
n) ((Duration -> SVG) -> Animation) -> (Duration -> SVG) -> Animation
forall a b. (a -> b) -> a -> b
$ \Duration
t -> Duration -> SVG
f ((Duration
tDuration -> Duration -> Duration
forall a. Num a => a -> a -> a
*Duration
n) Duration -> Duration -> Duration
forall a. Real a => a -> a -> a
`mod'` Duration
1)
freezeAtPercentage :: Time      
                                
                                
                                
                   -> Animation 
                                
                   -> Animation 
                                
                                
freezeAtPercentage :: Duration -> Animation -> Animation
freezeAtPercentage Duration
frac (Animation Duration
d Duration -> SVG
genFrame) =
  Duration -> (Duration -> SVG) -> Animation
Animation Duration
d ((Duration -> SVG) -> Animation) -> (Duration -> SVG) -> Animation
forall a b. (a -> b) -> a -> b
$ SVG -> Duration -> SVG
forall a b. a -> b -> a
const (SVG -> Duration -> SVG) -> SVG -> Duration -> SVG
forall a b. (a -> b) -> a -> b
$ Duration -> SVG
genFrame Duration
frac
addStatic :: SVG -> Animation -> Animation
addStatic :: SVG -> Animation -> Animation
addStatic SVG
static = (SVG -> SVG) -> Animation -> Animation
mapA (\SVG
frame -> [SVG] -> SVG
mkGroup [SVG
static, SVG
frame])
signalA :: Signal -> Animation -> Animation
signalA :: (Duration -> Duration) -> Animation -> Animation
signalA Duration -> Duration
fn (Animation Duration
d Duration -> SVG
gen) = Duration -> (Duration -> SVG) -> Animation
Animation Duration
d ((Duration -> SVG) -> Animation) -> (Duration -> SVG) -> Animation
forall a b. (a -> b) -> a -> b
$ Duration -> SVG
gen (Duration -> SVG) -> (Duration -> Duration) -> Duration -> SVG
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Duration -> Duration
fn
takeA :: Duration -> Animation -> Animation
takeA :: Duration -> Animation -> Animation
takeA Duration
len a :: Animation
a@(Animation Duration
d Duration -> SVG
gen)
  | Duration
len Duration -> Duration -> Bool
forall a. Ord a => a -> a -> Bool
>= Duration
d  = Animation
a
  | Bool
otherwise = Duration -> (Duration -> SVG) -> Animation
mkAnimation Duration
len ((Duration -> SVG) -> Animation) -> (Duration -> SVG) -> Animation
forall a b. (a -> b) -> a -> b
$ \Duration
t -> Duration -> SVG
gen (Duration
t Duration -> Duration -> Duration
forall a. Num a => a -> a -> a
* Duration
lenDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d)
dropA :: Duration -> Animation -> Animation
dropA :: Duration -> Animation -> Animation
dropA Duration
len a :: Animation
a@(Animation Duration
d Duration -> SVG
gen)
  | Duration
len Duration -> Duration -> Bool
forall a. Ord a => a -> a -> Bool
<= Duration
0  = Animation
a
  | Bool
otherwise = Duration -> (Duration -> SVG) -> Animation
mkAnimation Duration
rest ((Duration -> SVG) -> Animation) -> (Duration -> SVG) -> Animation
forall a b. (a -> b) -> a -> b
$ \Duration
t -> Duration -> SVG
gen (Duration
t Duration -> Duration -> Duration
forall a. Num a => a -> a -> a
* Duration
restDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d Duration -> Duration -> Duration
forall a. Num a => a -> a -> a
+ Duration
lenDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d)
  where
    rest :: Duration
rest = Duration
d Duration -> Duration -> Duration
forall a. Num a => a -> a -> a
- Duration
len
lastA :: Duration -> Animation -> Animation
lastA :: Duration -> Animation -> Animation
lastA Duration
len a :: Animation
a@(Animation Duration
d Duration -> SVG
_) = Duration -> Animation -> Animation
dropA (Duration
d Duration -> Duration -> Duration
forall a. Num a => a -> a -> a
- Duration
len) Animation
a
clamp :: Double -> Double -> Double -> Double
clamp :: Duration -> Duration -> Duration -> Duration
clamp Duration
a Duration
b Duration
number
  | Duration
a Duration -> Duration -> Bool
forall a. Ord a => a -> a -> Bool
< Duration
b     = Duration -> Duration -> Duration
forall a. Ord a => a -> a -> a
max Duration
a (Duration -> Duration -> Duration
forall a. Ord a => a -> a -> a
min Duration
b Duration
number)
  | Bool
otherwise = Duration -> Duration -> Duration
forall a. Ord a => a -> a -> a
max Duration
b (Duration -> Duration -> Duration
forall a. Ord a => a -> a -> a
min Duration
a Duration
number)
getAnimationFrame :: Sync -> Animation -> Time -> Duration -> SVG
getAnimationFrame :: Sync -> Animation -> Duration -> Duration -> SVG
getAnimationFrame Sync
sync (Animation Duration
aDur Duration -> SVG
aGen) Duration
t Duration
d =
  case Sync
sync of
    Sync
SyncStretch -> Duration -> SVG
aGen (Duration
tDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d)
    Sync
SyncLoop    -> Duration -> SVG
aGen (Duration -> Duration
takeFrac (Duration -> Duration) -> Duration -> Duration
forall a b. (a -> b) -> a -> b
$ Duration
tDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
aDur)
    Sync
SyncDrop    -> if Duration
t Duration -> Duration -> Bool
forall a. Ord a => a -> a -> Bool
> Duration
aDur then SVG
None else Duration -> SVG
aGen (Duration
tDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
aDur)
    Sync
SyncFreeze  -> Duration -> SVG
aGen (Duration -> Duration -> Duration
forall a. Ord a => a -> a -> a
min Duration
1 (Duration -> Duration) -> Duration -> Duration
forall a b. (a -> b) -> a -> b
$ Duration
tDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
aDur)
  where
    takeFrac :: Duration -> Duration
takeFrac Duration
f = (Int, Duration) -> Duration
forall a b. (a, b) -> b
snd (Duration -> (Int, Duration)
forall a b. (RealFrac a, Integral b) => a -> (b, a)
properFraction Duration
f :: (Int, Double))
data Sync
  = SyncStretch
  | SyncLoop
  | SyncDrop
  | SyncFreeze