Re: [GHC] #4241: Optimization causes HUnit to behave incorrectly

2010-10-07 Thread GHC
#4241: Optimization causes HUnit to behave incorrectly
--+-
  Reporter:  beej175560   |  Owner: 
  Type:  bug  | Status:  closed 
  Priority:  high |  Milestone:  7.0.1  
 Component:  Compiler |Version:  6.12.1 
Resolution:  fixed|   Keywords: 
  Testcase:   |  Blockedby:  3983   
Difficulty:   | Os:  MacOS X
  Blocking:   |   Architecture:  x86
   Failure:  Incorrect result at runtime  |  
--+-
Changes (by beej175560):

  * status:  infoneeded = closed
  * resolution:  = fixed


Comment:

 I confirm this is fixed in 6.12.3.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4241#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] #4241: Optimization causes HUnit to behave incorrectly

2010-10-07 Thread GHC
#4241: Optimization causes HUnit to behave incorrectly
--+-
  Reporter:  beej175560   |  Owner: 
  Type:  bug  | Status:  closed 
  Priority:  high |  Milestone:  7.0.1  
 Component:  Compiler |Version:  6.12.1 
Resolution:  fixed|   Keywords: 
  Testcase:   |  Blockedby:  3983   
Difficulty:   | Os:  MacOS X
  Blocking:   |   Architecture:  x86
   Failure:  Incorrect result at runtime  |  
--+-

Comment(by simonpj):

 Thanks for the original report, and for testing the fix.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4241#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] #4373: Lexer does not handle unicode numeric subscripts

2010-10-07 Thread GHC
#4373: Lexer does not handle unicode numeric subscripts
-+--
Reporter:  liamoc|Owner:   
Type:  bug   |   Status:  new  
Priority:  normal|Milestone:   
   Component:  Compiler (Parser) |  Version:   
Keywords:  lexer, unicode, tiny  | Testcase:   
   Blockedby:|   Difficulty:   
  Os:  Unknown/Multiple  | Blocking:   
Architecture:  Unknown/Multiple  |  Failure:  GHC rejects valid program
-+--

Comment(by simonmar):

 The change you suggest sounds reasonable.  You want to make these legal
 characters in an identifier, but not legal in a numeric constant, which is
 exactly what happens if you categorise them as digit.  Numeric constants
 are already restricted to only contain decimal digits.  Could you make a
 patch and attach it to this ticket?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4373#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] #4373: Lexer does not handle unicode numeric subscripts

2010-10-07 Thread GHC
#4373: Lexer does not handle unicode numeric subscripts
-+--
Reporter:  liamoc|Owner:  
Type:  feature request   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler (Parser) |  Version:  
Keywords:  lexer, unicode, tiny  | Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by simonmar):

  * failure:  GHC rejects valid program = None/Unknown
  * type:  bug = feature request


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4373#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


[GHC] #4376: Unexpected failures in testsuite due to .ghci

2010-10-07 Thread GHC
#4376: Unexpected failures in testsuite due to .ghci
--+-
Reporter:  daniel.is.fischer  |   Owner:  
Type:  bug|  Status:  new 
Priority:  normal |   Component:  Test Suite  
 Version:  7.1|Keywords:  
Testcase: |   Blockedby:  
  Os:  Unknown/Multiple   |Blocking:  
Architecture:  Unknown/Multiple   | Failure:  None/Unknown
--+-
 Running the testsuite, I get e.g.
 {{{
 = 3171(normal) 375 of 2596 [0, 1, 0]
 cd ./ghci/should_run  $MAKE -s --no-print-directory 3171/dev/null
 3171.run.stdout 23171.run.stderr
 = bug1465(normal) 376 of 2596 [0, 1, 0]
 cd ./typecheck/bug1465  $MAKE -s --no-print-directory bug1465
 /dev/null bug1465.run.stdout 2bug1465.run.stderr
 Actual stdout output differs from expected:
 --- ./ghci/should_run/3171.stdout.normalised2010-10-07
 13:20:16.0 +0200
 +++ ./ghci/should_run/3171.run.stdout.normalised2010-10-07
 13:20:16.0 +0200
 @@ -1 +1,3 @@
 +ghci: warnings (except type defaulting and unused do-binds) on; MR off.
 +(0.05 secs, 2799172 bytes)
  Interrupted.
 *** unexpected failure for 3171(normal)
 }}}
 since it reads ~/.ghci.

 I think -ignore-dot-ghci should be passed in the testsuite to avoid such
 gratuitous unexpected failures.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4376
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] #4376: Unexpected failures in testsuite due to .ghci

2010-10-07 Thread GHC
#4376: Unexpected failures in testsuite due to .ghci
--+-
Reporter:  daniel.is.fischer  |   Owner:  
Type:  bug|  Status:  new 
Priority:  normal |   Component:  Test Suite  
 Version:  7.1|Keywords:  
Testcase: |   Blockedby:  
  Os:  Unknown/Multiple   |Blocking:  
Architecture:  Unknown/Multiple   | Failure:  None/Unknown
--+-

Comment(by daniel.is.fischer):

 Hmm, actually, in testsuite/driver/testlib.py, it seems to be passed in
 {{{
 def ghci_script( name, way, script ):
 ...
cmd = HC=' + config.compiler + '  + \
   HC_OPTS=' + join(flags,' ') + '  + \
   ' + config.compiler + ' + \
   ' --interactive -v0 -ignore-dot-ghci ' + \
   join(flags,' ')
 }}}
 Nevertheless, apparently .ghci is not ignored.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4376#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] #3756: Missing -lz option in testsuite

2010-10-07 Thread GHC
#3756: Missing -lz option in testsuite
+---
  Reporter:  daniel.is.fischer  |   Type:  bug 
Status:  new|   Priority:  low 
 Milestone:  7.0.1  |  Component:  Build System
   Version:  6.12.1 |   Keywords:  
  Testcase: |  Blockedby:  
Difficulty: | Os:  Linux   
  Blocking: |   Architecture:  x86 
   Failure:  Other  |  
+---

Comment(by daniel.is.fischer):

 Still four unexpected failures while running validate in a HEAD repo
 today.[[BR]]
 Failing tests:
 {{{
 3231(threaded1)
 ffi014(threaded1)
 numsparks001(threaded1)
 testwsdeque(threaded1)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3756#comment:19
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] #4345: Compiler crash building regex-posix version 0.94.1 using ghc 7.0.1-rc1

2010-10-07 Thread GHC
#4345: Compiler crash building regex-posix version 0.94.1 using ghc 7.0.1-rc1
-+--
Reporter:  dsf   |Owner:  simonpj   
Type:  bug   |   Status:  new   
Priority:  highest   |Milestone:  7.0.1 
   Component:  Compiler  |  Version:  7.1   
Keywords:| Testcase:
   Blockedby:|   Difficulty:
  Os:  Linux | Blocking:
Architecture:  x86   |  Failure:  Compile-time crash
-+--
Changes (by HoseinAttarzadeh):

 * cc: HoseinAttarzadeh (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4345#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] #4372: Extending quasiquotation support

2010-10-07 Thread GHC
#4372: Extending quasiquotation support
-+--
Reporter:  simonpj   |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Template Haskell  |  Version:  6.12.3  
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--

Comment(by simonpj):

 It's also worth reminding ourselves that quasi-quote syntax is only
 shorthand for a TH splice.  Thus
 {{{
 [pads| blah |]
 }}}
 means
 {{{
 $(quoteExp pads blah)
 }}}
 So in the case proposed by Gershom you could say
 {{{
 $(quoteExp (jmt [jsModuleSig]) blah)
 }}}
 and away you go.  Is that so bad?

 At the moment you can't do TH splices in patterns or local declarations,
 whereas you can use quasi-quotes.  I have separate plans to change that
 (need time to write up), but let's assume for the sake of argument that
 patterns can be done the same way as expressions.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4372#comment:8
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] #4372: Extending quasiquotation support

2010-10-07 Thread GHC
#4372: Extending quasiquotation support
-+--
Reporter:  simonpj   |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Template Haskell  |  Version:  6.12.3  
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--

Comment(by gershomb):

 This is all shorthand, you're right. But the syntactic sugar makes a huge
 difference here. In quasiquote syntax, the only quotation issue that an
 end user has to worry about is the bar followed by close bracket. In
 standard splice syntax, the quoted expression is forced to respect all the
 rules of haskell. Multiline strings either use the \ syntax are have to be
 written with explicit appends. Double quotes need additional escaping,
 etc. Furthermore, error messages can't give nearly as nice locality.

 With quasiquotes, its possible to write very fluently in an embedded dsl
 with almost arbitrary concrete syntax. Template Haskell splices on their
 own make doing so very painful.

 Most of the libraries using quasiquotation that I now know of would be
 extremely painful to use without the shorthand syntax provided by
 quasiquotation.

 In general, Kathleen's preference is fine -- super lightweight syntax for
 the simple case, and extended syntax for the extended case. This causes a
 bit more work at the lexing level, and in the parser (but only a few
 lines), but subsequent to that there's a single code path which is as
 simple as or simpler than what exists now.

 In fact, '[$' for introducing an extended quoter and '|' alone for
 introducing the quotee, which is what I've now implemented, seems fine to
 me as well, unless there is strong sentiment otherwise.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4372#comment:9
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] #4372: Extending quasiquotation support

2010-10-07 Thread GHC
#4372: Extending quasiquotation support
-+--
Reporter:  simonpj   |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Template Haskell  |  Version:  6.12.3  
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by snoyberg):

 * cc: mich...@… (added)


Comment:

 Just to add another use case: Hamlet uses quasi-quotation for HTML
 templates. There are currently two parameters to the hamletWithSettings
 function: whether to close tags like HTML or XHTML (eg, br vs br/) and
 the doctype. Hamlet itself defines two quasi-quoters built on
 hamletWithSettings: hamlet and xhamlet.

 But it's easily imaginable that someone will want to create some other
 combination (such as HTML 3.2) that is not currently provided. Currently,
 they would need to define their new quasi-quoter in a separate module;
 this proposal would appear to make that process a little bit nicer.

 In fact, if I understand the proposal properly, I had originally assumed
 this ''is'' how quasi-quoters worked and was surprised when the compiler
 disagreed with me ;).

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4372#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


[GHC] #4377: sizedText function for Text.PrettyPrint

2010-10-07 Thread GHC
#4377: sizedText function for Text.PrettyPrint
-+--
Reporter:  lerkok|   Owner: 
   
Type:  feature request   |  Status:  new
   
Priority:  normal|   Component:  libraries/pretty   
   
 Version:|Keywords:  text, sizedText, pretty 
printing, Text.PrettyPrint
Testcase:|   Blockedby: 
   
  Os:  Unknown/Multiple  |Blocking: 
   
Architecture:  Unknown/Multiple  | Failure:  None/Unknown   
   
-+--
 The `Text.PrettyPrint` library has a `text` function for converting
 ordinary strings to documents. This function takes the length of the
 string to be its final size. However, there are use cases where the actual
 length of this string and the virtual length of the document it
 represents are not necessarily the same. This use case comes up in cases
 where the resulting Doc is rendered to String and a further processor
 works on that particular string with its own built-in assumptions about
 how things should be laid out. (In our case, we produce Isabelle/HOL code
 from Cryptol, which gets rendered by the Isabelle theorem prover. These
 strings are the tags that correspond to Isabelle's own escape sequences
 for certain theory specific logical symbols.)

 To remedy this, adding a function sizedText to the library would
 suffice:

 {{{
 sizedText :: Int - String - Doc
 sizedText l s = TextBeside (Str s') l Empty
where s' = s ++ take (l - length s) (repeat ' ')
 }}}

 Unfortunately this function can '''not''' be defined outside the
 `PrettyPrint` library itself, This is because the `TextBeside` constructor
 is not exported, and there seems to be no other way of accessing the
 length field otherwise.

 Note that in the above code the user given length `l` can be larger or
 smaller than the actual length of the string `s`; so the first argument to
 `take` can be positive or negative. In either case the function does the
 right thing for our use case: If smaller, you get the original string;
 which messes up the ASCII output a bit but is the right thing to the for
 the target processor; if larger, then it gets padded with space at the end
 appropriately to get the ASCII looking right as well.

 Our current workaround for this issue is to replicate the library code
 ourselves and add this function on top, which is a kludge at best that
 we'd like to avoid.

 The function `sizedText` satisfies the law:

 {{{
 sizedText (length s) s = text s
 }}}

 and hence agrees  with the existing `text` function for ordinary usage.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4377
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] #4370: Bring back monad comprehensions

2010-10-07 Thread GHC
#4370: Bring back monad comprehensions
-+--
Reporter:  simonpj   |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  6.12.3  
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by nsch):

 * cc: m...@… (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4370#comment:7
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] #2041: Allow splicing in concrete syntax

2010-10-07 Thread GHC
#2041: Allow splicing in concrete syntax
-+--
Reporter:  igloo |Owner:  
Type:  feature request   |   Status:  new 
Priority:  normal|Milestone:  _|_ 
   Component:  Template Haskell  |  Version:  6.8.2   
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  Unknown 
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by reinerp):

 * cc: reiner.p...@… (added)
  * failure:  = None/Unknown


Comment:

 Another use for this would be for creating custom quasiquoters with
 antiquoting. Say, to create a custom list quasiquoter:

 {{{
 [list| x^2+y, 3*z |]
 }}}

 the quasiquoter needs to parse antiquoted expressions such as {{{x^2+y}}}
 and {{{3*z}}} into TH abstract syntax. Current quasiquoters mostly do this
 using haskell-src-exts (via the haskell-src-meta library), but it would be
 neater just to return a {{{RawE antiquoted_stuff}}} expression.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2041#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] #4316: Interactive do notation in GHCi

2010-10-07 Thread GHC
#4316: Interactive do notation in GHCi
-+--
Reporter:  mitar |Owner:  vivian  
Type:  feature request   |   Status:  new 
Priority:  normal|Milestone:  7.2.1   
   Component:  GHCi  |  Version:  6.12.3  
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by vivian):

  * owner:  = vivian


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4316#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