Skip to content
Snippets Groups Projects
Commit 6711398b authored by Simon Marlow's avatar Simon Marlow
Browse files

add a raw callback performance benchmark

parent 0dd1973a
No related branches found
No related tags found
No related merge requests found
{-# OPTIONS_GHC -fffi #-}
-- Measure raw callback performance.
module Main where
import Control.Concurrent
import Control.Monad
import Foreign
import Foreign.C
import Data.IORef
import System.Environment
import System.IO
main = do
[s] <- getArgs
poke pcount (fromIntegral (read s))
callC =<< mkFunc (return ())
type FUNC = IO ()
foreign import ccall "&count" pcount :: Ptr CInt
foreign import ccall unsafe "wrapper"
mkFunc :: FUNC -> IO (FunPtr FUNC)
foreign import ccall threadsafe "cbits.h callC"
callC:: FunPtr FUNC -> IO ()
TOP = ../..
include $(TOP)/mk/boilerplate.mk
FAST_OPTS = 300000
NORM_OPTS = 3000000
SLOW_OPTS = 30000000
OBJS += Main_stub.o
include $(TOP)/mk/target.mk
#include "cbits.h"
int count;
void callC( FUNC* f) {
int i;
for(i=0;i<count;i++) f();
}
typedef void FUNC();
void callC( FUNC* f);
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment