
So gi-gtk is already using OverloadedLabels to fight the namespacing problem. What I'm afraid is that eventually people will pick up on this and stop using normal functions altogether. My problem with OverloadedLabels is that it is a class: if people start using it widely, the original modules of types are going to become even more privileged than they already are: only it will be canonically able to define functions which can be conveniently called, and everybody else will have to only define "second-class" normal functions or risk instance collisions. I mean yes, it's the same as in most OOP languages, but isn't it also bad? There must be a better way... Is there any alternative approach to name collisions coming?

I mean yes, it's the same as in most OOP languages, but isn't it also bad? There must be a better way...
Is there any alternative approach to name collisions coming?
I think we should start considering what problem we're actually solving (the "record problem"), and where all solutions inevitably converge toward when it comes to name resolution: ad-hoc overloading. In particular, I think OverloadedLabels is a bad solution, and every other special-case solution is similarly going to be bad. My opinion is and has always been: just allow type-directed name resolution in Haskell. All naming problems would go away instantly without any awkward, inconsistent extensions that need new syntax and heavy type-level machinery to work. C++ is doing it. Every OOP language is doing it. They do it, because it's useful and convenient. Let's do it, too! AND PLEASE not the way an [existing proposal] suggests to do it! Please let's just do ad-hoc overloading. There is no reason to introduce new syntax, because syntax is completely orthogonal to this problem. [existing proposal]: https://prime.haskell.org/wiki/TypeDirectedNameResolution Greets ertes

On 09/07/17 18:36, Ertugrul Söylemez wrote:
I mean yes, it's the same as in most OOP languages, but isn't it also bad? There must be a better way...
Is there any alternative approach to name collisions coming?
I think we should start considering what problem we're actually solving (the "record problem"), and where all solutions inevitably converge toward when it comes to name resolution: ad-hoc overloading. In particular, I think OverloadedLabels is a bad solution, and every other special-case solution is similarly going to be bad.
My opinion is and has always been: just allow type-directed name resolution in Haskell. All naming problems would go away instantly without any awkward, inconsistent extensions that need new syntax and heavy type-level machinery to work. C++ is doing it. Every OOP language is doing it. They do it, because it's useful and convenient. Let's do it, too!
AND PLEASE not the way an [existing proposal] suggests to do it! Please let's just do ad-hoc overloading. There is no reason to introduce new syntax, because syntax is completely orthogonal to this problem.
[existing proposal]: https://prime.haskell.org/wiki/TypeDirectedNameResolution
How would you propose to do TDNR instead, then? It's far from clear (to me at least) how to combine ad-hoc type-based overloading with Haskell's type inference, which is part of the reason why TDNR proposals have never been implemented. There are two basic questions that need to be answered: 1. When does an identifier get special treatment, as opposed to the usual name resolution process? 2. At what point during type inference does an ambiguous name get resolved, and what impact does that have on the type inference process? The OverloadedLabels answer to question 1 is that special identifiers get a syntactic cue (the prefix hash). It's ugly, but it's obvious that something special is happening. Similarly, the TDNR proposal uses the dot. We could say that any ambiguous identifier (i.e. one that would cause a name resolution error at present) gets special treatment, but that's rather implicit and leads to odd changes in type inference behaviour if a colliding name is brought into or removed from scope. The OverloadedLabels answer to question 2 is to use normal type class constraints to defer resolving the ambiguity to the constraint solver. This is relatively easy to specify and understand. Few alternatives have ever been properly specified (in particular, the original TDNR proposal does not really answer this question). FWIW, it has been suggested that OverloadedLabels be removed on the basis that using TypeApplications with a Symbol literal gives a not completely unreasonable syntax (fromLabel @"bar"). Note that OverloadedLabels as it currently stands does not have much interaction with records, though that might change in the future (see discussion on https://github.com/ghc-proposals/ghc-proposals/pull/6). Adam -- Adam Gundry, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/

On 2017-07-09 21:58, Adam Gundry wrote:
On 09/07/17 18:36, Ertugrul Söylemez wrote:
I mean yes, it's the same as in most OOP languages, but isn't it also bad? There must be a better way...
Is there any alternative approach to name collisions coming? […]
My opinion is and has always been: just allow type-directed name resolution in Haskell. […] There are two basic questions that need to be answered:
1. When does an identifier get special treatment, as opposed to the usual name resolution process?
2. At what point during type inference does an ambiguous name get resolved, and what impact does that have on the type inference process?
I want to apologize beforehand for the incoherence of my thoughts. These are only titbits I would like to throw into the discussion. Please excuse me if they are obvious or distracting for the more knowledgeable people here. The first titbit looks esoteric at first glance. About two months ago, Oleg dug up what seems like an old experiment of his. He showed that all classes, including fundeps, can be reduced to exactly one, carefully chosen class. (thread https://mail.haskell.org/pipermail/haskell-cafe/2017-May/127169.html and link to the article http://okmij.org/ftp/Haskell/TypeClass.html#Haskell1) Playing around with it I realized that a version of this one class is already in base. It is non other than IsLabel from OverloadedLabels. In a sense, IsLabel is the mother of all classes. That's not extremely surprising, as classes are basically records with, and IsLabel offers a kind of name-directed type resolution the same way classes do. What it means to me is that OverloadedLabels might have a more fundamental nature than is visible on the surface. Possible replacements should be approached with care. What this also tells me is that, in a way, OverloadedLabels offers the inverse of type-directed name resolution. No wonder it's awkward for that usecase. But maybe that perspective can lead to more ideas? The other titbit is much simpler: Isn't it about time to allow explicit imports, and more importantly, explicit non-imports for instances? Some time ago I fantasised about some special syntax for this, calling the (very rough) idea "aspects" (thread https://mail.haskell.org/pipermail/haskell-cafe/2017-May/127006.html). But we needn't go that far. The simplest implementation would entail only expanded import/export syntax. That wouldn't really be type-directed, but brute-force-directed, but sometime it's better to be explicit. And the time where our world is so small that only one mathematical truth is enough to rule all code is coming closer and closer to it's end. Just two small ideas. Hope they contribute something. Cheery, MarLinn

AND PLEASE not the way an [existing proposal] suggests to do it! Please let's just do ad-hoc overloading. There is no reason to introduce new syntax, because syntax is completely orthogonal to this problem.
[existing proposal]: https://prime.haskell.org/wiki/TypeDirectedNameResolution
How would you propose to do TDNR instead, then? It's far from clear (to me at least) how to combine ad-hoc type-based overloading with Haskell's type inference, which is part of the reason why TDNR proposals have never been implemented.
There are two basic questions that need to be answered:
1. When does an identifier get special treatment, as opposed to the usual name resolution process?
My proposal is *always*: ...
2. At what point during type inference does an ambiguous name get resolved, and what impact does that have on the type inference process?
... type inference would have to be done multiple times, once for each matching identifier in scope. Do each of them independently, then see which ones turn out to be well-typed (no ambiguity, no missing instances, no mismatch, etc.). If there is exactly one, take it, otherwise give up with a type error. For regular unique identifiers nothing would change, so this is a backward-compatible extension.
The OverloadedLabels answer to question 1 is that special identifiers get a syntactic cue (the prefix hash). It's ugly, but it's obvious that something special is happening. Similarly, the TDNR proposal uses the dot. We could say that any ambiguous identifier (i.e. one that would cause a name resolution error at present) gets special treatment, but that's rather implicit and leads to odd changes in type inference behaviour if a colliding name is brought into or removed from scope.
My point is that that's inevitable. 1. nice syntax, 2. simple semantics, 3. no inference interference -- pick two. In today's Haskell we have 2 and 3, but we lack 1, because we need to prefix our identifiers or use qualified imports. OverloadedLabels seems to go with 1 and 3, lacking 2, because of the heavy type-level machinery it relies on. I propose that we go with 1 and 2 instead. This can of course cause problems with applications that don't fully saturate a function. Since that's common in Haskell, we would have to use it sparingly, potentially only for record fields or lenses. But that's also the primary use case, so I'd be fine with that. Greets ertes

On Jul 10, 2017, at 2:38 PM, Ertugrul Söylemez
wrote: ... type inference would have to be done multiple times, once for each matching identifier in scope. Do each of them independently, then see which ones turn out to be well-typed (no ambiguity, no missing instances, no mismatch, etc.). If there is exactly one, take it, otherwise give up with a type error.
This would make type inference go exponential *extremely* quickly. This sort of approach is a non-starter, since it would imply typechecking a module 2^n times for n ambiguities where only 2 of the same identifiers are in scope; it would be even worse when there are more than 2. Due to the way Haskell’s type inference works, it would be very difficult (impossible?) in general to limit the duplicate work the typechecker would need to perform if you want to run it multiple times to see which binding would typecheck. GHC does no backtracking in the typechecker, and this would be even worse than backtracking, since it would always need to run multiple times. The only workable approach I can imagine for TDNR is something like the following: 1. If an identifier is unambiguous, don’t do anything differently from what already happens now. 2. If an identifier is ambiguous, ignore the bindings’ types entirely and assign the identifier a fresh type variable. (If the binding is in function application position, it can be assigned the type (a -> b -> c -> ...), depending on the number of expressions it is applied to, but this doesn’t fundamentally change anything.) 3. Typecheck the program using that information alone. Defer name resolution to the constraint solver. If the program typechecks, try to find an unambiguous substitution during constraint solving via subsumption. If one can be found, use it. Otherwise, bail with an appropriate error message. In my head, this seems less invasive than trying to typecheck the program multiple times and less wishful thinking than trying to divine the proper binding during the bulk of the typechecking process. However, I am not familiar with the details of GHC’s particularly advanced and complex typechecker, and it’s entirely possible that even the heavily constrained approach I just outlined is an enormous amount of work or even impossible. Even if it were possible to implement the above approach, it would still be limited. It’s possible it would need to be restricted to imported and top-level bindings (excluding local bindings), and it would probably sometimes fail to typecheck even when one of the bindings would successfully typecheck (when higher-rank types are involved, for example). I’d personally be quite happy with the feature even with those limitations, but I can’t make any claims to its practicality or possibility, since I have never touched GHC’s source at all, much less the typechecker.

On Jul 9, 2017, at 10:36, Ertugrul Söylemez
wrote: AND PLEASE not the way an [existing proposal] suggests to do it! Please let's just do ad-hoc overloading. There is no reason to introduce new syntax, because syntax is completely orthogonal to this problem.
[existing proposal]: https://prime.haskell.org/wiki/TypeDirectedNameResolution
If I understand correctly, what you’re proposing is the “syntax-free” variant of TDNR, which is already outlined here: https://ghc.haskell.org/trac/ghc/wiki/SyntaxFreeTypeDirectedNameResolution I agree that would be a very nice feature to have, and I think doing it without new syntax would be strongly preferable to adding new syntax. The proposal outlines the basics of how it would work, but I have no idea how difficult it would be to implement in practice.

AND PLEASE not the way an [existing proposal] suggests to do it! Please let's just do ad-hoc overloading. There is no reason to introduce new syntax, because syntax is completely orthogonal to this problem.
I think that a new syntax is needed though. Here's my reasoning: Why do mainstream OOP languages have it so easy, while Haskell hasn't been able to solve the name collision problem for many, many years? I think one of the obstacles is that currying has encouraged most libraries to put any object arguments last, eg: insert :: Int -> a -> [a] -> [a] insert :: a -> Set a -> Set a insert :: k -> v -> Map k v -> Map k v instead of putting it first (like in most OOP languages): insert :: [a] -> Int -> a -> [a] insert :: Set a -> a -> Set a insert :: Map k v -> k -> v -> Map k v I think this is precisely the reason why OOP languages have it easy while Haskell is struggling. If the significant argument is predictably first, TNDR is super-easy to implement even in current Haskell, if you are willing to create a class for every single method: {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FlexibleInstances #-} import Data.Set (Set) import Data.Map (Map) import qualified Data.Set as Set import qualified Data.Map as Map class Insert a f | a -> f where insert :: a -> f instance Insert [a] (Int -> a -> [a]) where insert list at item = take at list ++ [item] ++ drop at list instance Ord a => Insert (Set a) (a -> Set a) where insert set item = Set.insert item set instance Ord k => Insert (Map k v) (k -> v -> Map k v) where insert map k v = Map.insert k v map main = do print (insert [1, 3, 4] 1 2) print (insert Set.empty "hello") print (insert Map.empty "hello" "world") So, a new syntax is surely needed if the TNDR implementation relies on object arguments being the first, since $ no longer works for such functions. Also, I think that methods should get a namespace of their own, just like operators. The reason is to preserve backwards compatibility without having to create any new modules: methods can be implemented alongside old-style functions. Another reason: let name = person.name in ... If the .name method is in a namespace of its own, the name variable doesn't become ambiguous (with all associated problems). I don't think it would even be necessary to introduce any ambiguity- resolving behaviour into normal namespace if methods are in a namespace of their own. Methods would be defined like this: .insert :: Ord k => Map k v -> k -> v -> Map k v .insert map k v = ... Invoked like this (just like in existing proposal): Map.empty .insert "hello" "world" .insert "cat" "meow" .insert "haskell" "awesome" Currying by not applying the object: .insert x y :: Map k v -> Map k v Currying by not applying the arguments: map .insert :: k -> v -> Map k v Prefix application: (.insert) map k v

On 10/07/2017, at 9:03 AM, Nikita Churaev
wrote: I think that a new syntax is needed though. Here's my reasoning:
Why do mainstream OOP languages have it so easy, while Haskell hasn't been able to solve the name collision problem for many, many years?
Because mainstream object-oriented programming languages do not do (bidirectional) type inference, and the one exception I can think of (Ada) does not have variables in its type language. Amongst non-mainstream languages, F# might repay examination. Suspicious examination. I see F# code doing <module>.<function> all the time where you might have expected its OOP magic to be used...
I think one of the obstacles is that currying has encouraged most libraries to put any object arguments last, eg:
F# is a .Net language, which is thoroughly OO. Yet we see
Set.add;; val it : ('a -> Set<'a> -> Set<'a>) when 'a : comparison = fun:clo@1
Note: the "object" argument is second, not first. Currying and argument order really don't seem to be related. Haskell type-classes don't depend on which argument is which, after all. Consider class Addable f where Eq t => add :: t -> f t -> f t instance Addable [] where add x ys = if x`elem`ys then ys else x:ys newtype Set t = Set [t] instance (Eq x) => Addable Set where add x (Set ys) = Set (add x ys)
I think this is precisely the reason why OOP languages have it easy while Haskell is struggling.
And the OOP languages struggle to do what Haskell does easily. It is also worth remembering that ad hoc overloading (because that is what we're talking about) was present in PL/I, Algol 68, and Ada 83, without any trace of OOPiness at all. Also while letting the clue to resolution come from any argument (or combination of arguments). As a native speaker of an SVO language (English) in a country where one of the official languages is VSO (Māori), I sometimes find the OVS structure of "mainstream OO languages" a little uncomfortable... "Backward ran sentences until reeled the mind."

Why do mainstream OOP languages have it so easy, while Haskell hasn't been able to solve the name collision problem for many, many years? Because mainstream object-oriented programming languages do not do (bidirectional) type inference, and the one exception I can think of (Ada) does not have variables in its type language.
Then isn't it a trade-off? Convenience of bidirectional type inference vs. convenience of name collision resolution? And Haskell type system seems to support making this trade-off on case by case basis. OverloadedLabels and my Insert example implement the exact behaviour provided by mainstream OOP languages (looking up the function by the type of the main argument and the name of the function). Are there some hidden pitfalls that I am not aware of? If not or if they aren't particularly devastating, then what's left is to make making the trade-off in favor of avoiding name collisions as convenient as in OOP languages.
Note: the "object" argument is second, not first. Currying and argument order really don't seem to be related. Haskell type-classes don't depend on which argument is which, after all. Consider class Addable f where Eq t => add :: t -> f t -> f t
Yes, but as far as I know classes still depend on the predictability of argument positions. The problem is that "the last argument of a function" is not easily (if at all, somebody please enlighten me) expressible.
And the OOP languages struggle to do what Haskell does easily.
Yes, but the lack of something this obvious, present in most languages and extremely convenient definitely has the potential to plant doubts in the minds of Haskell beginners, thoughts that can make them give up Haskell without giving it a fair chance: "Haskell is impractical, just as the rumours say. Oh well..." "Haskell development is too hindered by fear of making decisions. Long- standing problems will never get solved. Sigh... Back to Microsoft C# we go..."

On Sun, Jul 9, 2017 at 9:53 PM, Nikita Churaev
And the OOP languages struggle to do what Haskell does easily.
Yes, but the lack of something this obvious, present in most languages and extremely convenient definitely has the potential to plant doubts in the minds of Haskell beginners, thoughts that can make them give up
Are you seriously arguing that Haskell must go OOP to matter? -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On Sun, Jul 9, 2017 at 9:58 PM, Brandon Allbery
On Sun, Jul 9, 2017 at 9:53 PM, Nikita Churaev
wrote: And the OOP languages struggle to do what Haskell does easily.
Yes, but the lack of something this obvious, present in most languages and extremely convenient definitely has the potential to plant doubts in the minds of Haskell beginners, thoughts that can make them give up
Are you seriously arguing that Haskell must go OOP to matter?
To be more clear: you brought up typeclasses, but typeclasses are the way they are in support of the real reason: putting the "object" last encourages functional programming. Last I checked, Haskell was about functional programming. You seem to be asserting that it is more important to support OOP thinking and discard the unnecessary FP baggage. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
participants (7)
-
Adam Gundry
-
Alexis King
-
Brandon Allbery
-
Ertugrul Söylemez
-
MarLinn
-
Nikita Churaev
-
Richard A. O'Keefe