[Hs-Generics] Request for code review: Generics for tuple/newtype introspection
Nicolas Frisby
nicolas.frisby at gmail.com
Wed Dec 18 15:26:05 UTC 2013
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 at 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/generics
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/generics/attachments/20131218/521f401a/attachment.html>
More information about the Generics
mailing list