Re: Call to arms: lambda-case is stuck and needs your help

2012-07-10 Thread Mikhail Vorozhtsov

On 07/10/2012 01:09 AM, Bardur Arantsson wrote:

On 07/09/2012 06:01 PM, Mikhail Vorozhtsov wrote:

On 07/09/2012 09:52 PM, Twan van Laarhoven wrote:

On 09/07/12 14:44, Simon Marlow wrote:

I now think '\' is too quiet to introduce a new layout context.  The
pressing
need is really for a combination of '\' and 'case', that is
single-argument so
that we don't have to write parentheses.  I think '\case' does the job
perfectly.  If you want a multi-clause multi-argument function, then
give it a
name.


There is an advantage here for \of in favor of \case, namely that
of already introduces layout, while case does not.

Do you think that adding \ + case as a layout herald would
complicate the language spec and/or confuse users? Because it certainly
does not complicate the implementation (there is a patch for \case
already).


Just being anal here, but: The existence of a patch to implement X does
not mean that X doesn't complicate the implemenatation.
In general, yes. But that particular patch[1] uses ~20 lines of pretty 
straightforward (if I'm allowed to say that about the code I wrote 
myself) code to handle layout. Which in my book is not complex at all.


[1] 
http://hackage.haskell.org/trac/ghc/attachment/ticket/4359/one-arg-lambda-case.patch


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Call to arms: lambda-case is stuck and needs your help

2012-07-10 Thread Simon Peyton-Jones
| I strongly favor a solution where lambda-case expressions start with \,
| because this can be generalized to proc expressions from arrow syntax
| simply by replacing the \ with proc.
| 
| Take, for example, the following function definition:
| 
| f (Left  x) = g x
| f (Right y) = h y
| 
| Now, let’s make an arrow version of it:
| 
| f = proc e - case e of
| Left  x - g - x
| Right y - h - y
| 
| It would be great if we could write something like this instead:
| 
| f = proc of
| Left  x - g - x
| Right y - h - y

I don't think I was aware of the proc part.

I think it's very helpful if lambdas start with a lambda, which to me suggests 
\case.  I'm not keen on \of; case says case analysis more clearly. But you 
presumably do not want \proc, because proc is the lambda. So that would leave 
use with \case and proc of as the two constructs.  Perhaps the lesser of 
the evils, but a bit inconsistent.

Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Call to arms: lambda-case is stuck and needs your help

2012-07-10 Thread Mikhail Vorozhtsov

On 07/10/2012 01:53 PM, Simon Peyton-Jones wrote:

| I strongly favor a solution where lambda-case expressions start with \,
| because this can be generalized to proc expressions from arrow syntax
| simply by replacing the \ with proc.
|
| Take, for example, the following function definition:
|
| f (Left  x) = g x
| f (Right y) = h y
|
| Now, let’s make an arrow version of it:
|
| f = proc e - case e of
| Left  x - g - x
| Right y - h - y
|
| It would be great if we could write something like this instead:
|
| f = proc of
| Left  x - g - x
| Right y - h - y

I don't think I was aware of the proc part.

I think it's very helpful if lambdas start with a lambda, which to me suggests \case.  I'm not keen on \of; 
case says case analysis more clearly. But you presumably do not want \proc, because proc is the 
lambda. So that would leave use with \case and proc of as the two constructs.  Perhaps the 
lesser of the evils, but a bit inconsistent.

Why not use proc case?

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Call to arms: lambda-case is stuck and needs your help

2012-07-10 Thread Donn Cave
 I think it's very helpful if lambdas start with a lambda, which to
 me suggests \case.

I'd be interested to hear that explained a little further.  To me it isn't
obvious that `case of' is `a lambda', but it's obvious enough what it is
and how it works (or would work) - it's `case' with type a - b instead
of just b ... and really the backslash just seems to confuse the issue.
I don't remember it from discussions of this proposal in years past.

 ... But you presumably do not want \proc, because proc is the lambda.

I also wondered if `case of' could be equally well generalized to
allow for `proc of', but I would certainly have no idea.

Donn

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Call to arms: lambda-case is stuck and needs your help

2012-07-10 Thread Simon Marlow

On 09/07/2012 17:32, Mikhail Vorozhtsov wrote:

On 07/09/2012 09:49 PM, Simon Marlow wrote:

On 09/07/2012 15:04, Mikhail Vorozhtsov wrote:

and respectively

\case
   P1, P2 - ...
   P3, P4 - ...

as sugar for

\x y - case x, y of
   P1, P2 - ...
   P3, P4 - ...


That looks a bit strange to me, because I would expect

  \case
 P1, P2 - ...
 P3, P4 - ...

to be a function of type (# a, b #) - ...

Hm, maybe I put it slightly wrong. Desugaring is really only a means of
implementation here.


I think the desugaring is helpful - after all, most of the syntactic 
sugar in Haskell is already specified by its desugaring.  And in this 
case, the desugaring helps to explain why the multi-argument version is 
strange.


 Would you still expect tuples for \case if you

didn't see the way `case x, y of ...` was implemented (or thought that
it is a primitive construct)?


Yes, I still think it's strange.  We don't separate arguments by commas 
anywhere else in the syntax; arguments are always separated by whitespace.


Cheers,
Simon

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Imported foreign functions should be strict

2012-07-10 Thread Simon Marlow

On 07/07/2012 05:06, Favonia wrote:

Hi all,

Recently I am tuning one of our incomplete libraries that uses FFI.
After dumping the interface file I realized strictness/demand analysis
failed for imported foreign functions---that is, they are not inferred
to be strict in their arguments. In my naive understanding all
imported foreign functions are strict! Here's a minimum example (with
GHC 7.4.2):

{-# LANGUAGE ForeignFunctionInterface #-}
module Main where
import Foreign.C
foreign import ccall unsafe sin sin' :: CDouble - CDouble

where in the interface file the function sin' will have strictness
U(L) (meaning Unpackable(Lazy)).


This is fine - it means the CDouble is unpacked into its unboxed Double# 
component.  An unboxed value is always represented by L in strictness 
signatures.


Cheers,
Simon

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Call to arms: lambda-case is stuck and needs your help

2012-07-10 Thread Simon Marlow

On 10/07/2012 07:33, Mikhail Vorozhtsov wrote:

On 07/10/2012 01:09 AM, Bardur Arantsson wrote:

On 07/09/2012 06:01 PM, Mikhail Vorozhtsov wrote:

On 07/09/2012 09:52 PM, Twan van Laarhoven wrote:

On 09/07/12 14:44, Simon Marlow wrote:

I now think '\' is too quiet to introduce a new layout context.  The
pressing
need is really for a combination of '\' and 'case', that is
single-argument so
that we don't have to write parentheses.  I think '\case' does the job
perfectly.  If you want a multi-clause multi-argument function, then
give it a
name.


There is an advantage here for \of in favor of \case, namely that
of already introduces layout, while case does not.

Do you think that adding \ + case as a layout herald would
complicate the language spec and/or confuse users? Because it certainly
does not complicate the implementation (there is a patch for \case
already).


Just being anal here, but: The existence of a patch to implement X does
not mean that X doesn't complicate the implemenatation.

In general, yes. But that particular patch[1] uses ~20 lines of pretty
straightforward (if I'm allowed to say that about the code I wrote
myself) code to handle layout. Which in my book is not complex at all.

[1]
http://hackage.haskell.org/trac/ghc/attachment/ticket/4359/one-arg-lambda-case.patch


The need to keep track of the previous token in the lexer *is* ugly though.

Cheers,
Simon

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


How to describe this bug?

2012-07-10 Thread Sönke Hahn
Hi!

I've discovered a strange bug that violates simple equational reasoning.
Basically, something similar to this:

let a = f x
in a == f x

evaluates to False.

I'd like to report this on ghc-trac, but I realised, that I don't know a
good name for behaviour like this. Is there one? Broken referential
transparency, perhaps?

Thanks,
Sönke


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to describe this bug?

2012-07-10 Thread Christopher Done
Depends what the real offending code is. For example, if it contains
unsafePerformIO then it's not a bug.

On 10 July 2012 12:42, Sönke Hahn sh...@cs.tu-berlin.de wrote:
 Hi!

 I've discovered a strange bug that violates simple equational reasoning.
 Basically, something similar to this:

 let a = f x
 in a == f x

 evaluates to False.

 I'd like to report this on ghc-trac, but I realised, that I don't know a
 good name for behaviour like this. Is there one? Broken referential
 transparency, perhaps?

 Thanks,
 Sönke


 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to describe this bug?

2012-07-10 Thread malcolm.wallace
Also, it is more likely to be a buggy instance of Eq, than a real loss of referential transparency.Regards,
MalcolmOn Jul 10, 2012, at 11:49 AM, Christopher Done chrisd...@gmail.com wrote:Depends what the real offending code is. For example, if it contains unsafePerformIO then it's not a bug.  On 10 July 2012 12:42, Sönke Hahn sh...@cs.tu-berlin.de wrote:  Hi!   I've discovered a strange bug that violates simple equational reasoning.  Basically, something similar to this:   let a = f x  in a == f x   evaluates to False.   I'd like to report this on ghc-trac, but I realised, that I don't know a  good name for behaviour like this. Is there one? "Broken referential  transparency", perhaps?   Thanks,  Sönke___  Glasgow-haskell-users mailing list  Glasgow-haskell-users@haskell.org  http://www.haskell.org/mailman/listinfo/glasgow-haskell-users  ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to describe this bug?

2012-07-10 Thread Sönke Hahn
I've attached the code. The code does not make direct use of
unsafePerformIO. It uses QuickCheck, but I don't think, this is a
QuickCheck bug. The used Eq-instance is the one for Float.

I've only managed to reproduce this bug on 32-bit-linux with ghc-7.4.2
when compiling with -O2.

(The code might seem a bit odd, but this is the most boiled down version
I could come up with. Even removing the module Main where line changes
the behaviour.)

Cheers,
Sönke


On 07/10/2012 12:51 PM, malcolm.wallace wrote:
 Also, it is more likely to be a buggy instance of Eq, than a real loss
 of referential transparency.
 
 Regards,
 Malcolm
 
 
 On Jul 10, 2012, at 11:49 AM, Christopher Done chrisd...@gmail.com wrote:
 
 Depends what the real offending code is. For example, if it contains
 unsafePerformIO then it's not a bug.

 On 10 July 2012 12:42, Sönke Hahn sh...@cs.tu-berlin.de
 mailto:sh...@cs.tu-berlin.de wrote:
  Hi!
 
  I've discovered a strange bug that violates simple equational reasoning.
  Basically, something similar to this:
 
  let a = f x
  in a == f x
 
  evaluates to False.
 
  I'd like to report this on ghc-trac, but I realised, that I don't know a
  good name for behaviour like this. Is there one? Broken referential
  transparency, perhaps?
 
  Thanks,
  Sönke
 
 
  ___
  Glasgow-haskell-users mailing list
  Glasgow-haskell-users@haskell.org
 mailto:Glasgow-haskell-users@haskell.org
  http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 mailto:Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 
 
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 




module Main where


import Test.QuickCheck


main :: IO ()
main = quickCheck $ prop 6.0 0.109998815

prop :: Float - Float - Property
prop m x =
let a = x * m
in printTestCase (show a ++  foo)
   (x * m == a)

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to describe this bug?

2012-07-10 Thread Aleksey Khudyakov
On Tue, Jul 10, 2012 at 3:06 PM, Sönke Hahn sh...@cs.tu-berlin.de wrote:
 I've attached the code. The code does not make direct use of
 unsafePerformIO. It uses QuickCheck, but I don't think, this is a
 QuickCheck bug. The used Eq-instance is the one for Float.

 I've only managed to reproduce this bug on 32-bit-linux with ghc-7.4.2
 when compiling with -O2.

It's expected behaviour with floats. Calculations in FPU are done in
maximul precision available.  If one evaluation result is kept in registers
and another has been moved to memory and rounded and move back to registers
number will be not the same indeed.

In short. Never compare floating point number for equality unless you
really know
what are you doing.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Call to arms: lambda-case is stuck and needs your help

2012-07-10 Thread Wolfgang Jeltsch
Am Dienstag, den 10.07.2012, 08:53 +0100 schrieb Simon Marlow:
 On 09/07/2012 17:32, Mikhail Vorozhtsov wrote:
  Would you still expect tuples for \case if you didn't see the way
  `case x, y of ...` was implemented (or thought that it is a
  primitive construct)?
 
 Yes, I still think it's strange.  We don't separate arguments by
 commas anywhere else in the syntax; arguments are always separated by
 whitespace.

This is the point I wanted to make in my e-mail yesterday. Using a comma
here seems to be against established Haskell syntax conventions.

Best wishes,
Wolfgang


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Call to arms: lambda-case is stuck and needs your help

2012-07-10 Thread Wolfgang Jeltsch
Am Dienstag, den 10.07.2012, 06:53 + schrieb Simon Peyton-Jones:
  I strongly favor a solution where lambda-case expressions start with \,
  because this can be generalized to proc expressions from arrow syntax
  simply by replacing the \ with proc.

  […]
  
 I think it's very helpful if lambdas start with a lambda, which to me
 suggests \case.  I'm not keen on \of; case says case analysis more
 clearly. But you presumably do not want \proc, because proc is the
 lambda. So that would leave use with \case and proc of as the two
 constructs.  Perhaps the lesser of the evils, but a bit inconsistent.

If we use \case for functions, we should use proc case for arrows;
if we use \of for functions, we should use proc of for arrows.

By the way, is proc a layout herald already?

Best wishes,
Wolfgang


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to describe this bug?

2012-07-10 Thread Simon Marlow

On 10/07/2012 12:21, Aleksey Khudyakov wrote:

On Tue, Jul 10, 2012 at 3:06 PM, Sönke Hahn sh...@cs.tu-berlin.de wrote:

I've attached the code. The code does not make direct use of
unsafePerformIO. It uses QuickCheck, but I don't think, this is a
QuickCheck bug. The used Eq-instance is the one for Float.

I've only managed to reproduce this bug on 32-bit-linux with ghc-7.4.2
when compiling with -O2.


It's expected behaviour with floats. Calculations in FPU are done in
maximul precision available.  If one evaluation result is kept in registers
and another has been moved to memory and rounded and move back to registers
number will be not the same indeed.

In short. Never compare floating point number for equality unless you
really know
what are you doing.


I consider it a bug, because as the original poster pointed out it is a 
violation of referential transparency.  What's more, it is *not* an 
inherent property of floating point arithmetic, because if the compiler 
is careful to do all the operations at the correct precision then you 
can get determinstic results.  This is why GHC has the 
-fexcess-precision flag: you have to explicitly ask to break referential 
transparency.


The bug is that the x86 native code generator behaves as if 
-fexcess-precision is always on.  I seriously doubt that we'll ever fix 
this bug: you can get correct behaviour by enabling -msse2, or using a 
64-bit machine.  I don't off-hand know what the LLVM backend does here, 
but I would guess that it has the same bug.


Cheers,
Simon

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Call to arms: lambda-case is stuck and needs your help

2012-07-10 Thread Chris Smith
On Tue, Jul 10, 2012 at 5:53 AM, Wolfgang Jeltsch
g9ks1...@acme.softbase.org wrote:
 If we use \case for functions, we should use proc case for arrows;
 if we use \of for functions, we should use proc of for arrows.

 By the way, is proc a layout herald already?

No, proc is not a layout herald.  The normal pattern is to use a do in
the command part of the proc syntax, so it's do that introduces the
layout.  So proc of would fit in cleanly as a way to do proc with
multiple patterns.  Or proc case, but again that's just a really
ugly language wart, IMO uglier than just writing out the longhand
version of proc x - case x of.

-- 
Chris Smith

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to describe this bug?

2012-07-10 Thread Christian Maeder

Am 10.07.2012 13:06, schrieb Sönke Hahn:

I've attached the code. The code does not make direct use of
unsafePerformIO. It uses QuickCheck, but I don't think, this is a
QuickCheck bug. The used Eq-instance is the one for Float.


The Eq-instance for floats is broken wrt NaN

Prelude (0/0 :: Float) == 0/0
False

I do not know if you create NaN in your tests, though.

C.



I've only managed to reproduce this bug on 32-bit-linux with ghc-7.4.2
when compiling with -O2.

(The code might seem a bit odd, but this is the most boiled down version
I could come up with. Even removing the module Main where line changes
the behaviour.)

Cheers,
Sönke


On 07/10/2012 12:51 PM, malcolm.wallace wrote:

Also, it is more likely to be a buggy instance of Eq, than a real loss
of referential transparency.

Regards,
 Malcolm


On Jul 10, 2012, at 11:49 AM, Christopher Done chrisd...@gmail.com wrote:


Depends what the real offending code is. For example, if it contains
unsafePerformIO then it's not a bug.

On 10 July 2012 12:42, Sönke Hahn sh...@cs.tu-berlin.de
mailto:sh...@cs.tu-berlin.de wrote:

Hi!

I've discovered a strange bug that violates simple equational reasoning.
Basically, something similar to this:

let a = f x
in a == f x

evaluates to False.

I'd like to report this on ghc-trac, but I realised, that I don't know a
good name for behaviour like this. Is there one? Broken referential
transparency, perhaps?

Thanks,
Sönke


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org

mailto:Glasgow-haskell-users@haskell.org

http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
mailto:Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users






___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users




___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to describe this bug?

2012-07-10 Thread Christian Maeder

It also works (exposes the bug on x86) without Quickcheck and Doubles:

main = prop 6.0 0.109998815
prop m x = do
let a = x * m
putStrLn (show a ++  foo)
print (x * m == a)


0.65999289 foo
False

The middle line seems to prevent CSE.

C.

Am 10.07.2012 13:06, schrieb Sönke Hahn:

I've attached the code. The code does not make direct use of
unsafePerformIO. It uses QuickCheck, but I don't think, this is a
QuickCheck bug. The used Eq-instance is the one for Float.

I've only managed to reproduce this bug on 32-bit-linux with ghc-7.4.2
when compiling with -O2.

(The code might seem a bit odd, but this is the most boiled down version
I could come up with. Even removing the module Main where line changes
the behaviour.)

Cheers,
Sönke


On 07/10/2012 12:51 PM, malcolm.wallace wrote:

Also, it is more likely to be a buggy instance of Eq, than a real loss
of referential transparency.

Regards,
 Malcolm


On Jul 10, 2012, at 11:49 AM, Christopher Done chrisd...@gmail.com wrote:


Depends what the real offending code is. For example, if it contains
unsafePerformIO then it's not a bug.

On 10 July 2012 12:42, Sönke Hahn sh...@cs.tu-berlin.de
mailto:sh...@cs.tu-berlin.de wrote:

Hi!

I've discovered a strange bug that violates simple equational reasoning.
Basically, something similar to this:

let a = f x
in a == f x

evaluates to False.

I'd like to report this on ghc-trac, but I realised, that I don't know a
good name for behaviour like this. Is there one? Broken referential
transparency, perhaps?

Thanks,
Sönke


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org

mailto:Glasgow-haskell-users@haskell.org

http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
mailto:Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users






___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users




___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to describe this bug?

2012-07-10 Thread Tyson Whitehead
On July 10, 2012 09:28:27 Christian Maeder wrote:
 Am 10.07.2012 13:06, schrieb Sönke Hahn:
  I've attached the code. The code does not make direct use of
  unsafePerformIO. It uses QuickCheck, but I don't think, this is a
  QuickCheck bug. The used Eq-instance is the one for Float.
 
 The Eq-instance for floats is broken wrt NaN
 
 Prelude (0/0 :: Float) == 0/0
 False
 
 I do not know if you create NaN in your tests, though.

Would that really be broken though?  NaN can arrise from many contexts (e.g., 
sqrt(-1)), so it would also not make much sense to return True.

The IEEE standard actually defines a mutually exclusive fourth unordered 
state wrt to NaNs for comparisons (in addition to lesser, greater, and equal).

I would like to suggest native floating point might be better modelled as 
Maybe Float, with NaN being the builtin Nothing, but leaves out Inf.

Cheers!  -Tyson

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to describe this bug?

2012-07-10 Thread roconnor

On Tue, 10 Jul 2012, Sönke Hahn wrote:


Hi!

I've discovered a strange bug that violates simple equational reasoning.
Basically, something similar to this:

let a = f x
in a == f x


While this code as it stands doesn't quite illustrate the referential 
transparency error, since == isn't guarenteed to return True on the same 
floating point value (see NaN), with a small tweek we can turn into an 
example that does illustrate the lack of referential transparency:


(let a = f x in a == f x) == (let a = f x in a == a)

or also perhaps

(let a = f x in a == f x) == (f x == f x)

If either of these return False than it is an error of referential 
transparency since equality on equivalent Bool expressions is always 
supposed to return True or diverge.


--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How to describe this bug?

2012-07-10 Thread Tyson Whitehead
On July 10, 2012 10:39:41 Colin Adams wrote:
 Sure they would be better modelled that way, but the whole point of using
 floating point arithmetic is to sacrifice accuracy for performance, is it
 not?

True.  I just find it interesting that some types have a builtin Nothing value.

Some further examples are pointer (where NULL is Nothing) and 
clamped/saturation arithmetic (where min and max values are Nothing).

It would be nice if somehow they could be unified at the top level without the 
performance penalty associated with a genuine Maybe value.

Another possibility might be to consider NaN to encode bottom in Float#.  When 
you constructed Float from Float# with a NaN it would give bottom.

Would the existance of unboxed lifted types be a problem?

Cheers!  -Tyson

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


[Fwd: Memory corruption issues when using newAlignedPinnedByteArray, GC kicking in?]

2012-07-10 Thread Nicolas Trangez
All,

I sent this mail to Haskell Cafe earlier today, and was pointed [1] at
this list. As such...

Any help/advice would be greatly appreciated!

Thanks,

Nicolas

[1] http://www.haskell.org/pipermail/haskell-cafe/2012-July/102242.html

 Forwarded Message 
 From: Nicolas Trangez nico...@incubaid.com
 To: haskell-c...@haskell.org
 Cc: Roman Leshchinskiy r...@cse.unsw.edu.au
 Subject: Memory corruption issues when using
 newAlignedPinnedByteArray, GC kicking in?
 Date: Tue, 10 Jul 2012 19:20:01 +0200
 
 All,
 
 While working on my vector-simd library, I noticed somehow memory I'm
 using gets corrupted/overwritten. I reworked this into a test case, and
 would love to get some help on how to fix this.
 
 Previously I used some custom FFI calls to C to allocate aligned memory,
 which yields correct results, but this has a significant (+- 10x)
 performance impact on my benchmarks. Later on I discovered the
 newAlignedPinnedByteArray# function, and wrote some code using this.
 
 Here's what I did in the test case: I created an MVector instance, with
 the exact same implementation as vector's
 Data.Vector.Storable.Mutable.MVector instance, except for basicUnsafeNew
 where I pass one more argument to mallocVector [1].
 
 I also use 3 different versions of mallocVector (depending on
 compile-time flags):
 
 mallocVectorOrig [2]: This is the upstream version, discarding the
 integer argument I added.
 
 Then here's my first attempt, very similar to the implementation of
 mallocPlainForeignPtrBytes [3] at [4] using GHC.* libraries.
 
 Finally there's something similar at [5] which uses the 'primitive'
 library.
 
 The test case creates vectors of increasing size, then checks whether
 they contain the expected values. For the default implementation this
 works correctly. For both others it fails at some random size, and the
 values stored in the vector are not exactly what they should be.
 
 I don't understand what's going on here. I suspect I lack a reference
 (or something along those lines) so GC kicks in, or maybe the buffer
 gets relocated, whilst it shouldn't.
 
 Basically I'd need something like
 
 GHC.ForeignPtr.mallocPlainAlignedForeignPtrBytes :: Int - Int - IO
 (ForeignPtr a)
 
 Thanks,
 
 Nicolas
 
 [1] https://gist.github.com/3084806#LC37
 [2] https://gist.github.com/3084806#LC119
 [3]
 http://hackage.haskell.org/packages/archive/base/latest/doc/html/src/GHC-ForeignPtr.html
 [4] https://gist.github.com/3084806#LC100
 [5] https://gist.github.com/3084806#LC81
 
 



___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


“Ambiguous type variable in the constraint” error in rewrite rule

2012-07-10 Thread Tsuyoshi Ito
Hello,

Why does GHC 7.4.1 reject the rewrite rule in the following code?

 module Test where

 import Data.Monoid
 import Control.Monad.Writer.Strict

 f :: Monad m = a - m a
 f = return

 g :: Monoid w = a - Writer w a
 g = return

 {-# RULES
 f-g f = g
   #-}

On the line containing the rewrite rule, GHC shows the following error message:

Test.hs:13:12:
Ambiguous type variable `w0' in the constraint:
  (Monoid w0) arising from a use of `g'
Probable fix: add a type signature that fixes these type variable(s)
In the expression: g
When checking the transformation rule f-g

Interestingly, the code compiles if the rewrite rule is replaced with
the following SPECIALIZE pragma:

 {-# SPECIALIZE f :: Monoid w = a - Writer w a #-}

I find this strange because if I am not mistaken, this specialization
is handled by using a rewrite rule of the same type as the one which
GHC rejects.

The following ticket might be related, but I am not sure:
Subclass Specialization in Rewrite Rules
http://hackage.haskell.org/trac/ghc/ticket/6102

Best regards,
  Tsuyoshi

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users