"Data.TupleFields" for review

Samuel Bronson naesten at gmail.com
Thu Aug 9 10:09:49 EDT 2007


On 8/9/07, Henning Thielemann <lemming at henning-thielemann.de> wrote:
>
> On Wed, 8 Aug 2007, Samuel Bronson wrote:
>
> > Hi. I wrote a module and dons suggested I ask you guys for some tips.
> > Here's a good deal of it:
> >
> > module Data.TupleFields where
> >
> > import Data.Tuple
> >
> > class Field1 t f | t -> f where
> >     field1   :: t -> f
> >     field1_u :: (f -> f) -> (t -> t)
> >     field1_s :: f -> (t -> t)
> >     field1_s x = field1_u (const x)
>
> Somewhen in the past I proposed a different usage of the field names of
> Haskell record fields:
>  http://www.haskell.org/haskellwiki/Record_access
>   Translated to the tuple issue, I use only one function of type
>     field1 :: f -> t -> (f,t)
>   which is a combination of 'get' and 'set'.
>   Using this function you can implement a generic 'set', 'get', and
> 'update'. Of course, you can argue that it is bad style to put the
> distinct 'set' and 'get' functionalities into one function. Nevertheless,
> I think 'field1_u' should not be a class method, but there should be a
> separate 'update' function which combines 'field1_s' and 'field1'. I would
> also rename 'field' to 'field_g' or better use 'field1get', 'field1set',
> 'field1update' or 'field1modify' (in analogy to State monad from MTL).

Hmm. How about getField1, setField1, modifyField1 etc.? Or see below.

> type Accessor r a  =  a -> r -> (a, r)
>
> {- | 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

Hmm, these names are a bit *too* close to the ones used in the mtl
;-). Also, are you going to make a package implementing this basic
interface (preferably with names that don't conflict with mtl), or
should I include it in another module in my package?


More information about the Libraries mailing list