Just another wild idea which I might find useful, but is more like
refactoring, is to convert the fields of a record to get/set type-classes,
and refactor all usages of those fields.

you could use a preprocessor (DrIFT, Data.Derive) to derive the instances, but you need to share the class declarations between all client modules.

-------------------
data Person = Person { name :: String, age :: Float }

main = print $ name p ++ " is " ++ show (age p) ++ " years old"
where p = Person { name = "Homer", age = 41 }
-------------------
..

alternatively, you could generalise this a bit, so that there is only one class for all combinations of records, fields, and field value types, and
then generalise it further so that you only need one pair of instances
to define selection and update for all records. that kind of operates at
the borders of the language, so you lose portability (the nicest version
is ghc-only; nearly all language extensions used are also supported
by hugs, but with a slightly different interpretation). you'd still need to share the label types between all client modules.

claus

----------------------------------------------------------
{-# OPTIONS_GHC -fallow-undecidable-instances #-}
{-# OPTIONS_GHC -fallow-overlapping-instances #-}
{-# OPTIONS_GHC -fglasgow-exts #-}

infixl ?
infixr <:,:<

------------------- poor man's records

-- record extension -- (ghc only: infix constructor; for hugs, use (,) instead)
data fieldValue :< record = fieldValue :< record

-- field selection (?) and update (<:)
-- needs overlapping instances to recurse down record extensions
-- for hugs: drop the functional dependency, use more type annotations
class Has field value record | field record -> value where
   (?)  :: record -> field -> value
   (<:) :: (field,value) -> record -> record

-- if the first field matches, we're done
instance Has field value ((field,value) :< record) where
 ((_f,v) :< _) ?  f            = v
 (f,v)        <: ((_f,_) :< r) = ((f,v) :< r)

-- otherwise, try again, with the remaining record
instance Has field value record => Has field value ((f,v) :< record) where
 ((f',v') :< r) ?  f             = r ? f
 (f,v)         <: ((f',v') :< r) = ((f',v') :< ( (f,v)<:r ) )

-- some field labels
data Name = Name
data Age  = Age

------------------- a generic version, no separate Person type or instances

type Person1 = (Name,String) :< (Age,Float) :< ()

homer :: Person1
homer = (Name,"Homer") :< (Age,41) :< ()

test1 = print $ homer?Name ++ " is " ++ show(homer?Age) ++ " years old"

------------------- a more down-to-earth version, closer to the original

data Person = Person String Float

instance Has Name String Person where
   (Person name age) ?  Name             = name
   (Name,newName)   <: (Person name age) = Person newName age

instance Has Age Float Person where
   (Person name age) ?  Age              = age
   (Age,newAge)     <: (Person name age) = Person name newAge

defaultPerson = Person "" 0

homer2 = (Name,"Homer2") <: (Age,42::Float) <: defaultPerson

test2 = print $ homer2?Name ++ " is " ++ show(homer2?Age::Float) ++ " years old"

-------------------

main = test1 >> test2



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

Reply via email to