sdl2-2.5.4.0: Both high- and low-level bindings to the SDL library (version 2.0.6+).
Safe HaskellSafe-Inferred
LanguageHaskell2010

SDL.Raw.Types

Synopsis

Type Aliases

Function Types

type AudioCallback = FunPtr (Ptr () -> Ptr Word8 -> CInt -> IO ()) Source #

type HintCallback = FunPtr (Ptr () -> CString -> CString -> 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 Cond = Ptr () Source #

type Cursor = Ptr () Source #

type GLContext = Ptr () Source #

type Haptic = Ptr () Source #

type Joystick = Ptr () Source #

type Mutex = Ptr () Source #

type Renderer = Ptr () Source #

type Sem = Ptr () Source #

type SysWMinfo = Ptr () Source #

type SysWMmsg = Ptr () Source #

type Texture = Ptr () Source #

type Thread = Ptr () Source #

type Window = Ptr () Source #

Data Structures

data Atomic Source #

Constructors

Atomic 

Fields

Instances

Instances details
Storable Atomic Source # 
Instance details

Defined in SDL.Raw.Types

Show Atomic Source # 
Instance details

Defined in SDL.Raw.Types

Eq Atomic Source # 
Instance details

Defined in SDL.Raw.Types

Methods

(==) :: Atomic -> Atomic -> Bool #

(/=) :: Atomic -> Atomic -> Bool #

data Color Source #

Constructors

Color 

Fields

Instances

Instances details
Storable Color Source # 
Instance details

Defined in SDL.Raw.Types

Methods

sizeOf :: Color -> Int #

alignment :: Color -> Int #

peekElemOff :: Ptr Color -> Int -> IO Color #

pokeElemOff :: Ptr Color -> Int -> Color -> IO () #

peekByteOff :: Ptr b -> Int -> IO Color #

pokeByteOff :: Ptr b -> Int -> Color -> IO () #

peek :: Ptr Color -> IO Color #

poke :: Ptr Color -> Color -> IO () #

Show Color Source # 
Instance details

Defined in SDL.Raw.Types

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Eq Color Source # 
Instance details

Defined in SDL.Raw.Types

Methods

(==) :: Color -> Color -> Bool #

(/=) :: Color -> Color -> Bool #

data Event Source #

Constructors

WindowEvent 
KeyboardEvent 
TextEditingEvent 
TextInputEvent 
KeymapChangedEvent 
MouseMotionEvent 
MouseButtonEvent 
MouseWheelEvent 
JoyAxisEvent 
JoyBallEvent 
JoyHatEvent 
JoyButtonEvent 
JoyDeviceEvent 
ControllerAxisEvent 
ControllerButtonEvent 
ControllerDeviceEvent 
AudioDeviceEvent 
QuitEvent 
UserEvent 
SysWMEvent 
TouchFingerEvent 
MultiGestureEvent 
DollarGestureEvent 
DropEvent 
ClipboardUpdateEvent 
UnknownEvent 

Instances

Instances details
Storable Event Source # 
Instance details

Defined in SDL.Raw.Types

Methods

sizeOf :: Event -> Int #

alignment :: Event -> Int #

peekElemOff :: Ptr Event -> Int -> IO Event #

pokeElemOff :: Ptr Event -> Int -> Event -> IO () #

peekByteOff :: Ptr b -> Int -> IO Event #

pokeByteOff :: Ptr b -> Int -> Event -> IO () #

peek :: Ptr Event -> IO Event #

poke :: Ptr Event -> Event -> IO () #

Show Event Source # 
Instance details

Defined in SDL.Raw.Types

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Eq Event Source # 
Instance details

Defined in SDL.Raw.Types

Methods

(==) :: Event -> Event -> Bool #

(/=) :: Event -> Event -> Bool #

data Finger Source #

Constructors

Finger 

Instances

Instances details
Storable Finger Source # 
Instance details

Defined in SDL.Raw.Types

Show Finger Source # 
Instance details

Defined in SDL.Raw.Types

Eq Finger Source # 
Instance details

Defined in SDL.Raw.Types

Methods

(==) :: Finger -> Finger -> Bool #

(/=) :: Finger -> Finger -> Bool #

data HapticEffect Source #

Constructors

HapticConstant 
HapticPeriodic 
HapticCondition 
HapticRamp 
HapticLeftRight 
HapticCustom 

data Keysym Source #

Instances

Instances details
Storable Keysym Source # 
Instance details

Defined in SDL.Raw.Types

Show Keysym Source # 
Instance details

Defined in SDL.Raw.Types

Eq Keysym Source # 
Instance details

Defined in SDL.Raw.Types

Methods

(==) :: Keysym -> Keysym -> Bool #

(/=) :: Keysym -> Keysym -> Bool #

data Palette Source #

Constructors

Palette 

Instances

Instances details
Storable Palette Source # 
Instance details

Defined in SDL.Raw.Types

Show Palette Source # 
Instance details

Defined in SDL.Raw.Types

Eq Palette Source # 
Instance details

Defined in SDL.Raw.Types

Methods

(==) :: Palette -> Palette -> Bool #

(/=) :: Palette -> Palette -> Bool #

data Point Source #

Constructors

Point 

Fields

Instances

Instances details
Storable Point Source # 
Instance details

Defined in SDL.Raw.Types

Methods

sizeOf :: Point -> Int #

alignment :: Point -> Int #

peekElemOff :: Ptr Point -> Int -> IO Point #

pokeElemOff :: Ptr Point -> Int -> Point -> IO () #

peekByteOff :: Ptr b -> Int -> IO Point #

pokeByteOff :: Ptr b -> Int -> Point -> IO () #

peek :: Ptr Point -> IO Point #

poke :: Ptr Point -> Point -> IO () #

Show Point Source # 
Instance details

Defined in SDL.Raw.Types

Methods

showsPrec :: Int -> Point -> ShowS #

show :: Point -> String #

showList :: [Point] -> ShowS #

Eq Point Source # 
Instance details

Defined in SDL.Raw.Types

Methods

(==) :: Point -> Point -> Bool #

(/=) :: Point -> Point -> Bool #

data Rect Source #

Constructors

Rect 

Fields

Instances

Instances details
Storable Rect Source # 
Instance details

Defined in SDL.Raw.Types

Methods

sizeOf :: Rect -> Int #

alignment :: Rect -> Int #

peekElemOff :: Ptr Rect -> Int -> IO Rect #

pokeElemOff :: Ptr Rect -> Int -> Rect -> IO () #

peekByteOff :: Ptr b -> Int -> IO Rect #

pokeByteOff :: Ptr b -> Int -> Rect -> IO () #

peek :: Ptr Rect -> IO Rect #

poke :: Ptr Rect -> Rect -> IO () #

Show Rect Source # 
Instance details

Defined in SDL.Raw.Types

Methods

showsPrec :: Int -> Rect -> ShowS #

show :: Rect -> String #

showList :: [Rect] -> ShowS #

Eq Rect Source # 
Instance details

Defined in SDL.Raw.Types

Methods

(==) :: Rect -> Rect -> Bool #

(/=) :: Rect -> Rect -> Bool #

data FPoint Source #

Constructors

FPoint 

Fields

Instances

Instances details
Storable FPoint Source # 
Instance details

Defined in SDL.Raw.Types

Show FPoint Source # 
Instance details

Defined in SDL.Raw.Types

Eq FPoint Source # 
Instance details

Defined in SDL.Raw.Types

Methods

(==) :: FPoint -> FPoint -> Bool #

(/=) :: FPoint -> FPoint -> Bool #

data FRect Source #

Constructors

FRect 

Fields

Instances

Instances details
Storable FRect Source # 
Instance details

Defined in SDL.Raw.Types

Methods

sizeOf :: FRect -> Int #

alignment :: FRect -> Int #

peekElemOff :: Ptr FRect -> Int -> IO FRect #

pokeElemOff :: Ptr FRect -> Int -> FRect -> IO () #

peekByteOff :: Ptr b -> Int -> IO FRect #

pokeByteOff :: Ptr b -> Int -> FRect -> IO () #

peek :: Ptr FRect -> IO FRect #

poke :: Ptr FRect -> FRect -> IO () #

Show FRect Source # 
Instance details

Defined in SDL.Raw.Types

Methods

showsPrec :: Int -> FRect -> ShowS #

show :: FRect -> String #

showList :: [FRect] -> ShowS #

Eq FRect Source # 
Instance details

Defined in SDL.Raw.Types

Methods

(==) :: FRect -> FRect -> Bool #

(/=) :: FRect -> FRect -> Bool #

data RWops Source #

Constructors

RWops 

Fields

Instances

Instances details
Storable RWops Source # 
Instance details

Defined in SDL.Raw.Types

Methods

sizeOf :: RWops -> Int #

alignment :: RWops -> Int #

peekElemOff :: Ptr RWops -> Int -> IO RWops #

pokeElemOff :: Ptr RWops -> Int -> RWops -> IO () #

peekByteOff :: Ptr b -> Int -> IO RWops #

pokeByteOff :: Ptr b -> Int -> RWops -> IO () #

peek :: Ptr RWops -> IO RWops #

poke :: Ptr RWops -> RWops -> IO () #

Show RWops Source # 
Instance details

Defined in SDL.Raw.Types

Methods

showsPrec :: Int -> RWops -> ShowS #

show :: RWops -> String #

showList :: [RWops] -> ShowS #

Eq RWops Source # 
Instance details

Defined in SDL.Raw.Types

Methods

(==) :: RWops -> RWops -> Bool #

(/=) :: RWops -> RWops -> Bool #

data Surface Source #

Instances

Instances details
Storable Surface Source # 
Instance details

Defined in SDL.Raw.Types

Show Surface Source # 
Instance details

Defined in SDL.Raw.Types

Eq Surface Source # 
Instance details

Defined in SDL.Raw.Types

Methods

(==) :: Surface -> Surface -> Bool #

(/=) :: Surface -> Surface -> Bool #

data Version Source #

Constructors

Version 

Instances

Instances details
Storable Version Source # 
Instance details

Defined in SDL.Raw.Types

Show Version Source # 
Instance details

Defined in SDL.Raw.Types

Eq Version Source # 
Instance details

Defined in SDL.Raw.Types

Methods

(==) :: Version -> Version -> Bool #

(/=) :: Version -> Version -> Bool #