module Reanimate.Effect
  ( 
  Effect
  , fadeInE
  , fadeOutE
  , fadeLineInE
  , fadeLineOutE
  , fillInE
  , drawInE
  , drawOutE
  , translateE
  , scaleE
  , constE
  
  , overBeginning
  , overEnding
  , overInterval
  , reverseE
  , delayE
  , aroundCenterE
  
  , applyE
  ) where
import           Graphics.SvgTree    (Tree)
import           Reanimate.Animation
import           Reanimate.Svg
type Effect = Duration 
           -> Time 
           -> Tree 
           -> Tree 
overBeginning :: Duration 
              -> Effect 
              -> Effect 
overBeginning :: Duration -> Effect -> Effect
overBeginning Duration
maxT Effect
effect Duration
_d Duration
t =
  if Duration
t Duration -> Duration -> Bool
forall a. Ord a => a -> a -> Bool
< Duration
maxT
    then Effect
effect Duration
maxT Duration
t
    else Tree -> Tree
forall a. a -> a
id
overEnding :: Duration 
           -> Effect  
           -> Effect 
overEnding :: Duration -> Effect -> Effect
overEnding Duration
minT Effect
effect Duration
d Duration
t =
  if Duration
t Duration -> Duration -> Bool
forall a. Ord a => a -> a -> Bool
>= Duration
blankDur
    then Effect
effect Duration
minT (Duration
tDuration -> Duration -> Duration
forall a. Num a => a -> a -> a
-Duration
blankDur)
    else Tree -> Tree
forall a. a -> a
id
  where
    blankDur :: Duration
blankDur = Duration
dDuration -> Duration -> Duration
forall a. Num a => a -> a -> a
-Duration
minT
overInterval :: Time 
             -> Time 
             -> Effect  
             -> Effect 
overInterval :: Duration -> Duration -> Effect -> Effect
overInterval Duration
start Duration
end Effect
effect Duration
_d Duration
t =
  if Duration
start Duration -> Duration -> Bool
forall a. Ord a => a -> a -> Bool
<= Duration
t Bool -> Bool -> Bool
&& Duration
t Duration -> Duration -> Bool
forall a. Ord a => a -> a -> Bool
<= Duration
end
    then Effect
effect Duration
dur ((Duration
t Duration -> Duration -> Duration
forall a. Num a => a -> a -> a
- Duration
start) Duration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/ Duration
dur)
    else Tree -> Tree
forall a. a -> a
id
  where
    dur :: Duration
dur = Duration
end Duration -> Duration -> Duration
forall a. Num a => a -> a -> a
- Duration
start
reverseE :: Effect -> Effect
reverseE :: Effect -> Effect
reverseE Effect
fn Duration
d Duration
t = Effect
fn Duration
d (Duration
dDuration -> Duration -> Duration
forall a. Num a => a -> a -> a
-Duration
t)
delayE :: Duration -> Effect -> Effect
delayE :: Duration -> Effect -> Effect
delayE Duration
delayT Effect
fn Duration
d = Duration -> Effect -> Effect
overEnding (Duration
dDuration -> Duration -> Duration
forall a. Num a => a -> a -> a
-Duration
delayT) Effect
fn Duration
d
applyE :: Effect -> Animation -> Animation
applyE :: Effect -> Animation -> Animation
applyE Effect
fn Animation
ani = let d :: Duration
d = Animation -> Duration
duration Animation
ani
                in Duration -> (Duration -> Tree) -> Animation
mkAnimation Duration
d ((Duration -> Tree) -> Animation)
-> (Duration -> Tree) -> Animation
forall a b. (a -> b) -> a -> b
$ \Duration
t -> Effect
fn Duration
d (Duration
dDuration -> Duration -> Duration
forall a. Num a => a -> a -> a
*Duration
t) (Tree -> Tree) -> Tree -> Tree
forall a b. (a -> b) -> a -> b
$ Duration -> Animation -> Tree
frameAt (Duration
dDuration -> Duration -> Duration
forall a. Num a => a -> a -> a
*Duration
t) Animation
ani
constE :: (Tree -> Tree) -> Effect
constE :: (Tree -> Tree) -> Effect
constE Tree -> Tree
fn Duration
_d Duration
_t = Tree -> Tree
fn
fadeInE :: Effect
fadeInE :: Effect
fadeInE Duration
d Duration
t = Duration -> Tree -> Tree
withGroupOpacity (Duration
tDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d)
fadeOutE :: Effect
fadeOutE :: Effect
fadeOutE = Effect -> Effect
reverseE Effect
fadeInE
fadeLineInE :: Double -> Effect
fadeLineInE :: Duration -> Effect
fadeLineInE Duration
w Duration
d Duration
t = Duration -> Tree -> Tree
withStrokeWidth (Duration
wDuration -> Duration -> Duration
forall a. Num a => a -> a -> a
*(Duration
tDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d))
fadeLineOutE :: Double -> Effect
fadeLineOutE :: Duration -> Effect
fadeLineOutE = Effect -> Effect
reverseE (Effect -> Effect) -> (Duration -> Effect) -> Duration -> Effect
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Duration -> Effect
fadeLineInE
drawInE :: Effect
drawInE :: Effect
drawInE Duration
d Duration
t = Duration -> Tree -> Tree
withFillOpacity Duration
0 (Tree -> Tree) -> (Tree -> Tree) -> Tree -> Tree
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Duration -> Tree -> Tree
partialSvg (Duration
tDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d) (Tree -> Tree) -> (Tree -> Tree) -> Tree -> Tree
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tree -> Tree
pathify
drawOutE :: Effect
drawOutE :: Effect
drawOutE = Effect -> Effect
reverseE Effect
drawInE
fillInE :: Effect
fillInE :: Effect
fillInE Duration
d Duration
t = Duration -> Tree -> Tree
withFillOpacity Duration
f
  where
    f :: Duration
f = Duration
tDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d
scaleE :: Double -> Effect
scaleE :: Duration -> Effect
scaleE Duration
target Duration
d Duration
t = Duration -> Tree -> Tree
scale (Duration
1 Duration -> Duration -> Duration
forall a. Num a => a -> a -> a
+ (Duration
targetDuration -> Duration -> Duration
forall a. Num a => a -> a -> a
-Duration
1) Duration -> Duration -> Duration
forall a. Num a => a -> a -> a
* Duration
tDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d)
translateE :: Double -> Double -> Effect
translateE :: Duration -> Duration -> Effect
translateE Duration
x Duration
y Duration
d Duration
t = Effect
translate (Duration
x Duration -> Duration -> Duration
forall a. Num a => a -> a -> a
* Duration
tDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d) (Duration
y Duration -> Duration -> Duration
forall a. Num a => a -> a -> a
* Duration
tDuration -> Duration -> Duration
forall a. Fractional a => a -> a -> a
/Duration
d)
aroundCenterE :: Effect -> Effect
aroundCenterE :: Effect -> Effect
aroundCenterE Effect
e Duration
d Duration
t = (Tree -> Tree) -> Tree -> Tree
aroundCenter (Effect
e Duration
d Duration
t)