[GHC] #9038: Foreign calls don't make their arguments look strict

GHC ghc-devs at haskell.org
Thu May 1 13:10:57 UTC 2014


#9038: Foreign calls don't make their arguments look strict
-------------------------------------+------------------------------------
        Reporter:  tibbe             |            Owner:
            Type:  bug               |           Status:  new
        Priority:  normal            |        Milestone:
       Component:  Compiler          |          Version:  7.8.2
      Resolution:                    |         Keywords:
Operating System:  Unknown/Multiple  |     Architecture:  Unknown/Multiple
 Type of failure:  None/Unknown      |       Difficulty:  Unknown
       Test Case:                    |       Blocked By:
        Blocking:                    |  Related Tickets:  1592
-------------------------------------+------------------------------------

Comment (by tibbe):

 Here's a trivially simple example:

 Test.hs:
 {{{
 {-# LANGUAGE BangPatterns #-}
 module Test ( f ) where

 f :: Int -> IO ()
 f !val = do
     cFunction1
     cFunction2 val

 foreign import ccall unsafe "function1" cFunction1 :: IO ()
 foreign import ccall unsafe "function2" cFunction2 :: Int -> IO ()
 }}}

 Compile with:

 {{{
 ghc -c -O2 -ddump-simpl Test.hs
 }}}

 Here's the core:

 {{{
 f1 :: Int -> State# RealWorld -> (# State# RealWorld, () #)
 f1 =
   \ (val_aeK :: Int) (eta_B1 :: State# RealWorld) ->
     case val_aeK of _ { I# ipv_sfl ->
     case {__pkg_ccall main function1 State# RealWorld
                             -> (# State# RealWorld #)}_df8
            eta_B1
     of _ { (# ds_df6 #) ->
     case {__pkg_ccall main function2 Int#
                             -> State# RealWorld -> (# State# RealWorld
 #)}_df4
            ipv_sfl ds_df6
     of _ { (# ds1_df2 #) ->
     (# ds1_df2, () #)
     }
     }
     }

 f :: Int -> IO ()
 f = f1 `cast` ...
 }}}

 Adding the bang pattern has one effect: the argument gets unboxed earlier.
 It doesn't make the function take an unboxed argument however (i.e.
 there's no worker-wrapper).

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9038#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list