FW: [Template-haskell] FW: [ ghc-Bugs-992199 ] Template crash onexistential types

Simon Peyton-Jones simonpj at microsoft.com
Fri Aug 20 11:37:40 EDT 2004


Second message referred to in my last post...

-----Original Message-----
From: template-haskell-bounces at haskell.org
[mailto:template-haskell-bounces at haskell.org] On Behalf Of Simon
Peyton-Jones
Sent: 19 July 2004 17:51
To: template-haskell at haskell.org
Subject: [Template-haskell] FW: [ ghc-Bugs-992199 ] Template crash
onexistential types


My previous message was about robust-ifying the conversion from:
	TH.Syntax -> HsSyn
but the other direction has very similar problems.  The functions in
DsMeta convert:
	HsSyn -> TH.Syntax
Unfortunately, of course TH does not implement all of GHC's extensions,
so the desugaring can fall over badly.

The right thing to do is presumably to make the desugarer monad support
failure and errors, like the type checker monad does, and fail more
gracefully.

Again, is there anyone who'd be prepared to take this on?

Simon 

-----Original Message-----
From: glasgow-haskell-bugs-bounces at haskell.org
[mailto:glasgow-haskell-bugs-bounces at haskell.org] On Behalf Of
SourceForge.net
Sent: 16 July 2004 10:10
To: noreply at sourceforge.net
Subject: [ ghc-Bugs-992199 ] Template crash on existential types

Bugs item #992199, was opened at 2004-07-16 09:08
Message generated for change (Settings changed) made by mm_aa
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=992199&grou
p_id=8032

Category: Compiler
Group: 6.2.1
Status: Open
Resolution: None
Priority: 5
Submitted By: Mike Aizatsky (mm_aa)
Assigned to: Nobody/Anonymous (nobody)
>Summary: Template crash on existential types

Initial Comment:
Windows XP

D:\Tools\ghc>ghc-6.2.1\bin\ghc.exe -fglasgow-exts foo.hs
ghc.exe: panic! (the `impossible' happened, GHC version 6.2.1):
        deSugar/DsMeta.hs:286: Non-exhaustive patterns in function 
repC



module Foo where

import Language.Haskell.THSyntax

class MyInterface a where
	foo :: a -> Int

data AnyMyInterface = forall a. (MyInterface a) => 
AnyMyInterface a

test =
    do{
        d <- unQ(reifyDecl AnyMyInterface)
      ; print d
      }


----------------------------------------------------------------------

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=992199&grou
p_id=8032
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs at haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
_______________________________________________
template-haskell mailing list
template-haskell at haskell.org
http://www.haskell.org/mailman/listinfo/template-haskell


More information about the template-haskell mailing list