"Data.TupleFields" for review

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 -- Copyright : (c) 2007 Samuel Bronson -- License : BSD3-style -- -- Maintainer : naesten@gmail.com -- Stability : experimental -- Portability : non-portable (multi-param classes, functional dependencies) -- -- -- This module provides tuple field access similar to ML's #1, #2 etc. -- ------------------------------------------------------------------------ {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-} 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) class Field1 t f1 => Field2 t f1 f | t -> f where field2 :: t -> f field2_u :: (f -> f) -> (t -> t) field2_s :: f -> (t -> t) field2_s x = field2_u (const x) class Field2 t f1 f2 => Field3 t f1 f2 f | t -> f where field3 :: t -> f field3_u :: (f -> f) -> (t -> t) field3_s :: f -> (t -> t) field3_s x = field3_u (const x) class Field3 t f1 f2 f3 => Field4 t f1 f2 f3 f | t -> f where field4 :: t -> f field4_u :: (f -> f) -> (t -> t) field4_s :: f -> (t -> t) field4_s x = field4_u (const x) class Field4 t f1 f2 f3 f4 => Field5 t f1 f2 f3 f4 f | t -> f where field5 :: t -> f field5_u :: (f -> f) -> (t -> t) field5_s :: f -> (t -> t) field5_s x = field5_u (const x) class Field5 t f1 f2 f3 f4 f5 => Field6 t f1 f2 f3 f4 f5 f | t -> f where field6 :: t -> f field6_u :: (f -> f) -> (t -> t) field6_s :: f -> (t -> t) field6_s x = field6_u (const x) class Field6 t f1 f2 f3 f4 f5 f6 => Field7 t f1 f2 f3 f4 f5 f6 f | t -> f where field7 :: t -> f field7_u :: (f -> f) -> (t -> t) field7_s :: f -> (t -> t) field7_s x = field7_u (const x) instance Field1 ((,) t1 t2) t1 where field1 ((,) x1 x2) = x1 field1_u f ((,) x1 x2) = (,) (f x1) x2 instance Field2 ((,) t1 t2) t1 t2 where field2 ((,) x1 x2) = x2 field2_u f ((,) x1 x2) = (,) x1 (f x2) instance Field1 ((,,) t1 t2 t3) t1 where field1 ((,,) x1 x2 x3) = x1 field1_u f ((,,) x1 x2 x3) = (,,) (f x1) x2 x3 instance Field2 ((,,) t1 t2 t3) t1 t2 where field2 ((,,) x1 x2 x3) = x2 field2_u f ((,,) x1 x2 x3) = (,,) x1 (f x2) x3 instance Field3 ((,,) t1 t2 t3) t1 t2 t3 where field3 ((,,) x1 x2 x3) = x3 field3_u f ((,,) x1 x2 x3) = (,,) x1 x2 (f x3) The module goes on to define instances for all the tuple types up through (,,,,,,) (7-tuples). Any suggestions?

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). An excerpt with basic functions: 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

On 8/9/07, Henning Thielemann
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?

Henning Thielemann wrote:
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.
I like that style. It reminds me of the zipper pattern, of accessors (or something like that). ...which is more important for more complicated things (Maps?) (Uniplate.) I don't know when I'd want to use a function polymorphic in tuple size - _personally_ I'd rather stick to simpler types and ... probably pattern-matching. It's too bad selectors via pattern-matching take a bit more syntax than (,,this,) unless you're already in a pattern-match location... ( (_,_,this,_) ). Large tuples whose size can change might be better represented with record syntax. So I'm not the target audience of this library :) Isaac

On Thu, 9 Aug 2007, Isaac Dupree wrote:
Henning Thielemann wrote:
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.
I like that style. It reminds me of the zipper pattern, of accessors (or something like that). ...which is more important for more complicated things (Maps?) (Uniplate.)
I don't know when I'd want to use a function polymorphic in tuple size - _personally_ I'd rather stick to simpler types and ... probably pattern-matching.
Me too. I think, I've never used other tuples than pairs and triples. Records are much clearer and safer.
participants (3)
-
Henning Thielemann
-
Isaac Dupree
-
Samuel Bronson