Re: Monads and Maybe

2003-08-22 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 C T McBride [EMAIL PROTECTED] wrote:

 My point, however, is not to use $ with that type, but the more general
 
   class Fun f where
 eta :: x - f x
 ($) :: f (s - t) - f s - f t
 
 Is there a better name for Fun? Is it ancient and venerable?

Ancient and venerable almost certainly, but not well-known. Lost 
Knowledge of Haskell, perhaps. People keep reinventing this class (which 
is a subclass of Functor btw).

In HBase I call it FunctorApplyReturn. My hierarchy looks more or less 
like this:

  class HasReturn f where
return :: a - f a -- eta

  class Functor f where
fmap :: (a - b) - f a - f b

  class (Functor f) = FunctorApply f where
fApply :: f (a - b) - f a - f b   -- ($)
fPassTo :: f a - f (a - b) - f b
() :: f a - f b - f b
fPassTo = liftF2 (\a ab - ab a)

  liftF2 func fa = fApply (fmap func fa)

  class (FunctorApply f,HasReturn f) = FunctorApplyReturn f

  instance (FunctorApply f,HasReturn f) = FunctorApplyReturn f

  class (FunctorApplyReturn f) = Monad f where
(=) :: f a - (a - f b) - f b
fail :: String - f a;
fail = error;
 
Certain functions that seem to require Monads actually work with any 
FunctorApplyReturn. For instance:

  class (Functor f) = ExtractableFunctor f where
fExtract :: (FunctorApplyReturn m) = f (m a) - m (f a)

  for :: (ExtractableFunctor f,FunctorApplyReturn m) =
(a - m b) - (f a - m (f b));
  for foo fa = fExtract (fmap foo fa)

All sorts of useful types such as [] and Maybe can be made 
ExtractableFunctors. And then 'for' can iterate on them.

IMO something like all this should be in the standard libraries. The 
downside is that people would have to make instances for HasReturn, 
Functor and FunctorApply with every Monad instance.

-- 
Ashley Yakeley, Seattle WA

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Monads and Maybe

2003-08-21 Thread C T McBride
Hi

  Or, more generally,
 
infixl 9 $
 
($) :: Monad m = m (s - t) - m s - m t
mf $ ms =
  do f - mf
 s - ms
 return (f s)

 or just liftM2 ($)
 or just ap

OK, I'm a bad citizen and I never look things up in the library. If it
isn't in the Gentle Introduction (circa 1999) or some old Hugs -98
extension guide, I probably don't know about it. One of my favourite
things about Haskell is that you can get a long way without troubling a
library. Why is this? I suspect it's because Haskell has neater ways of
expressing and manipulating data (especially in sum types) than, say,
Java.

My point, however, is not to use $ with that type, but the more general

  class Fun f where
eta :: x - f x
($) :: f (s - t) - f s - f t

Is there a better name for Fun? Is it ancient and venerable? Am I an
ignoramus twice over?

Sure, you can take

  instance Monad m = Fun m where
eta = return
($) = liftM2 ($)

but you don't always want to. Consider the following non-monadic examples

(1) vectorizing

  instance Fun [] where
eta = repeat
($) = zipWith ($)

(2) flattening

  newtype K x anything = K x

  class Monoid x where
zero :: x
(+) :: x - x - x

  instance Monoid x = Fun (K x) where
eta _ = K zero
K x $ K y = K (x + y)

Modulo some packing and unpacking, this buys you flattening for the price
of lifting map. (Is this what Lambert Meertens is talking about in his
paper `Functor Pulling'?)

(3) composition

  newtype Comp g h x = Comp (g (h x))

  instance (Fun g,Fun h) = Fun (Comp g h) where
eta x = Comp (eta (eta x))
Comp ghf $ Comp ghs = Comp (eta ($) ghf $ ghs)

That's to say, you can define $ for the composition of two Funs, hence
of two Monads, but, if I recall correctly, it's rather harder to define
= for the composition of two Monads.

(4) parsing (controversial?)

  I claim that you can write plausible parsers with some suitable
  type constructor, eg

newtype Parser x = Parser (String - Maybe (x,String))

  given only Fun Parser and Monoid (Parser x). Typically, one writes

  syntax :: Parser syntax
  syntax = eta rule1 $ syntax11 $ ... $ syntax1k_1
   + ... +
   eta rulen $ syntaxn1 $ ... $ syntaxnk_n

  where syntaxij :: Parser syntaxij
  and   rulei :: syntaxi1 - ... - syntaxik_i - syntax

The point, in general, is to make lifted functional programming look as
much like functional programming as possible. Of course, when something is
both Monad and Fun, you can freely mix with the more imperative-style do.

Cheers

Conor
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Monads and Maybe

2003-08-21 Thread Jon Cast

Konrad Hinsen [EMAIL PROTECTED] wrote:

 I have been following the recent Monad tutorial discussion with
 interest, and even read the tutorial, which is a useful addition to
 the existing Haskell documentation. So useful in fact that it raises a
 question...
 
 The whole monad mechanism seems to geared towards functions of one
 argument, plus eventually state, that get chained together. How about
 functions with several arguments?
 
 As an example, I'll use the Maybe monad. Suppose I want to write code
 to handle experimental data, in which there might be missing values. I
 might then decide to represent measurements by data of type Maybe
 Double, with missing values represented by Nothing. I could then go
 on to define functions on missing values, which would return Nothing
 when their argument is Nothing, and I could string these functions
 together via the monad mechanism. Fine.  But how would I handle
 e.g. addition of two such values?  The result should be Nothing when
 either of its arguments is Nothing. Is there any mechanism to handle
 that?

Yes.  Many complicated proposals have been made, but there's a
straightforward, general mechanism:

 addMaybe :: Num alpha = Maybe alpha - Maybe alpha - Maybe alpha
 addMaybe a b = a = \x -
b = \y -
return (x + y)

or

 addMaybe a b = do
   x - a
   y - b
   return (x + y)

(Incidentally, monads in Haskell are specified slightly differently than
the Categorical version to enable precisely this sort of pattern.)

Jon Cast

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Monads and Maybe

2003-08-21 Thread Martin Norbäck
tor 2003-08-21 klockan 22.26 skrev Jon Cast:
 Yes.  Many complicated proposals have been made, but there's a
 straightforward, general mechanism:
 
  addMaybe :: Num alpha = Maybe alpha - Maybe alpha - Maybe alpha
  addMaybe a b = a = \x -
 b = \y -
 return (x + y)
 
 or
 
  addMaybe a b = do
x - a
y - b
return (x + y)

or

addMaybe = Monad.liftM2 (+)

I personally use those monadic lifting functions a lot. Monad.sequence
combined with list comprehension is another favorite.

Regards,

Martin
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Monads and Maybe

2003-08-20 Thread Derek Elkins
On Tue, 19 Aug 2003 14:09:16 +0100 (BST)
C T McBride [EMAIL PROTECTED] wrote:

 Hi
 
   As an example, I'll use the Maybe monad. Suppose I want to write
   code to handle experimental data, in which there might be missing
   values. I might then decide to represent measurements by data of
   type Maybe Double, with missing values represented by Nothing.
   I could then go on to define functions on missing values, which
   would return Nothing when their argument is Nothing, and I
   could string these functions together via the monad mechanism.
   Fine.  But how would I handle e.g. addition of two such values?
   The result should be Nothing when either of its arguments
   isNothing. Is there any mechanism to handle that?
 
  Yes, liftM2. Defined in module Monad (or Data.Monad resp.).
 
   Konrad.
 
  Wolfgang
 
 Or, more generally,
 
   infixl 9 $
 
   ($) :: Monad m = m (s - t) - m s - m t
   mf $ ms =
 do f - mf
s - ms
return (f s)

or just liftM2 ($)
or just ap

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Monads and Maybe

2003-08-19 Thread Konrad Hinsen
I have been following the recent Monad tutorial discussion with interest, 
and even read the tutorial, which is a useful addition to the existing 
Haskell documentation. So useful in fact that it raises a question...

The whole monad mechanism seems to geared towards functions of one argument, 
plus eventually state, that get chained together. How about functions with 
several arguments?

As an example, I'll use the Maybe monad. Suppose I want to write code to 
handle experimental data, in which there might be missing values. I might 
then decide to represent measurements by data of type Maybe Double, with 
missing values represented by Nothing. I could then go on to define 
functions on missing values, which would return Nothing when their argument 
is Nothing, and I could string these functions together via the monad 
mechanism. Fine.  But how would I handle e.g. addition of two such values? 
The result should be Nothing when either of its arguments is Nothing. Is 
there any mechanism to handle that?

Konrad.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe