[Haskell-cafe] I'm afraid of OverloadedLabels.

Nikita Churaev lamefun.x0r at gmail.com
Sun Jul 9 21:03:24 UTC 2017


> 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



More information about the Haskell-Cafe mailing list