[Hs-Generics] Sample code
Johan Jeuring
johanj at cs.uu.nl
Fri Oct 27 08:35:34 EDT 2006
> I wonder if we should collect some example code and make it
> presentable.
I think we should.
> By that I mean there should be the classification of the
> example, brief description, and, mainly, sample test data and the
> expected results. And, of course, implementations for these examples
> in various generic programming approaches. Incidentally, the
> `expressibility' section in the library description can simply
> enumerate which examples the library can implement. _Some_ of the
> examples may become the part of the benchmarking suite (at this point
> I'm simply interested in what is possible).
>
> Here's what I have gleaned so far, from a couple of SYB
> papers and the code already in DARCS:
>
> generic show: essential type is t -> String
> [I say essential because there may be additional arguments, say, for
> type representation]
> Description: display the term; special processing for Strings,
> as opposed to general arrays.
> Category: closed Cartesian [sorry, couldn't resist]
> I mean, `consumer', reduce a generic term to a value of the
> fixed type, String.
> LIGD has the implementation; no test data though.
>
> generic size: essential type t -> Int
> Give the size of a term (in terms of data constructors). The
> user should be able to assign size matrix to specific data types (like
> strings).
> Category: consumer, reduce a generic term to a value of the
> fixed type, Int.
> SYB3 example, also used in Smash. I have test data and
> expected results (part of syb4.hs)
> This example is quite similar to gshow above; I personally
> prefer this over gshow, because the Show class already provides
> the latter, so it's hard to get excited over gshow.
Maybe not, but gshow is a good example of a function that uses the
constructor names of a data type. And I think it is interesting to see
how the different approaches provide access to constructor names
(and possibly even also data type name, although that is not used
in gshow).
> Salary Raise: essential type t -> t
> Transform a term (representing an `organization' or an XML document)
> into the term of the same type, but with different values of some
> primitive fields.
> Ralf's dream example, from SYB1.
> category: type-preserving transformer
> Variation: uniform transformation (raise everybody's salary by
> 10%); or the transformation should affect only specific parts of the
> term. Transformation can be context-independent (increment each float
> field by 10%) or context- (that is, traversal history)
> dependent (increment each float until the money runs out).
> Test data can be extracted from Ralf's web site.
>
> generic minimum: essential type t
> Provides the 'minimal' value of any term in the universe of
> discourse.
> category: pure producer
> Variation: functional term may or may not be handled.
> LIGD example. test data can be easily extracted from it.
>
> Replace all Ints with Floats in a term: essential type t -> t'
> where t' = f(t).
> category: transformer, to a term of a different type. The
> output type is the function of the input type.
> variation: replace all Ints with Floats and negate all
> booleans, in a single traversal (that is, `compose' multiple
> compatible processing steps)
> Smash example; test data are available in the syb4.hs
>
> generic equality: essential type t -> t -> Bool
> category: binary function over two generic arguments of the
> same type.
> Variation: try essential type t -> t' -> Bool
> Variation: permit the user supply their own comparison
> procedure for some data types
> Variation: local extensibility [as explained in Stefan Holdermans]
> LIGD example (including specific comparison of integers mod
> 2). Need test data though.
>
> something of the type t1 -> t2 -> t3 where
> t3 = f(t1, t2). Generalization of zip/zipWith. I have never
> seen that example.
>
>
> Obviously a lot is missing in the above -- in particular, good
> names for the examples, and the test data. And the idea how to
> organize the files with examples and test data within our DARCS
> repository.
I think these are good examples. The only thing I miss is a generic
variant
of map :: (a->b) -> [a]->[b].
-- Johan
More information about the Generics
mailing list