Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-06 Thread Bas van Dijk
On 6 December 2011 04:03, Joey Hess j...@kitenet.net 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,
                -- MonadControlIO
                MonadBaseControl IO
        )

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
import Control.Monad.Trans.State
import Control.Monad.IO.Class

newtype Annex a = Annex { runAnnex :: StateT AnnexState IO a }
   deriving (Applicative, Functor, Monad, MonadIO)

data AnnexState = AnnexState

instance MonadBase IO Annex where
liftBase = Annex . liftBase

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

When I have some time I will add some better documentation to monad-control.

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-06 Thread Bas van Dijk
On 6 December 2011 09:12, Bas van Dijk v.dijk@gmail.com 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 restoreM method:

   restoreM = Annex . restoreM . unStAnnex

unStAnnex (StAnnex st) = st

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-06 Thread Bas van Dijk
On 6 December 2011 05:06, Michael Snoyman mich...@snoyman.com 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 MonadTransControl instance of the
RWST transformer:

instance MonadTransControl (GGWidget master) where
newtype StT (GGWidget master) a =
StWidget {unStWidget :: StT (GWInner master) a}
liftWith f = GWidget $ liftWith $ \run -
   f $ liftM StWidget . run . unGWidget
restoreT = GWidget . restoreT . liftM unStWidget

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-06 Thread Michael Snoyman
On Tue, Dec 6, 2011 at 11:49 AM, Bas van Dijk v.dijk@gmail.com wrote:
 On 6 December 2011 05:06, Michael Snoyman mich...@snoyman.com 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 MonadTransControl instance of the
 RWST transformer:

 instance MonadTransControl (GGWidget master) where
    newtype StT (GGWidget master) a =
        StWidget {unStWidget :: StT (GWInner master) a}
    liftWith f = GWidget $ liftWith $ \run -
                   f $ liftM StWidget . run . unGWidget
    restoreT = GWidget . restoreT . liftM unStWidget

 Cheers,

 Bas

Thanks Bas, I was just in the process of converting Widget from being
a RWS to a Writer, and your code made it much simpler :).

Michael

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-06 Thread Bas van Dijk
On 6 December 2011 12:59, Michael Snoyman mich...@snoyman.com wrote:
 On Tue, Dec 6, 2011 at 11:49 AM, Bas van Dijk v.dijk@gmail.com wrote:
 On 6 December 2011 05:06, Michael Snoyman mich...@snoyman.com 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 MonadTransControl instance of the
 RWST transformer:

 instance MonadTransControl (GGWidget master) where
    newtype StT (GGWidget master) a =
        StWidget {unStWidget :: StT (GWInner master) a}
    liftWith f = GWidget $ liftWith $ \run -
                   f $ liftM StWidget . run . unGWidget
    restoreT = GWidget . restoreT . liftM unStWidget

 Cheers,

 Bas

 Thanks Bas, I was just in the process of converting Widget from being
 a RWS to a Writer, and your code made it much simpler :).

 Michael

Do you think it's useful to have the following two utility functions
for defining a MonadTransControl instance for your own monad
transformer provided that your transformers is defined in terms of
another transformer:

defaultLiftWith ∷ (Monad m, MonadTransControl tInner)
⇒ (tInner m α → t m α)  -- ^ Constructor
→ (∀ β n. t n β → tInner n β)   -- ^ Deconstructor
→ (∀ β. StT tInner β → StT t β) -- ^ State constructor
→ ((Run t → m α) → t m α)
defaultLiftWith con deCon st = \f → con $ liftWith $ \run →
  f $ liftM st ∘ run ∘ deCon

defaultRestoreT ∷ (Monad m, MonadTransControl tInner)
⇒ (tInner m α → t m α)  -- ^ Constructor
→ (StT t α  → StT tInner α) -- ^ State deconstructor
→ (m (StT t α) → t m α)
defaultRestoreT con unSt = con ∘ restoreT ∘ liftM unSt

For example in your case you would use these as follows:

instance MonadTransControl (GGWidget master) where
newtype StT (GGWidget master) a =
StWidget {unStWidget :: StT (GWInner master) a}
liftWith = defaultLiftWith GWidget unGWidget StWidget
restoreT = defaultRestoreT GWidget unStWidget

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-06 Thread Michael Snoyman
On Tue, Dec 6, 2011 at 3:03 PM, Bas van Dijk v.dijk@gmail.com wrote:
 On 6 December 2011 12:59, Michael Snoyman mich...@snoyman.com wrote:
 On Tue, Dec 6, 2011 at 11:49 AM, Bas van Dijk v.dijk@gmail.com wrote:
 On 6 December 2011 05:06, Michael Snoyman mich...@snoyman.com 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 MonadTransControl instance of the
 RWST transformer:

 instance MonadTransControl (GGWidget master) where
    newtype StT (GGWidget master) a =
        StWidget {unStWidget :: StT (GWInner master) a}
    liftWith f = GWidget $ liftWith $ \run -
                   f $ liftM StWidget . run . unGWidget
    restoreT = GWidget . restoreT . liftM unStWidget

 Cheers,

 Bas

 Thanks Bas, I was just in the process of converting Widget from being
 a RWS to a Writer, and your code made it much simpler :).

 Michael

 Do you think it's useful to have the following two utility functions
 for defining a MonadTransControl instance for your own monad
 transformer provided that your transformers is defined in terms of
 another transformer:

 defaultLiftWith ∷ (Monad m, MonadTransControl tInner)
                ⇒ (tInner m α → t m α)          -- ^ Constructor
                → (∀ β n. t n β → tInner n β)   -- ^ Deconstructor
                → (∀ β. StT tInner β → StT t β) -- ^ State constructor
                → ((Run t → m α) → t m α)
 defaultLiftWith con deCon st = \f → con $ liftWith $ \run →
                                      f $ liftM st ∘ run ∘ deCon

 defaultRestoreT ∷ (Monad m, MonadTransControl tInner)
                ⇒ (tInner m α → t m α)      -- ^ Constructor
                → (StT t α  → StT tInner α) -- ^ State deconstructor
                → (m (StT t α) → t m α)
 defaultRestoreT con unSt = con ∘ restoreT ∘ liftM unSt

 For example in your case you would use these as follows:

 instance MonadTransControl (GGWidget master) where
    newtype StT (GGWidget master) a =
        StWidget {unStWidget :: StT (GWInner master) a}
    liftWith = defaultLiftWith GWidget unGWidget StWidget
    restoreT = defaultRestoreT GWidget unStWidget

 Bas

I don't have a strong opinion, but it sounds like a net win, assuming
the documentation clearly explains how they are supposed to be used.

Michael

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-06 Thread Joey Hess
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
 import Control.Monad.Trans.State
 import Control.Monad.IO.Class
 
 newtype Annex a = Annex { runAnnex :: StateT AnnexState IO a }
deriving (Applicative, Functor, Monad, MonadIO)
 
 data AnnexState = AnnexState
 
 instance MonadBase IO Annex where
 liftBase = Annex . liftBase
 
 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
 
 When I have some time I will add some better documentation to monad-control.

Hmm, very close. With -Wall, I get:

Annex.hs:54:10:
Warning: No explicit method nor default method for `restoreM'
In the instance declaration for `MonadBaseControl IO Annex'

And my program crashes at runtime (!)

No instance nor default method for class operation 
Control.Monad.Trans.Control.restoreM

-- 
see shy jo


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-06 Thread Joey Hess
Bas van Dijk wrote:
 On 6 December 2011 09:12, Bas van Dijk v.dijk@gmail.com 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 restoreM method:
 
restoreM = Annex . restoreM . unStAnnex
 
 unStAnnex (StAnnex st) = st

Aha! Thanks again.

-- 
see shy jo


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-05 Thread Joey Hess
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
MonadBaseControl IO
)

I added that after seeing this when I changed some code to use
the new liftBaseOp instead of liftIOOp. (They're equivilant, right?)

No instance for (MonadBaseControl IO Annex)
 arising from a use of `liftBaseOp'

But with ghc 7.0.4, the derivation fails:

Annex.hs:45:17:
Can't make a derived instance of `MonadBaseControl IO Annex'
  (even with cunning newtype deriving):
  the class has associated types
In the newtype declaration for `Annex'

The only way I can find to make my code compile is to lose the newtype.
But of course that makes for some ugly type messages.

-- 
see shy jo


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-05 Thread Michael Snoyman
On Tue, Dec 6, 2011 at 5:03 AM, Joey Hess j...@kitenet.net 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,
                -- MonadControlIO
                MonadBaseControl IO
        )

 I added that after seeing this when I changed some code to use
 the new liftBaseOp instead of liftIOOp. (They're equivilant, right?)

    No instance for (MonadBaseControl IO Annex)
         arising from a use of `liftBaseOp'

 But with ghc 7.0.4, the derivation fails:

 Annex.hs:45:17:
    Can't make a derived instance of `MonadBaseControl IO Annex'
      (even with cunning newtype deriving):
      the class has associated types
    In the newtype declaration for `Annex'

 The only way I can find to make my code compile is to lose the newtype.
 But of course that makes for some ugly type messages.

 --
 see shy jo

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


Hi Joey,

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
changes. Be warned that Bas used some tricky CPP stuff, however, which
you'll have to unwind ;).

Michael

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-05 Thread Joey Hess
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
 changes. Be warned that Bas used some tricky CPP stuff, however, which
 you'll have to unwind ;).

I forgot to mention that I tried doing that, based on the example in the
haddock, but failed miserably. Care to share a working example, perhaps
in the form of a patch to the monad-control haddock? :)

-- 
see shy jo


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-05 Thread Michael Snoyman
On Tue, Dec 6, 2011 at 6:04 AM, Joey Hess j...@kitenet.net 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; just copy out the instance for StateT and make a few
 changes. Be warned that Bas used some tricky CPP stuff, however, which
 you'll have to unwind ;).

 I forgot to mention that I tried doing that, based on the example in the
 haddock, but failed miserably. Care to share a working example, perhaps
 in the form of a patch to the monad-control haddock? :)

 --
 see shy jo

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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-03 Thread Herbert Valerio Riedel
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's excellent new
 criterion-0.6 package.

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?


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-03 Thread Bas van Dijk
On 3 December 2011 10:18, Herbert Valerio Riedel h...@gnu.org 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 wonder why it's not possible to use two different versions of the
same package at the same time.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-03 Thread Bas van Dijk
On 3 December 2011 00:45, Bas van Dijk v.dijk@gmail.com 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 these fixes this weekend.

I just released the fixes:

http://hackage.haskell.org/package/monad-control-0.3.0.1
http://hackage.haskell.org/package/lifted-base-0.1.0.1

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-03 Thread Ertugrul Söylemez
Bas van Dijk v.dijk@gmail.com 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 have needed in the past. If you
 need a lifted version of some function, just ask me to add it or send
 me a patch.

 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 these fixes this weekend.

Just in time!  The forkable-monad library seems to fail with base
libraries more recent than mine, and I really need a generalized
forkIO. =)

Thanks for your great work.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


signature.asc
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-03 Thread wren ng thornton

On 12/2/11 7:35 PM, Bas van Dijk wrote:

On 3 December 2011 00:45, Bas van Dijkv.dijk@gmail.com  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 benchmarks use Bryan O'Sullivan's excellent new
criterion-0.6 package.



Those are some beautiful benchmarks. Not only is it much faster, but the 
distribution is much more peaked, which is always a good thing since it 
makes the performance more predictable. Kudos.


--
Live well,
~wren

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-02 Thread Bas van Dijk
On 3 December 2011 00:45, Bas van Dijk v.dijk@gmail.com 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 benchmarks use Bryan O'Sullivan's excellent new
criterion-0.6 package.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe