[Haskell-cafe] group-by (Was: Nested guards?)
Henning Thielemann
lemming at henning-thielemann.de
Fri Dec 7 08:11:00 EST 2007
On Fri, 7 Dec 2007, Simon Peyton-Jones wrote:
> | And I think that the solution is not to make the language larger and larger
> | everytime someone wants a feature but to give people the tools to provide
> | features without language changes.
>
> Of course that would be even better! (Provided of course the resulting
> programs were comprehensible.) Haskell is already pretty good in this
> respect, thanks to type classes, higher order functions, and laziness;
> that's why it's so good at embedded domain-specific languages.
When I learned about GROUP BY and HAVING in SQL with its rules about what
is allowed in GROUP BY and SELECT I considered GROUP BY a terrible hack,
that was just introduced because the SQL people didn't want to allow types
different from TABLE, namely lists of tables. I try to convince my data
base colleagues that GROUP BY can nicely be handled in relational algebra
by allowing sets of sets and that this is a fine combinatorial approach. I
think we simply need a function like
buckets :: (a -> key) -> [a] -> [(key, [a])]
(where (a -> key) is a simple selector)
or
buckets :: (a -> (key, rest)) -> [a] -> [(key, [rest])]
(where (a -> (key, rest)) is a bijection)
or
buckets :: Ord key => ... ah no :-)
buckets :: Indexable key => (a -> (key, rest)) -> [a] -> Map key [rest]
buckets f = Map.fromListWith (++) . map (\ a -> let (k,r) = f a in (k, [r]))
Btw. since I often need fromListWith with Maps of list types, I wonder
whether there should be variants of fromListWith and insertWith, which can
use (:) instead of (++):
fromListCons :: Indexable k =>
(b -> a -> a) -- ^ add a new sub-element to the dictionary element, for example (:)
-> a -- ^ empty dictionary element, for example []
-> [(k, b)]
-> Data.Map.Map k a
insertCons :: Indexable k =>
(b -> a -> a) -> a -> k -> b -> Data.Map.Map k a -> Data.Map.Map k a
More information about the Haskell-Cafe
mailing list