Skip to content
Snippets Groups Projects
Commit 2403c204 authored by sof's avatar sof
Browse files

[project @ 1999-10-26 08:41:54 by sof]

Foreign imports that use ByteArrays now need to be marked as being 'unsafe.'
parent 019d2244
No related merge requests found
......@@ -47,7 +47,7 @@ import ByteArray(ByteArray)
import Char(ord, chr)
import CString(packString, unpackCStringIO)
import IO(Handle)
import IOExts(IORef, newIORef, readIORef, writeIORef, unsafePerformIO)
import IOExts(IORef, newIORef, readIORef, writeIORef, unsafePerformIO, freeHaskellFunctionPtr)
import Maybe(fromMaybe)
import Monad(when)
import Posix(intToFd, fdToHandle)
......@@ -75,8 +75,8 @@ type RlCallbackFunction =
rlInitialize :: IO ()
rlInitialize = rlSetReadlineName =<< getProgName
foreign import ccall "free" free :: Addr -> IO ()
foreign import ccall "readline" readlineAux :: ByteArray Int -> IO Addr
foreign import "free" unsafe free :: Addr -> IO ()
foreign import "readline" unsafe readlineAux :: ByteArray Int -> IO Addr
readline :: String -- Prompt String
-> IO (Maybe String) -- Just returned line or Nothing if EOF
......@@ -88,15 +88,15 @@ readline prompt = do
free cstr
return (Just str)
foreign import ccall "add_history" add_history :: ByteArray Int -> IO ()
foreign import "add_history" unsafe add_history :: ByteArray Int -> IO ()
addHistory :: String -- String to enter in history
-> IO ()
addHistory = add_history . packString
foreign export ccall dynamic mkRlCallback :: (Int -> Int -> IO Int) -> IO Addr
foreign import ccall "rl_bind_key" rl_bind_key :: Int -> Addr -> IO Int
foreign export dynamic mkRlCallback :: (Int -> Int -> IO Int) -> IO Addr
foreign import "rl_bind_key" rl_bind_key :: Int -> Addr -> IO Int
rlBindKey :: KeyCode -- Key to Bind to
-> RlCallbackFunction -- Function to exec on execution
......@@ -106,7 +106,7 @@ rlBindKey key cback = do
ok <- rl_bind_key (ord key) cbAddr
if ok /= 0 then wrongKeyCode else addCbackEntry key cbAddr
foreign import ccall "rl_add_defun" rl_add_defun :: ByteArray Int -> Addr -> Int -> IO Int
foreign import "rl_add_defun" unsafe rl_add_defun :: ByteArray Int -> Addr -> Int -> IO Int
rlAddDefun :: String -> -- Function Name
RlCallbackFunction -> -- Function to call
......@@ -126,8 +126,6 @@ wrongKeyCode = ioError (userError "Invalid ASCII Key Code, must be in range 0..2
theCbackTable :: IORef [(KeyCode,Addr)]
theCbackTable = unsafePerformIO (newIORef [])
foreign import ccall "freeHaskellFunctionPtr" freeHaskellFunctionPtr :: Addr -> IO ()
addCbackEntry :: KeyCode -> Addr -> IO ()
addCbackEntry key cbAddr = do
cbackTable <- readIORef theCbackTable
......
......@@ -26,7 +26,6 @@ import Monad
import Maybe
import PrelIOBase
import PosixUtil (fdToInt)
\end{code}
This stuff should really be done using HDirect.
......@@ -75,7 +74,7 @@ getFd h = do
f <- handleToFd h
return (f,h)
foreign import "selectFrom__"
foreign import "selectFrom__" unsafe
selectFrom__ :: ByteArray Int
-> ByteArray Int
-> ByteArray Int
......@@ -113,16 +112,16 @@ marshallFDs ls = do
ba <- stToIO (unsafeFreezeByteArray ba)
return (x, ba)
foreign import "is_fd_set__"
foreign import "is_fd_set__" unsafe
is_fd_set :: ByteArray Int -> Int -> IO Int
foreign import "fd_zero__"
foreign import "fd_zero__" unsafe
fd_zero :: MutableByteArray RealWorld Int -> IO ()
foreign import "fd_set__"
foreign import "fd_set__" unsafe
fd_set :: MutableByteArray RealWorld Int -> Int -> IO ()
foreign import "sizeof_fd_set__"
foreign import "sizeof_fd_set__" unsafe
sizeof_fd_set :: Int
\end{code}
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