[Haskell-cafe] overloaded list literals?

Gábor Lehel illissius at gmail.com
Mon Sep 6 12:36:21 EDT 2010


On Mon, Sep 6, 2010 at 12:47 PM, Neil Brown <nccb2 at kent.ac.uk> wrote:
> On 06/09/10 11:23, Johannes Waldmann wrote:
>>
>> We have overloaded numerical literals (Num.fromInteger)
>> and we can overload string literals (IsString.fromString),
>> so how about using list syntax ( [], : )
>> for anything list-like (e.g., Data.Sequence)?
>>
>
> I would have thought you have two obvious choices for the type-class (things
> like folding are irrelevant to overloading list literals):
>
> class IsList f where
>  fromList :: [a] -> f a
>
> or:
>
> class IsList f where
>  cons :: a -> f a -> f a
>  empty :: f a
>
> I'd go for the first, as I'd imagine you are only overloading the [a,b,c]
> form, not the a:b:c:[] form, and the first reflects this better.  Both of
> these could be used to convert a list literal into a list-like type (e.g.
> Sequence).  But neither of them would be useful for sets or maps, because
> the classes lack an Ord constraint on the type a -- maybe this makes
> overloaded list literals fairly limited in utility.

I endorse the idea of a class along the lines of the first example.
That takes care of convenient syntax for literals; view patterns can
give you the other end, pattern matching*.

The fact that this doesn't work for Sets and the like is indeed
troublesome, but I think you can solve it:

class IsListLikeThingamabob f where
    type ElemOf f
    fromList :: [ElemOf f] -> f

then you can do:

instance Ord a => IsListLikeThingamabob (S.Set a) where
    type ElemOf (S.Set a) = a
    fromList = S.fromList

and that way you can also use it for *-kinded types like ByteString,
if for whatever reason you might want to.

I think the aim here should be just to gain access to the convenient
list syntax for use with other types -- a fully generalized interface
for collections of all shapes and sizes is out of scope, and _hard_.
(But Ivan Miljenovic seems to be working on it.)


* Especially if, as discussed on the wiki[1], view patterns also get
upgraded to hook into a type class:

data View a where
    type ViewOf a
    view :: a -> ViewOf a

where defining an instance would allow you to omit the name of the
viewing function, defaulting to 'view' instead. So if you define
ViewOf (MyContainer a) as [a], you could match using:

foo (-> []) = something
foo (-> x:xs) = something else

(I believe the main holdup wrt this is indecision over whether to use
a plain MPTC, or a fundep / associated type in one direction, or one
in the other. The version above looks clearly superior to me, but I
don't want to derail the thread further. If someone else does, fork
it. :)

[1] http://hackage.haskell.org/trac/ghc/wiki/ViewPatterns

> Thanks,
>
> Neil.
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
Work is punishment for failing to procrastinate effectively.


More information about the Haskell-Cafe mailing list