{-# LINE 1 "src/Bindings/PpDev.hsc" #-}

{-# LINE 2 "src/Bindings/PpDev.hsc" #-}
{-# OPTIONS_GHC   -Wall #-}
{-# LANGUAGE      DeriveDataTypeable
                  , ForeignFunctionInterface
                  , MultiParamTypeClasses
                  , StandaloneDeriving
                  , TypeSynonymInstances #-}


{-# LINE 10 "src/Bindings/PpDev.hsc" #-}

{-# LINE 11 "src/Bindings/PpDev.hsc" #-}

{-# LINE 12 "src/Bindings/PpDev.hsc" #-}

{-# LINE 13 "src/Bindings/PpDev.hsc" #-}

module Bindings.PpDev where
import System.Posix.IOCtl
import Foreign.Ptr (Ptr,FunPtr,plusPtr)
import Foreign.Ptr (wordPtrToPtr,castPtrToFunPtr)
import Foreign.Storable
import Foreign.C.Types
import Foreign.C.String (CString,CStringLen,CWString,CWStringLen)
import Foreign.Marshal.Alloc (alloca)
import Foreign.Marshal.Array (peekArray,pokeArray)
import Data.Int
import Data.Word

{-# LINE 17 "src/Bindings/PpDev.hsc" #-}
import Data.Typeable (Typeable)
deriving instance Typeable C'timeval
deriving instance Typeable C'ppdev_frob_struct

data C'timeval = C'timeval{
{-# LINE 22 "src/Bindings/PpDev.hsc" #-}

  c'timeval'tv_sec :: CLong
{-# LINE 23 "src/Bindings/PpDev.hsc" #-}
,
  c'timeval'tv_usec :: CLong
{-# LINE 24 "src/Bindings/PpDev.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'timeval where
  sizeOf _ = 8
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    return $ C'timeval v0 v1
  poke p (C'timeval v0 v1) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    return ()

{-# LINE 25 "src/Bindings/PpDev.hsc" #-}

c'PP_IOCTL = 112
c'PP_IOCTL :: (Num a) => a

{-# LINE 27 "src/Bindings/PpDev.hsc" #-}

-- | Set mode for read/write (e.g. IEEE1284_MODE_EPP)
c'PPSETMODE = 1074032768
c'PPSETMODE :: (Num a) => a

{-# LINE 30 "src/Bindings/PpDev.hsc" #-}
data C'PPSETMODE = C'PPSETMODE

{-# LINE 31 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPSETMODE CInt where ioctlReq _ = c'PPSETMODE

-- |  Read status
c'PPRSTATUS = 2147577985
c'PPRSTATUS :: (Num a) => a

{-# LINE 35 "src/Bindings/PpDev.hsc" #-}
data C'PPRSTATUS = C'PPRSTATUS

{-# LINE 36 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPRSTATUS CUChar where ioctlReq _ = c'PPRSTATUS

-- |  Read/write control
c'PPRCONTROL = 2147577987
c'PPRCONTROL :: (Num a) => a

{-# LINE 40 "src/Bindings/PpDev.hsc" #-}
data C'PPRCONTROL = C'PPRCONTROL

{-# LINE 41 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPRCONTROL CUChar where ioctlReq _ = c'PPRCONTROL

c'PPWCONTROL = 1073836164
c'PPWCONTROL :: (Num a) => a

{-# LINE 44 "src/Bindings/PpDev.hsc" #-}
data C'PPWCONTROL = C'PPWCONTROL

{-# LINE 45 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPWCONTROL CUChar where ioctlReq _ = c'PPWCONTROL

data C'ppdev_frob_struct = C'ppdev_frob_struct{
{-# LINE 48 "src/Bindings/PpDev.hsc" #-}

  c'ppdev_frob_struct'mask :: CUChar
{-# LINE 49 "src/Bindings/PpDev.hsc" #-}
,
  c'ppdev_frob_struct'val :: CUChar
{-# LINE 50 "src/Bindings/PpDev.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'ppdev_frob_struct where
  sizeOf _ = 2
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 1
    return $ C'ppdev_frob_struct v0 v1
  poke p (C'ppdev_frob_struct v0 v1) = do
    pokeByteOff p 0 v0
    pokeByteOff p 1 v1
    return ()

{-# LINE 51 "src/Bindings/PpDev.hsc" #-}

c'PPFCONTROL = 1073901710
c'PPFCONTROL :: (Num a) => a

{-# LINE 53 "src/Bindings/PpDev.hsc" #-}
data C'PPFCONTROL = C'PPFCONTROL

{-# LINE 54 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPFCONTROL C'ppdev_frob_struct where ioctlReq _ = c'PPFCONTROL


-- |  Read/write data
c'PPRDATA = 2147577989
c'PPRDATA :: (Num a) => a

{-# LINE 59 "src/Bindings/PpDev.hsc" #-}
data C'PPRDATA = C'PPRDATA

{-# LINE 60 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPRDATA CUChar where ioctlReq _ = c'PPRDATA

c'PPWDATA = 1073836166
c'PPWDATA :: (Num a) => a

{-# LINE 63 "src/Bindings/PpDev.hsc" #-}
data C'PPWDATA = C'PPWDATA

{-# LINE 64 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPWDATA CUChar where ioctlReq _ = c'PPWDATA

-- |  Claim the port to start using it
c'PPCLAIM = 28811
c'PPCLAIM :: (Num a) => a

{-# LINE 68 "src/Bindings/PpDev.hsc" #-}
data C'PPCLAIM = C'PPCLAIM

{-# LINE 69 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPCLAIM CInt where ioctlReq _ = c'PPCLAIM

-- |  Release the port when you aren't using it
c'PPRELEASE = 28812
c'PPRELEASE :: (Num a) => a

{-# LINE 73 "src/Bindings/PpDev.hsc" #-}
data C'PPRELEASE = C'PPRELEASE

{-# LINE 74 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPRELEASE CInt where ioctlReq _ = c'PPRELEASE


-- | Yield the port (release it if another driver is waiting,
--   then reclaim)
c'PPYIELD = 28813
c'PPYIELD :: (Num a) => a

{-# LINE 80 "src/Bindings/PpDev.hsc" #-}
data C'PPYIELD = C'PPYIELD

{-# LINE 81 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPYIELD CInt where ioctlReq _ = c'PPYIELD


-- |  Register device exclusively (must be before PPCLAIM).
c'PPEXCL = 28815
c'PPEXCL :: (Num a) => a

{-# LINE 86 "src/Bindings/PpDev.hsc" #-}
data C'PPEXCL = C'PPEXCL

{-# LINE 87 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPEXCL CInt where ioctlReq _ = c'PPEXCL


-- |  Data line direction: non-zero for input mode.
c'PPDATADIR = 1074032784
c'PPDATADIR :: (Num a) => a

{-# LINE 92 "src/Bindings/PpDev.hsc" #-}
data C'PPDATADIR = C'PPDATADIR

{-# LINE 93 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPDATADIR CInt where ioctlReq _ = c'PPDATADIR


-- |  Negotiate a particular IEEE 1284 mode.
c'PPNEGOT = 1074032785
c'PPNEGOT :: (Num a) => a

{-# LINE 98 "src/Bindings/PpDev.hsc" #-}
data C'PPNEGOT = C'PPNEGOT

{-# LINE 99 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPNEGOT CInt where ioctlReq _ = c'PPNEGOT


-- |  Set control lines when an interrupt occurs.
c'PPWCTLONIRQ = 1073836178
c'PPWCTLONIRQ :: (Num a) => a

{-# LINE 104 "src/Bindings/PpDev.hsc" #-}
data C'PPWCTLONIRQ = C'PPWCTLONIRQ

{-# LINE 105 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPWCTLONIRQ CUChar where ioctlReq _ = c'PPWCTLONIRQ


-- |  Clear (and return) interrupt count.
c'PPCLRIRQ = 2147774611
c'PPCLRIRQ :: (Num a) => a

{-# LINE 110 "src/Bindings/PpDev.hsc" #-}
data C'PPCLRIRQ = C'PPCLRIRQ

{-# LINE 111 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPCLRIRQ CInt where ioctlReq _ = c'PPCLRIRQ


-- |  Set the IEEE 1284 phase that we're in (e.g. IEEE1284_PH_FWD_IDLE)
c'PPSETPHASE = 1074032788
c'PPSETPHASE :: (Num a) => a

{-# LINE 116 "src/Bindings/PpDev.hsc" #-}
data C'PPSETPHASE = C'PPSETPHASE

{-# LINE 117 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPSETPHASE CInt where ioctlReq _ = c'PPSETPHASE


-- |  Set and get port timeout (struct timeval's)
c'PPGETTIME = 2148036757
c'PPGETTIME :: (Num a) => a

{-# LINE 122 "src/Bindings/PpDev.hsc" #-}
data C'PPGETTIME = C'PPGETTIME

{-# LINE 123 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPGETTIME C'timeval where ioctlReq _ = c'PPGETTIME

c'PPSETTIME = 1074294934
c'PPSETTIME :: (Num a) => a

{-# LINE 126 "src/Bindings/PpDev.hsc" #-}
data C'PPSETTIME = C'PPSETTIME

{-# LINE 127 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPSETTIME C'timeval where ioctlReq _ = c'PPSETTIME


-- |  Get available modes (what the hardware can do)
c'PPGETMODES = 2147774615
c'PPGETMODES :: (Num a) => a

{-# LINE 132 "src/Bindings/PpDev.hsc" #-}
data C'PPGETMODES = C'PPGETMODES

{-# LINE 133 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPGETMODES CUInt where ioctlReq _ = c'PPGETMODES


-- |  Get the current mode and phaze
c'PPGETMODE = 2147774616
c'PPGETMODE :: (Num a) => a

{-# LINE 138 "src/Bindings/PpDev.hsc" #-}
data C'PPGETMODE = C'PPGETMODE

{-# LINE 139 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPGETMODE CInt where ioctlReq _ = c'PPGETMODE

c'PPGETPHASE = 2147774617
c'PPGETPHASE :: (Num a) => a

{-# LINE 142 "src/Bindings/PpDev.hsc" #-}
data C'PPGETPHASE = C'PPGETPHASE

{-# LINE 143 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPGETPHASE CInt where ioctlReq _ = c'PPGETPHASE


-- |  get/set flags
c'PPGETFLAGS = 2147774618
c'PPGETFLAGS :: (Num a) => a

{-# LINE 148 "src/Bindings/PpDev.hsc" #-}
data C'PPGETFLAGS = C'PPGETFLAGS

{-# LINE 149 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPGETFLAGS CInt where ioctlReq _ = c'PPGETFLAGS

c'PPSETFLAGS = 1074032795
c'PPSETFLAGS :: (Num a) => a

{-# LINE 152 "src/Bindings/PpDev.hsc" #-}
data C'PPSETFLAGS = C'PPSETFLAGS

{-# LINE 153 "src/Bindings/PpDev.hsc" #-}
instance IOControl C'PPSETFLAGS CInt where ioctlReq _ = c'PPSETFLAGS

-- |  flags visible to the world
c'PP_FASTWRITE = 4
c'PP_FASTWRITE :: (Num a) => a

{-# LINE 157 "src/Bindings/PpDev.hsc" #-}
c'PP_FASTREAD = 8
c'PP_FASTREAD :: (Num a) => a

{-# LINE 158 "src/Bindings/PpDev.hsc" #-}
c'PP_W91284PIC = 16
c'PP_W91284PIC :: (Num a) => a

{-# LINE 159 "src/Bindings/PpDev.hsc" #-}

-- |  only masks user-visible flags
c'PP_FLAGMASK = 28
c'PP_FLAGMASK :: (Num a) => a

{-# LINE 162 "src/Bindings/PpDev.hsc" #-}