{-# LINE 1 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
{-# LANGUAGE CApiFFI #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE Trustworthy #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  System.Posix.Terminal.Common
-- Copyright   :  (c) The University of Glasgow 2002
-- License     :  BSD-style (see the file libraries/base/LICENSE)
--
-- Maintainer  :  libraries@haskell.org
-- Stability   :  provisional
-- Portability :  non-portable (requires POSIX)
--
-- POSIX Terminal support
--
-----------------------------------------------------------------------------

-- see https://android.googlesource.com/platform/bionic/+/9ae59c0/libc/bionic/pathconf.c#37

{-# LINE 24 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}


module System.Posix.Terminal.Common (
  -- * Terminal support

  -- ** Terminal attributes
  TerminalAttributes,
  getTerminalAttributes,
  TerminalState(..),
  setTerminalAttributes,

  CTermios,
  TerminalMode(..),
  withoutMode,
  withMode,
  terminalMode,
  bitsPerByte,
  withBits,

  ControlCharacter(..),
  controlChar,
  withCC,
  withoutCC,

  inputTime,
  withTime,
  minInput,
  withMinInput,

  BaudRate
    ( ..
    , B0
    , B50
    , B75
    , B110
    , B134
    , B150
    , B200
    , B300
    , B600
    , B1200
    , B1800
    , B2400
    , B4800
    , B9600
    , B19200
    , B38400

{-# LINE 74 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 77 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 80 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 81 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    , B57600

{-# LINE 83 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 86 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 87 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    , B115200

{-# LINE 89 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 90 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    , B230400

{-# LINE 92 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 93 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    , B460800

{-# LINE 95 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 96 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    , B500000

{-# LINE 98 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 99 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    , B576000

{-# LINE 101 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 102 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    , B921600

{-# LINE 104 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 105 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    , B1000000

{-# LINE 107 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 108 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    , B1152000

{-# LINE 110 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 111 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    , B1500000

{-# LINE 113 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 114 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    , B2000000

{-# LINE 116 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 117 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    , B2500000

{-# LINE 119 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 120 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    , B3000000

{-# LINE 122 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 123 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    , B3500000

{-# LINE 125 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 126 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    , B4000000

{-# LINE 128 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    ),
  inputSpeed,
  withInputSpeed,
  outputSpeed,
  withOutputSpeed,

  -- ** Terminal operations
  sendBreak,
  drainOutput,
  QueueSelector(..),
  discardData,
  FlowAction(..),
  controlFlow,

  -- ** Process groups
  getTerminalProcessGroupID,
  setTerminalProcessGroupID,

  -- ** Testing a file descriptor
  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 169 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}


{-# LINE 171 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

-- -----------------------------------------------------------------------------
-- Terminal attributes

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 :: forall a. 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


{-# LINE 188 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}


data TerminalMode
        -- input flags
   = InterruptOnBreak           -- ^ @BRKINT@ - Signal interrupt on break
   | MapCRtoLF                  -- ^ @ICRNL@ - Map CR to NL on input
   | IgnoreBreak                -- ^ @IGNBRK@ - Ignore break condition
   | IgnoreCR                   -- ^ @IGNCR@ - Ignore CR
   | IgnoreParityErrors         -- ^ @IGNPAR@ - Ignore characters with parity errors
   | MapLFtoCR                  -- ^ @INLCR@ - Map NL to CR on input
   | CheckParity                -- ^ @INPCK@ - Enable input parity check
   | StripHighBit               -- ^ @ISTRIP@ - Strip character
   | RestartOnAny               -- ^ @IXANY@ - Enable any character to restart output
   | StartStopInput             -- ^ @IXOFF@ - Enable start/stop input control
   | StartStopOutput            -- ^ @IXON@ - Enable start/stop output control
   | MarkParityErrors           -- ^ @PARMRK@ - Mark parity errors

        -- output flags
   | ProcessOutput              -- ^ @OPOST@ - Post-process output
   | MapLFtoCRLF                -- ^ @ONLCR@ - (XSI) Map NL to CR-NL on output
                                --
                                -- @since 2.8.0.0
   | OutputMapCRtoLF            -- ^ @OCRNL@ - (XSI) Map CR to NL on output
                                --
                                -- @since 2.8.0.0
   | NoCRAtColumnZero           -- ^ @ONOCR@ - (XSI) No CR output at column 0
                                --
                                -- @since 2.8.0.0
   | ReturnMeansLF              -- ^ @ONLRET@ - (XSI) NL performs CR function
                                --
                                -- @since 2.8.0.0
   | TabDelayMask0              -- ^ @TABDLY(TAB0)@ - (XSI) Select horizontal-tab delays: type 0
                                --
                                -- @since 2.8.0.0
   | TabDelayMask3              -- ^ @TABDLY(TAB3)@ - (XSI) Select horizontal-tab delays: type 3
                                --
                                -- @since 2.8.0.0

        -- control flags
   | LocalMode                  -- ^ @CLOCAL@ - Ignore modem status lines
   | ReadEnable                 -- ^ @CREAD@ - Enable receiver
   | TwoStopBits                -- ^ @CSTOPB@ - Send two stop bits, else one
   | HangupOnClose              -- ^ @HUPCL@ - Hang up on last close
   | EnableParity               -- ^ @PARENB@ - Parity enable
   | OddParity                  -- ^ @PARODD@ - Odd parity, else even

        -- local modes
   | EnableEcho                 -- ^ @ECHO@ - Enable echo
   | EchoErase                  -- ^ @ECHOE@ - Echo erase character as error-correcting backspace
   | EchoKill                   -- ^ @ECHOK@ - Echo KILL
   | EchoLF                     -- ^ @ECHONL@ - Echo NL
   | ProcessInput               -- ^ @ICANON@ - Canonical input (erase and kill processing)
   | ExtendedFunctions          -- ^ @IEXTEN@ - Enable extended input character processing
   | KeyboardInterrupts         -- ^ @ISIG@ - Enable signals
   | NoFlushOnInterrupt         -- ^ @NOFLSH@ - Disable flush after interrupt or quit
   | BackgroundWriteInterrupt   -- ^ @TOSTOP@ - Send @SIGTTOU@ for background output


{-# LINE 273 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

withoutMode :: TerminalAttributes -> TerminalMode -> TerminalAttributes
withoutMode :: TerminalAttributes -> TerminalMode -> TerminalAttributes
withoutMode TerminalAttributes
termios TerminalMode
InterruptOnBreak = CTcflag -> TerminalAttributes -> TerminalAttributes
clearInputFlag (CTcflag
2) TerminalAttributes
termios
{-# LINE 276 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios MapCRtoLF = clearInputFlag (256) termios
{-# LINE 277 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios IgnoreBreak = clearInputFlag (1) termios
{-# LINE 278 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios IgnoreCR = clearInputFlag (128) termios
{-# LINE 279 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios IgnoreParityErrors = clearInputFlag (4) termios
{-# LINE 280 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios MapLFtoCR = clearInputFlag (64) termios
{-# LINE 281 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios CheckParity = clearInputFlag (16) termios
{-# LINE 282 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios StripHighBit = clearInputFlag (32) termios
{-# LINE 283 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios RestartOnAny = clearInputFlag (2048) termios
{-# LINE 284 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios StartStopInput = clearInputFlag (4096) termios
{-# LINE 285 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios StartStopOutput = clearInputFlag (1024) termios
{-# LINE 286 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios MarkParityErrors = clearInputFlag (8) termios
{-# LINE 287 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios ProcessOutput = clearOutputFlag (1) termios
{-# LINE 288 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios MapLFtoCRLF = clearOutputFlag (4) termios
{-# LINE 289 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios OutputMapCRtoLF = clearOutputFlag (8) termios
{-# LINE 290 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios NoCRAtColumnZero = clearOutputFlag (16) termios
{-# LINE 291 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios ReturnMeansLF = clearOutputFlag (32) termios
{-# LINE 292 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios TabDelayMask0 = clearOutputFlag (0) termios
{-# LINE 293 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios TabDelayMask3 = clearOutputFlag (6144) termios
{-# LINE 294 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios LocalMode = clearControlFlag (2048) termios
{-# LINE 295 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios ReadEnable = clearControlFlag (128) termios
{-# LINE 296 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios TwoStopBits = clearControlFlag (64) termios
{-# LINE 297 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios HangupOnClose = clearControlFlag (1024) termios
{-# LINE 298 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios EnableParity = clearControlFlag (256) termios
{-# LINE 299 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios OddParity = clearControlFlag (512) termios
{-# LINE 300 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios EnableEcho = clearLocalFlag (8) termios
{-# LINE 301 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios EchoErase = clearLocalFlag (16) termios
{-# LINE 302 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios EchoKill = clearLocalFlag (32) termios
{-# LINE 303 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios EchoLF = clearLocalFlag (64) termios
{-# LINE 304 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios ProcessInput = clearLocalFlag (2) termios
{-# LINE 305 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios ExtendedFunctions = clearLocalFlag (32768) termios
{-# LINE 306 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios KeyboardInterrupts = clearLocalFlag (1) termios
{-# LINE 307 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios NoFlushOnInterrupt = setLocalFlag (128) termios
{-# LINE 308 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withoutMode termios BackgroundWriteInterrupt = clearLocalFlag (256) termios
{-# LINE 309 "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 312 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios MapCRtoLF = setInputFlag (256) termios
{-# LINE 313 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios IgnoreBreak = setInputFlag (1) termios
{-# LINE 314 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios IgnoreCR = setInputFlag (128) termios
{-# LINE 315 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios IgnoreParityErrors = setInputFlag (4) termios
{-# LINE 316 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios MapLFtoCR = setInputFlag (64) termios
{-# LINE 317 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios CheckParity = setInputFlag (16) termios
{-# LINE 318 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios StripHighBit = setInputFlag (32) termios
{-# LINE 319 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios RestartOnAny = setInputFlag (2048) termios
{-# LINE 320 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios StartStopInput = setInputFlag (4096) termios
{-# LINE 321 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios StartStopOutput = setInputFlag (1024) termios
{-# LINE 322 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios MarkParityErrors = setInputFlag (8) termios
{-# LINE 323 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios ProcessOutput = setOutputFlag (1) termios
{-# LINE 324 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios MapLFtoCRLF = setOutputFlag (4) termios
{-# LINE 325 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios OutputMapCRtoLF = setOutputFlag (8) termios
{-# LINE 326 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios NoCRAtColumnZero = setOutputFlag (16) termios
{-# LINE 327 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios ReturnMeansLF = setOutputFlag (32) termios
{-# LINE 328 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios TabDelayMask0 = setOutputFlag (0) termios
{-# LINE 329 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios TabDelayMask3 = setOutputFlag (6144) termios
{-# LINE 330 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios LocalMode = setControlFlag (2048) termios
{-# LINE 331 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios ReadEnable = setControlFlag (128) termios
{-# LINE 332 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios TwoStopBits = setControlFlag (64) termios
{-# LINE 333 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios HangupOnClose = setControlFlag (1024) termios
{-# LINE 334 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios EnableParity = setControlFlag (256) termios
{-# LINE 335 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios OddParity = setControlFlag (512) termios
{-# LINE 336 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios EnableEcho = setLocalFlag (8) termios
{-# LINE 337 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios EchoErase = setLocalFlag (16) termios
{-# LINE 338 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios EchoKill = setLocalFlag (32) termios
{-# LINE 339 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios EchoLF = setLocalFlag (64) termios
{-# LINE 340 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios ProcessInput = setLocalFlag (2) termios
{-# LINE 341 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios ExtendedFunctions = setLocalFlag (32768) termios
{-# LINE 342 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios KeyboardInterrupts = setLocalFlag (1) termios
{-# LINE 343 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios NoFlushOnInterrupt = clearLocalFlag (128) termios
{-# LINE 344 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
withMode termios BackgroundWriteInterrupt = setLocalFlag (256) termios
{-# LINE 345 "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 348 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode MapCRtoLF = testInputFlag (256)
{-# LINE 349 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode IgnoreBreak = testInputFlag (1)
{-# LINE 350 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode IgnoreCR = testInputFlag (128)
{-# LINE 351 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode IgnoreParityErrors = testInputFlag (4)
{-# LINE 352 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode MapLFtoCR = testInputFlag (64)
{-# LINE 353 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode CheckParity = testInputFlag (16)
{-# LINE 354 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode StripHighBit = testInputFlag (32)
{-# LINE 355 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode RestartOnAny = testInputFlag (2048)
{-# LINE 356 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode StartStopInput = testInputFlag (4096)
{-# LINE 357 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode StartStopOutput = testInputFlag (1024)
{-# LINE 358 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode MarkParityErrors = testInputFlag (8)
{-# LINE 359 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode ProcessOutput = testOutputFlag (1)
{-# LINE 360 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode MapLFtoCRLF = testOutputFlag (4)
{-# LINE 361 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode OutputMapCRtoLF = testOutputFlag (8)
{-# LINE 362 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode NoCRAtColumnZero = testOutputFlag (16)
{-# LINE 363 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode ReturnMeansLF = testOutputFlag (32)
{-# LINE 364 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode TabDelayMask0 = testOutputFlag (0)
{-# LINE 365 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode TabDelayMask3 = testOutputFlag (6144)
{-# LINE 366 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode LocalMode = testControlFlag (2048)
{-# LINE 367 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode ReadEnable = testControlFlag (128)
{-# LINE 368 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode TwoStopBits = testControlFlag (64)
{-# LINE 369 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode HangupOnClose = testControlFlag (1024)
{-# LINE 370 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode EnableParity = testControlFlag (256)
{-# LINE 371 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode OddParity = testControlFlag (512)
{-# LINE 372 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode EnableEcho = testLocalFlag (8)
{-# LINE 373 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode EchoErase = testLocalFlag (16)
{-# LINE 374 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode EchoKill = testLocalFlag (32)
{-# LINE 375 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode EchoLF = testLocalFlag (64)
{-# LINE 376 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode ProcessInput = testLocalFlag (2)
{-# LINE 377 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode ExtendedFunctions = testLocalFlag (32768)
{-# LINE 378 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode KeyboardInterrupts = testLocalFlag (1)
{-# LINE 379 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode NoFlushOnInterrupt = not . testLocalFlag (128)
{-# LINE 380 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
terminalMode BackgroundWriteInterrupt = testLocalFlag (256)
{-# LINE 381 "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 b. Ptr b -> Int -> IO CTcflag
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr CTermios
hsc_ptr Int
8)) Ptr CTermios
p
{-# LINE 386 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    return $! (word2Bits (cflag .&. (48)))
{-# LINE 387 "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 391 "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 392 "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 393 "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 394 "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 b. Ptr b -> Int -> IO CTcflag
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr CTermios
hsc_ptr Int
8)) Ptr CTermios
p
{-# LINE 400 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 8)) p
{-# LINE 401 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
       ((cflag .&. complement (48)) .|. mask bits)
{-# LINE 402 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  where
    mask :: Int -> CTcflag
    mask :: Int -> CTcflag
mask Int
5 = (CTcflag
0)
{-# LINE 405 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    mask 6 = (16)
{-# LINE 406 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    mask 7 = (32)
{-# LINE 407 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    mask 8 = (48)
{-# LINE 408 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    mask _ = error "withBits bit value out of range [5..8]"


{-# LINE 411 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

data ControlCharacter
  = EndOfFile           -- VEOF
  | EndOfLine           -- VEOL
  | Erase               -- VERASE
  | Interrupt           -- VINTR
  | Kill                -- VKILL
  | Quit                -- VQUIT
  | Start               -- VSTART
  | Stop                -- VSTOP
  | Suspend             -- VSUSP


{-# LINE 517 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

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 522 "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 524 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
       then Maybe Char -> IO (Maybe Char)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Char
forall a. Maybe a
Nothing
       else Maybe Char -> IO (Maybe Char)
forall a. a -> IO a
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 533 "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 541 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    pokeElemOff c_cc (cc2Word cc) ((0) :: CCc)
{-# LINE 542 "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 547 "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 553 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    pokeElemOff c_cc (5) (fromIntegral time :: CCc)
{-# LINE 554 "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 559 "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 565 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    pokeElemOff c_cc (6) (fromIntegral count :: CCc)
{-# LINE 566 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

-- | Serial line baudrate.  The set of supported speeds is system-dependent.
-- Portable use of the provided pattern synonyms that are outside the list
-- mandated by POSIX requires @#ifdef@ guards.
--
-- Applications may need to be prepared to encounter speeds not known at
-- compile time, these can be handled generically via the 'BaudRate'
-- constructor.  In other words, the provided pattern synonyms are not
-- necessarily a @COMPLETE@ set.
--
-- All non-zero /pseudo-terminal/ baud rates are functionally equivalent, and
-- the @pty@ driver may accept any speed within a suitable range.  Requested
-- speeds may be rounded up or down to fit into the supported range.
--
newtype BaudRate = BaudRate CSpeed deriving (BaudRate -> BaudRate -> Bool
(BaudRate -> BaudRate -> Bool)
-> (BaudRate -> BaudRate -> Bool) -> Eq BaudRate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BaudRate -> BaudRate -> Bool
== :: BaudRate -> BaudRate -> Bool
$c/= :: BaudRate -> BaudRate -> Bool
/= :: BaudRate -> BaudRate -> Bool
Eq, Eq BaudRate
Eq BaudRate =>
(BaudRate -> BaudRate -> Ordering)
-> (BaudRate -> BaudRate -> Bool)
-> (BaudRate -> BaudRate -> Bool)
-> (BaudRate -> BaudRate -> Bool)
-> (BaudRate -> BaudRate -> Bool)
-> (BaudRate -> BaudRate -> BaudRate)
-> (BaudRate -> BaudRate -> BaudRate)
-> Ord BaudRate
BaudRate -> BaudRate -> Bool
BaudRate -> BaudRate -> Ordering
BaudRate -> BaudRate -> BaudRate
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BaudRate -> BaudRate -> Ordering
compare :: BaudRate -> BaudRate -> Ordering
$c< :: BaudRate -> BaudRate -> Bool
< :: BaudRate -> BaudRate -> Bool
$c<= :: BaudRate -> BaudRate -> Bool
<= :: BaudRate -> BaudRate -> Bool
$c> :: BaudRate -> BaudRate -> Bool
> :: BaudRate -> BaudRate -> Bool
$c>= :: BaudRate -> BaudRate -> Bool
>= :: BaudRate -> BaudRate -> Bool
$cmax :: BaudRate -> BaudRate -> BaudRate
max :: BaudRate -> BaudRate -> BaudRate
$cmin :: BaudRate -> BaudRate -> BaudRate
min :: BaudRate -> BaudRate -> BaudRate
Ord, Int -> BaudRate -> ShowS
[BaudRate] -> ShowS
BaudRate -> [Char]
(Int -> BaudRate -> ShowS)
-> (BaudRate -> [Char]) -> ([BaudRate] -> ShowS) -> Show BaudRate
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BaudRate -> ShowS
showsPrec :: Int -> BaudRate -> ShowS
$cshow :: BaudRate -> [Char]
show :: BaudRate -> [Char]
$cshowList :: [BaudRate] -> ShowS
showList :: [BaudRate] -> ShowS
Show, Int -> BaudRate
BaudRate -> Int
BaudRate -> [BaudRate]
BaudRate -> BaudRate
BaudRate -> BaudRate -> [BaudRate]
BaudRate -> BaudRate -> BaudRate -> [BaudRate]
(BaudRate -> BaudRate)
-> (BaudRate -> BaudRate)
-> (Int -> BaudRate)
-> (BaudRate -> Int)
-> (BaudRate -> [BaudRate])
-> (BaudRate -> BaudRate -> [BaudRate])
-> (BaudRate -> BaudRate -> [BaudRate])
-> (BaudRate -> BaudRate -> BaudRate -> [BaudRate])
-> Enum BaudRate
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: BaudRate -> BaudRate
succ :: BaudRate -> BaudRate
$cpred :: BaudRate -> BaudRate
pred :: BaudRate -> BaudRate
$ctoEnum :: Int -> BaudRate
toEnum :: Int -> BaudRate
$cfromEnum :: BaudRate -> Int
fromEnum :: BaudRate -> Int
$cenumFrom :: BaudRate -> [BaudRate]
enumFrom :: BaudRate -> [BaudRate]
$cenumFromThen :: BaudRate -> BaudRate -> [BaudRate]
enumFromThen :: BaudRate -> BaudRate -> [BaudRate]
$cenumFromTo :: BaudRate -> BaudRate -> [BaudRate]
enumFromTo :: BaudRate -> BaudRate -> [BaudRate]
$cenumFromThenTo :: BaudRate -> BaudRate -> BaudRate -> [BaudRate]
enumFromThenTo :: BaudRate -> BaudRate -> BaudRate -> [BaudRate]
Enum, Num BaudRate
Ord BaudRate
(Num BaudRate, Ord BaudRate) =>
(BaudRate -> Rational) -> Real BaudRate
BaudRate -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: BaudRate -> Rational
toRational :: BaudRate -> Rational
Real, Integer -> BaudRate
BaudRate -> BaudRate
BaudRate -> BaudRate -> BaudRate
(BaudRate -> BaudRate -> BaudRate)
-> (BaudRate -> BaudRate -> BaudRate)
-> (BaudRate -> BaudRate -> BaudRate)
-> (BaudRate -> BaudRate)
-> (BaudRate -> BaudRate)
-> (BaudRate -> BaudRate)
-> (Integer -> BaudRate)
-> Num BaudRate
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: BaudRate -> BaudRate -> BaudRate
+ :: BaudRate -> BaudRate -> BaudRate
$c- :: BaudRate -> BaudRate -> BaudRate
- :: BaudRate -> BaudRate -> BaudRate
$c* :: BaudRate -> BaudRate -> BaudRate
* :: BaudRate -> BaudRate -> BaudRate
$cnegate :: BaudRate -> BaudRate
negate :: BaudRate -> BaudRate
$cabs :: BaudRate -> BaudRate
abs :: BaudRate -> BaudRate
$csignum :: BaudRate -> BaudRate
signum :: BaudRate -> BaudRate
$cfromInteger :: Integer -> BaudRate
fromInteger :: Integer -> BaudRate
Num)

-- | Hang up
pattern B0 :: BaudRate
pattern $mB0 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB0 :: BaudRate
B0 = BaudRate (0)
{-# LINE 585 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 50 baud
pattern B50 :: BaudRate
pattern $mB50 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB50 :: BaudRate
B50 = BaudRate (1)
{-# LINE 588 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 75 baud
pattern B75 :: BaudRate
pattern $mB75 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB75 :: BaudRate
B75 = BaudRate (2)
{-# LINE 591 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 110 baud
pattern B110 :: BaudRate
pattern $mB110 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB110 :: BaudRate
B110 = BaudRate (3)
{-# LINE 594 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 134.5 baud
pattern B134 :: BaudRate
pattern $mB134 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB134 :: BaudRate
B134 = BaudRate (4)
{-# LINE 597 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 150 baud
pattern B150 :: BaudRate
pattern $mB150 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB150 :: BaudRate
B150 = BaudRate (5)
{-# LINE 600 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 200 baud
pattern B200 :: BaudRate
pattern $mB200 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB200 :: BaudRate
B200 = BaudRate (6)
{-# LINE 603 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 300 baud
pattern B300 :: BaudRate
pattern $mB300 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB300 :: BaudRate
B300 = BaudRate (7)
{-# LINE 606 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 600 baud
pattern B600 :: BaudRate
pattern $mB600 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB600 :: BaudRate
B600 = BaudRate (8)
{-# LINE 609 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 1200 baud
pattern B1200 :: BaudRate
pattern $mB1200 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB1200 :: BaudRate
B1200 = BaudRate (9)
{-# LINE 612 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 1800 baud
pattern B1800 :: BaudRate
pattern $mB1800 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB1800 :: BaudRate
B1800 = BaudRate (10)
{-# LINE 615 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 2400 baud
pattern B2400 :: BaudRate
pattern $mB2400 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB2400 :: BaudRate
B2400 = BaudRate (11)
{-# LINE 618 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 4800 baud
pattern B4800 :: BaudRate
pattern $mB4800 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB4800 :: BaudRate
B4800 = BaudRate (12)
{-# LINE 621 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 9600 baud
pattern B9600 :: BaudRate
pattern $mB9600 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB9600 :: BaudRate
B9600 = BaudRate (13)
{-# LINE 624 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 19200 baud
pattern B19200 :: BaudRate
pattern $mB19200 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB19200 :: BaudRate
B19200 = BaudRate (14)
{-# LINE 627 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 38400 baud
pattern B38400 :: BaudRate
pattern $mB38400 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB38400 :: BaudRate
B38400 = BaudRate (15)
{-# LINE 630 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}


{-# LINE 636 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 641 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 646 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 647 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 57600 baud, non-POSIX system-dependent extension
pattern B57600 :: BaudRate
pattern $mB57600 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB57600 :: BaudRate
B57600 = BaudRate (4097)
{-# LINE 650 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 651 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 656 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 657 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 115200 baud, non-POSIX system-dependent extension
pattern B115200 :: BaudRate
pattern $mB115200 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB115200 :: BaudRate
B115200 = BaudRate (4098)
{-# LINE 660 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 661 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 662 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 230400 baud, non-POSIX system-dependent extension
pattern B230400 :: BaudRate
pattern $mB230400 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB230400 :: BaudRate
B230400 = BaudRate (4099)
{-# LINE 665 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 666 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 667 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 460800 baud, non-POSIX system-dependent extension
pattern B460800 :: BaudRate
pattern $mB460800 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB460800 :: BaudRate
B460800 = BaudRate (4100)
{-# LINE 670 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 671 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 672 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 500000 baud, non-POSIX system-dependent extension
pattern B500000 :: BaudRate
pattern $mB500000 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB500000 :: BaudRate
B500000 = BaudRate (4101)
{-# LINE 675 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 676 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 677 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 576000 baud, non-POSIX system-dependent extension
pattern B576000 :: BaudRate
pattern $mB576000 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB576000 :: BaudRate
B576000 = BaudRate (4102)
{-# LINE 680 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 681 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 682 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 921600 baud, non-POSIX system-dependent extension
pattern B921600 :: BaudRate
pattern $mB921600 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB921600 :: BaudRate
B921600 = BaudRate (4103)
{-# LINE 685 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 686 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 687 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 1000000 baud, non-POSIX system-dependent extension
pattern B1000000 :: BaudRate
pattern $mB1000000 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB1000000 :: BaudRate
B1000000 = BaudRate (4104)
{-# LINE 690 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 691 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 692 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 1152000 baud, non-POSIX system-dependent extension
pattern B1152000 :: BaudRate
pattern $mB1152000 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB1152000 :: BaudRate
B1152000 = BaudRate (4105)
{-# LINE 695 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 696 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 697 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 1500000 baud, non-POSIX system-dependent extension
pattern B1500000 :: BaudRate
pattern $mB1500000 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB1500000 :: BaudRate
B1500000 = BaudRate (4106)
{-# LINE 700 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 701 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 702 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 2000000 baud, non-POSIX system-dependent extension
pattern B2000000 :: BaudRate
pattern $mB2000000 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB2000000 :: BaudRate
B2000000 = BaudRate (4107)
{-# LINE 705 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 706 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 707 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 2500000 baud, non-POSIX system-dependent extension
pattern B2500000 :: BaudRate
pattern $mB2500000 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB2500000 :: BaudRate
B2500000 = BaudRate (4108)
{-# LINE 710 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 711 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 712 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 3000000 baud, non-POSIX system-dependent extension
pattern B3000000 :: BaudRate
pattern $mB3000000 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB3000000 :: BaudRate
B3000000 = BaudRate (4109)
{-# LINE 715 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 716 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 717 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 3500000 baud, non-POSIX system-dependent extension
pattern B3500000 :: BaudRate
pattern $mB3500000 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB3500000 :: BaudRate
B3500000 = BaudRate (4110)
{-# LINE 720 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 721 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 722 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
-- | 4000000 baud, non-POSIX system-dependent extension
pattern B4000000 :: BaudRate
pattern $mB4000000 :: forall {r}. BaudRate -> ((# #) -> r) -> ((# #) -> r) -> r
$bB4000000 :: BaudRate
B4000000 = BaudRate (4111)
{-# LINE 725 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

{-# LINE 726 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}


{-# LINE 728 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}


{-# LINE 757 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSpeed -> BaudRate
BaudRate 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 CSpeed
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 CSpeed
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSpeed -> BaudRate
BaudRate 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 CSpeed
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 CSpeed
br

foreign import capi unsafe "termios.h cfsetospeed"
  c_cfsetospeed :: Ptr CTermios -> CSpeed -> IO CInt

-- | @getTerminalAttributes fd@ calls @tcgetattr@ to obtain
--   the @TerminalAttributes@ associated with @Fd@ @fd@.
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 796 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  withForeignPtr fp $ \p ->
      throwErrnoIfMinus1_ "getTerminalAttributes" (c_tcgetattr fd p)
  TerminalAttributes -> IO TerminalAttributes
forall a. a -> IO a
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


{-# LINE 804 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

data TerminalState
  = Immediately
  | WhenDrained
  | WhenFlushed


{-# LINE 831 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

-- | @setTerminalAttributes fd attr ts@ calls @tcsetattr@ to change
--   the @TerminalAttributes@ associated with @Fd@ @fd@ to
--   @attr@, when the terminal is in the state indicated by @ts@.
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 846 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    state2Int WhenDrained = (1)
{-# LINE 847 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    state2Int WhenFlushed = (2)
{-# LINE 848 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

foreign import capi unsafe "termios.h tcsetattr"
   c_tcsetattr :: CInt -> CInt -> Ptr CTermios -> IO CInt

-- | @sendBreak fd duration@ calls @tcsendbreak@ to transmit a
--   continuous stream of zero-valued bits on @Fd@ @fd@ for the
--   specified implementation-dependent @duration@.
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@ calls @tcdrain@ to block until all output
--   written to @Fd@ @fd@ has been transmitted.
--
-- Throws 'IOError' (\"unsupported operation\") if platform does not
-- provide @tcdrain(3)@ (use @#if HAVE_TCDRAIN@ CPP guard to
-- detect availability).
drainOutput :: Fd -> IO ()

{-# LINE 870 "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 879 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}


{-# LINE 881 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

data QueueSelector
  = InputQueue          -- TCIFLUSH
  | OutputQueue         -- TCOFLUSH
  | BothQueues          -- TCIOFLUSH


{-# LINE 895 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

-- | @discardData fd queues@ calls @tcflush@ to discard
--   pending input and\/or output for @Fd@ @fd@,
--   as indicated by the @QueueSelector@ @queues@.
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 905 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    queue2Int OutputQueue = (1)
{-# LINE 906 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    queue2Int BothQueues  = (2)
{-# LINE 907 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

foreign import capi unsafe "termios.h tcflush"
  c_tcflush :: CInt -> CInt -> IO CInt


{-# LINE 912 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

data FlowAction
  = SuspendOutput       -- ^ TCOOFF
  | RestartOutput       -- ^ TCOON
  | TransmitStop        -- ^ TCIOFF
  | TransmitStart       -- ^ TCION


{-# LINE 937 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

-- | @controlFlow fd action@ calls @tcflow@ to control the
--   flow of data on @Fd@ @fd@, as indicated by
--   @action@.
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 947 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    action2Int RestartOutput = (1)
{-# LINE 948 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    action2Int TransmitStop  = (2)
{-# LINE 949 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    action2Int TransmitStart = (3)
{-# LINE 950 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

foreign import capi unsafe "termios.h tcflow"
  c_tcflow :: CInt -> CInt -> IO CInt

-- | @getTerminalProcessGroupID fd@ calls @tcgetpgrp@ to
--   obtain the @ProcessGroupID@ of the foreground process group
--   associated with the terminal attached to @Fd@ @fd@.
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 pgid@ calls @tcsetpgrp@ to
--   set the @ProcessGroupID@ of the foreground process group
--   associated with the terminal attached to @Fd@
--   @fd@ to @pgid@.
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


{-# LINE 976 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

-- -----------------------------------------------------------------------------
-- file descriptor queries

-- | @queryTerminal fd@ calls @isatty@ to determine whether or
--   not @Fd@ @fd@ is associated with a terminal.
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (CInt
r CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== CInt
1)
  -- ToDo: the spec says that it can set errno to EBADF if the result is zero

foreign import ccall unsafe "isatty"
  c_isatty :: CInt -> IO CInt

-- -----------------------------------------------------------------------------
-- Local utility functions

-- Convert Haskell ControlCharacter to Int


{-# LINE 997 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

cc2Word :: ControlCharacter -> Int
cc2Word :: ControlCharacter -> Int
cc2Word ControlCharacter
EndOfFile = (Int
4)
{-# LINE 1000 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
cc2Word EndOfLine = (11)
{-# LINE 1001 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
cc2Word Erase     = (2)
{-# LINE 1002 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
cc2Word Interrupt = (0)
{-# LINE 1003 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
cc2Word Kill      = (3)
{-# LINE 1004 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
cc2Word Quit      = (1)
{-# LINE 1005 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
cc2Word Suspend   = (10)
{-# LINE 1006 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
cc2Word Start     = (8)
{-# LINE 1007 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
cc2Word Stop      = (9)
{-# LINE 1008 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}

-- Clear termios i_flag

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 1014 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  withForeignPtr fp $ \p1 -> do
    withTerminalAttributes termios $ \p2 -> do
      copyBytes p1 p2 (60)
{-# LINE 1017 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      iflag <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) p2
{-# LINE 1018 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      ((\hsc_ptr -> pokeByteOff hsc_ptr 0)) p1 (iflag .&. complement flag)
{-# LINE 1019 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  return $ makeTerminalAttributes fp

-- Set termios i_flag

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 1026 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  withForeignPtr fp $ \p1 -> do
    withTerminalAttributes termios $ \p2 -> do
      copyBytes p1 p2 (60)
{-# LINE 1029 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      iflag <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) p2
{-# LINE 1030 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      ((\hsc_ptr -> pokeByteOff hsc_ptr 0)) p1 (iflag .|. flag)
{-# LINE 1031 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  return $ makeTerminalAttributes fp

-- Examine termios i_flag

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 b. Ptr b -> Int -> IO CTcflag
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr CTermios
hsc_ptr Int
0)) Ptr CTermios
p
{-# LINE 1039 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    return $! ((iflag .&. flag) /= 0)

-- Clear termios c_flag

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 1046 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  withForeignPtr fp $ \p1 -> do
    withTerminalAttributes termios $ \p2 -> do
      copyBytes p1 p2 (60)
{-# LINE 1049 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      cflag <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) p2
{-# LINE 1050 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      ((\hsc_ptr -> pokeByteOff hsc_ptr 8)) p1 (cflag .&. complement flag)
{-# LINE 1051 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  return $ makeTerminalAttributes fp

-- Set termios c_flag

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 1058 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  withForeignPtr fp $ \p1 -> do
    withTerminalAttributes termios $ \p2 -> do
      copyBytes p1 p2 (60)
{-# LINE 1061 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      cflag <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) p2
{-# LINE 1062 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      ((\hsc_ptr -> pokeByteOff hsc_ptr 8)) p1 (cflag .|. flag)
{-# LINE 1063 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  return $ makeTerminalAttributes fp

-- Examine termios c_flag

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 b. Ptr b -> Int -> IO CTcflag
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr CTermios
hsc_ptr Int
8)) Ptr CTermios
p
{-# LINE 1071 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    return $! ((cflag .&. flag) /= 0)

-- Clear termios l_flag

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 1078 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  withForeignPtr fp $ \p1 -> do
    withTerminalAttributes termios $ \p2 -> do
      copyBytes p1 p2 (60)
{-# LINE 1081 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      lflag <- ((\hsc_ptr -> peekByteOff hsc_ptr 12)) p2
{-# LINE 1082 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      ((\hsc_ptr -> pokeByteOff hsc_ptr 12)) p1 (lflag .&. complement flag)
{-# LINE 1083 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  return $ makeTerminalAttributes fp

-- Set termios l_flag

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 1090 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  withForeignPtr fp $ \p1 -> do
    withTerminalAttributes termios $ \p2 -> do
      copyBytes p1 p2 (60)
{-# LINE 1093 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      lflag <- ((\hsc_ptr -> peekByteOff hsc_ptr 12)) p2
{-# LINE 1094 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      ((\hsc_ptr -> pokeByteOff hsc_ptr 12)) p1 (lflag .|. flag)
{-# LINE 1095 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  return $ makeTerminalAttributes fp

-- Examine termios l_flag

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 b. Ptr b -> Int -> IO CTcflag
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr CTermios
hsc_ptr Int
12)) Ptr CTermios
p
{-# LINE 1103 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    return $! ((lflag .&. flag) /= 0)

-- Clear termios o_flag

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 1110 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  withForeignPtr fp $ \p1 -> do
    withTerminalAttributes termios $ \p2 -> do
      copyBytes p1 p2 (60)
{-# LINE 1113 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      oflag <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) p2
{-# LINE 1114 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      ((\hsc_ptr -> pokeByteOff hsc_ptr 4)) p1 (oflag .&. complement flag)
{-# LINE 1115 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  return $ makeTerminalAttributes fp

-- Set termios o_flag

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 1122 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  withForeignPtr fp $ \p1 -> do
    withTerminalAttributes termios $ \p2 -> do
      copyBytes p1 p2 (60)
{-# LINE 1125 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      oflag <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) p2
{-# LINE 1126 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
      ((\hsc_ptr -> pokeByteOff hsc_ptr 4)) p1 (oflag .|. flag)
{-# LINE 1127 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  return $ makeTerminalAttributes fp

-- Examine termios o_flag

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 b. Ptr b -> Int -> IO CTcflag
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr CTermios
hsc_ptr Int
4)) Ptr CTermios
p
{-# LINE 1135 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    return $! ((oflag .&. flag) /= 0)

withNewTermios :: TerminalAttributes -> (Ptr CTermios -> IO a)
  -> IO TerminalAttributes
withNewTermios :: forall a.
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 1141 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
  withForeignPtr fp1 $ \p1 -> do
   withTerminalAttributes termios $ \p2 -> do
    copyBytes p1 p2 (60)
{-# LINE 1144 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}
    _ <- action p1
    return ()
  TerminalAttributes -> IO TerminalAttributes
forall a. a -> IO a
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


{-# LINE 1149 "libraries/unix/System/Posix/Terminal/Common.hsc" #-}