Hello again,

while trying to get HashTable to work both in IO and in ST I
hit the following probable bug in 6.4.20050215.
6.2.1 does accept it, and the #ifdeffed-out version works in
both. When the typesignature is removed 6.4 does accept it.

Cheers,
Remi

{-# OPTIONS -cpp -fglasgow-exts #-}
module Foo where

data HT (ref :: * -> *)
  = HT { kcount :: Int }

#if 1
set_kcount :: Int -> HT ref -> HT ref
#endif

#if 1
set_kcount kc ht = ht{kcount=kc}
#else
set_kcount kcount (HT _) = (HT kcount)
#endif


foo.hs:12:19:
    Couldn't match kind `*' against `* -> *'
    When matching the kinds of `t :: *' and `ref :: * -> *'
      Expected type: HT t
      Inferred type: HT ref
    In the record update: ht {kcount = kc}
Failed, modules loaded: none.

-- 
Nobody can be exactly like me. Even I have trouble doing it.
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to