
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?