1 {-# LANGUAGE Arrows #-}
14 infinity :: (Fractional a) => a
17 -- Outputs the average time between intNum of the last events. Goes to
18 -- infinity if less than intNum events have occured or if no event has
19 -- occured in maxTime.
20 avgInt :: SF (Event a) DTime
21 avgInt = avgInt' [] `switch` ((>>^ fst) . avgInt')
22 where avgInt' :: [DTime] -> SF (Event a) (DTime, Event [DTime])
23 avgInt' l = proc e -> do
25 tooLate <- after maxTime [] -< ()
26 let timeList = (e `tag` (appDTime intNum t l)) `lMerge` tooLate
27 returnA -< (avgS intNum l, timeList)
29 appDTime :: Int -> Time -> [DTime] -> [DTime]
31 appDTime n t l = (t - head l):(take (n-1) l)
33 avgS :: (Fractional a) => Int -> [a] -> a
35 | length l /= n = infinity
36 | otherwise = foldl (+) 0 l / fromIntegral n