Implementing forward refs in monadic assembler and interprete r

Mike Gunter m@ryangunter.com
29 Nov 2002 12:42:08 -0800


Thank to all who replied.  After giving up on continuations (which
make everything but forward branches seductively easy), I settled on
something with the following interface:

> class MonadGoto lbl gm | gm -> lbl where
>   liftG	:: Monad m => m () -> gm m ()
>   label	:: Monad m => gm m lbl
>   gotoIf	:: Monad m => m Bool -> lbl -> gm m ()

Note that, unlike a monad transformer, only ()-producing computations
can be embedded.  This limitation reflects the problem of def-use
across basic-block boundaries.  Of course, computations in the
embedded monad can be done there, then lifted, e.g.:

>    ;top <-	label
>    ;		...
>    ;		liftG (do v <- m1
>    ;			  ...
>    ;			  m2 v
>    ;			  ...)
>    ;		brPositive r3 top
>    ;      	...                   


I've implemented MonadGoto as

> newtype GotoT m a	= GotoT { unGotoT ::  WriterT [GotoLbldT m ()] LblSupply a }
>
> data GotoLbldT m a	= Label  !Lbl
>			| GotoIf (m Bool) !Lbl
>			| Inner (m a)
>
> wrL	= GotoT . tell . (:[])
> instance MonadGoto Lbl GotoT where
>   liftG	= wrL . Inner
>   label	= GotoT $ lift fromSupply >>= \l -> tell [Label l] >> return l
>   gotoIf p l	= wrL $ GotoIf p l

where GotoLbldT gets converted to 

> data GotoLbldRunT m a	= ThenLabel  { before :: m (), next :: GotoLbldRunT m a, labelLbl :: !Lbl }
> 			| ThenGotoIf { before :: m (), next :: GotoLbldRunT m a
> 				     , gotoPred :: m Bool, gotoLbl :: !Lbl }
> 			| Tail (m a)

which can then be run

> type JumpArray m v	= [(Lbl, m v)]
> runGM			:: Monad m => JumpArray m v -> GotoLbldRunT m v -> (JumpArray m v, m v)

.  My Verilog has delayed branches (because that's the easy thing to
do.)  So, I implemented a DelayedGotoT which provides for delayed
branches by shuffling the "GotoLbldT"s and using a StateT to save the
result of the gotoPred evaluation.


"Erkok, Levent" <levent.erkok@intel.com> writes:

> You need a fairly recent version of Hugs to run this
> example, November 2002 release would do (try with -98). For ghc, you need
> the CVS version, or wait till the next release. As far as I know, no other
> implementation supports mdo, nor there are any plans for it.

For the moment I've chosen to do the mdo desugaring manually instead
of moving to the CVS ghc (or exclusively using Hugs.)  Will mdo be in
the next release?  (That's 5.04.2, I think -- though I've recently
been confused about GHC releases.)  The relevant revision to Lex.lhs
is pretty recent and doesn't seem to be on ghc-5-04-branch.

        thanks,
        mike