[Haskell-cafe] Re: Re: Re: monad subexpressions

2007-08-03 Thread Chris Smith
Neil Mitchell [EMAIL PROTECTED] wrote:
  Right.  In effect, as a matter of fact, the notation
 
  x - a
 
  would become equivalent to
 
  let x = (- a)
 
 Hmm, interesting. Consider:
 
 let x = 12
 let x = (- x)

Okay, so the desugaring process wouldn't terminate in that case!  One 
could either: (a) try to retain the equivalence in theory, but make it 
illegal to use x in a monadic subexpression when defining x; (b) we 
could abandon my claim that they are equivalent.

 I'm not convinced either, a nice concrete example would let people
 ponder this a bit more.

I tried to provide something in my response to Simon.  Here it is again:

 One could sugar:

 do tax - getTax
return $ map (\price - price * (1 + tax)) bill

 into:

 do return $ map (\price - price * (1 + (- getTax))) someNums

 What is nice to note is that all your answers
 to my questions matched perfectly with what I thought should happen.

That is nice.  I'm still very uncomfortable with the - syntax (a 
complete flip for me since this morning!); and a little uneasy about the 
use of case, if, lambdas, etc.  Time to keep thinking, I guess.

I'd like to take Simon's suggestion and do a wiki page about this; but 
it should probably be on the Haskell prime wiki, no?  I'm not entirely 
clear on how to get an account there.  I could add it to HaskellWiki, 
but I think that would be the wrong place for it.

-- 
Chris Smith

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


[Haskell-cafe] Re: Re: Re: monad subexpressions

2007-08-03 Thread Chris Smith
david48 [EMAIL PROTECTED] wrote:
 On 8/3/07, Neil Mitchell [EMAIL PROTECTED] wrote:
 
  Hmm, interesting. Consider:
 
  let x = 12
  let x = (- x)
 
 Wouldn't that be forbidden ?
 
 I'd expect the x in ( - x ) have to be of type m a.
 

Yes, unless of course you did:

instance (Monad m, Num n) = Num (m n)

or some such nonsense. :)

 If you meant :
 
 x - return 12
 let x = ( - x )

This would be equally wrong.  Perhaps you meant:

do let x = return 12
   let x = (- x)
   ...

Then this would become:

do let x = return 12
   t1 - x
   let x = t1
   ...

Which is, in turn:

let x = return 12 in x = (\t1 - let x = t1 in ...)

-- 
Chris Smith

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


Re: [Haskell-cafe] Re: Re: Re: monad subexpressions

2007-08-03 Thread Josef Svenningsson
On 8/3/07, Chris Smith [EMAIL PROTECTED] wrote:
 Neil Mitchell [EMAIL PROTECTED] wrote:
  I'm not convinced either, a nice concrete example would let people
  ponder this a bit more.

 I tried to provide something in my response to Simon.  Here it is again:

  One could sugar:

  do tax - getTax
 return $ map (\price - price * (1 + tax)) bill

  into:

  do return $ map (\price - price * (1 + (- getTax))) someNums

I think what Simon is worried about here is that the syntax in the
latter expression suggests that the effects of getTax will be
performed every time the lambda is applied. After all getTax appears
inside the lambda. But in fact is the side effects will only be
performed once. I agree with Simon that (- getTax) shouldn't be
promoted outside a lambda.

Fwiw, I'm all in favor for some new piece of syntax for this problem.

Cheers,

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


Re: [Haskell-cafe] Re: Re: Re: monad subexpressions

2007-08-03 Thread Neil Mitchell
Hi

  let x = 12
  let x = (- x)

 Okay, so the desugaring process wouldn't terminate in that case!  One
 could either: (a) try to retain the equivalence in theory, but make it
 illegal to use x in a monadic subexpression when defining x; (b) we
 could abandon my claim that they are equivalent.

This example isn't intended to be about termination of the desugaring,
or about types etc - the only point is to note the change in the
lexical scoping rules that (-) gives. I'll try and state my concern
more clearly:

let x = a

In this expression, x is available for use within a, since let is
recursive. This allows us to write:

let xs = paws : xs

With the end result that xs is bound to [paws,paws,paws,paws...

Now consider:

let x = (- a)

With the proposed desugaring we obtain:

temp - a
let x = temp

Now x is NOT in scope within the expression a! We have changed the
static lexical scoping, and only within the brackets. This behaviour
is (in my opinion) horrid. A quick poll of people in my office lead us
all to believe that this issue means you should not be allowed (-)
within a do's let statement.

This leads us to a second problem, floating these monadic expressions
outside any binding:

do case x of
 [] - return 1
 (y:ys) - f (- g y)

Here, the proposed desugaring does not work, since y is not in scope
where we move the element to.

Perhaps this leads to the conclusion that monadic subexpressions
should not be allowed inside any binding group, including let, case or
lambda.

Thanks

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


Re: [Haskell-cafe] Re: Re: Re: monad subexpressions

2007-08-03 Thread Neil Mitchell
Hi

 if you write :

 let x = (-a):x

 is it possible that is desugars into :

 temp -a
 let x = temp:x

 that would'nt work ?

That would work, since 'a' doesn't refer to 'x'. I can't think of a
real example where it becomes an issue, but the scope within 'a' has
changed.

 Also :

  do case x of
   [] - return 1
   (y:ys) - f (- g y)

 Is it not possible that is desugars to

 do case x of
  [] - return 1
  (y:ys) - g y = \temp - f temp

See the rule about always binding to the previous line of a do block.
This case then violates that.

Thanks

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


Re: [Haskell-cafe] Re: Re: Re: monad subexpressions

2007-08-03 Thread david48
On 8/3/07, Neil Mitchell [EMAIL PROTECTED] wrote:

 temp - a
 let x = temp

if you write :

let x = (-a):x

is it possible that is desugars into :

temp -a
let x = temp:x

that would'nt work ?
I realize I may be asking dumb questions but being dumb never harmed
anyone so :)


Also :

 do case x of
  [] - return 1
  (y:ys) - f (- g y)

Is it not possible that is desugars to

do case x of
 [] - return 1
 (y:ys) - g y = \temp - f temp



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

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


Re: [Haskell-cafe] Re: Re: Re: monad subexpressions

2007-08-03 Thread Neil Mitchell
Hi

   do case x of
[] - return 1
(y:ys) - g y = \temp - f temp

  See the rule about always binding to the previous line of a do block.
  This case then violates that.

 I assumed that the example was equivalent to :

 do case x of
  [] - return 1
  (y:ys) - do f (- g y)

 Shouldn't the rule work then ?

If the do was inserted, then yes, this would work. Without it, it
doesn't. Perhaps this makes a restriction to not inside
case/let/lambda not that severe, since usually an additional do could
be inserted.

Thanks

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


Re: [Haskell-cafe] Re: Re: Re: monad subexpressions

2007-08-03 Thread Antoine Latter
On 8/3/07, Chris Smith [EMAIL PROTECTED] wrote:
 Yes, unless of course you did:

 instance (Monad m, Num n) = Num (m n)

 or some such nonsense. :)

I decided to take this as a dare - at first I thought it would be easy
to declare (Monad m, Num n) = m n to be an instance of Num (just lift
or return the operators as necessary), but I ran into trouble once I
realized I needed two things I wasn't going to get:

An instance of Eq (m n), and an instance of Show (m n) for all monads
m.  Eq would need a function of the form:

(==) :: Monad m = m a - m a - Bool

and Show would need a function of type m a - String

There's no way I'm getting a function of those types using return and
join to operate on the monad.

So, there went that idea.

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


Re: [Haskell-cafe] Re: Re: Re: monad subexpressions

2007-08-03 Thread Twan van Laarhoven

Antoine Latter wrote:


On 8/3/07, Chris Smith [EMAIL PROTECTED] wrote:


Yes, unless of course you did:

   instance (Monad m, Num n) = Num (m n)

or some such nonsense. :)



I decided to take this as a dare - at first I thought it would be easy
to declare (Monad m, Num n) = m n to be an instance of Num (just lift
or return the operators as necessary), but I ran into trouble once I
realized I needed two things I wasn't going to get:

An instance of Eq (m n), and an instance of Show (m n) for all monads
m.  Eq would need a function of the form:

(==) :: Monad m = m a - m a - Bool

and Show would need a function of type m a - String


What about Eq1 and Show1 classes? In the same vein as Typeable1:

 class Eq1 f where
  eq1  :: Eq a = f a - f a - Bool
  neq1 :: Eq a = f a - f a - Bool

 class Show1 f where
  show1  :: Show a = f a - String
  showsPrec1 :: Show a = Int - f a - ShowS

Now you can declare the Num instance:

 instance (Monad m, Eq1 m, Show1 m, Num n) = Num (m n) where
  (+) = liftM2 (+)
  (-) = liftM2 (-)
  (*) = liftM2 (*)
  abs = liftM abs
  signum = liftM signum
  negate = ligtM negate
  fromInteger = return . fromInteger

And just to show that such instances can exist:

 instance Eq1 [] where
   eq1  = (==)
   neq1 = (/=)

 instance Show1 [] where
   show1 = show
   showsPrec1 = showsPrec


Note: All of this is untested code.

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