Re: [GHC] #2257: validate hangs in configure

2008-05-01 Thread GHC
#2257: validate hangs in configure
-+--
Reporter:  nr|Owner:   
Type:  bug   |   Status:  new  
Priority:  normal|Milestone:   
   Component:  Build System  |  Version:  6.8.2
Severity:  major |   Resolution:   
Keywords:| Testcase:   
Architecture:  x86   |   Os:  Linux
-+--
Comment (by nr):

 I take it back, both ways.

 1. Static linking doesn't solve the problem after all.  Must have been an
 error between the keyboard and the chair

 1. If you replace usleep with nanosleep, and you are willing to wait a
 long time for configure to finish, it finishes eventually.  Or at least it
 did once.

 1. Further experimenting with variations on the test program shows that
 the program hangs on the second call to timer_settime.  For all I know
 this is a kernel problem

 I am out of my depth.  Help!

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2257: validate hangs in configure

2008-05-01 Thread GHC
#2257: validate hangs in configure
-+--
Reporter:  nr|Owner:   
Type:  bug   |   Status:  new  
Priority:  normal|Milestone:   
   Component:  Build System  |  Version:  6.8.2
Severity:  major |   Resolution:   
Keywords:| Testcase:   
Architecture:  x86   |   Os:  Linux
-+--
Comment (by nr):

 OK, if I remove an LD_PRELOAD environment variable, which points to a
 wrapper around getaddrinfo, things work.  Perhaps the configure script
 should do something about checking for LD_PRELOAD?

 I'm leaving this ticket open because others will know how best to resolve
 it.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2257: validate hangs in configure

2008-05-01 Thread GHC
#2257: validate hangs in configure
-+--
Reporter:  nr|Owner:   
Type:  bug   |   Status:  new  
Priority:  normal|Milestone:   
   Component:  Build System  |  Version:  6.8.2
Severity:  major |   Resolution:   
Keywords:| Testcase:   
Architecture:  x86   |   Os:  Linux
-+--
Comment (by nr):

 Replacing usleep with nanosleep changes nothing.

 But linking the program statically makes it terminate instantly.

 So there is some kind of bad interaction between the dynamic linker and
 this test program.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2257: validate hangs in configure

2008-05-01 Thread GHC
#2257: validate hangs in configure
-+--
Reporter:  nr|Owner:   
Type:  bug   |   Status:  new  
Priority:  normal|Milestone:   
   Component:  Build System  |  Version:  6.8.2
Severity:  major |   Resolution:   
Keywords:| Testcase:   
Architecture:  x86   |   Os:  Linux
-+--
Comment (by nr):

 I did a little digging into the file that's hanging, and I notice it calls
 usleep and waits for a timer event.  It's hanging, and if interrupted, it
 shows this backtrace:
 {{{
 (gdb) bt
 #0  handler (i=26) at conftest.c:109
 #1  
 #2  0xb7f163d6 in _dl_fixup () from /lib/ld-linux.so.2
 #3  0xb7f1bc50 in _dl_runtime_resolve () from /lib/ld-linux.so.2
 #4  0x080488a9 in main () at conftest.c:178
 (gdb)
 }}}
 Line 178 is the call to usleep() and line 109 is the VTALARM handler
 installed by sigaction().

 I note that the man page for usleep contains these warnings:
 {{{
 CONFORMING TO
4.3BSD,  POSIX.1-2001.   POSIX.1-2001  declares this function
 obsolete;
use nanosleep(2) instead.
 }}}
 and
 {{{
The interaction of this function with  the  SIGALRM  signal,  and
 with
other   timer  functions  such  as  alarm(2),  sleep(3),
 nanosleep(2),
setitimer(2),  timer_create(3),  timer_delete(3),
 timer_getoverrun(3),
timer_gettime(3), timer_settime(3), ualarm(3) is unspecified.
 }}}

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #2258: ghc --cleanup

2008-05-01 Thread GHC
#2258: ghc --cleanup
+---
Reporter:  claus|   Owner:  
Type:  feature request  |  Status:  new 
Priority:  normal   |   Component:  Compiler
 Version:  6.8.2|Severity:  normal  
Keywords:   |Testcase:  
Architecture:  Unknown  |  Os:  Unknown 
+---
 calling `ghc --make` generates a lot of files, `.o`, `.hi`, `.exe`,
 `.exe.manifest`, .. moreover, those files may be in different directories,
 etc.

 a nice way to get rid of all those leftovers would be a `ghc --cleanup`,
 with the same options and parameters as `ghc --make`, which would delete
 everything that `ghc --make` would generate.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2252: Extreme performance degradation on minor code change

2008-05-01 Thread GHC
#2252: Extreme performance degradation on minor code change
--+-
 Reporter:  simona|  Owner:
 Type:  bug   | Status:  new   
 Priority:  normal|  Milestone:
Component:  Compiler  |Version:  6.8.2 
 Severity:  normal| Resolution:
 Keywords:| Difficulty:  Unknown   
 Testcase:|   Architecture:  x86_64 (amd64)
   Os:  Linux |  
--+-
Comment (by simonpj):

 You made a mistake in the new `GoodPerform.hs`; you wrote
 {{{
   replicateM_ 1000 $ do
 --res1 <- fixpoint initial bottom bottom vn 1
 --unless (res1 `subset` res1) $ putStrLn "something's wrong"
 res2 <- fixpoint initial bottom bottom vn 1
 unless (res2 `subset` res2) $ putStrLn "something's wrong"
 }}}
 but you meant to use two calls to `replicateM_`, didn't you?

 Anyway I know what's going on.  Here is the crucial fragment of the two
 forms, after desguaring:
 {{{
 Bad:
   replicateM_ 1000 (f 10 >>= (\res1 -> f 20 >>= (\res2 -> return (

 Good:
   replicateM_ 1000 (f 10) >> replicateM_ 1000 (f 20)
 }}}
 The `f` is the `fixpoint` function; the `10` and `20` are the constant
 args to those two calls.  Just look at it!  The key point is that in both
 cases, the subexpression `(f 10)` is outside any lambdas, and hence is
 executed just once.  It's just as I said, although obscured by clutter:
 the computation is unaffected by IO state, so there is no need for it to
 be repeated each time.

 Furthermore, in the `good` case, the call `(f 20)` is '''also#'' outside
 any lambdas, and ''hence is computed only once''. But in the `bad` case,
 the call `(f 20)` is inside the `(\ res1 -> ...)` abstraction, and so is
 computed once for each call of the (\res1...); that is 1000 times.

 So that's why there's the big difference.  It is a little puzzling, but it
 becomes much clearer when you desugar the do-notation.

 The moral, as often, is that if you put a constant expression inside a
 loop, GHC will often compute it just once.  But this occurs much more
 often in benchmarks than in real programs

 Simon

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #2257: validate hangs in configure

2008-05-01 Thread GHC
#2257: validate hangs in configure
---+
Reporter:  nr  |   Owner:  
Type:  bug |  Status:  new 
Priority:  normal  |   Component:  Build System
 Version:  6.8.2   |Severity:  major   
Keywords:  |Testcase:  
Architecture:  x86 |  Os:  Linux   
---+
 Running ./validate on a freshly updated HEAD results in the script hanging
 during the configuration process.

 Here's what's on the screen:

 {{{
 checking whether float word order is big endian... no
 checking for nlist in -lelf... no
 checking leading underscore in symbol names... no
 checking whether ld understands -x... yes
 checking whether ld is GNU ld... yes
 checking for .subsections_via_symbols... no
 checking for GNU non-executable stack support... no
 checking for clock_gettime in -lrt... yes
 checking for clock_gettime... yes
 checking for timer_create... yes
 checking for timer_settime... yes
 checking for a working timer_create(CLOCK_REALTIME)...
 }}}

 HEre's what 'top' has to say about what is running:

 {{{
   PID USER  PR  NI  VIRT  RES  SHR S %CPU %MEMTIME+  COMMAND
 29457 nr20   0  2000  480  368 R   88  0.0   9:18.12 conftest
 }}}

 And strace of that process reveals an endless stream of these:
 {{{
 --- SIGVTALRM (Virtual timer expired) @ 0 (0) ---
 sigreturn() = ? (mask now [])
 --- SIGVTALRM (Virtual timer expired) @ 0 (0) ---
 sigreturn() = ? (mask now [])
 --- SIGVTALRM (Virtual timer expired) @ 0 (0) ---
 sigreturn() = ? (mask now [])
 }}}

 The system is a 32-bit Debian testing/unstable, uname -a says
 {{{
 Linux homedog 2.6.24-1-686 #1 SMP Sat Apr 19 00:37:55 UTC 2008 i686
 GNU/Linux
 }}}

 The CPU is a dual-core AMD FX-60:
 {{{
 processor   : 0
 vendor_id   : AuthenticAMD
 cpu family  : 15
 model   : 35
 model name  : AMD Athlon(tm) 64 FX-60 Dual Core Processor
 stepping: 2
 }}}

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1544: Derived Read instances for recursive datatypes with infix constructors are too inefficient

2008-05-01 Thread GHC
#1544: Derived Read instances for recursive datatypes with infix constructors 
are
too inefficient
--+-
 Reporter:  [EMAIL PROTECTED]  |  Owner: 
 Type:  bug   | Status:  new
 Priority:  normal|  Milestone:  6.10 branch
Component:  Compiler  |Version:  6.6.1  
 Severity:  normal| Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  Unknown
   Os:  Unknown   |  
--+-
Comment (by simonpj):

 See
 
[http://www.cs.uu.nl/wiki/bin/view/Center/TTTAS#The_internals_for_a_better_Deriv
 The internals for a better Deriving Read and Write] which describes
 progress by Doaitse and his colleagues.

 Simon

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2254: have Control.Arrow re-export (>>>) and (<<<)

2008-05-01 Thread GHC
#2254: have Control.Arrow re-export (>>>) and (<<<)
---+
Reporter:  ross|Owner: 
Type:  proposal|   Status:  new
Priority:  normal  |Milestone: 
   Component:  libraries/base  |  Version:  6.8.2  
Severity:  normal  |   Resolution: 
Keywords:  | Testcase: 
Architecture:  Unknown |   Os:  Unknown
---+
Comment (by ganesh):

 I support this; I think it's unnecessarily burdensome on users to have to
 import Control.Category when using arrows.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #2256: Incompleteness of type inference: must quantify over implication constraints

2008-05-01 Thread GHC
#2256: Incompleteness of type inference: must quantify over implication
constraints
-+--
Reporter:  simonpj   |   Owner:  simonpj
Type:  bug   |  Status:  new
Priority:  normal|   Milestone:  6.10 branch
   Component:  Compiler  | Version:  6.8.2  
Severity:  normal|Keywords: 
  Difficulty:  Unknown   |Testcase: 
Architecture:  Unknown   |  Os:  Unknown
-+--
 Consider this program (from Iavor)
 {{{
 f x = let g y = let h :: Eq c => c -> ()
 h z = sig x y z
 in ()
   in fst x

 sig :: Eq (f b c) => f () () -> b -> c -> ()
 sig _ _ _ = ()
 }}}
 This example is rejected by both Hugs and GHC but I think that it is a
 well typed program. The Right Type to infer for g is this:
 {{{
 g :: forall b. (forall c. Eq c => Eq (b,c)) => b -> ()
 }}}
 but GHC never quantifies over implication constraints at the moment.  As a
 result, type inference is incomplete (although in practice no one
 notices).  I knew about this, but I don't think it's recorded in Trac,
 hence this ticket.

 Following this example through also led me to notice a lurking bug: see
 "BUG WARNING" around line 715 of `TcSimplify`.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2247: GHC accepts FD violations, unless the conflicing instances are used

2008-05-01 Thread GHC
#2247: GHC accepts FD violations, unless the conflicing instances are used
-+--
 Reporter:  claus|  Owner:  
 Type:  bug  | Status:  reopened
 Priority:  normal   |  Milestone:  
Component:  Compiler (Type checker)  |Version:  6.9 
 Severity:  normal   | Resolution:  
 Keywords:  TF vs FD | Difficulty:  Unknown 
 Testcase:   |   Architecture:  Unknown 
   Os:  Unknown  |  
-+--
Changes (by claus):

  * status:  closed => reopened
  * resolution:  duplicate =>

Comment:

 Replying to [comment:2 simonpj]:
 > I assume you are using some flags?

 always!-) in fact, as you can see from this little example, using GHC has
 become very inconvenient due to the proliferation of flags. first, i have
 to iterate to figure out which flags i need to get my code accepted. then,
 i have to do the same again because the GHCi session does *not* inherit
 the `LANGUAGE` pragmas from the module i load..

 it doesn't help that `UndecidableInstances` is needed so often for
 perfectly decidable code. in this case, delegating to another constraint
 that is no smaller than the original already requires this extension,
 independent of coverage.

 > In fact to get `Improve` to compile you need
 > {{{
 > $gpj -c -XFunctionalDependencies
 > -XMultiParamTypeClasses
 > -XFlexibleInstances
 > -fallow-undecidable-instances
 > -XFlexibleContexts
 > Foo.hs
 > }}}
 > The offending one is `-fallow-undecidable-instances`, and this ticket is
 an excellent example of #1241.  Currently saying `-fallow-undecidable-
 instances` lifts the coverage condition. I acknowledge that this isn't the
 Right Thing in #1241, but it doesn't threaten type soundness (ie programs
 will not seg-fault).
 >
 > So I'm going to close this bug and link to it from #1241.  Re-open if I
 have misunderstood.

 yes and no. yes, for the current implementation of FDs in GHC; no, in
 principle.

 neither coverage nor fullness appear necessary for confluence (cf.
 [http://www.cs.kuleuven.be/~toms/Research/papers/tfp08-full.pdf Restoring
 Confluence for Functional Dependencies, T. Schrijvers, M. Sulzmann]), and
 a confluent implementation of FDs should raise all inconsistencies, with
 the exception of dead code (the ticket example was meant to highlight this
 gap, see also the discussion of forward inference in
 http://www.haskell.org/pipermail/haskell-cafe/2008-April/042219.html).

 the variation shows clearly that GHC drops FD/improvement-related
 information, so that not even all conflicts in live constraints are
 flagged. it seems that one of the places where improvement-related
 information is dropped is separate compilation (if all FD-relevant
 constraints were cached as they arise, and preserved in interface files,
 inlining across module boundaries ought to make no difference, right?).

 note also this reduced variation
 {{{
 class FD a b | a -> b
 instance CFD a b => FD a b

 class FD a b => CFD a b
 instance CFD Bool Char
 -- instance CFD Bool Bool
 }}}
 which is accepted by Hugs (in Hugs mode), in spite of its presumably
 stricter conditions. yet, on uncommenting the second `CFD` instance, Hugs
 notices the FD-inconsistency immediately, while GHCi doesn't (and the
 other variations show that GHC won't necessarily notice the issue later,
 either).

 so, the two tickets are linked, but if one looks beyond ruling out this
 kind of example (and #1241 seemed to tend in the direction of finding less
 restrictive conditions than GHC has, not more restrictive conditions than
 Hugs has), there seems to be more going on. at the very least, this ticket
 should be looked into when #1241 gets fixed, in case it isn't covered by
 the same fix.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2252: Extreme performance degradation on minor code change

2008-05-01 Thread GHC
#2252: Extreme performance degradation on minor code change
--+-
 Reporter:  simona|  Owner:
 Type:  bug   | Status:  new   
 Priority:  normal|  Milestone:
Component:  Compiler  |Version:  6.8.2 
 Severity:  normal| Resolution:
 Keywords:| Difficulty:  Unknown   
 Testcase:|   Architecture:  x86_64 (amd64)
   Os:  Linux |  
--+-
Comment (by simona):

 I think (and hope) that BadPerform is going bizarrely slow. BadPerform
 runs the same loop twice and should thus only be twice as slow as
 GoodPerform, not 800 times as slow. I ran more complex examples a million
 times and got something in the range of 4-8s which means that each
 fixpoint computation (involving 8 iterations around the loop) takes 4-8us
 which is actually quite fast since that would mean that some complicated
 list operations and a several calls to simplex are done in a few thousand
 instructions on this 2.X GHz machine. But the numbers did seem to make
 sense in relation to each other.

 I tried to add the `-fno-state-hack` flag but that didn't change anything.

 I copied stubs of the relevant function into a new module called `Fake.hs`
 -- I tried putting the functions directly into `BadPerform.hs` but that it
 went as fast as `GoodPerform.hs`. I made the `fixpoint` function go slower
 by adding the test `minimum [i+j | i <- [1..100], j <- [1..100]]<3` as you
 suggested.

 The results:
 {{{
 1858$ rm -f tests/GoodPerform.o && ghc-6.8.2 --make GoodPerform.hs && time
 GoodPerform
 real0m0.008s
 user0m0.004s
 sys 0m0.004s
 1859$ rm -f tests/BadPerform.o && ghc-6.8.2 --make BadPerform.hs && time
 BadPerform
 Linking BadPerform ...

 real0m2.923s
 user0m2.911s
 sys 0m0.010s
 }}}

 I will update the two source files and their simplifier dump. I'll also
 add `Fake.hs`.

 Thanks for looking into this.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1241: Functional dependency Coverage Condition is lifted, and should not be

2008-05-01 Thread GHC
#1241: Functional dependency Coverage Condition is lifted, and should not be
-+--
 Reporter:  guest|  Owner: 
 Type:  bug  | Status:  new
 Priority:  normal   |  Milestone:  _|_
Component:  Compiler (Type checker)  |Version:  6.6
 Severity:  normal   | Resolution: 
 Keywords:   | Difficulty:  Unknown
 Testcase:   |   Architecture:  Unknown
   Os:  Unknown  |  
-+--
Comment (by simonpj):

 See also #2247, which gives an example of the confusing things that happen
 if we don't impose the Coverage Condition.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2247: GHC accepts FD violations, unless the conflicing instances are used

2008-05-01 Thread GHC
#2247: GHC accepts FD violations, unless the conflicing instances are used
-+--
 Reporter:  claus|  Owner:   
 Type:  bug  | Status:  closed   
 Priority:  normal   |  Milestone:   
Component:  Compiler (Type checker)  |Version:  6.9  
 Severity:  normal   | Resolution:  duplicate
 Keywords:  TF vs FD | Difficulty:  Unknown  
 Testcase:   |   Architecture:  Unknown  
   Os:  Unknown  |  
-+--
Changes (by simonpj):

  * status:  new => closed
  * difficulty:  => Unknown
  * resolution:  => duplicate

Comment:

 I assume you are using some flags?
 {{{
 ghc -c -XFunctionalDependencies Foo.hs -XMultiParamTypeClasses

 Foo.hs:5:1:
 Illegal instance declaration for `FD a b'
 (All instance types must be of the form (T a1 ... an)
  where a1 ... an are distinct type *variables*
  Use -XFlexibleInstances if you want to disable this.)
 In the instance declaration for `FD a b'
 }}}
 Adding `-XFlexibleInstances` gives
 {{{
 bash-3.1$ ghc -c -XFunctionalDependencies Foo.hs -XMultiParamTypeClasses
 -XFlexibleInstances

 Foo.hs:5:1:
 Constraint is no smaller than the instance head
   in the constraint: CFD a b
 (Use -fallow-undecidable-instances to permit this)
 In the instance declaration for `FD a b'

 Foo.hs:5:1:
 Illegal instance declaration for `FD a b'
 (the Coverage Condition fails for one of the functional
 dependencies;
  Use -fallow-undecidable-instances to permit this)
 In the instance declaration for `FD a b'
 }}}
 In fact to get `Improve` to compile you need
 {{{
 $gpj -c -XFunctionalDependencies
 -XMultiParamTypeClasses
 -XFlexibleInstances
 -fallow-undecidable-instances
 -XFlexibleContexts
 Foo.hs
 }}}
 The offending one is `-fallow-undecidable-instances`, and this ticket is
 an excellent example of #1241.  Currently saying `-fallow-undecidable-
 instances` lifts the coverage condition. I acknowledge that this isn't the
 Right Thing in #1241, but it doesn't threaten type soundness (ie programs
 will not seg-fault).

 So I'm going to close this bug and link to it from #1241.  Re-open if I
 have misunderstood.

 Simon

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2252: Extreme performance degradation on minor code change

2008-05-01 Thread GHC
#2252: Extreme performance degradation on minor code change
--+-
 Reporter:  simona|  Owner:
 Type:  bug   | Status:  new   
 Priority:  normal|  Milestone:
Component:  Compiler  |Version:  6.8.2 
 Severity:  normal| Resolution:
 Keywords:| Difficulty:  Unknown   
 Testcase:|   Architecture:  x86_64 (amd64)
   Os:  Linux |  
--+-
Comment (by simonpj):

 Crumbs!  So switching on -O makes `GoodPerform` run slowly too!

 Can you try with `-fno-state-hack`?

 How fast do you ''expect'' this to run?  For example, if you do just one
 of the fixpoints 1000 times, is that fast?  Is it supposed to be fast?
 I'm trying to ask whether `GoodPerform` is going bizarrely fast or
 `BadPerform` is going bizarrely slowly.

 Well done cutting down `fixpoint`.  It'd be a huge help if you could so so
 some more, so that GLPK, gmp etc were not needed.  If it runs too fast,
 just do something expensive, like `min [i+j | i <- [1..n], j <- [1..n]]`.

 Simon

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2252: Extreme performance degradation on minor code change

2008-05-01 Thread GHC
#2252: Extreme performance degradation on minor code change
--+-
 Reporter:  simona|  Owner:
 Type:  bug   | Status:  new   
 Priority:  normal|  Milestone:
Component:  Compiler  |Version:  6.8.2 
 Severity:  normal| Resolution:
 Keywords:| Difficulty:  Unknown   
 Testcase:|   Architecture:  x86_64 (amd64)
   Os:  Linux |  
--+-
Comment (by simona):

 I've simplified the programs. This is what they do now:
 {{{
 aconit:~/current/source/sparseDomain:1821$ rm -f tests/BadPerform.o &&
 ghc-6.8.2 --make tests/BadPerform.hs -ddump-simpl > badSimpl.txt && time
 tests/BadPerform
 [1 of 1] Compiling Main ( tests/BadPerform.hs,
 tests/BadPerform.o )
 Linking tests/BadPerform ...

 real0m9.585s
 user0m9.551s
 sys 0m0.033s
 aconit:~/current/source/sparseDomain:1822$ rm -f tests/GoodPerform.o &&
 ghc-6.8.2 --make tests/GoodPerform.hs -ddump-simpl > goodSimpl.txt && time
 tests/GoodPerform
 [1 of 1] Compiling Main ( tests/GoodPerform.hs,
 tests/GoodPerform.o )
 Linking tests/GoodPerform ...

 real0m0.015s
 user0m0.012s
 sys 0m0.002s
 }}}

 There are some fishy non-improving optimizations going on. As you
 suggested, I re-complied with optimizations:

 {{{
 aconit:~/current/source/sparseDomain:1825$ rm -f tests/BadPerform.o &&
 ghc-6.8.2 --make tests/BadPerform.hs -O -ddump-simpl > badSimplOpt.txt &&
 time tests/BadPerform
 [1 of 1] Compiling Main ( tests/BadPerform.hs,
 tests/BadPerform.o )
 Linking tests/BadPerform ...

 real0m19.101s
 user0m19.044s
 sys 0m0.054s
 aconit:~/current/source/sparseDomain:1826$ rm -f tests/GoodPerform.o &&
 ghc-6.8.2 --make tests/GoodPerform.hs -O -ddump-simpl > goodSimplOpt.txt
 && time tests/GoodPerform
 [1 of 1] Compiling Main ( tests/GoodPerform.hs,
 tests/GoodPerform.o )
 Linking tests/GoodPerform ...

 real0m18.974s
 user0m18.914s
 sys 0m0.056s
 }}}

 I have also tried to radically simplify the `fixpoint` function which
 would then return immediately. It is so simple, that I could build a cabal
 package that doesn't link to the simplex solver and which would therefore
 be easy to build for you. However, I'm not sure if you can see the
 difference anymore: Repeating the good case one million times takes 0.4
 seconds, repeating the bad case one million times (which does twice the
 amount of work in each iteration) takes 1.4 seconds. Repeating the good
 case two million times takes 0.8 seconds, as expected.

 I hope the attached simplifier outputs are informative enough. Note that
 I've updated the source files too!

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2252: Extreme performance degradation on minor code change

2008-05-01 Thread GHC
#2252: Extreme performance degradation on minor code change
--+-
 Reporter:  simona|  Owner:
 Type:  bug   | Status:  new   
 Priority:  normal|  Milestone:
Component:  Compiler  |Version:  6.8.2 
 Severity:  normal| Resolution:
 Keywords:| Difficulty:  Unknown   
 Testcase:|   Architecture:  x86_64 (amd64)
   Os:  Linux |  
--+-
Comment (by simonpj):

 Thanks.  More info: what command line arguments are you using when
 compiling your program?  In your `-ddump-simpl` I see invocations of
 `GHC.Base.$`, which suggests you aren't using -O. That never occurred to
 me. Do you get the same performance differences with -O?

 Of course, you still should not get these huge differences even without
 -O, but I'm interested because it'll give clues about where the problem
 is.


 The Core code looks ok to me, so I'm still v puzzled about why you would
 see big perf differences.   I wonder if you can make this easier to
 reproduce, and at the same time give more clues.  For example, suppose you
 trim out most of the functions the `fixpoint` calls, and leave just some
 reasonably-expensive thing (some random quadratically-expensive algorithm,
 say).  Does the effect still happen?  Or is it somehow connected to the
 code that is called (`meetAsym`, `equalityToInequalities`, etc)?  And if
 so can you narrow down which code is the culprit, by stubbing out other
 parts?


 Simon

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2252: Extreme performance degradation on minor code change

2008-05-01 Thread GHC
#2252: Extreme performance degradation on minor code change
--+-
 Reporter:  simona|  Owner:
 Type:  bug   | Status:  new   
 Priority:  normal|  Milestone:
Component:  Compiler  |Version:  6.8.2 
 Severity:  normal| Resolution:
 Keywords:| Difficulty:  Unknown   
 Testcase:|   Architecture:  x86_64 (amd64)
   Os:  Linux |  
--+-
Comment (by simona):

 Gosh I hope this isn't happening since I used the timing results of the
 good code in a paper.

 Adding `-fno-full-laziness` to the compilation of `GoodPerform.hs` changes
 nothing (thankfully). Note also that the good performer is less likely to
 benefit from lazyness optimization since it first runs one loop for 1000
 times, then another loop for 1000 times. The bad one has the potential for
 optimization since it runs two nearly identical calculations 1000 times. I
 might be possible, of course, that the loops in the good code are simple
 enough for optimizations to kick in whereas they are too big in the bad
 case. However, I ran other, more complex loops that have a good
 performance, too. I'm still assuming that it is the bad code that triggers
 some bad behavior.

 There is one side-effect in each loop iteration which tests some invariant
 on the result. There are quite a few computations that call the external
 library but which are pure, so I've wrapped them in `unsafePerformIO`. I
 don't know if that matters.

 Also, I should mention that both programs run in constant space (around
 20MB virtual space), hence it's not a space leak that keeps back the
 tighter loop in `BadPerform.hs`. I compiled the code without any -O flags
 and I attach the two simplifier outputs. There are no `lvl_` strings in
 either file.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #2255: Improve SpecConstr for free variables

2008-05-01 Thread GHC
#2255: Improve SpecConstr for free variables
-+--
Reporter:  simonpj   |   Owner: 
Type:  run-time performance bug  |  Status:  new
Priority:  normal|   Milestone:  _|_
   Component:  Compiler  | Version:  6.8.2  
Severity:  normal|Keywords: 
  Difficulty:  Unknown   |Testcase: 
Architecture:  Unknown   |  Os:  Unknown
-+--
 This ticket records a suggestion for improving `SpecConstr`, so we don't
 lose it. The original `SpecConstr` transformation is described in
 "[http://research.microsoft.com/%7Esimonpj/papers/spec-constr Call pattern
 specialisation for Haskell]".  Consider this program
 {{{
f x = let g y = ...case x of { z:zs -> e1; [] -> e2 } ...
   in
   ...case x of
 z:zs -> if ... then g 3 else g 4
 []   -> ...
 }}}
 Here 'x' is free in 'g', but x's value is known at g's call sites.  It's
 not enough just to know "x is a cons" inside g; we must also have access
 to z,zs.  So perhaps the thing to do is to imagine lambda-lifting 'g' to
 become 'gl' thus:
 {{{
   gl x y = ...case x of { z:zs -> e1; [] -> e2 } ...

   f x = ...case x of
 z:zs -> if ... then gl x 3 else gl x 4
 []   -> ...
 }}}
 Now the `SpecConstr` transformation will apply nicely.  And it's arguably
 a bad shortcoming that currently the mere act of lambda lifting can affect
 how effective `SpecConstr` is.

 Of course, we only want to lambda-lift wrt the parameters that'll be
 specialised, so this transformation probably wants to be done at the same
 time as the rest of `SpecConstr`. I don't have much idea of how hard
 that'd be, but it's a nice idea.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs