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 co
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
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
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 guarente
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
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'
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
On Tue, Jul 10, 2012 at 5:53 AM, Wolfgang Jeltsch
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 t
On 10/07/2012 12:21, Aleksey Khudyakov wrote:
On Tue, Jul 10, 2012 at 3:06 PM, Sönke Hahn 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 m
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 helpfu
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'
On Tue, Jul 10, 2012 at 3:06 PM, Sönke Hahn 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-l
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
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 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:
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 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
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 refere
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 cont
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 nai
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
> 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 -
20 matches
Mail list logo