On 10/29/07, Tim Newsham <newsham@lava.net> wrote:
I would love to have the ability to define binary operator modifiers.
For example:

   f \overline{op} g       = liftM2 op f g
   f \overleftarrow{op} n  = liftM2 op f (return n)
   n \overrightarrow{op} g = liftM2 op (return n) f
   \widehat{f} x           = liftM f x

so that for example you could define functions like:

    (*3) \overline{+} (/2)

and

    3 \overrightarrow{+} \widehat{read} getContents

Obviously you could write this out the long way:

    liftM2 (3+) $ liftM read getContents

or go through the trouble of defining a bunch of binops

    f <+> g = liftM2 (+) f g
    n +>  g = return n <+> g
    f <+  n = f <+> return n
    read' = liftM read

    (*3) <+> (/2)
    3 +> read' getContents

but doing this for more than one or two operators gets tedious
quickly...

Is there any way in Haskell to modify binops in this way and still
be able to use them infix?  If not, has anyone considered supporting
strange syntaxes like this?

I've wanted this at times, too, due to using a lot of J a year or so ago.  J has some weird parsing/semantics rules so that f g h essentially means liftM2 g f h.  For example, avg =. +/ % #   is the J equivalent of avg = liftM2 (/) sum length.  Anyway, the closest you can get in Haskell is something like this, using the infix expressions of Ken Shan and Dylan Thurston:

import Control.Monad
import Control.Monad.Instances

infixr 0 -:, :-

data Infix f y = f :- y
x -: f :- y = x `f` y

ov op = liftM2 op
ovL op f n = liftM2 op f (return n)
ovR op n f = liftM2 op (return n) f
hat f = liftM f

*Main> :t (*3) -:ov (+):- (/2)
(*3) -:ov (+):- (/2) :: forall a1. (Fractional a1) => a1 -> a1
*Main> ((*3) -:ov (+):- (/2)) 7
24.5
*Main> :t 3 -:ovR (+):- ((hat read) getContents)
3 -:ovR (+):- ((hat read) getContents) :: forall a. (Num a, Read a) => IO a

It works (?), but it's pretty ugly and hardly seems worth it, unfortunately.

-Brent