Syb Renovations? Issues with Data.Generics

Calling all Syb/Data.Generics users!-) I keep running into problems with Data.Generics, mostly because I actually want to use it (no claims that it is the best or final solution, or that other approaches aren't equally in need of support, just that it is the best-supported working approach right now). Some tricky issues are (sometimes against published expectations) solvable, suggesting useful additions to the library, but some seemingly trivial things have me stumped, suggesting (to me, at least;-) a need for improvements either in the library or in its documentation. Part of the reason I'm interested in this now is that Data/Typeable instances seem likely (I hope:-) to be added to the GHC Api, where Thomas Schilling is working on improvements http://hackage.haskell.org/trac/ghc/wiki/GhcApiStatus http://hackage.haskell.org/trac/ghc/wiki/GhcApiAstTraversals also, the old question of porting HaRe to the GHC Api is currently being looked into again, by Chaddaï Fouché, and crucially depends on Syb's generic traversals. As it is still holiday season, it is a bit early for proposal deadlines, but I'd like to start a discussion of Syb/Data.Generics and collect the issues and solutions arising, in the hope of following up with concrete proposals for improvements. To start the discussion, a simple item: 1. inconvenient convenience instances of Data for non-"data" types Data.Generics.Instances defines instances of Data for many types, including some abstract types that don't really fit into the concrete value based model of Data, like 'IO a' and 'a->b'. Those instances give runtime errors for some class methods, and mainly offer faked (no-op) gmap traversals, serving as a convenience/enabler for 'deriving instance Data': http://www.haskell.org/pipermail/generics/2008-June/000346.html A list of the odd instances in Data.Generics.Instances, with examples of their oddities, can be found here: http://www.haskell.org/pipermail/generics/2008-June/000347.html My suggestion is to split this module into two, and stop the implicit import/export of the incomplete instances from Data.Generics. Reactions to this suggestion have been muted so far (Simon PJ was as surprised as I was about the existence of these instances, but has no strong opinion about the issue, Alexey Rodriguez supports the suggestion, Ian Lynagh points out the difficulty of transition), which is one reason why I'll try to move the discussion to libraries@. Pro: - the instances are still available, and only one explicit import away, so 'deriving instance Data' for types containing uninteresting functions is still convenient - the problematic instances are no longer implicitly imported, so applications that don't want these instances can now avoid them completely, or define their own instances - these convenience instances are not just inconvenient for some applications, due to the way intances are handled in Haskell; they actually violate some "natural" invariants like "everything queries every substructure of the specified type", "everywhere applies a transformation at every substructure of matching type" - the situation is similar to Text.Show.Functions, as the convenience instances don't provide the full expected functionality, just barely enough for deriving to get by Cons: - due to the implicit import and use of these instances, there is no obvious transition scheme; it seems that the least painful process would be to make the change without transition/deprecation period and to document the explicit import option [it would be useful to have a way of deprecating instance imports, so that any deriving scheme depending on imports from a deprecated location would trigger a warning, in this case suggesting the new import location] As I said, I'd like to wait until at least the Syb authors are back from holidays before setting any proposal deadlines, but I'd like to invite feedback from Syb users on this and other Syb issues. Here is a preview on other items I'd like to raise later on, please add your own: 2. Data.Generics.Utils Since Data/Typeable are compiler-derivable (in GHC) while other classes like Functor/Traversable/etc are not, it would be useful if generic instances for those other classes could be defined in terms of Data/Typeable. The Uniplate library already does this for its own classes via Data.Generics.PlateData, and it appears that at least Functor is defineable as well (code exists, proof is only informal at this stage, and those invariant violations and runtime errors in the implicitly imported dummy instances from (1) really get in the way): http://www.haskell.org/pipermail/generics/2008-June/000343.html http://www.haskell.org/pipermail/generics/2008-July/000349.html http://www.haskell.org/pipermail/generics/2008-July/000351.html What other classes can be defined in this way? Traversable (traverse) seems very nearly possible, what else? 3. Performance Naive use of Syb traversal schemes can lead to huge performance losses. Experienced users tend to write their own traversal schemes, using Syb's low-level Api directly, but we can take inspiration from some Uniplate/PlateData optimization techniques and generalise them for use with Syb's high-level traversal scheme Api, yielding similar performance gains for everywhere/everything: http://www.haskell.org/pipermail/generics/2008-July/000353.html Another direction that might be worth exploring is to use Maps instead of nested generic extensions to define adhoc-overloaded transformation and queries (I've actually started playing with that, but am currently stuck on GHC ticket #2463). 4. Useability There is probably nothing one can do to make the types of Syb's low-level Api less of a brain hazard, but not all of the stumbling blocks seem to be necessary consequences of the carefully crafted edifice of interactions between nearly polymorphic types, runtime type checks and type reflection. Examples: - there doesn't seem to be a way to get hold of a types' constructors, only of constructor representations, structure scaffolds, and structure generators - the actual domain on which a transformation/query acts is hidden behind the near-polymorphic default type of generic extensions - I can't seem to figure out how to use typeOf1, when the other Syb operations only give me 'forall a . Data a => a'; instead, I seem to be forced to use something like: [ mkTyConApp tyCon (init tyArgs) | not (null tyArgs) ] where (tyCon,tyArgs) = splitTyConApp typeRep - others? What are your personal gripes with Syb/Data/Typeable, and for which of them do you see a chance of addressing them by changing/adding code? Claus

On Mon, Jul 28, 2008 at 07:13:08PM +0100, Claus Reinke wrote:
My suggestion is to split this module into two, and stop the implicit import/export of the incomplete instances from Data.Generics.
I don't think that this is a good idea.
Pro: - the instances are still available, and only one explicit import away, so 'deriving instance Data' for types containing uninteresting functions is still convenient
But suppose you want to make such an instance in a library you write. Then you will import the instance, which means that it will be visible to all users of your library too, so they cannot define their own instance. Nor can they use other libraries that define their own instance. I believe instances really do have to be global.
- the situation is similar to Text.Show.Functions, as the convenience instances don't provide the full expected functionality, just barely enough for deriving to get by
I assumed that the only reason this is in its own module is so that you can have Prelude not export the instance, as H98 requires, but I don't know or can't remember the history behind it. Thanks Ian

My suggestion is to split this module into two, and stop the implicit import/export of the incomplete instances from Data.Generics. I don't think that this is a good idea.
Could you please elaborate on your reasons?
Pro: - the instances are still available, and only one explicit import away, so 'deriving instance Data' for types containing uninteresting functions is still convenient But suppose you want to make such an instance in a library you write. Then you will import the instance, which means that it will be visible to all users of your library too, so they cannot define their own instance. Nor can they use other libraries that define their own instance.
True. But the current situation is even worse: we either get all instances (good and bad) or none, and to get none, we'd have to jump through hoops (not using Data.Generics, but importing its component modules directly; and anyone trying to mix such code with code importing Data.Generics is going to be in trouble). There might well be a better way of making deriving happy, without such nasty side effects, but it will have to start with not having those faulty instances by default.
I believe instances really do have to be global.
Instances are global. The only control we have are over the class we define instances of and the type we define instances for. The instances in question are of a non-local class, for non-local types, so if they are implicitly imported, we're stuck with them. The instances I don't want to be stuck with turn compile-time errors into runtime errors for some methods, and violate nice invariants for other methods. Claus

On Tue, Jul 29, 2008 at 08:27:00PM +0100, Claus Reinke wrote:
My suggestion is to split this module into two, and stop the implicit import/export of the incomplete instances from Data.Generics. I don't think that this is a good idea.
Could you please elaborate on your reasons?
That's what the rest of that e-mail was supposed to be.
True. But the current situation is even worse: we either get all instances (good and bad) or none
I think you should always get all:
I believe instances really do have to be global.
By the way, is there something somewhere describing the alternate instance that you want to define? Thanks Ian

I'd be very excited by Claus or someone else taking charge of worrying about efficiency/API issues in SYB. -- adding other useful common combinators and traversals, tuning for performance, etc. Furthermore, I very much agree that the incomplete instances are a bad idea. They're a hack which makes certain things simpler but makes lots of other things harder/less sound. I can see needing to import them for simplicity's sake in a single project, but I'd consider it very bad form for a library to need them as opposed to going the extra mile and wrapping usage in appropriate newtypes. One of the big problems with programming with Data.Generics is that various partial instances make it a real minefield if one isn't careful, and the more we can do to reduce that, the better. --S

On Tue, Jul 29, 2008 at 08:27:00PM +0100, Claus Reinke wrote:
My suggestion is to split this module into two, and stop the implicit import/export of the incomplete instances from Data.Generics. I don't think that this is a good idea. Could you please elaborate on your reasons? That's what the rest of that e-mail was supposed to be.
You explained why the change would not give as much flexibility as one might think, or at least not as easily, but you didn't explain why you think it is a bad idea to gain at least the flexibility to choose between instance and no instance for the problematic cases.
True. But the current situation is even worse: we either get all instances (good and bad) or none I think you should always get all:
That would be fine if all instances were completely defined. They aren't. So the partial instances are imposed globally and irrevocably, and instead of compiletime type errors, we get runtime errors.
By the way, is there something somewhere describing the alternate instance that you want to define?
That is the whole point, isn't it? The Data framework isn't designed to cope with things like (a->b) or (IO a), so there are no good instances one could define for these types (if anyone can suggest better instances, please do!-). Hence the incomplete instances mixed in with the standard ones in Data.Generics.Instances. Mostly, I don't want those instances at all (the incomplete ones), so that the typechecker will complain if I try to use Data on something it can't really handle. Scenario 1: We want to use deriving Data on types that have components of types (a->b) or (IO a), but we don't care about those components. This is the case for which the incomplete instances are provided. Scenario 2: Any attempt to use Data (a->b) or Data (IO a) indicates an error. If we want to derive Data for complex structures containing those types, we need to define Data instances for the immediately enclosing structures, or wrap those types in newtypes and define Data instances for those. This is the case for which the incomplete instances get in the way. Scenario 3: We want to use deriving Data on types that have components of types (a->b) or (IO a), we do care about what happens in those components. It is surprisingly tricky to come up with sensible Data instances for these types that do anything more than the current dummies, so this scenario isn't as likely as I thought at first. Scenario 4: We want to handle Data for (a->b) or (IO a) differently, depending on context. Unless we can wrap those types in newtypes, this is very nearly impossible, due to the way instances propagate through projects. The status quo supports only (1), and gives a mixture of runtime errors and wrong results for (2). In particular, the type checker does not help us to find the cases we need to cover to keep our programs from "going wrong". With selective import, we can support (1), or get compiletime errors consistently for (2). We cannot usually support both (1) and (2) in one program, but splitting the Instances module so that we can be more selective in imports seems a worthwhile improvement. Claus PS. The situation is not improved by the current reexports of Data.Generics.Instances from unexpected places. I have a package splitting Data.Generics.Instances into Standard and Dubious, and a Data.Generics.Alt that only reexports Standard instances. But as soon as I use this with, eg, an IntMap, I get duplicate instance errors. A quick grep shows that the following re-export all instances (sometimes deliberately, sometimes accidentally, by importing Data.Generics for other reasons): libraries/array/Data/Array.hs -- libraries/base/Data/Generics/Instances.hs libraries/base/Data/Generics.hs libraries/bytestring/Data/ByteString/Internal.hs libraries/bytestring/Data/ByteString/Lazy/Internal.hs libraries/containers/Data/IntMap.hs libraries/containers/Data/IntSet.hs libraries/containers/Data/Map.hs libraries/containers/Data/Set.hs libraries/containers/Data/Tree.hs libraries/haskell-src/Language/Haskell/Syntax.hs libraries/network/Network/URI.hs libraries/packedstring/Data/PackedString.hs libraries/template-haskell/Language/Haskell/TH/Quote.hs libraries/template-haskell/Language/Haskell/TH/Syntax.hs As far as I can see, none of these depends on the incomplete instances, so these instances get re-exported by accident. If Data.Generics.Instances was split into Data.Generics.Instances.Standard and Data.Generics.Instances.Dubious, and if Data.Generics.Alt only reexported the former, those modules could be more selective in their imports and the leaking of instances could be avoided.

On Thu, Jul 31, 2008 at 12:11:28AM +0100, Claus Reinke wrote:
On Tue, Jul 29, 2008 at 08:27:00PM +0100, Claus Reinke wrote:
My suggestion is to split this module into two, and stop the implicit import/export of the incomplete instances from Data.Generics. I don't think that this is a good idea. Could you please elaborate on your reasons? That's what the rest of that e-mail was supposed to be.
You explained why the change would not give as much flexibility as one might think, or at least not as easily, but you didn't explain why you think it is a bad idea to gain at least the flexibility to choose between instance and no instance for the problematic cases.
Ah, I see. There are two reasons why one might not want to have, e.g., an IO instance. The first one is to help the programmer find errors: if your program relies on having the instance then it's probably buggy (modulo the deriving instances thing). I've done a bit of generic programming (although doubtless not as much as others on this list) and haven't found this to be an issue. Note that if you took a correct program without the instance, and added the instance, then the program would still compile. The other one is because you want to define your own instance. Hopefully your instance differs from the existing one in some way (but if it's moved into a different module then it's likely that people will recreate the same empty instance because they don't realise that one already exists). If people start doing this then we will get libraries which cannot be used in the same project. I therefore don't think that we should make it possible for people to do this.
By the way, is there something somewhere describing the alternate instance that you want to define?
That is the whole point, isn't it? The Data framework isn't designed to cope with things like (a->b) or (IO a), so there are no good instances one could define for these types
OK, I think I've missed your point then. I've just reread the message you started this thread with, and you say this:
Pro: - the instances are still available, and only one explicit import away, so 'deriving instance Data' for types containing uninteresting functions is still convenient
- the problematic instances are no longer implicitly imported, so applications that don't want these instances can now avoid them completely, or define their own instances
- these convenience instances are not just inconvenient for some applications, due to the way intances are handled in Haskell; they actually violate some "natural" invariants like "everything queries every substructure of the specified type", "everywhere applies a transformation at every substructure of matching type"
- the situation is similar to Text.Show.Functions, as the convenience instances don't provide the full expected functionality, just barely enough for deriving to get by
Cons: - due to the implicit import and use of these instances, there is no obvious transition scheme; it seems that the least painful process would be to make the change without transition/deprecation period and to document the explicit import option
[it would be useful to have a way of deprecating instance imports, so that any deriving scheme depending on imports from a deprecated location would trigger a warning, in this case suggesting the new import location]
These are supposed to be pros and cons of moving the instances into their own module, as opposed to the status quo, right? If so, the first "pro" isn't a pro at all. Debatably it's a con - it would make it less convenient to derive instance Data for types containing IO etc. For the second one, not having an instance doesn't help a program (although it may help a programmer find his errors, which I agree is a pro), and you say that you can't think what an alternative instance would be. Even if you could, I still think that you shouldn't be able to define an alternative instance, as I said above, so I think that that is a con. The third one is more-or-less "help a programmer find his errors" again, I think? And the fourth one is just an observation, neither a pro or a con. Incidentally, another con is that it means the instances have to be orphan instances. I don't see a benefit to moving the instances to their own module, which outweighs the downsides, in my opinion.
Scenario 2:
Any attempt to use Data (a->b) or Data (IO a) indicates an error. If we want to derive Data for complex structures containing those types, we need to define Data instances for the immediately enclosing structures, or wrap those types in newtypes and define Data instances for those. This is the case for which the incomplete instances get in the way.
How do they "get in the way"? Do you mean the typechecker doesn't tell you which instances you need to define by hand, because deriving worked?
PS. The situation is not improved by the current reexports of Data.Generics.Instances from unexpected places.
Instances are not reexported, instances are global. Not even just within a project, but between every single library on hackage; pick any two libraries, and eventually someone is going to want them in the same program. (That module also contains things like "instance Data Int", so it's not surprising that lots of things need it) Thanks Ian

That is the whole point, isn't it? The Data framework isn't designed to cope with things like (a->b) or (IO a), so there are no good instances one could define for these types
OK, I think I've missed your point then.
I don't seem to have explained it well - I wouldn't expect so much opposition otherwise!-) Perhaps, some concrete code examples will help (see below).
I don't see a benefit to moving the instances to their own module, which outweighs the downsides, in my opinion.
To recap: I'm suggesting to - split the existing Data.Generics.Instances into Data.Generics.Instances.Standard Data.Generics.Instances.Dubious - provide Data.Generics.Alt, which is Data.Generics without Data.Generics.Instances.Dubious
How do they "get in the way"? Do you mean the typechecker doesn't tell you which instances you need to define by hand, because deriving worked?
Okay, I've cobbled together a package with my various code fragments, for discussion purposes only: http://www.cs.kent.ac.uk/~cr3/tmp/syb/syb-utils-0.0.2008.7.30.tar.gz If you install that, and then try examples/Examples.hs, once as it is and once with -DALT, you will directly see the difference between the status quo and my suggested alternative: the former gives a mixture of happily working code, runtime errors and silently wrong results, the latter gives compiletime type errors for those examples that would otherwise go haywire by defaulting to use non-standard instances (tested with ghci 6.9.20080514, code & output below *). Does that help? Claus * you have to try the two alternatives in different ghc invocations, because of a long-standing ghc session bug that accumulates instances over all modules seen. -------------------------------------------- example code {-# LANGUAGE CPP #-} -- {-# OPTIONS_GHC -DALT #-} import Data.Generics.Utils #ifdef ALT import Data.Generics.Alt -- compiletime type errors #else import Data.Generics -- runtime errors, wrong results #endif import qualified Control.Exception as CE(catch) -------------------------------- examples test = do putStrLn "-- traverseData examples" print $ traverseData (Just . not) tuple print $ traverseData (Just . not) list traverseData print tuple >>= print traverseData print list >>= print print $ traverseData id [ Just x | x <- [1..3::Integer] ] print $ traverseData id [ [1..3], [4..6::Integer] ] putStrLn "-- fmapData examples" print $ fmapData not tuple print $ fmapData not list putStrLn "-- fmapData (a->b) (IO a) examples" safely (print $ map (($True) . fmapData not) ([]::[Bool->Bool])) safely (mapM (fmapData not) ([]::[IO Bool]) >>= print) safely (print $ map (($True) . fmapData not) ([const True]::[Bool->Bool])) safely (mapM (fmapData not) ([return True]::[IO Bool]) >>= print) putStrLn "-- everywhere over inconsistent instances examples" print $ everywhere (mkT inc) (return 0 :: Maybe Integer) print $ everywhere (mkT inc) (return 0 :: [] Integer) print =<< everywhere (mkT inc) (return 0 :: IO Integer) print $ everywhere (mkT inc) (return 0 :: (->) () Integer) () where inc = (+1) :: Integer -> Integer tuple = (True,True) list = [True,True] safely m = CE.catch m (putStrLn . ("exception: "++) . show) -------------------------------------------- example output $ ghc -e test Examples.hs -- traverseData examples Just (True,False) Just [False,False] True (True,()) True True [(),()] Just [1,2,3] [[1,4],[1,5],[1,6],[2,4],[2,5],[2,6],[3,4],[3,5],[3,6]] -- fmapData examples (True,False) [False,False] -- fmapData (a->b) (IO a) examples [] [] exception: gunfold exception: gunfold -- everywhere over inconsistent instances examples Just 1 [1] 0 0 $ ghc -DALT -e test Examples.hs Examples.hs:31:33: No instances for (Data (Bool -> Bool), Data (Bool -> Data.Generics.Utils.X)) arising from a use of `fmapData' at Examples.hs:31:33-44 Possible fix: add an instance declaration for (Data (Bool -> Bool), Data (Bool -> Data.Generics.Utils.X)) In the second argument of `(.)', namely `fmapData not' In the first argument of `map', namely `(($ True) . fmapData not)' In the second argument of `($)', namely `map (($ True) . fmapData not) ([] :: [Bool -> Bool])' Examples.hs:32:16: No instances for (Data (IO Bool), Data (IO Data.Generics.Utils.X)) arising from a use of `fmapData' at Examples.hs:32:16-27 Possible fix: add an instance declaration for (Data (IO Bool), Data (IO Data.Generics.Utils.X)) In the first argument of `mapM', namely `(fmapData not)' In the first argument of `(>>=)', namely `mapM (fmapData not) ([] :: [IO Bool])' In the first argument of `safely', namely `(mapM (fmapData not) ([] :: [IO Bool]) >>= print)' Examples.hs:39:12: No instance for (Data (IO Integer)) arising from a use of `everywhere' at Examples.hs:39:12-59 Possible fix: add an instance declaration for (Data (IO Integer)) In the second argument of `(=<<)', namely `everywhere (mkT inc) (return 0 :: IO Integer)' In a stmt of a 'do' expression: print =<< everywhere (mkT inc) (return 0 :: IO Integer) In the expression: do putStrLn "-- traverseData examples" print $ traverseData (Just . not) tuple print $ traverseData (Just . not) list traverseData print tuple >>= print .... Examples.hs:40:12: No instance for (Data (() -> Integer)) arising from a use of `everywhere' at Examples.hs:40:12-64 Possible fix: add an instance declaration for (Data (() -> Integer)) In the second argument of `($)', namely `everywhere (mkT inc) (return 0 :: (->) () Integer) ()' In the expression: print $ everywhere (mkT inc) (return 0 :: (->) () Integer) () In the expression: do putStrLn "-- traverseData examples" print $ traverseData (Just . not) tuple print $ traverseData (Just . not) list traverseData print tuple >>= print ....

Some of you already know, but it seems I forgot to mention this here - my code has moved to a darcs repo, with a little bit of documentation and a README summarizing the issues. See my toolbox for more info: http://www.cs.kent.ac.uk/~cr3/toolbox/haskell/#syb-utils Neil: It turned out to be tricky to recognize nested types at the Data/Typeable level, let alone nested types that really have an infinite set of potential substructure types (which are the ones that break the PlateData optimization). Instead, I just count nesting levels (where nesting means that we encounter the top-level type constructor while exploring its substructure types), and set an arbitrary bound beyond which I assume the nesting to be recursive and fall back to the unoptimized case. You might want to apply something similar to PlateData. Cheers, Claus

Ian Lynagh wrote:
If so, the first "pro" isn't a pro at all. Debatably it's a con - it would make it less convenient to derive instance Data for types containing IO etc.
maybe in those cases of "convenience" we could use a tool like Data.Derive, and make some name to derive with it like "DubiousData". Then the dubious Data instances wouldn't have to be defined/imported. I wonder if it would be possible to have Derive have a "NotSoDubiousData" that somehow figured out whether dubious types were involved and rejected them.. (Admittedly, last I tried, using Derive or DrIFT for a project that wasn't using it already, was much harder than the built-in deriving mechanism) here's an example (which don't know enough to say whether it supports any particular position) : say we have a type data Something a = Something a (IO a) If we want instance (Data a) => Data (Something a) ignoring the IO member but traversing the "a" member, then if we use the normal deriving where we have dubious instances, then (Something (a->b)) is going to be in Data even if it shouldn't be, and it will be easy not to notice. Given how popular polymorphism is in Haskell, I guess this is fairly likely to happen? -Isaac

maybe in those cases of "convenience" we could use a tool like Data.Derive, and make some name to derive with it like "DubiousData". Then the dubious Data instances wouldn't have to be defined/imported. I wonder if it would be possible to have Derive have a "NotSoDubiousData" that somehow figured out whether dubious types were involved and rejected them..
generating instances of a different class might lead to ambiguities/ overlaps in use, but I like the idea of making deriving smarter to get rid of dummy instances. Let me see if I got your idea correctly. data Something a = Something a (IO a) Currently, we have two choices to get 'Data Something': - use naive deriving, for which we'd need to supply both 'Data a' and 'Data (IO a)', with unwanted consequences for the latter - write the Data instance for Something by hand, skipping the 'IO a' component If deriving was only a little bit smarter, we could write: data Something a = Something a {-# Data: skip #-} (IO a) deriving (Data,Typeable) and the deriving mechanism could give us a modified Data instance for Something that doesn't need 'Data (IO a)'. No need for instances we can't really write, and a clear hint in the source code that the 'IO a' component is treated specially (skipped rather than traversed)! I like the idea, Claus

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1
data Something a = Something a {-# Data: skip #-} (IO a)
ultimately, one would want a (1) unified, (2) typed and (3) extensible (by the programmer) treatment of source code annotations. http://java.sun.com/docs/books/jls/third_edition/html/interfaces.html#9.7 best regards, J.W. -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.9 (GNU/Linux) Comment: Using GnuPG with SUSE - http://enigmail.mozdev.org iEYEARECAAYFAkiR4SsACgkQDqiTJ5Q4dm/irQCfVlzLnWFMEIFi9LTN98LBTELL qXQAniX+OpA+aAS0grjG97vYbVkZvAeQ =S+Tv -----END PGP SIGNATURE-----

That is the whole point, isn't it? The Data framework isn't designed to cope with things like (a->b) or (IO a), so there are no good instances one could define for these types (if anyone can suggest better instances, please do!-). Hence the incomplete instances mixed in with the standard ones in Data.Generics.Instances.
Actually, one could try to improve at least the gmapT and related methods, since they are meant to map over immediate subterms: gmapT f fun = f . fun -- instead of gmapT f fun = fun gmapT f io = (return . f) =<< io -- instead of gmapT f io = io (we simply eta-expand until we can get hold of the "subterms", then apply f) While this would be more suitable for some applications of Data, such as everywhere (and everything, if we do the same for gmapQ), it still doesn't give consistent or complete instances of Data for functions or IO. But I thought I'd mention it an example of usefully different instances, rather than usefully absent instances for these types. Claus
participants (5)
-
Claus Reinke
-
Ian Lynagh
-
Isaac Dupree
-
Johannes Waldmann
-
Sterling Clover