{-# LINE 1 "System/Posix/Terminal.hsc" #-}{-# LANGUAGE CApiFFI #-}{-# LANGUAGE Safe #-}------------------------------------------------------------------------------- |-- Module : System.Posix.Terminal-- 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-------------------------------------------------------------------------------moduleSystem.Posix.Terminal(-- * Terminal support-- ** Terminal attributesTerminalAttributes ,getTerminalAttributes ,TerminalState (..),setTerminalAttributes ,TerminalMode (..),withoutMode ,withMode ,terminalMode ,bitsPerByte ,withBits ,ControlCharacter (..),controlChar ,withCC ,withoutCC ,inputTime ,withTime ,minInput ,withMinInput ,BaudRate (..),inputSpeed ,withInputSpeed ,outputSpeed ,withOutputSpeed ,-- ** Terminal operationssendBreak ,drainOutput ,QueueSelector (..),discardData ,FlowAction (..),controlFlow ,-- ** Process groupsgetTerminalProcessGroupID ,setTerminalProcessGroupID ,-- ** Testing a file descriptorqueryTerminal ,getTerminalName ,getControllingTerminalName ,-- ** Pseudoterminal operationsopenPseudoTerminal ,getSlaveTerminalName )whereimportForeignimportForeign.CimportSystem.Posix.Terminal.Common importSystem.Posix.Types{-# LINE 80 "System/Posix/Terminal.hsc" #-}importSystem.Posix.Internals(peekFilePath){-# LINE 87 "System/Posix/Terminal.hsc" #-}-- | @getTerminalName fd@ calls @ttyname@ to obtain a name associated-- with the terminal for @Fd@ @fd@. If @fd@ is associated-- with a terminal, @getTerminalName@ returns the name of the-- terminal.getTerminalName ::Fd->IOFilePathgetTerminalName :: Fd -> IO FilePath
getTerminalName (FdCInt
fd )=doPtr CChar
s <-FilePath -> IO (Ptr CChar) -> IO (Ptr CChar)
forall a. FilePath -> IO (Ptr a) -> IO (Ptr a)
throwErrnoIfNullFilePath
"getTerminalName"(CInt -> IO (Ptr CChar)
c_ttyname CInt
fd )Ptr CChar -> IO FilePath
peekFilePathPtr CChar
s foreignimportccallunsafe"ttyname"c_ttyname ::CInt->IOCString-- | @getControllingTerminalName@ calls @ctermid@ to obtain-- a name associated with the controlling terminal for the process. If a-- controlling terminal exists,-- @getControllingTerminalName@ returns the name of the-- controlling terminal.---- Throws 'IOError' (\"unsupported operation\") if platform does not-- provide @ctermid(3)@ (use @#if HAVE_CTERMID@ CPP guard to-- detect availability).getControllingTerminalName ::IOFilePath{-# LINE 111 "System/Posix/Terminal.hsc" #-}getControllingTerminalName=dos<-throwErrnoIfNull"getControllingTerminalName"(c_ctermidnullPtr)peekFilePathsforeignimportcapiunsafe"termios.h ctermid"c_ctermid ::CString->IOCString{-# LINE 122 "System/Posix/Terminal.hsc" #-}-- | @getSlaveTerminalName@ calls @ptsname@ to obtain the name of the-- slave terminal associated with a pseudoterminal pair. The file-- descriptor to pass in must be that of the master.getSlaveTerminalName ::Fd->IOFilePath{-# LINE 129 "System/Posix/Terminal.hsc" #-}getSlaveTerminalName(Fdfd)=dos<-throwErrnoIfNull"getSlaveTerminalName"(c_ptsnamefd)peekFilePathsforeignimportcapiunsafe"HsUnix.h ptsname"c_ptsname ::CInt->IOCString{-# LINE 140 "System/Posix/Terminal.hsc" #-}-- ------------------------------------------------------------------------------- openPseudoTerminal needs to be here because it depends on-- getSlaveTerminalName.-- | @openPseudoTerminal@ creates a pseudoterminal (pty) pair, and-- returns the newly created pair as a (@master@, @slave@) tuple.openPseudoTerminal ::IO(Fd,Fd){-# LINE 150 "System/Posix/Terminal.hsc" #-}openPseudoTerminal=alloca$\p_master->alloca$\p_slave->dothrowErrnoIfMinus1_"openPty"(c_openptyp_masterp_slavenullPtrnullPtrnullPtr)master<-peekp_masterslave<-peekp_slavereturn(Fdmaster,Fdslave)foreignimportccallunsafe"openpty"c_openpty ::PtrCInt->PtrCInt->CString->PtrCTermios->Ptra ->IOCInt{-# LINE 205 "System/Posix/Terminal.hsc" #-}

AltStyle によって変換されたページ (->オリジナル) /