Skip to content
Snippets Groups Projects
Commit 7ca70fbf authored by Herbert Valerio Riedel's avatar Herbert Valerio Riedel :man_dancing:
Browse files

Fix #7912 by using `CApiFFI` for `<termios.h>` imports


On Android, the functions imported from `<termios.h>` are actually
inlined functions, so we need to wrap them via the `capi` calling
convention.

Signed-off-by: Herbert Valerio Riedel's avatarHerbert Valerio Riedel <hvr@gnu.org>
parent 88bfec0c
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE CApiFFI #-}
#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE Trustworthy #-}
#endif
......@@ -331,14 +332,14 @@ inputSpeed termios = unsafePerformIO $ do
w <- c_cfgetispeed p
return (word2Baud w)
foreign import ccall unsafe "cfgetispeed"
foreign import capi unsafe "termios.h cfgetispeed"
c_cfgetispeed :: Ptr CTermios -> IO CSpeed
withInputSpeed :: TerminalAttributes -> BaudRate -> TerminalAttributes
withInputSpeed termios br = unsafePerformIO $ do
withNewTermios termios $ \p -> c_cfsetispeed p (baud2Word br)
foreign import ccall unsafe "cfsetispeed"
foreign import capi unsafe "termios.h cfsetispeed"
c_cfsetispeed :: Ptr CTermios -> CSpeed -> IO CInt
......@@ -348,14 +349,14 @@ outputSpeed termios = unsafePerformIO $ do
w <- c_cfgetospeed p
return (word2Baud w)
foreign import ccall unsafe "cfgetospeed"
foreign import capi unsafe "termios.h cfgetospeed"
c_cfgetospeed :: Ptr CTermios -> IO CSpeed
withOutputSpeed :: TerminalAttributes -> BaudRate -> TerminalAttributes
withOutputSpeed termios br = unsafePerformIO $ do
withNewTermios termios $ \p -> c_cfsetospeed p (baud2Word br)
foreign import ccall unsafe "cfsetospeed"
foreign import capi unsafe "termios.h cfsetospeed"
c_cfsetospeed :: Ptr CTermios -> CSpeed -> IO CInt
-- | @getTerminalAttributes fd@ calls @tcgetattr@ to obtain
......@@ -367,7 +368,7 @@ getTerminalAttributes (Fd fd) = do
throwErrnoIfMinus1_ "getTerminalAttributes" (c_tcgetattr fd p)
return $ makeTerminalAttributes fp
foreign import ccall unsafe "tcgetattr"
foreign import capi unsafe "termios.h tcgetattr"
c_tcgetattr :: CInt -> Ptr CTermios -> IO CInt
data TerminalState
......@@ -392,7 +393,7 @@ setTerminalAttributes (Fd fd) termios state = do
state2Int WhenDrained = (#const TCSADRAIN)
state2Int WhenFlushed = (#const TCSAFLUSH)
foreign import ccall unsafe "tcsetattr"
foreign import capi unsafe "termios.h tcsetattr"
c_tcsetattr :: CInt -> CInt -> Ptr CTermios -> IO CInt
-- | @sendBreak fd duration@ calls @tcsendbreak@ to transmit a
......@@ -402,7 +403,7 @@ sendBreak :: Fd -> Int -> IO ()
sendBreak (Fd fd) duration
= throwErrnoIfMinus1_ "sendBreak" (c_tcsendbreak fd (fromIntegral duration))
foreign import ccall unsafe "tcsendbreak"
foreign import capi unsafe "termios.h tcsendbreak"
c_tcsendbreak :: CInt -> CInt -> IO CInt
-- | @drainOutput fd@ calls @tcdrain@ to block until all output
......@@ -410,7 +411,7 @@ foreign import ccall unsafe "tcsendbreak"
drainOutput :: Fd -> IO ()
drainOutput (Fd fd) = throwErrnoIfMinus1_ "drainOutput" (c_tcdrain fd)
foreign import ccall unsafe "tcdrain"
foreign import capi unsafe "termios.h tcdrain"
c_tcdrain :: CInt -> IO CInt
......@@ -431,7 +432,7 @@ discardData (Fd fd) queue =
queue2Int OutputQueue = (#const TCOFLUSH)
queue2Int BothQueues = (#const TCIOFLUSH)
foreign import ccall unsafe "tcflush"
foreign import capi unsafe "termios.h tcflush"
c_tcflush :: CInt -> CInt -> IO CInt
data FlowAction
......@@ -453,7 +454,7 @@ controlFlow (Fd fd) action =
action2Int TransmitStop = (#const TCIOFF)
action2Int TransmitStart = (#const TCION)
foreign import ccall unsafe "tcflow"
foreign import capi unsafe "termios.h tcflow"
c_tcflow :: CInt -> CInt -> IO CInt
-- | @getTerminalProcessGroupID fd@ calls @tcgetpgrp@ to
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment