[Haskell-cafe] Alternatives to convoluted record syntax

Stuart Cook scook0 at gmail.com
Thu Jul 3 07:48:57 EDT 2008


On Thu, Jul 3, 2008 at 8:00 PM, Dougal Stanton <dougal at dougalstanton.net> wrote:
> Here's a snippet from the parser for one option (others omitted for clarity):
>
>> options :: [OptDescr (Opts -> Opts)]
>> options =
>>     [ Option "b" ["bus"] (ReqArg busNum "NUM") "Bus number"
>>     , ...
>>     ]
>>   where busNum n os = let b = (query os) { queryBusNumber = Just n }
>>                       in if isBusId n then os { query = b } else os
>
> Variations on that ugliness are repeated four times for other fields.
> Is there an alternative way to change the value of nested fields?

Here's one suggestion, though whether it's less ugly is questionable.
Start with these two handy TH functions:

  -- \f x -> x { field = f (field x) }
  alter :: Name -> Q Exp
  alter field = do
      f <- newName "f"
      x <- newName "x"
      lamE [varP f, varP x] $
          recUpdE (varE x)
              [return (field, AppE (VarE f) (AppE (VarE field) (VarE x)))]

  -- \a x -> x { field = a }
  set :: Name -> Q Exp
  set field = do
      a <- newName "a"
      x <- newName "x"
      lamE [varP a, varP x] $
          recUpdE (varE x)
              [return (field, VarE a)]

Now define busNum as follows:

  busNum n
    | (isBusId n) = $(modify 'query) ($(set 'queryBusNumber) (Just n))
    | otherwise = id

The TH brackets and quotes make it look rather cumbersome, but I think
the intent at least becomes clearer.


Stuart


More information about the Haskell-Cafe mailing list