"do" notation and ">>"

James B. White III (Trey) whitejbiii@ornl.gov
Wed, 27 Mar 2002 16:09:43 -0500


"James B. White III (Trey)" wrote:
> According to the Haskell 98 Tutorial, the following two statements
> should be equivalent, right?
> 
>         main = do put "hello"; put "world"
> 
>         main' = put "hello" >> put "world"
> 
> In the Hugs output below, it appears that they are not.

It looks like the problem is in "transDo" in "compiler.c". Both
"FROMQUAL" and "DOQUAL" are defined in terms of "nameBind" (see below),
where "nameBind" is defined in "type.c" as:

	nameBind        = linkName(">>=");

I think you need to define one or the other of these in terms of some
new "Name" object, say "nameBind_", such that:

	nameBind_ = linkName(">>");

I don't understand the guts of Hugs enough to know how to make this
change, or even which case needs the change. It looks like the right
place is the "DOQUAL" block.

Assuming I have "nameBind_" defined as above, can you describe the
changes I should make to "transDo" to get it to use ">>" directly?



/* --------------------------------------------------------------------------
 * Translation of monad comprehensions written using do-notation:
 *
 * do { e }               =>  e
 * do { p <- exp; qs }    =>  LETREC _h p = do { qs }
 *                                   _h _ = fail m "match fails"
 *                            IN bind m exp _h
 * do { LET decls; qs }   =>  LETREC decls IN do { qs }
 * do { IF guard; qs }    =>  if guard then do { qs } else fail m 
"guard fails"
 * do { e; qs }           =>  LETREC _h _ = [ e | qs ] in bind m exp _h
 *
 * where m :: Monad f
 * ------------------------------------------------------------------------*/

static Cell local transDo(m,e,qs)       /* Translate do { qs ; e }      
  */
Cell m;
Cell e;
List qs; {
    if (nonNull(qs)) {
        Cell q   = hd(qs);
        Cell qs1 = tl(qs);

        switch (fst(q)) {
            case FROMQUAL : {   Cell ld   = NIL;
                                Cell hVar = inventVar();

                                if (!failFree(fst(snd(q)))) {
                                    Cell str = mkStr(findText("match fails"));
                                    ld = cons(pair(singleton(WILDCARD),
                                                   ap2(nameMFail,m,str)),
                                              ld);
                                }

                                ld = cons(pair(singleton(fst(snd(q))),
                                               transDo(m,e,qs1)),
                                          ld);

                                return ap(LETREC,
                                          pair(singleton(pair(hVar,ld)),
                                               ap(ap(ap(nameBind,
                                                        m),
                                                     translate(snd(snd(q)))),
                                                  hVar)));
                            }

            case DOQUAL :   {   Cell hVar = inventVar();
                                Cell ld   = cons(pair(singleton(WILDCARD),
                                                      transDo(m,e,qs1)),
                                                 NIL);
                                return ap(LETREC,
                                          pair(singleton(pair(hVar,ld)),
                                               ap(ap(ap(nameBind,
                                                        m),
                                                     translate(snd(q))),
                                                  hVar)));
                            }

            case QWHERE   : return
                                expandLetrec(ap(LETREC,
                                                pair(snd(q),
                                                     transDo(m,e,qs1))));

            case BOOLQUAL : return
                                ap(COND,
                                   triple(translate(snd(q)),
                                          transDo(m,e,qs1),
                                          ap2(nameMFail,m,
                                            mkStr(findText("guard fails")))));
        }
    }
    return e;
}

-- 
James B. White III (Trey)
Center for Computational Sciences
Oak Ridge National Laboratory
whitejbiii@ornl.gov