Help me refactor this type!

More FRP stuff: a new type for Future that came to me in an inspiration this morning. But it's ugly and I need someone with better theoretical underpinnings than me to tell me what I've really built :) data Future t a = Known t a | Unknown (t -> IO (STM (Maybe (Future t a)))) Given Eq t, Ord t, Bounded t, this type is at least member of Monad, Applicative, Functor, and MonadPlus/Monoid. But the derivation gives me that "needs refactoring" feeling; here's an example: force :: (Ord t, Bounded t) => Future t a -> IO (t, a) force (Known t a) = return (t, a) force (Unknown f) = do stmF <- f maxBound mF <- atomically stmF case mF of Nothing -> return (maxBound, error "never") Just fut' -> force fut' delayF :: Ord t => t -> Future t a -> Future t a delayF t0 (Known t a) = Known (max t0 t) a delayF t0 (Unknown f) = Unknown $ \t -> fmap (fmap (fmap (delayF t0))) (f t) instance (Ord t, Bounded t) => Monad (Future t) where return = Known minBound Known t a >>= g = delayF t (g a) Unknown f >>= g = Unknown $ \t -> do -- IO stmF <- f t return $ do -- STM mF <- stmF return $ do -- Maybe fut' <- mF return (fut' >>= g) This code makes me sad; so many nested blocks. There's got to be a refactoring of this that I am missing! It's clearly got something to do with Fix, Either, ReaderT, and MaybeT, and type composition, but none of those seem to answer the whole question. Any thoughts? -- ryan

On Thu, Apr 24, 2008 at 11:10 PM, Ryan Ingram
More FRP stuff: a new type for Future that came to me in an inspiration this morning. But it's ugly and I need someone with better theoretical underpinnings than me to tell me what I've really built :)
data Future t a = Known t a | Unknown (t -> IO (STM (Maybe (Future t a))))
This looks similar to my friend the "free monad over exponentiation", or Suspend, which I also discovered while experimenting with FRP. After experimenting a bit, I found that the following variant lead to more elegant implementations of the same things: newtype SuspendT v m a = SuspendT (m (Either a (v -> SuspendT v m a))) Implemented pretty fully here: http://luqui.org/git/?p=luqui-misc.git;a=blob;f=work/code/haskell/frp/Fregl/... I'm not quite sure whether you can make it have all the capabilities yours does (there is no STMT...). Luke

Ryan Ingram wrote:
More FRP stuff: a new type for Future that came to me in an inspiration this morning. But it's ugly and I need someone with better theoretical underpinnings than me to tell me what I've really built :)
data Future t a = Known t a | Unknown (t -> IO (STM (Maybe (Future t a))))
This is a composition of (applicative) functors. Not sure whether this helps from the theoretical side, but it can be used to considerably shorten your code: type Tower t b = t -> IO (STM (Maybe b)) fmap4 :: (a -> b) -> Tower a -> Tower b fmap4 f = fmap . fmap . fmap . fmap $ f delayF :: Ord t => t -> Future t a -> Future t a delayF t0 (Known t a) = Known (max t0 t) a delayF t0 (Unknown f) = Unknown $ fmap4 (delayF0 t0) f instance (Ord t, Bounded t) => Monad (Future t) where return = Known minBound Known t a >>= g = delayF t (g a) Unknown f >>= g = Unknown $ fmap4 (>>= g) f Regards, apfelmus
participants (3)
-
apfelmus
-
Luke Palmer
-
Ryan Ingram