Difference between revisions of "Record access"

From HaskellWiki
Jump to navigation Jump to search
(Bug and Feature Tracker)
m (link to multi-parameter type class without underscore)
Line 218: Line 218:
 
</haskell>
 
</haskell>
   
It would also be interesting if we could automatically generate a [[multi-parameter_type_class]] for each element name,
+
It would also be interesting if we could automatically generate a [[multi-parameter type class]] for each element name,
 
with a [[functional dependency]] from record type to element type
 
with a [[functional dependency]] from record type to element type
 
which allows us to re-use an element name for multiple record types.
 
which allows us to re-use an element name for multiple record types.

Revision as of 17:42, 12 April 2010

Here some proposal for desugared fine functional record field access for HaskellTwo and above.

{- |
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, StateT)
import qualified Control.Monad.State as State
import Data.Char (ord)

{- |
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

{- | Set many fields at once.

This function could also be used for initialisation of record,
if record value with undefined fields is provided.

Drawback:
Since all types in a list must have the same type,
you can set only values of the same type.
-}
setMany :: [r -> (a, r)] -> r -> r
setMany = flip (foldl (\x f -> snd (f x)))

{- |
This is a general function,
but it is especially useful for setting many values of different type at once.
-}
compose :: [r -> r] -> r -> r
compose = flip (foldl (flip ($)))

{- | Get the value of a field. -}
get :: Accessor r a -> r -> a
get f = fst . f undefined

infixl 9 ^.

{- |
'get' as infix operator.
This lets us write @record^.field^.subfield@
-}
(^.) :: r -> Accessor r a -> a
(^.) = flip get


{- | 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


infixr 9 $%, ^:

{- |
'modify' as infix operator.
This lets us write @record$%field^:subfield^:(1+)@
or @record$%field^:subfield^:(const 1)@.
-}
(^:) :: Accessor r a -> (a -> a) -> (r -> r)
(^:) = modify

{- |
Flipped version of '($)'.
-}
($%) :: a -> (a -> b) -> b
($%) = flip ($)



infixr 9 .:

{- |
Combine an accessor with an accessor to a sub-field.
Speak \"stack\".
-}
(.:) :: Accessor a b -> Accessor b c -> Accessor a c
(.:) f g cNew aOld =
   let (bOld, aNew) = f bNew aOld
       (cOld, bNew) = g cNew bOld
   in  (cOld, aNew)




{- *
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)



{- * Reading records from streams -}

class ReadBin a where
   readBin :: String -> Maybe (a, String)

instance ReadBin Char where
   readBin (c:cs) = Just (c,cs)
   readBin _ = Nothing

instance ReadBin Int where
   readBin (c0:c1:c2:c3:cs) =
      Just (foldl1 (\acc d -> acc*256+d) (map ord [c0,c1,c2,c3]), cs)
   readBin _ = Nothing

type Parser r = (r, String) -> Maybe (r, String)

readField :: ReadBin a => Accessor r a -> Parser r
readField f (r,s) =
   do (x,s') <- readBin s
      return (set f x r, s')

readRecord :: [Parser r] -> Parser r
readRecord ps = flip (foldl (>>=)) ps . Just



{- * 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 accesses -}

{- | 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

exampleInit :: (Char,Int)
exampleInit =
   compose [set first 'b', modify first succ, set second 7]
           (undefined,undefined)
--   setMany [first 'b', second 7] (undefined,undefined)

exampleRead :: Maybe ((Char,Int), String)
exampleRead =
   readRecord
      [readField first, readField second]
      ((undefined,undefined), "c\059\154\202\000")

exampleInfix0 :: Int
exampleInfix0 =
   (('b',7),"hallo")^.first^.second

exampleInfix1 :: ((Char, Int), String)
exampleInfix1 =
   (('b',7),"hallo")$%first^:second^:(1+)

exampleInfix2 :: Int
exampleInfix2 =
   (('b',7),"hallo")^.(first.:second)

exampleInfix3 :: ((Char, Int), String)
exampleInfix3 =
   (('b',7),"hallo")$%(first.:second)^:(1+)

It would also be interesting if we could automatically generate a multi-parameter type class for each element name, with a functional dependency from record type to element type which allows us to re-use an element name for multiple record types.

See also