Hello,
I understand that with the proposed base package breakup [1], SYB will be
moved to a separate package. But I still don't know how this will reflect on
the development of the library. In particular:
1) Where is the source code going to be hosted? Here in Utrecht we currently
have a repository with several (cabalized) generic programming libraries,
SYB included. But maybe SYB will stay in the same repository as GHC?
2) Can development proceed independently of GHC, i.e. can a new version of
SYB be released without a new version of GHC?
3) How does the separation affect the automatic instance deriving mechanism?
Thanks,
Pedro
[1] http://hackage.haskell.org/trac/ghc/ticket/1338
On Tue, Aug 5, 2008 at 19:40, Ian Lynagh <igloo(a)earth.li> wrote:
> On Tue, Aug 05, 2008 at 04:46:50PM +0200, Sean Leather wrote:
> >
> > I think SYB should be extracted from 'base' into a package.
>
> I'll be sending a message about this soon.
>
>
> 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
....
Hello all,
This message focuses on a problem Claus mentioned before:
> One other thing I meant to ask was about procedure,
> given that Syb is currently in base and hence under the
> library modification process. How is this going to combine
> with an active maintainer and some parts on hackage?
>
> Claus
To be able to further develop SYB (see [1] for history), it's probably best
to develop it as a separate package, which people can install, upgrade, etc.
This would mean the library could be updated independently of GHC, and new
GHC releases could then use the most recent version of the package.
But how do these things merge? Can/should SYB be moved out of the base
package? And, if this happens, can the library being developed as a separate
package still use the automatic deriving mechanism?
I'm sending this message to libraries(a)haskell.org too because I guess this
problem might have shown up here before.
Cheers,
Pedro
[1]
http://search.gmane.org/?query=%22Owning+SYB%22&group=gmane.comp.lang.haske…
Hello all,
As Johan mentioned, here in Utrecht we are working on libraries for generic
programming. We want to make it easier for people to use generic libraries,
so we are packaging EMGM [1] and a library for generic programming for
mutually recursive datatypes [2]. We intend to release these on Hackage soon
(Summer vacations are delaying us a bit), along with useful generic
applications (a zipper and a generic rewriting framework).
Maintaining SYB fits well in this idea, and if no other natural maintainers
volunteer, I (with some support from the other people at Utrecht) am happy
to take it upon me. I probably won't do heavy development on the library,
but including patches, and providing support is fine. We're also planning to
maintain EMGM here in Utrecht, although we didn't develop that ourselves.
Recently, (at least) Claus and Oleg have been posting interesting
suggestions of improvements/modifications to SYB. Those should be further
analyzed and discussed, and finally introduced (or not) in the library. The
generic map for SYB, for instance, evolved from the "impossible to
implement", through the "unsafe implementation", until the latest gmap2 as
described by Oleg [3]. If further tests show this function behaves as
expected, then it's clearly a good candidate for extending SYB. We should
also rethink if other things previously deemed impossible remain so.
Maintaining SYB, alongside with the other generic libraries, will require
things such as:
* Releasing packages in Hackage, properly documented with Haddock;
* Updating such packages as necessary for new releases of GHC;
* Writing examples of how to use the libraries (from a user perspective);
* Writing testsuites, which are important for checking backwards
compatibility of any changes;
* Having an updated webpage linking to the library sources, documentation,
possibly a bug tracker, etc.
These are all things we plan to do for the libraries.
Additionally, we could think of improving syb-with-class [4] in parallel
with regular SYB. This is something to ask to its maintainer.
Cheers,
Pedro
[1]
http://books.google.com/books?id=OyY3ioMJRAsC&pg=PA199&sig=ACfU3U1nczeRAIjN…
[2] http://www.cs.uu.nl/research/techreps/UU-CS-2008-019.html
[3] http://www.haskell.org/pipermail/generics/2008-July/000362.html
[4]
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/syb-with-class