Request for code review: Generics for tuple/newtype introspection

(Jeremy's announcements and the occasional spam is meagre fare. I'm showing this list some love ;-) I asked a question on the cafe, starting here: http://www.haskell.org/pipermail/haskell-cafe/2013-October/111133.html and got some very helpful answers. Thank you. Only after that did I realise that I'd asked the wrong questions. I now have something that works (using Generics), but the types are scary (especially the instance constraints). John did warn me: "The types look bigger [than Data/Typeable], but the functions are probably simpler to grok. And once you start using generics the types get much easier to read." I'm looking for a little clarification of what value of "easier" I should expect. What am I trying to do? * As input have a tuple of newtypes: someTuple = (FooD 7, FooD2 True, FooD3 'X') (Think of it as a row in a databse table.) * As output I want a list of tuples of newtypes, each tuple describing an element: [(AttrAttr FooT. AttrBasedOn Int), (AttrAttr FooT2, AttrBasedOn Bool), (AttrAttr FooT3, AttrBasedOn Char)] (Think of this as the column specs for the database table. AttrAttr and AttrBasedOn are newtypes.) * The input tuple could have zero, one, two or more elements. * The elements could be newtypes or data with a single constructor and single based-on type. * Note that the tuples of the output also match this pattern. So I want to recurse inside the constructors, but only to a controlled depth. At first, I tried doing this with Data's gunfold. But in: newtype BarT = BarD alpha deriving (Data, ...) `alpha` is required to be in Data (and so through all its sub-constructors), and that's too stringent a constraint on the users of my package. Also some (base/abstract) types aren't in Data, especially TypeRep: newtype AttrBasedOn = AttrBasedOn TypeRep deriving (Data, ...) Then I turned to deriving Generic, which only requires Typeable of the based-on types. I've tried to follow the pattern in Generic.Deriving.Base and Generic.Deriving.ConNames. (Those are great examples! Pity that they don't seem to be pointed to from the wiki.) But I don't want to descend uniformly through the structures. So is the following appropriate?: {-# LANGUAGE KindSignatures, DataKinds, MultiParamTypeClasses, TypeFamilies, RankNTypes, FlexibleInstances, UndecidableInstances, PolyKinds, FlexibleContexts, FunctionalDependencies, OverlappingInstances, ScopedTypeVariables, NoMonomorphismRestriction, TupleSections, TypeOperators, DeriveDataTypeable, DeriveGeneric, DefaultSignatures #-} module TupleAttrGeneric where import Data.Typeable import GHC.Generics -- wrapper function tupToAttribs :: (Generic a, Rep a ~ (M1 D t1 (M1 C t3 t4)), BodyToAttribs t4 ) => a -> [(AttrAttrib, AttrBasedOn)] tupToAttribs x = map (\(xa, xd, xb) -> (AttrAttrib xa, AttrBasedOn xb)) $ bodyToAttribs body where (M1 (M1 body)) = from x -- worker class/method class BodyToAttribs f where bodyToAttribs :: f a -> [(TypeRep, String, TypeRep)] -- instance for empty tuple `()` instance BodyToAttribs U1 where bodyToAttribs _ = [] -- instance for a newtype element instance (Typeable t1, Generic t1, Rep t1 ~ (M1 D t1' (M1 C t3' (M1 S t4' (K1 t5' t6')))), Constructor t3', Typeable t6' ) => BodyToAttribs (M1 S t (K1 r t1)) where bodyToAttribs (M1 (K1 x)) = [(typeOf x, conName from2, typeOf xb)] where (M1 from2) = from x (M1 (M1 (K1 xb))) = undefined `asTypeOf` from2 -- instance for the products of elements instance (BodyToAttribs f, BodyToAttribs g) => BodyToAttribs (f :*: g) where bodyToAttribs (_ :: (f :*: g) a) = bodyToAttribs (undefined :: f a) ++ bodyToAttribs (undefined :: g a) Questions: * These pile-ups of types (M1 D ... (M1 C ... (...))) seem hairy. Is that the best way to control the depth of recursion? * The suggestion from John Lato (see gist from his message http://www.haskell.org/pipermail/haskell-cafe/2013-October/111139.html ) uses a different style for the class types, avoiding the mysterious unbound typevar class GConName a where getConName :: a -> String -- cp: class ... f where ... :: f a -> String Are there places where one or other is more suitable? (I did try John's style at first, but the constraints got uglier.) * The explicit data constructors in the pattern matching are a bit temperamental w.r.t. undefined values. (Specifically, my instance for (:*:) was crashing.) Should I use dummy `_` patterns throughout? (Then the type annotations are monsters!) Thank you AntC

Hi AntC, On Fri, Dec 13, 2013 at 12:04 AM, Anthony Clayden < anthony_clayden@clear.net.nz> wrote:
Questions: * These pile-ups of types (M1 D ... (M1 C ... (...))) seem hairy. Is that the best way to control the depth of recursion?
I think I would define a generic function |typeOfRecord :: a -> TypeRep|, which expects a newtype |a| and returns the |TypeRep| of its argument. Then I'd use that function instead of your call to |from| expecting to match on |M1 (M1 (M1 (K1 x)))|. I'd define that function as a regular generic consumer (like generic show), and give runtime errors for unexpected values (such as sums, or products, as we don't expect those in newtypes). The advantage of the "hairy types" you have right now is that these would be (obscure) compile-time errors.
* The suggestion from John Lato (see gist from his message http://www.haskell.org/pipermail/haskell-cafe/2013-October/111139.html ) uses a different style for the class types, avoiding the mysterious unbound typevar
class GConName a where getConName :: a -> String -- cp: class ... f where ... :: f a -> String
Are there places where one or other is more suitable? (I did try John's style at first, but the constraints got uglier.)
Perhaps this is more or less what I suggest above?
* The explicit data constructors in the pattern matching are a bit temperamental w.r.t. undefined values. (Specifically, my instance for (:*:) was crashing.) Should I use dummy `_` patterns throughout? (Then the type annotations are monsters!)
I don't see why you need |undefined| at all. Unless you are calling |tupToAttribs| with |undefined|; is that the case? Else, your generic function can just pattern-match on |a :*: b| on the product case, for example. Cheers, Pedro
Thank you AntC
_______________________________________________ Generics mailing list Generics@haskell.org http://www.haskell.org/mailman/listinfo/generics

José Pedro Magalhães
writes:
Thanks Pedro,
On Fri, Dec 13, 2013 at 12:04 AM, Anthony Clayden wrote:
Questions: * These pile-ups of types (M1 D ... (M1 C ... (...))) seem hairy. Is that the best way to control the depth of recursion?
... The advantage of the "hairy types" you have right now is that these would be (obscure) compile-time errors.
OK. For this functionality, I prefer compile-time fail to run-time.
* The explicit data constructors in the pattern matching are a bit temperamental w.r.t. undefined values. ...
I don't see why you need |undefined| at all. Unless you are calling |tupToAttribs| with |undefined|; is that the case?
Yes: a relation (aka database table) could be empty, in which case I have only the type of its tuple, no value. (And actually, for a bit of background, this was the main point of the exercise: I am in debate on another forum about whether a relation needs a "heading" -- whose main purpose seems to be to deliver the attributes and their based-on types even when the relation (body) is empty. (The counter-argument is along the lines: how can a non-existent value have a type?) I'm claiming that you don't need a "heading", because you can reify the schema from the tuple type -- even if you don't have a tuple. And I now have a function to prove it, thank you Generics!) Cheers AntC

Disclaimer: I didn't read all of the previous emails. Does this do what you need? http://lpaste.net/97165 I'm on GHC 7.4 at the moment, but I think this will work with later versions. HTH. On Thu, Dec 12, 2013 at 5:04 PM, Anthony Clayden < anthony_clayden@clear.net.nz> wrote:
(Jeremy's announcements and the occasional spam is meagre fare. I'm showing this list some love ;-)
I asked a question on the cafe, starting here: http://www.haskell.org/pipermail/haskell-cafe/2013-October/111133.html and got some very helpful answers. Thank you. Only after that did I realise that I'd asked the wrong questions.
I now have something that works (using Generics), but the types are scary (especially the instance constraints).
John did warn me: "The types look bigger [than Data/Typeable], but the functions are probably simpler to grok. And once you start using generics the types get much easier to read."
I'm looking for a little clarification of what value of "easier" I should expect.
What am I trying to do? * As input have a tuple of newtypes:
someTuple = (FooD 7, FooD2 True, FooD3 'X')
(Think of it as a row in a databse table.)
* As output I want a list of tuples of newtypes, each tuple describing an element:
[(AttrAttr FooT. AttrBasedOn Int), (AttrAttr FooT2, AttrBasedOn Bool), (AttrAttr FooT3, AttrBasedOn Char)]
(Think of this as the column specs for the database table. AttrAttr and AttrBasedOn are newtypes.)
* The input tuple could have zero, one, two or more elements. * The elements could be newtypes or data with a single constructor and single based-on type. * Note that the tuples of the output also match this pattern.
So I want to recurse inside the constructors, but only to a controlled depth.
At first, I tried doing this with Data's gunfold. But in:
newtype BarT = BarD alpha deriving (Data, ...)
`alpha` is required to be in Data (and so through all its sub-constructors), and that's too stringent a constraint on the users of my package. Also some (base/abstract) types aren't in Data, especially TypeRep:
newtype AttrBasedOn = AttrBasedOn TypeRep deriving (Data, ...)
Then I turned to deriving Generic, which only requires Typeable of the based-on types.
I've tried to follow the pattern in Generic.Deriving.Base and Generic.Deriving.ConNames. (Those are great examples! Pity that they don't seem to be pointed to from the wiki.)
But I don't want to descend uniformly through the structures. So is the following appropriate?:
{-# LANGUAGE KindSignatures, DataKinds, MultiParamTypeClasses, TypeFamilies, RankNTypes, FlexibleInstances, UndecidableInstances, PolyKinds, FlexibleContexts, FunctionalDependencies, OverlappingInstances, ScopedTypeVariables, NoMonomorphismRestriction, TupleSections, TypeOperators, DeriveDataTypeable, DeriveGeneric, DefaultSignatures #-}
module TupleAttrGeneric where
import Data.Typeable import GHC.Generics
-- wrapper function
tupToAttribs :: (Generic a, Rep a ~ (M1 D t1 (M1 C t3 t4)), BodyToAttribs t4 ) => a -> [(AttrAttrib, AttrBasedOn)] tupToAttribs x = map (\(xa, xd, xb) -> (AttrAttrib xa, AttrBasedOn xb)) $ bodyToAttribs body where (M1 (M1 body)) = from x
-- worker class/method
class BodyToAttribs f where bodyToAttribs :: f a -> [(TypeRep, String, TypeRep)]
-- instance for empty tuple `()` instance BodyToAttribs U1 where bodyToAttribs _ = []
-- instance for a newtype element instance (Typeable t1, Generic t1, Rep t1 ~ (M1 D t1' (M1 C t3' (M1 S t4' (K1 t5' t6')))), Constructor t3', Typeable t6' ) => BodyToAttribs (M1 S t (K1 r t1)) where bodyToAttribs (M1 (K1 x)) = [(typeOf x, conName from2, typeOf xb)] where (M1 from2) = from x (M1 (M1 (K1 xb))) = undefined `asTypeOf` from2
-- instance for the products of elements instance (BodyToAttribs f, BodyToAttribs g) => BodyToAttribs (f :*: g) where bodyToAttribs (_ :: (f :*: g) a) = bodyToAttribs (undefined :: f a) ++ bodyToAttribs (undefined :: g a)
Questions: * These pile-ups of types (M1 D ... (M1 C ... (...))) seem hairy. Is that the best way to control the depth of recursion?
* The suggestion from John Lato (see gist from his message http://www.haskell.org/pipermail/haskell-cafe/2013-October/111139.html ) uses a different style for the class types, avoiding the mysterious unbound typevar
class GConName a where getConName :: a -> String -- cp: class ... f where ... :: f a -> String
Are there places where one or other is more suitable? (I did try John's style at first, but the constraints got uglier.)
* The explicit data constructors in the pattern matching are a bit temperamental w.r.t. undefined values. (Specifically, my instance for (:*:) was crashing.) Should I use dummy `_` patterns throughout? (Then the type annotations are monsters!)
Thank you AntC
_______________________________________________ Generics mailing list Generics@haskell.org http://www.haskell.org/mailman/listinfo/generics

Nicolas Frisby
writes: Disclaimer: I didn't read all of the previous emails. Does this do what you need?
I'm on GHC 7.4 at the moment, but I think this will work with later versions.
HTH.
Thank you Nicolas (and yes it works on GHC 7.6). It does look 'cleaner' than the version I posted. But I still see plenty of pileups of (type and data) constructors. However, perhaps it looks 'cleaner' because it doesn't work in the corner cases you could have seen discussed in the previous emails? * There's no instance for the unit tuple `toAttrs ()` -- that's easily fixed: instance ToAttrsR U1 where toAttrsR _ = [] * It crashes '*** Exception: Prelude.undefined' when toAttrs' argument is undefined. I tried a quick fix to the (:*:) instance, similar to my version, but that wasn't enough. * (And a minor point: I wanted to be able to go feed toAttrs' output tuple into itself. -- that's fixable easily enough. My version for a bonus also grabbed the newtype's data constructor. -- that's also fixable, I think.) AntC

For the "minor point", you'd like for example the following equivalence (modulo decomposing the Attr type)? toAttrs (FooD 7,BarD True,BazD 'X') == (Attr FooT Int,Attr BarT Bool,Attr BazT Char) If I understood correctly, take a look at the most recent edit of http://lpaste.net/97165 The code gets hairier, but you can now say
example = let (a,_,_) = toAttrs (FooD 7,BarD True,BazD 'X') in a
If you do not specify the "container type" of the result (the pattern
suffices in my example), there will be a type-error. Loosening that
requirement would require a mapping that includes
f a b goes to f Attr Attr where for example f = (,)
f a b c goes to f Attr Attr Attr where for example f = (,,)
f a b c d goes to f Attr Attr Attr Attr where for example f = (,,,)
and so on
But I don't know how to specify such a general one, since all (instances
of) tuple types are distinct types that are not formally related to one
another within the GHC type system.
So:
1) Have I understood your specification correctly?
2) Other experts: is there safe trickery to generally specify this map? I
think it might actually be doable in 7.4, but as far as I know, that was
accidental generally-unsound functionality that was removed in 7.6+.
HTH also.
On Fri, Dec 20, 2013 at 1:44 AM, AntC
Nicolas Frisby
writes: Disclaimer: I didn't read all of the previous emails. Does this do what you need?
I'm on GHC 7.4 at the moment, but I think this will work with later versions.
HTH.
Thank you Nicolas (and yes it works on GHC 7.6).
It does look 'cleaner' than the version I posted. But I still see plenty of pileups of (type and data) constructors.
However, perhaps it looks 'cleaner' because it doesn't work in the corner cases you could have seen discussed in the previous emails?
* There's no instance for the unit tuple `toAttrs ()` -- that's easily fixed:
instance ToAttrsR U1 where toAttrsR _ = []
* It crashes '*** Exception: Prelude.undefined' when toAttrs' argument is undefined. I tried a quick fix to the (:*:) instance, similar to my version, but that wasn't enough.
* (And a minor point: I wanted to be able to go feed toAttrs' output tuple into itself. -- that's fixable easily enough. My version for a bonus also grabbed the newtype's data constructor. -- that's also fixable, I think.)
AntC
_______________________________________________ Generics mailing list Generics@haskell.org http://www.haskell.org/mailman/listinfo/generics

Nicolas Frisby
writes:
For the "minor point", you'd like for example the following equivalence (modulo decomposing the Attr type)? ...
Thanks Nicolas No, I do want a list result. it's a different list element I want. So I can go: toAttrs (undefined `asTypeOf` head (toAttrs (FooD 7, ...))) (Compare: typeOf $ typeOf ... The applicable Relational Theory here is that any data structure can be represented as a Set (List) of tuples, each tuple element being a Name with value of some type. And since that applies for _any_ data structure, it must also apply for the structure of structures.) So instead of returning Attr: data Attr = Attr TypeRep TypeRep deriving (Show) Return a tuple of: newtype AttrAttrib = AttrAttrib TypeRep deriving (Show, Typeable, Generic) newtype AttrBasedOn = AttrBasedOn TypeRep deriving (Show, Typeable, Generic) toAttrs :: (Generic product,ToAttrsR (Rep product)) => product -> [(AttrAttrib, AttrBasedOn)] toAttrs = map (\(Attr a b) -> (AttrAttrib a, AttrBasedOn b)) . toAttrsR . from
So:
1) Have I understood your specification correctly?
No, but I've learnt something more about the power of Generics.
2) Other experts: is there safe trickery to generally specify this map? I think it might actually be doable in 7.4, but as far as I know, that was accidental generally-unsound functionality that was removed in 7.6+.

Ah. I took "feed toAttrs' output tuple into itself" too literally.
Good luck to you.
On Sat, Dec 21, 2013 at 2:21 AM, AntC
Nicolas Frisby
writes: For the "minor point", you'd like for example the following equivalence (modulo decomposing the Attr type)? ...
Thanks Nicolas No, I do want a list result. it's a different list element I want. So I can go:
toAttrs (undefined `asTypeOf` head (toAttrs (FooD 7, ...)))
(Compare: typeOf $ typeOf ... The applicable Relational Theory here is that any data structure can be represented as a Set (List) of tuples, each tuple element being a Name with value of some type. And since that applies for _any_ data structure, it must also apply for the structure of structures.)
So instead of returning Attr: data Attr = Attr TypeRep TypeRep deriving (Show)
Return a tuple of:
newtype AttrAttrib = AttrAttrib TypeRep deriving (Show, Typeable, Generic) newtype AttrBasedOn = AttrBasedOn TypeRep deriving (Show, Typeable, Generic)
toAttrs :: (Generic product,ToAttrsR (Rep product)) => product -> [(AttrAttrib, AttrBasedOn)] toAttrs = map (\(Attr a b) -> (AttrAttrib a, AttrBasedOn b)) . toAttrsR . from
So:
1) Have I understood your specification correctly?
No, but I've learnt something more about the power of Generics.
2) Other experts: is there safe trickery to generally specify this map? I think it might actually be doable in 7.4, but as far as I know, that was accidental generally-unsound functionality that was removed in 7.6+.
_______________________________________________ Generics mailing list Generics@haskell.org http://www.haskell.org/mailman/listinfo/generics
participants (4)
-
AntC
-
Anthony Clayden
-
José Pedro Magalhães
-
Nicolas Frisby