{-# LINE 1 "System/Posix/Realtime/RTDataTypes.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LINE 2 "System/Posix/Realtime/RTDataTypes.hsc" #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  System.Posix.Realtime.RTDataTypes
-- Copyright   :  (c) The University of Glasgow 2002
-- License     :  BSD-style (see the file libraries/base/LICENSE)
--
-- Maintainer  :  William N. Halchin (vigalchin@gmail.com)
-- Stability   :  provisional
-- Portability :  non-portable (requires POSIX)
--
-- POSIX 1003.1b real-time data types used by multiple Haskell modules.
--
-----------------------------------------------------------------------------

module System.Posix.Realtime.RTDataTypes (
  Sigval(..),
  Sigevent(..),
  TimeSpec(..),
  ItimerSpec(..)
  ) where

import System.IO
import System.IO.Error
import System.Posix.Signals
import System.Posix.Types
import System.Posix.Error
import System.Posix.Internals

import Foreign
import Foreign.C
import Data.Bits
import Data.Word


{-# LINE 36 "System/Posix/Realtime/RTDataTypes.hsc" #-}
import GHC.IO
import GHC.IO.Handle hiding (fdToHandle)
import qualified GHC.IO.Handle

{-# LINE 40 "System/Posix/Realtime/RTDataTypes.hsc" #-}


{-# LINE 45 "System/Posix/Realtime/RTDataTypes.hsc" #-}


{-# LINE 47 "System/Posix/Realtime/RTDataTypes.hsc" #-}

{-# LINE 48 "System/Posix/Realtime/RTDataTypes.hsc" #-}

{-# LINE 49 "System/Posix/Realtime/RTDataTypes.hsc" #-}

{-# LINE 50 "System/Posix/Realtime/RTDataTypes.hsc" #-}


-- data Sigval = SivalInt Int | SivalPtr (Ptr Char) -- TBD!!!!!!!!!!
newtype Sigval = SivalInt Int  -- TEMP
  deriving(Show)

instance Storable Sigval where
  sizeOf _ = (8)
{-# LINE 58 "System/Posix/Realtime/RTDataTypes.hsc" #-}
  alignment _ = 1
  poke p_Sigval (SivalInt i) = do
    ((\hsc_ptr -> pokeByteOff hsc_ptr 0)) p_Sigval i
{-# LINE 61 "System/Posix/Realtime/RTDataTypes.hsc" #-}
  peek p_Sigval = do
    sigvalInt <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) p_Sigval
{-# LINE 63 "System/Posix/Realtime/RTDataTypes.hsc" #-}
    return (SivalInt sigvalInt)   -- TBD ?????

data Sigevent = Sigevent {
  sigevVal :: Sigval,
  sigevSigno :: Signal,
  sigevNotify :: Int,
  sigevFunction :: FunPtr (Sigval -> IO ()),
  sigevAttribute :: Ptr Char
  } deriving(Show)

instance Storable Sigevent where
  sizeOf _ = (64)
{-# LINE 75 "System/Posix/Realtime/RTDataTypes.hsc" #-}
  alignment _ = 1
  poke p_Sigevent (Sigevent sigevVal sigevSigno sigevNotify sigevFunction sigevAttribute) = do
    ((\hsc_ptr -> pokeByteOff hsc_ptr 0)) p_Sigevent sigevVal
{-# LINE 78 "System/Posix/Realtime/RTDataTypes.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 8)) p_Sigevent sigevSigno
{-# LINE 79 "System/Posix/Realtime/RTDataTypes.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 12)) p_Sigevent sigevNotify
{-# LINE 80 "System/Posix/Realtime/RTDataTypes.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 16)) p_Sigevent sigevFunction
{-# LINE 81 "System/Posix/Realtime/RTDataTypes.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 24)) p_Sigevent sigevAttribute
{-# LINE 82 "System/Posix/Realtime/RTDataTypes.hsc" #-}
  peek p_Sigevent = do
    sigevVal <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) p_Sigevent
{-# LINE 84 "System/Posix/Realtime/RTDataTypes.hsc" #-}
    sigevSigno <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) p_Sigevent
{-# LINE 85 "System/Posix/Realtime/RTDataTypes.hsc" #-}
    sigevNotify <- ((\hsc_ptr -> peekByteOff hsc_ptr 12)) p_Sigevent
{-# LINE 86 "System/Posix/Realtime/RTDataTypes.hsc" #-}
    sigevFunction <- ((\hsc_ptr -> peekByteOff hsc_ptr 16)) p_Sigevent
{-# LINE 87 "System/Posix/Realtime/RTDataTypes.hsc" #-}
    sigevAttribute <- ((\hsc_ptr -> peekByteOff hsc_ptr 24)) p_Sigevent
{-# LINE 88 "System/Posix/Realtime/RTDataTypes.hsc" #-}
    return (Sigevent sigevVal sigevSigno sigevNotify sigevFunction sigevAttribute)

data TimeSpec = TimeSpec {
  tvSec :: Int,     -- Seconds
  tvNsec :: Int     -- Nano-seconds
  } deriving Show

instance Storable TimeSpec where
  sizeOf _ = (16)
{-# LINE 97 "System/Posix/Realtime/RTDataTypes.hsc" #-}
  alignment _ = 1
  poke p_timespec (TimeSpec tvSec tvNsec) = do
    ((\hsc_ptr -> pokeByteOff hsc_ptr 0)) p_timespec tvSec
{-# LINE 100 "System/Posix/Realtime/RTDataTypes.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 8)) p_timespec tvNsec
{-# LINE 101 "System/Posix/Realtime/RTDataTypes.hsc" #-}
  peek p_timespec = do
    tvSec <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) p_timespec
{-# LINE 103 "System/Posix/Realtime/RTDataTypes.hsc" #-}
    tvNsec <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) p_timespec
{-# LINE 104 "System/Posix/Realtime/RTDataTypes.hsc" #-}
    return (TimeSpec  tvSec tvNsec)

data ItimerSpec = ItimerSpec {
  itInterval :: TimeSpec,   -- ^ Timer period
  itValue :: TimeSpec       -- ^ Timer expiration
} deriving(Show)

instance Storable ItimerSpec where
  sizeOf _ = (32)
{-# LINE 113 "System/Posix/Realtime/RTDataTypes.hsc" #-}
  alignment _ = 1
  poke p_itimerspec (ItimerSpec itInterval itValue) = do
    ((\hsc_ptr -> pokeByteOff hsc_ptr 0)) p_itimerspec itInterval
{-# LINE 116 "System/Posix/Realtime/RTDataTypes.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 16)) p_itimerspec itValue 
{-# LINE 117 "System/Posix/Realtime/RTDataTypes.hsc" #-}
  peek p_itimerspec = do
    itInterval <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) p_itimerspec
{-# LINE 119 "System/Posix/Realtime/RTDataTypes.hsc" #-}
    itValue <- ((\hsc_ptr -> peekByteOff hsc_ptr 16)) p_itimerspec
{-# LINE 120 "System/Posix/Realtime/RTDataTypes.hsc" #-}
    return (ItimerSpec itInterval itValue)