Re: [GHC] #709: Fixup too large error with -fasm on PowerPC

2012-12-06 Thread GHC
#709: Fixup too large error with -fasm on PowerPC
--+-
  Reporter:  simonmar |  Owner:
  Type:  bug  | Status:  patch 
  Priority:  low  |  Milestone:  6.8.1 
 Component:  Compiler (NCG)   |Version:  7.7   
Resolution:   |   Keywords:
Os:  Unknown/Multiple |   Architecture:  powerpc   
   Failure:  Building GHC failed  | Difficulty:  Moderate (less than a day)
  Testcase:   |  Blockedby:
  Blocking:   |Related:
--+-

Comment(by simonmar):

 Replying to [comment:10 PHO]:
  Replying to [comment:9 simonmar]:

   Could we not use something better than a hardcoded 5 for the info
 table size?  We know the size of the info table for a continuation:
 `sizeof(StgRetInfoTable)`, and add to that the maximum offset due to
 alignment.
 
  The size of `StgRetInfoTable` varies depending on the way (e.g. -prof)
 so we can't simply grab it from the C compiler. I think it's easy to
  calculate the size of each tables represented as `CmmStatics`.

 It also varies based on `tablesNextToCode` and other things, but you only
 need the upper bound here.  I would add an `stgRetInfoTableMaxWords ::
 Int` somewhere, maybe `CmmInfo`.

   You could also do better than `length blocks`: the actual number of
 info tables is available.
 
  Right, but since info tables are scattered around a proc, I couldn't
 simply replace {{{length blocks}}} with the actual number of tables.

 I don't really understand that.  But I don't mind if you want to use
 `length blocks`, it's just a bit pessimistic.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/709#comment:11
GHC http://www.haskell.org/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] #7483: Broken Read instance for Data.Fixed (no parse in legitimate cases).

2012-12-06 Thread GHC
#7483: Broken Read instance for Data.Fixed (no parse in legitimate cases).
+---
Reporter:  navaati  |  Owner:  
Type:  bug  | Status:  new 
Priority:  normal   |  Component:  libraries/base  
 Version:  7.6.1|   Keywords:  
  Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
 Failure:  Incorrect result at runtime  |  Blockedby:  
Blocking:   |Related:  #4502   
+---
 {{{read Just 12.30 :: Maybe Centi}}} throws *** Exception:
 Prelude.read: no parse, as do {{{read  12.30 :: Centi}}}.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7483
GHC http://www.haskell.org/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] #7484: Template Haskell allows building invalid record fields/names

2012-12-06 Thread GHC
#7484: Template Haskell allows building invalid record fields/names
-+--
Reporter:  iustin|  Owner:  
Type:  bug   | Status:  new 
Priority:  normal|  Component:  Template Haskell
 Version:  7.6.1 |   Keywords:  
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
 Failure:  None/Unknown  |  Blockedby:  
Blocking:|Related:  
-+--
 This is not really a bug, more like a unintuitive behaviour.

 Due to a bug in my definitions, I was passing a name like `opTestDelay `
 (note extra space) to a TH splice builder, which ended up with:

 {{{
 data OpCode
   = OpTestDelay {opDelayDuration  :: Double,
  opDelayOnMaster :: Bool,
  opDelayOnNodes :: [Ganeti.Types.NonEmptyString],
  opDelayRepeat :: Ganeti.Types.NonNegative Int}
 }}}

 Note the double space around the first record field. This results in the
 actual accessor functions having the space in the name, which makes them
 unusable from normal code.

 This seems to be allowed as well in other TH constructs:

 {{{
 λ runQ $ return (ValD (VarP (mkName a ) ) (NormalB (LitE (IntegerL 5)))
 [])
 ValD (VarP a ) (NormalB (LitE (IntegerL 5))) []
 }}}

 I think that names should not be allowed to contain invalid identifiers
 (that would make them non-usable in normal Haskell code), but I'm not sure
 - maybe TH is designed to allow you to shoot yourself in the foot indeed.
 Anyway, opening this bug just in case.

 Tested and behaves the same both on 6.12 and 7.6.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7484
GHC http://www.haskell.org/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] #7484: Template Haskell allows building invalid record fields/names

2012-12-06 Thread GHC
#7484: Template Haskell allows building invalid record fields/names
-+--
Reporter:  iustin|   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Template Haskell  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonpj):

  * difficulty:  = Unknown


Comment:

 Yes I see that.  What would you like? Should `mkName` fail (by calling
 `error`) when given an illegal name?

 I wonder if some people might use an illegal name specificaly to ''avoid''
 the danger of accidental capture?  (Though you can always use `newName`
 for that.)

 Perhaps it would suffice to reject spaces in names, becuase that is
 perhaps particularly confusing.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7484#comment:1
GHC http://www.haskell.org/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] #6040: Adding a type signature changes heap allocation into stack allocation without changing the actual type

2012-12-06 Thread GHC
#6040: Adding a type signature changes heap allocation into stack allocation
without changing the actual type
-+--
Reporter:  tibbe |   Owner:  simonpj 
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.4.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by simonpj):

 Right.  This is an example of my first comment. If we do a final lambda-
 floating phase at the end the two would become identical. Thanks for
 confirming.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6040#comment:5
GHC http://www.haskell.org/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] #7484: Template Haskell allows building invalid record fields/names

2012-12-06 Thread GHC
#7484: Template Haskell allows building invalid record fields/names
-+--
Reporter:  iustin|   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Template Haskell  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by iustin):

 Replying to [comment:1 simonpj]:
  Yes I see that.  What would you like? Should `mkName` fail (by calling
 `error`) when given an illegal name?

 Yes, I think that makes sense (and is appropriate).

  I wonder if some people might use an illegal name specificaly to
 ''avoid'' the danger of accidental capture?  (Though you can always use
 `newName` for that.)

 That would be a very ugly way of solving the problem. Since `newName`
 exists and works well, I don't see a problem against moving to that (if
 anyone relies on such behaviour).

  Perhaps it would suffice to reject spaces in names, becuase that is
 perhaps particularly confusing.

 Indeed. I don't know how difficult is to decide whether a name is
 correct versus simply checking for spaces; ideally names should be well-
 formed, but if spaces are much easier to detect, doing just space-checks
 is already an improvement.

 Thanks!
 Iustin

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7484#comment:2
GHC http://www.haskell.org/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] #7482: GHC.Event overwrites main IO managers hooks to RTS

2012-12-06 Thread GHC
#7482: GHC.Event overwrites main IO managers hooks to RTS
-+--
Reporter:  AndreasVoellmy|   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  libraries/base| Version:  7.4.1   
Keywords:  IO Manager, RTS   |  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by AndreasVoellmy):

 Here is a proposal to fix this problem: remove 'new' from GHC.Event public
 interface. Then users can only use the built-in IO manager, and therefore
 the problem above will not arise. No projects on hackage use
 GHC.Event.new.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7482#comment:4
GHC http://www.haskell.org/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] #7445: template-haskell : need a good error message instead of just an unexplained panic

2012-12-06 Thread GHC
#7445: template-haskell : need a good error message instead of just an 
unexplained
panic
---+
Reporter:  erikd   |  Owner:  
Type:  bug | Status:  new 
Priority:  normal  |  Component:  Template Haskell
 Version:  7.7 |   Keywords:  
  Os:  Unknown/Multiple|   Architecture:  Unknown/Multiple
 Failure:  Compile-time crash  |  Blockedby:  
Blocking:  |Related:  
---+

Comment(by simonpj@…):

 commit 9a20e540754fc2af74c2e7392f2786a81d8d5f11
 {{{
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Thu Dec 6 16:03:16 2012 +

 Stop attempting to trim data types in interface files

 Without -O, we previously tried to make interface files smaller
 by not including the data constructors of data types.  But
 there are a lot of exceptions, notably when Template Haskell is
 involved or, more recently, DataKinds.

 However Trac #7445 shows that even without TemplateHaskell, using
 the Data class and invoking Language.Haskell.TH.Quote.dataToExpQ
 is enough to require us to expose the data constructors.

 So I've given up on this optimisation -- it's probably not
 important anyway.  Now I'm simply not attempting to trim off
 the data constructors.  The gain in simplicity is worth the
 modest cost in interface file growth, which is limited to the
 bits reqd to describe those data constructors.

  compiler/main/TidyPgm.lhs |  207
 -
  1 files changed, 109 insertions(+), 98 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7445#comment:6
GHC http://www.haskell.org/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] #2725: Remove Hack in compiler/nativeGen/MachCodeGen.hs

2012-12-06 Thread GHC
#2725: Remove Hack in compiler/nativeGen/MachCodeGen.hs
-+--
Reporter:  clemens   |   Owner:  clemens 
Type:  bug   |  Status:  new 
Priority:  high  |   Milestone:  7.8.1   
   Component:  Compiler (NCG)| Version:  6.11
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by igloo):

  * priority:  lowest = high
  * milestone:  7.6.2 = 7.8.1


Comment:

 This was opened 4 years ago; let's see if we can remove the hack and close
 it now.

 nb, it's now in `nativeGen/X86/CodeGen.hs`.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2725#comment:10
GHC http://www.haskell.org/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] #7143: ghc-7.6.0.20120810-x86_64-windows.exe - ghc can't figure out LLVM version

2012-12-06 Thread GHC
#7143: ghc-7.6.0.20120810-x86_64-windows.exe - ghc can't figure out LLVM 
version
-+--
Reporter:  cetinsert |   Owner:  dterei 
  
Type:  bug   |  Status:  new
  
Priority:  high  |   Milestone:  7.8.1  
  
   Component:  Compiler (LLVM)   | Version:  7.6.1-rc1  
  
Keywords:  llvm  |  Os:  Windows
  
Architecture:  Unknown/Multiple  | Failure:  Incorrect warning at 
compile-time
  Difficulty:  Unknown   |Testcase: 
  
   Blockedby:|Blocking: 
  
 Related:|  
-+--
Changes (by igloo):

  * component:  Compiler = Compiler (LLVM)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7143#comment:5
GHC http://www.haskell.org/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] #5140: Fix LLVM backend for PowerPC

2012-12-06 Thread GHC
#5140: Fix LLVM backend for PowerPC
+---
Reporter:  erikd|   Owner:  erikd   
Type:  task |  Status:  new 
Priority:  low  |   Milestone:  7.6.2   
   Component:  Compiler (LLVM)  | Version:  7.1 
Keywords:   |  Os:  Linux   
Architecture:  powerpc  | Failure:  None/Unknown
  Difficulty:  Unknown  |Testcase:  
   Blockedby:   |Blocking:  
 Related:   |  
+---
Changes (by igloo):

  * difficulty:  = Unknown
  * component:  Compiler = Compiler (LLVM)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5140#comment:6
GHC http://www.haskell.org/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] #4245: ghci panic: thread blocked indefinitely in an MVar operation

2012-12-06 Thread GHC
#4245: ghci panic: thread blocked indefinitely in an MVar operation
---+
Reporter:  pturnbull   |   Owner:  tibbe 
Type:  bug |  Status:  new   
Priority:  high|   Milestone:  7.6.2 
   Component:  GHCi| Version:  6.12.3
Keywords:  MVar|  Os:  MacOS X   
Architecture:  x86_64 (amd64)  | Failure:  GHCi crash
  Difficulty:  Unknown |Testcase:
   Blockedby:  |Blocking:
 Related:  |  
---+
Changes (by tibbe):

  * owner:  igloo = tibbe


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4245#comment:28
GHC http://www.haskell.org/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] #7133: GHCi: strange behaviour after CTRL-C, followed by 'hPutChar: resource vanished (Broken Pipe)' when quitting

2012-12-06 Thread GHC
#7133: GHCi: strange behaviour after CTRL-C, followed by 'hPutChar: resource
vanished (Broken Pipe)' when quitting
-+--
Reporter:  DuncanMortimer|   Owner:  tibbe  
Type:  bug   |  Status:  new
Priority:  normal|   Milestone:  7.8.1  
   Component:  GHCi  | Version:  7.4.1  
Keywords:|  Os:  MacOS X
Architecture:  Unknown/Multiple  | Failure:  Other  
  Difficulty:  Unknown   |Testcase: 
   Blockedby:|Blocking: 
 Related:|  
-+--
Changes (by tibbe):

  * owner:  igloo = tibbe


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7133#comment:2
GHC http://www.haskell.org/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] #709: Fixup too large error with -fasm on PowerPC

2012-12-06 Thread GHC
#709: Fixup too large error with -fasm on PowerPC
--+-
  Reporter:  simonmar |  Owner:
  Type:  bug  | Status:  patch 
  Priority:  low  |  Milestone:  6.8.1 
 Component:  Compiler (NCG)   |Version:  7.7   
Resolution:   |   Keywords:
Os:  Unknown/Multiple |   Architecture:  powerpc   
   Failure:  Building GHC failed  | Difficulty:  Moderate (less than a day)
  Testcase:   |  Blockedby:
  Blocking:   |Related:
--+-

Comment(by PHO):

 Replying to [comment:11 simonmar]:
  It also varies based on `tablesNextToCode` and other things, but you
 only need the upper bound here.  I would add an `stgRetInfoTableMaxWords
 :: Int` somewhere, maybe `CmmInfo`.

 That would be handy though I have no idea how to generate such a constant.
 Do you intend to hardcode it?

You could also do better than length blocks: the actual number of
 info tables is available.
   Right, but since info tables are scattered around a proc, I couldn't
 simply replace {{{length blocks}}} with the actual number of tables.
 
  I don't really understand that.  But I don't mind if you want to use
 `length blocks`, it's just a bit pessimistic.

 I found it was my misunderstanding while I was trying to explain why it
 was wrong to calculate `nearLimit` by the number of tables. Sorry, you
 were right.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/709#comment:12
GHC http://www.haskell.org/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] #5682: Properly parse kind operators (from promoted type operators)

2012-12-06 Thread GHC
#5682: Properly parse kind operators (from promoted type operators)
-+--
Reporter:  lunaris   |   Owner:  dreixel  
Type:  bug   |  Status:  new  
Priority:  low   |   Milestone:  7.6.2
   Component:  Compiler  | Version:  7.3  
Keywords:  PolyKinds, ghc-kinds  |  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple  | Failure:  GHC rejects valid program
  Difficulty:  Unknown   |Testcase:   
   Blockedby:|Blocking:   
 Related:|  
-+--
Changes (by goldfire):

 * cc: eir@… (added)


Comment:

 I agree with dreixel's examples in spirit, but generally {{{'}}} is not
 applied to kinds.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5682#comment:5
GHC http://www.haskell.org/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] #7485: Tuple constraints not properly kinded

2012-12-06 Thread GHC
#7485: Tuple constraints not properly kinded
-+--
Reporter:  goldfire  |  Owner:  
Type:  bug   | Status:  new 
Priority:  normal|  Component:  Compiler
 Version:  7.7   |   Keywords:  ConstraintKinds 
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
 Failure:  None/Unknown  |  Blockedby:  
Blocking:|Related:  
-+--
 Consider this:

 {{{
 {-# LANGUAGE DataKinds, ConstraintKinds, KindSignatures #-}

 import GHC.Exts ( Constraint )

 type UnitType = (() :: *)
 type UnitConstraint = (() :: Constraint)

 type PairType = ((,) :: * - * - *)
 }}}

 So far, so good. But, adding the following causes an error:

 {{{
 type PairConstraint = ((,) :: Constraint - Constraint - Constraint)
 }}}

 The error is

 {{{
 The signature specified kind `Constraint
   - Constraint - Constraint',
   but `(,)' has kind `* - * - *'
 }}}

 In general, you can't use the prefix form of {{{(,)}}} in a constraint, to
 my surprise. It's not entirely clear what is the correct behavior here,
 but this all seems a little fishy as currently implemented.

 This was all tested on 7.7.20121130.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7485
GHC http://www.haskell.org/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] #7486: dblatex can't build docs; fix included.

2012-12-06 Thread GHC
#7486: dblatex can't build docs; fix included.
+---
Reporter:  rlpowell |  Owner:  
Type:  bug  | Status:  new 
Priority:  normal   |  Component:  Build System
 Version:  7.6.1|   Keywords:  
  Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
 Failure:  Building GHC failed  |  Blockedby:  
Blocking:   |Related:  
+---
 Currently, on my Fedora 17 system, the following occurs when you try to
 build the docs:


 {{{
 pdflatex failed
 users_guide.tex:1030: Undefined control sequence \Documents.
 users_guide.tex:1030: leading text: }
 users_guide.tex:1030: Undefined control sequence \user.
 users_guide.tex:1030: leading text: }
 users_guide.tex:3719: Undefined control sequence \Person.
 users_guide.tex:3719: leading text:   or \nolinkurl{Data\Person.hs}
 users_guide.tex:6016: Undefined control sequence \Documents.
 users_guide.tex:6016: leading text:
 ...ts~And~Settings\user\ghc\package.conf.d}
 users_guide.tex:6016: Undefined control sequence \user.
 users_guide.tex:6016: leading text:
 ...ts~And~Settings\user\ghc\package.conf.d}
 users_guide.tex:6016: Undefined control sequence \ghc.
 users_guide.tex:6016: leading text:
 ...ts~And~Settings\user\ghc\package.conf.d}
 users_guide.tex:6016: Undefined control sequence \package.
 users_guide.tex:6016: leading text:
 ...ts~And~Settings\user\ghc\package.conf.d}
 users_guide.tex:29016: Undefined control sequence \cygwin.
 users_guide.tex:29016: leading text: \nolinkurl{/} is
 \nolinkurl{C:\cygwin\ }
 users_guide.tex:29022: Undefined control sequence \cygwin.
 users_guide.tex:29022: leading text: system (probably
 \nolinkurl{C:\cygwin\bin}
 users_guide.tex:29022: Undefined control sequence \bin.
 users_guide.tex:29022: leading text: system (probably
 \nolinkurl{C:\cygwin\bin}
 users_guide.tex:29022: Undefined control sequence \cygwin.
 users_guide.tex:29022: leading text: ...} and
 \nolinkurl{C:\cygwin\usr\include}
 users_guide.tex:29022: Undefined control sequence \usr.
 users_guide.tex:29022: leading text: ...} and
 \nolinkurl{C:\cygwin\usr\include}
 users_guide.tex:29022: Incomplete \iffalse; all text was ignored after
 line 29022.
 users_guide.tex: Emergency stop.
 Unexpected error occured
 }}}

 This is easily fixed like so:

 DBLATEX_OPTS=-P 'filename.as.url=0' make

 makes it work.

 see http://dblatex.sourceforge.net/doc/manual/sec-param-value.html and
 http://dblatex.sourceforge.net/doc/manual/filename.as.url.html for an
 explanation; if you leave it as url style, dblatex leaves \ , as in
 C:\Documents And Settings, in there literally, and I didn't want to hack
 dblatex, and this fixes the problem.

 No idea where to put this in the makefiles or whatever to solve it for
 real, sorry.

 It may be the case, probably *is* the case in fact, that a newer dblatex
 fixes this, but I doubt very much that y'all rely on this feature anyways,
 and not building on the latest Fedora is kind of unfortunate.

 -Robin

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7486
GHC http://www.haskell.org/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] #7162: RULES that never fire (automatically)

2012-12-06 Thread GHC
#7162: RULES that never fire (automatically)
---+
  Reporter:  andygill  |  Owner:  
  Type:  feature request   | Status:  patch   
  Priority:  normal|  Milestone:  7.8.1   
 Component:  Compiler  |Version:  7.7 
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+
Changes (by afarmer):

  * status:  new = patch


Comment:

 Here are two patches that implement option 1. This includes a note in the
 user's guide about [~] on RULES.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7162#comment:12
GHC http://www.haskell.org/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] #7487: Deriving Generic1 for a type containing Either

2012-12-06 Thread GHC
#7487: Deriving Generic1 for a type containing Either
-+--
Reporter:  spl   |  Owner:  dreixel 
Type:  bug   | Status:  new 
Priority:  normal|  Component:  Compiler
 Version:  7.6.1 |   Keywords:  
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
 Failure:  None/Unknown  |  Blockedby:  
Blocking:|Related:  
-+--
 With the following code:

 {{{
 {-# LANGUAGE DeriveGeneric #-}
 import GHC.Generics
 data T a = C (Either Int a) deriving Generic1
 }}}

 I get the error message:

 {{{
 Main.hs:3:38:
 Can't make a derived instance of `Generic1 T':
   must not apply type constructors that cannot be represented with
 `Rep1'
   (such as `Either') to arguments that involve the last type parameter
 In the data declaration for `T'
 }}}

 But when I look at the instances of `Generic1`, I see the following
 (summarized):

 {{{
 *Main :i Generic1
 ...
 instance Generic1 (Either a) -- Defined in `GHC.Generics'
 ...
 }}}

 So, it seems that `Either a` can be represented with `Rep1`. Consequently,
 the error message is a bit confusing.

 Similarly, I can define my own version of `Either` -- e.g. `data U a b = A
 a | B b deriving Generic1` -- replace `Either` with `U` and still get the
 message. I also get this problem using `U` as `data U a b = U a b deriving
 Generic1` but not with `T` as `data T a = C (Int, a) deriving Generic1`.

 Lastly, I try this:

 {{{
 data T a = C (Either Int (T a)) deriving Generic1
 }}}

 but the error is even stranger here:

 {{{
 Main.hs:3:38:
 Can't make a derived instance of `Generic1 T':
   must not apply type constructors that cannot be represented with
 `Rep1'
   (such as `T') to arguments that involve the last type parameter
 In the data declaration for `T'
 }}}

 What's the general problem with these examples?

  * Can the error message be improved?
  * Can the deriving mechanism be extended for these types?

 I'm assuming I can write my own `Generic1` instance, though I haven't
 actually tried.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7487
GHC http://www.haskell.org/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] #7486: dblatex can't build docs; fix included.

2012-12-06 Thread GHC
#7486: dblatex can't build docs; fix included.
+---
Reporter:  rlpowell |  Owner:  
Type:  bug  | Status:  new 
Priority:  normal   |  Component:  Build System
 Version:  7.6.1|   Keywords:  
  Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
 Failure:  Building GHC failed  |  Blockedby:  
Blocking:   |Related:  
+---

Comment(by rlpowell):

 dblatex 0.3.4 (latest) does not fix this problem, so perhaps it's the
 other way around and earlier versions worked.

 -Robin

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7486#comment:1
GHC http://www.haskell.org/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] #7063: Register allocators can't handle non-uniform register sets

2012-12-06 Thread GHC
#7063: Register allocators can't handle non-uniform register sets
---+
Reporter:  simonmar|   Owner:  benl   
Type:  bug |  Status:  new
Priority:  normal  |   Milestone:  7.8.1  
   Component:  Compiler (NCG)  | Version:  7.4.2  
Keywords:  |  Os:  Unknown/Multiple   
Architecture:  x86 | Failure:  Runtime performance bug
  Difficulty:  Unknown |Testcase: 
   Blockedby:  |Blocking: 
 Related:  |  
---+
Changes (by benl):

  * owner:  = benl


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7063#comment:1
GHC http://www.haskell.org/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] #7479: ArrowChoice unit law in haddock seems to be wrong

2012-12-06 Thread GHC
#7479: ArrowChoice unit law in haddock seems to be wrong
+---
  Reporter:  pminten|  Owner:  
  Type:  bug| Status:  closed  
  Priority:  normal |  Milestone:  
 Component:  libraries/base |Version:  7.7 
Resolution:  fixed  |   Keywords:  
Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple
   Failure:  Documentation bug  | Difficulty:  Unknown 
  Testcase: |  Blockedby:  
  Blocking: |Related:  
+---
Changes (by igloo):

  * status:  merge = closed
  * difficulty:  = Unknown
  * resolution:  = fixed


Comment:

 Merged as 56c8295c638a03676a9be8d34195e6be945ddc2c.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7479#comment:2
GHC http://www.haskell.org/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] #7347: Existential data constructors should not be promoted

2012-12-06 Thread GHC
#7347: Existential data constructors should not be promoted
---+
  Reporter:  simonpj   |  Owner:  
  Type:  bug   | Status:  closed  
  Priority:  normal|  Milestone:  
 Component:  Compiler  |Version:  7.6.1   
Resolution:  fixed |   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:  polykinds/T7347   |  Blockedby:  
  Blocking:|Related:  
---+
Changes (by igloo):

  * status:  merge = closed


Comment:

 Merged as e3dc71de7307d30f6063a8447b93e54f1551a041 and
 f630eb5122b5d6c16b449451e33adda5341b6775.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7347#comment:17
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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