Extended functionality for record field accessors

Here is some proposal for Haskell 2 1/2 or so: {- | In Haskell 98 the name of a record field is automatically also the name of a function which gets the value of the according field. E.g. if we have @ data Pair a b = Pair {first :: a, second :: b} @ then @ first :: Pair a b -> a second :: Pair a b -> b @ However for setting or modifying a field value we need to use some syntactic sugar, which is often clumsy. @ modifyFirst :: (a -> a) -> (Pair a b -> Pair a b) modifyFirst f r@(Pair {first=a}) = r{first = f a} @ We propose to extend the meaning of the record field names to a function which allows setting, getting and modifying values easily. -} module RecordAccess where import Control.Monad.State (MonadState) import qualified Control.Monad.State as State {- | The access functions we propose, look very similar to those needed for List.mapAccumL (but parameter order is swapped) and State monad. They get the new value of the field and the record and return the old value of the field and the record with the updated field. -} type Accessor r a = a -> r -> (a, r) {- * Access helper functions, these are similar to State methods and should be in Prelude -} {- | Set the value of a field. -} set :: Accessor r a -> a -> r -> r set f x = snd . f x {- | Get the value of a field. -} get :: Accessor r a -> r -> a get f = fst . f undefined {- | Transform the value of a field by a function. -} modify :: Accessor r a -> (a -> a) -> (r -> r) modify f g rOld = let (a,rNew) = f (g a) rOld in rNew {- * Access helper functions in a State monad. -} setState :: MonadState r m => Accessor r a -> a -> m () setState f x = State.modify (set f x) getState :: MonadState r m => Accessor r a -> m a getState f = State.gets (get f) modifyState :: MonadState r m => Accessor r a -> (a -> a) -> m () modifyState f g = State.modify (modify f g) {- * Example accessors for the pair type -} {- | Access to the first value of a pair. -} first :: Accessor (a,b) a first xNew (xOld,y) = (xOld, (xNew,y)) {- | Access to the second value of a pair. -} second :: Accessor (a,b) b second yNew (x,yOld) = (yOld, (x,yNew)) {- * Example accessors for the pair type -} {- | Example of using 'set', 'get', 'modify'. -} example :: Int example = get second $ modify second succ $ set first 'a' $ ('b',7) exampleState :: State.State (Char,Int) Int exampleState = do setState first 'a' modifyState second succ getState second
participants (1)
-
Henning Thielemann