
On 25/05/11 10:00, Jonas Almström Duregård wrote:
As an equivalent to:
f (x a) (y b) (z c)
Of course my intention is that the new keyword should initiate layout syntax so we can write this:
f <applied to> x a y b z c
Here's a (tongue-in-cheek) trick that allows for layout close to what you wanted (spoiler: but not close enough!). We start by switching to parameterised monads (which allow you to change the type of the monad as you go down the do-block; look carefully at the second and third parameters in the monad class): {-# LANGUAGE RebindableSyntax #-}
import Control.Applicative import Prelude ((++), (.), Num(..), Eq(..), ($), id, Int, Char, String, Float, ?, const, Show(..), Fractional(..))
class Monad m where (>>=) :: m a b y -> (y -> m b c z) -> m a c z return :: b -> m a a b
(>>) :: Monad m => m a b y -> m b c z -> m a c z (>>) m n = m >>= const n
Then we define a type for wrapping pure functions in this monad:
data Fun a b c = Fun (a -> b) c
instance Monad Fun where (>>=) (Fun f x) m = let Fun g y = m x in Fun (g . f) y return x = Fun id x
Then we add a helper for unwrapping it:
($$) :: a -> Fun a b c -> b ($$) f (Fun g _) = g f
And a function for supplying an argument:
r :: a -> Fun (a -> b) b a r x = Fun ($ x) x
And so what does let us do? Well, here's how it's used:
foo :: Int -> Char -> String -> Float -> String foo a b c d = show (a, b, c, d)
eg :: String eg = foo $$ do r$ 2 + 1 r$ 'c' r$ "hello" ++ "goodbye" r$ 3.0
foo is the function we want to apply, and eg shows how to apply it in do-notation with an argument on each line. I couldn't manage to remove the r$ at the beginning of each line, which rather ruins the whole scheme :-( On the plus side, there's no brackets, it's only two extra characters per line, and you can have whatever you like after the r$. For those who are interested, you can also use the same trick for writing Applicatives in a do notation. Continuing the same module, we can add an analogue for each of the types and functions for Applicative:
data App f a b c = App (f a -> f b) c
instance Applicative f => Monad (App f) where (>>=) (App f x) m = let App g y = m x in App (g . f) y return x = App id x
(<$$>) :: Applicative f => f a -> App f a b c -> f b (<$$>) f (App g _) = g f
s :: Applicative f => f a -> App f (a -> b) b (f a) s x = App (<*> x) x
Then we can use this on things which are Applicative but not Monad, e.g.
egA :: [String] egA = getZipList $ pure foo <$$> do s$ ZipList [3, 6, 7] s$ ZipList "hello" s$ ZipList ["more", "strings"] s$ ZipList [1.0, 1.5, 2.0]
And that's enough silly playing around :-) Thanks, Neil.