{-# OPTIONS_GHC -Wall #-} {-# LANGUAGE DeriveDataTypeable , ForeignFunctionInterface , MultiParamTypeClasses , StandaloneDeriving , TypeSynonymInstances #-} #include #include #include #include module Bindings.PpDev where import System.Posix.IOCtl #strict_import import Data.Typeable (Typeable) deriving instance Typeable C'timeval deriving instance Typeable C'ppdev_frob_struct #starttype struct timeval #field tv_sec , CLong #field tv_usec , CLong #stoptype #num PP_IOCTL -- | Set mode for read/write (e.g. IEEE1284_MODE_EPP) #num PPSETMODE #opaque_t PPSETMODE instance IOControl C'PPSETMODE CInt where ioctlReq _ = c'PPSETMODE -- | Read status #num PPRSTATUS #opaque_t PPRSTATUS instance IOControl C'PPRSTATUS CUChar where ioctlReq _ = c'PPRSTATUS -- | Read/write control #num PPRCONTROL #opaque_t PPRCONTROL instance IOControl C'PPRCONTROL CUChar where ioctlReq _ = c'PPRCONTROL #num PPWCONTROL #opaque_t PPWCONTROL instance IOControl C'PPWCONTROL CUChar where ioctlReq _ = c'PPWCONTROL #starttype struct ppdev_frob_struct #field mask , CUChar #field val , CUChar #stoptype #num PPFCONTROL #opaque_t PPFCONTROL instance IOControl C'PPFCONTROL C'ppdev_frob_struct where ioctlReq _ = c'PPFCONTROL -- | Read/write data #num PPRDATA #opaque_t PPRDATA instance IOControl C'PPRDATA CUChar where ioctlReq _ = c'PPRDATA #num PPWDATA #opaque_t PPWDATA instance IOControl C'PPWDATA CUChar where ioctlReq _ = c'PPWDATA -- | Claim the port to start using it #num PPCLAIM #opaque_t PPCLAIM instance IOControl C'PPCLAIM CInt where ioctlReq _ = c'PPCLAIM -- | Release the port when you aren't using it #num PPRELEASE #opaque_t PPRELEASE instance IOControl C'PPRELEASE CInt where ioctlReq _ = c'PPRELEASE -- | Yield the port (release it if another driver is waiting, -- then reclaim) #num PPYIELD #opaque_t PPYIELD instance IOControl C'PPYIELD CInt where ioctlReq _ = c'PPYIELD -- | Register device exclusively (must be before PPCLAIM). #num PPEXCL #opaque_t PPEXCL instance IOControl C'PPEXCL CInt where ioctlReq _ = c'PPEXCL -- | Data line direction: non-zero for input mode. #num PPDATADIR #opaque_t PPDATADIR instance IOControl C'PPDATADIR CInt where ioctlReq _ = c'PPDATADIR -- | Negotiate a particular IEEE 1284 mode. #num PPNEGOT #opaque_t PPNEGOT instance IOControl C'PPNEGOT CInt where ioctlReq _ = c'PPNEGOT -- | Set control lines when an interrupt occurs. #num PPWCTLONIRQ #opaque_t PPWCTLONIRQ instance IOControl C'PPWCTLONIRQ CUChar where ioctlReq _ = c'PPWCTLONIRQ -- | Clear (and return) interrupt count. #num PPCLRIRQ #opaque_t PPCLRIRQ instance IOControl C'PPCLRIRQ CInt where ioctlReq _ = c'PPCLRIRQ -- | Set the IEEE 1284 phase that we're in (e.g. IEEE1284_PH_FWD_IDLE) #num PPSETPHASE #opaque_t PPSETPHASE instance IOControl C'PPSETPHASE CInt where ioctlReq _ = c'PPSETPHASE -- | Set and get port timeout (struct timeval's) #num PPGETTIME #opaque_t PPGETTIME instance IOControl C'PPGETTIME C'timeval where ioctlReq _ = c'PPGETTIME #num PPSETTIME #opaque_t PPSETTIME instance IOControl C'PPSETTIME C'timeval where ioctlReq _ = c'PPSETTIME -- | Get available modes (what the hardware can do) #num PPGETMODES #opaque_t PPGETMODES instance IOControl C'PPGETMODES CUInt where ioctlReq _ = c'PPGETMODES -- | Get the current mode and phaze #num PPGETMODE #opaque_t PPGETMODE instance IOControl C'PPGETMODE CInt where ioctlReq _ = c'PPGETMODE #num PPGETPHASE #opaque_t PPGETPHASE instance IOControl C'PPGETPHASE CInt where ioctlReq _ = c'PPGETPHASE -- | get/set flags #num PPGETFLAGS #opaque_t PPGETFLAGS instance IOControl C'PPGETFLAGS CInt where ioctlReq _ = c'PPGETFLAGS #num PPSETFLAGS #opaque_t PPSETFLAGS instance IOControl C'PPSETFLAGS CInt where ioctlReq _ = c'PPSETFLAGS -- | flags visible to the world #num PP_FASTWRITE #num PP_FASTREAD #num PP_W91284PIC -- | only masks user-visible flags #num PP_FLAGMASK