Bas van Dijk wrote:
> On 6 December 2011 09:12, Bas van Dijk wrote:
> > instance MonadBaseControl IO Annex where
> > newtype StM Annex a = StAnnex (StM (StateT AnnexState IO) a)
> > liftBaseWith f = Annex $ liftBaseWith $ \runInIO ->
> > f $ liftM StAnnex . runInIO . ru
Bas van Dijk wrote:
> You can use the following:
>
> {-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies, MultiParamTypeClasses
> #-}
>
> import Control.Applicative
> import Control.Monad
> import Control.Monad.Base
> import Control.Monad.Trans.Class
> import Control.Monad.Trans.Control
> impo
On Tue, Dec 6, 2011 at 3:03 PM, Bas van Dijk wrote:
> On 6 December 2011 12:59, Michael Snoyman wrote:
>> On Tue, Dec 6, 2011 at 11:49 AM, Bas van Dijk wrote:
>>> On 6 December 2011 05:06, Michael Snoyman wrote:
Maybe this will help[1]. It's using RWST instead of StateT, but it's
the
On 6 December 2011 12:59, Michael Snoyman wrote:
> On Tue, Dec 6, 2011 at 11:49 AM, Bas van Dijk wrote:
>> On 6 December 2011 05:06, Michael Snoyman wrote:
>>> Maybe this will help[1]. It's using RWST instead of StateT, but it's
>>> the same idea.
>>>
>>> [1]
>>> https://github.com/yesodweb/yes
On Tue, Dec 6, 2011 at 11:49 AM, Bas van Dijk wrote:
> On 6 December 2011 05:06, Michael Snoyman wrote:
>> Maybe this will help[1]. It's using RWST instead of StateT, but it's
>> the same idea.
>>
>> [1]
>> https://github.com/yesodweb/yesod/commit/7619e4e9dd88c152d1e00b6fea073c3d52dc797f#L0R105
On 6 December 2011 05:06, Michael Snoyman wrote:
> Maybe this will help[1]. It's using RWST instead of StateT, but it's
> the same idea.
>
> [1]
> https://github.com/yesodweb/yesod/commit/7619e4e9dd88c152d1e00b6fea073c3d52dc797f#L0R105
Hi Michael,
Note that you can just reuse the MonadTransCont
On 6 December 2011 09:12, Bas van Dijk wrote:
> instance MonadBaseControl IO Annex where
> newtype StM Annex a = StAnnex (StM (StateT AnnexState IO) a)
> liftBaseWith f = Annex $ liftBaseWith $ \runInIO ->
> f $ liftM StAnnex . runInIO . runAnnex
Oops forgot the restor
On 6 December 2011 04:03, Joey Hess wrote:
> I'm trying to convert from 0.2 to 0.3, but in way over my head.
>
> {-# LANGUAGE GeneralizedNewtypeDeriving #-}
> newtype Annex a = Annex { runAnnex :: StateT AnnexState IO a }
> deriving (
> Monad,
> MonadIO,
>
On Tue, Dec 6, 2011 at 6:04 AM, Joey Hess wrote:
> Michael Snoyman wrote:
>> I just spent a fair amount of time yesterday upgrading packages to
>> monad-control 0.3. What I had to do was add in the MonadTransControl
>> and MonadBaseControl instances manually. It's actually not too
>> difficult; ju
Michael Snoyman wrote:
> I just spent a fair amount of time yesterday upgrading packages to
> monad-control 0.3. What I had to do was add in the MonadTransControl
> and MonadBaseControl instances manually. It's actually not too
> difficult; just copy out the instance for StateT and make a few
> cha
On Tue, Dec 6, 2011 at 5:03 AM, Joey Hess wrote:
> I'm trying to convert from 0.2 to 0.3, but in way over my head.
>
> {-# LANGUAGE GeneralizedNewtypeDeriving #-}
> newtype Annex a = Annex { runAnnex :: StateT AnnexState IO a }
> deriving (
> Monad,
> MonadIO,
I'm trying to convert from 0.2 to 0.3, but in way over my head.
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
newtype Annex a = Annex { runAnnex :: StateT AnnexState IO a }
deriving (
Monad,
MonadIO,
-- MonadControlIO
MonadBaseC
On 12/2/11 7:35 PM, Bas van Dijk wrote:
On 3 December 2011 00:45, Bas van Dijk wrote:
* 60 times faster than the previous release!
Here are some benchmark results that compare the original monad-peel,
the previous monad-control-0.2.0.3 and the new monad-control-0.3:
http://basvandijk.github.
Bas van Dijk wrote:
> It provides lifted versions of functions from the base library.
> Currently it exports the following modules:
>
> * Control.Exception.Lifted
> * Control.Concurrent.Lifted
> * Control.Concurrent.MVar.Lifted
> * System.Timeout.Lifted
>
> These are just modules which people hav
On 3 December 2011 00:45, Bas van Dijk wrote:
> Note that Peter Simons just discovered that these packages don't build
> with GHC-7.0.4 (https://github.com/basvandijk/monad-control/issues/3).
> I just committed some fixes which enable them to be build on GHC >=
> 6.12.3. Hopefully I can release th
On 3 December 2011 10:18, Herbert Valerio Riedel wrote:
> btw, how did you manage to get measurements from 2 different versions of
> the same library (monad-control 0.3 and 0.2.0.3) into a single report?
By renaming the old package to monad-control2 and using the
PackageImports extension.
I do w
On Sat, 2011-12-03 at 01:35 +0100, Bas van Dijk wrote:
> Here are some benchmark results that compare the original monad-peel,
> the previous monad-control-0.2.0.3 and the new monad-control-0.3:
>
> http://basvandijk.github.com/monad-control.html
>
> Note that the benchmarks use Bryan O'Sullivan'
On 3 December 2011 00:45, Bas van Dijk wrote:
> * 60 times faster than the previous release!
Here are some benchmark results that compare the original monad-peel,
the previous monad-control-0.2.0.3 and the new monad-control-0.3:
http://basvandijk.github.com/monad-control.html
Note that the benc
Hello,
I just released monad-control-0.3. The package for lifting control
operations (like catch, bracket, mask, alloca, timeout, forkIO,
modifyMVar, etc.) through monad transformers:
http://hackage.haskell.org/package/monad-control-0.3
It has a new and improved API which is:
* easier to unders
19 matches
Mail list logo