Skip to content
Snippets Groups Projects
Commit 2e1efd57 authored by sof's avatar sof
Browse files

[project @ 1999-07-08 13:51:17 by sof]

foreign export regression test
parent 2ef5da49
No related merge requests found
module For where
{-
import IOExts
import Addr
--y = putChar
count :: IORef Int -> IO Int
count ref = do
x <- readIORef ref
writeIORef ref (x+1)
return x
createCounter :: IO Addr
createCounter = do
ref <- newIORef 0
mkCounter (count ref)
foreign import "sin" msin :: Double -> IO Double
-}
foreign export "putChar" putChar :: Char -> IO ()
--foreign export "createCounter" createCounter :: IO Addr
--foreign export dynamic mkCounter :: (IO Int) -> IO Addr
TOP = ..
include $(TOP)/mk/boilerplate.mk
SRC_HC_OPTS += -fglasgow-exts -no-hs-main
CC = $(HC)
all :: runtest
include $(TOP)/mk/target.mk
Hello, world
#include "For_stub.h"
int
main(int argc, char *argv[])
{
int i;
char msg[] = "Hello, world\n";
startupHaskell(argc,argv);
for (i=0; i < sizeof(msg) - 1; i++) {
putChar(msg[i]);
}
shutdownHaskell();
}
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