
Something for SimonPJ
----- Forwarded message from Reiner Pope
{-# LANGUAGE BangPatterns #-}
module Test(ans1,ans2) where
import Prelude hiding(Maybe(..))
data Maybe a = Just !a | Nothing
Nothing `mapp` Just b = Just b Just a `mapp` Just b = Just (max a b)
ans1 = g1 Nothing (0::Int)
g1 m !n = case m of Nothing -> if n > 10 then m else g1 (m `mapp` Just n) (n+1) Just x -> if n > 10 then m else g1 (m `mapp` Just n) (n+1)
ans2 = g2 Nothing (0::Int)
g2 m !n = expose m (if n > 10 then m else g2 (m `mapp` Just n) (n+1)) expose Nothing b = b expose (Just a) b = a `seq` b
On a similar note, when I was having difficulties with this problem, I started to wonder if it would be possible to come up with a more direct way to tell GHC, "do SpecConstr on this variable". From reading the source code of the stream-fusion package, it seems that the current way of doing this is with 'expose' functions like I wrote below. Could we instead have a {-# SPECCONSTR #-} pragma, to be used on function arguments, like: foo {-# SPECCONSTR #-} x y {-# SPECCONSTR #-} z = ... This pragma should say to the GHC something like "ignore conditions H2, H5 and H6 of the SpecConstr paper, for this function and this argument". Cheers, Reiner _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ----- End forwarded message -----