[Haskell-cafe] the trivial monad- thoughts and a question

2008-01-12 Thread Brian Hurt


So, I've been playing around with what I call the trivial monad:

module TrivialMonad where

data TrivialMonad a = M a

recover :: TrivialMonad a - a
recover (M x) = x

instance Monad TrivialMonad where

(M x) = f = f x
(M x)  f = f
return x = M x
fail s = undefined

This is actually a surprisingly usefull little sucker- it allows you to 
demonadify code.  Which is usefull when you have some places where you 
want to use the code within a monad, and some places where you don't.  You 
write the base bit of code monadically, and then demonadify it as needed.


The first question I have is it is possible to implement this guy without 
wrapping the value in a constructor?  What I'd like to do is replace the:

data TrivialMonad a = M a
with something like:
type TrivialMonad a = a
and then be able to junk the recover function.

The second question I have is: is there any hope of getting something like 
this into the standard library?


Thanks,
Brian

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


Re: [Haskell-cafe] the trivial monad- thoughts and a question

2008-01-12 Thread Isaac Dupree

Brian Hurt wrote:
The second question I have is: is there any hope of getting something 
like this into the standard library?


the newtype Identity in module Control.Monad.Identity in package `mtl` 
is what you describe:

http://www.haskell.org/ghc/docs/latest/html/libraries/mtl/Control-Monad-Identity.html

in other words, it already is practically in the standard library.

The type-synonym technique doesn't work very well because, e.g., is 
(TrivialMonad (IO ())) = an IO function or a Trivial function?  It 
has been thoroughly discussed before, IIRC...


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


Re: [Haskell-cafe] the trivial monad- thoughts and a question

2008-01-12 Thread Daniel Fischer
Am Sonntag, 13. Januar 2008 01:47 schrieb Brian Hurt:
 So, I've been playing around with what I call the trivial monad:

 module TrivialMonad where

 data TrivialMonad a = M a

 recover :: TrivialMonad a - a
 recover (M x) = x

 instance Monad TrivialMonad where

   (M x) = f = f x
   (M x)  f = f
   return x = M x
   fail s = undefined

 This is actually a surprisingly usefull little sucker- it allows you to
 demonadify code.  Which is usefull when you have some places where you
 want to use the code within a monad, and some places where you don't.  You
 write the base bit of code monadically, and then demonadify it as needed.

 The first question I have is it is possible to implement this guy without
 wrapping the value in a constructor?  What I'd like to do is replace the:
   data TrivialMonad a = M a
 with something like:
   type TrivialMonad a = a
 and then be able to junk the recover function.

No, but you can use a newtype instead of data, so you have no run-time 
overhead.


 The second question I have is: is there any hope of getting something like
 this into the standard library?

It's already there:
Control.Monad.Identity


 Thanks,
 Brian

Cheers,
Daniel

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


Re: [Haskell-cafe] the trivial monad- thoughts and a question

2008-01-12 Thread Luke Palmer
On Jan 13, 2008 12:47 AM, Brian Hurt [EMAIL PROTECTED] wrote:
 So, I've been playing around with what I call the trivial monad:

 module TrivialMonad where

 data TrivialMonad a = M a

Better to use newtype here; then it really is operationally equivalent
to using just a, except that it's possible to implement a monad
instance for it (see below).

 The first question I have is it is possible to implement this guy without
 wrapping the value in a constructor?  What I'd like to do is replace the:
 data TrivialMonad a = M a
 with something like:
 type TrivialMonad a = a
 and then be able to junk the recover function.

Nope.  That would mean that every type is a monad, which would cause endless
troubles for type inference.  For example, what monad is (putStrLn x) a
member of:  IO () or TrivialMonad (IO ())  (or even TrivialMonad
(TrivialMonad (IO(?

 The second question I have is: is there any hope of getting something like
 this into the standard library?

Control.Monad.Identity, perhaps?

http://www.haskell.org/ghc/docs/latest/html/libraries/mtl/Control-Monad-Identity.html

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


Re: [Haskell-cafe] the trivial monad- thoughts and a question

2008-01-12 Thread Miguel Mitrofanov
The first question I have is it is possible to implement this guy  
without wrapping the value in a constructor?


No.

The second question I have is: is there any hope of getting  
something like this into the standard library?


It's there already. It's called Identity monad.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe