Re: [GHC] #5248: Infer type context in a type signature

2011-06-09 Thread GHC
#5248: Infer type context in a type signature
+---
Reporter:  gidyn|Owner: 
  
Type:  feature request  |   Status:  new
  
Priority:  normal   |Milestone: 
  
   Component:  Compiler (Type checker)  |  Version:  7.0.3  
  
Keywords:   | Testcase: 
  
   Blockedby:   |   Difficulty: 
  
  Os:  Unknown/Multiple | Blocking: 
  
Architecture:  Unknown/Multiple |  Failure:  GHC rejects valid 
program
+---

Comment(by gidyn):

 I'm not sure what you mean by "that's the way Haskell is"; many GHC
 features go beyond the Haskell standard.

 Perhaps I misworded the ticket, as I wasn't referring to inferring type
 contexts from a method's implementation. The type context given in a data-
 type's definition should be available wherever the data type is used, so
 the (...) => syntax shouldn't be necessary for this case.

 To put the issue differently: A type variable in a data/type constructor
 is restricted to a given type class. Currently, this restriction has to be
 repeated in the signature of every function that uses the restriction.
 This repetition is superfluous noise, which is required by the compiler,
 but adds no information.

-- 
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] #4504: "awaitSignal Nothing" does not block thread with -threaded

2011-06-09 Thread GHC
#4504: "awaitSignal Nothing" does not block thread with -threaded
--+-
  Reporter:  adept|  Owner:  
  Type:  bug  | Status:  new 
  Priority:  normal   |  Milestone:  7.0.2   
 Component:  Runtime System   |Version:  7.0.1   
Resolution:   |   Keywords:  
  Testcase:   |  Blockedby:  
Difficulty:   | Os:  Unknown/Multiple
  Blocking:   |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  |  
--+-
Changes (by kazu-yamamoto):

  * owner:  adept =>
  * status:  closed => new
  * resolution:  fixed =>


Comment:

 This bug appears again in GHC 7.0.3. I tested the code above both on Linux
 and Mac. awaitSignal does not block in both cases with -threaded.

-- 
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] #5249: Non-understandable comment in compiler/main/GHC.hs

2011-06-09 Thread GHC
#5249: Non-understandable comment in compiler/main/GHC.hs
-+--
Reporter:  dterei|   Owner:  
Type:  task  |  Status:  new 
Priority:  normal|   Component:  Compiler
 Version:  7.1   |Keywords:  
Testcase:|   Blockedby:  
  Os:  Unknown/Multiple  |Blocking:  
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
-+--
 the file [[GhcFile(compiler/main/GHC.hs)]] contains a comment that
 follows:

 {{{
 -- | Request information about a loaded 'Module'
 getModuleInfo :: GhcMonad m => Module -> m (Maybe ModuleInfo)  -- XXX:
 Maybe X
 getModuleInfo mdl = withSession $ \hsc_env -> do
   let mg = hsc_mod_graph hsc_env
   if mdl `elem` map ms_mod mg
 then liftIO $ getHomeModuleInfo hsc_env (moduleName mdl)
 else do
   {- if isHomeModule (hsc_dflags hsc_env) mdl
 then return Nothing
 else -} liftIO $ getPackageModuleInfo hsc_env mdl
-- getPackageModuleInfo will attempt to find the interface, so
-- we don't want to call it for a home module, just in case there
-- was a problem loading the module and the interface doesn't
-- exist... hence the isHomeModule test here.  (ToDo: reinstate)
 }}}

 Neither myself or Simon M know what the comment means. We should figure it
 out and fix up this code and comment accordingly. The XXX: Maybe X doesn't
 make sense either.

-- 
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] #2189: hSetBuffering stdin NoBuffering doesn't work on Windows

2011-06-09 Thread GHC
#2189: hSetBuffering stdin NoBuffering doesn't work on Windows
-+--
  Reporter:  FalconNL|  Owner:
  Type:  bug | Status:  new   
  Priority:  low |  Milestone:  7.2.1 
 Component:  libraries/base  |Version:  6.8.2 
Resolution:  |   Keywords:  hsetbuffering buffering buffer
  Testcase:  |  Blockedby:
Difficulty:  Unknown | Os:  Windows   
  Blocking:  |   Architecture:  x86   
   Failure:  None/Unknown|  
-+--
Changes (by Artyom.Kazak):

 * cc: Artyom.Kazak@… (added)


-- 
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] #5234: The parListWHNF optimisation isn't

2011-06-09 Thread GHC
#5234: The parListWHNF optimisation isn't
--+-
Reporter:  duncan |Owner:  simonmar
Type:  bug|   Status:  new 
Priority:  high   |Milestone:  7.2.1   
   Component:  libraries (other)  |  Version:  7.1 
Keywords: | Testcase:  
   Blockedby: |   Difficulty:  
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-
Changes (by simonpj):

  * owner:  => simonmar
  * priority:  normal => high
  * milestone:  => 7.2.1


Comment:

 Simon, you know what's going on here. Shouldn't be hard to fix.

 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] #5205: Control.Monad.forever leaks space

2011-06-09 Thread GHC
#5205: Control.Monad.forever leaks space
-+--
Reporter:  akio  |Owner:  igloo  
Type:  bug   |   Status:  new
Priority:  highest   |Milestone:  7.2.1  
   Component:  libraries/base|  Version:  7.0.3  
Keywords:| Testcase: 
   Blockedby:|   Difficulty: 
  Os:  Unknown/Multiple  | Blocking: 
Architecture:  Unknown/Multiple  |  Failure:  Runtime performance bug
-+--
Changes (by simonpj):

  * owner:  simonpj => igloo


Comment:

 I've made 'forever' INLINABLE, and added a SPECIALISE pragma in GHC.ST.
 {{{
 commit ae10342b49b95393b09ffee8df8c847409699968
 Author: Simon Peyton Jones 
 Date:   Thu Jun 9 20:44:21 2011 +0100

 Make 'forever' inlinable (fixes Trac #5205)

 See Note [Make forever INLINABLE] in Control.Monad

 >---

  Control/Monad.hs |   18 ++
  GHC/ST.lhs   |4 
  2 files changed, 22 insertions(+), 0 deletions(-)
 }}}

 That fixes the bug, but only with `-O`.  Without `-O` you still get the
 leak, and I don't really think its unreasonable.  You have
 {{{
 x = forever (return ())
 }}}
 which expands to
 {{{
 x = return () >> return () >> return () >> etc
 }}}
 If `(>>)` was expensive when applied to two args, then it'd be right to
 hang onto the computed result.  In the case of IO it isn't expensive, and
 it's best to recompute (and save space) but only the optimiser can reveal
 that.

 Ian: can you add a perf/ test please, then close?

 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] #5248: Infer type context in a type signature (was: Infer type context from type or data constructor)

2011-06-09 Thread GHC
#5248: Infer type context in a type signature
+---
Reporter:  gidyn|Owner: 
  
Type:  feature request  |   Status:  new
  
Priority:  normal   |Milestone: 
  
   Component:  Compiler (Type checker)  |  Version:  7.0.3  
  
Keywords:   | Testcase: 
  
   Blockedby:   |   Difficulty: 
  
  Os:  Unknown/Multiple | Blocking: 
  
Architecture:  Unknown/Multiple |  Failure:  GHC rejects valid 
program
+---

Old description:

> If I have code such as
>
> {{{
> class Foo f where
> foo :: a -> f a
>
> data Bar f a = Foo f => Bar {bar :: f a}
>
> instance Foo (Bar f) where
> foo a = Bar (foo a)
> }}}
>
> GHC will demand Foo f => on the instance declaration, even though this
> can be inferred from the definition of Bar.
>
> I understand ''why'' this is happening, but it should not be necessary to
> repeat information already given. Some code violates DRY dozens of times
> because of this limitation.

New description:

 If I have code such as

 {{{
 class Foo f where
 foo :: a -> f a

 data Bar f a = Foo f => Bar {bar :: f a}

 instance Foo (Bar f) where
 foo a = Bar (foo a)
 }}}

 GHC will demand `Foo f =>` on the instance declaration, even though this
 can be inferred from the definition of Bar.

 I understand ''why'' this is happening, but it should not be necessary to
 repeat information already given. Some code violates DRY dozens of times
 because of this limitation.

--

Comment(by simonpj):

 I'm sorry but that's the way Haskell is.  You could imagine some form like
 {{{
 instance (...) => Foo (Bar f) where
   foo a = ...
 }}}
 meaning "please infer the context for me".  This would be useful for type
 signatures more generally. For example:
 {{{
 f :: (...) => [a] -> String
 f xs = show (sum xs)
 }}}
 Here the full type signature would be
 {{{
 f :: (Num a, Show a) => [a] -> String
 }}}
 This has come up before but I can't find a ticket for it, so I'll treat
 this as it.

 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] #5246: Duplicate type error messages with implicit parameters

2011-06-09 Thread GHC
#5246: Duplicate type error messages with implicit parameters
--+-
  Reporter:  NickSmallbone|  Owner:  
  Type:  bug  | Status:  closed  
  Priority:  normal   |  Milestone:  
 Component:  Compiler (Type checker)  |Version:  7.0.3   
Resolution:  fixed|   Keywords:  
  Testcase:  typecheck/should_fail/T5246  |  Blockedby:  
Difficulty:   | Os:  Unknown/Multiple
  Blocking:   |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown |  
--+-
Changes (by simonpj):

 * cc: dimitris@… (added)
  * status:  new => closed
  * resolution:  => fixed
  * testcase:  => typecheck/should_fail/T5246


Comment:

 Happily this error is gone in HEAD (= 7.2).  There are quite a few
 typechecker changes, and I don't know which one fixed it!

 I've added a regresssion test.  Thanks for reporting.

 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] #5248: Infer type context from type or data constructor

2011-06-09 Thread GHC
#5248: Infer type context from type or data constructor
-+--
Reporter:  gidyn |   Owner:   
Type:  feature request   |  Status:  new  
Priority:  normal|   Component:  Compiler (Type checker)  
 Version:  7.0.3 |Keywords:   
Testcase:|   Blockedby:   
  Os:  Unknown/Multiple  |Blocking:   
Architecture:  Unknown/Multiple  | Failure:  GHC rejects valid program
-+--
 If I have code such as

 {{{
 class Foo f where
 foo :: a -> f a

 data Bar f a = Foo f => Bar {bar :: f a}

 instance Foo (Bar f) where
 foo a = Bar (foo a)
 }}}

 GHC will demand Foo f => on the instance declaration, even though this can
 be inferred from the definition of Bar.

 I understand ''why'' this is happening, but it should not be necessary to
 repeat information already given. Some code violates DRY dozens of times
 because of this limitation.

-- 
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] #5247: include generics library

2011-06-09 Thread GHC
#5247: include generics library
-+--
Reporter:  jhala |   Owner:   
Type:  feature request   |  Status:  new  
Priority:  normal|   Component:  libraries (other)
 Version:  7.0.3 |Keywords:   
Testcase:|   Blockedby:   
  Os:  Unknown/Multiple  |Blocking:   
Architecture:  Unknown/Multiple  | Failure:  None/Unknown 
-+--
 Is it possible to include a generics library (e.g. SYB) in the boot
 libraries?
 This would make the GHC API easier to use within systems whose
 dependencies are a subset of GHC's (e.g. Haddock). In particular,
 various internal GHC types are instances of Data etc. and can be
 accessed easily via the generics library.

 (I have a variant of Haddock that can, in conjunction with HsColour,
 generate mouseover types, http://goto.ucsd.edu/~rjhala/Annot/ but
 it uses SYB to traverse the parsed-and-typechecked-source.)

-- 
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] #5208: Unroll array copy/clone primops in the native and LLVM code generators

2011-06-09 Thread GHC
#5208: Unroll array copy/clone primops in the native and LLVM code generators
-+--
Reporter:  tibbe |Owner:  
Type:  feature request   |   Status:  patch   
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  7.1 
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--

Comment(by dterei):

 Replying to [comment:9 tibbe]:
 > Probably. I will make it a top-level constant for now. Ideally each
 architecture should have its own limit and I'd like to see a common place
 to but architecture specific configuration. The memcpy unrolling
 optimization should ideally be written once and reused on all
 architectures. This requires that we abstract over move instructions and
 the like. This is what LLVM does. It significantly reduces implementation
 effort.

 OK. I'm not sure if it would be worth the effort given we only have two
 backends (X86 and SPARC) and only really X86 is used.

 > Here's what I suggest: I'll work on improving the tests and fix the
 minor things. The bigger things (like movabs) are additional optimizations
 on top of the current ones so I suggest we save those for separate
 patches.

 Sounds good to me!

-- 
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] #5236: Circular functional dependencies cause loop in typechecker

2011-06-09 Thread GHC
#5236: Circular functional dependencies cause loop in typechecker
--+-
 Reporter:  dimitris  |  Owner:
 Type:  bug   | Status:  closed
 Priority:  normal|  Component:  Compiler (Type checker)   
  Version:  7.0.3 | Resolution:  fixed 
 Keywords:|   Testcase:  typecheck/should_fail/T5236.hs
Blockedby:| Os:  Unknown/Multiple  
 Blocking:|   Architecture:  Unknown/Multiple  
  Failure:  None/Unknown  |  
--+-
Changes (by dimitris):

  * status:  new => closed
  * testcase:  => typecheck/should_fail/T5236.hs
  * resolution:  => fixed


Comment:

 OK, I just pushed the fix:

 commit 107715b367678d1325a5eecd4a4f13ba6ada3c6c
 Author: Dimitrios Vytiniotis 
 Date:   Wed Jun 8 18:24:21 2011 +0100

 Reorganized functional dependency reactions once more:
  1) generating Derived FDs as happens for equality superclasses
  2) Kept the optimization of immediately discharging items
 if fundeps cause a match
  3) Restructured top-reactions and interactions with inerts to
 behave similarly to each other.

 In particular, (1) fixes ticket #5236.

  compiler/typecheck/TcCanonical.lhs |  108 +---
  compiler/typecheck/TcInteract.lhs  |  256
 
  2 files changed, 204 insertions(+), 160 deletions(-)

-- 
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] #5208: Unroll array copy/clone primops in the native and LLVM code generators

2011-06-09 Thread GHC
#5208: Unroll array copy/clone primops in the native and LLVM code generators
-+--
Reporter:  tibbe |Owner:  
Type:  feature request   |   Status:  patch   
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  7.1 
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--

Comment(by tibbe):

 Thanks for reviewing!

 Replying to [comment:7 dterei]:
 >  '-- TODO: Add movabs instruction and support 64-bit sets.' - Can this
 be done now rather than later? It doesn't seem like it should take very
 long. Also I think once you have this done you should be able to unify the
 go functions of memcpy and memset

 The only reason I haven't done so already is that I don't know how to add
 a new instruction. If someone could give some pointers to all the places
 that need to be updated after adding a new instruction and whether I need
 to do something special for 64-bit only instructions I can take a stab at
 it.

 >  By saying add the movabs instruction I assume you want to change the
 memset function to initially store the value to set into a register and
 then mov that register into each of the memory slots. With this change you
 could also have memset handle the case where the value to be set is an
 expression other than a literal.

 Storing the value in a register is necessary as the mov instructions don't
 take 64-bit immediates.

 >  Should 'maxInlineSizeThreshold' be shared rather than duplicated?

 Probably. I will make it a top-level constant for now. Ideally each
 architecture should have its own limit and I'd like to see a common place
 to but architecture specific configuration. The memcpy unrolling
 optimization should ideally be written once and reused on all
 architectures. This requires that we abstract over move instructions and
 the like. This is what LLVM does. It significantly reduces implementation
 effort.

 > Looks fine but would it be worthwhile handling the alignment number in
 the 'emitMemmoveCall', 'emitMemcpyCall' and 'emitMemsetCall' functions
 themselves rather than passing it in as argument?

 I did it this way on purpose as I'd like it to be possible to use the
 `CallishMachOp`s even when the memory isn't aligned. I think this makes
 them more generally useful in GHC.

 > I think this testing method works well. I think you should test when the
 alignment is 8 though as well as 4. Also maybe try to cover a few more
 cases by using some different sizes and alignments. So create the arrays
 at size 71 but then test a few times using sizes say 1,64,65,66,67,71 and
 alignments 1,2,4,8. The unroll code is fairly tricky and so we want an
 extensive test case.

 I'll try to improve the test case this weekend.

 > I'll be happy to help out with any of these points when I have time.
 Other than extending the test case though I would be happy pushing it to
 head as it stands.

 Here's what I suggest: I'll work on improving the tests and fix the minor
 things. The bigger things (like movabs) are additional optimizations on
 top of the current ones so I suggest we save those for separate patches.

-- 
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] #5227: Large space usage when deriving Generic

2011-06-09 Thread GHC
#5227: Large space usage when deriving Generic
---+
  Reporter:  igloo |  Owner:  dreixel 
  Type:  bug   | Status:  closed  
  Priority:  high  |  Milestone:  7.2.1   
 Component:  Compiler  |Version:  7.1 
Resolution:  fixed |   Keywords:  
  Testcase:|  Blockedby:  
Difficulty:| Os:  Unknown/Multiple
  Blocking:|   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  |  
---+
Changes (by dreixel):

  * status:  new => closed
  * resolution:  => fixed


Comment:

 Done:
 
http://hackage.haskell.org/trac/ghc/changeset/bca02fda94c406cc484a3bfbcb6d120d43439935

 Heap profile now only goes up to 5M, Tuple.hi file is less than 10% in
 size compared to 7.0.

-- 
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] #5246: Duplicate type error messages with implicit parameters

2011-06-09 Thread GHC
#5246: Duplicate type error messages with implicit parameters
-+--
Reporter:  NickSmallbone |   Owner: 
Type:  bug   |  Status:  new
Priority:  normal|   Component:  Compiler (Type checker)
 Version:  7.0.3 |Keywords: 
Testcase:|   Blockedby: 
  Os:  Unknown/Multiple  |Blocking: 
Architecture:  Unknown/Multiple  | Failure:  None/Unknown   
-+--
 The following ill-typed program generates two identical type errors at the
 same source location:

 {{{
 {-# LANGUAGE ImplicitParams #-}

 foo :: (?x :: Int) => a
 foo = undefined

 bar =
 let ?x = "hello"
 in foo
 }}}

 The error messages are:

 {{{
 Test.hs:8:8:
 Couldn't match type `Int' with `[Char]'
 In the expression: foo
 In the expression: let ?x = "hello" in foo
 In an equation for `bar': bar = let ?x = "hello" in foo

 Test.hs:8:8:
 Couldn't match type `Int' with `[Char]'
 In the expression: foo
 In the expression: let ?x = "hello" in foo
 In an equation for `bar': bar = let ?x = "hello" in foo
 }}}

 Obviously, it should only print this error once. I encountered this in a
 larger program where it meant I got ''eight'' identical type errors at the
 same source position!

-- 
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] #5129: "evaluate" optimized away

2011-06-09 Thread GHC
#5129: "evaluate" optimized away
-+--
Reporter:  dons  |Owner:  simonmar   
Type:  bug   |   Status:  new
Priority:  normal|Milestone: 
   Component:  Compiler  |  Version:  7.0.3  
Keywords:  seq, evaluate | Testcase: 
   Blockedby:|   Difficulty: 
  Os:  Unknown/Multiple  | Blocking: 
Architecture:  Unknown/Multiple  |  Failure:  Incorrect result at runtime
-+--

Comment(by simonmar):

 See also `Note [Desugaring seq]` (1) and (2) in `DsUtils`.

-- 
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] #5205: Control.Monad.forever leaks space

2011-06-09 Thread GHC
#5205: Control.Monad.forever leaks space
-+--
Reporter:  akio  |Owner:  simonpj
Type:  bug   |   Status:  new
Priority:  highest   |Milestone:  7.2.1  
   Component:  libraries/base|  Version:  7.0.3  
Keywords:| Testcase: 
   Blockedby:|   Difficulty: 
  Os:  Unknown/Multiple  | Blocking: 
Architecture:  Unknown/Multiple  |  Failure:  Runtime performance bug
-+--
Changes (by simonmar):

  * owner:  igloo => simonpj


Comment:

 Ok, we looked at this, and it turns out that 6.12.3 desugars `forever`
 differently: in 6.12, a local recursive `let` was introduced, which meant
 that `forever` could be inlined (and hence specialised) at every call
 site, whereas in 7.0 the desugarer leaves the function as a top-level
 recursive function which cannot be inlined.

 The solution is to add an `INLINABLE` pragma for `forever`, which will
 allow it to be specialised at a call site.

-- 
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] #5243: ghc --make and ghci misses dependencies with explicit braces

2011-06-09 Thread GHC
#5243: ghc --make and ghci misses dependencies with explicit braces
-+--
Reporter:  simonpj   |Owner:  simonmar 
Type:  bug   |   Status:  new  
Priority:  high  |Milestone:  7.2.1
   Component:  Compiler  |  Version:  7.0.3
Keywords:| Testcase:   
   Blockedby:|   Difficulty:   
  Os:  Unknown/Multiple  | Blocking:   
Architecture:  Unknown/Multiple  |  Failure:  GHC rejects valid program
-+--
Changes (by simonmar):

  * owner:  => simonmar
  * failure:  None/Unknown => GHC rejects valid program


Comment:

 The bug appears to be in the parser: `Parser.parseHeader` does not handle
 the case where a module consists of explicit curly braces with no module
 header (see `body2` in `Parser.y`).

-- 
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] #5224: Improve consistency checking for family instances

2011-06-09 Thread GHC
#5224: Improve consistency checking for family instances
-+--
Reporter:  simonpj   |Owner:  
Type:  bug   |   Status:  new 
Priority:  highest   |Milestone:  7.2.1   
   Component:  Compiler  |  Version:  7.0.3   
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  Compile-time performance bug
-+--
Changes (by simonpj):

 * cc: chak@… (added)


-- 
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] #5224: Improve consistency checking for family instances

2011-06-09 Thread GHC
#5224: Improve consistency checking for family instances
-+--
Reporter:  simonpj   |Owner:  
Type:  bug   |   Status:  new 
Priority:  highest   |Milestone:  7.2.1   
   Component:  Compiler  |  Version:  7.0.3   
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  Compile-time performance bug
-+--

Comment(by simonpj):

 The problem here is the the (necessary) eager check for type-function
 overlap.  This is causing interface files to be read (ones that contain
 type instance declarations) that would not previously have been read.

 I have two ideas.

 First, many type function instances have the form
 {{{
 module X where
 import M(F)
 data T a = ...
 type instance F (T a) = ...
 }}}
 Can another instance of F overlap with this?  Yes in principle:
 {{{
 type instance F a = ...
 }}}
 But '''suppose we don't allow type variables in (all) the index positions
 of a type function'''.  After all, such a type instance would make the
 family degenerate to a synonym, and you could never declare any other
 instances!

 With that restriction we know that you can only overlap the type instance
 if you import (transitively) M, so you have access to T. So for instances
 of this form we don't need to treat M as an orphan module.

 I think this is a wildly common case, and in particular hits the examples
 in the Prelude.

 Second idea: export a bit more info about the family instance modules,
 namely which type functions they have instances for.  No need to check for
 overlap between `M.hi` which defines instancs for F and `N.hi` which
 defines instances for G.

-- 
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] #5227: Large space usage when deriving Generic

2011-06-09 Thread GHC
#5227: Large space usage when deriving Generic
-+--
Reporter:  igloo |Owner:  dreixel 
Type:  bug   |   Status:  new 
Priority:  high  |Milestone:  7.2.1   
   Component:  Compiler  |  Version:  7.1 
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by dreixel):

  * owner:  jpm@… => dreixel


Comment:

 Ok, I'll see what happens when we only go up to 7-tuples and report here.

 Fortunately users can always use standalone deriving for bigger tuples if
 necessary.

-- 
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] #5227: Large space usage when deriving Generic

2011-06-09 Thread GHC
#5227: Large space usage when deriving Generic
-+--
Reporter:  igloo |Owner:  jpm@…   
Type:  bug   |   Status:  new 
Priority:  high  |Milestone:  7.2.1   
   Component:  Compiler  |  Version:  7.1 
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--

Comment(by simonpj):

 * We only derive Eq, Ord etc for tuples up to 15-tuples (see `GHC.Base`)
 and Data for tuples up to 7-tuples.  I think it would be reasonable to
 derive `Generic` only up to 7-tuples.  Could you try that?

  * I'm guessing (but I have not checked) that a big reason for the blow-up
 is the repetition of type arguments; see http://research.microsoft.com/en-
 us/um/people/simonpj/papers/variant-f/if.pdf, page 5.  Indeed Section 2.3
 explicitly mentions the derivable-type-classes stuff as provoking the bad
 behaviour.

  * The paper mentions a quadratic blow-up, but I think it's actually only
 N*logN if the tuples are balanced.  But the constant factor seems large:
 see the example below.

  * At the moment every derived instance is totally independent of every
 other one.  But there must be a lot of repetition.  Could we generate more
 compact code by hand-writing the derived tuple instances?

 For this innocent triple:
 {{{
 data T = MkT Int Int Int deriving( Generic )
 }}}
 we get the following "from" function (omitting all type info):
 {{{
 ghc -c -XDeriveGeneric Foo.hs -ddump-simpl -dsuppress-all
 ...
 $cfrom_rjE =
   \ (@ x_af9) (ds_dj5 :: T) ->
 case ds_dj5 of _ { MkT g1_af0 g2_af1 g3_af2 ->
 (:*:
(g1_af0 `cast` ...) (:*: (g2_af1 `cast` ...) (g3_af2 `cast` ...)))
 `cast` ...
 }
 }}}
 Seems reasonable.  But show the type info and it looks like this:
 {{{
 $cfrom_rjE :: forall x_af8. Foo.T -> GHC.Generics.Rep Foo.T x_af8
 [GblId, Arity=1, Caf=NoCafRefs]
 $cfrom_rjE =
   \ (@ x_af9) (ds_dj5 :: Foo.T) ->
 case ds_dj5 of _ { Foo.MkT g1_af0 g2_af1 g3_af2 ->
 (GHC.Generics.:*:
@ (GHC.Generics.M1
 GHC.Generics.S
 GHC.Generics.NoSelector
 (GHC.Generics.K1 GHC.Generics.R GHC.Types.Int))
@ (GHC.Generics.M1
 GHC.Generics.S
 GHC.Generics.NoSelector
 (GHC.Generics.K1 GHC.Generics.R GHC.Types.Int)
   GHC.Generics.:*: GHC.Generics.M1
  GHC.Generics.S
  GHC.Generics.NoSelector
  (GHC.Generics.K1 GHC.Generics.R
 GHC.Types.Int))
@ x_af9
(g1_af0
 `cast` (Sym
   (GHC.Generics.NTCo:K1
) ; Sym
 (GHC.Generics.NTCo:M1
 
 
 ) 
 :: GHC.Types.Int
  ~
GHC.Generics.M1
  GHC.Generics.S
  GHC.Generics.NoSelector
  (GHC.Generics.K1 GHC.Generics.R GHC.Types.Int)
  x_af9))
(GHC.Generics.:*:
   @ (GHC.Generics.M1
GHC.Generics.S
GHC.Generics.NoSelector
(GHC.Generics.K1 GHC.Generics.R GHC.Types.Int))
   @ (GHC.Generics.M1
GHC.Generics.S
GHC.Generics.NoSelector
(GHC.Generics.K1 GHC.Generics.R GHC.Types.Int))
   @ x_af9
   (g2_af1
`cast` (Sym
  (GHC.Generics.NTCo:K1
   ) ; Sym
 (GHC.Generics.NTCo:M1
 
 
 ) 
:: GHC.Types.Int
 ~
   GHC.Generics.M1
 GHC.Generics.S
 GHC.Generics.NoSelector
 (GHC.Generics.K1 GHC.Generics.R GHC.Types.Int)
 x_af9))
   (g3_af2
`cast` (Sym
  (GHC.Generics.NTCo:K1
   ) ; Sym
 (GHC.Generics.NTCo:M1
 
 
 ) 
:: GHC.Types.Int
 ~
   GHC.Generics.M1
 GHC.Generics.S
 GHC.Generics.NoSelector
 (GHC.Generics.K1 GHC.Generics.R GHC.Types.Int)
 x_af9
 `cast` (Sym
   (GHC.Generics.NTCo:M1
  
  
  ) ; (Sym
 (GHC.Generics.NTCo:M1
 
 
 ) ; Sym
 (Foo.TFCo:Rep_T)) 
 :: (GHC.Generics.:*:)
  (GHC.Generics.M1
 GHC.Generics.S
 GHC.Generics.NoSelector
 (GHC.Generics.K1 GHC.Generics.R GHC.Types.Int))