Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
- 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 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 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 #
Data Structures
Atomic | |
|
AudioCVT | |
|
AudioSpec | |
|
data DisplayMode Source #
DisplayMode | |
|
data HapticDirection Source #
data HapticEffect Source #
data JoystickGUID Source #
JoystickGUID | |
|
Keysym | |
|
data MessageBoxColor Source #
Palette | |
|
data PixelFormat Source #
RWops | |
|
Surface | |
|