Re: [GHC] #816: Weird fundep behavior (with -fallow-undecidable-instances)

2006-07-07 Thread GHC
#816: Weird fundep behavior (with -fallow-undecidable-instances)
--+-
  Reporter:  nibro|  Owner:  simonpj
  Type:  bug  | Status:  new
  Priority:  normal   |  Milestone: 
 Component:  Compiler (Type checker)  |Version:  6.4.2  
  Severity:  normal   | Resolution: 
  Keywords:   | Os:  Unknown
Difficulty:  Unknown  |   Architecture:  Unknown
--+-
Changes (by simonpj):

  * owner:  = simonpj

Old description:

 I encounter a strange behavior with functional dependencies. Assume we
 have a class defined as

 class Foo x y | x - y where
  foo :: x - y

 and another class

 class Bar x y where
  bar :: x - y - Int

 and I want to write the instance declaration

 instance (Foo x y, Bar y z) = Bar x z where
  bar x z = bar (foo x) z

 Compiling (with 6.4.2, -fallow-undecidable-instances and -fglasgow-exts)
 I get the following error message:
 error
 Foo.hs:12:0:
 Context reduction stack overflow; size = 21
 Use -fcontext-stack20 to increase stack size to (e.g.) 20
 `$dBar :: Bar y z' arising from use of `bar' at Foo.hs:13:11-13
 [... same thing 20 times ...]
 `$dBar :: Bar y z' arising from use of `bar' at Foo.hs:13:11-13
 `bar :: {bar at [y z]}' arising from use of `bar' at Foo.hs:13
 :11-13
 When trying to generalise the type inferred for `bar'
   Signature type: forall x y z. (Foo x y, Bar y z) = x - z -
 Int
   Type to generalise: x - z - Int
 In the instance declaration for `Bar x z'
 /error

 The declaration requires undecidable instances, but I doubt that the
 problem comes from that. What makes it even more weird is that I can get
 this to compile, and behave as expected, if I do one of a) declare an
 instance of Bar for any type, or
 b) add an explicit type signature (foo x :: y) in the definition of Bar.
 The first seems weird since how could a different, unrelated instance
 affect the typeability of the second instance? The second, b), is weird
 since by the FD x - y we should already know that foo x :: y.

 Same behavior in GHC 6.4.1. Hugs (with -98 +O) accepts the code.

New description:

 I encounter a strange behavior with functional dependencies. Consider this
 program
 {{{
 class Foo x y | x - y where
  foo :: x - y

 class Bar x y where
  bar :: x - y - Int

 instance (Foo x y, Bar y z) = Bar x z where
  bar x z = bar (foo x) z
 }}}
 Compiling (with 6.4.2, -fallow-undecidable-instances and -fglasgow-exts) I
 get the following error message:
 {{{
 Foo.hs:12:0:
 Context reduction stack overflow; size = 21
 Use -fcontext-stack20 to increase stack size to (e.g.) 20
 `$dBar :: Bar y z' arising from use of `bar' at Foo.hs:13:11-13
 [... same thing 20 times ...]
 `$dBar :: Bar y z' arising from use of `bar' at Foo.hs:13:11-13
 `bar :: {bar at [y z]}' arising from use of `bar' at Foo.hs:13:11-
 13
 When trying to generalise the type inferred for `bar'
   Signature type: forall x y z. (Foo x y, Bar y z) = x - z -
 Int
   Type to generalise: x - z - Int
 In the instance declaration for `Bar x z'
 }}}

 The declaration requires undecidable instances, but I doubt that the
 problem comes from that. What makes it even more weird is that I can get
 this to compile, and behave as expected, if I do one of a) declare an
 instance of Bar for any type, or
 b) add an explicit type signature (foo x :: y) in the definition of Bar.
 The first seems weird since how could a different, unrelated instance
 affect the typeability of the second instance? The second, b), is weird
 since by the FD x - y we should already know that foo x :: y.

 Same behavior in GHC 6.4.1. Hugs (with -98 +O) accepts the code.

Comment:

 Great report.  This is a nice simple example of something that has only
 shown up in complicated programs so far.

 Here's what happens.  In the instance decl
 {{{
 instance (Foo x y, Bar y z) = Bar x z where
  bar x z = bar (foo x) z
 }}}
 Ghc solves the following problem:
 {{{
HAS: (Foo x y, Bar y z)
WANTS: (Foo x y', Bar y' z)
 }}}
 The (Foo x y') arises from the call to foo, and the (Bar y' z) from the
 call to bar.

 Now, if we did improvement '''now''', we'd see that y'=y.  But GHC
 doesn't.  For historical reasons, it alternates constraint simplification
 with improvement.  So it sees (Bar y' z).  Yes!  That matches an instance
 declaration!  So it removes tha constraint and adds (Foo x y'', Bar y''
 z).  And then it does that repeatedly.

 The solution is to do improvement more eagerly, which will form part of my
 upcoming house-cleaning operation on constraint solving.

 Short term: you are stuck. But this bug report makes sure I'll fix it in a
 while.

 

Re: [GHC] #811: GHC panics when compiling some mutually recursive modules that export something imported

2006-07-07 Thread GHC
#811: GHC panics when compiling some mutually recursive modules that export
something imported
---+
  Reporter:  guest |  Owner: 
  Type:  bug   | Status:  closed 
  Priority:  normal|  Milestone: 
 Component:  Compiler  |Version:  6.4.2  
  Severity:  critical  | Resolution:  fixed  
  Keywords:| Os:  Linux  
Difficulty:  Unknown   |   Architecture:  powerpc
---+
Changes (by simonpj):

  * resolution:  = fixed
  * status:  new = closed

Comment:

 Good catch.  There was a two-character typo in LoadIface, which I've just
 fixed.

 To work around, if M.hi-boot exports a type T, make sure you define T in M
 .hi-boot; do not import it from elsewhere.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/811
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] #817: internal error: stg_ap_ppp_ret

2006-07-07 Thread GHC
#817: internal error: stg_ap_ppp_ret
-+--
Reporter:  [EMAIL PROTECTED]  |Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone: 
   Component:  Runtime System|  Version:  6.4
Severity:  normal| Keywords: 
  Os:  Linux |   Difficulty:  Unknown
Architecture:  x86   |  
-+--
I'm running a server application using Haskell, and during a stress test
 with repeated connections coming from multiple clients, I got the
 following exception:

 internal error: stg_ap_ppp_ret

 I'll attempt to repeat and get some debug info.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/817
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] #794: System.Random: StdGen's genRange doesn't match its next

2006-07-07 Thread GHC
#794: System.Random: StdGen's genRange doesn't match its next
---+
  Reporter:  [EMAIL PROTECTED]  |  Owner: 
  Type:  bug   | Status:  closed 
  Priority:  normal|  Milestone: 
 Component:  libraries/base|Version:  6.4.2  
  Severity:  normal| Resolution:  fixed  
  Keywords:| Os:  Unknown
Difficulty:  Easy (1 hr)   |   Architecture:  Unknown
---+
Changes (by simonpj):

  * resolution:  = fixed
  * status:  new = closed

Comment:

 Good point.  Rather than try to make {{{Random.stdNext}}} return numbers
 in the full range (which is dodgy, because stdNext is carefully crafted
 code), I changed the {{{genRange}}} method of {{{Random StdGen}}} to
 return the range that {{{stdNext}}} actually delivers.

 The documentation only guarantees a 30-bit range, which is still the case.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/794
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] #818: Uncaught kind error leads to the 'impossible' happening

2006-07-07 Thread GHC
#818: Uncaught kind error leads to the 'impossible' happening
---+
Reporter:  [EMAIL PROTECTED]  |Owner: 
Type:  bug |   Status:  new
Priority:  normal  |Milestone: 
   Component:  Compiler|  Version:  6.4
Severity:  normal  | Keywords: 
  Os:  MacOS X |   Difficulty:  Unknown
Architecture:  Unknown |  
---+
data F c a = F (c a)

 data Val c a = Val (F c) a  --- should produce a kind error but doesn't

 t = Val (F [True]) False --- here we get the impossible

 ---
 dhcp38-137:~/writing/exrep sweirich$ ghci test.hs
___ ___ _
   / _ \ /\  /\/ __(_)
  / /_\// /_/ / /  | |  GHC Interactive, version 6.4, for Haskell 98.
 / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
 \/\/ /_/\/|_|  Type :? for help.

 Loading package base-1.0 ... linking ... done.
 Compiling Main ( test.hs, interpreted )
 ghc-6.4: panic! (the `impossible' happened, GHC version 6.4):
 Unify.unifyTauTyLists: mismatched type lists!

 Please report it as a compiler bug to glasgow-haskell-bugs@haskell.org,
 or http://sourceforge.net/projects/ghc/.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/818
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] #819: Uncaught kind error leads to the 'impossible' happening

2006-07-07 Thread GHC
#819: Uncaught kind error leads to the 'impossible' happening
---+
Reporter:  [EMAIL PROTECTED]  |Owner: 
Type:  bug |   Status:  new
Priority:  normal  |Milestone: 
   Component:  Compiler|  Version:  6.4
Severity:  normal  | Keywords: 
  Os:  MacOS X |   Difficulty:  Unknown
Architecture:  Unknown |  
---+
data F c a = F (c a)

 data Val c a = Val (F c) a  --- should produce a kind error but doesn't

 t = Val (F [True]) False --- here we get the impossible

 ---
 dhcp38-137:~/writing/exrep sweirich$ ghci test.hs
___ ___ _
   / _ \ /\  /\/ __(_)
  / /_\// /_/ / /  | |  GHC Interactive, version 6.4, for Haskell 98.
 / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
 \/\/ /_/\/|_|  Type :? for help.

 Loading package base-1.0 ... linking ... done.
 Compiling Main ( test.hs, interpreted )
 ghc-6.4: panic! (the `impossible' happened, GHC version 6.4):
 Unify.unifyTauTyLists: mismatched type lists!

 Please report it as a compiler bug to glasgow-haskell-bugs@haskell.org,
 or http://sourceforge.net/projects/ghc/.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/819
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] #818: Uncaught kind error leads to the 'impossible' happening

2006-07-07 Thread GHC
#818: Uncaught kind error leads to the 'impossible' happening
-+--
  Reporter:  [EMAIL PROTECTED]  |  Owner: 
  Type:  bug | Status:  new
  Priority:  normal  |  Milestone: 
 Component:  Compiler|Version:  6.4
  Severity:  normal  | Resolution: 
  Keywords:  | Os:  MacOS X
Difficulty:  Unknown |   Architecture:  Unknown
-+--
Old description:

 data F c a = F (c a)

 data Val c a = Val (F c) a  --- should produce a kind error but doesn't

 t = Val (F [True]) False --- here we get the impossible

 ---
 dhcp38-137:~/writing/exrep sweirich$ ghci test.hs
___ ___ _
   / _ \ /\  /\/ __(_)
  / /_\// /_/ / /  | |  GHC Interactive, version 6.4, for Haskell 98.
 / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
 \/\/ /_/\/|_|  Type :? for help.

 Loading package base-1.0 ... linking ... done.
 Compiling Main ( test.hs, interpreted )
 ghc-6.4: panic! (the `impossible' happened, GHC version 6.4):
 Unify.unifyTauTyLists: mismatched type lists!

 Please report it as a compiler bug to glasgow-haskell-bugs@haskell.org,
 or http://sourceforge.net/projects/ghc/.

New description:

 {{{
 data F c a = F (c a)

 data Val c a = Val (F c) a  --- should produce a kind error but doesn't

 t = Val (F [True]) False --- here we get the impossible
 }}}
 Here is a run
 {{{
 dhcp38-137:~/writing/exrep sweirich$ ghci test.hs
___ ___ _
   / _ \ /\  /\/ __(_)
  / /_\// /_/ / /  | |  GHC Interactive, version 6.4, for Haskell 98.
 / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
 \/\/ /_/\/|_|  Type :? for help.

 Loading package base-1.0 ... linking ... done.
 Compiling Main ( test.hs, interpreted )
 ghc-6.4: panic! (the `impossible' happened, GHC version 6.4):
 Unify.unifyTauTyLists: mismatched type lists!

 Please report it as a compiler bug to glasgow-haskell-bugs@haskell.org,
 or http://sourceforge.net/projects/ghc/.
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/818
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] #819: Uncaught kind error leads to the 'impossible' happening

2006-07-07 Thread GHC
#819: Uncaught kind error leads to the 'impossible' happening
-+--
  Reporter:  [EMAIL PROTECTED]  |  Owner:   
  Type:  bug | Status:  closed   
  Priority:  normal  |  Milestone:   
 Component:  Compiler|Version:  6.4  
  Severity:  normal  | Resolution:  duplicate
  Keywords:  | Os:  MacOS X  
Difficulty:  Unknown |   Architecture:  Unknown  
-+--
Changes (by simonpj):

  * resolution:  = duplicate
  * status:  new = closed

Comment:

 Duplicate of #818

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/819
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] #818: Uncaught kind error leads to the 'impossible' happening

2006-07-07 Thread GHC
#818: Uncaught kind error leads to the 'impossible' happening
-+--
  Reporter:  [EMAIL PROTECTED]  |  Owner: 
  Type:  bug | Status:  closed 
  Priority:  normal  |  Milestone: 
 Component:  Compiler|Version:  6.4
  Severity:  normal  | Resolution:  fixed  
  Keywords:  | Os:  MacOS X
Difficulty:  Unknown |   Architecture:  Unknown
-+--
Changes (by simonpj):

  * resolution:  = fixed
  * status:  new = closed

Comment:

 I think this is already fixed in 6.4.1.  Try upgrading

 Foo8.hs:5:19:
 Kind error: `F c' is not applied to enough type arguments
 In the data type declaration for `Val'


 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/818
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] #820: problem compiling a file with top level Template Haskell splice

2006-07-07 Thread GHC
#820: problem compiling a file with top level Template Haskell splice
-+--
Reporter:  guest |Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone:  6.4.2  
   Component:  Template Haskell  |  Version:  6.4.2  
Severity:  normal| Keywords: 
  Os:  Linux |   Difficulty:  Unknown
Architecture:  x86_64 (amd64)|  
-+--
when compiling a file has both the following
   a. a -package option that loads a package with ref to external library,
   b. a top level Template Haskell splice $(...)
 The compiler fails to load the library required by the package properly
 and yields a failed compile due to 'unknown symbol'

 I have a simple example that refers to the JRegex package, which loads
 libpcre.so. The compile fails when compiling UseTH.hs, which refers to the
 package JRegex, and has a top level splice.
 Regex is available with cabalized build setup at
 http://repetae.net/john/computer/haskell/JRegex/
 and is trivial to install.

 It is simple to get around the problem, as 'make separate' does here by
 eliminating the dependency on the package in the file that splices but in
 case someone else has this problem it doesn't hurt to have it documented.

 uname -a =
 Linux server2 2.6.14-1.1656_FC4 #1 Thu Jan 5 22:13:55 EST 2006 x86_64
 x86_64 x86_64 GNU/Linux

 ghc -v =
 Glasgow Haskell Compiler, Version 6.4.2, for Haskell 98, compiled by GHC
 version 6.4.2
 Using package config file: /usr/local/lib/ghc-6.4.2/package.conf
 Using package config file: /home/ben/.ghc/x86_64-linux-6.4.2/package.conf
 Hsc static flags: -static
 *** Deleting temp files
 Deleting:
 ghc-6.4.2: no input files
 Usage: For basic information, try the `--help' option.


 Files = Makefile, Regex.hs, DefineTH.hs, UseTH.hs

 Makefile
 --
 SRCS = Regex.hs UseTH.hs DefineTH.hs

 together : $(SRCS)
 ghc -v --make -package JRegex -fth -lpcre $^


 separate : $(SRCS:.hs=.o)
 ghc -v -package JRegex -package template-haskell -fth -lpcre $^

 # eliminate -package JRegex to get TH splice to work
 UseTH.o : UseTH.hs
 ghc -v -c -fth $

 %.o:%.hs
 ghc -v -c -i. -package JRegex -fth -lpcre $^

 %.hi:   %.o
 @:


 .PHONY: clean
 clean:
 rm *.hi *.o a.out

 Regex.o : UseTH.hi
 UseTH.o : DefineTH.hi



 -
 Regex.hs
 -
 module Main where

 import Text.JRegex
 import Data.Array
 import UseTH

 main = putStrLn hello


 -
 DefineTH.hs
 
 module DefineTH

 where
 import Language.Haskell.TH
 import Language.Haskell.TH.Syntax
 import System

 getEnvExpr :: String - String - ExpQ
 getEnvExpr s alt =
 (runIO $ System.getEnv s `catch` (\e - return alt)) = lift


 
 UseTH.hs
 --
 module UseTH
 where

 import DefineTH

 dir = $(getEnvExpr HOME )



 -
 - run of make together
 -
 ghc -v --make -package JRegex -fth -lpcre Regex.hs UseTH.hs DefineTH.hs
 Glasgow Haskell Compiler, Version 6.4.2, for Haskell 98, compiled by GHC
 version 6.4.2
 Using package config file: /usr/local/lib/ghc-6.4.2/package.conf
 Using package config file: /home/ben/.ghc/x86_64-linux-6.4.2/package.conf
 Hsc static flags: -static
 *** Chasing dependencies:
 Chasing modules from: Regex.hs,UseTH.hs,DefineTH.hs
 Stable modules:
 *** Compiling DefineTH ( DefineTH.hs, interpreted ):
 compile: input file DefineTH.hs
 *** Checking old interface for DefineTH:
 Compiling DefineTH ( DefineTH.hs, DefineTH.o )
 *** Parser:
 *** Renamer/typechecker:
 *** Desugar:
 Result size = 44
 *** Simplify:
 Result size = 40
 Result size = 38
 *** Tidy Core:
 Result size = 38
 *** CorePrep:
 Result size = 46
 *** Stg2Stg:
 *** CodeGen:
 *** CodeOutput:
 *** Assembler
 gcc -I. -c /tmp/ghc28762.s -o DefineTH.o
 *** Deleting temp files
 Deleting: /tmp/ghc28762.s
 *** Compiling UseTH( UseTH.hs, interpreted ):
 compile: input file UseTH.hs
 *** Checking old interface for UseTH:
 Compiling UseTH( UseTH.hs, UseTH.o )
 *** Parser:
 *** Renamer/typechecker:
 *** Desugar:
 *** Simplify:
 *** CorePrep:
 *** ByteCodeGen:
 Loading package base-1.0 ... linking ... done.
 ghc-6.4.2: /usr/local/lib/JRegex-1.0/ghc-6.4.2/HSJRegex-1.0.o: unknown
 symbol `pcre_version'
 *** Deleting temp files
 Deleting: /tmp/ghc28762.s
 Warning: deleting non-existent /tmp/ghc28762.s
 Loading package JRegex-1.0 ... linking ... ghc-6.4.2: unable to load
 package `JRegex-1.0'
 make: *** [together] Error 1





 ---
 --- run of make separate
 

Re: [GHC] #820: problem compiling a file with top level Template Haskell splice

2006-07-07 Thread GHC
#820: problem compiling a file with top level Template Haskell splice
---+
  Reporter:  guest |  Owner:
  Type:  bug   | Status:  new   
  Priority:  normal|  Milestone:  6.4.2 
 Component:  Template Haskell  |Version:  6.4.2 
  Severity:  normal| Resolution:
  Keywords:| Os:  Linux 
Difficulty:  Unknown   |   Architecture:  x86_64 (amd64)
---+
-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/820
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] #821: implicit parameters and type synonyms

2006-07-07 Thread GHC
#821: implicit parameters and type synonyms
---+
Reporter:  [EMAIL PROTECTED]  |Owner: 
Type:  support request |   Status:  new
Priority:  normal  |Milestone: 
   Component:  Compiler|  Version:  6.5
Severity:  normal  | Keywords: 
  Os:  Unknown |   Difficulty:  Unknown
Architecture:  Unknown |  
---+
I wouldn't call this a bug.  But we have various pieces of code at Galois
 that rely on this undocumented (AFAIK)
 feature of GHC:
   Allow implicit parameter constraints in type synonyms and float the
 constraints out when the synonym
   is used.

 So, given the following program:
 {{{
 {-# OPTIONS -fglasgow-exts -fimplicit-params #-}
 module TestIP where

 type PPEnv = Int
 type Doc   = Char

 type PPDoc = (?env :: PPEnv) = Doc

 f :: Char - PPDoc
 f = succ
 }}}

 In ghc 6.4.1 and 6.2.1 it compiles fine.
 In ghc 6.5.20060526 I get this:
 {{{
 src $ ghci ~/TestIP.hs
___ ___ _
   / _ \ /\  /\/ __(_)
  / /_\// /_/ / /  | |  GHC Interactive, version 6.5.20060526, for
 Haskell 98.
 / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
 \/\/ /_/\/|_|  Type :? for help.

 Loading package base-1.0 ... linking ... done.
 [1 of 1] Compiling TestIP   ( /Users/tullsen/TestIP.hs,
 interpreted )

 /Users/tullsen/TestIP.hs:10:4:
 Couldn't match expected type `PPDoc' against inferred type `Char'
 Probable cause: `succ' is applied to too many arguments
 In the expression: succ
 In the definition of `f': f = succ
 Failed, modules loaded: none.
 Prelude
 }}}
 So, my question is
  Is this a bug or the removing of an undocumented 'feature'?

 Thanks,

 Mark

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