[commit: packages/unix] master: Fix #7912 by using `CApiFFI` for `<termios.h>` imports (7ca70fb)

git at git.haskell.org git at git.haskell.org
Thu Nov 7 12:25:38 UTC 2013


Repository : ssh://git@git.haskell.org/unix

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/7ca70fbf7b82bcca945669d043673a06973c1edf/unix

>---------------------------------------------------------------

commit 7ca70fbf7b82bcca945669d043673a06973c1edf
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Thu Nov 7 13:22:34 2013 +0100

    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 <hvr at gnu.org>


>---------------------------------------------------------------

7ca70fbf7b82bcca945669d043673a06973c1edf
 System/Posix/Terminal/Common.hsc |   21 +++++++++++----------
 1 file changed, 11 insertions(+), 10 deletions(-)

diff --git a/System/Posix/Terminal/Common.hsc b/System/Posix/Terminal/Common.hsc
index 4075ba3..e43a59a 100644
--- a/System/Posix/Terminal/Common.hsc
+++ b/System/Posix/Terminal/Common.hsc
@@ -1,3 +1,4 @@
+{-# 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



More information about the ghc-commits mailing list