[Haskell-cafe] help for the usage on mfix

Gang Yu yugang.bj at gmail.com
Wed Feb 23 07:46:04 CET 2011


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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110223/87485fb1/attachment.htm>


More information about the Haskell-Cafe mailing list