
It seems that a couple of modules in HList libraries didn't have enough LANGUAGE pragmas (in one case, GHC 6.8.3 started to require ScopedTypeVariables where the previous version of GHC did not). Cabal and OOHaskell supply all needed extensions on the command line, and so see no problems. I have corrected the pragmas, in http://darcs.haskell.org/HList You example indeed requires three more imports. In addition, if you import MakeLables and enable TemplateHaskell extension, you can define labels in a simpler way, for example $(label "varX") $(label "getX") The complete example follows. Also, the following file http://darcs.haskell.org/OOHaskell/OCamlTutorial.hs might possibly serve as a quite detailed example of extensible records. As the name of the file indicates, it is the OCaml Object tutorial (part of the OCaml documentation), only implemented in Haskell. {-# LANGUAGE EmptyDataDecls, TemplateHaskell #-} module Tst where import Data.HList import Data.HList.Label4 import Data.HList.TypeEqGeneric1 import Data.HList.TypeCastGeneric1 import Data.HList.MakeLabels data Foo; foo = proxy::Proxy Foo data Bar; bar = proxy::Proxy Bar rec1 = foo .=. 1 .*. bar .=. "hello" .*. emptyRecord -- Ralf likes this style rec2 = foo .=. 1 .*. bar .=. "hello" .*. emptyRecord t1 = rec2 # bar -- "hello" -- inferred foosel :: (HasField (Proxy Foo) r v) => r -> v foosel x = x # foo t2 = foosel rec1 -- 1 $(label "varX") $(label "getX") $(label "moveX") rec3 = varX .=. True .*. rec2 t4 = rec3 # varX -- True