Re: [GHC] #7483: Broken Read instance for Data.Fixed (no parse in legitimate cases).

2013-01-03 Thread GHC
#7483: Broken Read instance for Data.Fixed (no parse in legitimate cases).
-+--
Reporter:  navaati   |   Owner: 
Type:  bug   |  Status:  new
Priority:  normal|   Milestone: 
   Component:  libraries/base| Version:  7.6.1  
Keywords:|  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple  | Failure:  Incorrect result at runtime
  Difficulty:  Unknown   |Testcase: 
   Blockedby:|Blocking: 
 Related:  #4502 |  
-+--
Changes (by simonpj):

  * difficulty:  = Unknown


Comment:

 This commit claims to fix it.  Close?
 {{{
 commit 3fb1aacabbded36e9203adf922af197db0652646
 Author: Ian Lynagh i...@well-typed.com
 Date:   Wed Jan 2 23:18:18 2013 +

 Fix Data.Fixed.Fixed's Read instance; fixes #7483

 ---

  Data/Fixed.hs |   37 ++---
  GHC/Read.lhs  |1 +
  Text/Read/Lex.hs  |   18 +-
  tests/all.T   |1 +
  tests/readFixed001.hs |   13 +
  tests/readFixed001.stdout |6 ++
  6 files changed, 52 insertions(+), 24 deletions(-)

 diff --git a/Data/Fixed.hs b/Data/Fixed.hs index b4a9857..fd0ca01 100644
 --- a/Data/Fixed.hs
 +++ b/Data/Fixed.hs
 @@ -1,5 +1,5 @@
  {-# LANGUAGE Trustworthy #-}
 -{-# LANGUAGE CPP #-}
 +{-# LANGUAGE CPP, ScopedTypeVariables, PatternGuards #-}
  {-# OPTIONS -Wall -fno-warn-unused-binds #-}  #ifndef __NHC__  {-#
 LANGUAGE DeriveDataTypeable #-} @@ -40,12 +40,13 @@ module Data.Fixed
  ) where

  import Prelude -- necessary to get dependencies right -import Data.Char
 -import Data.List  #ifndef __NHC__  import Data.Typeable  import Data.Data
 #endif
 +import GHC.Read
 +import Text.ParserCombinators.ReadPrec
 +import Text.Read.Lex

  #ifndef __NHC__
  default () -- avoid any defaulting shenanigans @@ -159,30 +160,20 @@
 showFixed chopTrailingZeros fa@(MkFixed a) = (show i) ++ (withDot
 (showIntegerZe
  maxnum = 10 ^ digits
  fracNum = div (d * maxnum) res

 -readsFixed :: (HasResolution a) = ReadS (Fixed a) -readsFixed =
 readsSigned
 -where readsSigned ('-' : xs) = [ (negate x, rest)
 -   | (x, rest) - readsUnsigned xs ]
 -  readsSigned xs = readsUnsigned xs
 -  readsUnsigned xs = case span isDigit xs of
 - ([], _) - []
 - (is, xs') -
 - let i = fromInteger (read is)
 - in case xs' of
 -'.' : xs'' -
 -case span isDigit xs'' of
 -([], _) - []
 -(js, xs''') -
 -let j = fromInteger (read js)
 -l = genericLength js ::
 Integer
 -in [(i + (j / (10 ^ l)),
 xs''')]
 -_ - [(i, xs')]
 -
  instance (HasResolution a) = Show (Fixed a) where
  show = showFixed False

  instance (HasResolution a) = Read (Fixed a) where
 -readsPrec _ = readsFixed
 +readPrec = readNumber convertFixed
 +readListPrec = readListPrecDefault
 +readList = readListDefault
 +
 +convertFixed :: forall a . HasResolution a = Lexeme - ReadPrec (Fixed
 +a) convertFixed (Number n)
 + | Just (i, f) - numberToFixed r n =
 +return (fromInteger i + (fromInteger f / (10 ^ r)))
 +where r = resolution (undefined :: Fixed a) convertFixed _ = pfail

  data E0 = E0
  #ifndef __NHC__
 diff --git a/GHC/Read.lhs b/GHC/Read.lhs index c542274..5ad9527 100644
 --- a/GHC/Read.lhs
 +++ b/GHC/Read.lhs
 @@ -38,6 +38,7 @@ module GHC.Read
, list
, choose
, readListDefault, readListPrecDefault
 +  , readNumber

-- Temporary
, readParen
 diff --git a/Text/Read/Lex.hs b/Text/Read/Lex.hs index 8a64e21..c1592c6
 100644
 --- a/Text/Read/Lex.hs
 +++ b/Text/Read/Lex.hs
 @@ -19,7 +19,7 @@ module Text.Read.Lex
-- lexing types
( Lexeme(..)

 -  , numberToInteger, numberToRational, numberToRangedRational
 +  , numberToInteger, numberToFixed, numberToRational,
 + numberToRangedRational

-- lexer
, lex, expect
 @@ -82,6 +82,22 @@ numberToInteger (MkNumber base iPart) = Just (val
 (fromIntegral base) 0 iPart)  numberToInteger (MkDecimal iPart Nothing
 Nothing) = Just (val 10 0 iPart)  numberToInteger _ = Nothing

 +numberToFixed :: Integer - Number - Maybe (Integer, 

[GHC] #7551: GHCI does not support UTF8 file names.

2013-01-03 Thread GHC
#7551: GHCI does not support UTF8 file names.
---+
Reporter:  timthelion  |  Owner:  
Type:  bug | Status:  new 
Priority:  normal  |  Component:  GHCi
 Version:  7.4.2   |   Keywords:  
  Os:  Linux   |   Architecture:  Unknown/Multiple
 Failure:  GHCi crash  |  Blockedby:  
Blocking:  |Related:  
---+
 {{{
 [timothy@timothy current]$ ghci první/syntax/poznamky.hs
 GHCi, version 7.4.2: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.

 no location info: can't find file: prvn?/syntax/poznamky.hs
 Failed, modules loaded: none.
 Prelude :q
 Leaving GHCi.
 [timothy@timothy current]$ ghci
 GHCi, version 7.4.2: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 Prelude :load první/syntax/poznamky.hs

 no location info: can't find file: první/syntax/poznamky.hs
 Failed, modules loaded: none.
 Prelude :q
 Leaving GHCi.
 [timothy@timothy current]$ cd první/syntax/
 [timothy@timothy syntax]$ ghci poznamky.hs
 GHCi, version 7.4.2: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 [1 of 1] Compiling Main ( poznamky.hs, interpreted )
 Ok, modules loaded: Main.
 *Main
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7551
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] #7258: Compiling DynFlags is jolly slow

2013-01-03 Thread GHC
#7258: Compiling DynFlags is jolly slow
-+--
Reporter:  simonpj   |   Owner:  simonpj 
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by simonpj):

 OK I have verified that the changes to the occurrence analyser (above)
 make essentially zero different to nofib numbers.  It's a very worthwhile
 simplification, because it completely gets rid of the `getProxies` stuff
 that was eating all the time before.

 Alas, compiling W2 is still non-linear.  Here's the allocation by the
 stage-2 compiler
  * 50 fields: 1.01 Gbyte
  * 100 fields: 2.98 Gbyte
  * 200 fields: 9.64 Gbyte

 This is after including the improvements to the derived `Read` code in
 #7450.

 So something is still wrong.  Need to do some profilling to find out.

 There are some very deeply nested lambdas, which lead to SRTs of ever-
 increasing size, so there is definitely a quadratic effect there.  But I'm
 not sure that is all.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7258#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] #7521: Simplifier ticks exhausted when compiling Accelerate example.

2013-01-03 Thread GHC
#7521: Simplifier ticks exhausted when compiling Accelerate example.
-+--
Reporter:  eamsden   |   Owner:
Type:  bug   |  Status:  new   
Priority:  normal|   Milestone:
   Component:  Compiler  | Version:  7.6.1 
Keywords:|  Os:  Linux 
Architecture:  Unknown/Multiple  | Failure:  Compile-time crash
  Difficulty:  Unknown   |Testcase:
   Blockedby:|Blocking:
 Related:|  
-+--
Changes (by simonpj):

  * difficulty:  = Unknown


Old description:

 When doing $ cabal build for:

 http://github.com/AccelerateHS/accelerate-examples (commit
 def2495a1e7bd88e444540c3494b8674da99e201)

 [31 of 36] Compiling SMVM.Matrix  (
 examples/tests/simple/SMVM/Matrix.hs, dist_accelerate/build/accelerate-
 examples/accelerate-examples-tmp/SMVM/Matrix.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.6.1 for x86_64-unknown-linux):
 Simplifier ticks exhausted
 When trying UnfoldingDone base:GHC.Base.returnIO1{v r5g} [gid]
 To increase the limit, use -fsimpl-tick-factor=N (default 100)
 If you need to do this, let GHC HQ know, and what factor you needed
 To see detailed counts use -ddump-simpl-stats
 Total ticks: 27960

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

New description:

 When doing $ `cabal build` for: http://github.com/AccelerateHS/accelerate-
 examples (commit def2495a1e7bd88e444540c3494b8674da99e201):
 {{{
 [31 of 36] Compiling SMVM.Matrix  (
 examples/tests/simple/SMVM/Matrix.hs, dist_accelerate/build/accelerate-
 examples/accelerate-examples-tmp/SMVM/Matrix.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.6.1 for x86_64-unknown-linux):
 Simplifier ticks exhausted
 When trying UnfoldingDone base:GHC.Base.returnIO1{v r5g} [gid]
 To increase the limit, use -fsimpl-tick-factor=N (default 100)
 If you need to do this, let GHC HQ know, and what factor you needed
 To see detailed counts use -ddump-simpl-stats
 Total ticks: 27960
 }}}

--

Comment:

 What `-fsimpl-tick-factor` makes it work?

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7521#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] #7421: Data.List.insert / insertBy do not match the documentation

2013-01-03 Thread GHC
#7421: Data.List.insert / insertBy do not match the documentation
-+--
Reporter:  Bart Massey   |   Owner: 
Type:  bug   |  Status:  merge  
Priority:  normal|   Milestone:  7.6.2  
   Component:  libraries/base| Version:  7.6.1  
Keywords:|  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple  | Failure:  Incorrect result at runtime
  Difficulty:  Unknown   |Testcase: 
   Blockedby:|Blocking: 
 Related:|  
-+--
Changes (by igloo):

  * status:  new = merge
  * difficulty:  = Unknown
  * milestone:  = 7.6.2


Comment:

 Thanks for the report. Fixed by:
 {{{
 commit 08f3e69e34a889c8b85513b243935665a000bfac
 Author: Ian Lynagh i...@well-typed.com
 Date:   Wed Jan 2 21:42:22 2013 +

 Clarify the wording of the 'insert' haddock; fixes #7421

 Wording suggested by Bart Massey.
 }}}

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

2013-01-03 Thread GHC
#7483: Broken Read instance for Data.Fixed (no parse in legitimate cases).
--+-
  Reporter:  navaati  |  Owner:  
  Type:  bug  | Status:  closed  
  Priority:  normal   |  Milestone:  
 Component:  libraries/base   |Version:  7.6.1   
Resolution:  fixed|   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown 
  Testcase:  readFixed001 |  Blockedby:  
  Blocking:   |Related:  #4502   
--+-
Changes (by igloo):

  * status:  new = closed
  * testcase:  = readFixed001
  * resolution:  = fixed


Comment:

 Fixed by above patch.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7483#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] #7450: Regression in optimisation time of functions with many patterns (6.12 to 7.4)?

2013-01-03 Thread GHC
#7450: Regression in optimisation time of functions with many patterns (6.12 to
7.4)?
---+
  Reporter:  iustin|  Owner:  
  Type:  bug   | Status:  new 
  Priority:  normal|  Milestone:  
 Component:  Compiler  |Version:  7.6.1   
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Compile-time performance bug  | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by simonpj):

 OK with these changes I now get this:

 ||  ||6.12.3||  6.12.3||HEAD||  HEAD||
 ||#constructors||   Alloc (Mbytes)||Time (s)||  Alloc
 (Mbytes)  ||Time (s)||
 ||40||  || ||   1075||  1.7||
 ||80||1646||4|| 2184||5||
 ||160|| 3217||8 ||4862  ||10||
 ||320   ||6385  ||16||12242 ||23||
 ||640|| 12766   ||34||  35009|| 60||

 So it still looks quite a bit less well-behaved than 6.12.3, for reasons I
 don't yet understand.  But better than before.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7450#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] #7436: Derived Foldable and Traversable instances become extremely inefficient due to eta-expansion

2013-01-03 Thread GHC
#7436: Derived Foldable and Traversable instances become extremely inefficient 
due
to eta-expansion
-+--
Reporter:  shachaf   |   Owner: 
Type:  bug   |  Status:  patch  
Priority:  normal|   Milestone: 
   Component:  Compiler  | Version:  7.6.1  
Keywords:|  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple  | Failure:  Runtime performance bug
  Difficulty:  Unknown   |Testcase: 
   Blockedby:|Blocking: 
 Related:|  
-+--

Comment(by twanvl):

 I added an explanation of the behaviour and a link to this ticket to the
 description at the top of the Functor deriving code. I did not make it a
 separate note, since there is no reference to it from inside the code. The
 patch that adds this note is attached.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7436#comment:14
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] #7542: GHC doesn't optimize (strict) composition with id

2013-01-03 Thread GHC
#7542: GHC doesn't optimize (strict) composition with id
-+--
Reporter:  shachaf   |   Owner: 
Type:  bug   |  Status:  new
Priority:  normal|   Milestone: 
   Component:  Compiler  | Version:  7.6.1  
Keywords:|  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple  | Failure:  Runtime performance bug
  Difficulty:  Unknown   |Testcase: 
   Blockedby:|Blocking: 
 Related:|  
-+--
Changes (by shachaf):

  * status:  infoneeded = new


Comment:

 Here's an example of the sort of context this comes up in:

 {{{
 module T7542 where

 import Unsafe.Coerce

 newtype Id a = MkId { unId :: a }

 -- Think of `mapped` as `mapM`, but restricted to Id (we could make it
 work
 -- with any Functor, rather than just []). `over` takes the Id wrappers
 back
 -- off. The goal is to make it easy to compose mapped with other functions
 of
 -- the same form. The wrapper should be free because it's just newtype
 noise.

 mapped1 :: (a - Id b) - [a] - Id [b]
 mapped1 f = MkId . map (unId . f)

 over1 :: ((a - Id b) - s - Id t) - (a - b) - s - t
 over1 l f = unId . l (MkId . f)

 map1 :: (a - b) - [a] - [b]
 map1 f xs = over1 mapped1 f xs
 -- Core: map1 = \f xs - map (\x - f x) xs

 -- over1 mapped1 = unId . MkId . map (unId . MkId . f)
 --   ~ map
 -- However, if f = ⊥, unId . MkId . f /= f!
 -- Therefore `over1 mapped1` must turn into \f - map (\x - f x)
 -- We can't expect GHC to compile it to `map` because it has different
 strictness.

 -- Let's define strict versions of (MkId .) and (unId .):
 mkIdDot2 :: (a - b) - a - Id b
 mkIdDot2 f = f `seq` \x - MkId (f x)

 unIdDot2 :: (a - Id b) - a - b
 unIdDot2 f = f `seq` \x - unId (f x)

 mapped2 :: (a - Id b) - [a] - Id [b]
 mapped2 f = mkIdDot2 (map (unIdDot2 f))

 over2 :: ((a - Id b) - s - Id t) - (a - b) - s - t
 over2 l f = unIdDot2 (l (mkIdDot2 f))

 map2 :: (a - b) - [a] - [b]
 map2 f xs = over2 mapped2 f xs
 -- map2 should have the same semantics as map. But the Core isn't the
 same:
 -- Without -fpedantic-bottoms: map2 = \f xs - map (\e - f e) xs
 -- With -fpedantic-bottoms:
 -- map2 = \f xs - map (case f of g { __DEFAULT - \x - g x }) xs
 -- Ideally, (case f of g { __DEFAULT - \x - g x }) would simply be f.

 -- Let's try manually telling GHC that our newtype compositions are
 coercions:
 -- (Ideally, this is what mkIdDot2 and unIdDot2 would compile into.)
 mkIdDot3 :: (a - b) - a - Id b
 mkIdDot3 = unsafeCoerce

 unIdDot3 :: (a - Id b) - a - b
 unIdDot3 = unsafeCoerce
 -- (Note: Due to #7398, we couldn't define a strict composition operator
 and
 -- rely on RULES to turn (MkId `dot`) into unsafeCoerce -- the `MkId`
 itself
 -- gets turned into a coercion before any RULES have a chance to fire.)

 mapped3 :: (a - Id b) - [a] - Id [b]
 mapped3 f = mkIdDot3 (map (unIdDot3 f))

 over3 :: ((a - Id b) - s - Id t) - (a - b) - s - t
 over3 l f = unIdDot3 (l (mkIdDot3 f))

 map3 :: (a - b) - [a] - [b]
 map3 f xs = over3 mapped3 f xs
 -- Core: map3 = map
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7542#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] #7551: GHCI does not support UTF8 file names.

2013-01-03 Thread GHC
#7551: GHCI does not support UTF8 file names.
---+
Reporter:  timthelion  |  Owner:  
Type:  bug | Status:  new 
Priority:  normal  |  Component:  GHCi
 Version:  7.4.2   |   Keywords:  
  Os:  Linux   |   Architecture:  Unknown/Multiple
 Failure:  GHCi crash  |  Blockedby:  
Blocking:  |Related:  
---+

Comment(by shachaf):

 I see the same problem in 7.4.1, but it works in 7.6.1.

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

2013-01-03 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 igloo):

 The problem with doing the check in `mkName` is that it would still be
 possible to make a variable that starts with a capital letter, or a
 constructor that starts with a lower case letter.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7484#comment:3
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] #7500: GHC: internal error: getMBlock: mmap: Operation not permitted

2013-01-03 Thread GHC
#7500: GHC: internal error: getMBlock: mmap: Operation not permitted
+---
  Reporter:  guest  |  Owner:  
  Type:  bug| Status:  closed  
  Priority:  normal |  Milestone:  
 Component:  Compiler   |Version:  7.4.1   
Resolution:  invalid|   Keywords:  
Os:  Linux  |   Architecture:  Unknown/Multiple
   Failure:  Runtime crash  | Difficulty:  Unknown 
  Testcase: |  Blockedby:  
  Blocking: |Related:  
+---
Changes (by igloo):

  * status:  infoneeded = closed
  * difficulty:  = Unknown
  * resolution:  = invalid


Comment:

 I don't think there's a bug here: on a 32bit platform, a single process is
 still limited to 2G of memory.

 If you still think there's something wrong, please reopen and clarify what
 behaviour you were expecting.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7500#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] #7496: Support for JavaScript as an official GHC output language

2013-01-03 Thread GHC
#7496: Support for JavaScript as an official GHC output language
---+
  Reporter:  mcandre   |  Owner:   
  Type:  feature request   | Status:  closed   
  Priority:  normal|  Milestone:   
 Component:  Compiler  |Version:  7.6.1
Resolution:  wontfix   |   Keywords:  js, javascript, fay, compiler
Os:  Unknown/Multiple  |   Architecture:  Other
   Failure:  None/Unknown  | Difficulty:  Unknown  
  Testcase:|  Blockedby:   
  Blocking:|Related:   
---+

Comment(by simonpj):

 Javascript isn't the same as .NET or the JVM, but the same general
 sentiments apply.  Maybe a cut-down version of Haskell and libraries?  It
 would be a real project though.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7496#comment:3
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] #7528: Non terminating thunk resolution blocks world, even in the case of forkOS

2013-01-03 Thread GHC
#7528: Non terminating thunk resolution blocks world, even in the case of forkOS
--+-
  Reporter:  timthelion   |  Owner: 

  Type:  bug  | Status:  closed 

  Priority:  normal   |  Milestone: 

 Component:  Runtime System   |Version:  7.4.2  

Resolution:  duplicate|   Keywords:  forkOS Concurrent 
thunk
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   

   Failure:  Incorrect result at runtime  | Difficulty:  Unknown

  Testcase:   |  Blockedby: 

  Blocking:   |Related: 

--+-
Changes (by igloo):

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


Comment:

 Agreed, duplicate of #367.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7528#comment:3
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] #7551: GHCI does not support UTF8 file names.

2013-01-03 Thread GHC
#7551: GHCI does not support UTF8 file names.
-+--
  Reporter:  timthelion  |  Owner:  
  Type:  bug | Status:  closed  
  Priority:  normal  |  Milestone:  
 Component:  GHCi|Version:  7.4.2   
Resolution:  fixed   |   Keywords:  
Os:  Linux   |   Architecture:  Unknown/Multiple
   Failure:  GHCi crash  | Difficulty:  Unknown 
  Testcase:  |  Blockedby:  
  Blocking:  |Related:  
-+--
Changes (by igloo):

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


Comment:

 Yup, thanks for the report but it looks like it's already fixed.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7551#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] #2431: Allow empty case analysis

2013-01-03 Thread GHC
#2431: Allow empty case analysis
+---
Reporter:  RalfHinze|   Owner:  
Type:  feature request  |  Status:  new 
Priority:  low  |   Milestone:  _|_ 
   Component:  Compiler | Version:  6.8.3   
Keywords:  empty case analysis  |  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple | Failure:  None/Unknown
  Difficulty:  Unknown  |Testcase:  
   Blockedby:   |Blocking:  
 Related:   |  
+---

Comment(by simonpj):

 Oh ok I'll join up the final dots... patch coming.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2431#comment:13
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] #7493: STM and TVar report incorrect results

2013-01-03 Thread GHC
#7493: STM and TVar report incorrect results
--+-
  Reporter:  parcs|  Owner:  
  Type:  bug  | Status:  closed  
  Priority:  highest  |  Milestone:  7.6.2   
 Component:  Runtime System   |Version:  7.6.1   
Resolution:  fixed|   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by igloo):

  * status:  merge = closed
  * resolution:  = fixed


Comment:

 Reverted, and merged as 57c8d1c2c8ceba6973a48d138d1bb018ec2988ae

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


Re: [GHC] #7368: kindFunResult panic in the

2013-01-03 Thread GHC
#7368: kindFunResult panic in the
--+-
  Reporter:  ChrisN   |  Owner: 
 
  Type:  bug  | Status:  closed 
 
  Priority:  normal   |  Milestone: 
 
 Component:  Compiler (Type checker)  |Version:  7.6.1  
 
Resolution:  fixed|   Keywords:  Kinds, 
kindfunresult
Os:  Unknown/Multiple |   Architecture:  
Unknown/Multiple
   Failure:  Compile-time crash   | Difficulty:  Unknown
 
  Testcase:  typecheck/should_fail/T7368, T7368a  |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-
Changes (by igloo):

  * status:  merge = closed
  * resolution:  = fixed


Comment:

 Merged as c4b2ac3775323948b7a6abdb241a4ad02afa7141

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7368#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] #7545: Type variable capture in InstanceSigs message

2013-01-03 Thread GHC
#7545: Type variable capture in InstanceSigs message
--+-
  Reporter:  Feuerbach|  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:  typecheck/should_fail/T7545  |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by igloo):

  * status:  merge = closed
  * resolution:  = fixed


Comment:

 Merged as c4a2c5f6034b26425f617844b158457a592be379

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7545#comment:3
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] #7546: Manual 6.2 doesn't match current output formatting

2013-01-03 Thread GHC
#7546: Manual 6.2 doesn't match current output formatting
---+
  Reporter:  chrisseaton   |  Owner:  
  Type:  bug   | Status:  closed  
  Priority:  normal|  Milestone:  
 Component:  Documentation |Version:  7.6.1   
Resolution:  fixed |   Keywords:  strictness iface
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+
Changes (by igloo):

  * status:  merge = closed
  * resolution:  = fixed


Comment:

 Merged as 1e73d02befc5b3c4efe130964ea6088edbbeaaea

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7546#comment:3
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] #7421: Data.List.insert / insertBy do not match the documentation

2013-01-03 Thread GHC
#7421: Data.List.insert / insertBy do not match the documentation
--+-
  Reporter:  Bart Massey  |  Owner:  
  Type:  bug  | Status:  closed  
  Priority:  normal   |  Milestone:  7.6.2   
 Component:  libraries/base   |Version:  7.6.1   
Resolution:  fixed|   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by igloo):

  * status:  merge = closed
  * resolution:  = fixed


Comment:

 Merged as c4dec4948fc0b1185404e2a6d66aec25aa293b9f

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7421#comment:3
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] #7290: Minor documentation fix for directory

2013-01-03 Thread GHC
#7290: Minor documentation fix for directory
--+-
  Reporter:  SimonHengel  |  Owner:  
  Type:  bug  | Status:  closed  
  Priority:  normal   |  Milestone:  
 Component:  libraries/directory  |Version:  7.6.1   
Resolution:  fixed|   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Documentation bug| Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by igloo):

  * status:  merge = closed
  * resolution:  = fixed


Comment:

 Merged as 5ad061f1e54da784b0622169798f91ceb40ea382

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7290#comment:3
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] #7489: Obscure warning: Var/Type length mismatch when using GADTs and TypeFamilies

2013-01-03 Thread GHC
#7489: Obscure warning: Var/Type length mismatch when using GADTs and 
TypeFamilies
-+--
  Reporter:  portnov |  Owner:  

  Type:  bug | Status:  closed  

  Priority:  normal  |  Milestone:  

 Component:  Compiler|Version:  7.6.1   

Resolution:  fixed   |   Keywords:  

Os:  Unknown/Multiple|   Architecture:  
Unknown/Multiple
   Failure:  Incorrect warning at compile-time   | Difficulty:  Unknown 

  Testcase:  indexed_types/should_compile/T7489  |  Blockedby:  

  Blocking:  |Related:  

-+--
Changes (by igloo):

  * status:  merge = closed


Comment:

 Merged as 52e00f821c03fd2e3be7033f4f3b50ace05300fc

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7489#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] #7496: Support for JavaScript as an official GHC output language

2013-01-03 Thread GHC
#7496: Support for JavaScript as an official GHC output language
---+
  Reporter:  mcandre   |  Owner:
  
  Type:  feature request   | Status:  closed
  
  Priority:  normal|  Milestone:
  
 Component:  Compiler  |Version:  7.6.1 
  
Resolution:  wontfix   |   Keywords:  js, javascript, fay, 
compiler, ghcjs
Os:  Unknown/Multiple  |   Architecture:  Other 
  
   Failure:  None/Unknown  | Difficulty:  Unknown   
  
  Testcase:|  Blockedby:
  
  Blocking:|Related:
  
---+
Changes (by hamish):

  * keywords:  js, javascript, fay, compiler = js, javascript, fay,
   compiler, ghcjs


Comment:

 GHCJS is still making progress, but we could always use more help

 https://github.com/ghcjs/ghcjs/
 https://github.com/ghcjs/ghcjs-examples/

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

2013-01-03 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 ian@…):

 commit d9674323f6c39374c254da40054f28a7361fd100
 {{{
 Author: Ian Lynagh i...@well-typed.com
 Date:   Fri Jan 4 01:46:21 2013 +

 Set DBLATEX_OPTS to -P 'filename.as.url=0' (fixes #7486)

 Apparently this fixes the build with dblatex 0.3.4.

  mk/config.mk.in |2 ++
  1 files changed, 2 insertions(+), 0 deletions(-)
 }}}

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

2013-01-03 Thread GHC
#7486: dblatex can't build docs; fix included.
-+--
Reporter:  rlpowell  |   Owner: 
Type:  bug   |  Status:  merge  
Priority:  normal|   Milestone: 
   Component:  Build System  | Version:  7.6.1  
Keywords:|  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple  | Failure:  Building GHC failed
  Difficulty:  Unknown   |Testcase: 
   Blockedby:|Blocking: 
 Related:|  
-+--
Changes (by igloo):

  * status:  new = merge
  * difficulty:  = Unknown


Comment:

 Thanks for the report and the fix; applied in HEAD.

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