Re: [Haskell-cafe] SYB with class: Bug in Derive.hs module

2012-09-05 Thread Roman Cheplyaka
* Andrea Vezzosi sanzhi...@gmail.com [2012-09-05 03:13:56+0200] I've pushed the discussed changes to the repo[1], it'd be good if you (and other users) could test them before they get to hackage. [1] darcs get http://patch-tag.com/r/Saizan/syb-with-class/ I confirm that it fixed my problem.

Re: [Haskell-cafe] SYB with class: Bug in Derive.hs module

2012-09-04 Thread Andrea Vezzosi
I've pushed the discussed changes to the repo[1], it'd be good if you (and other users) could test them before they get to hackage. [1] darcs get http://patch-tag.com/r/Saizan/syb-with-class/ -- Andrea ___ Haskell-Cafe mailing list

[Haskell-cafe] SYB with class: Bug in Derive.hs module

2012-09-03 Thread Roman Cheplyaka
There's a bug in syb-with-class reported by Alexey Rodriguez Yakushev in 2008 [1]. I can confirm that the bug is still there (syb-with-class-0.6.1.3, ghc 7.4.1). [1]: http://www.haskell.org/pipermail/haskell-cafe/2008-March/041179.html Here's an even simpler test case: {-# LANGUAGE

Re: [Haskell-cafe] SYB with class: Bug in Derive.hs module

2012-09-03 Thread Andrea Vezzosi
On Mon, Sep 3, 2012 at 12:00 PM, Roman Cheplyaka r...@ro-che.info wrote: There's a bug in syb-with-class reported by Alexey Rodriguez Yakushev in 2008 [1]. I can confirm that the bug is still there (syb-with-class-0.6.1.3, ghc 7.4.1). [1]:

Re: [Haskell-cafe] SYB with class: Bug in Derive.hs module

2012-09-03 Thread Roman Cheplyaka
* Andrea Vezzosi sanzhi...@gmail.com [2012-09-03 12:50:03+0200] On Mon, Sep 3, 2012 at 12:00 PM, Roman Cheplyaka r...@ro-che.info wrote: There's a bug in syb-with-class reported by Alexey Rodriguez Yakushev in 2008 [1]. I can confirm that the bug is still there (syb-with-class-0.6.1.3, ghc

Re: [Haskell-cafe] SYB with class: Bug in Derive.hs module

2012-09-03 Thread Andrea Vezzosi
On Mon, Sep 3, 2012 at 2:53 PM, Roman Cheplyaka r...@ro-che.info wrote: * Andrea Vezzosi sanzhi...@gmail.com [2012-09-03 12:50:03+0200] [...] This is pretty similar to what ended up being a ghc bug, fixed in 7.0 though: http://hackage.haskell.org/trac/ghc/ticket/3731 The difference between

Re: [Haskell-cafe] Odd HDBC connection bug

2012-07-07 Thread William Shackleton
I found the solution to this problem: for both libraries, I had to wrap calls in 'withRTSSignalsBlocked' from HDBC-mysql. On 16 June 2012 00:32, William Shackleton w.shackle...@gmail.com wrote: Hi I'm having issues with HDBC when connecting to a remote MySQL server - certain queries cause

[Haskell-cafe] Odd HDBC connection bug

2012-06-15 Thread William Shackleton
Hi I'm having issues with HDBC when connecting to a remote MySQL server - certain queries cause the DB connection to be lost. The following program demonstrates this: import Database.HDBC import Database.HDBC.ODBC main = do conn - connectODBC DSN=owlro putStrLn Connected

Re: [Haskell-cafe] Label macro expansion bug In HList.

2011-11-11 Thread aditya siram
I just pulled the latest version of HList : darcs clone http://code.haskell.org/HList I compiled it with GHC 7.2.1 and I am still running into the same issue the makeLabels function: runQ (makeLabels [test1,test2]) = putStrLn . pprint data Foo_0 deriving (Data.Typeable.Internal.Typeable) foo_1

Re: [Haskell-cafe] Label macro expansion bug In HList.

2011-11-11 Thread aditya siram
I also have the same issue with OOHaskell after pulling from http://code.haskell.org/OOHaskell. After loading GHCI I did: :l ../samples/OCamlTutorial.hs ../samples/OCamlTutorial.hs:97:3: Multiple declarations of `foo' Declared at: ../samples/OCamlTutorial.hs:53:1

Re: [Haskell-cafe] Label macro expansion bug In HList.

2011-11-11 Thread aditya siram
I have verified that the issue with the makeLabels function goes away if I install 7.0.4. I got an extremely large error (~ 5000 lines) when loading OCamlTutorial.hs. When I've parsed through it, I'll post back. Sorry for the confusion. -deech On Fri, Nov 11, 2011 at 1:33 PM, aditya siram

Re: [Haskell-cafe] Label macro expansion bug In HList.

2011-11-11 Thread oleg
I have verified that the issue with the makeLabels function goes away if I install 7.0.4. I'm glad to hear that. GHC 7.0.4 has updated Template Haskell in backward-incopatible ways. I got an extremely large error (~ 5000 lines) when loading OCamlTutorial.hs. Quite likely the reason was

Re: [Haskell-cafe] Label macro expansion bug In HList.

2011-11-11 Thread aditya siram
Thanks for updating the Cabal file. The reason I commented out the Data.HList.TypeEqO was because I couldn't find it. I grepped the HList source tree for it and I found references to it only in the following places: ./Data/HList/RecordD.hs:import Data.HList.TypeEqO

Re: [Haskell-cafe] Label macro expansion bug In HList.

2011-11-11 Thread oleg
The reason I commented out the Data.HList.TypeEqO was because I couldn't find it. My apologies! It turns out I have forgotten to 'darcs add' it. It is committed now: http://code.haskell.org/HList/Data/HList/TypeEqO.hs ___ Haskell-Cafe

Re: [Haskell-cafe] Label macro expansion bug In HList.

2011-11-11 Thread aditya siram
Awesome! The samples now work. Thanks so much for your help. -deech On Fri, Nov 11, 2011 at 11:14 PM, o...@okmij.org wrote: The reason I commented out the Data.HList.TypeEqO was because I couldn't find it. My apologies! It turns out I have forgotten to 'darcs add' it. It is committed

[Haskell-cafe] Label macro expansion bug In HList.

2011-11-08 Thread aditya siram
Hi all, I am exploring OOHaskell and ran into some compilation issues with some of the samples. I hope this is the right place to report it. For example OCamlTutorial.hs generates the following error: ../samples/OCamlTutorial.hs:98:3: Multiple declarations of `foo' Declared at:

Re: [Haskell-cafe] Label macro expansion bug In HList.

2011-11-08 Thread oleg
I believe this is the case of OOHaskell gotten a bit out of sync with HList and GHC. Please use the latest code bases http://code.haskell.org/HList http://code.haskell.org/OOHaskell OCamlTutorial and all other OOHaskell code should work (with GHC 7.0.4).

Re: [Haskell-cafe] Is it a bug in haskell-src-meta package?

2011-09-01 Thread Jonas Almström Duregård
Its a bug in haskell-src-meta. I just reported it: https://github.com/benmachine/haskell-src-meta/issues/8 Regards, Jonas On 1 September 2011 03:19, bob zhang bobzhang1...@gmail.com wrote: Hi, all parseExp (,) 3 4 = Right (AppE (AppE (ConE GHC.Unit.(,)) (LitE (IntegerL 3))) (LitE

[Haskell-cafe] Is it a bug in haskell-src-meta package?

2011-08-31 Thread bob zhang
Hi, all parseExp (,) 3 4 = Right (AppE (AppE (ConE GHC.Unit.(,)) (LitE (IntegerL 3))) (LitE (IntegerL 4))) where's GHC.Unit.(,) ? Many thanks best, bob ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Is it a bug in haskell-src-meta package?

2011-08-31 Thread Ivan Lazar Miljenovic
On 1 September 2011 11:19, bob zhang bobzhang1...@gmail.com wrote: Hi, all parseExp (,) 3 4 = Right (AppE (AppE (ConE GHC.Unit.(,)) (LitE (IntegerL 3))) (LitE (IntegerL 4))) where's GHC.Unit.(,) ? GHC.Unit (like all GHC.* modules) is an internal module used by GHC to implement base,

Re: [Haskell-cafe] Is it a bug in haskell-src-meta package?

2011-08-31 Thread bob zhang
于 11-8-31 下午10:01, Ivan Lazar Miljenovic 写道: On 1 September 2011 11:19, bob zhangbobzhang1...@gmail.com wrote: Hi, all parseExp (,) 3 4 = Right (AppE (AppE (ConE GHC.Unit.(,)) (LitE (IntegerL 3))) (LitE (IntegerL 4))) where's GHC.Unit.(,) ? GHC.Unit (like all GHC.* modules) is an internal

Re: [Haskell-cafe] Is it a bug in haskell-src-meta package?

2011-08-31 Thread bob zhang
于 11-8-31 下午10:01, Ivan Lazar Miljenovic 写道: On 1 September 2011 11:19, bob zhangbobzhang1...@gmail.com wrote: Hi, all parseExp (,) 3 4 = Right (AppE (AppE (ConE GHC.Unit.(,)) (LitE (IntegerL 3))) (LitE (IntegerL 4))) where's GHC.Unit.(,) ? GHC.Unit (like all GHC.* modules) is an internal

Re: [Haskell-cafe] Is it a bug in haskell-src-meta package?

2011-08-31 Thread Ivan Lazar Miljenovic
On 1 September 2011 12:29, bob zhang bobzhang1...@gmail.com wrote: 于 11-8-31 下午10:01, Ivan Lazar Miljenovic 写道: On 1 September 2011 11:19, bob zhangbobzhang1...@gmail.com  wrote: Hi, all parseExp (,) 3 4 = Right (AppE (AppE (ConE GHC.Unit.(,)) (LitE (IntegerL 3))) (LitE (IntegerL 4)))

Re: [Haskell-cafe] Is it a bug in haskell-src-meta package?

2011-08-31 Thread bob zhang
于 11-8-31 下午10:35, Ivan Lazar Miljenovic 写道: May I ask though why you're trying to use (,) as an explicit constructor in a quasi-quotation? Thanks for your reply. I just generated some code this way, and it does not work. this style is common in applicative functor, right? Best, bob

Re: [Haskell-cafe] maybe a GHC bug but not sure

2011-06-01 Thread Edward Amsden
And after a lot more sleep and some digging, it turns out that the build script was forcing GCC to build the .o file as a 32 bit binary, and thus causing the magic mismatch. On Mon, May 30, 2011 at 11:20 PM, Edward Amsden eca7...@cs.rit.edu wrote: When building the Haskell Objective C bindings

[Haskell-cafe] maybe a GHC bug but not sure

2011-05-30 Thread Edward Amsden
When building the Haskell Objective C bindings tool from http://code.google.com/p/hoc Using GHC 7.0.3 for Haskell Platform 2011.2.0.1, OS X 64 bit HOC compiles HOC_cbits.o before trying to build it into the rest of the program (I don't say link because this came up while trying to compile: [18

[Haskell-cafe] Curious data family bug

2010-11-15 Thread Michael Snoyman
Hey all, While trying to get a commit pushed for Yesod[1], Alexander Dunlap pointed out one of his programs didn't work with the new code. After some investigation, I was able to reproduce the bug with the following code snippet: {-# LANGUAGE TypeFamilies #-} data family Foo a data Bar = Bar

Re: [Haskell-cafe] Curious data family bug

2010-11-15 Thread Daniel Peebles
Hmm, strange. I have a project that uses data families with dozens of constructors per clause/instantiation of the type function. I use GADT syntax to define them though as they also refine one of the parameter type variables. Never had any issues with it, although I haven't tried building that

RE: [Haskell-cafe] Curious data family bug

2010-11-15 Thread Simon Peyton-Jones
- | From: haskell-cafe-boun...@haskell.org [mailto:haskell-cafe-boun...@haskell.org] On | Behalf Of Michael Snoyman | Sent: 14 November 2010 19:16 | To: Haskell Cafe | Subject: [Haskell-cafe] Curious data family bug | | Hey all, | | While trying to get a commit pushed for Yesod[1], Alexander Dunlap

Re: [Haskell-cafe] Curious data family bug

2010-11-15 Thread Michael Snoyman
] On | Behalf Of Michael Snoyman | Sent: 14 November 2010 19:16 | To: Haskell Cafe | Subject: [Haskell-cafe] Curious data family bug | | Hey all, | | While trying to get a commit pushed for Yesod[1], Alexander Dunlap | pointed out one of his programs didn't work with the new code. After | some

[Haskell-cafe] Failed inference: maybe bug?

2010-08-18 Thread Edward Z. Yang
On the prompting of napping, I humbly submit the following code to haskell-cafe: ezy...@javelin:~/Dev/haskell/generic-typeclass$ cat Bar.hs {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleContexts #-} data Foo b = Foo class

Re: [Haskell-cafe] Please report any bug of gtk2hs-0.11.0!

2010-07-26 Thread Sebastian Fischer
Hello, On Jul 13, 2010, at 9:15 AM, Andy Stewart wrote: Please report any bug of gtk2hs-0.11.0, we will fix it before release gtk2hs-0.11.1 I have just installed the new Haskell Platform under Mac OS X 10.5. With the previous installation of GHC 6.10.4 I managed to install gtk2hs

Re: [Haskell-cafe] Please report any bug of gtk2hs-0.11.0!

2010-07-26 Thread Andy Stewart
Sebastian Fischer s...@informatik.uni-kiel.de writes: Hello, On Jul 13, 2010, at 9:15 AM, Andy Stewart wrote: Please report any bug of gtk2hs-0.11.0, we will fix it before release gtk2hs-0.11.1 I have just installed the new Haskell Platform under Mac OS X 10.5. With the previous

Re: [Haskell-cafe] Please report any bug of gtk2hs-0.11.0!

2010-07-26 Thread Sebastian Fischer
On Jul 26, 2010, at 6:59 PM, Andy Stewart wrote: cabal install gtk fails with the message Configuring gtk-0.11.0... setup: ./Graphics/UI/Gtk/General/IconTheme.chs: invalid argument cabal: Error: some packages failed to install: gtk-0.11.0 failed during the building phase. The

Re: [Haskell-cafe] Please report any bug of gtk2hs-0.11.0!

2010-07-19 Thread Felipe Lessa
Err... where is pixbufFromImageSurface [1] now? I have an old program that draws using cairo an static diagram to a pixbuf which then becomes the backend of an Image. If pixbufFromImageSurface got deprecated, what's a better solution? [1]

Re: [Haskell-cafe] is this a bug ?

2010-07-17 Thread Daniel Fischer
On Saturday 17 July 2010 05:39:00, gat...@landcroft.co.uk wrote: On Sat 17/07/10 04:17 , Alexander Solla a...@2piix.com sent: Why are you performing unsafe IO actions? They don't play nice with laziness. OK, fair cop, but without the unsafe IO action, it still misbehaves.

[Haskell-cafe] is this a bug ?

2010-07-16 Thread gate03
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=27631 The comments in the code explain the problem. If .Lazy be removed from the code (occurs three times), i.e., the code is changed to strict byte strings, it works as expected. Michael Mounteney. ___

Re: [Haskell-cafe] is this a bug ?

2010-07-16 Thread gate03
On Sat 17/07/10 04:17 , Alexander Solla a...@2piix.com sent: Why are you performing unsafe IO actions? They don't play nice with laziness. OK, fair cop, but without the unsafe IO action, it still misbehaves. http://hpaste.org/fastcgi/hpaste.fcgi/view?id=27650 Michael.

Re: [Haskell-cafe] is this a bug ?

2010-07-16 Thread Felipe Lessa
You should probably CC the maintainer of the regex package. Cheers, -- Felipe. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Please report any bug of gtk2hs-0.11.0!

2010-07-13 Thread Andy Stewart
Hi all, We plan to release bug fix version : gtk2hs-0.11.1 Please report any bug of gtk2hs-0.11.0, we will fix it before release gtk2hs-0.11.1 We plan to add many new APIs in gtk2hs-0.12.0, so gtk2hs-0.11.1 will be the last stable version with current APIs. Thanks for your help! -- Andy

[Haskell-cafe] GHC AT inference bug?

2010-07-04 Thread Kevin Quick
I started with the following: {-# LANGUAGE TypeFamilies #-} class DoC a where type A2 a op :: a - A2 a data Con x = InCon (x (Con x)) type FCon x = x (Con x) foldDoC :: Functor f = (f a - a) - Con f - a foldDoC f (InCon t) = f (fmap (foldDoC f) t) doCon :: (DoC (FCon x)) = Con x -

[Haskell-cafe] When is a bug GHC's fault/strange STM behaviour

2010-03-13 Thread Michael Lesniak
Hello, In one of my example programs I have a strange behaviour: it is a very simple taskpool using STM; in pseudocode it's 1. generate data structures 2. initialize data structures 3. fork threads 4. wait (using STM) until the pool is empty and all threads are finished 5. print a final message

Re: [Haskell-cafe] When is a bug GHC's fault/strange STM behaviour

2010-03-13 Thread Carter Schonwald
is it possibly something related to how the gc interacts with that many threads in that context? On Sat, Mar 13, 2010 at 11:36 AM, Michael Lesniak mlesn...@uni-kassel.dewrote: Hello, In one of my example programs I have a strange behaviour: it is a very simple taskpool using STM; in

Re: [Haskell-cafe] When is a bug GHC's fault/strange STM behaviour

2010-03-13 Thread Daniel Fischer
Am Samstag 13 März 2010 17:36:49 schrieb Michael Lesniak: Hello, In one of my example programs I have a strange behaviour: it is a very simple taskpool using STM; in pseudocode it's 1. generate data structures 2. initialize data structures 3. fork threads 4. wait (using STM) until the

Re: [Haskell-cafe] When is a bug GHC's fault/strange STM behaviour

2010-03-13 Thread Michael Lesniak
Hi, is it possibly something related to how the  gc interacts with that many threads in that context? Would be one possibility, but it even hangs with just a few threads (e.g. 2); it just takes more iterations until it hangs. Cheers, Michael ___

Re: [Haskell-cafe] When is a bug GHC's fault/strange STM behaviour

2010-03-13 Thread Michael Lesniak
Hello, For the attached programme, in the task-getting,            else if Set.null work                    then return Nothing                    else retry doesn't really make sense, when the channel is empty, we could return Nothing right away. I suppose, in the real programme, some

Re: [Haskell-cafe] GHC bug? Cabal bug? Haddock bug?

2010-01-22 Thread David Waern
2010/1/17 Mark Lentczner ma...@glyphic.com: AHA! Note that after running cabal haddock we re-build all of our .hi and .o files EXCEPT ./dist/build/HSsyb-with-class-0.6.1.o And now, since TH generates random symbols, we have symbols in the new .hi files that aren't in the old (and only)

[Haskell-cafe] GHC bug? Cabal bug? Haddock bug?

2010-01-16 Thread Mark Lentczner
=== Short Story === If I build syb-with-class-0.6 via cabal (cabal configure; cabal build) in the unpacked tar directory, it builds correctly. If I build it via cabal install (either from the unpacked directory, or by letting cabal fetch it), then the resulting package is corrupted. In

Re: [Haskell-cafe] GHC bug? Cabal bug? Haddock bug?

2010-01-16 Thread Antoine Latter
This sounds similar to an issue I was seeing over here: http://groups.google.com/group/happs/msg/04ecfe4fd6285c0d The module being compiled also includes TH top-level statements, and was only reproducible when building from Cabal. Here's another occurance on a different platform:

Re: [Haskell-cafe] GHC bug? Cabal bug? Haddock bug?

2010-01-16 Thread Mark Lentczner
Indeed - all those look exactly like the same issue. And the workaround: http://groups.google.com/group/happs/msg/1e7761d421b0e5eb That doesn't fix the real issue: It causes happstack-data to not need the thing that is built wrong in syb-with-class. I believe my work-around (build

Re: [Haskell-cafe] GHC bug? Cabal bug? Haddock bug?

2010-01-16 Thread Antoine Latter
2010/1/16 Mark Lentczner ma...@glyphic.com: Indeed - all those look exactly like the same issue. And the workaround: http://groups.google.com/group/happs/msg/1e7761d421b0e5eb That doesn't fix the real issue: It causes happstack-data to not need the thing that is built wrong in

Re: [Haskell-cafe] GHC bug? Cabal bug? Haddock bug?

2010-01-16 Thread Mark Lentczner
AHA! Note that after running cabal haddock we re-build all of our .hi and .o files EXCEPT ./dist/build/HSsyb-with-class-0.6.1.o And now, since TH generates random symbols, we have symbols in the new .hi files that aren't in the old (and only) HSsyb-with-class-0.6.1.o. So, this leaves us

[Haskell-cafe] Announcing the GHC Bug Sweep

2009-11-16 Thread Simon Marlow
Help us weed the GHC ticket database, and get a warm fuzzy feeling from contributing to Haskell core technology! There are currently ~750 tickets against GHC. Many of them have not been looked at in months or years. Often when I go through old tickets I find easy targets: bugs that have

Re: [Haskell-cafe] Announcing the GHC Bug Sweep

2009-11-16 Thread Roman Cheplyaka
Cool, I'm in! (Also inspired by [1]this post by Erik de Castro Lopo) It would be nice to keep track of participants somewhere, so that each of us knows he's not alone :) 1. http://www.mega-nerd.com/erikd/Blog/CodeHacking/DDC/hacking_ddc.html * Simon Marlow marlo...@gmail.com [2009-11-16

Re: [Haskell-cafe] Announcing the GHC Bug Sweep

2009-11-16 Thread Michael Lesniak
Hello, I'm also interested and find Roman's idea about a wiki-page for tracking motivating. So the idea we have is this: do an incremental sweep of the whole database, starting from the oldest tickets.  Check each one, and try to make some progress on it.  If we get enough momentum going we

[Haskell-cafe] Re: Is a bug?

2009-07-26 Thread Linker
Sorry.I defined a function : *GHCi, version 6.10.3: http://www.haskell.org/ghc/ :? for help* *Loading package ghc-prim ... linking ... done.* *Loading package integer ... linking ... done.* *Loading package base ... linking ... done.* *Prelude sqrt $ 3 + 4 + 9* *4.0* *Prelude let f $ x = f x*

Re: [Haskell-cafe] Re: Is a bug?

2009-07-26 Thread Dan Doel
On Sunday 26 July 2009 10:54:53 pm Linker wrote: Sorry.I defined a function : *GHCi, version 6.10.3: http://www.haskell.org/ghc/ :? for help* *Loading package ghc-prim ... linking ... done.* *Loading package integer ... linking ... done.* *Loading package base ... linking ... done.*

[Haskell-cafe] Possible floating point bug in GHC?

2009-04-03 Thread Peter Verswyvelen
For days I'm fighting against a weird bug. My Haskell code calls into a C function residing in a DLL (I'm on Windows, the DLL is generated using Visual Studio). This C function computes a floating point expression. However, the floating point result is incorrect. I think I found the source of the

Re: [Haskell-cafe] Possible floating point bug in GHC?

2009-04-03 Thread Malcolm Wallace
Interesting. This could be the cause of a weird floating point bug that has been showing up in the ghc testsuite recently, specifically affecting MacOS/Intel (but not MacOS/ppc). http://darcs.haskell.org/testsuite/tests/ghc-regress/lib/Numeric/num009.hs That test compares the result of

Re: [Haskell-cafe] Possible floating point bug in GHC?

2009-04-03 Thread Peter Verswyvelen
Well this situation can indeed not occur on PowerPCs since these CPUs just have floating point registers, not some weird dual stack sometimes / registers sometimes architecture. But in my case the bug is consistent, not from time to time. So I'll try to reduce this to a small reproducible test

Re: [Haskell-cafe] Possible floating point bug in GHC?

2009-04-03 Thread Zachary Turner
What floating point model is your DLL compiled with? There are a variety of different options here with regards to optimizations, and I don't know about the specific assembly that each option produces, but I know there are options like Strict, Fast, or Precise, and maybe when you do something

Re: [Haskell-cafe] Possible floating point bug in GHC?

2009-04-03 Thread Peter Verswyvelen
I tried both precise and fast, but that did not help. Compiling to SSE2 fixed it, since that does not use a floating point stack I guess. I'm preparing a repro test case, but it is tricky since removing code tends to change the optimizations and then the bug does not occur. Does anybody know what

Re: [Haskell-cafe] Possible floating point bug in GHC?

2009-04-03 Thread Ian Lynagh
On Fri, Apr 03, 2009 at 10:10:17PM +0200, Peter Verswyvelen wrote: I tried both precise and fast, but that did not help. Compiling to SSE2 fixed it, since that does not use a floating point stack I guess. You didn't say what version of GHC you are using, but it sounds like this might already be

Re: [Haskell-cafe] Possible floating point bug in GHC?

2009-04-03 Thread Peter Verswyvelen
Ouch, what a waste of time on my side :-( This bugfix is not mentioned in the notable bug fixes herehttp://haskell.org/ghc/docs/6.10.2/html/users_guide/release-6-10-2.html Since this is such a severe bug, I would recommend listing it :) Anyway, I have a very small repro test case now. Will

Re: [Haskell-cafe] Possible floating point bug in GHC?

2009-04-03 Thread Peter Verswyvelen
Okay, I can confirm the bug is fixed. It's insane this bug did not cause any more problems. Every call into every C function that uses floating point could have been affected (OpenGL, BLAS, etc) On Fri, Apr 3, 2009 at 10:47 PM, Peter Verswyvelen bugf...@gmail.comwrote: Ouch, what a waste of

[Haskell-cafe] A ghc-6.10.1 bug or a feature?

2009-01-28 Thread Juraj Hercek
Hello people, I've recently tried this: $ uname -smpr Linux 2.6.28-ARCH x86_64 Intel(R) Core(TM)2 CPU 6600 @ 2.40GHz $ ghci GHCi, version 6.10.1: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer ... linking ... done. Loading package

Re: [Haskell-cafe] A ghc-6.10.1 bug or a feature?

2009-01-28 Thread David Leimbach
On Wed, Jan 28, 2009 at 7:56 AM, Juraj Hercek juhe_hask...@hck.sk wrote: Hello people, I've recently tried this: $ uname -smpr Linux 2.6.28-ARCH x86_64 Intel(R) Core(TM)2 CPU 6600 @ 2.40GHz $ ghci GHCi, version 6.10.1: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ...

Re: [Haskell-cafe] A ghc-6.10.1 bug or a feature?

2009-01-28 Thread Duncan Coutts
On Wed, 2009-01-28 at 16:56 +0100, Juraj Hercek wrote: Hello people, I've recently tried this: $ uname -smpr Linux 2.6.28-ARCH x86_64 Intel(R) Core(TM)2 CPU 6600 @ 2.40GHz $ ghci GHCi, version 6.10.1: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ...

Re: [Haskell-cafe] Maybe a compiler bug?

2009-01-06 Thread Murray Gross
The issue here is not whether or not the code is pretty or elegant, but whether or not I get correct execution of what I have, which is a correct statement of what I want (even if not the prettiest or most lint free), and I don't. There are lots of ways to work around the problem, but that

Re: [Haskell-cafe] Maybe a compiler bug?

2009-01-06 Thread Peter Verswyvelen
Exactly. The best you can do is try to reduce your code to a tiny fragment that still exposes the problem, and report it as a bug. On Tue, Jan 6, 2009 at 4:52 PM, Murray Gross mgros...@verizon.net wrote: The issue here is not whether or not the code is pretty or elegant, but whether or not I

Re: [Haskell-cafe] Maybe a compiler bug?

2009-01-06 Thread Neil Mitchell
Hi Murray, The issue here is not whether or not the code is pretty or elegant, but whether or not I get correct execution of what I have, which is a correct statement of what I want (even if not the prettiest or most lint free), and I don't. Sorry, I was merely responding to someone else

Re: [Haskell-cafe] Maybe a compiler bug?

2009-01-06 Thread Murray Gross
My last note had an error in it, and the code originally sent to the list should be ignored. I have attached the current version of the code, and here is some further information (the behavior is different, by the way, but still apparently wrong). I have attached the current version of the

Re: [Haskell-cafe] Maybe a compiler bug?

2009-01-06 Thread Don Stewart
If you believe this is a compiler bug, please report it: http://hackage.haskell.org/trac/ghc/newticket?type=bug mgross21: My last note had an error in it, and the code originally sent to the list should be ignored. I have attached the current version of the code, and here is some

Re: [Haskell-cafe] Maybe a compiler bug?

2009-01-06 Thread Daniel Fischer
Am Dienstag, 6. Januar 2009 18:32 schrieb Murray Gross: My last note had an error in it, and the code originally sent to the list should be ignored. I have attached the current version of the code, and here is some further information (the behavior is different, by the way, but still

Re: [Haskell-cafe] Maybe a compiler bug?

2009-01-06 Thread Murray Gross
On Tue, 6 Jan 2009, Daniel Fischer wrote: Could you elaborate? I couldn't find an inconsistency using your previous code, it behaved as it should (until I ^C-ed it). In several versions of the code, now unfortunately lost because of a crash on a power failure (which is extremely rare

[Haskell-cafe] Maybe a compiler bug?

2009-01-05 Thread Murray Gross
When using any of -O, -O1, -O2 with the Debian binary build of GHC 6.6, trace shows that the expression if (lr ll) then False else True is (at least partially) evaluated, but the value returned is always True, even though trace reports that (lr ll) is True. When I use only the

Re: [Haskell-cafe] Maybe a compiler bug?

2009-01-05 Thread Luke Palmer
On Mon, Jan 5, 2009 at 4:34 PM, Murray Gross mgros...@verizon.net wrote: When using any of -O, -O1, -O2 with the Debian binary build of GHC 6.6, trace shows that the expression if (lr ll) then False else True is (at least partially) evaluated, but the value returned is always

Re: [Haskell-cafe] Maybe a compiler bug?

2009-01-05 Thread Murray Gross
No unsafe perform (except what may be hidden in trace), nothing, fancy, no gimmicks (very pedestrian, even heavy-handed) code. Complete code is attached (I don't have smaller snippets, because I just discovered the problem). Best, Murray Gross On Mon, 5 Jan 2009, Luke Palmer wrote:

[Haskell-cafe] Re: [Haskell] possible bug in pretty-1.0.1.0

2008-12-18 Thread Duncan Coutts
On Mon, 2008-12-15 at 08:17 -0800, John MacFarlane wrote: I noticed a difference in how hang works between pretty-1.0.0.0 and pretty-1.0.1.0. I think it's a bug. If this isn't the right place to report it, please let me know where I should. (Maintainer is listed as librar...@haskell.org, but

[Haskell-cafe] Re: [Haskell] possible bug in pretty-1.0.1.0

2008-12-18 Thread Duncan Coutts
On Thu, 2008-12-18 at 13:27 +, Neil Mitchell wrote: Hi Duncan, I'd just like to advertise the fact that as of Cabal-1.6 you can put a bug-reports field in your .cabal file and it will be displayed by hackage. Fantastic. Is it backwards compatible? i.e. if I add such a field, will

RE: [Haskell-cafe] SYB with class: Bug in Derive.hs module

2008-09-16 Thread Simon Peyton-Jones
- | From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of | Alexey Rodriguez Yakushev | Sent: 31 March 2008 14:47 | To: haskell-cafe | Cc: [EMAIL PROTECTED]; Ralf Laemmel | Subject: [Haskell-cafe] SYB with class: Bug in Derive.hs module | | Hi people (and Ralf and Alex), | | I found a bug

[Haskell-cafe] Re: apparent minor bug in Getting started tutorial at Haskell Hacking: a journal of Haskell programming

2008-08-27 Thread Benjamin L . Russell
On Wed, 27 Aug 2008 16:22:56 +0900, Benjamin L.Russell [EMAIL PROTECTED] wrote: Sorry, what I really meant was not to update the reference to a.out to be changed to main.exe, but to change the following line: This produces a new executable, ./a.out (a.out.exe on windows), which you can run like

Re: [Haskell-cafe] Re: apparent minor bug in Getting started tutorial at Haskell Hacking: a journal of Haskell programming

2008-08-27 Thread Brandon S. Allbery KF8NH
On 2008 Aug 27, at 3:28, Benjamin L.Russell wrote: On Wed, 27 Aug 2008 16:22:56 +0900, Benjamin L.Russell [EMAIL PROTECTED] wrote: Sorry, what I really meant was not to update the reference to a.out to be changed to main.exe, but to change the following line: This produces a new executable,

[Haskell-cafe] GHC Feature or Bug: f x = (`head` x, ())

2008-08-05 Thread Jeremy Shaw
Hello, GHC is happy to compile this code: f x = (`head` x, ()) but Hugs does not like it, and Section 3.5 of the Haskell Report does not give any obvious indications that it is valid. Numerous people have suggested that some additional parens are required: f x = ((`head` x), ()) Is this GHC

Re: [Haskell-cafe] This is a bug?

2008-06-20 Thread Malcolm Wallace
How I solve this issue when call readXml: in score-partwise, In a sequence: in part, In a sequence: in measure, Too many elements inside measure at file ../../../parsers/elite2.xml at line 75 col 15 Found excess: So, your XML document contains a score-partwise, which contains a

[Haskell-cafe] This is a bug?

2008-06-19 Thread Samuel Silva
Hello I'm using HaXml library to handle XML. How I solve this issue when call readXml: in score-partwise, In a sequence: in part, In a sequence: in measure, Too many elements inside measure at file ../../../parsers/elite2.xml at line 75 col 15 Found excess: Done. I don't

Re: [Haskell-cafe] SYB with class: Bug in Derive.hs module

2008-04-02 Thread Ian Lynagh
On Mon, Mar 31, 2008 at 03:47:04PM +0200, Alexey Rodriguez Yakushev wrote: The Data instance that Derive generates is as follows: instance (Data ctx a, Data ctx (BinTree a), Sat (ctx (BinTree a))) = Data ctx (BinTree a) where

[Haskell-cafe] SYB with class: Bug in Derive.hs module

2008-03-31 Thread Alexey Rodriguez Yakushev
Hi people (and Ralf and Alex), I found a bug in the SYB with class library when trying to implement generic equality. I am hoping that someone in the Cafe (maybe Ralf) can confirm it is a bug, or maybe show me that I am doing something wrong. I am using the Scrap your boilerplate with

Re: [Haskell-cafe] gui libs? no [...] - bug report

2007-07-19 Thread Claus Reinke
as Marc pointed out, there was a problem with my javascript use that showed up as an event error in firefox. Miguel has suggested how to remove that issue. i've also added commands to set the colour explicitly, and to move to the origin after translation, so that firefox now draws whole

Re: [Haskell-cafe] gui libs? no [...] - bug report

2007-07-18 Thread Marc Weber
Hi Claus Ising ghc-6.6 and Opera 9.20 i thought that everything would work until I tried the page in Firefox 2.0.0.1 Opera: Those maroon rectangles in all four corners appear, alse the text x/y: ... is shown when clicking. But the drawing doesn't appear, does'n show any errors within the Error

[Haskell-cafe] Announce: DisTract: Distributed Bug Tracker implemented in Haskell

2007-04-23 Thread Matthew Sackman
DisTract is a Distributed Bug Tracker. We're all now familiar with working with distributed software control systems, such as Monotone, Git, Darcs, Mercurial and others, but bug trackers still seem to be fully stuck in the centralised model: Bugzilla and Trac both have single centralised servers.

Re: [Haskell-cafe] Announce: DisTract: Distributed Bug Tracker implemented in Haskell

2007-04-23 Thread Bryan O'Sullivan
Nice. You might find Bugs Everywhere http://www.panoramicfeedback.com/opensource/ interesting for comparison. b ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Haddock/Cabal/base bug?

2006-08-21 Thread Henning Thielemann
On Sun, 20 Aug 2006, Neil Mitchell wrote: Hi, I want to generate documentation for the base libraries, so I darcs get the base libraries, and a very basic (the sample default) Setup.hs, and try: runhaskell Setup configure runhaskell Setup build Pretty much no luck, but I'll leave

Re: [Haskell-cafe] Haddock/Cabal/base bug?

2006-08-21 Thread Neil Mitchell
Hi haddock.exe: Main.all_subs_of_qname: unexpected unqual'd name:IOMode Sometimes such an error is a Haddock problem, sometimes one of the 'unliterate' procedure in Cabal. Does the problem remain if you start Haddock manually, maybe on manually unliterated modules? Base is a bit too big and

[Haskell-cafe] Haddock/Cabal/base bug?

2006-08-20 Thread Neil Mitchell
Hi, I want to generate documentation for the base libraries, so I darcs get the base libraries, and a very basic (the sample default) Setup.hs, and try: runhaskell Setup configure runhaskell Setup build Pretty much no luck, but I'll leave that for someone else to sort out :) runhaskell Setup

Re: [Haskell-cafe] Seeking a small bug-fix for previously-posted code

2005-08-16 Thread Andy Elvey
Stefan Holdermans wrote: Andy, Many thanks again - I'll make this my last post for at least a week or two (to give others some bandwidth) - Well, if you are having difficulties learning the language, you really shouldn't hold back on asking questions, of course. So, please, do ask those

Re: [Haskell-cafe] Seeking a small bug-fix for previously-posted code

2005-08-15 Thread Andy Elvey
Bulat Ziganshin wrote: Hello Stefan, Sunday, August 14, 2005, 2:05:00 PM, you wrote: SH let format line = [ ++ concat (intersperse , (words line)) ++ ] SH return $ map (mkVec . read . format) $ lines str -- CORRECTED or just return $ map (mkVec . map read . words) $ lines str Hi

Re[2]: [Haskell-cafe] Seeking a small bug-fix for previously-posted code

2005-08-15 Thread Bulat Ziganshin
Hello Andy, Tuesday, August 16, 2005, 2:58:43 AM, you wrote: AE If there were a Haskell cookbook (as there is a Python one), I AE would have gone straight there. I regularly use the Python cookbook AE site which is very useful . However, until there's a Haskell equivalent AE (which then

Re: Re[2]: [Haskell-cafe] Seeking a small bug-fix for previously-posted code

2005-08-15 Thread Stefan Holdermans
Bulat, or just return $ map (mkVec . map read . words) $ lines str Yeah, I wrote that one down a little bit later, but didn't really find it worth mentioning. ;) As said, I don't really think this kind of programs is suitable for learning Haskell, anyway. Regards, Stefan

Re: [Haskell-cafe] Seeking a small bug-fix for previously-posted code

2005-08-15 Thread Stefan Holdermans
Andy, Many thanks again - I'll make this my last post for at least a week or two (to give others some bandwidth) - Well, if you are having difficulties learning the language, you really shouldn't hold back on asking questions, of course. So, please, do ask those questions. I can recommend

  1   2   >