On Sun, Mar 30, 2008 at 1:09 PM, Henning Thielemann
<[EMAIL PROTECTED]> wrote:
> It's like working in the List monad mainly, collapsing duplicates from
> time to time, right?
Sort of. You can look at it that way and get a basic understanding of
what's going on.
A slightly more accurate analysi
On Tue, 25 Mar 2008, Ryan Ingram wrote:
settest :: S.Set Int
settest = runSetM $ do
x <- mplus (mplus mzero (return 2)) (mplus (return 2) (return 3))
return (x+3)
-- fromList [5,6]
What this does under the hood is treat the computation on each element of the
set separately, except at pr
On 3/28/08, Dan Weston <[EMAIL PROTECTED]> wrote:
> I'm having trouble embedding unconstrained monads into the NewMonad:
> Is there some trick (e.g. newtype boxing/unboxing) to get all the
> unconstrained monads automatically instanced? Then the do notation could
> be presumably remapped to the ne
I'm having trouble embedding unconstrained monads into the NewMonad:
> {-# LANGUAGE ...,UndecidableInstances #-}
>
> instance Monad m => Suitable m v where
> data Constraints m v = NoConstraints
> constraints _= NoConstraints
>
> instance Monad m => NewMonad m where
> newRetur
On Fri, 28 Mar 2008, Wolfgang Jeltsch wrote:
But it is possible to give a construction of an Ord dictionary from an
AssociatedMonad dictionary. See the attached code. It works like a
charm. :-)
This is really cool, and with much wider applicability than restricted
monads; it gives us a gen
On Fri, 28 Mar 2008, Wolfgang Jeltsch wrote:
But it is possible to give a construction of an Ord dictionary from an
AssociatedMonad dictionary. See the attached code. It works like a
charm. :-)
Yeah, type families! In which GHC release they will be included?
Sometimes I wonder how many s
Am Montag, 24. März 2008 20:47 schrieb Henning Thielemann:
> […]
> Here is another approach that looks tempting, but unfortunately does not
> work, and I wonder whether this can be made working.
>
> module RestrictedMonad where
>
> import Data.Set(Set)
> import qualified Data.Set as Set
>
> class
On Tue, 25 Mar 2008, Ryan Ingram wrote:
I was experimenting with Prompt today and found that you can get a
"restricted monad" style of behavior out of a regular monad using Prompt:
I recently developed a similar trick:
http://hsenag.livejournal.com/11803.html
It uses the regular MonadPlus r
I was experimenting with Prompt today and found that you can get a
"restricted monad" style of behavior out of a regular monad using Prompt:
> {-# LANGUAGE GADTs #-}
> module SetTest where
> import qualified Data.Set as S
Prompt is available from
http://hackage.haskell.org/cgi-bin/hackage-scripts
The following code solves exactly the problem of implementing
(restricted) MonadPlus in terms of Data.Set:
http://okmij.org/ftp/Haskell/DoRestrictedM.hs
The code is written to demonstrate the do-notation. We write the
monadic code as usual:
> test1s_do () = do
> x <- return "a"
> re
The blog article
http://www.randomhacks.net/articles/2007/03/15/data-set-monad-haskell-macros
describes a variant of the Monad class which allows to restrict the type
of the monadic result, in order to be able to make Data.Set an instance of
Monad (requiring Ord constraint for the monadic re
11 matches
Mail list logo