Re: [GHC] #5506: LLVM AST : needs an LlvmType ctor to represent vectors so that LLVM can generate SIMD instructions

2011-09-27 Thread GHC
#5506: LLVM AST : needs an LlvmType ctor to represent vectors so that LLVM can
generate SIMD instructions
-+--
Reporter:  erikd |   Owner:  dterei 
Type:  task  |  Status:  patch  
Priority:  normal|   Component:  Compiler (LLVM)
 Version:  7.3   |Keywords: 
Testcase:|   Blockedby: 
  Os:  Unknown/Multiple  |Blocking: 
Architecture:  Unknown/Multiple  | Failure:  None/Unknown   
-+--

Comment(by chak):

 Replying to [comment:2 erikd]:
  The only caveat is that generated code is really good when the vector
 length is a multiple of the vector register length (eg 4, 8, 12 etc for
 MMX/SSE) and woefull otherwise (I tested a vector length of 11).

 I am not surprised by this finding.  We'll have to break up larger vector
 operations into chunks that are a multiple of the vector length and handle
 the excess ourselves further up in the compilation pipeline.  This will
 involve having some knowledge of the target hardware capabilities further
 up in the compiler.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5506#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] #5509: quotes pretty-printer not working as comments specify

2011-09-27 Thread Malcolm Wallace
 From compiler/utils/Outputable.lhs
 {{{
 -- quotes encloses something in single quotes...
 -- but it omits them if the thing ends in a single quote
 -- so that we don't get `foo''.  Instead we just have foo'.
 quotes d = SDoc $ \sty -
let pp_d = runSDoc d sty in
case show pp_d of
  ('\'' : _) - pp_d
  _other - Pretty.quotes pp_d
 }}}
 
 This implementation does not match the comment - the code is checking for
 a leading single-quote, not for a trailing one.

I was bitten by this bug the other day.  The code I was modifying had values 
called
foo
foo'
foo''

and a type error message told me there was a fault with
   `foo''

so I ended up looking in entirely the wrong place for five minutes.

Regards,
Malcolm


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


Re: [GHC] #5506: LLVM AST : needs an LlvmType ctor to represent vectors so that LLVM can generate SIMD instructions

2011-09-27 Thread GHC
#5506: LLVM AST : needs an LlvmType ctor to represent vectors so that LLVM can
generate SIMD instructions
-+--
Reporter:  erikd |   Owner:  dterei 
Type:  task  |  Status:  patch  
Priority:  normal|   Component:  Compiler (LLVM)
 Version:  7.3   |Keywords: 
Testcase:|   Blockedby: 
  Os:  Unknown/Multiple  |Blocking: 
Architecture:  Unknown/Multiple  | Failure:  None/Unknown   
-+--

Comment(by erikd):

 Replying to [comment:3 chak]:
  I am not surprised by this finding.  We'll have to break up larger
 vector operations into chunks that are a multiple of the vector length and
 handle the excess ourselves further up in the compilation pipeline.  This
 will involve having some knowledge of the target hardware capabilities
 further up in the compiler.

 I actually think this should be fixed in LLVM. I asked about this in the
 LLVM dev mailing list and they say this is a bug. Bug reported here:

http://llvm.org/bugs/show_bug.cgi?id=11023

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


[GHC] #5512: UTF-16//ROUNDTRIP encoding behaves weirdly

2011-09-27 Thread GHC
#5512: UTF-16//ROUNDTRIP encoding behaves weirdly
-+--
Reporter:  batterseapower|   Owner: 
Type:  bug   |  Status:  new
Priority:  normal|   Component:  libraries/base 
 Version:  7.2.1 |Keywords: 
Testcase:|   Blockedby: 
  Os:  Unknown/Multiple  |Blocking: 
Architecture:  Unknown/Multiple  | Failure:  Incorrect result at runtime
-+--
 Try this program:

 {{{
 module Main where

 import System.IO

 main = do
 roundtrip_enc - mkTextEncoding UTF16//ROUNDTRIP
 h - openFile out.temp WriteMode
 hSetEncoding h roundtrip_enc
 hPutStr h Hi\xEFE8Hi
 }}}

 It fails with:

 {{{
 hSetEncoding: invalid argument (Invalid argument)
 }}}

 If you change UTF16 to UTF-16 (so we use the builtin encoding rather than
 iconv) it works, but the output file only contains the first Hi.

 I think what is going on here is that iconv does not generate EILSEQ for
 identity transformations such as that between a UTF-16 text file and our
 UTF-16 CharBuffers. Since we never get that exception, we can't fix up the
 lone surrogates we use to encode roundtrip characters.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5512
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] #5512: UTF-16//ROUNDTRIP encoding behaves weirdly

2011-09-27 Thread GHC
#5512: UTF-16//ROUNDTRIP encoding behaves weirdly
-+--
Reporter:  batterseapower|   Owner: 
Type:  bug   |  Status:  new
Priority:  normal|   Component:  libraries/base 
 Version:  7.2.1 |Keywords: 
Testcase:|   Blockedby: 
  Os:  Unknown/Multiple  |Blocking: 
Architecture:  Unknown/Multiple  | Failure:  Incorrect result at runtime
-+--
Description changed by batterseapower:

Old description:

 Try this program:

 {{{
 module Main where

 import System.IO

 main = do
 roundtrip_enc - mkTextEncoding UTF16//ROUNDTRIP
 h - openFile out.temp WriteMode
 hSetEncoding h roundtrip_enc
 hPutStr h Hi\xEFE8Hi
 }}}

 It fails with:

 {{{
 hSetEncoding: invalid argument (Invalid argument)
 }}}

 If you change UTF16 to UTF-16 (so we use the builtin encoding rather than
 iconv) it works, but the output file only contains the first Hi.

 I think what is going on here is that iconv does not generate EILSEQ for
 identity transformations such as that between a UTF-16 text file and our
 UTF-16 CharBuffers. Since we never get that exception, we can't fix up
 the lone surrogates we use to encode roundtrip characters.

New description:

 Try this program:

 {{{
 module Main where

 import System.IO

 main = do
 roundtrip_enc - mkTextEncoding UTF16//ROUNDTRIP
 h - openFile out.temp WriteMode
 hSetEncoding h roundtrip_enc
 hPutStr h Hi\xEFE8Hi
 }}}

 It fails with:

 {{{
 hSetEncoding: invalid argument (Invalid argument)
 }}}

 If you change UTF16 to UTF-16 (so we use the builtin encoding rather than
 iconv) it works, but the output file only contains the first Hi.

 I think part of what is going on here is that iconv does not generate
 EILSEQ for identity transformations such as that between a UTF-16 text
 file and our UTF-16 CharBuffers. Since we never get that exception, we
 can't fix up the lone surrogates we use to encode roundtrip characters.

--

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5512#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] #3356: {-# LANGUAGE NoTraditionalRecordSyntax #-} to disable the current record syntax

2011-09-27 Thread GHC
#3356: {-# LANGUAGE NoTraditionalRecordSyntax #-} to disable the current record
syntax
-+--
Reporter:  SamB  |Owner:  
Type:  feature request   |   Status:  new 
Priority:  normal|Milestone:  7.2.1   
   Component:  Compiler  |  Version:  6.10.2  
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  Unknown 
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--

Comment(by igloo@…):

 commit 742067003bfe91dbde91d1ff2e57c3182dabaa67
 {{{
 Author: Ian Lynagh ig...@earth.li
 Date:   Mon Sep 26 23:32:04 2011 +0100

 Define a TraditionalRecordSyntax extension; fixes #3356

 This allows the extension (which is on by default) to be turned off,
 which gets us a small step closer to replacing Haskell98 records with
 something better.

  compiler/main/DynFlags.hs|4 
  compiler/parser/Lexer.x  |6 ++
  compiler/parser/Parser.y.pp  |7 ---
  compiler/parser/RdrHsSyn.lhs |   10 ++
  4 files changed, 24 insertions(+), 3 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3356#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] #3356: {-# LANGUAGE NoTraditionalRecordSyntax #-} to disable the current record syntax

2011-09-27 Thread GHC
#3356: {-# LANGUAGE NoTraditionalRecordSyntax #-} to disable the current record
syntax
--+-
  Reporter:  SamB |  Owner:  
  Type:  feature request  | Status:  closed  
  Priority:  normal   |  Milestone:  7.2.1   
 Component:  Compiler |Version:  6.10.2  
Resolution:  fixed|   Keywords:  
  Testcase:   |  Blockedby:  
Difficulty:  Unknown  | Os:  Unknown/Multiple
  Blocking:   |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown |  
--+-
Changes (by igloo):

  * status:  new = closed
  * resolution:  = fixed


Comment:

 Implemented.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3356#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] #5435: GHCi linker should run constructors for linked libraries

2011-09-27 Thread GHC
#5435: GHCi linker should run constructors for linked libraries
-+--
Reporter:  pumpkin   |Owner:  
Type:  bug   |   Status:  new 
Priority:  high  |Milestone:  7.4.1   
   Component:  Compiler  |  Version:  7.2.1   
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by PHO):

 * cc: pho@… (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5435#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] #5513: panic! (the 'impossible' happened) on ‘deriving instance lowercase_name a’

2011-09-27 Thread GHC
#5513: panic! (the 'impossible' happened) on ‘deriving instance lowercase_name 
a’
-+--
Reporter:  andersk   |   Owner:
Type:  bug   |  Status:  new   
Priority:  normal|   Component:  Compiler  
 Version:  7.3   |Keywords:
Testcase:|   Blockedby:
  Os:  Unknown/Multiple  |Blocking:
Architecture:  Unknown/Multiple  | Failure:  Compile-time crash
-+--
 This bogus code:
 {{{
 {-# LANGUAGE StandaloneDeriving #-}
 deriving instance lowercase_name a
 }}}
 causes current GHC HEAD to panic:
 {{{
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.3.20110927 for x86_64-unknown-linux):
 nameModule lowercase_name{tv aar}

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

 I also tested GHC 7.0.3, which correctly diagnosed the problem:
 {{{
 crash.hs:2:19: Malformed instance header: lowercase_name a
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5513
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] #5506: LLVM AST : needs an LlvmType ctor to represent vectors so that LLVM can generate SIMD instructions

2011-09-27 Thread GHC
#5506: LLVM AST : needs an LlvmType ctor to represent vectors so that LLVM can
generate SIMD instructions
-+--
Reporter:  erikd |   Owner:  dterei 
Type:  task  |  Status:  patch  
Priority:  normal|   Component:  Compiler (LLVM)
 Version:  7.3   |Keywords: 
Testcase:|   Blockedby: 
  Os:  Unknown/Multiple  |Blocking: 
Architecture:  Unknown/Multiple  | Failure:  None/Unknown   
-+--

Comment(by dterei):

 Thanks for the patch. Will look at this soon but probably not till the
 weekend.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5506#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] #5506: LLVM AST : needs an LlvmType ctor to represent vectors so that LLVM can generate SIMD instructions

2011-09-27 Thread GHC
#5506: LLVM AST : needs an LlvmType ctor to represent vectors so that LLVM can
generate SIMD instructions
-+--
Reporter:  erikd |   Owner:  dterei 
Type:  task  |  Status:  patch  
Priority:  normal|   Component:  Compiler (LLVM)
 Version:  7.3   |Keywords: 
Testcase:|   Blockedby: 
  Os:  Unknown/Multiple  |Blocking: 
Architecture:  Unknown/Multiple  | Failure:  None/Unknown   
-+--

Comment(by dterei):

 As for the vector 11 size example. Is the poor performance when the vector
 isn't length that is multiple of the native vector size? OR when its not a
 power of 2? The LLVM bug you linked to seems to indicate the latter. If
 the latter it makes it easier for us to handle in GHC / Haskell code since
 we don't need to know the native vector size, just handle power of 2
 correction.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5506#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] #5499: Tagging constructors with record/product phantom type

2011-09-27 Thread GHC
#5499: Tagging constructors with record/product phantom type
+---
  Reporter:  basvandijk |  Owner:  
  Type:  feature request| Status:  closed  
  Priority:  normal |  Milestone:  
 Component:  libraries (other)  |Version:  7.2.1   
Resolution:  wontfix|   Keywords:  
  Testcase: |  Blockedby:  
Difficulty: | Os:  Unknown/Multiple
  Blocking: |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown   |  
+---
Changes (by basvandijk):

  * status:  new = closed
  * resolution:  = wontfix


Comment:

 I
 
[https://github.com/basvandijk/aeson/commit/4ee946745573ad4a6da2416e612cd4b94929d36c
 solved it] using both Pedro's `IsRecord` type-level predicate and the
 technique from Simon and Oleg for
 [http://www.haskell.org/haskellwiki/GHC/AdvancedOverlap choosing an
 instance based on a context].

 Although the solution requires some advanced techniques and some extra
 language extensions, I'm happy about it. I also managed to keep the change
 local (only the instance for constructors has changed).

 A tag on [http://www.haskell.org/ghc/docs/latest/html/libraries/ghc-
 prim-0.2.0.0/GHC-Generics.html#t:C C] would make all of this a lot easier
 and doesn't require as much type-level computation. But it would mean
 changing GHC which may not be worth it. So I'm closing the ticket as
 `wontfix`.

 Pedro and Simon, much thanks for your help!

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5499#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] #5506: LLVM AST : needs an LlvmType ctor to represent vectors so that LLVM can generate SIMD instructions

2011-09-27 Thread GHC
#5506: LLVM AST : needs an LlvmType ctor to represent vectors so that LLVM can
generate SIMD instructions
-+--
Reporter:  erikd |   Owner:  dterei 
Type:  task  |  Status:  patch  
Priority:  normal|   Component:  Compiler (LLVM)
 Version:  7.3   |Keywords: 
Testcase:|   Blockedby: 
  Os:  Unknown/Multiple  |Blocking: 
Architecture:  Unknown/Multiple  | Failure:  None/Unknown   
-+--

Comment(by erikd):

 Replying to [comment:6 dterei]:
  As for the vector 11 size example. Is the poor performance when the
 vector isn't length that is multiple of the native vector size?

 This one. It needs to be an integer multiple of the native vector size.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5506#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] #5170: Include LLVM tools for windows

2011-09-27 Thread GHC
#5170: Include LLVM tools for windows
-+--
Reporter:  dterei|Owner:  dterei
Type:  task  |   Status:  new   
Priority:  normal|Milestone:  7.4.1 
   Component:  Compiler (LLVM)   |  Version:  7.0.3 
Keywords:| Testcase:
   Blockedby:|   Difficulty:
  Os:  Unknown/Multiple  | Blocking:
Architecture:  Unknown/Multiple  |  Failure:  Other 
-+--
Changes (by tanakh):

 * cc: tanaka.hideyuki@… (added)


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


[GHC] #5514: bad variable escape analysis when TypeFamilies are enabled

2011-09-27 Thread GHC
#5514: bad variable escape analysis when TypeFamilies are enabled
-+--
Reporter:  dmwit |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Component:  Compiler
 Version:  7.3   |Keywords:  
Testcase:|   Blockedby:  
  Os:  Unknown/Multiple  |Blocking:  
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
-+--
 The following minimal example causes a type error in 7.3.20110927:

 {{{
 {-# LANGUAGE TypeFamilies #-}

 class Foo a where
 foo :: a - a

 instance (Foo a, Foo b) = Foo (a, b) where
 foo = foo' ()

 foo' es = const id (unitId es)

 unitId :: () - ()
 unitId = id
 }}}

 Specifically, the error given is:

 {{{
 test.hs:6:10:
 Couldn't match type `a0' with `(a, b)'
   because type variables `a', `b' would escape their scope
 These (rigid, skolem) type variables are bound by
   the instance declaration
 The following variables have types that mention a0
   foo' :: () - a0 - a0 (bound at test.hs:9:1)
 In the instance declaration for `Foo (a, b)'
 }}}

 This code compiles successfully as recently as 7.3.20110726 (though I
 haven't tested any GHC versions in between these two).

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5514
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] #5515: panic! (the 'impossible' happened) with evil self-referential instance

2011-09-27 Thread GHC
#5515: panic! (the 'impossible' happened) with evil self-referential instance
-+--
Reporter:  andersk   |   Owner:
Type:  bug   |  Status:  new   
Priority:  normal|   Component:  Compiler  
 Version:  7.3   |Keywords:
Testcase:|   Blockedby:
  Os:  Unknown/Multiple  |Blocking:
Architecture:  Unknown/Multiple  | Failure:  Compile-time crash
-+--
 This bit of code escaped from my fingertips:
 {{{
 #!hs
 {-# LANGUAGE ConstraintKinds, FlexibleInstances, TypeFamilies,
 UndecidableInstances #-}
 class ctx (Arg ctx) = Some ctx where type Arg ctx
 instance ctx a = Some ctx where type Arg ctx = a
 }}}
 and crashed GHC master with:
 {{{
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.3.20110927 for x86_64-unknown-linux):
 tcTyVarDetails a{tv aav} [tv]

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

 This causes a similar crash without using ConstraintKinds:
 {{{
 #!hs
 {-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses,
 TypeFamilies, UndecidableInstances #-}
 class C f a
 class C f (Arg f) = Some f where type Arg f
 instance C f a = Some f where type Arg f = a
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5515
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] #5516: Universally quantified GADT context leads to overlapping instance

2011-09-27 Thread GHC
#5516: Universally quantified GADT context leads to overlapping instance
-+--
Reporter:  andersk   |   Owner:   
Type:  bug   |  Status:  new  
Priority:  normal|   Component:  Compiler 
 Version:  7.3   |Keywords:   
Testcase:|   Blockedby:   
  Os:  Unknown/Multiple  |Blocking:   
Architecture:  Unknown/Multiple  | Failure:  GHC rejects valid program
-+--
 This example from comment:8:ticket:2893 works in GHC 7.0.3, but fails in
 GHC master 7.3.20110927:
 {{{
 #!hs
 {-# LANGUAGE GADTs, Rank2Types, FlexibleContexts #-}

 class Foo a where
 foo :: a - String

 instance Foo [b] where
 foo = show . length

 data FooDict a where
 FooDict :: Foo a = FooDict a

 f :: (forall b. FooDict [b]) - String
 f FooDict = foo Hello ++ foo [1, 2, 3]

 use_foo :: String
 use_foo = f FooDict
 }}}
 with this error:
 {{{

 foo.hs:13:28:
 Overlapping instances for Foo [t0]
   arising from a use of `foo'
 Matching instances: instance Foo [b] -- Defined at foo.hs:6:10
 Matching givens (or their superclasses):
   (Foo [b_a])
 bound by a pattern with constructor
FooDict :: forall a. Foo a = FooDict a,
  in an equation for `f'
 at foo.hs:13:3-9
 (The choice depends on the instantiation of `t0')
 In the second argument of `(++)', namely `foo [1, 2, 3]'
 In the expression: foo Hello ++ foo [1, 2, 3]
 In an equation for `f': f FooDict = foo Hello ++ foo [1, 2, 3]
 }}}

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