#1349: Generalise the ! and UNPACK mechanism for data types, to unpack function arguments ---------------------------------+------------------------------------------ Reporter: simonpj | Owner: Type: task | Status: new Priority: normal | Milestone: 6.12.3 Component: Compiler | Version: 6.6.1 Keywords: | Difficulty: Unknown Os: Unknown/Multiple | Testcase: Architecture: Unknown/Multiple | Failure: None/Unknown ---------------------------------+------------------------------------------
Comment(by tibbe): It's a bit tricky to come up with a good example as inlining seems to remove the problem for simple cases. Here's an attempt. Given the module: {{{ module Cont (run) where type Cont = (Int -> Int) -> Int -> Int g :: Cont g k n = let n' = n + 1 in n' `seq` k n' loop :: Int -> Cont loop 0 = id loop n = g . loop (n - 1) run = loop 10 id }}} we get the Core {{{ Cont.$wloop :: Int# -> (Int -> Int) -> Int -> Int Cont.$wloop = \ (ww_shX :: Int#) -> case ww_shX of ds_Xhe { __DEFAULT -> let { g_si5 :: (Int -> Int) -> Int -> Int g_si5 = Cont.$wloop (-# ds_Xhe 1) } in \ (x_ahg :: Int -> Int) -> let { k_si7 [ALWAYS Just L] :: Int -> Int k_si7 = g_si5 x_ahg } in \ (n_adm :: Int) -> case n_adm of _ { I# x1_ahv -> k_si7 (I# (+# x1_ahv 1)) }; 0 -> id @ (Int -> Int) } Cont.run :: Int -> Int Cont.run = Cont.$wloop 10 (id @ Int) }}} However, manual unboxing {{{ {-# LANGUAGE MagicHash #-} module Cont2 (run) where import GHC.Prim import GHC.Base type Cont = (Int# -> Int) -> Int# -> Int g :: Cont g k n = k (n +# 1#) loop :: Int -> Cont loop 0 = id loop n = g . loop (n - 1) run = loop 10 (\i -> (I# i)) }}} gives {{{ Cont2.$wloop :: Int# -> (Int# -> Int) -> Int# -> Int Cont2.$wloop = \ (ww_shs :: Int#) -> case ww_shs of ds_XgX { __DEFAULT -> let { g_shA :: (Int# -> Int) -> Int# -> Int g_shA = Cont2.$wloop (-# ds_XgX 1) } in \ (x_agX :: Int# -> Int) -> let { k_shC [ALWAYS Just L] :: Int# -> Int k_shC = g_shA x_agX } in \ (n_adn :: Int#) -> k_shC (+# n_adn 1); 0 -> id @ (Int# -> Int) } Cont2.run :: Int# -> Int Cont2.run = Cont2.$wloop 10 I# }}} I'd like to be able to express that `Cont`'s first parameter (of type `Int -> Int`) is strict in its first (and only) arguments and that I want it unboxed. -- Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/1349#comment:21> 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