Hi,

while trying to modify Data.HashTable to support both IO and ST
without simply copying it, 6.4.20050215 again decided it doesn't
like me:

/tmp/test% touch *.hs
/tmp/test% /var/tmp/ghc/bin/ghc -O -c MHashTable.hs
/tmp/test% /var/tmp/ghc/bin/ghc -O --make CompatHashTable.hs
Chasing modules from: CompatHashTable.hs
Skipping  MHashTable       ( ./MHashTable.hs, ./MHashTable.o )
Compiling CompatHashTable  ( CompatHashTable.hs, CompatHashTable.o )
ghc-6.4.20050215: panic! (the `impossible' happened, GHC version 6.4.20050215):
        lookupVers1 MHashTable HT{d}

To trigger it, compilation must actually be performed in two
seperate steps, and the second one must be done using "--make".
"-O" is also a vital ingredient for the panic.

The killing code is attached.

Happy Hacking,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
module CompatHashTable where

import MHashTable (new, HashTable)
import GHC.IOBase (IOArray, IORef)

new' :: IO (HashTable IOArray IORef IO)
new' = new
{-# OPTIONS -fglasgow-exts #-}
module MHashTable ( new, HashTable ) where

import GHC.IOBase   ( IOArray, newIOArray, IORef, newIORef )

class Monad m => MutHash arr ref m | arr -> m, ref -> m
                                   , arr -> ref, ref -> arr where
    newMHArray  :: (Int, Int) -> a -> m (arr Int a)
    newMHRef    :: a -> m (ref a)

instance MutHash IOArray IORef IO where
    newMHArray  = newIOArray
    newMHRef    = newIORef

newtype HashTable arr ref m = HashTable (ref (HT arr ref m))
data HT arr (ref :: * -> *) (m :: * -> *) = HT { dir :: !(arr Int Int) }

new :: (MutHash arr ref m) => m (HashTable arr ref m)
new = do
  dir <- newMHArray (0,42) undefined
  table <- newMHRef HT { dir=dir }
  return (HashTable table)
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to