Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- type VkGetInstanceProcAddrFunc = VkInstance -> CString -> IO (FunPtr ())
- type AudioCallback = FunPtr (Ptr () -> Ptr Word8 -> CInt -> IO ())
- type EventFilter = FunPtr (Ptr () -> Ptr Event -> IO CInt)
- type HintCallback = FunPtr (Ptr () -> CString -> CString -> CString -> IO ())
- type LogOutputFunction = FunPtr (Ptr () -> CInt -> LogPriority -> CString -> IO ())
- type ThreadFunction = FunPtr (Ptr () -> IO CInt)
- type TimerCallback = FunPtr (Word32 -> Ptr () -> IO Word32)
- mkAudioCallback :: (Ptr () -> Ptr Word8 -> CInt -> IO ()) -> IO AudioCallback
- mkEventFilter :: (Ptr () -> Ptr Event -> IO CInt) -> IO EventFilter
- mkHintCallback :: (Ptr () -> CString -> CString -> CString -> IO ()) -> IO HintCallback
- mkLogOutputFunction :: (Ptr () -> CInt -> LogPriority -> CString -> IO ()) -> IO LogOutputFunction
- mkThreadFunction :: (Ptr () -> IO CInt) -> IO ThreadFunction
- mkTimerCallback :: (Word32 -> Ptr () -> IO Word32) -> IO TimerCallback
- type AudioDeviceID = Word32
- type AudioFormat = Word16
- type Cond = Ptr ()
- type Cursor = Ptr ()
- type FingerID = Int64
- type GameController = Ptr ()
- type GestureID = Int64
- type GLContext = Ptr ()
- type Haptic = Ptr ()
- type Joystick = Ptr ()
- type JoystickID = Int32
- type Mutex = Ptr ()
- type Renderer = Ptr ()
- type Sem = Ptr ()
- type SpinLock = CInt
- type SysWMinfo = Ptr ()
- type SysWMmsg = Ptr ()
- type Texture = Ptr ()
- type Thread = Ptr ()
- type ThreadID = CULong
- type TimerID = CInt
- type TLSID = CUInt
- type TouchID = Int64
- type VkInstance = Ptr ()
- type VkSurfaceKHR = Word64
- type Window = Ptr ()
- data Atomic = Atomic {
- atomicValue :: !CInt
- data AudioCVT = AudioCVT {
- audioCVTNeeded :: !CInt
- audioCVTSrcFormat :: !AudioFormat
- audioCVTDstFormat :: !AudioFormat
- audioCVTRateIncr :: !CDouble
- audioCVTBuf :: !(Ptr Word8)
- audioCVTLen :: !CInt
- audioCVTLenCvt :: !CInt
- audioCVTLenMult :: !CInt
- audioCVTLenRatio :: !CDouble
- data AudioSpec = AudioSpec {
- audioSpecFreq :: !CInt
- audioSpecFormat :: !AudioFormat
- audioSpecChannels :: !Word8
- audioSpecSilence :: !Word8
- audioSpecSamples :: !Word16
- audioSpecSize :: !Word32
- audioSpecCallback :: !AudioCallback
- audioSpecUserdata :: !(Ptr ())
- data Color = Color {}
- data DisplayMode = DisplayMode {
- displayModeFormat :: !Word32
- displayModeW :: !CInt
- displayModeH :: !CInt
- displayModeRefreshRate :: !CInt
- displayModeDriverData :: !(Ptr ())
- data Event
- = WindowEvent { }
- | KeyboardEvent { }
- | TextEditingEvent { }
- | TextInputEvent {
- eventType :: !Word32
- eventTimestamp :: !Word32
- textInputEventWindowID :: !Word32
- textInputEventText :: ![CChar]
- | KeymapChangedEvent {
- eventType :: !Word32
- eventTimestamp :: !Word32
- | MouseMotionEvent { }
- | MouseButtonEvent { }
- | MouseWheelEvent { }
- | JoyAxisEvent { }
- | JoyBallEvent { }
- | JoyHatEvent { }
- | JoyButtonEvent { }
- | JoyDeviceEvent {
- eventType :: !Word32
- eventTimestamp :: !Word32
- joyDeviceEventWhich :: !Int32
- | ControllerAxisEvent { }
- | ControllerButtonEvent { }
- | ControllerDeviceEvent { }
- | AudioDeviceEvent { }
- | QuitEvent {
- eventType :: !Word32
- eventTimestamp :: !Word32
- | UserEvent {
- eventType :: !Word32
- eventTimestamp :: !Word32
- userEventWindowID :: !Word32
- userEventCode :: !Int32
- userEventData1 :: !(Ptr ())
- userEventData2 :: !(Ptr ())
- | SysWMEvent {
- eventType :: !Word32
- eventTimestamp :: !Word32
- sysWMEventMsg :: !SysWMmsg
- | TouchFingerEvent { }
- | MultiGestureEvent { }
- | DollarGestureEvent { }
- | DropEvent {
- eventType :: !Word32
- eventTimestamp :: !Word32
- dropEventFile :: !CString
- | ClipboardUpdateEvent {
- eventType :: !Word32
- eventTimestamp :: !Word32
- | UnknownEvent {
- eventType :: !Word32
- eventTimestamp :: !Word32
- data Finger = Finger {}
- data GameControllerButtonBind
- data HapticDirection = HapticDirection {}
- data HapticEffect
- = HapticConstant {
- hapticEffectType :: !Word16
- hapticConstantDirection :: !HapticDirection
- hapticConstantLength :: !Word32
- hapticConstantDelay :: !Word16
- hapticConstantButton :: !Word16
- hapticConstantInterval :: !Word16
- hapticConstantLevel :: !Int16
- hapticConstantAttackLength :: !Word16
- hapticConstantAttackLevel :: !Word16
- hapticConstantFadeLength :: !Word16
- hapticConstantFadeLevel :: !Word16
- | HapticPeriodic {
- hapticEffectType :: !Word16
- hapticPeriodicDirection :: !HapticDirection
- hapticPeriodicLength :: !Word32
- hapticPeriodicDelay :: !Word16
- hapticPeriodicButton :: !Word16
- hapticPeriodicInterval :: !Word16
- hapticPeriodicPeriod :: !Word16
- hapticPeriodicMagnitude :: !Int16
- hapticPeriodicOffset :: !Int16
- hapticPeriodicPhase :: !Word16
- hapticPeriodicAttackLength :: !Word16
- hapticPeriodicAttackLevel :: !Word16
- hapticPeriodicFadeLength :: !Word16
- hapticPeriodicFadeLevel :: !Word16
- | HapticCondition {
- hapticEffectType :: !Word16
- hapticConditionLength :: !Word32
- hapticConditionDelay :: !Word16
- hapticConditionButton :: !Word16
- hapticConditionInterval :: !Word16
- hapticConditionRightSat :: ![Word16]
- hapticConditionLeftSat :: ![Word16]
- hapticConditionRightCoeff :: ![Int16]
- hapticConditionLeftCoeff :: ![Int16]
- hapticConditionDeadband :: ![Word16]
- hapticConditionCenter :: ![Int16]
- | HapticRamp {
- hapticEffectType :: !Word16
- hapticRampDirection :: !HapticDirection
- hapticRampLength :: !Word32
- hapticRampDelay :: !Word16
- hapticRampButton :: !Word16
- hapticRampInterval :: !Word16
- hapticRampStart :: !Int16
- hapticRampEnd :: !Int16
- hapticRampAttackLength :: !Word16
- hapticRampAttackLevel :: !Word16
- hapticRampFadeLength :: !Word16
- hapticRampFadeLevel :: !Word16
- | HapticLeftRight { }
- | HapticCustom {
- hapticEffectType :: !Word16
- hapticCustomDirection :: !HapticDirection
- hapticCustomLength :: !Word32
- hapticCustomDelay :: !Word16
- hapticCustomButton :: !Word16
- hapticCustomInterval :: !Word16
- hapticCustomChannels :: !Word8
- hapticCustomPeriod :: !Word16
- hapticCustomSamples :: !Word16
- hapticCustomData :: !(Ptr Word16)
- hapticCustomAttackLength :: !Word16
- hapticCustomAttackLevel :: !Word16
- hapticCustomFadeLength :: !Word16
- hapticCustomFadeLevel :: !Word16
- = HapticConstant {
- data JoystickGUID = JoystickGUID {
- joystickGUID :: ![Word8]
- data Keysym = Keysym {
- keysymScancode :: !Scancode
- keysymKeycode :: !Keycode
- keysymMod :: !Word16
- data MessageBoxButtonData = MessageBoxButtonData {}
- data MessageBoxColor = MessageBoxColor {}
- data MessageBoxColorScheme = MessageBoxColorScheme {}
- data MessageBoxData = MessageBoxData {}
- data Palette = Palette {
- paletteNColors :: !CInt
- paletteColors :: !(Ptr Color)
- data PixelFormat = PixelFormat {}
- data Point = Point {}
- data Rect = Rect {}
- data RendererInfo = RendererInfo {}
- data RWops = RWops {
- rwopsSize :: !(FunPtr (Ptr RWops -> IO Int64))
- rwopsSeek :: !(FunPtr (Ptr RWops -> Int64 -> CInt -> IO Int64))
- rwopsRead :: !(FunPtr (Ptr RWops -> Ptr () -> CSize -> CSize -> IO CSize))
- rwopsWrite :: !(FunPtr (Ptr RWops -> Ptr () -> CSize -> CSize -> IO CSize))
- rwopsClose :: !(FunPtr (Ptr RWops -> IO CInt))
- rwopsType :: !Word32
- data Surface = Surface {
- surfaceFormat :: !(Ptr PixelFormat)
- surfaceW :: !CInt
- surfaceH :: !CInt
- surfacePixels :: !(Ptr ())
- surfaceUserdata :: !(Ptr ())
- surfaceClipRect :: !Rect
- surfaceRefcount :: !CInt
- data Version = Version {
- versionMajor :: !Word8
- versionMinor :: !Word8
- versionPatch :: !Word8
Type Aliases
Function Types
type VkGetInstanceProcAddrFunc = VkInstance -> CString -> IO (FunPtr ()) Source #
type LogOutputFunction = FunPtr (Ptr () -> CInt -> LogPriority -> CString -> IO ()) Source #
mkAudioCallback :: (Ptr () -> Ptr Word8 -> CInt -> IO ()) -> IO AudioCallback Source #
The storage associated with the resulting FunPtr
has to be released with
freeHaskellFunPtr
when it is no longer required.
mkEventFilter :: (Ptr () -> Ptr Event -> IO CInt) -> IO EventFilter Source #
The storage associated with the resulting FunPtr
has to be released with
freeHaskellFunPtr
when it is no longer required.
mkHintCallback :: (Ptr () -> CString -> CString -> CString -> IO ()) -> IO HintCallback Source #
The storage associated with the resulting FunPtr
has to be released with
freeHaskellFunPtr
when it is no longer required.
mkLogOutputFunction :: (Ptr () -> CInt -> LogPriority -> CString -> IO ()) -> IO LogOutputFunction Source #
The storage associated with the resulting FunPtr
has to be released with
freeHaskellFunPtr
when it is no longer required.
mkThreadFunction :: (Ptr () -> IO CInt) -> IO ThreadFunction Source #
The storage associated with the resulting FunPtr
has to be released with
freeHaskellFunPtr
when it is no longer required.
mkTimerCallback :: (Word32 -> Ptr () -> IO Word32) -> IO TimerCallback Source #
The storage associated with the resulting FunPtr
has to be released with
freeHaskellFunPtr
when it is no longer required.
Common Types
type AudioDeviceID = Word32 Source #
type AudioFormat = Word16 Source #
type GameController = Ptr () Source #
type JoystickID = Int32 Source #
type VkInstance = Ptr () Source #
type VkSurfaceKHR = Word64 Source #
Data Structures
Atomic | |
|
Instances
Eq Atomic Source # | |
Show Atomic Source # | |
Storable Atomic Source # | |
AudioCVT | |
|
Instances
Eq AudioCVT Source # | |
Show AudioCVT Source # | |
Storable AudioCVT Source # | |
AudioSpec | |
|
Instances
Eq AudioSpec Source # | |
Show AudioSpec Source # | |
Storable AudioSpec Source # | |
Defined in SDL.Raw.Types |
Instances
Eq Color Source # | |
Show Color Source # | |
Storable Color Source # | |
data DisplayMode Source #
DisplayMode | |
|
Instances
Eq DisplayMode Source # | |
Defined in SDL.Raw.Types (==) :: DisplayMode -> DisplayMode -> Bool # (/=) :: DisplayMode -> DisplayMode -> Bool # | |
Show DisplayMode Source # | |
Defined in SDL.Raw.Types showsPrec :: Int -> DisplayMode -> ShowS # show :: DisplayMode -> String # showList :: [DisplayMode] -> ShowS # | |
Storable DisplayMode Source # | |
Defined in SDL.Raw.Types sizeOf :: DisplayMode -> Int # alignment :: DisplayMode -> Int # peekElemOff :: Ptr DisplayMode -> Int -> IO DisplayMode # pokeElemOff :: Ptr DisplayMode -> Int -> DisplayMode -> IO () # peekByteOff :: Ptr b -> Int -> IO DisplayMode # pokeByteOff :: Ptr b -> Int -> DisplayMode -> IO () # peek :: Ptr DisplayMode -> IO DisplayMode # poke :: Ptr DisplayMode -> DisplayMode -> IO () # |
Instances
Eq Event Source # | |
Show Event Source # | |
Storable Event Source # | |
Instances
Eq Finger Source # | |
Show Finger Source # | |
Storable Finger Source # | |
data GameControllerButtonBind Source #
GameControllerButtonBindNone | |
GameControllerButtonBindButton | |
GameControllerButtonBindAxis | |
GameControllerButtonBindHat | |
Instances
Eq GameControllerButtonBind Source # | |
Defined in SDL.Raw.Types | |
Show GameControllerButtonBind Source # | |
Defined in SDL.Raw.Types showsPrec :: Int -> GameControllerButtonBind -> ShowS # show :: GameControllerButtonBind -> String # showList :: [GameControllerButtonBind] -> ShowS # | |
Storable GameControllerButtonBind Source # | |
Defined in SDL.Raw.Types sizeOf :: GameControllerButtonBind -> Int # alignment :: GameControllerButtonBind -> Int # peekElemOff :: Ptr GameControllerButtonBind -> Int -> IO GameControllerButtonBind # pokeElemOff :: Ptr GameControllerButtonBind -> Int -> GameControllerButtonBind -> IO () # peekByteOff :: Ptr b -> Int -> IO GameControllerButtonBind # pokeByteOff :: Ptr b -> Int -> GameControllerButtonBind -> IO () # peek :: Ptr GameControllerButtonBind -> IO GameControllerButtonBind # poke :: Ptr GameControllerButtonBind -> GameControllerButtonBind -> IO () # |
data HapticDirection Source #
HapticDirection | |
|
Instances
Eq HapticDirection Source # | |
Defined in SDL.Raw.Types (==) :: HapticDirection -> HapticDirection -> Bool # (/=) :: HapticDirection -> HapticDirection -> Bool # | |
Show HapticDirection Source # | |
Defined in SDL.Raw.Types showsPrec :: Int -> HapticDirection -> ShowS # show :: HapticDirection -> String # showList :: [HapticDirection] -> ShowS # | |
Storable HapticDirection Source # | |
Defined in SDL.Raw.Types sizeOf :: HapticDirection -> Int # alignment :: HapticDirection -> Int # peekElemOff :: Ptr HapticDirection -> Int -> IO HapticDirection # pokeElemOff :: Ptr HapticDirection -> Int -> HapticDirection -> IO () # peekByteOff :: Ptr b -> Int -> IO HapticDirection # pokeByteOff :: Ptr b -> Int -> HapticDirection -> IO () # peek :: Ptr HapticDirection -> IO HapticDirection # poke :: Ptr HapticDirection -> HapticDirection -> IO () # |
data HapticEffect Source #
Instances
Eq HapticEffect Source # | |
Defined in SDL.Raw.Types (==) :: HapticEffect -> HapticEffect -> Bool # (/=) :: HapticEffect -> HapticEffect -> Bool # | |
Show HapticEffect Source # | |
Defined in SDL.Raw.Types showsPrec :: Int -> HapticEffect -> ShowS # show :: HapticEffect -> String # showList :: [HapticEffect] -> ShowS # | |
Storable HapticEffect Source # | |
Defined in SDL.Raw.Types sizeOf :: HapticEffect -> Int # alignment :: HapticEffect -> Int # peekElemOff :: Ptr HapticEffect -> Int -> IO HapticEffect # pokeElemOff :: Ptr HapticEffect -> Int -> HapticEffect -> IO () # peekByteOff :: Ptr b -> Int -> IO HapticEffect # pokeByteOff :: Ptr b -> Int -> HapticEffect -> IO () # peek :: Ptr HapticEffect -> IO HapticEffect # poke :: Ptr HapticEffect -> HapticEffect -> IO () # |
data JoystickGUID Source #
JoystickGUID | |
|
Instances
Eq JoystickGUID Source # | |
Defined in SDL.Raw.Types (==) :: JoystickGUID -> JoystickGUID -> Bool # (/=) :: JoystickGUID -> JoystickGUID -> Bool # | |
Show JoystickGUID Source # | |
Defined in SDL.Raw.Types showsPrec :: Int -> JoystickGUID -> ShowS # show :: JoystickGUID -> String # showList :: [JoystickGUID] -> ShowS # | |
Storable JoystickGUID Source # | |
Defined in SDL.Raw.Types sizeOf :: JoystickGUID -> Int # alignment :: JoystickGUID -> Int # peekElemOff :: Ptr JoystickGUID -> Int -> IO JoystickGUID # pokeElemOff :: Ptr JoystickGUID -> Int -> JoystickGUID -> IO () # peekByteOff :: Ptr b -> Int -> IO JoystickGUID # pokeByteOff :: Ptr b -> Int -> JoystickGUID -> IO () # peek :: Ptr JoystickGUID -> IO JoystickGUID # poke :: Ptr JoystickGUID -> JoystickGUID -> IO () # |
Keysym | |
|
Instances
Eq Keysym Source # | |
Show Keysym Source # | |
Storable Keysym Source # | |
data MessageBoxButtonData Source #
Instances
Eq MessageBoxButtonData Source # | |
Defined in SDL.Raw.Types (==) :: MessageBoxButtonData -> MessageBoxButtonData -> Bool # (/=) :: MessageBoxButtonData -> MessageBoxButtonData -> Bool # | |
Show MessageBoxButtonData Source # | |
Defined in SDL.Raw.Types showsPrec :: Int -> MessageBoxButtonData -> ShowS # show :: MessageBoxButtonData -> String # showList :: [MessageBoxButtonData] -> ShowS # | |
Storable MessageBoxButtonData Source # | |
Defined in SDL.Raw.Types sizeOf :: MessageBoxButtonData -> Int # alignment :: MessageBoxButtonData -> Int # peekElemOff :: Ptr MessageBoxButtonData -> Int -> IO MessageBoxButtonData # pokeElemOff :: Ptr MessageBoxButtonData -> Int -> MessageBoxButtonData -> IO () # peekByteOff :: Ptr b -> Int -> IO MessageBoxButtonData # pokeByteOff :: Ptr b -> Int -> MessageBoxButtonData -> IO () # peek :: Ptr MessageBoxButtonData -> IO MessageBoxButtonData # poke :: Ptr MessageBoxButtonData -> MessageBoxButtonData -> IO () # |
data MessageBoxColor Source #
Instances
Eq MessageBoxColor Source # | |
Defined in SDL.Raw.Types (==) :: MessageBoxColor -> MessageBoxColor -> Bool # (/=) :: MessageBoxColor -> MessageBoxColor -> Bool # | |
Show MessageBoxColor Source # | |
Defined in SDL.Raw.Types showsPrec :: Int -> MessageBoxColor -> ShowS # show :: MessageBoxColor -> String # showList :: [MessageBoxColor] -> ShowS # | |
Storable MessageBoxColor Source # | |
Defined in SDL.Raw.Types sizeOf :: MessageBoxColor -> Int # alignment :: MessageBoxColor -> Int # peekElemOff :: Ptr MessageBoxColor -> Int -> IO MessageBoxColor # pokeElemOff :: Ptr MessageBoxColor -> Int -> MessageBoxColor -> IO () # peekByteOff :: Ptr b -> Int -> IO MessageBoxColor # pokeByteOff :: Ptr b -> Int -> MessageBoxColor -> IO () # peek :: Ptr MessageBoxColor -> IO MessageBoxColor # poke :: Ptr MessageBoxColor -> MessageBoxColor -> IO () # |
data MessageBoxColorScheme Source #
Instances
Eq MessageBoxColorScheme Source # | |
Defined in SDL.Raw.Types (==) :: MessageBoxColorScheme -> MessageBoxColorScheme -> Bool # (/=) :: MessageBoxColorScheme -> MessageBoxColorScheme -> Bool # | |
Show MessageBoxColorScheme Source # | |
Defined in SDL.Raw.Types showsPrec :: Int -> MessageBoxColorScheme -> ShowS # show :: MessageBoxColorScheme -> String # showList :: [MessageBoxColorScheme] -> ShowS # | |
Storable MessageBoxColorScheme Source # | |
Defined in SDL.Raw.Types sizeOf :: MessageBoxColorScheme -> Int # alignment :: MessageBoxColorScheme -> Int # peekElemOff :: Ptr MessageBoxColorScheme -> Int -> IO MessageBoxColorScheme # pokeElemOff :: Ptr MessageBoxColorScheme -> Int -> MessageBoxColorScheme -> IO () # peekByteOff :: Ptr b -> Int -> IO MessageBoxColorScheme # pokeByteOff :: Ptr b -> Int -> MessageBoxColorScheme -> IO () # peek :: Ptr MessageBoxColorScheme -> IO MessageBoxColorScheme # poke :: Ptr MessageBoxColorScheme -> MessageBoxColorScheme -> IO () # |
data MessageBoxData Source #
Instances
Eq MessageBoxData Source # | |
Defined in SDL.Raw.Types (==) :: MessageBoxData -> MessageBoxData -> Bool # (/=) :: MessageBoxData -> MessageBoxData -> Bool # | |
Show MessageBoxData Source # | |
Defined in SDL.Raw.Types showsPrec :: Int -> MessageBoxData -> ShowS # show :: MessageBoxData -> String # showList :: [MessageBoxData] -> ShowS # | |
Storable MessageBoxData Source # | |
Defined in SDL.Raw.Types sizeOf :: MessageBoxData -> Int # alignment :: MessageBoxData -> Int # peekElemOff :: Ptr MessageBoxData -> Int -> IO MessageBoxData # pokeElemOff :: Ptr MessageBoxData -> Int -> MessageBoxData -> IO () # peekByteOff :: Ptr b -> Int -> IO MessageBoxData # pokeByteOff :: Ptr b -> Int -> MessageBoxData -> IO () # peek :: Ptr MessageBoxData -> IO MessageBoxData # poke :: Ptr MessageBoxData -> MessageBoxData -> IO () # |
Palette | |
|
Instances
Eq Palette Source # | |
Show Palette Source # | |
Storable Palette Source # | |
data PixelFormat Source #
Instances
Eq PixelFormat Source # | |
Defined in SDL.Raw.Types (==) :: PixelFormat -> PixelFormat -> Bool # (/=) :: PixelFormat -> PixelFormat -> Bool # | |
Show PixelFormat Source # | |
Defined in SDL.Raw.Types showsPrec :: Int -> PixelFormat -> ShowS # show :: PixelFormat -> String # showList :: [PixelFormat] -> ShowS # | |
Storable PixelFormat Source # | |
Defined in SDL.Raw.Types sizeOf :: PixelFormat -> Int # alignment :: PixelFormat -> Int # peekElemOff :: Ptr PixelFormat -> Int -> IO PixelFormat # pokeElemOff :: Ptr PixelFormat -> Int -> PixelFormat -> IO () # peekByteOff :: Ptr b -> Int -> IO PixelFormat # pokeByteOff :: Ptr b -> Int -> PixelFormat -> IO () # peek :: Ptr PixelFormat -> IO PixelFormat # poke :: Ptr PixelFormat -> PixelFormat -> IO () # |
Instances
Eq Point Source # | |
Show Point Source # | |
Storable Point Source # | |
data RendererInfo Source #
Instances
Eq RendererInfo Source # | |
Defined in SDL.Raw.Types (==) :: RendererInfo -> RendererInfo -> Bool # (/=) :: RendererInfo -> RendererInfo -> Bool # | |
Show RendererInfo Source # | |
Defined in SDL.Raw.Types showsPrec :: Int -> RendererInfo -> ShowS # show :: RendererInfo -> String # showList :: [RendererInfo] -> ShowS # | |
Storable RendererInfo Source # | |
Defined in SDL.Raw.Types sizeOf :: RendererInfo -> Int # alignment :: RendererInfo -> Int # peekElemOff :: Ptr RendererInfo -> Int -> IO RendererInfo # pokeElemOff :: Ptr RendererInfo -> Int -> RendererInfo -> IO () # peekByteOff :: Ptr b -> Int -> IO RendererInfo # pokeByteOff :: Ptr b -> Int -> RendererInfo -> IO () # peek :: Ptr RendererInfo -> IO RendererInfo # poke :: Ptr RendererInfo -> RendererInfo -> IO () # |
RWops | |
|
Instances
Eq RWops Source # | |
Show RWops Source # | |
Storable RWops Source # | |
Surface | |
|
Instances
Eq Surface Source # | |
Show Surface Source # | |
Storable Surface Source # | |
Version | |
|
Instances
Eq Version Source # | |
Show Version Source # | |
Storable Version Source # | |