Re: [Haskell-cafe] help for the usage on mfix

2011-02-23 Thread Ryan Ingram
Just write a loop:

 let loop gs gu
| Just z - find_obj gu usyms = do
...
(gs', gu') - handle_obj_ar ...
loop gs' gu'
| otherwise = return (gs,gu)
 (gs, gu) - loop def undef

mfix is for when you have mutually recursive data but you want the IO
operation to only execute once.  It's most useful when working with some
sort of lazy data structure like a list, tree, or graph.

I can't come up with an example for IO off the top of my head, but for the
ICFP contest this year I wrote a gate/wire embedded language which had code
that looks like this:

sample wireIn = do
   rec
   (wireOut,a) - gate (wireIn,d)
   (d,b) - gate (a, b)
   return wireOut

which would create a circuit like this:

---in-[  ]--out
  +-d-[  ]--a--[  ]-d---+
  | +-b-[  ]-b-+ |
  | +---+ |
  +---+

This code translates to something like

sample wireIn = do
(wireOut, _, _, _) - mfix $ \(_, b, d) - do
(wireOut', a) - gate (wireIn, d)
(d', b') - gate (a,b)
return (wireOut', b', d')
return wireOut'

The key is that gate was lazy in its arguments; the gate didn't care what
its input wires were, it just needed them to exist at the time you asked for
the entire circuit definition.  mfix says 'run the *effects* in this code
once, but the *data* might be recursive'.

  -- ryan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] help for the usage on mfix

2011-02-22 Thread Gang Yu
hello cafe,

  I just want to do cursion to a fixpoint in an IO function, I write sth.
like this,

handle_ar::(Set String,Set String)-FilePath- IO (Set String, Set String)
handle_ar (def,undef) ar=do
  let gs = def
  gu = undef
  syms - liftM (map (\x - (symb x, x))) $ defined_syms ar
  usyms - liftM (map (\x - (symb x, x))) $ undefined_syms ar
  mfix (\(gs,gu) - do
   case find_obj gu usyms of Nothing - return (gs,gu)
 Just z -
   do
 let
   fout = fromList . map fst .
filter ((== (objf z)) . objf . snd)
   ls = fout syms
   lu = fout usyms
 handle_obj_ar (gs,gu) (ls,lu))
What I want to express is:

gs and gu are initiliazed to def and undef, then do recursion until
find_obj gu usyms is nothing, i.e, (gs,gu) reaches a fixpoint (suppose
handle_obj_ar always change the pair).

I am not sure I am on the right track since there is no room for def and
undef stand in the function.

Anyone can help?

thanks a lot.

Gang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe