[GHC] #7649: BangPatterns + ViewPatterns
GHC
cvs-ghc at haskell.org
Fri Feb 1 18:31:21 CET 2013
#7649: BangPatterns + ViewPatterns
---------------------------------+------------------------------------------
Reporter: igloo | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Keywords: | Os: Unknown/Multiple
Architecture: Unknown/Multiple | Failure: None/Unknown
Difficulty: Unknown | Testcase:
Blockedby: | Blocking:
Related: |
---------------------------------+------------------------------------------
This program:
{{{
{-# LANGUAGE ViewPatterns, BangPatterns #-}
import Control.Exception
main :: IO ()
main = do print (f False)
print (f True)
print (g undefined) `catchE` \_ -> putStrLn "g exception"
print (h undefined) `catchE` \_ -> putStrLn "h exception"
print (i undefined) `catchE` \_ -> putStrLn "i exception"
putStrLn "Done"
f :: Bool -> String
f (view -> Nothing) = "Got Nothing"
f (view -> Just x) = "Got Just " ++ show x
g :: Bool -> String
g (view -> x) = "g Got something"
h :: Bool -> String
h (view -> !x) = "h Got something"
i :: Bool -> String
i !(view -> x) = "i Got something"
view :: Bool -> Maybe Int
view False = Nothing
view True = Just 5
catchE :: IO a -> (ErrorCall -> IO a) -> IO a
catchE = catch
}}}
prints:
{{{
"Got Nothing"
"Got Just 5"
"g Got something"
"h exception
"i Got something"
Done
}}}
but presumably `i` ought to be strict in `x`.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7649>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list