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

[project @ 2000-09-05 12:35:09 by simonmar]

Use newtype Ptr instead of just Addr, test newtypes in foreign decls.
parent acedd0b2
No related merge requests found
import Foreign
import Monad
newtype Ptr a = Ptr Addr
unPtr (Ptr x) = x
type CInt = Int32
type CSize = Word32
foreign export dynamic mkComparator :: (Addr -> Addr -> IO CInt) -> IO Addr
foreign import qsort :: Addr -> CSize -> CSize -> Addr -> IO ()
foreign export dynamic
mkComparator :: (Ptr Int -> Ptr Int -> IO CInt)
-> IO (Ptr (Ptr Int -> Ptr Int -> IO CInt))
foreign import
qsort :: Addr -> CSize -> CSize -> Ptr (Ptr Int -> Ptr Int -> IO CInt)
-> IO ()
compareInts :: Addr -> Addr -> IO CInt
compareInts :: Ptr Int -> Ptr Int -> IO CInt
compareInts a1 a2 = do
i1 <- peek a1
i2 <- peek a2
i1 <- peek (unPtr a1)
i2 <- peek (unPtr a2)
return (fromIntegral (i1 - i2 :: Int))
main :: IO ()
......
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