{-# LANGUAGE TupleSections, RecursiveDo, RankNTypes, DeriveDataTypeable #-} module SimpleH.Reactive.Time ( -- * Unambiguous times Time, timeVal, -- * Time utilities Seconds, timeIO,waitTill,currentTime ) where import SimpleH import Control.Concurrent import SimpleH.Reactive.TimeVal import System.IO.Unsafe import Data.IORef import System.Clock import Control.Exception (handle,Exception(..)) import Data.Typeable data Freezed = Freezed deriving (Typeable,Show) instance Exception Freezed -- |A type wrappers for timestamps that can be compared unambiguously data Time t = Time (TimeVal t -> TimeVal t) (TimeVal t -> TimeVal t) instance (Eq t,Show t) => Show (Time t) where show = show . timeVal instance Ord t => Eq (Time t) where a == b = compare a b == EQ instance Ord t => Ord (Time t) where compare ~(Time fa fa') ~(Time fb fb') = cmp fa fb' `unamb` invertOrd (cmp fb fa') where cmp f f' = compare a (f' a) where a = f maxBound -- |The Time semigroup where @ta + tb == max ta tb@ instance Ord t => Semigroup (Time t) where ~(Time fa fa') + ~(Time fb fb') = Time (mapT max fa fb) (mapT max fa' fb') -- |The Time monoid where @zero == minBound@ instance Ord t => Monoid (Time t) where zero = minBound -- |The Time ring where @(*) == min@ and @one == maxBound@ instance Ord t => Ring (Time t) where one = maxBound ~(Time fa fa') * ~(Time fb fb') = Time (mapT min fa fb) (mapT min fa' fb') instance Ord t => Orderable (Time t) where inOrder a b = (a*b,if z then b else a,z) where z = a<=b mapT :: (t -> t -> a) -> (t -> t) -> (t -> t) -> t -> a mapT f fa fb h = f a (fb a) `unamb` f b (fa b) where a = fa h ; b = fb h instance Bounded (Time t) where minBound = Time (pure minBound) (pure minBound) maxBound = Time (pure maxBound) (pure maxBound) instance Unit Time where pure t = Time (pure (pure t)) (pure (pure t)) amb :: IO a -> IO a -> IO a ma `amb` mb = do res <- newEmptyMVar ta <- forkIO $ handle (\Freezed -> unit) $ ma >>= putMVar res . Left tb <- forkIO $ handle (\Freezed -> unit) $ mb >>= putMVar res . Right takeMVar res >>= \c -> case c of Left a -> pure a <* killThread tb Right a -> pure a <* killThread ta unamb :: a -> a -> a unamb = warp2 (from _thunk) amb type Seconds = Double -- |A Time's pure value. May not be defined immediately. timeVal :: Time t -> TimeVal t timeVal (Time fa _) = fa maxBound -- |Constructs a Time representing the time at which the argument terminates. -- -- Warning: This function executes its argument, ignoring its -- value. Thus, it would be wise to use it on repeatable blocking -- actions, such as @readMVar@. timeIO :: IO a -> IO (Time Seconds) timeIO io = do sem <- newEmptyMVar ret <- newIORef id minAction <- newIORef $ \tm -> readIORef ret <**> Since<$>amb (readMVar sem) ( case tm of Always -> currentTime Since t -> waitTill t >> currentTime Never -> throw Freezed) maxAction <- newIORef $ \tm -> readIORef ret <**> amb (Since<$>readMVar sem) ( case tm of Always -> throw Freezed Since t -> waitTill t >> pure Never Never -> Since<$>currentTime) let refAction ref = \t -> unsafePerformIO (join (readIORef ref<*>pure t)) _ <- forkIO $ void $ mfix $ \t -> do _ <- io writeIORef minAction (const (pure (pure t))) writeIORef maxAction (const (pure (pure t))) writeIORef ret (const (pure t)) putMVar sem t currentTime return $ Time (refAction minAction) (refAction maxAction) waitTill :: Seconds -> IO () waitTill t = do now <- t `seq` currentTime when (t>now) $ threadDelay (floor $ (t-now)*1000000) seconds :: TimeSpec -> Seconds seconds t = fromIntegral (sec t) + fromIntegral (nsec t)/1000000000 :: Seconds currentTime :: IO Seconds currentTime = seconds<$>getTime Realtime