Re: [GHC] #3990: UNPACK doesn't unbox data families

2011-06-14 Thread GHC
#3990: UNPACK doesn't unbox data families
-+--
Reporter:  rl|Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone:  7.2.1  
   Component:  Compiler  |  Version:  7.0.3  
Keywords:| Testcase: 
   Blockedby:|   Difficulty: 
  Os:  Unknown/Multiple  | Blocking: 
Architecture:  Unknown/Multiple  |  Failure:  Runtime performance bug
-+--
Changes (by liyang):

 * cc: hackage.haskell.org@… (added)
  * version:  6.13 => 7.0.3


Comment:

 In 7.0.3, at least there's a warning:
 {{{
 Warning: Ignoring unusable UNPACK pragma on the
  first argument of `T'
 }}}

-- 
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-14 Thread GHC
#4504: "awaitSignal Nothing" does not block thread with -threaded
--+-
  Reporter:  adept|  Owner:  
  Type:  bug  | Status:  closed  
  Priority:  normal   |  Milestone:  7.0.2   
 Component:  Runtime System   |Version:  7.0.1   
Resolution:  fixed|   Keywords:  
  Testcase:   |  Blockedby:  
Difficulty:   | Os:  Unknown/Multiple
  Blocking:   |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  |  
--+-

Comment(by kazu-yamamoto):

 Ian,

 Thank you for your reply and sorry for my misunderstanding. I comfirmed
 that adding "blockSignals reservedSignals" fixes 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] #5208: Unroll array copy/clone primops in the native and LLVM code generators

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

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


Comment:

 Committed:

 6c7d2a946a96ed74799cf353f3f62c875f56639b
 790063769da85adefa9ad9194e00f69e6ca6fd5c
 01c9b2f8ece0a7f1226d0768e811666f792787bc

-- 
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] #4081: Strict constructor fields inspected in loop

2011-06-14 Thread GHC
#4081: Strict constructor fields inspected in loop
-+--
Reporter:  rl|Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone:  7.2.1  
   Component:  Compiler  |  Version:  6.13   
Keywords:| Testcase: 
   Blockedby:|   Difficulty: 
  Os:  Unknown/Multiple  | Blocking: 
Architecture:  Unknown/Multiple  |  Failure:  Runtime performance bug
-+--
Changes (by nightski):

 * cc: nightski@… (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


[GHC] #5257: Calling fail on a UTF-8 encoded string (in file) causes garbage to be printed

2011-06-14 Thread GHC
#5257: Calling fail on a UTF-8 encoded string (in file) causes garbage to be
printed
-+--
Reporter:  anthony.de.almeida.lopes  |   Owner: 

Type:  bug   |  Status:  new

Priority:  normal|   Component:  Runtime System 

 Version:  7.0.2 |Keywords: 

Testcase:|   Blockedby: 

  Os:  Linux |Blocking: 

Architecture:  x86_64 (amd64)| Failure:  Incorrect result at 
runtime
-+--
 For example,

 guerrilla@delta:/tmp/foo$ cat Test.hs
 module Main where

 main :: IO ()
 main =
 do
 putStrLn "μ"
 fail "μ"
 guerrilla@delta:/tmp/foo$ ./Test
 μ
 Test: user error (�)
 guerrilla@delta:/tmp/foo$ ./Test 2>&1 | xxd
 000: cebc 0a54 6573 743a 2075 7365 7220 6572  ...Test: user er
 010: 726f 7220 28bc 290a  ror (.).


 Using either encodeString or writing it in escaped hexidecimal does work.

-- 
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-14 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):

 I've addressed the comments that we agreed on and updated the test to be
 more comprehensive. Please review.

-- 
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] #5256: code in an "else" branch that is never executed still does influence runtime (Vectorizer?)

2011-06-14 Thread GHC
#5256: code in an "else" branch that is never executed still does influence
runtime (Vectorizer?)
---+
Reporter:  j.waldmann  |   Owner:  
Type:  bug |  Status:  new 
Priority:  normal  |   Component:  Compiler
 Version:  7.0.3   |Keywords:  
Testcase:  |   Blockedby:  
  Os:  Linux   |Blocking:  
Architecture:  x86_64 (amd64)  | Failure:  None/Unknown
---+

Comment(by daniel.is.fischer):

 The problem is that with the undefined, GHC sees that the else-branch is
 uninteresting and ignores the complicated recursion, thus effectively we
 get
 {{{
 foldb_cap cap ... = if cap <= 1 then V.foldl' ... else undefined
 }}}
 which is simple enough to be inlined, the function parameters get inlined
 too, so we get a nice explicit loop
 {{{
 $s$wfoldlM'_loop_s3Am [Occ=LoopBreaker]
   :: GHC.Prim.Int#
  -> GHC.Prim.Int#
  -> GHC.Prim.Int#
  -> (# GHC.Types.Int, GHC.Types.Int #)
 }}}
 with primops.

 In the other case, GHC passes the function arguments to the recursive
 calls and it doesn't see that it could inline them here (it's only ever
 called once from main, so it never gets passed other functions), leading
 to a loop
 {{{
 $s$wfoldlM'_loop_s3EE [Occ=LoopBreaker]
   :: GHC.Prim.Int#
  -> (GHC.Types.Int, GHC.Types.Int)
  -> (# GHC.Types.Int, GHC.Types.Int #)
 }}}
 calling the function arguments in each iteration.

 A manual static argument transformation for the two function arguments
 {{{
 foldb_cap cp strt f g xs = work cp strt xs
   where
 work cap e s = if cap <= 1 then ... else ... work ...
 }}}
 makes it clear that it never gets different function arguments, allowing
 them to be inlined (since it's not exported and only called once, they
 aren't inlined if foldb_cap is exported unless you have an INLINE pragma
 on foldb_cap) here, again giving the primop loop.

 So perhaps GHC should be keener to SAT function arguments?

-- 
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] #5255: String literals cause runtime crashes when OverloadedStrings is in effect

2011-06-14 Thread GHC
#5255: String literals cause runtime crashes when OverloadedStrings is in effect
-+--
Reporter:  YitzGale  |Owner:  
Type:  feature request   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  7.0.3   
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--

Comment(by cdsmith):

 Just copying this from elsewhere.  I'm not necessarily in favor of this
 idea, but I think it would be a valid, semantics-preserving transformation
 to have the compiler speculatively try to evaluate string (and numeric,
 for that matter) literals at compile time, and just give up if:

 * The code ran for too long.
 * The code used unsafePerformIO or something similar.

 At its root, this would be nothing more than an optimization -- evaluating
 a complex expression at compile time.  But there could be a warning for
 cases when you gave up due to the computation taking too long or doing
 unsafePerformIO tricks, or where it's known that the literal is bottom.

 I'm not saying I think we *should* do this.  But I'm saying I think it
 would beat adding another order of magnitude of complexity to the
 semantics of literals by making them depend on TH and quasiquoting.

-- 
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] #5218: Add unpackCStringLen# to create Strings from string literals

2011-06-14 Thread GHC
#5218: Add unpackCStringLen# to create Strings from string literals
-+--
Reporter:  tibbe |Owner:  
Type:  feature request   |   Status:  new 
Priority:  high  |Milestone:  7.4.1   
   Component:  Compiler  |  Version:  7.0.3   
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--

Comment(by duncan):

 Solution 2 looks good to me.

 As tibbe says, solution 1 would also be useful in other use cases. Hex,
 octal or bit string literals.

 And if we ever switch `Text` to use UTF8 then `unpackCStringUtf8Len#`
 would be useful there 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] #4504: "awaitSignal Nothing" does not block thread with -threaded

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

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


Comment:

 All the patches looks merged to me.

 If I understand correctly, the program needs to be changed to
 {{{
 module Main where

 import System.Posix.Signals
 import Control.Concurrent

 main :: IO ()
 main = do
   blockSignals reservedSignals
   awaitSignal Nothing >> yield
 }}}
 and that behaves correctly.

-- 
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] #5255: String literals cause runtime crashes when OverloadedStrings is in effect

2011-06-14 Thread GHC
#5255: String literals cause runtime crashes when OverloadedStrings is in effect
-+--
Reporter:  YitzGale  |Owner:  
Type:  feature request   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  7.0.3   
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--

Comment(by simonpj):

 OK, so this is largely a question of syntactic overhead.

 I still think TH is the right mechanism, regardless of the syntax
  * TH is GHC's only mechanism for guaranteeing compile time evaluation
  * It hooks into the error reporting monad, so you get proper civilised
 error messages with decent line numbres.  Something based on "`evaluate
 (packBS "foo{name")`" at compile time will not.
  * Adding interaction with overloading is even worse.  What is supposed to
 happen for
 {{{
 f :: IsString s => [s]
 f = ["foo", "bar{n"]
 }}}
  You can't do this statically.

 That said, I don't see a way to achieve what you want with zero syntactic
 overhead.

 Still, if you can think of a quieter notation for quasiquoting, sing out.

-- 
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] #5255: String literals cause runtime crashes when OverloadedStrings is in effect

2011-06-14 Thread GHC
#5255: String literals cause runtime crashes when OverloadedStrings is in effect
-+--
Reporter:  YitzGale  |Owner:  
Type:  feature request   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  7.0.3   
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--

Comment(by snoyberg):

 Replying to [comment:8 simonpj]:
 > I'm having trouble following the details of this discussion; some
 examples would help.
 >
 > As I understand it, what you want is to be able to write the Haskell
 expression
 > {{{
 >  "mumble" :: XML
 > }}}
 > and have a ''compile-time'' error saying that the string is ill-formed.
 Is that right.
 >
 > If so, the solution is to hand, in the form of quasi-quotation
 ([http://www.haskell.org/ghc/docs/7.0-latest/html/users_guide/template-
 haskell.html#th-quasiquotation]), Geoff Mainland's enhancement to Template
 Haskell.  You say
 > {{{
 >   [xml| mumble |]
 > }}}

 We're not using IsString for the XML datatype, but rather for the Name
 datatype. An element or attribute name is composed of a local name, a
 namespace and a prefix, resulting in the datatype:

 {{{
 data Name = Name { local :: Text, namespace :: Maybe Text, prefix :: Maybe
 Text }
 }}}

 The idea of the current IsString instance for Name is to be able to encode
 both the namespace and the local name simultaneously, via "clark
 notation." In other words, "foo" => Name "foo" Nothing Nothing, and
 "{bar}foo" => Name "foo" (Just "bar") Nothing. The problem arises when the
 programmer enters the string literal "{barfoo", which currently errors
 out.

 The reason we'd like to avoid using a quasi-quoter is that it's simply
 much bigger syntax overhead than a string literal. My code base makes use
 of the IsString instance all over the place, and having to turn "{bar}foo"
 into [name|{bar}foo|] everywhere would just be inconvenient.

-- 
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] #4978: Continuation passing style loop doesn't compile into a loop

2011-06-14 Thread GHC
#4978: Continuation passing style loop doesn't compile into a loop
+---
  Reporter:  tibbe  |  Owner:  
  Type:  bug| Status:  closed  
  Priority:  normal |  Milestone:  7.2.1   
 Component:  Compiler   |Version:  7.0.1   
Resolution:  fixed  |   Keywords:  
  Testcase:  perf/should_run/T4978  |  Blockedby:  
Difficulty: | Os:  Unknown/Multiple
  Blocking: |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown   |  
+---
Changes (by simonpj):

  * testcase:  => perf/should_run/T4978


-- 
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] #5218: Add unpackCStringLen# to create Strings from string literals

2011-06-14 Thread GHC
#5218: Add unpackCStringLen# to create Strings from string literals
-+--
Reporter:  tibbe |Owner:  
Type:  feature request   |   Status:  new 
Priority:  high  |Milestone:  7.4.1   
   Component:  Compiler  |  Version:  7.0.3   
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--

Comment(by simonmar):

 I think we want to do both - the two solutions are complementary.

 For large ByteString literals, such as when you've serialised and gzipped
 a data structure for unpacking at runtime, the quasiquotation syntax makes
 perfect sense.

 However, some people want to write ByteString literals using string
 syntax, and to not have to use TH just for one of these small literals (TH
 is seen as a heavyweight dependency if you haven't already bought in).

-- 
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] #5250: SEGFAULT in FFI to C++ library

2011-06-14 Thread GHC
#5250: SEGFAULT in FFI to C++ library
-+--
Reporter:  acowley   |Owner:  simonmar 
Type:  bug   |   Status:  new  
Priority:  high  |Milestone:  7.2.1
   Component:  Compiler (FFI)|  Version:  7.0.3
Keywords:| Testcase:   
   Blockedby:|   Difficulty:   
  Os:  Unknown/Multiple  | Blocking:   
Architecture:  x86   |  Failure:  Runtime crash
-+--
Changes (by simonmar):

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


-- 
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] #5218: Add unpackCStringLen# to create Strings from string literals

2011-06-14 Thread GHC
#5218: Add unpackCStringLen# to create Strings from string literals
-+--
Reporter:  tibbe |Owner:  
Type:  feature request   |   Status:  new 
Priority:  high  |Milestone:  7.4.1   
   Component:  Compiler  |  Version:  7.0.3   
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--

Comment(by simonpj):

 What's wrong with Template Haskell?  The solution is so simple, it seems a
 shame not to use it, no?

-- 
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] #5218: Add unpackCStringLen# to create Strings from string literals

2011-06-14 Thread GHC
#5218: Add unpackCStringLen# to create Strings from string literals
-+--
Reporter:  tibbe |Owner:  
Type:  feature request   |   Status:  new 
Priority:  high  |Milestone:  7.4.1   
   Component:  Compiler  |  Version:  7.0.3   
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--

Comment(by tibbe):

 If solution two works I'm for it. It feels a bit complex but perhaps
 there's no better option. I'm against solution 1 as it would make most
 Haskell programs Template Haskell programs, as byte string literals are
 quite common, and that feels a bit too much to solve this problem.

 If we could have proper byte string literals (ala Python's b"...") that
 would be even better but I guess that would be a too invasive change.

-- 
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] #5255: String literals cause runtime crashes when OverloadedStrings is in effect

2011-06-14 Thread GHC
#5255: String literals cause runtime crashes when OverloadedStrings is in effect
-+--
Reporter:  YitzGale  |Owner:  
Type:  feature request   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  7.0.3   
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by simonmar):

  * type:  bug => feature request


Comment:

 Replying to [comment:6 jmillikin]:

 > (side note: Calling this a "crash" is silly, since nothing crashes, and
 the error is reported as a standard exception. The word "crash" should be
 reserved for actual crashes, such as {{{peek nullPtr}}}).

 Hear hear.  I panicked when I saw the word "crash" in this bug report,
 only to find that GHC is working exactly as it is supposed to.

 This ticket is not a bug.  It's not really a feature request either, since
 there's no agreement yet on what changes should be made (if any), but I'm
 changing it to a feature request so the discussion can continue here if
 you like.  It might be better to take this somewhere else though (e.g.
 ghc-users).

-- 
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] #5255: String literals cause runtime crashes when OverloadedStrings is in effect

2011-06-14 Thread GHC
#5255: String literals cause runtime crashes when OverloadedStrings is in effect
-+--
Reporter:  YitzGale  |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  7.0.3   
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--

Comment(by simonmar):

 Replying to [comment:2 duncan]:
 > Closely related is that for ByteString it'd be nice to enforce that the
 chars are ASCII only. Currently it is possible to use unicode literals
 with ByteString and the result you get is not defined (I think it will
 actually vary depending on -O0 vs -O1 due to RULES that bypass B.pack).

 Actually the RULEs for ByteString literals won't apply to non-ASCII string
 literals, because GHC uses a different desugaring for these.  For a
 detailed description of the current (sorry) state, see #5218.

-- 
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] #4081: Strict constructor fields inspected in loop

2011-06-14 Thread GHC
#4081: Strict constructor fields inspected in loop
-+--
Reporter:  rl|Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone:  7.2.1  
   Component:  Compiler  |  Version:  6.13   
Keywords:| Testcase: 
   Blockedby:|   Difficulty: 
  Os:  Unknown/Multiple  | Blocking: 
Architecture:  Unknown/Multiple  |  Failure:  Runtime performance bug
-+--
Changes (by benl):

 * cc: benl@… (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] #5031: GHC API (7.0.2) + runhaskell causes bus error in Mac OS X 10.6

2011-06-14 Thread GHC
#5031: GHC API (7.0.2) + runhaskell causes bus error in Mac OS X 10.6
-+--
Reporter:  guest |Owner:  igloo   
Type:  bug   |   Status:  new 
Priority:  high  |Milestone:  7.2.1   
   Component:  GHC API   |  Version:  7.0.2   
Keywords:  ghc api,runhaskell,ghci,segv  | Testcase:  
   Blockedby:|   Difficulty:  
  Os:  MacOS X   | Blocking:  
Architecture:  x86   |  Failure:  None/Unknown
-+--
Changes (by jcpetruzza):

 * cc: jcpetruzza@… (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] #5132: Segfault on OS X in GHCi when using GHC API

2011-06-14 Thread GHC
#5132: Segfault on OS X in GHCi when using GHC API
---+
Reporter:  nominolo|Owner:  igloo 
Type:  bug |   Status:  new   
Priority:  high|Milestone:  7.2.1 
   Component:  GHCi|  Version:  7.0.2 
Keywords:  | Testcase:
   Blockedby:  |   Difficulty:
  Os:  MacOS X | Blocking:
Architecture:  x86_64 (amd64)  |  Failure:  GHCi crash
---+
Changes (by jcpetruzza):

 * cc: jcpetruzza@… (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] #5255: String literals cause runtime crashes when OverloadedStrings is in effect

2011-06-14 Thread GHC
#5255: String literals cause runtime crashes when OverloadedStrings is in effect
-+--
Reporter:  YitzGale  |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  7.0.3   
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--

Old description:

> There has been a discussion[1] on the web-devel list about
> the fate of the `IsString` instance for Name in the xml-types
> library[2]. A Name is the name of an XML element or attribute.
>
> That instance calls error when the string contains a certain
> kind of invalid domain-specific syntax. Some are even advocating
> expanding this behavior to any string that is syntactically
> invalid for XML names.
>
> So we now have GHC as the only major compiler which
> can cause *runtime* crashes depending on what characters
> are used in a string literal.
>
> `OverloadedStrings` as a more general mechanism is very
> convenient in many settings. One of them is XML names;
> another is attoparsec-text[3] parsers. I must
> admit I have succumbed to the temptation of making this
> deal with the devil and benefiting from them.
>
> But when used this way `OverloadedStrings`
> is really just another syntax for quasi-quotation, and that
> is what should have been used explicitly instead of these
> unsafe domain-specific IsString instances.
>
> I propose fixing the problem in one of the following ways:
>
> A. Make string literals syntax in fact a specialized
> quasi-quotation when `OverloadedStrings` is turned on. That way,
> exceptions are caught at compile time as they should be.
>
> B. Bless Text, and possibly `ByteString`, as the only types that
> get magical behavior of string literals.
>
> C. Remove `OverloadedStrings` altogether.
>
> Option A is by far the nicest. But it requires GHC
> to know the type of the string literal before
> the cast is applied. We might also need some way to help
> GHC find the cast function at the right time, beyond just
> having an IsString instance somewhere in scope.
>
> By submitting this bug, I am making it clear that I am opposed
> to Option D, leaving things the way they are and wishing
> everyone the best of luck. The `OverloadedStrings` pragma
> is not really optional anymore now that Text is becoming
> the default string type in practice for Haskell. It is not
> acceptable to have to wrap every string awkwardly with
> `(T.pack "")` and give up the chance of it being CAFfed.
> In fact, the blaze-html[4] library relies on
> `OverloadedStrings` for its performance[5].
>
> I am also opposed, though less so, to providing a
> deprecation route by using a new language pragma for
> Option A or B. The current behavior is dangerous and
> should be summarily removed.
>
>  * [1] http://www.haskell.org/pipermail/web-devel/2011/001630.html
>  * [2] http://hackage.haskell.org/package/xml-types
>  * [3] http://hackage.haskell.org/package/attoparsec-text
>  * [4] http://hackage.haskell.org/package/blaze-html
>  * [5] http://www.haskell.org/pipermail/web-devel/2011/001717.html

New description:

 There has been a discussion[1] on the web-devel list about
 the fate of the `IsString` instance for Name in the xml-types
 library[2]. A Name is the name of an XML element or attribute.

 That instance calls error when the string contains a certain
 kind of invalid domain-specific syntax. Some are even advocating
 expanding this behavior to any string that is syntactically
 invalid for XML names.

 So we now have GHC as the only major compiler which
 can cause *runtime* crashes depending on what characters
 are used in a string literal.

 `OverloadedStrings` as a more general mechanism is very
 convenient in many settings. One of them is XML names;
 another is attoparsec-text[3] parsers. I must
 admit I have succumbed to the temptation of making this
 deal with the devil and benefiting from them.

 But when used this way `OverloadedStrings`
 is really just another syntax for quasi-quotation, and that
 is what should have been used explicitly instead of these
 unsafe domain-specific `IsString` instances.

 I propose fixing the problem in one of the following ways:

 A. Make string literals syntax in fact a specialized
 quasi-quotation when `OverloadedStrings` is turned on. That way,
 exceptions are caught at compile time as they should be.

 B. Bless Text, and possibly `ByteString`, as the only types that
 get magical behavior of string literals.

 C. Remove `OverloadedStrings` altogether.

 Option A is by far the nicest. But it requires GHC
 to know the type of

Re: [GHC] #5255: String literals cause runtime crashes when OverloadedStrings is in effect

2011-06-14 Thread GHC
#5255: String literals cause runtime crashes when OverloadedStrings is in effect
-+--
Reporter:  YitzGale  |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  7.0.3   
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Description changed by simonpj:

Old description:

> There has been a discussion[1] on the web-devel list about
> the fate of the IsString instance for Name in the xml-types
> library[2]. A Name is the name of an XML element or attribute.
>
> That instance calls error when the string contains a certain
> kind of invalid domain-specific syntax. Some are even advocating
> expanding this behavior to any string that is syntactically
> invalid for XML names.
>
> So we now have GHC as the only major compiler which
> can cause *runtime* crashes depending on what characters
> are used in a string literal.
>
> OverloadedStrings as a more general mechanism is very
> convenient in many settings. One of them is XML names;
> another is attoparsec-text[3] parsers. I must
> admit I have succumbed to the temptation of making this
> deal with the devil and benefiting from them.
>
> But when used this way OverloadedStrings
> is really just another syntax for quasi-quotation, and that
> is what should have been used explicitly instead of these
> unsafe domain-specific IsString instances.
>
> I propose fixing the problem in one of the following ways:
>
> A. Make string literals syntax in fact a specialized
> quasi-quotation when OverloadedStrings is turned on. That way, exceptions
> are caught at compile time as they should be.
>
> B. Bless Text, and possibly ByteString, as the only types that
> get magical behavior of string literals.
>
> C. Remove OverloadedStrings altogether.
>
> Option A is by far the nicest. But it requires GHC
> to know the type of the string literal before
> the cast is applied. We might also need some way to help
> GHC find the cast function at the right time, beyond just
> having an IsString instance somewhere in scope.
>
> By submitting this bug, I am making it clear that I am opposed
> to Option D, leaving things the way they are and wishing
> everyone the best of luck. The OverloadedStrings pragma
> is not really optional anymore now that Text is becoming
> the default string type in practice for Haskell. It is not
> acceptable to have to wrap every string awkwardly with
> `(T.pack "")` and give up the chance of it being CAFfed.
> In fact, the blaze-html[4] library relies on
> OverloadedStrings for its performance[5].
>
> I am also opposed, though less so, to providing a
> deprecation route by using a new language pragma for
> Option A or B. The current behavior is dangerous and
> should be summarily removed.
>
>  * [1] http://www.haskell.org/pipermail/web-devel/2011/001630.html
>  * [2] http://hackage.haskell.org/package/xml-types
>  * [3] http://hackage.haskell.org/package/attoparsec-text
>  * [4] http://hackage.haskell.org/package/blaze-html
>  * [5] http://www.haskell.org/pipermail/web-devel/2011/001717.html

New description:

 There has been a discussion[1] on the web-devel list about
 the fate of the `IsString` instance for Name in the xml-types
 library[2]. A Name is the name of an XML element or attribute.

 That instance calls error when the string contains a certain
 kind of invalid domain-specific syntax. Some are even advocating
 expanding this behavior to any string that is syntactically
 invalid for XML names.

 So we now have GHC as the only major compiler which
 can cause *runtime* crashes depending on what characters
 are used in a string literal.

 `OverloadedStrings` as a more general mechanism is very
 convenient in many settings. One of them is XML names;
 another is attoparsec-text[3] parsers. I must
 admit I have succumbed to the temptation of making this
 deal with the devil and benefiting from them.

 But when used this way `OverloadedStrings`
 is really just another syntax for quasi-quotation, and that
 is what should have been used explicitly instead of these
 unsafe domain-specific IsString instances.

 I propose fixing the problem in one of the following ways:

 A. Make string literals syntax in fact a specialized
 quasi-quotation when `OverloadedStrings` is turned on. That way,
 exceptions are caught at compile time as they should be.

 B. Bless Text, and possibly `ByteString`, as the only types that
 get magical behavior of string literals.

 C. Remove `OverloadedStrings` altogether.

 Option A is by far the nicest. But it requires GHC
 to kn