Sven Panne writes:
> Ralf Hinze wrote:
> > [...] Rewriting the definition to
> > 
> > > (@@) f g a            =  g a >>= f
> > 
> > avoids the problem.
> 
> I discovered something similar yesterday. Things are even more funny:
> 
> > (f @@ g) = \a -> g a >>= f  -- Does not work
> 
> > f @@ g = \a -> g a >>= f   -- Does work!
> 

Weird as it may seem, the former version of (@@) above and Ralf's
example

@@       :: (Monad m) => (a -> m b) -> (c -> m a) -> c -> m b
(f @@ g) a =  g a >>= f

are both examples of value definitions with invalid LHSes.

The LHS for a valdef in Haskell is either:

 - a pattern, e.g., "(x:xs)"
 - a var followed by a series of patterns, e.g., "f (n+1) (x:xs)"
 - the infix binary application of a varop, e.g., "f @@ [g,h]".

The LHS "(f @@ g) =" doesn't fall into any of these since (bracketed)
patterns cannot contain infix applications of varops. If @@ is
substituted for a constructor, everything is cool.

"(f @@ g) a =" fails because of the same, but has the additional
problem of mixing infix varop application with a trailing apat ("a"),
which just ain't legal.

Don't let any other implementations of the Haskell grammar tell you
otherwise :-)

--Sigbjorn
  • @@ Ralf Hinze
    • Re: @@ Sven Panne
      • Sigbjorn Finne

Reply via email to