Skip to content

Instantly share code, notes, and snippets.

@NathanHowell
Created May 8, 2012 22:16
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save NathanHowell/2639866 to your computer and use it in GitHub Desktop.
Save NathanHowell/2639866 to your computer and use it in GitHub Desktop.
int someCall(int x)
{
return x * x;
}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeFamilies #-}
module Main where
import Criterion.Main
import GHC.Generics
-- use a regular newtype
newtype Foo1 = Foo1 Int deriving (Generic, Show)
-- or with record syntax
newtype Foo2 = Foo2{foo2 :: Int} deriving (Generic, Show)
unpack
:: (Generic a, Rep a ~ M1 D c0 (M1 C c1 (M1 S c2 (K1 R c))))
=> a
-> c
unpack = unK1 . unM1 . unM1 . unM1 . from
pack
:: (Generic a, Rep a ~ M1 D c0 (M1 C c1 (M1 S c2 (K1 R c))))
=> c
-> a
pack = to . M1 . M1 . M1 . K1
-- the C import uses Ints
foreign import ccall "someCall" directCall :: Foo1 -> IO Foo2
foreign import ccall "someCall" c'genericCall :: Int -> IO Int
genericCall :: Foo1 -> IO Foo2
genericCall = fmap pack . c'genericCall . unpack
-- and our typed wrapper packs/unpacks to FFI primitives
main :: IO ()
main = defaultMain
[ bench "direct" (whnfIO (directCall (Foo1 0)))
, bench "generic" (whnfIO (genericCall (Foo1 0))) ]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment