[Haskell-cafe] Call for discussion: OverloadedLists extension

Michael Snoyman michael at snoyman.com
Sun Sep 23 06:06:57 CEST 2012


(Prettier formatting available at: https://gist.github.com/3761252)

Many of us use the OverloadedStrings language extension on a regular
basis. It provides the ability to keep the ease-of-use of string
literal syntax, while getting the performance and correctness
advantages of specialized datatypes like ByteString and Text. I think
we can get the same kind of benefit by allowing another literal syntax
to be overloaded, namely lists.

## Overly simple approach

The simplest example I can think of is allowing easier usage of Vector:

    [1, 2, 3] :: Vector Int

In order to allow this, we could use a typeclass approach similar to
how OverloadedStrings works:

    class IsList a where
        fromList :: [b] -> a b
    instance IsList Vector where
        fromList = V.fromList
    foo :: Vector Int
    foo = fromList [1, 2, 3]

## Flaws

However, such a proposal does not allow for constraints, e.g.:

    instance IsList Set where
        fromList = Set.fromList

    No instance for (Ord b)
      arising from a use of `Set.fromList'
    In the expression: Set.fromList
    In an equation for `fromList': fromList = Set.fromList
    In the instance declaration for `IsList Set'

Additionally, it provides for no means of creating instances for
datatypes like Map, where the contained value is not identical to the
value contained in the original list. In other words, what I'd like to
see is:

    [("foo", 1), ("bar", 2)] :: Map Text Int

## A little better: MPTC

A simplistic approach to solve this would be to just use MultiParamTypeClasses:

    class IsList input output where
        fromList :: [input] -> output
    instance IsList a (Vector a) where
        fromList = V.fromList
    foo :: Vector Int
    foo = fromList [1, 2, 3]

Unfortunately, this will fail due to too much polymorphism:

    No instance for (IsList input0 (Vector Int))
      arising from a use of `fromList'
    Possible fix:
      add an instance declaration for (IsList input0 (Vector Int))
    In the expression: fromList [1, 2, 3]
    In an equation for `foo': foo = fromList [1, 2, 3]

This can be worked around by giving an explicit type signature on the
numbers in the list, but that's not a robust solution. In order to
solve this properly, I think we need either functional dependencies or
type families:

## Functional dependencies

    class IsList input output | output -> input where
        fromList :: [input] -> output
    instance IsList a (Vector a) where
        fromList = V.fromList
    instance Ord a => IsList a (Set a) where
        fromList = Set.fromList
    instance Ord k => IsList (k, v) (Map k v) where
        fromList = Map.fromList

    foo :: Vector Int
    foo = fromList [1, 2, 3]

    bar :: Set Int
    bar = fromList [1, 2, 3]

    baz :: Map String Int
    baz = fromList [("foo", 1), ("bar", 2)]

## Type families

    class IsList a where
        type IsListInput a
        fromList :: [IsListInput a] -> a
    instance IsList (Vector a) where
        type IsListInput (Vector a) = a
        fromList = V.fromList
    instance Ord a => IsList (Set a) where
        type IsListInput (Set a) = a
        fromList = Set.fromList
    instance Ord k => IsList (Map k v) where
        type IsListInput (Map k v) = (k, v)
        fromList = Map.fromList

    foo :: Vector Int
    foo = fromList [1, 2, 3]

    bar :: Set Int
    bar = fromList [1, 2, 3]

    baz :: Map String Int
    baz = fromList [("foo", 1), ("bar", 2)]

## Conclusion

Consider most of this proposal to be a strawman: names and techniques
are completely up to debate. I'm fairly certain that our only two
choices to implement this extension is a useful way is fundeps and
type families, but perhaps there's another approach I'm missing. I
don't have any particular recommendation here, except to say that
fundeps is likely more well supported by other compilers.



More information about the Haskell-Cafe mailing list