11

Say I have the following record:

data Rec = Rec {
   field1 :: Int,
   field2 :: Int
}

How do I write the function:

changeField :: Rec -> String -> Int -> Rec
changeField rec fieldName value 

such that I can pass in the strings "field1" or "field2" into the fieldName argument and have it update the associated field? I understand Data.Data and Data.Typeable are what to use here but I can't figure these two packages out.


An example of a library I've seen do this is cmdArgs. Below is an excerpt from a blog posting on how to use this library:

{-# LANGUAGE DeriveDataTypeable #-}
import System.Console.CmdArgs

data Guess = Guess {min :: Int, max :: Int, limit :: Maybe Int} deriving (Data,Typeable,Show)

main = do
    x <- cmdArgs $ Guess 1 100 Nothing
    print x

Now we have a simple command line parser. Some sample interactions are:

$ guess --min=10
NumberGuess {min = 10, max = 100, limit = Nothing}
Chris Stryczynski
  • 30,145
  • 48
  • 175
  • 286
  • 2
    You probably don't want to do this. Have you heard about [lenses](http://stackoverflow.com/questions/5767129/lenses-fclabels-data-accessor-which-library-for-structure-access-and-mutatio)? I think the only way to achieve this would be a hack involving pairing up field names with their argument indices and using `gmapQi` or similar. (You'd need to add `deriving (Typeable, Data)` to your record declaration for this to have any hope of working; it can't be done for arbitrary types.) – ehird Dec 28 '11 at 18:54
  • 1
    I do want to do this. I'd like to create a library where the user can supply a record, and the library can populate the record by parsing some text. The text will contain references to field in the record that I want to set. –  Dec 28 '11 at 19:27
  • It is best to avoid tying the implementation of this user-facing functionality to the internal implementation detail of record field names. I second the lens-based solution @pat suggested; you could automate the creation of `recMap` from record field names with Template Haskell. – ehird Dec 28 '11 at 19:32
  • ehird, please see my updated question. cmdArgs is an example of a library which does what I'm looking for. I don't see the problem. –  Dec 28 '11 at 19:35
  • 1
    Bad choice of example, I'm afraid; cmdargs' implicit mode is one of the most reviled Haskell libraries for its impurity :) Still, if you *do* want to accomplish this, then I still suggest using Template Haskell to generate the `recMap`; it's more flexible and less magical. – ehird Dec 28 '11 at 19:39
  • 1
    This kind of goes agains the Haskell mentality of compile time safety. You should consider using a less dynamic solution – hugomg Dec 28 '11 at 19:43
  • I see. cmdArgs does what it does because it is impure? I was under the impression it does what it does by using Typeable and Data. –  Dec 28 '11 at 19:47
  • @Ana: No, it probably uses the Data instance to achieve that particular functionality, but it's based on a completely impure interface in general, so it's not a very good standard for what good Haskell code should do :) – ehird Dec 28 '11 at 19:58
  • Then I still don't see what the problem is. It is possible to use Typeable and Data to do what I'm looking for, which are standard packages, and not have to use a third party package or use Template Haskell. Sure, it sounds like it side-steps static typing, but I'd like to learn how it can be done so that I have the option to make an informed choice rather than blindly pick the popular option because the other is not the preferred one. –  Dec 28 '11 at 20:03
  • 1
    @Ana: Certainly, but a full answer to a question like this might well entail pointing out that there is likely to be a much better way of achieving the same goal; if someone asked "How can I use `unsafeCoerce` to convert between integral types in Haskell?", it would be remiss not to point out that you should use `fromIntegral` instead; thus my comments. – ehird Dec 28 '11 at 21:17

2 Answers2

10

OK, here's a solution that doesn't use template haskell, or require you to manage the field map manually.

I implemented a more general modifyField which accepts a mutator function, and implemented setField (nee changeField) using it with const value.

The signature of modifyField and setField is generic in both the record and mutator/value type; however, in order to avoid Num ambiguity, the numeric constants in the invocation example have to be given explicit :: Int signatures.

I also changed the parameter order so rec comes last, allowing a chain of modifyField/setField to be created by normal function composition (see the last invocation example).

modifyField is built on top of the primitive gmapTi, which is a 'missing' function from Data.Data. It is a cross between gmapT and gmapQi.

{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE RankNTypes #-}

import Data.Typeable (Typeable, typeOf)
import Data.Data (Data, gfoldl, gmapQi, ConstrRep(AlgConstr),
                  toConstr, constrRep, constrFields)
import Data.Generics (extT, extQ)
import Data.List (elemIndex)
import Control.Arrow ((&&&))

data Rec = Rec {
    field1 :: Int,
    field2 :: String
} deriving(Show, Data, Typeable)

main = do
  let r = Rec { field1 = 1, field2 = "hello" }
  print r
  let r' = setField "field1" (10 :: Int) r
  print r'
  let r'' = setField "field2" "world" r'
  print r''
  print . modifyField "field1" (succ :: Int -> Int) . setField "field2" "there" $ r
  print (getField "field2" r' :: String)

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

data Ti a = Ti Int a

gmapTi :: Data a => Int -> (forall b. Data b => b -> b) -> a -> a
gmapTi i f x = case gfoldl k z x of { Ti _ a -> a }
  where
    k :: Data d => Ti (d->b) -> d -> Ti b
    k (Ti i' c) a = Ti (i'+1) (if i==i' then c (f a) else c a)
    z :: g -> Ti g
    z = Ti 0

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

fieldNames :: (Data r) => r -> [String]
fieldNames rec =
  case (constrRep &&& constrFields) $ toConstr rec of
    (AlgConstr _, fs) | not $ null fs -> fs
    otherwise                         -> error "Not a record type"

fieldIndex :: (Data r) => String -> r -> Int
fieldIndex fieldName rec =
  case fieldName `elemIndex` fieldNames rec of
    Just i  -> i
    Nothing -> error $ "No such field: " ++ fieldName

modifyField :: (Data r, Typeable v) => String -> (v -> v) -> r -> r
modifyField fieldName m rec = gmapTi i (e `extT` m) rec
  where
    i = fieldName `fieldIndex` rec
    e x = error $ "Type mismatch: " ++ fieldName ++
                             " :: " ++ (show . typeOf $ x) ++
                           ", not " ++ (show . typeOf $ m undefined)

setField :: (Data r, Typeable v) => String -> v -> r -> r
setField fieldName value = modifyField fieldName (const value)

getField :: (Data r, Typeable v) => String -> r -> v
getField fieldName rec = gmapQi i (e `extQ` id) rec
  where
    i = fieldName `fieldIndex` rec
    e x = error $ "Type mismatch: " ++ fieldName ++
                             " :: " ++ (show . typeOf $ x) ++
                           ", not " ++ (show . typeOf $ e undefined)
pat
  • 12,587
  • 1
  • 23
  • 52
5

You can build a map from the field names to their lenses:

{-# LANGUAGE TemplateHaskell #-}
import Data.Lens
import Data.Lens.Template
import qualified Data.Map as Map

data Rec = Rec {
    _field1 :: Int,
    _field2 :: Int
} deriving(Show)

$( makeLens ''Rec )

recMap = Map.fromList [ ("field1", field1)
                      , ("field2", field2)
                      ]

changeField :: Rec -> String -> Int -> Rec
changeField rec fieldName value = set rec
    where set = (recMap Map.! fieldName) ^= value

main = do
  let r = Rec { _field1 = 1, _field2 = 2 }
  print r
  let r' = changeField r "field1" 10
  let r'' = changeField r' "field2" 20
  print r''

or without lenses:

import qualified Data.Map as Map

data Rec = Rec {
    field1 :: Int,
    field2 :: Int
} deriving(Show)

recMap = Map.fromList [ ("field1", \r v -> r { field1 = v })
                      , ("field2", \r v -> r { field2 = v })
                      ]

changeField :: Rec -> String -> Int -> Rec
changeField rec fieldName value =
    (recMap Map.! fieldName) rec value

main = do
  let r = Rec { field1 = 1, field2 = 2 }
  print r
  let r' = changeField r "field1" 10
  let r'' = changeField r' "field2" 20
  print r''
pat
  • 12,587
  • 1
  • 23
  • 52
  • 2
    The recMap is precisely the item that I am avoiding. I requires me to specialize for every field, and I would like to do the mapping from string to field dynamically. –  Dec 28 '11 at 19:21