Re: Syb Renovations? Issues with Data.Generics

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
participants (1)
-
Claus Reinke