{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  GHC.IO.Device
-- Copyright   :  (c) The University of Glasgow, 1994-2008
-- License     :  see libraries/base/LICENSE
--
-- Maintainer  :  libraries@haskell.org
-- Stability   :  internal
-- Portability :  non-portable
--
-- Type classes for I/O providers.
--
-----------------------------------------------------------------------------

module GHC.IO.Device (
        RawIO(..),
        IODevice(..),
        IODeviceType(..),
        SeekMode(..)
    ) where

import GHC.Base
import GHC.Word
import GHC.Arr
import GHC.Enum
import GHC.Read
import GHC.Show
import GHC.Ptr
import GHC.Num
import GHC.IO
import {-# SOURCE #-} GHC.IO.Exception ( unsupportedOperation )

-- | A low-level I/O provider where the data is bytes in memory.
--   The Word64 offsets currently have no effect on POSIX system or consoles
--   where the implicit behaviour of the C runtime is assume to move the file
--   pointer on every read/write without needing an explicit seek.
class RawIO a where
  -- | Read up to the specified number of bytes starting from a specified
  -- offset, returning the number of bytes actually read.  This function
  -- should only block if there is no data available.  If there is not enough
  -- data available, then the function should just return the available data.
  -- A return value of zero indicates that the end of the data stream (e.g. end
  -- of file) has been reached.
  read                :: a -> Ptr Word8 -> Word64 -> Int -> IO Int

  -- | Read up to the specified number of bytes starting from a specified
  -- offset, returning the number of bytes actually read, or 'Nothing' if
  -- the end of the stream has been reached.
  readNonBlocking     :: a -> Ptr Word8 -> Word64 -> Int -> IO (Maybe Int)

  -- | Write the specified number of bytes starting at a given offset.
  write               :: a -> Ptr Word8 -> Word64 -> Int -> IO ()

  -- | Write up to the specified number of bytes without blocking starting at a
  -- given offset.  Returns the actual number of bytes written.
  writeNonBlocking    :: a -> Ptr Word8 -> Word64 -> Int -> IO Int


-- | I/O operations required for implementing a 'System.IO.Handle'.
class IODevice a where
  -- | @ready dev write msecs@ returns 'True' if the device has data
  -- to read (if @write@ is 'False') or space to write new data (if
  -- @write@ is 'True').  @msecs@ specifies how long to wait, in
  -- milliseconds.
  --
  ready :: a -> Bool -> Int -> IO Bool

  -- | closes the device.  Further operations on the device should
  -- produce exceptions.
  close :: a -> IO ()

  -- | returns 'True' if the device is a terminal or console.
  isTerminal :: a -> IO Bool
  isTerminal a
_ = forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False

  -- | returns 'True' if the device supports 'seek' operations.
  isSeekable :: a -> IO Bool
  isSeekable a
_ = forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False

  -- | seek to the specified position in the data.
  seek :: a -> SeekMode -> Integer -> IO Integer
  seek a
_ SeekMode
_ Integer
_ = forall a. IO a
ioe_unsupportedOperation

  -- | return the current position in the data.
  tell :: a -> IO Integer
  tell a
_ = forall a. IO a
ioe_unsupportedOperation

  -- | return the size of the data.
  getSize :: a -> IO Integer
  getSize a
_ = forall a. IO a
ioe_unsupportedOperation

  -- | change the size of the data.
  setSize :: a -> Integer -> IO ()
  setSize a
_ Integer
_ = forall a. IO a
ioe_unsupportedOperation

  -- | for terminal devices, changes whether characters are echoed on
  -- the device.
  setEcho :: a -> Bool -> IO ()
  setEcho a
_ Bool
_ = forall a. IO a
ioe_unsupportedOperation

  -- | returns the current echoing status.
  getEcho :: a -> IO Bool
  getEcho a
_ = forall a. IO a
ioe_unsupportedOperation

  -- | some devices (e.g. terminals) support a "raw" mode where
  -- characters entered are immediately made available to the program.
  -- If available, this operations enables raw mode.
  setRaw :: a -> Bool -> IO ()
  setRaw a
_ Bool
_ = forall a. IO a
ioe_unsupportedOperation

  -- | returns the 'IODeviceType' corresponding to this device.
  devType :: a -> IO IODeviceType

  -- | duplicates the device, if possible.  The new device is expected
  -- to share a file pointer with the original device (like Unix @dup@).
  dup :: a -> IO a
  dup a
_ = forall a. IO a
ioe_unsupportedOperation

  -- | @dup2 source target@ replaces the target device with the source
  -- device.  The target device is closed first, if necessary, and then
  -- it is made into a duplicate of the first device (like Unix @dup2@).
  dup2 :: a -> a -> IO a
  dup2 a
_ a
_ = forall a. IO a
ioe_unsupportedOperation

ioe_unsupportedOperation :: IO a
ioe_unsupportedOperation :: forall a. IO a
ioe_unsupportedOperation = forall e a. Exception e => e -> IO a
throwIO IOError
unsupportedOperation

-- | Type of a device that can be used to back a
-- 'GHC.IO.Handle.Handle' (see also 'GHC.IO.Handle.mkFileHandle'). The
-- standard libraries provide creation of 'GHC.IO.Handle.Handle's via
-- Posix file operations with file descriptors (see
-- 'GHC.IO.Handle.FD.mkHandleFromFD') with FD being the underlying
-- 'GHC.IO.Device.IODevice' instance.
--
-- Users may provide custom instances of 'GHC.IO.Device.IODevice'
-- which are expected to conform the following rules:

data IODeviceType
  = Directory -- ^ The standard libraries do not have direct support
              -- for this device type, but a user implementation is
              -- expected to provide a list of file names in
              -- the directory, in any order, separated by @\'\\0\'@
              -- characters, excluding the @"."@ and @".."@ names. See
              -- also 'System.Directory.getDirectoryContents'.  Seek
              -- operations are not supported on directories (other
              -- than to the zero position).
  | Stream    -- ^ A duplex communications channel (results in
              -- creation of a duplex 'GHC.IO.Handle.Handle'). The
              -- standard libraries use this device type when
              -- creating 'GHC.IO.Handle.Handle's for open sockets.
  | RegularFile -- ^ A file that may be read or written, and also
                -- may be seekable.
  | RawDevice -- ^ A "raw" (disk) device which supports block binary
              -- read and write operations and may be seekable only
              -- to positions of certain granularity (block-
              -- aligned).
  deriving ( IODeviceType -> IODeviceType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IODeviceType -> IODeviceType -> Bool
$c/= :: IODeviceType -> IODeviceType -> Bool
== :: IODeviceType -> IODeviceType -> Bool
$c== :: IODeviceType -> IODeviceType -> Bool
Eq -- ^ @since 4.2.0.0
           )

-- -----------------------------------------------------------------------------
-- SeekMode type

-- | A mode that determines the effect of 'System.IO.hSeek' @hdl mode i@.
data SeekMode
  = AbsoluteSeek        -- ^ the position of @hdl@ is set to @i@.
  | RelativeSeek        -- ^ the position of @hdl@ is set to offset @i@
                        -- from the current position.
  | SeekFromEnd         -- ^ the position of @hdl@ is set to offset @i@
                        -- from the end of the file.
    deriving ( SeekMode -> SeekMode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SeekMode -> SeekMode -> Bool
$c/= :: SeekMode -> SeekMode -> Bool
== :: SeekMode -> SeekMode -> Bool
$c== :: SeekMode -> SeekMode -> Bool
Eq   -- ^ @since 4.2.0.0
             , Eq SeekMode
SeekMode -> SeekMode -> Bool
SeekMode -> SeekMode -> Ordering
SeekMode -> SeekMode -> SeekMode
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
min :: SeekMode -> SeekMode -> SeekMode
$cmin :: SeekMode -> SeekMode -> SeekMode
max :: SeekMode -> SeekMode -> SeekMode
$cmax :: SeekMode -> SeekMode -> SeekMode
>= :: SeekMode -> SeekMode -> Bool
$c>= :: SeekMode -> SeekMode -> Bool
> :: SeekMode -> SeekMode -> Bool
$c> :: SeekMode -> SeekMode -> Bool
<= :: SeekMode -> SeekMode -> Bool
$c<= :: SeekMode -> SeekMode -> Bool
< :: SeekMode -> SeekMode -> Bool
$c< :: SeekMode -> SeekMode -> Bool
compare :: SeekMode -> SeekMode -> Ordering
$ccompare :: SeekMode -> SeekMode -> Ordering
Ord  -- ^ @since 4.2.0.0
             , Ord SeekMode
(SeekMode, SeekMode) -> Int
(SeekMode, SeekMode) -> [SeekMode]
(SeekMode, SeekMode) -> SeekMode -> Bool
(SeekMode, SeekMode) -> SeekMode -> Int
forall a.
Ord a
-> ((a, a) -> [a])
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Bool)
-> ((a, a) -> Int)
-> ((a, a) -> Int)
-> Ix a
unsafeRangeSize :: (SeekMode, SeekMode) -> Int
$cunsafeRangeSize :: (SeekMode, SeekMode) -> Int
rangeSize :: (SeekMode, SeekMode) -> Int
$crangeSize :: (SeekMode, SeekMode) -> Int
inRange :: (SeekMode, SeekMode) -> SeekMode -> Bool
$cinRange :: (SeekMode, SeekMode) -> SeekMode -> Bool
unsafeIndex :: (SeekMode, SeekMode) -> SeekMode -> Int
$cunsafeIndex :: (SeekMode, SeekMode) -> SeekMode -> Int
index :: (SeekMode, SeekMode) -> SeekMode -> Int
$cindex :: (SeekMode, SeekMode) -> SeekMode -> Int
range :: (SeekMode, SeekMode) -> [SeekMode]
$crange :: (SeekMode, SeekMode) -> [SeekMode]
Ix   -- ^ @since 4.2.0.0
             , Int -> SeekMode
SeekMode -> Int
SeekMode -> [SeekMode]
SeekMode -> SeekMode
SeekMode -> SeekMode -> [SeekMode]
SeekMode -> SeekMode -> SeekMode -> [SeekMode]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: SeekMode -> SeekMode -> SeekMode -> [SeekMode]
$cenumFromThenTo :: SeekMode -> SeekMode -> SeekMode -> [SeekMode]
enumFromTo :: SeekMode -> SeekMode -> [SeekMode]
$cenumFromTo :: SeekMode -> SeekMode -> [SeekMode]
enumFromThen :: SeekMode -> SeekMode -> [SeekMode]
$cenumFromThen :: SeekMode -> SeekMode -> [SeekMode]
enumFrom :: SeekMode -> [SeekMode]
$cenumFrom :: SeekMode -> [SeekMode]
fromEnum :: SeekMode -> Int
$cfromEnum :: SeekMode -> Int
toEnum :: Int -> SeekMode
$ctoEnum :: Int -> SeekMode
pred :: SeekMode -> SeekMode
$cpred :: SeekMode -> SeekMode
succ :: SeekMode -> SeekMode
$csucc :: SeekMode -> SeekMode
Enum -- ^ @since 4.2.0.0
             , ReadPrec [SeekMode]
ReadPrec SeekMode
Int -> ReadS SeekMode
ReadS [SeekMode]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SeekMode]
$creadListPrec :: ReadPrec [SeekMode]
readPrec :: ReadPrec SeekMode
$creadPrec :: ReadPrec SeekMode
readList :: ReadS [SeekMode]
$creadList :: ReadS [SeekMode]
readsPrec :: Int -> ReadS SeekMode
$creadsPrec :: Int -> ReadS SeekMode
Read -- ^ @since 4.2.0.0
             , Int -> SeekMode -> ShowS
[SeekMode] -> ShowS
SeekMode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SeekMode] -> ShowS
$cshowList :: [SeekMode] -> ShowS
show :: SeekMode -> String
$cshow :: SeekMode -> String
showsPrec :: Int -> SeekMode -> ShowS
$cshowsPrec :: Int -> SeekMode -> ShowS
Show -- ^ @since 4.2.0.0
             )