Skip to content
GitLab
Menu
Projects
Groups
Snippets
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Tobias Decking
GHC
Commits
092081de
Commit
092081de
authored
Sep 01, 1999
by
sof
Browse files
[project @ 1999-09-01 14:18:54 by sof]
FFI decl tests
parent
7644077d
Changes
3
Hide whitespace changes
Inline
Side-by-side
ghc/tests/ccall/should_compile/cc004.hs
0 → 100644
View file @
092081de
-- !!! cc004 -- foreign declarations
module
ShouldCompile
where
import
Foreign
import
GlaExts
import
Int
import
Word
-- importing functions
foreign
import
stdcall
"m"
m_stdcall
::
StablePtr
a
->
IO
(
StablePtr
b
)
foreign
import
ccall
"m"
unsafe
m_ccall
::
ByteArray
Int
->
IO
Int
foreign
import
stdcall
"Math"
"sin"
my_sin
::
Double
->
IO
Double
foreign
import
stdcall
"Math"
"cos"
my_cos
::
Double
->
IO
Double
foreign
import
stdcall
"m1"
m8
::
IO
Int8
foreign
import
stdcall
"m2"
m16
::
IO
Int16
foreign
import
stdcall
"m3"
m32
::
IO
Int32
foreign
import
stdcall
"m4"
m64
::
IO
Int64
foreign
import
stdcall
dynamic
d8
::
Addr
->
IO
Int8
foreign
import
stdcall
dynamic
d16
::
Addr
->
IO
Int16
foreign
import
stdcall
dynamic
d32
::
Addr
->
IO
Int32
foreign
import
stdcall
dynamic
d64
::
Addr
->
IO
Int64
foreign
import
ccall
"kitchen"
unsafe
sink
::
ForeignObj
->
ByteArray
Int
->
MutableByteArray
Int
RealWorld
->
Int
->
Int8
->
Int16
->
Int32
->
Int64
->
Word8
->
Word16
->
Word32
->
Word64
->
Float
->
Double
->
IO
()
foreign
import
ccall
dynamic
unsafe
sink2
::
Addr
->
(
ForeignObj
->
ByteArray
Int
->
MutableByteArray
Int
RealWorld
->
Int
->
Int8
->
Int16
->
Int32
->
Word8
->
Word16
->
Word32
->
Float
->
Double
->
IO
()
)
ghc/tests/ccall/should_compile/cc005.hs
0 → 100644
View file @
092081de
-- !!! cc005 -- foreign export declarations
module
ShouldCompile
(
d8
)
where
import
Foreign
import
GlaExts
import
Int
import
Word
foreign
export
ccall
dynamic
d8
::
(
Int
->
IO
()
)
->
IO
Addr
-- exporting functions
{-
m_stdcall :: Int -> IO Int
m_stdcall x = return x
x = putChar
foreign export ccall "m1" doo :: Int -> IO Int
doo :: Eq a => a -> IO Int
doo _ = return 2
foreign export ccall "listAppend" plusplus :: StablePtr [a] -> StablePtr [a] -> IO (StablePtr [a])
plusplus :: StablePtr [a] -> StablePtr [a] -> IO (StablePtr [a])
plusplus x y = do
l1 <- deRefStablePtr x
l2 <- deRefStablePtr y
makeStablePtr (l1 ++ l2)
foreign export ccall "m11" m_stdcall :: Int -> IO Int
m_ccall :: Int -> Int -> IO Int
m_ccall x y = return (x-y)
foreign export ccall "m2" m_ccall :: Int -> Int -> IO Int
foreign export ccall "putcha" putChar :: Char -> IO ()
foreign export stdcall "Math" "sin" my_sin :: Double -> IO Double
foreign export stdcall "Math" "cos" my_cos :: Double -> IO Double
my_sin = undefined
my_cos = undefined
foreign export stdcall "m111" m8 :: IO Int8
foreign export stdcall "m22" m16 :: IO Int16
foreign export stdcall "m3" m32 :: IO Int32
foreign export stdcall "m4" m64 :: IO Int64
m8 = undefined
m16 = undefined
m32 = undefined
m64 = undefined
foreign export stdcall dynamic d8 :: (Addr -> IO Int8) -> IO Addr
foreign export stdcall dynamic d16 :: (Addr -> IO Int16) -> IO Addr
foreign export stdcall dynamic d32 :: (Addr -> IO Int32) -> IO Addr
foreign export stdcall dynamic d64 :: (Addr -> IO Int64) -> IO Addr
d8 = undefined
d16 = undefined
d32 = undefined
d64 = undefined
foreign export ccall "kitchen"
sink :: --ForeignObj
-- -> ByteArray Int
-- -> MutableByteArray Int RealWorld
Int
-> Int8
-> Int16
-> Int32
-> Int64
-> Word8
-> Word16
-> Word32
-> Word64
-> Float
-> Double
-> IO Int
sink = undefined
sink2 = undefined
foreign export ccall dynamic
sink2 :: (--ForeignObj
-- -> ByteArray Int
-- -> MutableByteArray Int RealWorld
StablePtr a
-> Int
-> Int8
-> Int16
-> Int32
-> Int64
-> Word8
-> Word16
-> Word32
-> Word64
-> Float
-> Double
-> IO ())
-> IO Addr
-}
ghc/tests/ccall/should_compile/cc007.hs
0 → 100644
View file @
092081de
-- !!! cc007 -- foreign import with external name equal to Haskell name.
module
Test
where
foreign
import
sine
::
Double
->
Double
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment