Monad transformer to consume a list

Hello, is there a monad transformer to consume an input list? I've got external events "streaming into the monad" that are consumed on demand and I'm not sure if there's something better than a StateT. //Stephan -- Früher hieß es ja: Ich denke, also bin ich. Heute weiß man: Es geht auch so. - Dieter Nuhr

On Mon, 6 Apr 2009, Stephan Friedrichs wrote:
Hello,
is there a monad transformer to consume an input list? I've got external events "streaming into the monad" that are consumed on demand and I'm not sure if there's something better than a StateT.
I wondered that, too. I wondered whether there is something inverse to Writer, and Reader is appearently not the answer. Now I think, that State is indeed the way to go to consume a list. Even better is StateT List Maybe: next :: StateT [a] Maybe a next = StateT Data.List.HT.viewL -- see utility-ht package

Henning Thielemann wrote:
is there a monad transformer to consume an input list? I've got external events "streaming into the monad" that are consumed on demand and I'm not sure if there's something better than a StateT.
I wondered that, too. I wondered whether there is something inverse to Writer, and Reader is appearently not the answer. Now I think, that State is indeed the way to go to consume a list. Even better is StateT List Maybe:
next :: StateT [a] Maybe a next = StateT Data.List.HT.viewL -- see utility-ht package
But a StateT provides the power to modify the list in other ways than reading the first element (modify (x:)). Maybe ParsecT is closer to what I'm looking for ;) -- Früher hieß es ja: Ich denke, also bin ich. Heute weiß man: Es geht auch so. - Dieter Nuhr

On Tue, 7 Apr 2009, Stephan Friedrichs wrote:
Henning Thielemann wrote:
is there a monad transformer to consume an input list? I've got external events "streaming into the monad" that are consumed on demand and I'm not sure if there's something better than a StateT.
I wondered that, too. I wondered whether there is something inverse to Writer, and Reader is appearently not the answer. Now I think, that State is indeed the way to go to consume a list. Even better is StateT List Maybe:
next :: StateT [a] Maybe a next = StateT Data.List.HT.viewL -- see utility-ht package
But a StateT provides the power to modify the list in other ways than reading the first element (modify (x:)). Maybe ParsecT is closer to what I'm looking for ;)
If you want to restrict the functionality of StateT, then wrap it in a newtype.

Hello,
is there a monad transformer to consume an input list? I've got external events "streaming into the monad" that are consumed on demand and I'm not sure if there's something better than a StateT.
I wondered that, too. I wondered whether there is something inverse to Writer, and Reader is appearently not the answer. Now I think, that State is indeed the way to go to consume a list. Even better is StateT List Maybe:
next :: StateT [a] Maybe a next = StateT Data.List.HT.viewL -- see utility-ht package
Or make the transformer a MonadPlus transformer and call mzero for the empty list? Tom -- Tom Schrijvers Department of Computer Science K.U. Leuven Celestijnenlaan 200A B-3001 Heverlee Belgium tel: +32 16 327544 e-mail: tom.schrijvers@cs.kuleuven.be url: http://www.cs.kuleuven.be/~toms/

My solution is this transformer: newtype ConsumerT c m a = ConsumerT { runConsumerT :: [c] -> m (a, [c]) } instance (Monad m) => Monad (ConsumerT c m) where return x = ConsumerT $ \cs -> return (x, cs) m >>= f = ConsumerT $ \cs -> do ~(x, cs') <- runConsumerT m cs runConsumerT (f x) cs' fail msg = ConsumerT $ const (fail msg) consume :: (Monad m) => ConsumerT c m (Maybe c) consume = ConsumerT $ \css -> case css of [] -> return (Nothing, []) (c:cs) -> return (Just c, cs) consumeAll :: (Monad m) => ConsumerT c m [c] consumeAll = ConsumerT $ \cs -> return (cs, []) -- Früher hieß es ja: Ich denke, also bin ich. Heute weiß man: Es geht auch so. - Dieter Nuhr

On Tue, 7 Apr 2009, Stephan Friedrichs wrote:
My solution is this transformer:
newtype ConsumerT c m a = ConsumerT { runConsumerT :: [c] -> m (a, [c]) }
instance (Monad m) => Monad (ConsumerT c m) where return x = ConsumerT $ \cs -> return (x, cs) m >>= f = ConsumerT $ \cs -> do ~(x, cs') <- runConsumerT m cs runConsumerT (f x) cs' fail msg = ConsumerT $ const (fail msg)
But this is precisely the StateT, wrapped in a newtype and with restricted operations on it. You could as well define newtype ConsumerT c m a = ConsumerT { runConsumerT :: StateT [c] m a } instance (Monad m) => Monad (ConsumerT c m) where return x = ConsumerT $ return x m >>= f = ConsumerT $ runConsumerT . f =<< runConsumerT m

Henning Thielemann wrote:
[...]
But this is precisely the StateT, wrapped in a newtype and with restricted operations on it. You could as well define
newtype ConsumerT c m a = ConsumerT { runConsumerT :: StateT [c] m a }
Oh I see - my bad. I was somehow thinking I could prevent modification of the input list but that's obviously impossible when the ConsumerT constructor is... exported? public? how do you say that?
[...]
//Stephan -- Früher hieß es ja: Ich denke, also bin ich. Heute weiß man: Es geht auch so. - Dieter Nuhr

Stephan Friedrichs wrote:
Oh I see - my bad. I was somehow thinking I could prevent modification of the input list but that's obviously impossible when the ConsumerT constructor is... exported? public? how do you say that?
You can export ConsumerT as an abstract type constructor.
{-# LANGUAGE GeneralizedNewtypeDeriving #-} module ConsumerT(ConsumerT, runConsumerT, next) where
import Control.Monad.State import Control.Monad.Trans
newtype ConsumerT c m a = ConsumerT { runConsumerT' :: StateT [c] m a } deriving (Functor, Monad, MonadTrans)
runConsumerT = runStateT . runConsumerT'
next :: Monad m => ConsumerT a m a next = ConsumerT $ StateT $ \(x:xs) -> return (x, xs)
participants (4)
-
Gleb Alexeyev
-
Henning Thielemann
-
Stephan Friedrichs
-
Tom Schrijvers