[GHC] #9883: Make OverloadedLists more usable by splitting the class interface

#9883: Make OverloadedLists more usable by splitting the class interface -------------------------------------+------------------------------------- Reporter: muesli4 | Owner: Type: feature request | Status: new Priority: normal | Milestone: ⊥ Component: External Core | Version: 7.8.3 Keywords: overloaded lists, | Operating System: islist | Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: Difficulty: Moderate (less | None/Unknown than a day) | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- == Problem == While the OverloadedLists extension is very useful, it limits the types which can be used with it, by requesting too much. Assume you have a database specific DSEL which allows you to use list-like expressions in queries, it's easy to implement {{{fromList}}}, but we are unable to implement {{{toList}}} in a reasonable fashion without a backend and an existing connection. == Proposal == Modify the class interface in a way that does not require the instance to be ''listable''. {{{ class IsList l where type Item l fromList :: [Item l] -> l fromListN :: Int -> [Item l] -> l }}} We could then provide the pattern matching functionality on {{{IsList}}} instances with different approaches. === Another class === Just add another class which is used to provide the {{{toList}}} function, used on pattern matches. This is the easiest approach {{{ class AsList l where type Item l toList :: l -> [Item l] }}} Desugaring works as usual and it goes well with all structures. (The name is not the best though.) === Using Data.Foldable === The list pattern gets desugared using Data.Foldable: {{{ f :: (IsList l, Foldable l) => l -> l f [x, y, z] = [x, y] f l = l }}} gets something like: {{{ import Data.Foldable (toList) f :: (IsList l, Foldable l) => l -> l f (toList -> [x, y, z]) = fromList [x, y] f l = l }}} This approach does not go well with structures like {{{Data.Map}}}, because it expects the type constructor to take the ''element type'' as first argument, but we would like to have a tuple type. Maybe a wrapper could be provided, but I think it's not the way to go, as long as Data.Foldable does not use type families. == Drawbacks == Both approaches complicate the type of list expressions. This requires a bit more of typing, but it specifies exactly which functionality you need and one can simply drop the unused one, without creating dangerous dummy implementations: - {{{IsList}}} for overloaded list expressions - {{{AsList}}} or {{{Foldable}}} for pattern matching Most of the time OverloadedLists is used for convenience, so I don't expect the normal user to be really affected, library writers, specifically those who write some kind of DSEL, will have to be more precise, but get a more type-safe approach, which can not fail at runtime. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9883 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9883: Make OverloadedLists more usable by splitting the class interface -------------------------------------+------------------------------------- Reporter: muesli4 | Owner: Type: feature | Status: closed request | Milestone: ⊥ Priority: normal | Version: 7.8.3 Component: External | Keywords: overloaded lists, Core | islist Resolution: duplicate | Architecture: Unknown/Multiple Operating System: | Difficulty: Moderate (less Unknown/Multiple | than a day) Type of failure: | Blocked By: None/Unknown | Related Tickets: #7495 Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by carter): * status: new => closed * resolution: => duplicate * related: => #7495 Comment: interesting ideas! Its a dupe (at least in part) of https://ghc.haskell.org/trac/ghc/ticket/7495, so i'm closing it as a dupe of that, and adding a related ticket link ther -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9883#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9883: Make OverloadedLists more usable by splitting the class interface -------------------------------------+------------------------------------- Reporter: muesli4 | Owner: Type: feature | Status: closed request | Milestone: ⊥ Priority: normal | Version: 7.8.3 Component: External | Keywords: overloaded lists, Core | islist Resolution: duplicate | Architecture: Unknown/Multiple Operating System: | Difficulty: Moderate (less Unknown/Multiple | than a day) Type of failure: | Blocked By: 7495 None/Unknown | Related Tickets: #7495 Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by simonpj): I'm far from sure that it's a dup of #7495, so I'm reopening. This ticket has a clear proposal; #7495 does not. By all means go ahead and forge a consensus about this ticket. I wonder if `IsList` could be a superclass of `AsList`? That is, do you want to be able to pattern-match on a list-like thing, but not be able to use literals for that type? Or are they best considered as orthogonal? The nomenclature clearly needs fixing! Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9883#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9883: Make OverloadedLists more usable by splitting the class interface -------------------------------------+------------------------------------- Reporter: muesli4 | Owner: Type: feature | Status: new request | Milestone: ⊥ Priority: normal | Version: 7.8.3 Component: External | Keywords: overloaded lists, Core | islist Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Moderate (less Unknown/Multiple | than a day) Type of failure: | Blocked By: 7495 None/Unknown | Related Tickets: #7495 Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: closed => new * resolution: duplicate => -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9883#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9883: Make OverloadedLists more usable by splitting the class interface -------------------------------------+------------------------------------- Reporter: muesli4 | Owner: Type: feature | Status: new request | Milestone: ⊥ Priority: normal | Version: 7.8.3 Component: External | Keywords: overloaded lists, Core | islist Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Moderate (less Unknown/Multiple | than a day) Type of failure: | Blocked By: 7495 None/Unknown | Related Tickets: #7495 Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by muesli4): Replying to [comment:3 simonpj]:
I'm far from sure that it's a dup of #7495, so I'm reopening. This ticket has a clear proposal; #7495 does not. I'm not sure either. I was trying to get a discussion running about this, since I'm not that much experienced in Haskell (at least I haven't written an extension), which does not mean I'm not interested in working on GHC. :)
By all means go ahead and forge a consensus about this ticket.
I wonder if `IsList` could be a superclass of `AsList`? It could and it would even remove the redundant element type definition. My first intent was, to decouple the ''literal''-functionality from the rest. That's also a point I don't like about the {{{Num}}} class, instead of using {{{Num}}}, one could provide the ''literal''-functionality with a {{{NumLit}}} class, which then in turn could be a super class of {{{Num}}}. But I'm not sure whether I'm keeping track of everything it affects, so feel free to correct me.
That is, do you want to be able to pattern-match on a list-like thing, but not be able to use literals for that type? It could make sense, though I admit probably not often.
Or are they best considered as orthogonal? Aren't they already orthogonal semantically in the OverloadedLists extension?
I would keep them split, if someone needs both, he or she can use both.
The nomenclature clearly needs fixing!
How about this (I added the {{{ListView}}} class only because I thought it sounded exactly how it should be.): {{{ {-# LANGUAGE TypeFamilies #-} type family ListViewItem :: * -> * -- From ListLiteral class ListLit l where fromList :: [ListViewItem l] -> l fromListN :: Int -> [ListViewItem l] -> l -- From ListConvertible class ListConv l where -- Name could conflict with Data.Foldable.toList toList :: l -> [ListViewItem l] -- From ListViewable, since we provide a view into something utilizing a list. -- FIXME Better use some kind of type class alias here! class (ListLit l, ListConv l) => ListView l where }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9883#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9883: Make OverloadedLists more usable by splitting the class interface -------------------------------------+------------------------------------- Reporter: muesli4 | Owner: Type: feature | Status: new request | Milestone: ⊥ Priority: normal | Version: 7.8.3 Component: External | Keywords: overloaded lists, Core | islist Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Moderate (less Unknown/Multiple | than a day) Type of failure: | Blocked By: 7495 None/Unknown | Related Tickets: #7495 Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by goldfire): Maybe I'm missing something basic, but why do we need classes at all here? I propose we just desugar the list to use some functions in scope, and if they don't type-check, that's the programmer's problem. Concretely, here are the 7 expression forms from OverloadedLists, and my proposal for what they desugar to: {{{ [] -- buildList 0 (listStart `listSep` listEnd) [x] -- buildList 1 (listStart `listSep` x `listSep` listEnd) [x,y,z] -- buildList 3 (listStart `listSep` x `listSep` y `listSep` z `listSep` listEnd) [x .. ] -- enumFrom x [x,y ..] -- enumFromThen x y [x .. y] -- enumFromTo x y [x,y .. z] -- enumFromThenTo x y z }}} The `enumXXX` functions would use whatever is in scope -- not necessarily the methods from `Enum`. For regular old lists, we get {{{ buildList _ (_:elts) = elts listStart = undefined listSep = (:) infixr 5 `listSep` listEnd = [] }}} and the `enumXXX` functions are indeed taken from the `Enum` class. Note that I included the fixity declaration for `listSep` above -- there's no reason to disallow a ''left''-associative separator. (Though, all the elements in the list would effectively be wrapped in parentheses; the precedence level of the `listSep` fixity declaration is meaningless in the desugaring.) To me, this seems maximally flexible. With pattern synonyms, we could mimc this behavior in patterns. {{{ [] -- MatchList 0 (ListStart `ListSep` ListEnd) [x] -- MatchList 1 (ListStart `ListSep` x `ListSep` ListEnd) [x,y,z] -- MatchList 3 (ListStart `ListSep` x `ListSep` y `ListSep` z `ListSep` ListEnd) }}} For regular old lists, we get {{{ pattern MatchList n l <- ((\list -> (length list, undefined:list)) -> (n, l)) pattern ListStart <- _ pattern ListSep h t = h : t infixr 5 `ListSep` pattern ListEnd = [] }}} The construction for `MatchList` is painful. Improvements here are welcome. Sorry, @muesli4, I didn't mean to steal your thunder here! I hope you don't mind the debate. :) Thoughts (anyone) on this alternative? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9883#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9883: Make OverloadedLists more usable by splitting the class interface -------------------------------------+------------------------------------- Reporter: muesli4 | Owner: Type: feature | Status: new request | Milestone: ⊥ Priority: normal | Version: 7.8.3 Component: External | Keywords: overloaded lists, Core | islist Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Moderate (less Unknown/Multiple | than a day) Type of failure: | Blocked By: 7495 None/Unknown | Related Tickets: #7495 Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by carter): that might work, even for some of my really generic ideas over here https://github.com/cartazio/HetList/blob/master/HetList.hs -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9883#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9883: Make OverloadedLists more usable by splitting the class interface -------------------------------------+------------------------------------- Reporter: muesli4 | Owner: Type: feature | Status: new request | Milestone: ⊥ Priority: normal | Version: 7.8.3 Component: External | Keywords: overloaded lists, Core | islist Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Moderate (less Unknown/Multiple | than a day) Type of failure: | Blocked By: 7495 None/Unknown | Related Tickets: #7495 Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by carter): i'm not sure if the pattern synonyms trick works for Hlist / HRecord style constructions but i'll have to think about it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9883#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Maybe I'm missing something basic, but why do we need classes at all here? I propose we just desugar the list to use some functions in scope, and if they don't type-check, that's the programmer's problem. This sounds like something, which should be done with the RebindableSyntax extension. Type classes are useful, because other libraries can easily
#9883: Make OverloadedLists more usable by splitting the class interface -------------------------------------+------------------------------------- Reporter: muesli4 | Owner: Type: feature | Status: new request | Milestone: ⊥ Priority: normal | Version: 7.8.3 Component: External | Keywords: overloaded lists, Core | islist Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Moderate (less Unknown/Multiple | than a day) Type of failure: | Blocked By: 7495 None/Unknown | Related Tickets: #7495 Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by muesli4): Replying to [comment:6 goldfire]: provide instances for it, without them you have to provide them via some third party library and it seems to me that other uses are more like a corner case. But of course I may be wrong, so I am all for usability and convenience, without excluding special cases (as I said, these could be introduced with the RebindableSyntax extension).
Concretely, here are the 7 expression forms from OverloadedLists, and my
proposal for what they desugar to:
{{{ [] -- buildList 0 (listStart `listSep` listEnd) [x] -- buildList 1 (listStart `listSep` x `listSep` listEnd) [x,y,z] -- buildList 3 (listStart `listSep` x `listSep` y `listSep`
[x .. ] -- enumFrom x [x,y ..] -- enumFromThen x y [x .. y] -- enumFromTo x y [x,y .. z] -- enumFromThenTo x y z }}}
The `enumXXX` functions would use whatever is in scope -- not necessarily the methods from `Enum`.
For regular old lists, we get
{{{ buildList _ (_:elts) = elts listStart = undefined listSep = (:) infixr 5 `listSep` listEnd = [] }}}
and the `enumXXX` functions are indeed taken from the `Enum` class.
Note that I included the fixity declaration for `listSep` above --
To me, this seems maximally flexible.
With pattern synonyms, we could mimc this behavior in patterns.
{{{ [] -- MatchList 0 (ListStart `ListSep` ListEnd) [x] -- MatchList 1 (ListStart `ListSep` x `ListSep` ListEnd) [x,y,z] -- MatchList 3 (ListStart `ListSep` x `ListSep` y `ListSep` z `ListSep` ListEnd) }}}
For regular old lists, we get
{{{ pattern MatchList n l <- ((\list -> (length list, undefined:list)) -> (n, l)) pattern ListStart <- _ pattern ListSep h t = h : t infixr 5 `ListSep` pattern ListEnd = [] }}}
The construction for `MatchList` is painful. Improvements here are welcome. Can you use different types with the same pattern? The compiler should know the length of the list, so maybe it can be expressed with a type
z `listSep` listEnd) there's no reason to disallow a ''left''-associative separator. (Though, all the elements in the list would effectively be wrapped in parentheses; the precedence level of the `listSep` fixity declaration is meaningless in the desugaring.) I like what you could achieve with it, but I don't like how you do it: * The use of {{{undefined}}} seems like a hack to make the types work. * Can you provide some use cases where different associativity is an advantage? * I don't like to use operator syntax here. * Are you able to give definitions for these functions, such that we could use the list syntax for different types in the same module? Let's say heterogenous lists (was that the intention?) and normal lists. literal (though I have no idea how to do that).
Sorry, @muesli4, I didn't mean to steal your thunder here! I hope you don't mind the debate. :) Of course, that was the reason I started the ticket. I appreciate your contribution, but I think it goes a bit over the top, my proposal was just a slight change in an already existing extension. And I don't know whether you can provide the same functionality, which currently exists.
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9883#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9883: Make OverloadedLists more usable by splitting the class interface -------------------------------------+------------------------------------- Reporter: muesli4 | Owner: Type: feature | Status: new request | Milestone: ⊥ Priority: normal | Version: 7.8.3 Component: External | Keywords: overloaded lists, Core | islist Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Moderate (less Unknown/Multiple | than a day) Type of failure: | Blocked By: 7495 None/Unknown | Related Tickets: #7495 Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by simonpj): Replying to [comment:6 goldfire]:
Maybe I'm missing something basic, but why do we need classes at all here? I propose we just desugar the list to use some functions in scope, and if they don't type-check, that's the programmer's problem.
What if you wanted to use list syntax for two different types in the same module? You'd need two different `buildList` functions in scope. Aha! Type classes would solve that! What if you wanted to use list syntax for a type constructor that is as- yet abstract. Aha! Type classes can do that too. Maybe you are saying "if you want to use type classes, then just import a module that defines `buildList` in a class". And yes you could do that. But it's not the way ordinary list syntax or list comprehensions or monad do-notation work. There they desugar to some ''specific'' functions; and you use `-XRebindableSyntax` if you want instead to use "whatever is in scope". `-XOverloadedLists` works in a way consistent with that approach. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9883#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC