{-# LINE 1 "System/Posix/PtyLight.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LINE 2 "System/Posix/PtyLight.hsc" #-}

{-|
POSIX pseudo-terminal support. The functions 'openPt', 'grantPt',
'unlockPt', and 'ptsName' all correspond directly to POSIX functions,
whereas the 'openPseudoTerminal' function provides more convenient
interface to pseudo-terminal functionality.

Note that later versions of the @unix@ package include pseudo-terminal
support in the "System.Posix.Terminal" module. You should probably
only use this module if you need backwards compatibility with GHC
versions earlier than 6.8, or if you want direct bindings to the
low-level pseudo-terminal functions.
-}
module System.Posix.PtyLight (
    -- * Opening a pseudo-terminal
    openPt,
    -- ** Flags
    oRDWR,
    oNOCTTY,
    
    -- * Allowing access
    grantPt,
    unlockPt,
    ptsName,
    
    -- * Convenience wrapper
    openPseudoTerminal,
    
    -- * Re-exports
    {-| For convenience, the 'Fd' type and 'closeFd' function are
    re-exported from this module. -}
    Fd,
    closeFd,
) where


{-# LINE 38 "System/Posix/PtyLight.hsc" #-}

{-# LINE 39 "System/Posix/PtyLight.hsc" #-}

import Control.Exception
import Control.Monad
import Foreign.C.Error
import Foreign.C.String
import Foreign.C.Types
import Foreign.Ptr
import System.Posix.IO
import System.Posix.Types

--- constants

{-| Causes 'openPt' to open the pseudo-terminal for both reading
and writing. (This flag is usually specified.)

Corresponds to @O_RDWR@ from @\<fcntl.h\>@.
-}
oRDWR :: CInt
oRDWR = 2
{-# LINE 58 "System/Posix/PtyLight.hsc" #-}

{-| Prevents 'openPt' from causing the terminal device to become
the controlling terminal for the process.

Corresponds to @O_NOCTTY@ from @\<fcntl.h\>@.
-}
oNOCTTY :: CInt
oNOCTTY = 256
{-# LINE 66 "System/Posix/PtyLight.hsc" #-}

--- posix_openpt

foreign import ccall unsafe
    "posix_openpt" _posix_openpt :: CInt -> IO Fd

{-| Opens a pseudo-terminal master and associates it with a file
descriptor.

Corresponds to @posix_openpt@ from @\<stdlib.h\>@.
-}
openPt :: CInt -- ^ bitwise-or of desired flags
       -> IO Fd
openPt flags = throwErrnoIfMinus1 "posix_openpt(3)" $
    _posix_openpt flags

--- grantpt

foreign import ccall unsafe
    "grantpt" _grantpt :: Fd -> IO CInt

{-| Change the ownership of the pseudo-terminal slave corresponding
to the given master so that it belongs to and can be read/written by
the current process's owner.
This should be called before 'unlockPt'.

Corresponds to @grantpt@ from @\<stdlib.h\>@.
-}
grantPt :: Fd -> IO ()
grantPt fd = throwErrnoIfMinus1_ "grantpt(3)" $
    _grantpt fd

--- unlockpt

foreign import ccall unsafe
    "unlockpt" _unlockpt :: Fd -> IO CInt

{-| Unlocks the pseudo-terminal slave corresponding to the given
master. This must be called before opening the slave
side of the pseudo-terminal.

Corresponds to @unlockpt@ from @\<stdlib.h\>@.
-}
unlockPt :: Fd -> IO ()
unlockPt fd = throwErrnoIfMinus1_ "unlockpt(3)" $
    _unlockpt fd

--- ptsname

foreign import ccall unsafe
    "ptsname" _ptsname :: Fd -> IO (Ptr CChar)

{-| Obtains the name of a pseudo-terminal slave device from the
master's file descriptor.

Corresponds to @ptsname@ from @\<stdlib.h\>@.
-}
ptsName :: Fd -> IO String
ptsName fd = (peekCAString =<<) . throwErrnoIfNull "ptsname(3)" $
    _ptsname fd

--- (openPseudoTerminal)

{-| Creates, grants, and unlocks a read/write pseudo-terminal,
returning an open file descriptor for the master device and the
file-system path of the slave device.

Performs the following actions:

* opens a pseudo-terminal

* grants and unlocks its slave

* obtains the slave's name

* returns the master's file descriptor and the slave's name

If an exception is thrown, the master file descriptor will be closed.
Otherwise, the caller is responsible for closing it.
-}
openPseudoTerminal :: IO (Fd, String)
openPseudoTerminal =
    bracketOnError (openPt oRDWR) (closeFd) $ \master -> do
        grantPt  master
        unlockPt master
        slave  <- ptsName master
        return (master, slave)