hi,

i'm trying to get labelled records working with the current version of HList.

i've got code that looks like:

>{-# language EmptyDataDecls #-}
>module Tst where
>       import Data.HList
>
>       data Foo;    foo     = proxy::Proxy Foo
>       data Bar;   bar    = proxy::Proxy Bar
>       rec1 =
>               foo .=. 1 .*.
>               bar .=. "hello" .*.
>               emptyRecord

which gives me the error:

Tst4.hs:8:2:
    No instance for (HEq (Proxy Foo) (Proxy Bar) HFalse)
      arising from a use of `.*.' at Tst4.hs:(8,2)-(10,12)
    Possible fix:
      add an instance declaration for
      (HEq (Proxy Foo) (Proxy Bar) HFalse)
    In the expression: foo .=. 1 .*. bar .=. "hello" .*. emptyRecord
    In the definition of `rec1':
        rec1 = foo .=. 1 .*. bar .=. "hello" .*. emptyRecord

some discussion on #haskell suggesting importing Label4 and TypeEqGeneric1
but a) that's not possible because both are hidden inside the HList package
and b) even when i get around that restriction, i still get a "No instance
for (TypeCast HFalse HFalse)" error.

thanks,
  rog.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to