apfelmus wrote: > In the end, I think that applicatively used monads are the wrong > abstraction.
Simon Peyton-Jones wrote: > Can you be more explicit? Monadic code is often over-linearised. > I want to generate fresh names, say, and suddenly I have to name > sub-expressions. Not all sub-expressions, just the effectful ones. Neil Mitchell wrote: > The monad in question simply supplies free variables, so could be > applied in any order. I see, the dreaded name-supply problem. Well, it just seems that monads are not quite the right abstraction for that one, right? (Despite that monads make up a good implementation). In other words, my opinion is that it's not the monadic code that is over-linearized but the code that is over-monadized. The main property of a "monad" for name-supply is of course f >> g = g >> f modulo alpha-conversion. Although we have to specify an order, it's completely immaterial. There _has_ to be a better abstraction than "monad" to capture this! SPJ: > It'a a pain to define liftM_yes_no_yes which takes an effectful > argument in first and third position, and a non-effectful one as > the second arg: > > liftM_yes_no_yes :: (a->b->c->m d) > -> m a -> b -> m c -> m d > > What a pain. So we have either > > do { ...; va <- a; vc <- c; f va b vc; ... } > > or > do { ...; liftM_yes_no_yes f a b c; ...} > > or, with some syntactic sugar... > > do { ...; f $(a) b $(c); ...} > > The liftM solution is even more awkward if I want > > f (g $(a)) b c > > for example. (the last one is already a typo, i guess you mean f $(g $(a)) b c) Neil: > -- helpers, ' is yes, _ is no > > coreLet__ x y = f $ CoreLet x y > coreLet_' x y = f . CoreLet x =<< y > > coreLet x y = f $ CoreLet x y > > f (CoreApp (CoreLet bind xs) ys) = coreLet bind $(coreApp xs ys) > Uhm, but you guys know that while (m a -> a) requires the proposed syntactic sugar, (a -> m a) is easy? r = return elevateM f x1 = join $ liftM f x1 elevateM3 f x1 x2 x3 = join $ liftM3 f x1 x2 x3 do { ...; elevateM3 f a (r$ b) c; ...} elevateM3 f (elevateM g a) (r$ b) (r$ c) coreLet x y = liftM2 CoreLet x y >>= f g (CoreApp (CoreLet bind xs) ys) = coreLet (r$ bind) (coreApp xs ys) In other words, you can avoid creating special yes_no_yes wrappers by creating a yes_yes_yes wrapper and turning a no into a yes here and there. No need for turning yes into no. One could even use left-associative infix operators ($@) :: (a -> b) -> a -> b ($@@) :: Monad m => (m a -> b) -> a -> b ($@) = id ($@@) = id . return and currying elevateM3 f $@@ (elevateM g $@@ a) $@ b $@ c g (CoreApp (CoreLet bind xs) ys) = coreLet $@ bind $@@ coreApp xs ys The intention is that a (mixed!) sequence of operators should parse as f $@ x1 $@@ x2 $@ x3 = ((f $@ x1) $@@ x2) $@ x3 Leaving such games aside, the fact that yes_yes_yes-wrappers subsumes the others is a hint that types like NameSupply Expr -> NameSupply Expr -> NameSupply Expr are fundamental. In other words, the right type for expressions is probably not Expr but NameSupply Expr with the interpretation that the latter represents expressions with "holes" where the concrete names for variables are filled in. The crucial point is that holes may be _shared_, i.e. supplying free variable names will fill several holes with the same name. Put differently, the question is: how to share names without giving concrete names too early? I think it's exactly the same question as How to make sharing observable? This is a problem that haunts many people and probably every DSL-embedder (Lava for Hardware, Pan for Images, Henning Thielemann's work on sound synthesis, Frisby for parser combinators). In a sense, writing a Haskell compiler is similar to embedding a DSL. I have no practical experiences with the name-supply problem. So, the first question is: can the name-supply problem indeed be solved by some form of observable sharing? Having a concrete toy-language showing common patterns of the name-supply problem would be ideal for that. The second task would be to solve the observable sharing problem, _that_ would require some syntactic sugar. Currently, one can use MonadFix to "solve" it. Let's take parser combinators as an example. The left-recursive grammar digit -> 0 | .. | 9 number -> number' digit number' -> ε | number can be represented by something like mdo digit <- newRule $ foldr1 (|||) [0...9] number <- newRule $ number' &&& digit number' <- newRule $ empty ||| number This way, we can observe the sharing and break the left recursion. But of course, the monad is nothing more than syntactic sugar here, the order does not matter at all. What we really want to write is a custom let-expression let' digit = foldr1 (|||) [0..9] number = number' &&& digit number' = empty ||| number and still be able to observe sharing. SPJ: > I'm thinking of this as a very superficial piece of syntactic sugar, > aimed at avoiding the excessive linearization of monadic code. Nothing deep. I don't agree, the excessive linearization is a feature, not a bug. Even if the sugar would be nothing deep, that shouldn't stop us from thinking deeply about it :) Regards, apfelmus _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime