[Haskell-cafe] Call for discussion: OverloadedLists extension
George Giorgidze
giorgidze at gmail.com
Tue Nov 6 15:59:41 CET 2012
I have created a wiki page about the current implementation of the
OverloadedLists extension:
http://hackage.haskell.org/trac/ghc/wiki/OverloadedLists
The link to the GHC branch that provides a preliminary implementation
of the extension is given in the wiki page.
The wiki page documents what works already and how the extension can
be extended/improved further.
We would welcome contributions. If you would like to make a change in
the current design and implementation of the extension, please
document it (e.g., on the wiki page) and/or send us a GHC patch or a
pull request.
Please also comment whether you would like to see this extension
included in GHC.
Cheers, George
On 24 September 2012 18:29, Simon Peyton-Jones <simonpj at microsoft.com> wrote:
> | 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.
>
> Interestingly, Achim Krause, George Giorgidze and Jeroen Weijers have been thinking about this very question. They have most of an implementation too. I'm ccing them so they can post a status update.
>
> Your email broadens the topic somewhat; I don't think we'd considered overloading for maps too, though I can see it makes sense. I'd much prefer the type-family solution (with a single-parameter type class) to the fundep one, if we go that route.
>
> This topic deserves its own page on the GHC wiki, if someone wants to start one.
>
> If we can evolve a design consensus, I'm happy to incorporate the result in GHC.
>
> Simon
>
>
> | -----Original Message-----
> | From: haskell-cafe-bounces at haskell.org [mailto:haskell-cafe-
> | bounces at haskell.org] On Behalf Of Michael Snoyman
> | Sent: 23 September 2012 05:07
> | To: Haskell Cafe
> | Subject: [Haskell-cafe] Call for discussion: OverloadedLists extension
> |
> | (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.
> |
> | _______________________________________________
> | Haskell-Cafe mailing list
> | Haskell-Cafe at haskell.org
> | http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
More information about the Haskell-Cafe
mailing list