module Control.FRPNow.Time(localTime,timeFrac, lastInputs, bufferBehavior,delayBy, delayByN, delayTime, integrate, VectorSpace(..)) where
import Control.FRPNow.Core
import Control.FRPNow.Lib
import Control.FRPNow.EvStream
import Data.Sequence
import Control.Applicative hiding (empty)
import Data.Foldable
import Debug.Trace
localTime :: (Floating time, Ord time) => Behavior time -> Behavior (Behavior time)
localTime t = do n <- t
return ((\x -> x n) <$> t)
timeFrac :: (Floating time, Ord time) => Behavior time -> time -> Behavior (Behavior time)
timeFrac t d = do t' <- localTime t
e <- when $ (>= d) <$> t'
let frac = (\x -> min 1.0 (x / d)) <$> t'
return (frac `switch` (pure 1.0 <$ e))
tagTime :: (Floating time, Ord time) => Behavior time -> EvStream a -> EvStream (time,a)
tagTime c s = ((,) <$> c) <@@> s
lastInputs :: (Floating time, Ord time) =>
Behavior time
-> time
-> EvStream a
-> Behavior (Behavior [a])
lastInputs clock dur s = do s' <- bufferStream clock dur s
bs <- fromChanges [] s'
let dropIt cur s = dropWhile (\(t,_) -> t + dur < cur) s
return $ (fmap snd) <$> (dropIt <$> clock <*> bs)
bufferStream :: (Floating time, Ord time) => Behavior time -> time -> EvStream a -> Behavior (EvStream [(time,a)])
bufferStream clock dur s = do s' <- scanlEv addDrop empty $ tagTime clock s
return $ toList <$> s' where
addDrop ss s@(last,v) = dropWhileL (\(tn,_) -> tn + dur < last) (ss |> s)
data TimeTag t a = TimeTag t a
instance Eq t => Eq (TimeTag t a) where
(TimeTag t1 _) == (TimeTag t2 _) = t1 == t2
bufferBehavior :: (Floating time, Ord time) =>
Behavior time
-> time
-> Behavior a
-> Behavior (Behavior [(time,a)])
bufferBehavior clock dur b = fmap toList <$> foldB update empty (TimeTag <$> clock <*> b)
where update l (TimeTag now x) = trimList (l |> (now,x)) (now dur)
trimList l after = loop l where
loop l =
case viewl l of
EmptyL -> empty
(t1,v1) :< tail1
| after <= t1 -> l
| otherwise ->
case viewl tail1 of
(t2,v2) :< tail2
| t2 <= after -> loop tail2
| otherwise -> l
delayBy :: (Floating time, Ord time) =>
Behavior time
-> time
-> Behavior a
-> Behavior (Behavior a)
delayBy time d b = fmap (snd . head) <$> bufferBehavior time d b
delayByN :: (Floating time, Ord time) =>
Behavior time
-> time
-> Integer
-> Behavior a
-> Behavior (Behavior [a])
delayByN clock dur n b =
let durN = (fromIntegral n) * dur
in do samples <- bufferBehavior clock durN b
return $ interpolateFromList <$> clock <*> samples where
interpolateFromList now l= loop (n 1) l where
loop n l =
if n < 0 then []
else let sampleTime = now (fromIntegral n * dur)
in case l of
[] -> []
[(_,v)] -> v : loop (n1) l
((t1,v1) : (t2,v2) : rest)
| sampleTime >= t2 -> loop n ((t2,v2) : rest)
| otherwise -> v1 : loop (n1) l
integrate :: (VectorSpace v time) =>
Behavior time -> Behavior v -> Behavior (Behavior v)
integrate time v = do t <- time
vp <- delayTime time (t,zeroVector) ((,) <$> time <*> v)
foldB add zeroVector $ (,) <$> vp <*> time
where add total ((t1,v),t2) = total ^+^ ((t2 t1) *^ v)
delayTime :: Eq time => Behavior time -> a -> Behavior a -> Behavior (Behavior a)
delayTime time i b = loop i where
loop i =
do e <- futuristic $
do (t,cur) <- (,) <$> time <*> b
e <- when ((/= t) <$> time)
return (cur <$ e)
e' <- plan ( loop <$> e)
return (i `step` e')
infixr *^
infixl ^/
infix 7 `dot`
infixl 6 ^+^, ^-^
class (Eq a, Eq v, Ord v, Ord a, Floating a) => VectorSpace v a | v -> a where
zeroVector :: v
(*^) :: a -> v -> v
(^/) :: v -> a -> v
negateVector :: v -> v
(^+^) :: v -> v -> v
(^-^) :: v -> v -> v
dot :: v -> v -> a
norm :: v -> a
normalize :: v -> v
v ^/ a = (1/a) *^ v
negateVector v = (1) *^ v
v1 ^-^ v2 = v1 ^+^ negateVector v2
norm v = sqrt (v `dot` v)
normalize v = if nv /= 0 then v ^/ nv else error "normalize: zero vector"
where nv = norm v
instance VectorSpace Float Float where
zeroVector = 0
a *^ x = a * x
x ^/ a = x / a
negateVector x = (x)
x1 ^+^ x2 = x1 + x2
x1 ^-^ x2 = x1 x2
x1 `dot` x2 = x1 * x2
instance VectorSpace Double Double where
zeroVector = 0
a *^ x = a * x
x ^/ a = x / a
negateVector x = (x)
x1 ^+^ x2 = x1 + x2
x1 ^-^ x2 = x1 x2
x1 `dot` x2 = x1 * x2
instance (Eq a, Floating a, Ord a) => VectorSpace (a,a) a where
zeroVector = (0,0)
a *^ (x,y) = (a * x, a * y)
(x,y) ^/ a = (x / a, y / a)
negateVector (x,y) = (x, y)
(x1,y1) ^+^ (x2,y2) = (x1 + x2, y1 + y2)
(x1,y1) ^-^ (x2,y2) = (x1 x2, y1 y2)
(x1,y1) `dot` (x2,y2) = x1 * x2 + y1 * y2
instance (Eq a, Floating a, Ord a) => VectorSpace (a,a,a) a where
zeroVector = (0,0,0)
a *^ (x,y,z) = (a * x, a * y, a * z)
(x,y,z) ^/ a = (x / a, y / a, z / a)
negateVector (x,y,z) = (x, y, z)
(x1,y1,z1) ^+^ (x2,y2,z2) = (x1+x2, y1+y2, z1+z2)
(x1,y1,z1) ^-^ (x2,y2,z2) = (x1x2, y1y2, z1z2)
(x1,y1,z1) `dot` (x2,y2,z2) = x1 * x2 + y1 * y2 + z1 * z2
instance (Eq a, Floating a, Ord a) => VectorSpace (a,a,a,a) a where
zeroVector = (0,0,0,0)
a *^ (x,y,z,u) = (a * x, a * y, a * z, a * u)
(x,y,z,u) ^/ a = (x / a, y / a, z / a, u / a)
negateVector (x,y,z,u) = (x, y, z, u)
(x1,y1,z1,u1) ^+^ (x2,y2,z2,u2) = (x1+x2, y1+y2, z1+z2, u1+u2)
(x1,y1,z1,u1) ^-^ (x2,y2,z2,u2) = (x1x2, y1y2, z1z2, u1u2)
(x1,y1,z1,u1) `dot` (x2,y2,z2,u2) = x1 * x2 + y1 * y2 + z1 * z2 + u1 * u2
instance (Eq a, Floating a, Ord a) => VectorSpace (a,a,a,a,a) a where
zeroVector = (0,0,0,0,0)
a *^ (x,y,z,u,v) = (a * x, a * y, a * z, a * u, a * v)
(x,y,z,u,v) ^/ a = (x / a, y / a, z / a, u / a, v / a)
negateVector (x,y,z,u,v) = (x, y, z, u, v)
(x1,y1,z1,u1,v1) ^+^ (x2,y2,z2,u2,v2) = (x1+x2, y1+y2, z1+z2, u1+u2, v1+v2)
(x1,y1,z1,u1,v1) ^-^ (x2,y2,z2,u2,v2) = (x1x2, y1y2, z1z2, u1u2, v1v2)
(x1,y1,z1,u1,v1) `dot` (x2,y2,z2,u2,v2) =
x1 * x2 + y1 * y2 + z1 * z2 + u1 * u2 + v1 * v2