[Haskell-cafe] Type Directed Name Resolution

Claus Reinke claus.reinke at talk21.com
Thu Nov 11 13:36:53 EST 2010


> but if improved records are never going to happen

Just to inject the usual comment: improved records have
been here for quite some time now. In Hugs, there is TREX;
in GHC, you can define your own. No need to wait for them.

Using one particular random variation of extensible records 
and labels:

{-# LANGUAGE CPP,TypeOperators,QuasiQuotes #-}

import Data.Label
import Data.Record

data PetOwner = PetOwner deriving Show
data FurnitureOwner = FurnitureOwner deriving Show

-- abstract out labels so that we can bridge backwards-incompatibility
-- http://haskell.org/haskellwiki/Upgrading_packages/Updating_to_GHC_7
#if __GLASGOW_HASKELL__>=700
catOwner   = [l|catOwner|]
chairOwner = [l|chairOwner|]
owner      = [l|owner|]
#else
catOwner   = [$l|catOwner|]
chairOwner = [$l|chairOwner|]
owner      = [$l|owner|]
#endif

-- we can still give unique labels, if we want
oldcat   = catOwner := PetOwner
        :# ()

oldchair = chairOwner := FurnitureOwner
        :# ()

-- but we don't have to, even if the field types differ
newcat   = owner := PetOwner
         :# ()

newchair = owner := FurnitureOwner
         :# ()

main = do
  print $ oldcat #? catOwner
  print $ oldchair #? chairOwner
  print $ newcat #? owner
  print $ newchair #? owner

This variation collected some of the techniques in a sort-of
library, which you can find at 

    http://community.haskell.org/~claus/
    
    in files (near bottom of page)

    Data.Record
    Data.Label
    Data.Label.TH
    
    (there are examples in Data.Record and labels.hs)

That "library" code was for discussion purposes only, there
is no cabal package, I don't maintain it (I just had to update
the code for current GHC versions because of the usual 
non-backward-compatibility issues, and the operator 
precedences don't look quite right). There are maintained
alternatives on hackage (eg, HList), but most of the time
people define their own variant when needed (the basics
take less than a page, see labels.hs for an example).

I'm not aware of any systematic performance studies
of such library-defined extensible records (heavy use
of type-class machinery that could be compile-time,
but probably is partly runtime with current compilers;
the difference could affect whether field access is
constant or not).

It is also worrying that these libraries tend to be defined
in the gap between Hugs' strict (only allow what is known
to be sound) and GHC's lenient (allow what doesn't bite
now) view of type system feature interactions. 

The practical success weighs heavily in favour of GHC's
approach, but I'm looking forward to when the current
give-it-a-solid-basis-and-reimplement-everything
effort in GHC reaches the same level of expressiveness
as the old-style lenient implementation!-)

Claus
 


More information about the Haskell-Cafe mailing list