{-# LINE 1 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
{-# LANGUAGE CApiFFI #-}
{-# LANGUAGE Trustworthy #-}
{-# LINE 22 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
module System.Posix.Terminal.Common (
  
  
  TerminalAttributes,
  getTerminalAttributes,
  TerminalState(..),
  setTerminalAttributes,
  CTermios,
  TerminalMode(..),
  withoutMode,
  withMode,
  terminalMode,
  bitsPerByte,
  withBits,
  ControlCharacter(..),
  controlChar,
  withCC,
  withoutCC,
  inputTime,
  withTime,
  minInput,
  withMinInput,
  BaudRate(..),
  inputSpeed,
  withInputSpeed,
  outputSpeed,
  withOutputSpeed,
  
  sendBreak,
  drainOutput,
  QueueSelector(..),
  discardData,
  FlowAction(..),
  controlFlow,
  
  getTerminalProcessGroupID,
  setTerminalProcessGroupID,
  
  queryTerminal,
  ) where
import Data.Bits
import Data.Char
import Foreign.C.Error ( throwErrnoIfMinus1, throwErrnoIfMinus1_ )
import Foreign.C.Types
import Foreign.ForeignPtr ( ForeignPtr, withForeignPtr, mallocForeignPtrBytes )
import Foreign.Marshal.Utils ( copyBytes )
import Foreign.Ptr ( Ptr, plusPtr )
import Foreign.Storable ( Storable(..) )
import System.IO.Unsafe ( unsafePerformIO )
import System.Posix.Types
import System.Posix.Internals ( CTermios )
{-# LINE 91 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
newtype TerminalAttributes = TerminalAttributes (ForeignPtr CTermios)
makeTerminalAttributes :: ForeignPtr CTermios -> TerminalAttributes
makeTerminalAttributes :: ForeignPtr CTermios -> TerminalAttributes
makeTerminalAttributes = ForeignPtr CTermios -> TerminalAttributes
TerminalAttributes
withTerminalAttributes :: TerminalAttributes -> (Ptr CTermios -> IO a) -> IO a
withTerminalAttributes :: TerminalAttributes -> (Ptr CTermios -> IO a) -> IO a
withTerminalAttributes (TerminalAttributes ForeignPtr CTermios
termios) = ForeignPtr CTermios -> (Ptr CTermios -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr CTermios
termios
data TerminalMode
        
   = InterruptOnBreak           
   | MapCRtoLF                  
   | IgnoreBreak                
   | IgnoreCR                   
   | IgnoreParityErrors         
   | MapLFtoCR                  
   | CheckParity                
   | StripHighBit               
   | StartStopInput             
   | StartStopOutput            
   | MarkParityErrors           
        
   | ProcessOutput              
        
        
        
        
        
   | LocalMode                  
   | ReadEnable                 
   | TwoStopBits                
   | HangupOnClose              
   | EnableParity               
   | OddParity                  
        
   | EnableEcho                 
   | EchoErase                  
   | EchoKill                   
   | EchoLF                     
   | ProcessInput               
   | ExtendedFunctions          
   | KeyboardInterrupts         
   | NoFlushOnInterrupt         
   | BackgroundWriteInterrupt   
withoutMode :: TerminalAttributes -> TerminalMode -> TerminalAttributes
withoutMode :: TerminalAttributes -> TerminalMode -> TerminalAttributes
withoutMode TerminalAttributes
termios TerminalMode
InterruptOnBreak = CTcflag -> TerminalAttributes -> TerminalAttributes
clearInputFlag (CTcflag
2) TerminalAttributes
termios
{-# LINE 146 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios MapCRtoLF = clearInputFlag (256) termios
{-# LINE 147 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios IgnoreBreak = clearInputFlag (1) termios
{-# LINE 148 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios IgnoreCR = clearInputFlag (128) termios
{-# LINE 149 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios IgnoreParityErrors = clearInputFlag (4) termios
{-# LINE 150 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios MapLFtoCR = clearInputFlag (64) termios
{-# LINE 151 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios CheckParity = clearInputFlag (16) termios
{-# LINE 152 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios StripHighBit = clearInputFlag (32) termios
{-# LINE 153 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios StartStopInput = clearInputFlag (4096) termios
{-# LINE 154 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios StartStopOutput = clearInputFlag (1024) termios
{-# LINE 155 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios MarkParityErrors = clearInputFlag (8) termios
{-# LINE 156 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios ProcessOutput = clearOutputFlag (1) termios
{-# LINE 157 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios LocalMode = clearControlFlag (2048) termios
{-# LINE 158 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios ReadEnable = clearControlFlag (128) termios
{-# LINE 159 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios TwoStopBits = clearControlFlag (64) termios
{-# LINE 160 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios HangupOnClose = clearControlFlag (1024) termios
{-# LINE 161 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios EnableParity = clearControlFlag (256) termios
{-# LINE 162 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios OddParity = clearControlFlag (512) termios
{-# LINE 163 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios EnableEcho = clearLocalFlag (8) termios
{-# LINE 164 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios EchoErase = clearLocalFlag (16) termios
{-# LINE 165 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios EchoKill = clearLocalFlag (32) termios
{-# LINE 166 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios EchoLF = clearLocalFlag (64) termios
{-# LINE 167 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios ProcessInput = clearLocalFlag (2) termios
{-# LINE 168 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios ExtendedFunctions = clearLocalFlag (32768) termios
{-# LINE 169 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios KeyboardInterrupts = clearLocalFlag (1) termios
{-# LINE 170 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios NoFlushOnInterrupt = setLocalFlag (128) termios
{-# LINE 171 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios BackgroundWriteInterrupt = clearLocalFlag (256) termios
{-# LINE 172 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode :: TerminalAttributes -> TerminalMode -> TerminalAttributes
withMode :: TerminalAttributes -> TerminalMode -> TerminalAttributes
withMode TerminalAttributes
termios TerminalMode
InterruptOnBreak = CTcflag -> TerminalAttributes -> TerminalAttributes
setInputFlag (CTcflag
2) TerminalAttributes
termios
{-# LINE 175 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios MapCRtoLF = setInputFlag (256) termios
{-# LINE 176 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios IgnoreBreak = setInputFlag (1) termios
{-# LINE 177 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios IgnoreCR = setInputFlag (128) termios
{-# LINE 178 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios IgnoreParityErrors = setInputFlag (4) termios
{-# LINE 179 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios MapLFtoCR = setInputFlag (64) termios
{-# LINE 180 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios CheckParity = setInputFlag (16) termios
{-# LINE 181 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios StripHighBit = setInputFlag (32) termios
{-# LINE 182 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios StartStopInput = setInputFlag (4096) termios
{-# LINE 183 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios StartStopOutput = setInputFlag (1024) termios
{-# LINE 184 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios MarkParityErrors = setInputFlag (8) termios
{-# LINE 185 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios ProcessOutput = setOutputFlag (1) termios
{-# LINE 186 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios LocalMode = setControlFlag (2048) termios
{-# LINE 187 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios ReadEnable = setControlFlag (128) termios
{-# LINE 188 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios TwoStopBits = setControlFlag (64) termios
{-# LINE 189 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios HangupOnClose = setControlFlag (1024) termios
{-# LINE 190 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios EnableParity = setControlFlag (256) termios
{-# LINE 191 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios OddParity = setControlFlag (512) termios
{-# LINE 192 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios EnableEcho = setLocalFlag (8) termios
{-# LINE 193 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios EchoErase = setLocalFlag (16) termios
{-# LINE 194 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios EchoKill = setLocalFlag (32) termios
{-# LINE 195 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios EchoLF = setLocalFlag (64) termios
{-# LINE 196 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios ProcessInput = setLocalFlag (2) termios
{-# LINE 197 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios ExtendedFunctions = setLocalFlag (32768) termios
{-# LINE 198 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios KeyboardInterrupts = setLocalFlag (1) termios
{-# LINE 199 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios NoFlushOnInterrupt = clearLocalFlag (128) termios
{-# LINE 200 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios BackgroundWriteInterrupt = setLocalFlag (256) termios
{-# LINE 201 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode :: TerminalMode -> TerminalAttributes -> Bool
terminalMode :: TerminalMode -> TerminalAttributes -> Bool
terminalMode TerminalMode
InterruptOnBreak = CTcflag -> TerminalAttributes -> Bool
testInputFlag (CTcflag
2)
{-# LINE 204 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode MapCRtoLF = testInputFlag (256)
{-# LINE 205 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode IgnoreBreak = testInputFlag (1)
{-# LINE 206 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode IgnoreCR = testInputFlag (128)
{-# LINE 207 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode IgnoreParityErrors = testInputFlag (4)
{-# LINE 208 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode MapLFtoCR = testInputFlag (64)
{-# LINE 209 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode CheckParity = testInputFlag (16)
{-# LINE 210 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode StripHighBit = testInputFlag (32)
{-# LINE 211 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode StartStopInput = testInputFlag (4096)
{-# LINE 212 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode StartStopOutput = testInputFlag (1024)
{-# LINE 213 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode MarkParityErrors = testInputFlag (8)
{-# LINE 214 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode ProcessOutput = testOutputFlag (1)
{-# LINE 215 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode LocalMode = testControlFlag (2048)
{-# LINE 216 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode ReadEnable = testControlFlag (128)
{-# LINE 217 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode TwoStopBits = testControlFlag (64)
{-# LINE 218 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode HangupOnClose = testControlFlag (1024)
{-# LINE 219 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode EnableParity = testControlFlag (256)
{-# LINE 220 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode OddParity = testControlFlag (512)
{-# LINE 221 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode EnableEcho = testLocalFlag (8)
{-# LINE 222 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode EchoErase = testLocalFlag (16)
{-# LINE 223 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode EchoKill = testLocalFlag (32)
{-# LINE 224 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode EchoLF = testLocalFlag (64)
{-# LINE 225 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode ProcessInput = testLocalFlag (2)
{-# LINE 226 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode ExtendedFunctions = testLocalFlag (32768)
{-# LINE 227 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode KeyboardInterrupts = testLocalFlag (1)
{-# LINE 228 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode NoFlushOnInterrupt = not . testLocalFlag (128)
{-# LINE 229 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode BackgroundWriteInterrupt = testLocalFlag (256)
{-# LINE 230 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
bitsPerByte :: TerminalAttributes -> Int
bitsPerByte :: TerminalAttributes -> Int
bitsPerByte TerminalAttributes
termios = IO Int -> Int
forall a. IO a -> a
unsafePerformIO (IO Int -> Int) -> IO Int -> Int
forall a b. (a -> b) -> a -> b
$ do
  TerminalAttributes -> (Ptr CTermios -> IO Int) -> IO Int
forall a. TerminalAttributes -> (Ptr CTermios -> IO a) -> IO a
withTerminalAttributes TerminalAttributes
termios ((Ptr CTermios -> IO Int) -> IO Int)
-> (Ptr CTermios -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Ptr CTermios
p -> do
    CTcflag
cflag <- ((\Ptr CTermios
hsc_ptr -> Ptr CTermios -> Int -> IO CTcflag
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr CTermios
hsc_ptr Int
8)) Ptr CTermios
p
{-# LINE 235 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    return $! (word2Bits (cflag .&. (48)))
{-# LINE 236 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  where
    word2Bits :: CTcflag -> Int
    word2Bits :: CTcflag -> Int
word2Bits CTcflag
x =
        if CTcflag
x CTcflag -> CTcflag -> Bool
forall a. Eq a => a -> a -> Bool
== (CTcflag
0) then Int
5
{-# LINE 240 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
        else if CTcflag
x CTcflag -> CTcflag -> Bool
forall a. Eq a => a -> a -> Bool
== (CTcflag
16) then Int
6
{-# LINE 241 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
        else if CTcflag
x CTcflag -> CTcflag -> Bool
forall a. Eq a => a -> a -> Bool
== (CTcflag
32) then Int
7
{-# LINE 242 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
        else if CTcflag
x CTcflag -> CTcflag -> Bool
forall a. Eq a => a -> a -> Bool
== (CTcflag
48) then Int
8
{-# LINE 243 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
        else Int
0
withBits :: TerminalAttributes -> Int -> TerminalAttributes
withBits :: TerminalAttributes -> Int -> TerminalAttributes
withBits TerminalAttributes
termios Int
bits = IO TerminalAttributes -> TerminalAttributes
forall a. IO a -> a
unsafePerformIO (IO TerminalAttributes -> TerminalAttributes)
-> IO TerminalAttributes -> TerminalAttributes
forall a b. (a -> b) -> a -> b
$ do
  TerminalAttributes
-> (Ptr CTermios -> IO ()) -> IO TerminalAttributes
forall a.
TerminalAttributes
-> (Ptr CTermios -> IO a) -> IO TerminalAttributes
withNewTermios TerminalAttributes
termios ((Ptr CTermios -> IO ()) -> IO TerminalAttributes)
-> (Ptr CTermios -> IO ()) -> IO TerminalAttributes
forall a b. (a -> b) -> a -> b
$ \Ptr CTermios
p -> do
    CTcflag
cflag <- ((\Ptr CTermios
hsc_ptr -> Ptr CTermios -> Int -> IO CTcflag
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr CTermios
hsc_ptr Int
8)) Ptr CTermios
p
{-# LINE 249 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 8)) p
{-# LINE 250 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
       ((cflag .&. complement (48)) .|. mask bits)
{-# LINE 251 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  where
    mask :: Int -> CTcflag
    mask :: Int -> CTcflag
mask Int
5 = (CTcflag
0)
{-# LINE 254 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    mask 6 = (16)
{-# LINE 255 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    mask 7 = (32)
{-# LINE 256 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    mask 8 = (48)
{-# LINE 257 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    mask _ = error "withBits bit value out of range [5..8]"
data ControlCharacter
  = EndOfFile           
  | EndOfLine           
  | Erase               
  | Interrupt           
  | Kill                
  | Quit                
  | Start               
  | Stop                
  | Suspend             
controlChar :: TerminalAttributes -> ControlCharacter -> Maybe Char
controlChar :: TerminalAttributes -> ControlCharacter -> Maybe Char
controlChar TerminalAttributes
termios ControlCharacter
cc = IO (Maybe Char) -> Maybe Char
forall a. IO a -> a
unsafePerformIO (IO (Maybe Char) -> Maybe Char) -> IO (Maybe Char) -> Maybe Char
forall a b. (a -> b) -> a -> b
$ do
  TerminalAttributes
-> (Ptr CTermios -> IO (Maybe Char)) -> IO (Maybe Char)
forall a. TerminalAttributes -> (Ptr CTermios -> IO a) -> IO a
withTerminalAttributes TerminalAttributes
termios ((Ptr CTermios -> IO (Maybe Char)) -> IO (Maybe Char))
-> (Ptr CTermios -> IO (Maybe Char)) -> IO (Maybe Char)
forall a b. (a -> b) -> a -> b
$ \Ptr CTermios
p -> do
    let c_cc :: Ptr b
c_cc = ((\Ptr CTermios
hsc_ptr -> Ptr CTermios
hsc_ptr Ptr CTermios -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
17)) Ptr CTermios
p
{-# LINE 274 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    val <- peekElemOff c_cc (cc2Word cc)
    if CCc
val CCc -> CCc -> Bool
forall a. Eq a => a -> a -> Bool
== ((CCc
0)::CCc)
{-# LINE 276 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
       then Maybe Char -> IO (Maybe Char)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Char
forall a. Maybe a
Nothing
       else Maybe Char -> IO (Maybe Char)
forall (m :: * -> *) a. Monad m => a -> m a
return (Char -> Maybe Char
forall a. a -> Maybe a
Just (Int -> Char
chr (CCc -> Int
forall a. Enum a => a -> Int
fromEnum CCc
val)))
withCC :: TerminalAttributes
       -> (ControlCharacter, Char)
       -> TerminalAttributes
withCC :: TerminalAttributes
-> (ControlCharacter, Char) -> TerminalAttributes
withCC TerminalAttributes
termios (ControlCharacter
cc, Char
c) = IO TerminalAttributes -> TerminalAttributes
forall a. IO a -> a
unsafePerformIO (IO TerminalAttributes -> TerminalAttributes)
-> IO TerminalAttributes -> TerminalAttributes
forall a b. (a -> b) -> a -> b
$ do
  TerminalAttributes
-> (Ptr CTermios -> IO ()) -> IO TerminalAttributes
forall a.
TerminalAttributes
-> (Ptr CTermios -> IO a) -> IO TerminalAttributes
withNewTermios TerminalAttributes
termios ((Ptr CTermios -> IO ()) -> IO TerminalAttributes)
-> (Ptr CTermios -> IO ()) -> IO TerminalAttributes
forall a b. (a -> b) -> a -> b
$ \Ptr CTermios
p -> do
    let c_cc :: Ptr b
c_cc = ((\Ptr CTermios
hsc_ptr -> Ptr CTermios
hsc_ptr Ptr CTermios -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
17)) Ptr CTermios
p
{-# LINE 285 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    pokeElemOff c_cc (cc2Word cc) (fromIntegral (ord c) :: CCc)
withoutCC :: TerminalAttributes
          -> ControlCharacter
          -> TerminalAttributes
withoutCC :: TerminalAttributes -> ControlCharacter -> TerminalAttributes
withoutCC TerminalAttributes
termios ControlCharacter
cc = IO TerminalAttributes -> TerminalAttributes
forall a. IO a -> a
unsafePerformIO (IO TerminalAttributes -> TerminalAttributes)
-> IO TerminalAttributes -> TerminalAttributes
forall a b. (a -> b) -> a -> b
$ do
  TerminalAttributes
-> (Ptr CTermios -> IO ()) -> IO TerminalAttributes
forall a.
TerminalAttributes
-> (Ptr CTermios -> IO a) -> IO TerminalAttributes
withNewTermios TerminalAttributes
termios ((Ptr CTermios -> IO ()) -> IO TerminalAttributes)
-> (Ptr CTermios -> IO ()) -> IO TerminalAttributes
forall a b. (a -> b) -> a -> b
$ \Ptr CTermios
p -> do
    let c_cc :: Ptr b
c_cc = ((\Ptr CTermios
hsc_ptr -> Ptr CTermios
hsc_ptr Ptr CTermios -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
17)) Ptr CTermios
p
{-# LINE 293 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    pokeElemOff c_cc (cc2Word cc) ((0) :: CCc)
{-# LINE 294 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
inputTime :: TerminalAttributes -> Int
inputTime :: TerminalAttributes -> Int
inputTime TerminalAttributes
termios = IO Int -> Int
forall a. IO a -> a
unsafePerformIO (IO Int -> Int) -> IO Int -> Int
forall a b. (a -> b) -> a -> b
$ do
  TerminalAttributes -> (Ptr CTermios -> IO Int) -> IO Int
forall a. TerminalAttributes -> (Ptr CTermios -> IO a) -> IO a
withTerminalAttributes TerminalAttributes
termios ((Ptr CTermios -> IO Int) -> IO Int)
-> (Ptr CTermios -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Ptr CTermios
p -> do
    CCc
c <- Ptr CCc -> Int -> IO CCc
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff (((\Ptr CTermios
hsc_ptr -> Ptr CTermios
hsc_ptr Ptr CTermios -> Int -> Ptr CCc
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
17)) Ptr CTermios
p) (Int
5)
{-# LINE 299 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    return (fromEnum (c :: CCc))
withTime :: TerminalAttributes -> Int -> TerminalAttributes
withTime :: TerminalAttributes -> Int -> TerminalAttributes
withTime TerminalAttributes
termios Int
time = IO TerminalAttributes -> TerminalAttributes
forall a. IO a -> a
unsafePerformIO (IO TerminalAttributes -> TerminalAttributes)
-> IO TerminalAttributes -> TerminalAttributes
forall a b. (a -> b) -> a -> b
$ do
  TerminalAttributes
-> (Ptr CTermios -> IO ()) -> IO TerminalAttributes
forall a.
TerminalAttributes
-> (Ptr CTermios -> IO a) -> IO TerminalAttributes
withNewTermios TerminalAttributes
termios ((Ptr CTermios -> IO ()) -> IO TerminalAttributes)
-> (Ptr CTermios -> IO ()) -> IO TerminalAttributes
forall a b. (a -> b) -> a -> b
$ \Ptr CTermios
p -> do
    let c_cc :: Ptr b
c_cc = ((\Ptr CTermios
hsc_ptr -> Ptr CTermios
hsc_ptr Ptr CTermios -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
17)) Ptr CTermios
p
{-# LINE 305 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    pokeElemOff c_cc (5) (fromIntegral time :: CCc)
{-# LINE 306 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
minInput :: TerminalAttributes -> Int
minInput :: TerminalAttributes -> Int
minInput TerminalAttributes
termios = IO Int -> Int
forall a. IO a -> a
unsafePerformIO (IO Int -> Int) -> IO Int -> Int
forall a b. (a -> b) -> a -> b
$ do
  TerminalAttributes -> (Ptr CTermios -> IO Int) -> IO Int
forall a. TerminalAttributes -> (Ptr CTermios -> IO a) -> IO a
withTerminalAttributes TerminalAttributes
termios ((Ptr CTermios -> IO Int) -> IO Int)
-> (Ptr CTermios -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Ptr CTermios
p -> do
    CCc
c <- Ptr CCc -> Int -> IO CCc
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff (((\Ptr CTermios
hsc_ptr -> Ptr CTermios
hsc_ptr Ptr CTermios -> Int -> Ptr CCc
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
17)) Ptr CTermios
p) (Int
6)
{-# LINE 311 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    return (fromEnum (c :: CCc))
withMinInput :: TerminalAttributes -> Int -> TerminalAttributes
withMinInput :: TerminalAttributes -> Int -> TerminalAttributes
withMinInput TerminalAttributes
termios Int
count = IO TerminalAttributes -> TerminalAttributes
forall a. IO a -> a
unsafePerformIO (IO TerminalAttributes -> TerminalAttributes)
-> IO TerminalAttributes -> TerminalAttributes
forall a b. (a -> b) -> a -> b
$ do
  TerminalAttributes
-> (Ptr CTermios -> IO ()) -> IO TerminalAttributes
forall a.
TerminalAttributes
-> (Ptr CTermios -> IO a) -> IO TerminalAttributes
withNewTermios TerminalAttributes
termios ((Ptr CTermios -> IO ()) -> IO TerminalAttributes)
-> (Ptr CTermios -> IO ()) -> IO TerminalAttributes
forall a b. (a -> b) -> a -> b
$ \Ptr CTermios
p -> do
    let c_cc :: Ptr b
c_cc = ((\Ptr CTermios
hsc_ptr -> Ptr CTermios
hsc_ptr Ptr CTermios -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
17)) Ptr CTermios
p
{-# LINE 317 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    pokeElemOff c_cc (6) (fromIntegral count :: CCc)
{-# LINE 318 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
data BaudRate
  = B0
  | B50
  | B75
  | B110
  | B134
  | B150
  | B200
  | B300
  | B600
  | B1200
  | B1800
  | B2400
  | B4800
  | B9600
  | B19200
  | B38400
  | B57600
  | B115200
inputSpeed :: TerminalAttributes -> BaudRate
inputSpeed :: TerminalAttributes -> BaudRate
inputSpeed TerminalAttributes
termios = IO BaudRate -> BaudRate
forall a. IO a -> a
unsafePerformIO (IO BaudRate -> BaudRate) -> IO BaudRate -> BaudRate
forall a b. (a -> b) -> a -> b
$ do
  TerminalAttributes -> (Ptr CTermios -> IO BaudRate) -> IO BaudRate
forall a. TerminalAttributes -> (Ptr CTermios -> IO a) -> IO a
withTerminalAttributes TerminalAttributes
termios ((Ptr CTermios -> IO BaudRate) -> IO BaudRate)
-> (Ptr CTermios -> IO BaudRate) -> IO BaudRate
forall a b. (a -> b) -> a -> b
$ \Ptr CTermios
p -> do
    CSpeed
w <- Ptr CTermios -> IO CSpeed
c_cfgetispeed Ptr CTermios
p
    BaudRate -> IO BaudRate
forall (m :: * -> *) a. Monad m => a -> m a
return (CSpeed -> BaudRate
word2Baud CSpeed
w)
foreign import capi unsafe "termios.h cfgetispeed"
  c_cfgetispeed :: Ptr CTermios -> IO CSpeed
withInputSpeed :: TerminalAttributes -> BaudRate -> TerminalAttributes
withInputSpeed :: TerminalAttributes -> BaudRate -> TerminalAttributes
withInputSpeed TerminalAttributes
termios BaudRate
br = IO TerminalAttributes -> TerminalAttributes
forall a. IO a -> a
unsafePerformIO (IO TerminalAttributes -> TerminalAttributes)
-> IO TerminalAttributes -> TerminalAttributes
forall a b. (a -> b) -> a -> b
$ do
  TerminalAttributes
-> (Ptr CTermios -> IO CInt) -> IO TerminalAttributes
forall a.
TerminalAttributes
-> (Ptr CTermios -> IO a) -> IO TerminalAttributes
withNewTermios TerminalAttributes
termios ((Ptr CTermios -> IO CInt) -> IO TerminalAttributes)
-> (Ptr CTermios -> IO CInt) -> IO TerminalAttributes
forall a b. (a -> b) -> a -> b
$ \Ptr CTermios
p -> Ptr CTermios -> CSpeed -> IO CInt
c_cfsetispeed Ptr CTermios
p (BaudRate -> CSpeed
baud2Word BaudRate
br)
foreign import capi unsafe "termios.h cfsetispeed"
  c_cfsetispeed :: Ptr CTermios -> CSpeed -> IO CInt
outputSpeed :: TerminalAttributes -> BaudRate
outputSpeed :: TerminalAttributes -> BaudRate
outputSpeed TerminalAttributes
termios = IO BaudRate -> BaudRate
forall a. IO a -> a
unsafePerformIO (IO BaudRate -> BaudRate) -> IO BaudRate -> BaudRate
forall a b. (a -> b) -> a -> b
$ do
  TerminalAttributes -> (Ptr CTermios -> IO BaudRate) -> IO BaudRate
forall a. TerminalAttributes -> (Ptr CTermios -> IO a) -> IO a
withTerminalAttributes TerminalAttributes
termios ((Ptr CTermios -> IO BaudRate) -> IO BaudRate)
-> (Ptr CTermios -> IO BaudRate) -> IO BaudRate
forall a b. (a -> b) -> a -> b
$ \Ptr CTermios
p ->  do
    CSpeed
w <- Ptr CTermios -> IO CSpeed
c_cfgetospeed Ptr CTermios
p
    BaudRate -> IO BaudRate
forall (m :: * -> *) a. Monad m => a -> m a
return (CSpeed -> BaudRate
word2Baud CSpeed
w)
foreign import capi unsafe "termios.h cfgetospeed"
  c_cfgetospeed :: Ptr CTermios -> IO CSpeed
withOutputSpeed :: TerminalAttributes -> BaudRate -> TerminalAttributes
withOutputSpeed :: TerminalAttributes -> BaudRate -> TerminalAttributes
withOutputSpeed TerminalAttributes
termios BaudRate
br = IO TerminalAttributes -> TerminalAttributes
forall a. IO a -> a
unsafePerformIO (IO TerminalAttributes -> TerminalAttributes)
-> IO TerminalAttributes -> TerminalAttributes
forall a b. (a -> b) -> a -> b
$ do
  TerminalAttributes
-> (Ptr CTermios -> IO CInt) -> IO TerminalAttributes
forall a.
TerminalAttributes
-> (Ptr CTermios -> IO a) -> IO TerminalAttributes
withNewTermios TerminalAttributes
termios ((Ptr CTermios -> IO CInt) -> IO TerminalAttributes)
-> (Ptr CTermios -> IO CInt) -> IO TerminalAttributes
forall a b. (a -> b) -> a -> b
$ \Ptr CTermios
p -> Ptr CTermios -> CSpeed -> IO CInt
c_cfsetospeed Ptr CTermios
p (BaudRate -> CSpeed
baud2Word BaudRate
br)
foreign import capi unsafe "termios.h cfsetospeed"
  c_cfsetospeed :: Ptr CTermios -> CSpeed -> IO CInt
getTerminalAttributes :: Fd -> IO TerminalAttributes
getTerminalAttributes :: Fd -> IO TerminalAttributes
getTerminalAttributes (Fd CInt
fd) = do
  ForeignPtr CTermios
fp <- Int -> IO (ForeignPtr CTermios)
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes (Int
60)
{-# LINE 377 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  withForeignPtr fp $ \p ->
      throwErrnoIfMinus1_ "getTerminalAttributes" (c_tcgetattr fd p)
  TerminalAttributes -> IO TerminalAttributes
forall (m :: * -> *) a. Monad m => a -> m a
return (TerminalAttributes -> IO TerminalAttributes)
-> TerminalAttributes -> IO TerminalAttributes
forall a b. (a -> b) -> a -> b
$ ForeignPtr CTermios -> TerminalAttributes
makeTerminalAttributes ForeignPtr CTermios
fp
foreign import capi unsafe "termios.h tcgetattr"
  c_tcgetattr :: CInt -> Ptr CTermios -> IO CInt
data TerminalState
  = Immediately
  | WhenDrained
  | WhenFlushed
setTerminalAttributes :: Fd
                      -> TerminalAttributes
                      -> TerminalState
                      -> IO ()
setTerminalAttributes :: Fd -> TerminalAttributes -> TerminalState -> IO ()
setTerminalAttributes (Fd CInt
fd) TerminalAttributes
termios TerminalState
state = do
  TerminalAttributes -> (Ptr CTermios -> IO ()) -> IO ()
forall a. TerminalAttributes -> (Ptr CTermios -> IO a) -> IO a
withTerminalAttributes TerminalAttributes
termios ((Ptr CTermios -> IO ()) -> IO ())
-> (Ptr CTermios -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr CTermios
p ->
    [Char] -> IO CInt -> IO ()
forall a. (Eq a, Num a) => [Char] -> IO a -> IO ()
throwErrnoIfMinus1_ [Char]
"setTerminalAttributes"
      (CInt -> CInt -> Ptr CTermios -> IO CInt
c_tcsetattr CInt
fd (TerminalState -> CInt
state2Int TerminalState
state) Ptr CTermios
p)
  where
    state2Int :: TerminalState -> CInt
    state2Int :: TerminalState -> CInt
state2Int TerminalState
Immediately = (CInt
0)
{-# LINE 403 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    state2Int WhenDrained = (1)
{-# LINE 404 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    state2Int WhenFlushed = (2)
{-# LINE 405 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
foreign import capi unsafe "termios.h tcsetattr"
   c_tcsetattr :: CInt -> CInt -> Ptr CTermios -> IO CInt
sendBreak :: Fd -> Int -> IO ()
sendBreak :: Fd -> Int -> IO ()
sendBreak (Fd CInt
fd) Int
duration
  = [Char] -> IO CInt -> IO ()
forall a. (Eq a, Num a) => [Char] -> IO a -> IO ()
throwErrnoIfMinus1_ [Char]
"sendBreak" (CInt -> CInt -> IO CInt
c_tcsendbreak CInt
fd (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
duration))
foreign import capi unsafe "termios.h tcsendbreak"
  c_tcsendbreak :: CInt -> CInt -> IO CInt
drainOutput :: Fd -> IO ()
{-# LINE 427 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
drainOutput (Fd fd) = throwErrnoIfMinus1_ "drainOutput" (c_tcdrain fd)
foreign import capi safe "termios.h tcdrain"
  c_tcdrain :: CInt -> IO CInt
{-# LINE 436 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
data QueueSelector
  = InputQueue          
  | OutputQueue         
  | BothQueues          
discardData :: Fd -> QueueSelector -> IO ()
discardData :: Fd -> QueueSelector -> IO ()
discardData (Fd CInt
fd) QueueSelector
queue =
  [Char] -> IO CInt -> IO ()
forall a. (Eq a, Num a) => [Char] -> IO a -> IO ()
throwErrnoIfMinus1_ [Char]
"discardData" (CInt -> CInt -> IO CInt
c_tcflush CInt
fd (QueueSelector -> CInt
queue2Int QueueSelector
queue))
  where
    queue2Int :: QueueSelector -> CInt
    queue2Int :: QueueSelector -> CInt
queue2Int QueueSelector
InputQueue  = (CInt
0)
{-# LINE 451 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    queue2Int OutputQueue = (1)
{-# LINE 452 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    queue2Int BothQueues  = (2)
{-# LINE 453 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
foreign import capi unsafe "termios.h tcflush"
  c_tcflush :: CInt -> CInt -> IO CInt
data FlowAction
  = SuspendOutput       
  | RestartOutput       
  | TransmitStop        
  | TransmitStart       
controlFlow :: Fd -> FlowAction -> IO ()
controlFlow :: Fd -> FlowAction -> IO ()
controlFlow (Fd CInt
fd) FlowAction
action =
  [Char] -> IO CInt -> IO ()
forall a. (Eq a, Num a) => [Char] -> IO a -> IO ()
throwErrnoIfMinus1_ [Char]
"controlFlow" (CInt -> CInt -> IO CInt
c_tcflow CInt
fd (FlowAction -> CInt
action2Int FlowAction
action))
  where
    action2Int :: FlowAction -> CInt
    action2Int :: FlowAction -> CInt
action2Int FlowAction
SuspendOutput = (CInt
0)
{-# LINE 472 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    action2Int RestartOutput = (1)
{-# LINE 473 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    action2Int TransmitStop  = (2)
{-# LINE 474 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    action2Int TransmitStart = (3)
{-# LINE 475 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
foreign import capi unsafe "termios.h tcflow"
  c_tcflow :: CInt -> CInt -> IO CInt
getTerminalProcessGroupID :: Fd -> IO ProcessGroupID
getTerminalProcessGroupID :: Fd -> IO ProcessGroupID
getTerminalProcessGroupID (Fd CInt
fd) = do
  [Char] -> IO ProcessGroupID -> IO ProcessGroupID
forall a. (Eq a, Num a) => [Char] -> IO a -> IO a
throwErrnoIfMinus1 [Char]
"getTerminalProcessGroupID" (CInt -> IO ProcessGroupID
c_tcgetpgrp CInt
fd)
foreign import ccall unsafe "tcgetpgrp"
  c_tcgetpgrp :: CInt -> IO CPid
setTerminalProcessGroupID :: Fd -> ProcessGroupID -> IO ()
setTerminalProcessGroupID :: Fd -> ProcessGroupID -> IO ()
setTerminalProcessGroupID (Fd CInt
fd) ProcessGroupID
pgid =
  [Char] -> IO CInt -> IO ()
forall a. (Eq a, Num a) => [Char] -> IO a -> IO ()
throwErrnoIfMinus1_ [Char]
"setTerminalProcessGroupID" (CInt -> ProcessGroupID -> IO CInt
c_tcsetpgrp CInt
fd ProcessGroupID
pgid)
foreign import ccall unsafe "tcsetpgrp"
  c_tcsetpgrp :: CInt -> CPid -> IO CInt
queryTerminal :: Fd -> IO Bool
queryTerminal :: Fd -> IO Bool
queryTerminal (Fd CInt
fd) = do
  CInt
r <- CInt -> IO CInt
c_isatty CInt
fd
  Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (CInt
r CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== CInt
1)
  
foreign import ccall unsafe "isatty"
  c_isatty :: CInt -> IO CInt
cc2Word :: ControlCharacter -> Int
cc2Word :: ControlCharacter -> Int
cc2Word ControlCharacter
EndOfFile = (Int
4)
{-# LINE 521 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
cc2Word EndOfLine = (11)
{-# LINE 522 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
cc2Word Erase     = (2)
{-# LINE 523 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
cc2Word Interrupt = (0)
{-# LINE 524 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
cc2Word Kill      = (3)
{-# LINE 525 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
cc2Word Quit      = (1)
{-# LINE 526 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
cc2Word Suspend   = (10)
{-# LINE 527 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
cc2Word Start     = (8)
{-# LINE 528 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
cc2Word Stop      = (9)
{-# LINE 529 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
baud2Word :: BaudRate -> CSpeed
baud2Word :: BaudRate -> CSpeed
baud2Word BaudRate
B0 = (CSpeed
0)
{-# LINE 534 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
baud2Word B50 = (1)
{-# LINE 535 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
baud2Word B75 = (2)
{-# LINE 536 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
baud2Word B110 = (3)
{-# LINE 537 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
baud2Word B134 = (4)
{-# LINE 538 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
baud2Word B150 = (5)
{-# LINE 539 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
baud2Word B200 = (6)
{-# LINE 540 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
baud2Word B300 = (7)
{-# LINE 541 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
baud2Word B600 = (8)
{-# LINE 542 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
baud2Word B1200 = (9)
{-# LINE 543 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
baud2Word B1800 = (10)
{-# LINE 544 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
baud2Word B2400 = (11)
{-# LINE 545 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
baud2Word B4800 = (12)
{-# LINE 546 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
baud2Word B9600 = (13)
{-# LINE 547 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
baud2Word B19200 = (14)
{-# LINE 548 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
baud2Word B38400 = (15)
{-# LINE 549 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
{-# LINE 550 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
baud2Word B57600 = (4097)
{-# LINE 551 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
{-# LINE 554 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
{-# LINE 555 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
baud2Word B115200 = (4098)
{-# LINE 556 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
{-# LINE 559 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
word2Baud :: CSpeed -> BaudRate
word2Baud :: CSpeed -> BaudRate
word2Baud CSpeed
x =
    if CSpeed
x CSpeed -> CSpeed -> Bool
forall a. Eq a => a -> a -> Bool
== (CSpeed
0) then BaudRate
B0
{-# LINE 566 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    else if CSpeed
x CSpeed -> CSpeed -> Bool
forall a. Eq a => a -> a -> Bool
== (CSpeed
1) then BaudRate
B50
{-# LINE 567 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    else if CSpeed
x CSpeed -> CSpeed -> Bool
forall a. Eq a => a -> a -> Bool
== (CSpeed
2) then BaudRate
B75
{-# LINE 568 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    else if CSpeed
x CSpeed -> CSpeed -> Bool
forall a. Eq a => a -> a -> Bool
== (CSpeed
3) then BaudRate
B110
{-# LINE 569 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    else if CSpeed
x CSpeed -> CSpeed -> Bool
forall a. Eq a => a -> a -> Bool
== (CSpeed
4) then BaudRate
B134
{-# LINE 570 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    else if CSpeed
x CSpeed -> CSpeed -> Bool
forall a. Eq a => a -> a -> Bool
== (CSpeed
5) then BaudRate
B150
{-# LINE 571 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    else if CSpeed
x CSpeed -> CSpeed -> Bool
forall a. Eq a => a -> a -> Bool
== (CSpeed
6) then BaudRate
B200
{-# LINE 572 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    else if CSpeed
x CSpeed -> CSpeed -> Bool
forall a. Eq a => a -> a -> Bool
== (CSpeed
7) then BaudRate
B300
{-# LINE 573 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    else if CSpeed
x CSpeed -> CSpeed -> Bool
forall a. Eq a => a -> a -> Bool
== (CSpeed
8) then BaudRate
B600
{-# LINE 574 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    else if CSpeed
x CSpeed -> CSpeed -> Bool
forall a. Eq a => a -> a -> Bool
== (CSpeed
9) then BaudRate
B1200
{-# LINE 575 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    else if CSpeed
x CSpeed -> CSpeed -> Bool
forall a. Eq a => a -> a -> Bool
== (CSpeed
10) then BaudRate
B1800
{-# LINE 576 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    else if CSpeed
x CSpeed -> CSpeed -> Bool
forall a. Eq a => a -> a -> Bool
== (CSpeed
11) then BaudRate
B2400
{-# LINE 577 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    else if CSpeed
x CSpeed -> CSpeed -> Bool
forall a. Eq a => a -> a -> Bool
== (CSpeed
12) then BaudRate
B4800
{-# LINE 578 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    else if CSpeed
x CSpeed -> CSpeed -> Bool
forall a. Eq a => a -> a -> Bool
== (CSpeed
13) then BaudRate
B9600
{-# LINE 579 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    else if CSpeed
x CSpeed -> CSpeed -> Bool
forall a. Eq a => a -> a -> Bool
== (CSpeed
14) then BaudRate
B19200
{-# LINE 580 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    else if CSpeed
x CSpeed -> CSpeed -> Bool
forall a. Eq a => a -> a -> Bool
== (CSpeed
15) then BaudRate
B38400
{-# LINE 581 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
{-# LINE 582 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    else if CSpeed
x CSpeed -> CSpeed -> Bool
forall a. Eq a => a -> a -> Bool
== (CSpeed
4097) then BaudRate
B57600
{-# LINE 583 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
{-# LINE 584 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
{-# LINE 585 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    else if CSpeed
x CSpeed -> CSpeed -> Bool
forall a. Eq a => a -> a -> Bool
== (CSpeed
4098) then BaudRate
B115200
{-# LINE 586 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
{-# LINE 587 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    else [Char] -> BaudRate
forall a. HasCallStack => [Char] -> a
error [Char]
"unknown baud rate"
clearInputFlag :: CTcflag -> TerminalAttributes -> TerminalAttributes
clearInputFlag :: CTcflag -> TerminalAttributes -> TerminalAttributes
clearInputFlag CTcflag
flag TerminalAttributes
termios = IO TerminalAttributes -> TerminalAttributes
forall a. IO a -> a
unsafePerformIO (IO TerminalAttributes -> TerminalAttributes)
-> IO TerminalAttributes -> TerminalAttributes
forall a b. (a -> b) -> a -> b
$ do
  ForeignPtr CTermios
fp <- Int -> IO (ForeignPtr CTermios)
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes (Int
60)
{-# LINE 594 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  withForeignPtr fp $ \p1 -> do
    withTerminalAttributes termios $ \p2 -> do
      copyBytes p1 p2 (60)
{-# LINE 597 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      iflag <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) p2
{-# LINE 598 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      ((\hsc_ptr -> pokeByteOff hsc_ptr 0)) p1 (iflag .&. complement flag)
{-# LINE 599 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  return $ makeTerminalAttributes fp
setInputFlag :: CTcflag -> TerminalAttributes -> TerminalAttributes
setInputFlag :: CTcflag -> TerminalAttributes -> TerminalAttributes
setInputFlag CTcflag
flag TerminalAttributes
termios = IO TerminalAttributes -> TerminalAttributes
forall a. IO a -> a
unsafePerformIO (IO TerminalAttributes -> TerminalAttributes)
-> IO TerminalAttributes -> TerminalAttributes
forall a b. (a -> b) -> a -> b
$ do
  ForeignPtr CTermios
fp <- Int -> IO (ForeignPtr CTermios)
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes (Int
60)
{-# LINE 606 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  withForeignPtr fp $ \p1 -> do
    withTerminalAttributes termios $ \p2 -> do
      copyBytes p1 p2 (60)
{-# LINE 609 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      iflag <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) p2
{-# LINE 610 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      ((\hsc_ptr -> pokeByteOff hsc_ptr 0)) p1 (iflag .|. flag)
{-# LINE 611 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  return $ makeTerminalAttributes fp
testInputFlag :: CTcflag -> TerminalAttributes -> Bool
testInputFlag :: CTcflag -> TerminalAttributes -> Bool
testInputFlag CTcflag
flag TerminalAttributes
termios = IO Bool -> Bool
forall a. IO a -> a
unsafePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$
  TerminalAttributes -> (Ptr CTermios -> IO Bool) -> IO Bool
forall a. TerminalAttributes -> (Ptr CTermios -> IO a) -> IO a
withTerminalAttributes TerminalAttributes
termios ((Ptr CTermios -> IO Bool) -> IO Bool)
-> (Ptr CTermios -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr CTermios
p ->  do
    CTcflag
iflag <- ((\Ptr CTermios
hsc_ptr -> Ptr CTermios -> Int -> IO CTcflag
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr CTermios
hsc_ptr Int
0)) Ptr CTermios
p
{-# LINE 619 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    return $! ((iflag .&. flag) /= 0)
clearControlFlag :: CTcflag -> TerminalAttributes -> TerminalAttributes
clearControlFlag :: CTcflag -> TerminalAttributes -> TerminalAttributes
clearControlFlag CTcflag
flag TerminalAttributes
termios = IO TerminalAttributes -> TerminalAttributes
forall a. IO a -> a
unsafePerformIO (IO TerminalAttributes -> TerminalAttributes)
-> IO TerminalAttributes -> TerminalAttributes
forall a b. (a -> b) -> a -> b
$ do
  ForeignPtr CTermios
fp <- Int -> IO (ForeignPtr CTermios)
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes (Int
60)
{-# LINE 626 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  withForeignPtr fp $ \p1 -> do
    withTerminalAttributes termios $ \p2 -> do
      copyBytes p1 p2 (60)
{-# LINE 629 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      cflag <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) p2
{-# LINE 630 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      ((\hsc_ptr -> pokeByteOff hsc_ptr 8)) p1 (cflag .&. complement flag)
{-# LINE 631 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  return $ makeTerminalAttributes fp
setControlFlag :: CTcflag -> TerminalAttributes -> TerminalAttributes
setControlFlag :: CTcflag -> TerminalAttributes -> TerminalAttributes
setControlFlag CTcflag
flag TerminalAttributes
termios = IO TerminalAttributes -> TerminalAttributes
forall a. IO a -> a
unsafePerformIO (IO TerminalAttributes -> TerminalAttributes)
-> IO TerminalAttributes -> TerminalAttributes
forall a b. (a -> b) -> a -> b
$ do
  ForeignPtr CTermios
fp <- Int -> IO (ForeignPtr CTermios)
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes (Int
60)
{-# LINE 638 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  withForeignPtr fp $ \p1 -> do
    withTerminalAttributes termios $ \p2 -> do
      copyBytes p1 p2 (60)
{-# LINE 641 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      cflag <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) p2
{-# LINE 642 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      ((\hsc_ptr -> pokeByteOff hsc_ptr 8)) p1 (cflag .|. flag)
{-# LINE 643 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  return $ makeTerminalAttributes fp
testControlFlag :: CTcflag -> TerminalAttributes -> Bool
testControlFlag :: CTcflag -> TerminalAttributes -> Bool
testControlFlag CTcflag
flag TerminalAttributes
termios = IO Bool -> Bool
forall a. IO a -> a
unsafePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$
  TerminalAttributes -> (Ptr CTermios -> IO Bool) -> IO Bool
forall a. TerminalAttributes -> (Ptr CTermios -> IO a) -> IO a
withTerminalAttributes TerminalAttributes
termios ((Ptr CTermios -> IO Bool) -> IO Bool)
-> (Ptr CTermios -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr CTermios
p -> do
    CTcflag
cflag <- ((\Ptr CTermios
hsc_ptr -> Ptr CTermios -> Int -> IO CTcflag
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr CTermios
hsc_ptr Int
8)) Ptr CTermios
p
{-# LINE 651 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    return $! ((cflag .&. flag) /= 0)
clearLocalFlag :: CTcflag -> TerminalAttributes -> TerminalAttributes
clearLocalFlag :: CTcflag -> TerminalAttributes -> TerminalAttributes
clearLocalFlag CTcflag
flag TerminalAttributes
termios = IO TerminalAttributes -> TerminalAttributes
forall a. IO a -> a
unsafePerformIO (IO TerminalAttributes -> TerminalAttributes)
-> IO TerminalAttributes -> TerminalAttributes
forall a b. (a -> b) -> a -> b
$ do
  ForeignPtr CTermios
fp <- Int -> IO (ForeignPtr CTermios)
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes (Int
60)
{-# LINE 658 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  withForeignPtr fp $ \p1 -> do
    withTerminalAttributes termios $ \p2 -> do
      copyBytes p1 p2 (60)
{-# LINE 661 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      lflag <- ((\hsc_ptr -> peekByteOff hsc_ptr 12)) p2
{-# LINE 662 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      ((\hsc_ptr -> pokeByteOff hsc_ptr 12)) p1 (lflag .&. complement flag)
{-# LINE 663 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  return $ makeTerminalAttributes fp
setLocalFlag :: CTcflag -> TerminalAttributes -> TerminalAttributes
setLocalFlag :: CTcflag -> TerminalAttributes -> TerminalAttributes
setLocalFlag CTcflag
flag TerminalAttributes
termios = IO TerminalAttributes -> TerminalAttributes
forall a. IO a -> a
unsafePerformIO (IO TerminalAttributes -> TerminalAttributes)
-> IO TerminalAttributes -> TerminalAttributes
forall a b. (a -> b) -> a -> b
$ do
  ForeignPtr CTermios
fp <- Int -> IO (ForeignPtr CTermios)
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes (Int
60)
{-# LINE 670 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  withForeignPtr fp $ \p1 -> do
    withTerminalAttributes termios $ \p2 -> do
      copyBytes p1 p2 (60)
{-# LINE 673 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      lflag <- ((\hsc_ptr -> peekByteOff hsc_ptr 12)) p2
{-# LINE 674 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      ((\hsc_ptr -> pokeByteOff hsc_ptr 12)) p1 (lflag .|. flag)
{-# LINE 675 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  return $ makeTerminalAttributes fp
testLocalFlag :: CTcflag -> TerminalAttributes -> Bool
testLocalFlag :: CTcflag -> TerminalAttributes -> Bool
testLocalFlag CTcflag
flag TerminalAttributes
termios = IO Bool -> Bool
forall a. IO a -> a
unsafePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$
  TerminalAttributes -> (Ptr CTermios -> IO Bool) -> IO Bool
forall a. TerminalAttributes -> (Ptr CTermios -> IO a) -> IO a
withTerminalAttributes TerminalAttributes
termios ((Ptr CTermios -> IO Bool) -> IO Bool)
-> (Ptr CTermios -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr CTermios
p ->  do
    CTcflag
lflag <- ((\Ptr CTermios
hsc_ptr -> Ptr CTermios -> Int -> IO CTcflag
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr CTermios
hsc_ptr Int
12)) Ptr CTermios
p
{-# LINE 683 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    return $! ((lflag .&. flag) /= 0)
clearOutputFlag :: CTcflag -> TerminalAttributes -> TerminalAttributes
clearOutputFlag :: CTcflag -> TerminalAttributes -> TerminalAttributes
clearOutputFlag CTcflag
flag TerminalAttributes
termios = IO TerminalAttributes -> TerminalAttributes
forall a. IO a -> a
unsafePerformIO (IO TerminalAttributes -> TerminalAttributes)
-> IO TerminalAttributes -> TerminalAttributes
forall a b. (a -> b) -> a -> b
$ do
  ForeignPtr CTermios
fp <- Int -> IO (ForeignPtr CTermios)
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes (Int
60)
{-# LINE 690 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  withForeignPtr fp $ \p1 -> do
    withTerminalAttributes termios $ \p2 -> do
      copyBytes p1 p2 (60)
{-# LINE 693 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      oflag <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) p2
{-# LINE 694 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      ((\hsc_ptr -> pokeByteOff hsc_ptr 4)) p1 (oflag .&. complement flag)
{-# LINE 695 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  return $ makeTerminalAttributes fp
setOutputFlag :: CTcflag -> TerminalAttributes -> TerminalAttributes
setOutputFlag :: CTcflag -> TerminalAttributes -> TerminalAttributes
setOutputFlag CTcflag
flag TerminalAttributes
termios = IO TerminalAttributes -> TerminalAttributes
forall a. IO a -> a
unsafePerformIO (IO TerminalAttributes -> TerminalAttributes)
-> IO TerminalAttributes -> TerminalAttributes
forall a b. (a -> b) -> a -> b
$ do
  ForeignPtr CTermios
fp <- Int -> IO (ForeignPtr CTermios)
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes (Int
60)
{-# LINE 702 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  withForeignPtr fp $ \p1 -> do
    withTerminalAttributes termios $ \p2 -> do
      copyBytes p1 p2 (60)
{-# LINE 705 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      oflag <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) p2
{-# LINE 706 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      ((\hsc_ptr -> pokeByteOff hsc_ptr 4)) p1 (oflag .|. flag)
{-# LINE 707 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  return $ makeTerminalAttributes fp
testOutputFlag :: CTcflag -> TerminalAttributes -> Bool
testOutputFlag :: CTcflag -> TerminalAttributes -> Bool
testOutputFlag CTcflag
flag TerminalAttributes
termios = IO Bool -> Bool
forall a. IO a -> a
unsafePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$
  TerminalAttributes -> (Ptr CTermios -> IO Bool) -> IO Bool
forall a. TerminalAttributes -> (Ptr CTermios -> IO a) -> IO a
withTerminalAttributes TerminalAttributes
termios ((Ptr CTermios -> IO Bool) -> IO Bool)
-> (Ptr CTermios -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr CTermios
p -> do
    CTcflag
oflag <- ((\Ptr CTermios
hsc_ptr -> Ptr CTermios -> Int -> IO CTcflag
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr CTermios
hsc_ptr Int
4)) Ptr CTermios
p
{-# LINE 715 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    return $! ((oflag .&. flag) /= 0)
withNewTermios :: TerminalAttributes -> (Ptr CTermios -> IO a)
  -> IO TerminalAttributes
withNewTermios :: TerminalAttributes
-> (Ptr CTermios -> IO a) -> IO TerminalAttributes
withNewTermios TerminalAttributes
termios Ptr CTermios -> IO a
action = do
  ForeignPtr CTermios
fp1 <- Int -> IO (ForeignPtr CTermios)
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes (Int
60)
{-# LINE 721 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  withForeignPtr fp1 $ \p1 -> do
   withTerminalAttributes termios $ \p2 -> do
    copyBytes p1 p2 (60)
{-# LINE 724 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    _ <- action p1
    return ()
  TerminalAttributes -> IO TerminalAttributes
forall (m :: * -> *) a. Monad m => a -> m a
return (TerminalAttributes -> IO TerminalAttributes)
-> TerminalAttributes -> IO TerminalAttributes
forall a b. (a -> b) -> a -> b
$ ForeignPtr CTermios -> TerminalAttributes
makeTerminalAttributes ForeignPtr CTermios
fp1