Hi,

I get a reproducible crash with ghci 6.4 (ubuntu package version
6.4-4.1ubuntu2).  I am using HList as retrieved yesterday from
http://darcs.haskell.org/HList.

If you need further details please let me know.  I am also happy to
meet on irc/gizmo/skype and talk it through in real-time.

thanks,
Matthias



======================================================================
module Main
where

import IO
import Monad
import List
import Array
import HListPrelude

data T = T Int

class C a
    where f :: C a -> Int

instance C T
    where f (T i) = i

class HList l => CList l

instance CList HNil
instance (C c, CList cs) => CList (HCons c cs)

test :: (CList l) => l -> [Int]
test = hMapOut f

main :: IO ()
main = error ""

======================================================================
   ___         ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |      GHC Interactive, version 6.4, for Haskell 98.
/ /_\\/ __  / /___| |      http://www.haskell.org/ghc/
\____/\/ /_/\____/|_|      Type :? for help.

Loading package base-1.0 ... linking ... done.
Prelude> :load /home/fis/tmp/Main.hs
Compiling FakePrelude      ( 
/home/fis/wiwi/reputation/esim/HList/FakePrelude.hs, interpreted )
Compiling HListPrelude     ( 
/home/fis/wiwi/reputation/esim/HList/HListPrelude.hs, interpreted )
Compiling Main             ( /home/fis/tmp/Main.hs, interpreted )
ghc-6.4: panic! (the `impossible' happened, GHC version 6.4):
        ds_app_type Main.C{tc r5nj} [a{tv a5oO}]

Please report it as a compiler bug to ,
or http://sourceforge.net/projects/ghc/.


> 
======================================================================

Attachment: signature.asc
Description: Digital signature

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

Reply via email to