A lot of great ideas here. I want to comment on many of them, so please bear with me while I summarize some of the points in the process. Hopefully this will also help anybody new to the discussion, which has become extremely long.

- Local opens are somewhat of an anti-pattern in OCaml, because they're usually used in places where you have the same names defined in multiple modules:

(* both M and N are in other files, and they define (+).  M also defines (*) *)

M.(let x = foo + bar in
  N.(y + z * x))

The first + uses M's implementation and the second uses N's implementation.

The problem is, if you ever change one of the modules to include another function that wasn't expected originally (for example, N now includes *), you now have subtle bugs breaking your code in completely separate files from the ones you were editing, and the type system can't necessarily do anything to catch these errors.

- Similar languages to OCaml (such as Haskell) outlaw having the same name defined twice in the same scope. OCaml only issues a warning. IMO, this warning should be turned into an error. However, these other languages also provide a way to use the same name in the same scope by having type-based dispatch or disambiguation. For example, haskell has typeclasses. OCaml currently doesn't have this. I think this shows that Modular Implicits aren't just a nice-to-have feature -- we really need them to be able to get to do the kinds of things other languages do safely.

- I personally don't think the splitting of the warning between alphanumerics and operators is that helpful. This isn't a warning you should ever turn off IMO, regardless of the domain.

- The destructive versions of local opens which disable these warnings are even worse anti-patterns, since they're just a huge recipe for bugs.

- In the absence of Modular Implicits, as Petter mentioned, it would be nice to have the warnings/potential errors only generated when the same names have the same types. In case of different types with the same name, the type system should take care of any issues. For example, if M's (*) has a different type than N's (*), there's no problem per se since we'll get a type error. I think this is definitely something worth pursuing.

- In general, it would be nice not to have to open all these local scopes, and rather, as Simon mentioned, to reference operators directly when needed (as in, M.+). The problem is that these cannot be used infix in the code due to parser reasons. I think that while we're looking for a parsing solution for this, it might be better to also look for a parsing solution for turning any name into an infix function, and simply apply that. Haskell uses backtick (` as in x `mod` y), which we already use for polymorphic variants. Can we think of another symbol with which to do this? We could then apply it to M.+ as well.

- Another good point is that it would be nice to limit our imports of a module in the same file in which it is used. The issue is that module syntax is too verbose, due to the fact that it requires types. However, our module type signatures could possibly drop the type definitions, relying on imported type definitions instead. Something like the following would be nice:

module M : sig val (+) val (-) val mult end = LongModuleName

Note that this is similar to haskell's qualified import statement, but is more powerful since it creates a local module. This is also easy to parse since val is a keyword. The dropped types would form holes in the signature, which must be made available in the referenced module. When wanting to do multi-level local opens, rather than opening modules blindly, you'd first create smaller submodules locally, and then only open those locally. This would be much safer, and is in fact much closer to the original point of having multiple possible type signature 'views' into a module implementation (which is nice in theory but is not used much except for functors and artificial illustrations of OCaml's abilities).

- Another point that was brought up was that it would be nice to access the local scope of the current module, which I think is extremely useful. How about _.foo as a possible syntax?

-Yotam

On Thu, Aug 20, 2015 at 1:06 AM, Romain Bardou <romain.bardou@inria.fr> wrote:
So basically we have to write more stuff to be able to write less stuff. Unless the "write more stuff" part can be factored there is no point. The best place to factor is in libraries, and we're back to annotating libraries, something that Daniel pointed out was not ideal either.

It seems to me that trying to tackle this issue from a syntax perspective will not yield good results, and that one should seek help from the type-checker instead.

Basically we want some form of overloading. Type classes would solve a lot of use cases. OCaml does provide typing-based disambiguation though, although that is only for records and sum types and not for values. What if we could use infix symbols for sum types? Let's assume for a moment that (!) and (+) are valid constructors.

module Int =
struct
  type t =
    | (!) of int
    | (+) of t * t
end

module Float =
struct
  type t =
    | (!) of float
    | (+) of t * t
end

let x: Int.t = !42 + !59
let y: Float.t = !42. + !59.

(If you replace ! by A and + by B this is a valid OCaml program.)

Compare the last two lines with:

let x = Int.(!42 + !59)
let y = Float.(!42. + !59.)

The character count is similar but in the first example there is less risk of shadowing, at the cost of having to disable warning 40. I personally believe that disambiguation is cleaner than local open. Also, in more complex examples the first solution may not even need the type annotation, such as in:

type t = { x: Int.t; y: Float.t }

(* disambiguation-based example *)
let _ = { x = !42 + !59; y = !42. + !59. }

(* local-open-based example *)
let _ = { x = Int.(!42 + !59); y = Float.(!42. + !59.) }

OCaml's disambiguation is kind of reversed type classes: disambiguation propagates type constraints top-down whereas type classes propagates type constraints bottom-up. The latter is more powerful - in particular typing can be principal - but it requires much more from the type system.


On 19/08/2015 23:15, octachron wrote:
 From my point of view, a prefixed notation M.+ does not replace all use
case of local opens, for at least two reasons:

     1. It makes operators harder to spot since I can not rely any more
on the first character
     2. It adds syntactic noise and thus decreases readability within
the DSL

As an illustration, a simple rotation

    (** Rotation on the vect(x,y) plane with an angle t
         precondition: x and y are orthonormal  *)
    let rotation (x,y) t v = let open V in
      v
       + R.( ( cos t - 1. ) * (v|*|x) - sin t * (v|*|y) ) * x
       + R.( sin t * (v|*|x) + ( cos t - 1. ) * (v|*|y) ) * y

(where V is a vector module, R the associated real-like field and |*|
the scalar product)
becomes

    let rotation (x,y) t v =
      v
       V.+ ( ( cos t R.- 1. ) R.* ( v V.|*| x ) R.- sin t R.* ( v V.|*|
    y ) ) V.* x
       V.+ ( sin t R.* ( v V.|*| x ) R.+ ( cos t R.- 1. ) R.* ( v V.|*|
    y ) ) V.* y

  with your proposition.

In this second version, I have a hard time separating the different
subexpressions, and I don't think it would improve much with a better
familiarity with the syntax.

At the same time, I do agree that it would be nice to be able to use
operators as operators without having to bring them in the local scope.

-- octachron

Le 08/19/15 17:55, Simon Cruanes a écrit :
This whole thread makes me wonder whether local opens are worth it. I
don't like global open (at all), and shadowing is harmful even in
smaller scopes. Local open seems to be used for DSL that have a lot of
infix operators (maths, etc.) as demonstrated by the proposal of new
warnings and syntax about shadowing of infix operators.

If modules have short names (Z, Q from Zarith come to mind, but
module-aliasing your favorite monad to "M" would do too), would M.+ be
a reasonable infix operator? I would be ready to have slightly more
verbose calls to M.>>= if it removes ambiguity and potential shadowing
bugs. Of course I don't know if this is compatible with the current
syntax.

--
Simon



--
Caml-list mailing list.  Subscription management and archives:
https://sympa.inria.fr/sympa/arc/caml-list
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners
Bug reports: http://caml.inria.fr/bin/caml-bugs