{- Copyright 2010 Mario Blazevic This file is part of the Streaming Component Combinators (SCC) project. The SCC project is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. SCC is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with SCC. If not, see . -} -- | This module defines suspension functors for use with the "Control.Monad.Coroutine" module. -- module Control.Monad.Coroutine.SuspensionFunctors ( -- * Suspension functors Yield(Yield), Await(Await), Request(Request), EitherFunctor(LeftF, RightF), yield, await, request ) where import Control.Monad (Monad) import Control.Monad.Coroutine (Coroutine, resume, suspend) -- | The 'Yield' functor instance is equivalent to (,) but more descriptive. data Yield x y = Yield x y instance Functor (Yield x) where fmap f (Yield x y) = Yield x (f y) -- | The 'Await' functor instance is equivalent to (->) but more descriptive. newtype Await x y = Await (x -> y) instance Functor (Await x) where fmap f (Await g) = Await (f . g) -- | The 'Request' functor instance combines a 'Yield' of a request with an 'Await' for a response. data Request request response x = Request request (response -> x) instance Functor (Request x f) where fmap f (Request x g) = Request x (f . g) -- | Combines two alternative functors into one, applying one or the other. Used for nested coroutines. data EitherFunctor l r x = LeftF (l x) | RightF (r x) instance (Functor l, Functor r) => Functor (EitherFunctor l r) where fmap f (LeftF l) = LeftF (fmap f l) fmap f (RightF r) = RightF (fmap f r) -- | Suspend yielding a value. yield :: Monad m => x -> Coroutine (Yield x) m () yield x = suspend (Yield x (return ())) -- | Suspend until a value is provided. await :: Monad m => Coroutine (Await x) m x await = suspend (Await return) -- | Suspend yielding a request and awaiting the response. request :: Monad m => x -> Coroutine (Request x y) m y request x = suspend (Request x return)