#2806: Require bang-patterns for unlifted bindings
---------------------------------+------------------------------------------
    Reporter:  simonpj           |       Owner:                  
        Type:  feature request   |      Status:  new             
    Priority:  normal            |   Milestone:  6.12 branch     
   Component:  Compiler          |     Version:  6.8.3           
    Severity:  normal            |    Keywords:                  
  Difficulty:  Unknown           |    Testcase:                  
Architecture:  Unknown/Multiple  |          Os:  Unknown/Multiple
---------------------------------+------------------------------------------
 GHC allows let/where bindings for unlifted values, but they are
 necessarily ''strict''.  That does lead to confusing behaviour.  For
 example, 'f' and 'g' behave differently here:
 {{{
     {-# LANGUAGE MagicHash #-}

     import GHC.Base
     import GHC.Exts

     main :: IO ()
     main = do print (I# (f 5# 0#))
               print (I# (g 4# 0#))

     f :: Int# -> Int# -> Int#
     f x y | False = x `divInt#` y
     f x y = x

     g :: Int# -> Int# -> Int#
     g x y | False = z
         where z = x `divInt#` y
     g x y = x
 }}}
 Suggestion: require that an unlifted let/where binding has a bang on it.
 That would make lifted and unlifted bindings behave uniformly.

 Simon

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

Reply via email to