#2798: Enable "rec" keyword when RecursiveDo is enabled?
---------------------------------+------------------------------------------
    Reporter:  nominolo          |       Owner:                  
        Type:  task              |      Status:  new             
    Priority:  normal            |   Component:  Compiler        
     Version:  6.11              |    Severity:  minor           
    Keywords:                    |    Testcase:                  
Architecture:  Unknown/Multiple  |          Os:  Unknown/Multiple
---------------------------------+------------------------------------------
 GHC supports recursive statement groups marked by the keyword {{{rec}}},
 however this is only activated via a hack.  Consider this (silly) example
 program:
 {{{
 {-# LANGUAGE RecursiveDo, Arrows #-}

 main :: IO ()

 main =
  mdo x <- return (length [1..42::Int])
      rec b <- return x
          let a = const c
          c <- print "x"
      return (a b)
 }}}
 The {{{Arrow}}} language needs to be enabled, otherwise the {{{rec}}}
 keyword wouldn't be recognised.  Currently this behaviour is undocumented,
 and {{{rec}}} groups only appear in the internal AST.

 This ticket has been created to have a documented decsion whether this
 feature is supported or not.  Given that GHC automatically identifies
 strongly-connected components and re-groups things (although it cannot re-
 order statements due to probable dependencies) having an explicet
 {{{rec}}} keyword probably isn't that useful.  In particular
 {{{
 mdo foo   ...is equivalent to...      mdo rec foo
     bar                                       bar
     baz                                   baz
 }}}
 Thoughts?

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2798>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to