reflex-sdl2-0.3.0.3: SDL2 and reflex FRP
Safe HaskellSafe-Inferred
LanguageHaskell2010

Reflex.SDL2

Description

This module contains a minimum yet convenient API needed to get started writing reflex apps with sdl2.

For an example see app/Main.hs

Synopsis

Running an app

host Source #

Arguments

:: ConcreteReflexSDL2 ()

A concrete reflex-sdl2 network to run.

-> IO () 

Host a reflex-sdl2 app.

Gracefully shutting down an app

The reflex-sdl2 class

class (Reflex t, Monad m) => HasSDL2Events t m | m -> t where Source #

Methods

getTicksEvent :: m (Event t Word32) Source #

getAnySDLEvent :: m (Event t EventPayload) Source #

getWindowShownEvent :: m (Event t WindowShownEventData) Source #

getWindowHiddenEvent :: m (Event t WindowHiddenEventData) Source #

getWindowExposedEvent :: m (Event t WindowExposedEventData) Source #

getWindowMovedEvent :: m (Event t WindowMovedEventData) Source #

getWindowResizedEvent :: m (Event t WindowResizedEventData) Source #

getWindowSizeChangedEvent :: m (Event t WindowSizeChangedEventData) Source #

getWindowMinimizedEvent :: m (Event t WindowMinimizedEventData) Source #

getWindowMaximizedEvent :: m (Event t WindowMaximizedEventData) Source #

getWindowRestoredEvent :: m (Event t WindowRestoredEventData) Source #

getWindowGainedMouseFocusEvent :: m (Event t WindowGainedMouseFocusEventData) Source #

getWindowLostMouseFocusEvent :: m (Event t WindowLostMouseFocusEventData) Source #

getWindowGainedKeyboardFocusEvent :: m (Event t WindowGainedKeyboardFocusEventData) Source #

getWindowLostKeyboardFocusEvent :: m (Event t WindowLostKeyboardFocusEventData) Source #

getWindowClosedEvent :: m (Event t WindowClosedEventData) Source #

getKeyboardEvent :: m (Event t KeyboardEventData) Source #

getTextEditingEvent :: m (Event t TextEditingEventData) Source #

getTextInputEvent :: m (Event t TextInputEventData) Source #

getKeymapChangedEvent :: m (Event t ()) Source #

getMouseMotionEvent :: m (Event t MouseMotionEventData) Source #

getMouseButtonEvent :: m (Event t MouseButtonEventData) Source #

getMouseWheelEvent :: m (Event t MouseWheelEventData) Source #

getJoyAxisEvent :: m (Event t JoyAxisEventData) Source #

getJoyBallEvent :: m (Event t JoyBallEventData) Source #

getJoyHatEvent :: m (Event t JoyHatEventData) Source #

getJoyButtonEvent :: m (Event t JoyButtonEventData) Source #

getJoyDeviceEvent :: m (Event t JoyDeviceEventData) Source #

getControllerAxisEvent :: m (Event t ControllerAxisEventData) Source #

getControllerButtonEvent :: m (Event t ControllerButtonEventData) Source #

getControllerDeviceEvent :: m (Event t ControllerDeviceEventData) Source #

getAudioDeviceEvent :: m (Event t AudioDeviceEventData) Source #

getQuitEvent :: m (Event t ()) Source #

getUserEvent :: m (Event t UserEventData) Source #

getSysWMEvent :: m (Event t SysWMEventData) Source #

getTouchFingerEvent :: m (Event t TouchFingerEventData) Source #

getMultiGestureEvent :: m (Event t MultiGestureEventData) Source #

getDollarGestureEvent :: m (Event t DollarGestureEventData) Source #

getDropEvent :: m (Event t DropEventData) Source #

getClipboardUpdateEvent :: m (Event t ()) Source #

getUnknownEvent :: m (Event t UnknownEventData) Source #

getQuitVar :: m (MVar ()) Source #

Instances

Instances details
(ReflexHost t, Monad m) => HasSDL2Events t (ReflexSDL2T t m) Source # 
Instance details

Defined in Reflex.SDL2.Base

Methods

getTicksEvent :: ReflexSDL2T t m (Event t Word32) Source #

getAnySDLEvent :: ReflexSDL2T t m (Event t EventPayload) Source #

getWindowShownEvent :: ReflexSDL2T t m (Event t WindowShownEventData) Source #

getWindowHiddenEvent :: ReflexSDL2T t m (Event t WindowHiddenEventData) Source #

getWindowExposedEvent :: ReflexSDL2T t m (Event t WindowExposedEventData) Source #

getWindowMovedEvent :: ReflexSDL2T t m (Event t WindowMovedEventData) Source #

getWindowResizedEvent :: ReflexSDL2T t m (Event t WindowResizedEventData) Source #

getWindowSizeChangedEvent :: ReflexSDL2T t m (Event t WindowSizeChangedEventData) Source #

getWindowMinimizedEvent :: ReflexSDL2T t m (Event t WindowMinimizedEventData) Source #

getWindowMaximizedEvent :: ReflexSDL2T t m (Event t WindowMaximizedEventData) Source #

getWindowRestoredEvent :: ReflexSDL2T t m (Event t WindowRestoredEventData) Source #

getWindowGainedMouseFocusEvent :: ReflexSDL2T t m (Event t WindowGainedMouseFocusEventData) Source #

getWindowLostMouseFocusEvent :: ReflexSDL2T t m (Event t WindowLostMouseFocusEventData) Source #

getWindowGainedKeyboardFocusEvent :: ReflexSDL2T t m (Event t WindowGainedKeyboardFocusEventData) Source #

getWindowLostKeyboardFocusEvent :: ReflexSDL2T t m (Event t WindowLostKeyboardFocusEventData) Source #

getWindowClosedEvent :: ReflexSDL2T t m (Event t WindowClosedEventData) Source #

getKeyboardEvent :: ReflexSDL2T t m (Event t KeyboardEventData) Source #

getTextEditingEvent :: ReflexSDL2T t m (Event t TextEditingEventData) Source #

getTextInputEvent :: ReflexSDL2T t m (Event t TextInputEventData) Source #

getKeymapChangedEvent :: ReflexSDL2T t m (Event t ()) Source #

getMouseMotionEvent :: ReflexSDL2T t m (Event t MouseMotionEventData) Source #

getMouseButtonEvent :: ReflexSDL2T t m (Event t MouseButtonEventData) Source #

getMouseWheelEvent :: ReflexSDL2T t m (Event t MouseWheelEventData) Source #

getJoyAxisEvent :: ReflexSDL2T t m (Event t JoyAxisEventData) Source #

getJoyBallEvent :: ReflexSDL2T t m (Event t JoyBallEventData) Source #

getJoyHatEvent :: ReflexSDL2T t m (Event t JoyHatEventData) Source #

getJoyButtonEvent :: ReflexSDL2T t m (Event t JoyButtonEventData) Source #

getJoyDeviceEvent :: ReflexSDL2T t m (Event t JoyDeviceEventData) Source #

getControllerAxisEvent :: ReflexSDL2T t m (Event t ControllerAxisEventData) Source #

getControllerButtonEvent :: ReflexSDL2T t m (Event t ControllerButtonEventData) Source #

getControllerDeviceEvent :: ReflexSDL2T t m (Event t ControllerDeviceEventData) Source #

getAudioDeviceEvent :: ReflexSDL2T t m (Event t AudioDeviceEventData) Source #

getQuitEvent :: ReflexSDL2T t m (Event t ()) Source #

getUserEvent :: ReflexSDL2T t m (Event t UserEventData) Source #

getSysWMEvent :: ReflexSDL2T t m (Event t SysWMEventData) Source #

getTouchFingerEvent :: ReflexSDL2T t m (Event t TouchFingerEventData) Source #

getMultiGestureEvent :: ReflexSDL2T t m (Event t MultiGestureEventData) Source #

getDollarGestureEvent :: ReflexSDL2T t m (Event t DollarGestureEventData) Source #

getDropEvent :: ReflexSDL2T t m (Event t DropEventData) Source #

getClipboardUpdateEvent :: ReflexSDL2T t m (Event t ()) Source #

getUnknownEvent :: ReflexSDL2T t m (Event t UnknownEventData) Source #

getQuitVar :: ReflexSDL2T t m (MVar ()) Source #

HasSDL2Events t m => HasSDL2Events t (ReaderT r m) Source # 
Instance details

Defined in Reflex.SDL2.Class

Methods

getTicksEvent :: ReaderT r m (Event t Word32) Source #

getAnySDLEvent :: ReaderT r m (Event t EventPayload) Source #

getWindowShownEvent :: ReaderT r m (Event t WindowShownEventData) Source #

getWindowHiddenEvent :: ReaderT r m (Event t WindowHiddenEventData) Source #

getWindowExposedEvent :: ReaderT r m (Event t WindowExposedEventData) Source #

getWindowMovedEvent :: ReaderT r m (Event t WindowMovedEventData) Source #

getWindowResizedEvent :: ReaderT r m (Event t WindowResizedEventData) Source #

getWindowSizeChangedEvent :: ReaderT r m (Event t WindowSizeChangedEventData) Source #

getWindowMinimizedEvent :: ReaderT r m (Event t WindowMinimizedEventData) Source #

getWindowMaximizedEvent :: ReaderT r m (Event t WindowMaximizedEventData) Source #

getWindowRestoredEvent :: ReaderT r m (Event t WindowRestoredEventData) Source #

getWindowGainedMouseFocusEvent :: ReaderT r m (Event t WindowGainedMouseFocusEventData) Source #

getWindowLostMouseFocusEvent :: ReaderT r m (Event t WindowLostMouseFocusEventData) Source #

getWindowGainedKeyboardFocusEvent :: ReaderT r m (Event t WindowGainedKeyboardFocusEventData) Source #

getWindowLostKeyboardFocusEvent :: ReaderT r m (Event t WindowLostKeyboardFocusEventData) Source #

getWindowClosedEvent :: ReaderT r m (Event t WindowClosedEventData) Source #

getKeyboardEvent :: ReaderT r m (Event t KeyboardEventData) Source #

getTextEditingEvent :: ReaderT r m (Event t TextEditingEventData) Source #

getTextInputEvent :: ReaderT r m (Event t TextInputEventData) Source #

getKeymapChangedEvent :: ReaderT r m (Event t ()) Source #

getMouseMotionEvent :: ReaderT r m (Event t MouseMotionEventData) Source #

getMouseButtonEvent :: ReaderT r m (Event t MouseButtonEventData) Source #

getMouseWheelEvent :: ReaderT r m (Event t MouseWheelEventData) Source #

getJoyAxisEvent :: ReaderT r m (Event t JoyAxisEventData) Source #

getJoyBallEvent :: ReaderT r m (Event t JoyBallEventData) Source #

getJoyHatEvent :: ReaderT r m (Event t JoyHatEventData) Source #

getJoyButtonEvent :: ReaderT r m (Event t JoyButtonEventData) Source #

getJoyDeviceEvent :: ReaderT r m (Event t JoyDeviceEventData) Source #

getControllerAxisEvent :: ReaderT r m (Event t ControllerAxisEventData) Source #

getControllerButtonEvent :: ReaderT r m (Event t ControllerButtonEventData) Source #

getControllerDeviceEvent :: ReaderT r m (Event t ControllerDeviceEventData) Source #

getAudioDeviceEvent :: ReaderT r m (Event t AudioDeviceEventData) Source #

getQuitEvent :: ReaderT r m (Event t ()) Source #

getUserEvent :: ReaderT r m (Event t UserEventData) Source #

getSysWMEvent :: ReaderT r m (Event t SysWMEventData) Source #

getTouchFingerEvent :: ReaderT r m (Event t TouchFingerEventData) Source #

getMultiGestureEvent :: ReaderT r m (Event t MultiGestureEventData) Source #

getDollarGestureEvent :: ReaderT r m (Event t DollarGestureEventData) Source #

getDropEvent :: ReaderT r m (Event t DropEventData) Source #

getClipboardUpdateEvent :: ReaderT r m (Event t ()) Source #

getUnknownEvent :: ReaderT r m (Event t UnknownEventData) Source #

getQuitVar :: ReaderT r m (MVar ()) Source #

HasSDL2Events t m => HasSDL2Events t (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.SDL2.Class

Methods

getTicksEvent :: DynamicWriterT t w m (Event t Word32) Source #

getAnySDLEvent :: DynamicWriterT t w m (Event t EventPayload) Source #

getWindowShownEvent :: DynamicWriterT t w m (Event t WindowShownEventData) Source #

getWindowHiddenEvent :: DynamicWriterT t w m (Event t WindowHiddenEventData) Source #

getWindowExposedEvent :: DynamicWriterT t w m (Event t WindowExposedEventData) Source #

getWindowMovedEvent :: DynamicWriterT t w m (Event t WindowMovedEventData) Source #

getWindowResizedEvent :: DynamicWriterT t w m (Event t WindowResizedEventData) Source #

getWindowSizeChangedEvent :: DynamicWriterT t w m (Event t WindowSizeChangedEventData) Source #

getWindowMinimizedEvent :: DynamicWriterT t w m (Event t WindowMinimizedEventData) Source #

getWindowMaximizedEvent :: DynamicWriterT t w m (Event t WindowMaximizedEventData) Source #

getWindowRestoredEvent :: DynamicWriterT t w m (Event t WindowRestoredEventData) Source #

getWindowGainedMouseFocusEvent :: DynamicWriterT t w m (Event t WindowGainedMouseFocusEventData) Source #

getWindowLostMouseFocusEvent :: DynamicWriterT t w m (Event t WindowLostMouseFocusEventData) Source #

getWindowGainedKeyboardFocusEvent :: DynamicWriterT t w m (Event t WindowGainedKeyboardFocusEventData) Source #

getWindowLostKeyboardFocusEvent :: DynamicWriterT t w m (Event t WindowLostKeyboardFocusEventData) Source #

getWindowClosedEvent :: DynamicWriterT t w m (Event t WindowClosedEventData) Source #

getKeyboardEvent :: DynamicWriterT t w m (Event t KeyboardEventData) Source #

getTextEditingEvent :: DynamicWriterT t w m (Event t TextEditingEventData) Source #

getTextInputEvent :: DynamicWriterT t w m (Event t TextInputEventData) Source #

getKeymapChangedEvent :: DynamicWriterT t w m (Event t ()) Source #

getMouseMotionEvent :: DynamicWriterT t w m (Event t MouseMotionEventData) Source #

getMouseButtonEvent :: DynamicWriterT t w m (Event t MouseButtonEventData) Source #

getMouseWheelEvent :: DynamicWriterT t w m (Event t MouseWheelEventData) Source #

getJoyAxisEvent :: DynamicWriterT t w m (Event t JoyAxisEventData) Source #

getJoyBallEvent :: DynamicWriterT t w m (Event t JoyBallEventData) Source #

getJoyHatEvent :: DynamicWriterT t w m (Event t JoyHatEventData) Source #

getJoyButtonEvent :: DynamicWriterT t w m (Event t JoyButtonEventData) Source #

getJoyDeviceEvent :: DynamicWriterT t w m (Event t JoyDeviceEventData) Source #

getControllerAxisEvent :: DynamicWriterT t w m (Event t ControllerAxisEventData) Source #

getControllerButtonEvent :: DynamicWriterT t w m (Event t ControllerButtonEventData) Source #

getControllerDeviceEvent :: DynamicWriterT t w m (Event t ControllerDeviceEventData) Source #

getAudioDeviceEvent :: DynamicWriterT t w m (Event t AudioDeviceEventData) Source #

getQuitEvent :: DynamicWriterT t w m (Event t ()) Source #

getUserEvent :: DynamicWriterT t w m (Event t UserEventData) Source #

getSysWMEvent :: DynamicWriterT t w m (Event t SysWMEventData) Source #

getTouchFingerEvent :: DynamicWriterT t w m (Event t TouchFingerEventData) Source #

getMultiGestureEvent :: DynamicWriterT t w m (Event t MultiGestureEventData) Source #

getDollarGestureEvent :: DynamicWriterT t w m (Event t DollarGestureEventData) Source #

getDropEvent :: DynamicWriterT t w m (Event t DropEventData) Source #

getClipboardUpdateEvent :: DynamicWriterT t w m (Event t ()) Source #

getUnknownEvent :: DynamicWriterT t w m (Event t UnknownEventData) Source #

getQuitVar :: DynamicWriterT t w m (MVar ()) Source #

Base transformer

data ReflexSDL2T t (m :: Type -> Type) a Source #

Provides an implementation of the HasSDL2Events type class.

Instances

Instances details
(ReflexHost t, MonadHold t m) => MonadHold (t :: Type) (ReflexSDL2T t m) Source #

ReflexSDL2T is an instance of MonadHold.

Instance details

Defined in Reflex.SDL2.Base

Methods

hold :: a -> Event t a -> ReflexSDL2T t m (Behavior t a) #

holdDyn :: a -> Event t a -> ReflexSDL2T t m (Dynamic t a) #

holdIncremental :: Patch p => PatchTarget p -> Event t p -> ReflexSDL2T t m (Incremental t p) #

buildDynamic :: PushM t a -> Event t a -> ReflexSDL2T t m (Dynamic t a) #

headE :: Event t a -> ReflexSDL2T t m (Event t a) #

now :: ReflexSDL2T t m (Event t ()) #

(ReflexHost t, Applicative m, Monad m, MonadSample t m) => MonadSample (t :: Type) (ReflexSDL2T t m) Source #

ReflexSDL2T is an instance of MonadHold.

Instance details

Defined in Reflex.SDL2.Base

Methods

sample :: Behavior t a -> ReflexSDL2T t m a #

(ReflexHost t, Monad m) => HasSDL2Events t (ReflexSDL2T t m) Source # 
Instance details

Defined in Reflex.SDL2.Base

Methods

getTicksEvent :: ReflexSDL2T t m (Event t Word32) Source #

getAnySDLEvent :: ReflexSDL2T t m (Event t EventPayload) Source #

getWindowShownEvent :: ReflexSDL2T t m (Event t WindowShownEventData) Source #

getWindowHiddenEvent :: ReflexSDL2T t m (Event t WindowHiddenEventData) Source #

getWindowExposedEvent :: ReflexSDL2T t m (Event t WindowExposedEventData) Source #

getWindowMovedEvent :: ReflexSDL2T t m (Event t WindowMovedEventData) Source #

getWindowResizedEvent :: ReflexSDL2T t m (Event t WindowResizedEventData) Source #

getWindowSizeChangedEvent :: ReflexSDL2T t m (Event t WindowSizeChangedEventData) Source #

getWindowMinimizedEvent :: ReflexSDL2T t m (Event t WindowMinimizedEventData) Source #

getWindowMaximizedEvent :: ReflexSDL2T t m (Event t WindowMaximizedEventData) Source #

getWindowRestoredEvent :: ReflexSDL2T t m (Event t WindowRestoredEventData) Source #

getWindowGainedMouseFocusEvent :: ReflexSDL2T t m (Event t WindowGainedMouseFocusEventData) Source #

getWindowLostMouseFocusEvent :: ReflexSDL2T t m (Event t WindowLostMouseFocusEventData) Source #

getWindowGainedKeyboardFocusEvent :: ReflexSDL2T t m (Event t WindowGainedKeyboardFocusEventData) Source #

getWindowLostKeyboardFocusEvent :: ReflexSDL2T t m (Event t WindowLostKeyboardFocusEventData) Source #

getWindowClosedEvent :: ReflexSDL2T t m (Event t WindowClosedEventData) Source #

getKeyboardEvent :: ReflexSDL2T t m (Event t KeyboardEventData) Source #

getTextEditingEvent :: ReflexSDL2T t m (Event t TextEditingEventData) Source #

getTextInputEvent :: ReflexSDL2T t m (Event t TextInputEventData) Source #

getKeymapChangedEvent :: ReflexSDL2T t m (Event t ()) Source #

getMouseMotionEvent :: ReflexSDL2T t m (Event t MouseMotionEventData) Source #

getMouseButtonEvent :: ReflexSDL2T t m (Event t MouseButtonEventData) Source #

getMouseWheelEvent :: ReflexSDL2T t m (Event t MouseWheelEventData) Source #

getJoyAxisEvent :: ReflexSDL2T t m (Event t JoyAxisEventData) Source #

getJoyBallEvent :: ReflexSDL2T t m (Event t JoyBallEventData) Source #

getJoyHatEvent :: ReflexSDL2T t m (Event t JoyHatEventData) Source #

getJoyButtonEvent :: ReflexSDL2T t m (Event t JoyButtonEventData) Source #

getJoyDeviceEvent :: ReflexSDL2T t m (Event t JoyDeviceEventData) Source #

getControllerAxisEvent :: ReflexSDL2T t m (Event t ControllerAxisEventData) Source #

getControllerButtonEvent :: ReflexSDL2T t m (Event t ControllerButtonEventData) Source #

getControllerDeviceEvent :: ReflexSDL2T t m (Event t ControllerDeviceEventData) Source #

getAudioDeviceEvent :: ReflexSDL2T t m (Event t AudioDeviceEventData) Source #

getQuitEvent :: ReflexSDL2T t m (Event t ()) Source #

getUserEvent :: ReflexSDL2T t m (Event t UserEventData) Source #

getSysWMEvent :: ReflexSDL2T t m (Event t SysWMEventData) Source #

getTouchFingerEvent :: ReflexSDL2T t m (Event t TouchFingerEventData) Source #

getMultiGestureEvent :: ReflexSDL2T t m (Event t MultiGestureEventData) Source #

getDollarGestureEvent :: ReflexSDL2T t m (Event t DollarGestureEventData) Source #

getDropEvent :: ReflexSDL2T t m (Event t DropEventData) Source #

getClipboardUpdateEvent :: ReflexSDL2T t m (Event t ()) Source #

getUnknownEvent :: ReflexSDL2T t m (Event t UnknownEventData) Source #

getQuitVar :: ReflexSDL2T t m (MVar ()) Source #

(Reflex t, ReflexHost t, Adjustable t m, Monad m) => Adjustable t (ReflexSDL2T t m) Source #

ReflexSDL2T is an instance of Adjustable.

Instance details

Defined in Reflex.SDL2.Base

Methods

runWithReplace :: ReflexSDL2T t m a -> Event t (ReflexSDL2T t m b) -> ReflexSDL2T t m (a, Event t b) #

traverseIntMapWithKeyWithAdjust :: (Key -> v -> ReflexSDL2T t m v') -> IntMap v -> Event t (PatchIntMap v) -> ReflexSDL2T t m (IntMap v', Event t (PatchIntMap v')) #

traverseDMapWithKeyWithAdjust :: GCompare k => (forall a. k a -> v a -> ReflexSDL2T t m (v' a)) -> DMap k v -> Event t (PatchDMap k v) -> ReflexSDL2T t m (DMap k v', Event t (PatchDMap k v')) #

traverseDMapWithKeyWithAdjustWithMove :: GCompare k => (forall a. k a -> v a -> ReflexSDL2T t m (v' a)) -> DMap k v -> Event t (PatchDMapWithMove k v) -> ReflexSDL2T t m (DMap k v', Event t (PatchDMapWithMove k v')) #

(ReflexHost t, PerformEvent t m) => PerformEvent t (ReflexSDL2T t m) Source #

ReflexSDL2T is an instance of PerformEvent.

Instance details

Defined in Reflex.SDL2.Base

Associated Types

type Performable (ReflexSDL2T t m) :: Type -> Type #

Methods

performEvent :: Event t (Performable (ReflexSDL2T t m) a) -> ReflexSDL2T t m (Event t a) #

performEvent_ :: Event t (Performable (ReflexSDL2T t m) ()) -> ReflexSDL2T t m () #

(Reflex t, PostBuild t m, ReflexHost t, Monad m) => PostBuild t (ReflexSDL2T t m) Source #

ReflexSDL2T is an instance of PostBuild.

Instance details

Defined in Reflex.SDL2.Base

Methods

getPostBuild :: ReflexSDL2T t m (Event t ()) #

(ReflexHost t, TriggerEvent t m) => TriggerEvent t (ReflexSDL2T t m) Source # 
Instance details

Defined in Reflex.SDL2.Base

Methods

newTriggerEvent :: ReflexSDL2T t m (Event t a, a -> IO ()) #

newTriggerEventWithOnComplete :: ReflexSDL2T t m (Event t a, a -> IO () -> IO ()) #

newEventWithLazyTriggerWithOnComplete :: ((a -> IO () -> IO ()) -> IO (IO ())) -> ReflexSDL2T t m (Event t a) #

ReflexHost t => MonadTrans (ReflexSDL2T t) Source # 
Instance details

Defined in Reflex.SDL2.Base

Methods

lift :: Monad m => m a -> ReflexSDL2T t m a #

(ReflexHost t, MonadFix m) => MonadFix (ReflexSDL2T t m) Source # 
Instance details

Defined in Reflex.SDL2.Base

Methods

mfix :: (a -> ReflexSDL2T t m a) -> ReflexSDL2T t m a #

(ReflexHost t, MonadIO m) => MonadIO (ReflexSDL2T t m) Source # 
Instance details

Defined in Reflex.SDL2.Base

Methods

liftIO :: IO a -> ReflexSDL2T t m a #

(ReflexHost t, Applicative m) => Applicative (ReflexSDL2T t m) Source # 
Instance details

Defined in Reflex.SDL2.Base

Methods

pure :: a -> ReflexSDL2T t m a #

(<*>) :: ReflexSDL2T t m (a -> b) -> ReflexSDL2T t m a -> ReflexSDL2T t m b #

liftA2 :: (a -> b -> c) -> ReflexSDL2T t m a -> ReflexSDL2T t m b -> ReflexSDL2T t m c #

(*>) :: ReflexSDL2T t m a -> ReflexSDL2T t m b -> ReflexSDL2T t m b #

(<*) :: ReflexSDL2T t m a -> ReflexSDL2T t m b -> ReflexSDL2T t m a #

(ReflexHost t, Functor m) => Functor (ReflexSDL2T t m) Source # 
Instance details

Defined in Reflex.SDL2.Base

Methods

fmap :: (a -> b) -> ReflexSDL2T t m a -> ReflexSDL2T t m b #

(<$) :: a -> ReflexSDL2T t m b -> ReflexSDL2T t m a #

(ReflexHost t, Monad m) => Monad (ReflexSDL2T t m) Source # 
Instance details

Defined in Reflex.SDL2.Base

Methods

(>>=) :: ReflexSDL2T t m a -> (a -> ReflexSDL2T t m b) -> ReflexSDL2T t m b #

(>>) :: ReflexSDL2T t m a -> ReflexSDL2T t m b -> ReflexSDL2T t m b #

return :: a -> ReflexSDL2T t m a #

(ReflexHost t, MonadException m) => MonadException (ReflexSDL2T t m) Source # 
Instance details

Defined in Reflex.SDL2.Base

Methods

throw :: Exception e => e -> ReflexSDL2T t m a #

catch :: Exception e => ReflexSDL2T t m a -> (e -> ReflexSDL2T t m a) -> ReflexSDL2T t m a #

finally :: ReflexSDL2T t m a -> ReflexSDL2T t m b -> ReflexSDL2T t m a #

type Performable (ReflexSDL2T t m) Source # 
Instance details

Defined in Reflex.SDL2.Base

Common constraints (most powerful but convenient)

type ReflexSDL2 t m = (Reflex t, MonadHold t m, MonadSample t m, Adjustable t m, PostBuild t m, PerformEvent t m, TriggerEvent t m, MonadFix m, MonadIO m, MonadIO (Performable m), HasSDL2Events t m) Source #

A collection of constraints that represent the default reflex-sdl2 network.

Concrete stack

type ConcreteReflexSDL2 = ReflexSDL2T Spider (TriggerEventT Spider (PostBuildT Spider (PerformEventT Spider (SpiderHost Global)))) Source #

The monomorphic type used to run reflex-sdl2 apps.

Higher order switching

holdView :: ReflexSDL2 t m => m a -> Event t (m a) -> m (Dynamic t a) Source #

Run a placeholder network until the given Event fires, then replace it with the network of the Events value. This process is repeated each time the Event fires a new network. Returns a Dynamic of the inner network's result that updates any time the Event fires.

dynView :: ReflexSDL2 t m => Dynamic t (m a) -> m (Event t a) Source #

Run a Dynamically changing network, replacing the current one with the new one every time the Dynamic updates. Returns an Event of the inner network's result value that fires every time the Dynamic changes.

Time and recurring timer events

data TickInfo #

Metadata associated with a timer "tick"

Constructors

TickInfo 

Fields

Instances

Instances details
Show TickInfo 
Instance details

Defined in Reflex.Time

Eq TickInfo 
Instance details

Defined in Reflex.Time

Ord TickInfo 
Instance details

Defined in Reflex.Time

getDeltaTickEvent :: (MonadHold t m, MonadFix m, HasSDL2Events t m) => m (Event t Word32) Source #

Returns an event that fires each frame with the number of milliseconds since the last frame. Be aware that subscribing to this Event (by using it in a monadic action) will result in your app running sdl2's event loop every frame.

performEventDelta :: ReflexSDL2 t m => Event t a -> m (Event t Word32) Source #

Populate the event value with the time in milliseconds since the last time the event fired.

Async events

getAsyncEvent :: ReflexSDL2 t m => IO a -> m (Event t a) Source #

Debugging

putDebugLnE Source #

Arguments

:: (PerformEvent t m, Reflex t, MonadIO (Performable m)) 
=> Event t a

The Event to trigger the print.

-> (a -> String)

A function to show the Events value.

-> m () 

Like putStrLn, but for Events.

Re-exports

newtype V1 a #

A 1-dimensional vector

>>> pure 1 :: V1 Int
V1 1
>>> V1 2 + V1 3
V1 5
>>> V1 2 * V1 3
V1 6
>>> sum (V1 2)
2

Constructors

V1 a 

Instances

Instances details
MonadFix V1 
Instance details

Defined in Linear.V1

Methods

mfix :: (a -> V1 a) -> V1 a #

MonadZip V1 
Instance details

Defined in Linear.V1

Methods

mzip :: V1 a -> V1 b -> V1 (a, b) #

mzipWith :: (a -> b -> c) -> V1 a -> V1 b -> V1 c #

munzip :: V1 (a, b) -> (V1 a, V1 b) #

Foldable V1 
Instance details

Defined in Linear.V1

Methods

fold :: Monoid m => V1 m -> m #

foldMap :: Monoid m => (a -> m) -> V1 a -> m #

foldMap' :: Monoid m => (a -> m) -> V1 a -> m #

foldr :: (a -> b -> b) -> b -> V1 a -> b #

foldr' :: (a -> b -> b) -> b -> V1 a -> b #

foldl :: (b -> a -> b) -> b -> V1 a -> b #

foldl' :: (b -> a -> b) -> b -> V1 a -> b #

foldr1 :: (a -> a -> a) -> V1 a -> a #

foldl1 :: (a -> a -> a) -> V1 a -> a #

toList :: V1 a -> [a] #

null :: V1 a -> Bool #

length :: V1 a -> Int #

elem :: Eq a => a -> V1 a -> Bool #

maximum :: Ord a => V1 a -> a #

minimum :: Ord a => V1 a -> a #

sum :: Num a => V1 a -> a #

product :: Num a => V1 a -> a #

Eq1 V1 
Instance details

Defined in Linear.V1

Methods

liftEq :: (a -> b -> Bool) -> V1 a -> V1 b -> Bool #

Ord1 V1 
Instance details

Defined in Linear.V1

Methods

liftCompare :: (a -> b -> Ordering) -> V1 a -> V1 b -> Ordering #

Read1 V1 
Instance details

Defined in Linear.V1

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V1 a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [V1 a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (V1 a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [V1 a] #

Show1 V1 
Instance details

Defined in Linear.V1

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V1 a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [V1 a] -> ShowS #

Traversable V1 
Instance details

Defined in Linear.V1

Methods

traverse :: Applicative f => (a -> f b) -> V1 a -> f (V1 b) #

sequenceA :: Applicative f => V1 (f a) -> f (V1 a) #

mapM :: Monad m => (a -> m b) -> V1 a -> m (V1 b) #

sequence :: Monad m => V1 (m a) -> m (V1 a) #

Applicative V1 
Instance details

Defined in Linear.V1

Methods

pure :: a -> V1 a #

(<*>) :: V1 (a -> b) -> V1 a -> V1 b #

liftA2 :: (a -> b -> c) -> V1 a -> V1 b -> V1 c #

(*>) :: V1 a -> V1 b -> V1 b #

(<*) :: V1 a -> V1 b -> V1 a #

Functor V1 
Instance details

Defined in Linear.V1

Methods

fmap :: (a -> b) -> V1 a -> V1 b #

(<$) :: a -> V1 b -> V1 a #

Monad V1 
Instance details

Defined in Linear.V1

Methods

(>>=) :: V1 a -> (a -> V1 b) -> V1 b #

(>>) :: V1 a -> V1 b -> V1 b #

return :: a -> V1 a #

Serial1 V1 
Instance details

Defined in Linear.V1

Methods

serializeWith :: MonadPut m => (a -> m ()) -> V1 a -> m () #

deserializeWith :: MonadGet m => m a -> m (V1 a) #

Representable V1 
Instance details

Defined in Linear.V1

Associated Types

type Rep V1 #

Methods

tabulate :: (Rep V1 -> a) -> V1 a #

index :: V1 a -> Rep V1 -> a #

Distributive V1 
Instance details

Defined in Linear.V1

Methods

distribute :: Functor f => f (V1 a) -> V1 (f a) #

collect :: Functor f => (a -> V1 b) -> f a -> V1 (f b) #

distributeM :: Monad m => m (V1 a) -> V1 (m a) #

collectM :: Monad m => (a -> V1 b) -> m a -> V1 (m b) #

Foldable1 V1 
Instance details

Defined in Linear.V1

Methods

fold1 :: Semigroup m => V1 m -> m #

foldMap1 :: Semigroup m => (a -> m) -> V1 a -> m #

foldMap1' :: Semigroup m => (a -> m) -> V1 a -> m #

toNonEmpty :: V1 a -> NonEmpty a #

maximum :: Ord a => V1 a -> a #

minimum :: Ord a => V1 a -> a #

head :: V1 a -> a #

last :: V1 a -> a #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> V1 a -> b #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> V1 a -> b #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> V1 a -> b #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> V1 a -> b #

Hashable1 V1 
Instance details

Defined in Linear.V1

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> V1 a -> Int #

Affine V1 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V1 :: Type -> Type #

Methods

(.-.) :: Num a => V1 a -> V1 a -> Diff V1 a #

(.+^) :: Num a => V1 a -> Diff V1 a -> V1 a #

(.-^) :: Num a => V1 a -> Diff V1 a -> V1 a #

Metric V1 
Instance details

Defined in Linear.V1

Methods

dot :: Num a => V1 a -> V1 a -> a #

quadrance :: Num a => V1 a -> a #

qd :: Num a => V1 a -> V1 a -> a #

distance :: Floating a => V1 a -> V1 a -> a #

norm :: Floating a => V1 a -> a #

signorm :: Floating a => V1 a -> V1 a #

Trace V1 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => V1 (V1 a) -> a #

diagonal :: V1 (V1 a) -> V1 a #

Finite V1 
Instance details

Defined in Linear.V1

Associated Types

type Size V1 :: Nat #

Methods

toV :: V1 a -> V (Size V1) a #

fromV :: V (Size V1) a -> V1 a #

R1 V1 
Instance details

Defined in Linear.V1

Methods

_x :: Lens' (V1 a) a #

Additive V1 
Instance details

Defined in Linear.V1

Methods

zero :: Num a => V1 a #

(^+^) :: Num a => V1 a -> V1 a -> V1 a #

(^-^) :: Num a => V1 a -> V1 a -> V1 a #

lerp :: Num a => a -> V1 a -> V1 a -> V1 a #

liftU2 :: (a -> a -> a) -> V1 a -> V1 a -> V1 a #

liftI2 :: (a -> b -> c) -> V1 a -> V1 b -> V1 c #

Apply V1 
Instance details

Defined in Linear.V1

Methods

(<.>) :: V1 (a -> b) -> V1 a -> V1 b #

(.>) :: V1 a -> V1 b -> V1 b #

(<.) :: V1 a -> V1 b -> V1 a #

liftF2 :: (a -> b -> c) -> V1 a -> V1 b -> V1 c #

Bind V1 
Instance details

Defined in Linear.V1

Methods

(>>-) :: V1 a -> (a -> V1 b) -> V1 b #

join :: V1 (V1 a) -> V1 a #

Traversable1 V1 
Instance details

Defined in Linear.V1

Methods

traverse1 :: Apply f => (a -> f b) -> V1 a -> f (V1 b) #

sequence1 :: Apply f => V1 (f b) -> f (V1 b) #

Generic1 V1 
Instance details

Defined in Linear.V1

Associated Types

type Rep1 V1 :: k -> Type #

Methods

from1 :: forall (a :: k). V1 a -> Rep1 V1 a #

to1 :: forall (a :: k). Rep1 V1 a -> V1 a #

Num r => Algebra r (E V1) 
Instance details

Defined in Linear.Algebra

Methods

mult :: (E V1 -> E V1 -> r) -> E V1 -> r #

unital :: r -> E V1 -> r #

Num r => Coalgebra r (E V1) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V1 -> r) -> E V1 -> E V1 -> r #

counital :: (E V1 -> r) -> r #

Lift a => Lift (V1 a :: Type) 
Instance details

Defined in Linear.V1

Methods

lift :: Quote m => V1 a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => V1 a -> Code m (V1 a) #

Unbox a => Vector Vector (V1 a) 
Instance details

Defined in Linear.V1

Methods

basicUnsafeFreeze :: Mutable Vector s (V1 a) -> ST s (Vector (V1 a)) #

basicUnsafeThaw :: Vector (V1 a) -> ST s (Mutable Vector s (V1 a)) #

basicLength :: Vector (V1 a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V1 a) -> Vector (V1 a) #

basicUnsafeIndexM :: Vector (V1 a) -> Int -> Box (V1 a) #

basicUnsafeCopy :: Mutable Vector s (V1 a) -> Vector (V1 a) -> ST s () #

elemseq :: Vector (V1 a) -> V1 a -> b -> b #

Unbox a => MVector MVector (V1 a) 
Instance details

Defined in Linear.V1

Methods

basicLength :: MVector s (V1 a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V1 a) -> MVector s (V1 a) #

basicOverlaps :: MVector s (V1 a) -> MVector s (V1 a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (V1 a)) #

basicInitialize :: MVector s (V1 a) -> ST s () #

basicUnsafeReplicate :: Int -> V1 a -> ST s (MVector s (V1 a)) #

basicUnsafeRead :: MVector s (V1 a) -> Int -> ST s (V1 a) #

basicUnsafeWrite :: MVector s (V1 a) -> Int -> V1 a -> ST s () #

basicClear :: MVector s (V1 a) -> ST s () #

basicSet :: MVector s (V1 a) -> V1 a -> ST s () #

basicUnsafeCopy :: MVector s (V1 a) -> MVector s (V1 a) -> ST s () #

basicUnsafeMove :: MVector s (V1 a) -> MVector s (V1 a) -> ST s () #

basicUnsafeGrow :: MVector s (V1 a) -> Int -> ST s (MVector s (V1 a)) #

Data a => Data (V1 a) 
Instance details

Defined in Linear.V1

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V1 a -> c (V1 a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V1 a) #

toConstr :: V1 a -> Constr #

dataTypeOf :: V1 a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V1 a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V1 a)) #

gmapT :: (forall b. Data b => b -> b) -> V1 a -> V1 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V1 a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V1 a -> r #

gmapQ :: (forall d. Data d => d -> u) -> V1 a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> V1 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> V1 a -> m (V1 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V1 a -> m (V1 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V1 a -> m (V1 a) #

Storable a => Storable (V1 a) 
Instance details

Defined in Linear.V1

Methods

sizeOf :: V1 a -> Int #

alignment :: V1 a -> Int #

peekElemOff :: Ptr (V1 a) -> Int -> IO (V1 a) #

pokeElemOff :: Ptr (V1 a) -> Int -> V1 a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (V1 a) #

pokeByteOff :: Ptr b -> Int -> V1 a -> IO () #

peek :: Ptr (V1 a) -> IO (V1 a) #

poke :: Ptr (V1 a) -> V1 a -> IO () #

Monoid a => Monoid (V1 a) 
Instance details

Defined in Linear.V1

Methods

mempty :: V1 a #

mappend :: V1 a -> V1 a -> V1 a #

mconcat :: [V1 a] -> V1 a #

Semigroup a => Semigroup (V1 a) 
Instance details

Defined in Linear.V1

Methods

(<>) :: V1 a -> V1 a -> V1 a #

sconcat :: NonEmpty (V1 a) -> V1 a #

stimes :: Integral b => b -> V1 a -> V1 a #

Bounded a => Bounded (V1 a) 
Instance details

Defined in Linear.V1

Methods

minBound :: V1 a #

maxBound :: V1 a #

Floating a => Floating (V1 a) 
Instance details

Defined in Linear.V1

Methods

pi :: V1 a #

exp :: V1 a -> V1 a #

log :: V1 a -> V1 a #

sqrt :: V1 a -> V1 a #

(**) :: V1 a -> V1 a -> V1 a #

logBase :: V1 a -> V1 a -> V1 a #

sin :: V1 a -> V1 a #

cos :: V1 a -> V1 a #

tan :: V1 a -> V1 a #

asin :: V1 a -> V1 a #

acos :: V1 a -> V1 a #

atan :: V1 a -> V1 a #

sinh :: V1 a -> V1 a #

cosh :: V1 a -> V1 a #

tanh :: V1 a -> V1 a #

asinh :: V1 a -> V1 a #

acosh :: V1 a -> V1 a #

atanh :: V1 a -> V1 a #

log1p :: V1 a -> V1 a #

expm1 :: V1 a -> V1 a #

log1pexp :: V1 a -> V1 a #

log1mexp :: V1 a -> V1 a #

Generic (V1 a) 
Instance details

Defined in Linear.V1

Associated Types

type Rep (V1 a) :: Type -> Type #

Methods

from :: V1 a -> Rep (V1 a) x #

to :: Rep (V1 a) x -> V1 a #

Ix a => Ix (V1 a) 
Instance details

Defined in Linear.V1

Methods

range :: (V1 a, V1 a) -> [V1 a] #

index :: (V1 a, V1 a) -> V1 a -> Int #

unsafeIndex :: (V1 a, V1 a) -> V1 a -> Int #

inRange :: (V1 a, V1 a) -> V1 a -> Bool #

rangeSize :: (V1 a, V1 a) -> Int #

unsafeRangeSize :: (V1 a, V1 a) -> Int #

Num a => Num (V1 a) 
Instance details

Defined in Linear.V1

Methods

(+) :: V1 a -> V1 a -> V1 a #

(-) :: V1 a -> V1 a -> V1 a #

(*) :: V1 a -> V1 a -> V1 a #

negate :: V1 a -> V1 a #

abs :: V1 a -> V1 a #

signum :: V1 a -> V1 a #

fromInteger :: Integer -> V1 a #

Read a => Read (V1 a) 
Instance details

Defined in Linear.V1

Fractional a => Fractional (V1 a) 
Instance details

Defined in Linear.V1

Methods

(/) :: V1 a -> V1 a -> V1 a #

recip :: V1 a -> V1 a #

fromRational :: Rational -> V1 a #

Show a => Show (V1 a) 
Instance details

Defined in Linear.V1

Methods

showsPrec :: Int -> V1 a -> ShowS #

show :: V1 a -> String #

showList :: [V1 a] -> ShowS #

Binary a => Binary (V1 a) 
Instance details

Defined in Linear.V1

Methods

put :: V1 a -> Put #

get :: Get (V1 a) #

putList :: [V1 a] -> Put #

Serial a => Serial (V1 a) 
Instance details

Defined in Linear.V1

Methods

serialize :: MonadPut m => V1 a -> m () #

deserialize :: MonadGet m => m (V1 a) #

Serialize a => Serialize (V1 a) 
Instance details

Defined in Linear.V1

Methods

put :: Putter (V1 a) #

get :: Get (V1 a) #

NFData a => NFData (V1 a) 
Instance details

Defined in Linear.V1

Methods

rnf :: V1 a -> () #

Eq a => Eq (V1 a) 
Instance details

Defined in Linear.V1

Methods

(==) :: V1 a -> V1 a -> Bool #

(/=) :: V1 a -> V1 a -> Bool #

Ord a => Ord (V1 a) 
Instance details

Defined in Linear.V1

Methods

compare :: V1 a -> V1 a -> Ordering #

(<) :: V1 a -> V1 a -> Bool #

(<=) :: V1 a -> V1 a -> Bool #

(>) :: V1 a -> V1 a -> Bool #

(>=) :: V1 a -> V1 a -> Bool #

max :: V1 a -> V1 a -> V1 a #

min :: V1 a -> V1 a -> V1 a #

Hashable a => Hashable (V1 a) 
Instance details

Defined in Linear.V1

Methods

hashWithSalt :: Int -> V1 a -> Int #

hash :: V1 a -> Int #

Epsilon a => Epsilon (V1 a) 
Instance details

Defined in Linear.V1

Methods

nearZero :: V1 a -> Bool #

Ixed (V1 a) 
Instance details

Defined in Linear.V1

Methods

ix :: Index (V1 a) -> Traversal' (V1 a) (IxValue (V1 a)) #

Random a => Random (V1 a) 
Instance details

Defined in Linear.V1

Methods

randomR :: RandomGen g => (V1 a, V1 a) -> g -> (V1 a, g) #

random :: RandomGen g => g -> (V1 a, g) #

randomRs :: RandomGen g => (V1 a, V1 a) -> g -> [V1 a] #

randoms :: RandomGen g => g -> [V1 a] #

Unbox a => Unbox (V1 a) 
Instance details

Defined in Linear.V1

FoldableWithIndex (E V1) V1 
Instance details

Defined in Linear.V1

Methods

ifoldMap :: Monoid m => (E V1 -> a -> m) -> V1 a -> m #

ifoldMap' :: Monoid m => (E V1 -> a -> m) -> V1 a -> m #

ifoldr :: (E V1 -> a -> b -> b) -> b -> V1 a -> b #

ifoldl :: (E V1 -> b -> a -> b) -> b -> V1 a -> b #

ifoldr' :: (E V1 -> a -> b -> b) -> b -> V1 a -> b #

ifoldl' :: (E V1 -> b -> a -> b) -> b -> V1 a -> b #

FunctorWithIndex (E V1) V1 
Instance details

Defined in Linear.V1

Methods

imap :: (E V1 -> a -> b) -> V1 a -> V1 b #

TraversableWithIndex (E V1) V1 
Instance details

Defined in Linear.V1

Methods

itraverse :: Applicative f => (E V1 -> a -> f b) -> V1 a -> f (V1 b) #

Each (V1 a) (V1 b) a b 
Instance details

Defined in Linear.V1

Methods

each :: Traversal (V1 a) (V1 b) a b #

Field1 (V1 a) (V1 b) a b 
Instance details

Defined in Linear.V1

Methods

_1 :: Lens (V1 a) (V1 b) a b #

type Rep V1 
Instance details

Defined in Linear.V1

type Rep V1 = E V1
type Diff V1 
Instance details

Defined in Linear.Affine

type Diff V1 = V1
type Size V1 
Instance details

Defined in Linear.V1

type Size V1 = 1
type Rep1 V1 
Instance details

Defined in Linear.V1

type Rep1 V1 = D1 ('MetaData "V1" "Linear.V1" "lnr-1.22-7520e77e" 'True) (C1 ('MetaCons "V1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
newtype MVector s (V1 a) 
Instance details

Defined in Linear.V1

newtype MVector s (V1 a) = MV_V1 (MVector s a)
type Rep (V1 a) 
Instance details

Defined in Linear.V1

type Rep (V1 a) = D1 ('MetaData "V1" "Linear.V1" "lnr-1.22-7520e77e" 'True) (C1 ('MetaCons "V1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type Index (V1 a) 
Instance details

Defined in Linear.V1

type Index (V1 a) = E V1
type IxValue (V1 a) 
Instance details

Defined in Linear.V1

type IxValue (V1 a) = a
newtype Vector (V1 a) 
Instance details

Defined in Linear.V1

newtype Vector (V1 a) = V_V1 (Vector a)

class R1 (t :: Type -> Type) where #

A space that has at least 1 basis vector _x.

Methods

_x :: Lens' (t a) a #

>>> V1 2 ^._x
2
>>> V1 2 & _x .~ 3
V1 3

Instances

Instances details
R1 Identity 
Instance details

Defined in Linear.V1

Methods

_x :: Lens' (Identity a) a #

R1 Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

_x :: Lens' (Quaternion a) a #

R1 V1 
Instance details

Defined in Linear.V1

Methods

_x :: Lens' (V1 a) a #

R1 V2 
Instance details

Defined in Linear.V2

Methods

_x :: Lens' (V2 a) a #

R1 V3 
Instance details

Defined in Linear.V3

Methods

_x :: Lens' (V3 a) a #

R1 V4 
Instance details

Defined in Linear.V4

Methods

_x :: Lens' (V4 a) a #

R1 f => R1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

_x :: Lens' (Point f a) a #

newtype E (t :: Type -> Type) #

Basis element

Constructors

E 

Fields

Instances

Instances details
Num r => Algebra r (E Complex) 
Instance details

Defined in Linear.Algebra

Methods

mult :: (E Complex -> E Complex -> r) -> E Complex -> r #

unital :: r -> E Complex -> r #

(Num r, TrivialConjugate r) => Algebra r (E Quaternion) 
Instance details

Defined in Linear.Algebra

Methods

mult :: (E Quaternion -> E Quaternion -> r) -> E Quaternion -> r #

unital :: r -> E Quaternion -> r #

Num r => Algebra r (E V0) 
Instance details

Defined in Linear.Algebra

Methods

mult :: (E V0 -> E V0 -> r) -> E V0 -> r #

unital :: r -> E V0 -> r #

Num r => Algebra r (E V1) 
Instance details

Defined in Linear.Algebra

Methods

mult :: (E V1 -> E V1 -> r) -> E V1 -> r #

unital :: r -> E V1 -> r #

Num r => Coalgebra r (E Complex) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E Complex -> r) -> E Complex -> E Complex -> r #

counital :: (E Complex -> r) -> r #

(Num r, TrivialConjugate r) => Coalgebra r (E Quaternion) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E Quaternion -> r) -> E Quaternion -> E Quaternion -> r #

counital :: (E Quaternion -> r) -> r #

Num r => Coalgebra r (E V0) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V0 -> r) -> E V0 -> E V0 -> r #

counital :: (E V0 -> r) -> r #

Num r => Coalgebra r (E V1) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V1 -> r) -> E V1 -> E V1 -> r #

counital :: (E V1 -> r) -> r #

Num r => Coalgebra r (E V2) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V2 -> r) -> E V2 -> E V2 -> r #

counital :: (E V2 -> r) -> r #

Num r => Coalgebra r (E V3) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V3 -> r) -> E V3 -> E V3 -> r #

counital :: (E V3 -> r) -> r #

Num r => Coalgebra r (E V4) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V4 -> r) -> E V4 -> E V4 -> r #

counital :: (E V4 -> r) -> r #

FoldableWithIndex (E Plucker) Plucker 
Instance details

Defined in Linear.Plucker

Methods

ifoldMap :: Monoid m => (E Plucker -> a -> m) -> Plucker a -> m #

ifoldMap' :: Monoid m => (E Plucker -> a -> m) -> Plucker a -> m #

ifoldr :: (E Plucker -> a -> b -> b) -> b -> Plucker a -> b #

ifoldl :: (E Plucker -> b -> a -> b) -> b -> Plucker a -> b #

ifoldr' :: (E Plucker -> a -> b -> b) -> b -> Plucker a -> b #

ifoldl' :: (E Plucker -> b -> a -> b) -> b -> Plucker a -> b #

FoldableWithIndex (E Quaternion) Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

ifoldMap :: Monoid m => (E Quaternion -> a -> m) -> Quaternion a -> m #

ifoldMap' :: Monoid m => (E Quaternion -> a -> m) -> Quaternion a -> m #

ifoldr :: (E Quaternion -> a -> b -> b) -> b -> Quaternion a -> b #

ifoldl :: (E Quaternion -> b -> a -> b) -> b -> Quaternion a -> b #

ifoldr' :: (E Quaternion -> a -> b -> b) -> b -> Quaternion a -> b #

ifoldl' :: (E Quaternion -> b -> a -> b) -> b -> Quaternion a -> b #

FoldableWithIndex (E V0) V0 
Instance details

Defined in Linear.V0

Methods

ifoldMap :: Monoid m => (E V0 -> a -> m) -> V0 a -> m #

ifoldMap' :: Monoid m => (E V0 -> a -> m) -> V0 a -> m #

ifoldr :: (E V0 -> a -> b -> b) -> b -> V0 a -> b #

ifoldl :: (E V0 -> b -> a -> b) -> b -> V0 a -> b #

ifoldr' :: (E V0 -> a -> b -> b) -> b -> V0 a -> b #

ifoldl' :: (E V0 -> b -> a -> b) -> b -> V0 a -> b #

FoldableWithIndex (E V1) V1 
Instance details

Defined in Linear.V1

Methods

ifoldMap :: Monoid m => (E V1 -> a -> m) -> V1 a -> m #

ifoldMap' :: Monoid m => (E V1 -> a -> m) -> V1 a -> m #

ifoldr :: (E V1 -> a -> b -> b) -> b -> V1 a -> b #

ifoldl :: (E V1 -> b -> a -> b) -> b -> V1 a -> b #

ifoldr' :: (E V1 -> a -> b -> b) -> b -> V1 a -> b #

ifoldl' :: (E V1 -> b -> a -> b) -> b -> V1 a -> b #

FoldableWithIndex (E V2) V2 
Instance details

Defined in Linear.V2

Methods

ifoldMap :: Monoid m => (E V2 -> a -> m) -> V2 a -> m #

ifoldMap' :: Monoid m => (E V2 -> a -> m) -> V2 a -> m #

ifoldr :: (E V2 -> a -> b -> b) -> b -> V2 a -> b #

ifoldl :: (E V2 -> b -> a -> b) -> b -> V2 a -> b #

ifoldr' :: (E V2 -> a -> b -> b) -> b -> V2 a -> b #

ifoldl' :: (E V2 -> b -> a -> b) -> b -> V2 a -> b #

FoldableWithIndex (E V3) V3 
Instance details

Defined in Linear.V3

Methods

ifoldMap :: Monoid m => (E V3 -> a -> m) -> V3 a -> m #

ifoldMap' :: Monoid m => (E V3 -> a -> m) -> V3 a -> m #

ifoldr :: (E V3 -> a -> b -> b) -> b -> V3 a -> b #

ifoldl :: (E V3 -> b -> a -> b) -> b -> V3 a -> b #

ifoldr' :: (E V3 -> a -> b -> b) -> b -> V3 a -> b #

ifoldl' :: (E V3 -> b -> a -> b) -> b -> V3 a -> b #

FoldableWithIndex (E V4) V4 
Instance details

Defined in Linear.V4

Methods

ifoldMap :: Monoid m => (E V4 -> a -> m) -> V4 a -> m #

ifoldMap' :: Monoid m => (E V4 -> a -> m) -> V4 a -> m #

ifoldr :: (E V4 -> a -> b -> b) -> b -> V4 a -> b #

ifoldl :: (E V4 -> b -> a -> b) -> b -> V4 a -> b #

ifoldr' :: (E V4 -> a -> b -> b) -> b -> V4 a -> b #

ifoldl' :: (E V4 -> b -> a -> b) -> b -> V4 a -> b #

FunctorWithIndex (E Plucker) Plucker 
Instance details

Defined in Linear.Plucker

Methods

imap :: (E Plucker -> a -> b) -> Plucker a -> Plucker b #

FunctorWithIndex (E Quaternion) Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

imap :: (E Quaternion -> a -> b) -> Quaternion a -> Quaternion b #

FunctorWithIndex (E V0) V0 
Instance details

Defined in Linear.V0

Methods

imap :: (E V0 -> a -> b) -> V0 a -> V0 b #

FunctorWithIndex (E V1) V1 
Instance details

Defined in Linear.V1

Methods

imap :: (E V1 -> a -> b) -> V1 a -> V1 b #

FunctorWithIndex (E V2) V2 
Instance details

Defined in Linear.V2

Methods

imap :: (E V2 -> a -> b) -> V2 a -> V2 b #

FunctorWithIndex (E V3) V3 
Instance details

Defined in Linear.V3

Methods

imap :: (E V3 -> a -> b) -> V3 a -> V3 b #

FunctorWithIndex (E V4) V4 
Instance details

Defined in Linear.V4

Methods

imap :: (E V4 -> a -> b) -> V4 a -> V4 b #

TraversableWithIndex (E Plucker) Plucker 
Instance details

Defined in Linear.Plucker

Methods

itraverse :: Applicative f => (E Plucker -> a -> f b) -> Plucker a -> f (Plucker b) #

TraversableWithIndex (E Quaternion) Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

itraverse :: Applicative f => (E Quaternion -> a -> f b) -> Quaternion a -> f (Quaternion b) #

TraversableWithIndex (E V0) V0 
Instance details

Defined in Linear.V0

Methods

itraverse :: Applicative f => (E V0 -> a -> f b) -> V0 a -> f (V0 b) #

TraversableWithIndex (E V1) V1 
Instance details

Defined in Linear.V1

Methods

itraverse :: Applicative f => (E V1 -> a -> f b) -> V1 a -> f (V1 b) #

TraversableWithIndex (E V2) V2 
Instance details

Defined in Linear.V2

Methods

itraverse :: Applicative f => (E V2 -> a -> f b) -> V2 a -> f (V2 b) #

TraversableWithIndex (E V3) V3 
Instance details

Defined in Linear.V3

Methods

itraverse :: Applicative f => (E V3 -> a -> f b) -> V3 a -> f (V3 b) #

TraversableWithIndex (E V4) V4 
Instance details

Defined in Linear.V4

Methods

itraverse :: Applicative f => (E V4 -> a -> f b) -> V4 a -> f (V4 b) #

class R1 t => R2 (t :: Type -> Type) where #

A space that distinguishes 2 orthogonal basis vectors _x and _y, but may have more.

Minimal complete definition

_xy

Methods

_y :: Lens' (t a) a #

>>> V2 1 2 ^._y
2
>>> V2 1 2 & _y .~ 3
V2 1 3

_xy :: Lens' (t a) (V2 a) #

Instances

Instances details
R2 Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

_y :: Lens' (Quaternion a) a #

_xy :: Lens' (Quaternion a) (V2 a) #

R2 V2 
Instance details

Defined in Linear.V2

Methods

_y :: Lens' (V2 a) a #

_xy :: Lens' (V2 a) (V2 a) #

R2 V3 
Instance details

Defined in Linear.V3

Methods

_y :: Lens' (V3 a) a #

_xy :: Lens' (V3 a) (V2 a) #

R2 V4 
Instance details

Defined in Linear.V4

Methods

_y :: Lens' (V4 a) a #

_xy :: Lens' (V4 a) (V2 a) #

R2 f => R2 (Point f) 
Instance details

Defined in Linear.Affine

Methods

_y :: Lens' (Point f a) a #

_xy :: Lens' (Point f a) (V2 a) #

data Vertex #

Instances

Instances details
Storable Vertex 
Instance details

Defined in SDL.Raw.Types

Show Vertex 
Instance details

Defined in SDL.Raw.Types

Eq Vertex 
Instance details

Defined in SDL.Raw.Types

Methods

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

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

data Mode #

The mode a driver should use when creating an OpenGL context.

Constructors

Normal

A normal profile with no special debugging support

Debug

Use a debug context, allowing the usage of extensions such as GL_ARB_debug_output

Instances

Instances details
Data Mode 
Instance details

Defined in SDL.Video.OpenGL

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Mode -> c Mode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Mode #

toConstr :: Mode -> Constr #

dataTypeOf :: Mode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Mode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Mode) #

gmapT :: (forall b. Data b => b -> b) -> Mode -> Mode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Mode -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Mode -> r #

gmapQ :: (forall d. Data d => d -> u) -> Mode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Mode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Mode -> m Mode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Mode -> m Mode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Mode -> m Mode #

Bounded Mode 
Instance details

Defined in SDL.Video.OpenGL

Enum Mode 
Instance details

Defined in SDL.Video.OpenGL

Methods

succ :: Mode -> Mode #

pred :: Mode -> Mode #

toEnum :: Int -> Mode #

fromEnum :: Mode -> Int #

enumFrom :: Mode -> [Mode] #

enumFromThen :: Mode -> Mode -> [Mode] #

enumFromTo :: Mode -> Mode -> [Mode] #

enumFromThenTo :: Mode -> Mode -> Mode -> [Mode] #

Generic Mode 
Instance details

Defined in SDL.Video.OpenGL

Associated Types

type Rep Mode :: Type -> Type #

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

Read Mode 
Instance details

Defined in SDL.Video.OpenGL

Show Mode 
Instance details

Defined in SDL.Video.OpenGL

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

Eq Mode 
Instance details

Defined in SDL.Video.OpenGL

Methods

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

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

Ord Mode 
Instance details

Defined in SDL.Video.OpenGL

Methods

compare :: Mode -> Mode -> Ordering #

(<) :: Mode -> Mode -> Bool #

(<=) :: Mode -> Mode -> Bool #

(>) :: Mode -> Mode -> Bool #

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

max :: Mode -> Mode -> Mode #

min :: Mode -> Mode -> Mode #

type Rep Mode 
Instance details

Defined in SDL.Video.OpenGL

type Rep Mode = D1 ('MetaData "Mode" "SDL.Video.OpenGL" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "Normal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Debug" 'PrefixI 'False) (U1 :: Type -> Type))

class Conjugate a => TrivialConjugate a #

Requires and provides a default definition such that

conjugate = id

Instances

Instances details
TrivialConjugate CDouble 
Instance details

Defined in Linear.Conjugate

TrivialConjugate CFloat 
Instance details

Defined in Linear.Conjugate

TrivialConjugate Int16 
Instance details

Defined in Linear.Conjugate

TrivialConjugate Int32 
Instance details

Defined in Linear.Conjugate

TrivialConjugate Int64 
Instance details

Defined in Linear.Conjugate

TrivialConjugate Int8 
Instance details

Defined in Linear.Conjugate

TrivialConjugate Word16 
Instance details

Defined in Linear.Conjugate

TrivialConjugate Word32 
Instance details

Defined in Linear.Conjugate

TrivialConjugate Word64 
Instance details

Defined in Linear.Conjugate

TrivialConjugate Word8 
Instance details

Defined in Linear.Conjugate

TrivialConjugate Integer 
Instance details

Defined in Linear.Conjugate

TrivialConjugate Double 
Instance details

Defined in Linear.Conjugate

TrivialConjugate Float 
Instance details

Defined in Linear.Conjugate

TrivialConjugate Int 
Instance details

Defined in Linear.Conjugate

TrivialConjugate Word 
Instance details

Defined in Linear.Conjugate

class Num a => Conjugate a where #

An involutive ring

Minimal complete definition

Nothing

Methods

conjugate :: a -> a #

Conjugate a value. This defaults to the trivial involution.

>>> conjugate (1 :+ 2)
1.0 :+ (-2.0)
>>> conjugate 1
1

Instances

Instances details
Conjugate CDouble 
Instance details

Defined in Linear.Conjugate

Methods

conjugate :: CDouble -> CDouble #

Conjugate CFloat 
Instance details

Defined in Linear.Conjugate

Methods

conjugate :: CFloat -> CFloat #

Conjugate Int16 
Instance details

Defined in Linear.Conjugate

Methods

conjugate :: Int16 -> Int16 #

Conjugate Int32 
Instance details

Defined in Linear.Conjugate

Methods

conjugate :: Int32 -> Int32 #

Conjugate Int64 
Instance details

Defined in Linear.Conjugate

Methods

conjugate :: Int64 -> Int64 #

Conjugate Int8 
Instance details

Defined in Linear.Conjugate

Methods

conjugate :: Int8 -> Int8 #

Conjugate Word16 
Instance details

Defined in Linear.Conjugate

Methods

conjugate :: Word16 -> Word16 #

Conjugate Word32 
Instance details

Defined in Linear.Conjugate

Methods

conjugate :: Word32 -> Word32 #

Conjugate Word64 
Instance details

Defined in Linear.Conjugate

Methods

conjugate :: Word64 -> Word64 #

Conjugate Word8 
Instance details

Defined in Linear.Conjugate

Methods

conjugate :: Word8 -> Word8 #

Conjugate Integer 
Instance details

Defined in Linear.Conjugate

Methods

conjugate :: Integer -> Integer #

Conjugate Double 
Instance details

Defined in Linear.Conjugate

Methods

conjugate :: Double -> Double #

Conjugate Float 
Instance details

Defined in Linear.Conjugate

Methods

conjugate :: Float -> Float #

Conjugate Int 
Instance details

Defined in Linear.Conjugate

Methods

conjugate :: Int -> Int #

Conjugate Word 
Instance details

Defined in Linear.Conjugate

Methods

conjugate :: Word -> Word #

(Conjugate a, RealFloat a) => Conjugate (Complex a) 
Instance details

Defined in Linear.Conjugate

Methods

conjugate :: Complex a -> Complex a #

(Conjugate a, RealFloat a) => Conjugate (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Methods

conjugate :: Quaternion a -> Quaternion a #

class Num a => Epsilon a where #

Provides a fairly subjective test to see if a quantity is near zero.

>>> nearZero (1e-11 :: Double)
False
>>> nearZero (1e-17 :: Double)
True
>>> nearZero (1e-5 :: Float)
False
>>> nearZero (1e-7 :: Float)
True

Methods

nearZero :: a -> Bool #

Determine if a quantity is near zero.

Instances

Instances details
Epsilon CDouble
abs a <= 1e-12
Instance details

Defined in Linear.Epsilon

Methods

nearZero :: CDouble -> Bool #

Epsilon CFloat
abs a <= 1e-6
Instance details

Defined in Linear.Epsilon

Methods

nearZero :: CFloat -> Bool #

Epsilon Double
abs a <= 1e-12
Instance details

Defined in Linear.Epsilon

Methods

nearZero :: Double -> Bool #

Epsilon Float
abs a <= 1e-6
Instance details

Defined in Linear.Epsilon

Methods

nearZero :: Float -> Bool #

(Epsilon a, RealFloat a) => Epsilon (Complex a) 
Instance details

Defined in Linear.Epsilon

Methods

nearZero :: Complex a -> Bool #

Epsilon a => Epsilon (Plucker a) 
Instance details

Defined in Linear.Plucker

Methods

nearZero :: Plucker a -> Bool #

(RealFloat a, Epsilon a) => Epsilon (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Methods

nearZero :: Quaternion a -> Bool #

Epsilon (V0 a) 
Instance details

Defined in Linear.V0

Methods

nearZero :: V0 a -> Bool #

Epsilon a => Epsilon (V1 a) 
Instance details

Defined in Linear.V1

Methods

nearZero :: V1 a -> Bool #

Epsilon a => Epsilon (V2 a) 
Instance details

Defined in Linear.V2

Methods

nearZero :: V2 a -> Bool #

Epsilon a => Epsilon (V3 a) 
Instance details

Defined in Linear.V3

Methods

nearZero :: V3 a -> Bool #

Epsilon a => Epsilon (V4 a) 
Instance details

Defined in Linear.V4

Methods

nearZero :: V4 a -> Bool #

Epsilon (f a) => Epsilon (Point f a) 
Instance details

Defined in Linear.Affine

Methods

nearZero :: Point f a -> Bool #

(Dim n, Epsilon a) => Epsilon (V n a) 
Instance details

Defined in Linear.V

Methods

nearZero :: V n a -> Bool #

class Functor f => Additive (f :: Type -> Type) where #

A vector is an additive group with additional structure.

Minimal complete definition

Nothing

Methods

zero :: Num a => f a #

The zero vector

(^+^) :: Num a => f a -> f a -> f a infixl 6 #

Compute the sum of two vectors

>>> V2 1 2 ^+^ V2 3 4
V2 4 6

(^-^) :: Num a => f a -> f a -> f a infixl 6 #

Compute the difference between two vectors

>>> V2 4 5 ^-^ V2 3 1
V2 1 4

lerp :: Num a => a -> f a -> f a -> f a #

Linearly interpolate between two vectors.

liftU2 :: (a -> a -> a) -> f a -> f a -> f a #

Apply a function to merge the 'non-zero' components of two vectors, unioning the rest of the values.

  • For a dense vector this is equivalent to liftA2.
  • For a sparse vector this is equivalent to unionWith.

liftI2 :: (a -> b -> c) -> f a -> f b -> f c #

Apply a function to the components of two vectors.

Instances

Instances details
Additive ZipList 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => ZipList a #

(^+^) :: Num a => ZipList a -> ZipList a -> ZipList a #

(^-^) :: Num a => ZipList a -> ZipList a -> ZipList a #

lerp :: Num a => a -> ZipList a -> ZipList a -> ZipList a #

liftU2 :: (a -> a -> a) -> ZipList a -> ZipList a -> ZipList a #

liftI2 :: (a -> b -> c) -> ZipList a -> ZipList b -> ZipList c #

Additive Complex 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => Complex a #

(^+^) :: Num a => Complex a -> Complex a -> Complex a #

(^-^) :: Num a => Complex a -> Complex a -> Complex a #

lerp :: Num a => a -> Complex a -> Complex a -> Complex a #

liftU2 :: (a -> a -> a) -> Complex a -> Complex a -> Complex a #

liftI2 :: (a -> b -> c) -> Complex a -> Complex b -> Complex c #

Additive Identity 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => Identity a #

(^+^) :: Num a => Identity a -> Identity a -> Identity a #

(^-^) :: Num a => Identity a -> Identity a -> Identity a #

lerp :: Num a => a -> Identity a -> Identity a -> Identity a #

liftU2 :: (a -> a -> a) -> Identity a -> Identity a -> Identity a #

liftI2 :: (a -> b -> c) -> Identity a -> Identity b -> Identity c #

Additive IntMap 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => IntMap a #

(^+^) :: Num a => IntMap a -> IntMap a -> IntMap a #

(^-^) :: Num a => IntMap a -> IntMap a -> IntMap a #

lerp :: Num a => a -> IntMap a -> IntMap a -> IntMap a #

liftU2 :: (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a #

liftI2 :: (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c #

Additive Plucker 
Instance details

Defined in Linear.Plucker

Methods

zero :: Num a => Plucker a #

(^+^) :: Num a => Plucker a -> Plucker a -> Plucker a #

(^-^) :: Num a => Plucker a -> Plucker a -> Plucker a #

lerp :: Num a => a -> Plucker a -> Plucker a -> Plucker a #

liftU2 :: (a -> a -> a) -> Plucker a -> Plucker a -> Plucker a #

liftI2 :: (a -> b -> c) -> Plucker a -> Plucker b -> Plucker c #

Additive Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

zero :: Num a => Quaternion a #

(^+^) :: Num a => Quaternion a -> Quaternion a -> Quaternion a #

(^-^) :: Num a => Quaternion a -> Quaternion a -> Quaternion a #

lerp :: Num a => a -> Quaternion a -> Quaternion a -> Quaternion a #

liftU2 :: (a -> a -> a) -> Quaternion a -> Quaternion a -> Quaternion a #

liftI2 :: (a -> b -> c) -> Quaternion a -> Quaternion b -> Quaternion c #

Additive V0 
Instance details

Defined in Linear.V0

Methods

zero :: Num a => V0 a #

(^+^) :: Num a => V0 a -> V0 a -> V0 a #

(^-^) :: Num a => V0 a -> V0 a -> V0 a #

lerp :: Num a => a -> V0 a -> V0 a -> V0 a #

liftU2 :: (a -> a -> a) -> V0 a -> V0 a -> V0 a #

liftI2 :: (a -> b -> c) -> V0 a -> V0 b -> V0 c #

Additive V1 
Instance details

Defined in Linear.V1

Methods

zero :: Num a => V1 a #

(^+^) :: Num a => V1 a -> V1 a -> V1 a #

(^-^) :: Num a => V1 a -> V1 a -> V1 a #

lerp :: Num a => a -> V1 a -> V1 a -> V1 a #

liftU2 :: (a -> a -> a) -> V1 a -> V1 a -> V1 a #

liftI2 :: (a -> b -> c) -> V1 a -> V1 b -> V1 c #

Additive V2 
Instance details

Defined in Linear.V2

Methods

zero :: Num a => V2 a #

(^+^) :: Num a => V2 a -> V2 a -> V2 a #

(^-^) :: Num a => V2 a -> V2 a -> V2 a #

lerp :: Num a => a -> V2 a -> V2 a -> V2 a #

liftU2 :: (a -> a -> a) -> V2 a -> V2 a -> V2 a #

liftI2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c #

Additive V3 
Instance details

Defined in Linear.V3

Methods

zero :: Num a => V3 a #

(^+^) :: Num a => V3 a -> V3 a -> V3 a #

(^-^) :: Num a => V3 a -> V3 a -> V3 a #

lerp :: Num a => a -> V3 a -> V3 a -> V3 a #

liftU2 :: (a -> a -> a) -> V3 a -> V3 a -> V3 a #

liftI2 :: (a -> b -> c) -> V3 a -> V3 b -> V3 c #

Additive V4 
Instance details

Defined in Linear.V4

Methods

zero :: Num a => V4 a #

(^+^) :: Num a => V4 a -> V4 a -> V4 a #

(^-^) :: Num a => V4 a -> V4 a -> V4 a #

lerp :: Num a => a -> V4 a -> V4 a -> V4 a #

liftU2 :: (a -> a -> a) -> V4 a -> V4 a -> V4 a #

liftI2 :: (a -> b -> c) -> V4 a -> V4 b -> V4 c #

Additive Vector 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => Vector a #

(^+^) :: Num a => Vector a -> Vector a -> Vector a #

(^-^) :: Num a => Vector a -> Vector a -> Vector a #

lerp :: Num a => a -> Vector a -> Vector a -> Vector a #

liftU2 :: (a -> a -> a) -> Vector a -> Vector a -> Vector a #

liftI2 :: (a -> b -> c) -> Vector a -> Vector b -> Vector c #

Additive Maybe 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => Maybe a #

(^+^) :: Num a => Maybe a -> Maybe a -> Maybe a #

(^-^) :: Num a => Maybe a -> Maybe a -> Maybe a #

lerp :: Num a => a -> Maybe a -> Maybe a -> Maybe a #

liftU2 :: (a -> a -> a) -> Maybe a -> Maybe a -> Maybe a #

liftI2 :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c #

Additive [] 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => [a] #

(^+^) :: Num a => [a] -> [a] -> [a] #

(^-^) :: Num a => [a] -> [a] -> [a] #

lerp :: Num a => a -> [a] -> [a] -> [a] #

liftU2 :: (a -> a -> a) -> [a] -> [a] -> [a] #

liftI2 :: (a -> b -> c) -> [a] -> [b] -> [c] #

Ord k => Additive (Map k) 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => Map k a #

(^+^) :: Num a => Map k a -> Map k a -> Map k a #

(^-^) :: Num a => Map k a -> Map k a -> Map k a #

lerp :: Num a => a -> Map k a -> Map k a -> Map k a #

liftU2 :: (a -> a -> a) -> Map k a -> Map k a -> Map k a #

liftI2 :: (a -> b -> c) -> Map k a -> Map k b -> Map k c #

Additive f => Additive (Point f) 
Instance details

Defined in Linear.Affine

Methods

zero :: Num a => Point f a #

(^+^) :: Num a => Point f a -> Point f a -> Point f a #

(^-^) :: Num a => Point f a -> Point f a -> Point f a #

lerp :: Num a => a -> Point f a -> Point f a -> Point f a #

liftU2 :: (a -> a -> a) -> Point f a -> Point f a -> Point f a #

liftI2 :: (a -> b -> c) -> Point f a -> Point f b -> Point f c #

(Eq k, Hashable k) => Additive (HashMap k) 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => HashMap k a #

(^+^) :: Num a => HashMap k a -> HashMap k a -> HashMap k a #

(^-^) :: Num a => HashMap k a -> HashMap k a -> HashMap k a #

lerp :: Num a => a -> HashMap k a -> HashMap k a -> HashMap k a #

liftU2 :: (a -> a -> a) -> HashMap k a -> HashMap k a -> HashMap k a #

liftI2 :: (a -> b -> c) -> HashMap k a -> HashMap k b -> HashMap k c #

Dim n => Additive (V n) 
Instance details

Defined in Linear.V

Methods

zero :: Num a => V n a #

(^+^) :: Num a => V n a -> V n a -> V n a #

(^-^) :: Num a => V n a -> V n a -> V n a #

lerp :: Num a => a -> V n a -> V n a -> V n a #

liftU2 :: (a -> a -> a) -> V n a -> V n a -> V n a #

liftI2 :: (a -> b -> c) -> V n a -> V n b -> V n c #

(Additive f, Additive g) => Additive (Product f g) 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => Product f g a #

(^+^) :: Num a => Product f g a -> Product f g a -> Product f g a #

(^-^) :: Num a => Product f g a -> Product f g a -> Product f g a #

lerp :: Num a => a -> Product f g a -> Product f g a -> Product f g a #

liftU2 :: (a -> a -> a) -> Product f g a -> Product f g a -> Product f g a #

liftI2 :: (a -> b -> c) -> Product f g a -> Product f g b -> Product f g c #

Additive ((->) b) 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => b -> a #

(^+^) :: Num a => (b -> a) -> (b -> a) -> b -> a #

(^-^) :: Num a => (b -> a) -> (b -> a) -> b -> a #

lerp :: Num a => a -> (b -> a) -> (b -> a) -> b -> a #

liftU2 :: (a -> a -> a) -> (b -> a) -> (b -> a) -> b -> a #

liftI2 :: (a -> b0 -> c) -> (b -> a) -> (b -> b0) -> b -> c #

(Additive f, Additive g) => Additive (Compose f g) 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => Compose f g a #

(^+^) :: Num a => Compose f g a -> Compose f g a -> Compose f g a #

(^-^) :: Num a => Compose f g a -> Compose f g a -> Compose f g a #

lerp :: Num a => a -> Compose f g a -> Compose f g a -> Compose f g a #

liftU2 :: (a -> a -> a) -> Compose f g a -> Compose f g a -> Compose f g a #

liftI2 :: (a -> b -> c) -> Compose f g a -> Compose f g b -> Compose f g c #

class Additive f => Metric (f :: Type -> Type) where #

Free and sparse inner product/metric spaces.

Minimal complete definition

Nothing

Methods

dot :: Num a => f a -> f a -> a #

Compute the inner product of two vectors or (equivalently) convert a vector f a into a covector f a -> a.

>>> V2 1 2 `dot` V2 3 4
11

quadrance :: Num a => f a -> a #

Compute the squared norm. The name quadrance arises from Norman J. Wildberger's rational trigonometry.

qd :: Num a => f a -> f a -> a #

Compute the quadrance of the difference

distance :: Floating a => f a -> f a -> a #

Compute the distance between two vectors in a metric space

norm :: Floating a => f a -> a #

Compute the norm of a vector in a metric space

signorm :: Floating a => f a -> f a #

Convert a non-zero vector to unit vector.

Instances

Instances details
Metric ZipList 
Instance details

Defined in Linear.Metric

Methods

dot :: Num a => ZipList a -> ZipList a -> a #

quadrance :: Num a => ZipList a -> a #

qd :: Num a => ZipList a -> ZipList a -> a #

distance :: Floating a => ZipList a -> ZipList a -> a #

norm :: Floating a => ZipList a -> a #

signorm :: Floating a => ZipList a -> ZipList a #

Metric Identity 
Instance details

Defined in Linear.Metric

Methods

dot :: Num a => Identity a -> Identity a -> a #

quadrance :: Num a => Identity a -> a #

qd :: Num a => Identity a -> Identity a -> a #

distance :: Floating a => Identity a -> Identity a -> a #

norm :: Floating a => Identity a -> a #

signorm :: Floating a => Identity a -> Identity a #

Metric IntMap 
Instance details

Defined in Linear.Metric

Methods

dot :: Num a => IntMap a -> IntMap a -> a #

quadrance :: Num a => IntMap a -> a #

qd :: Num a => IntMap a -> IntMap a -> a #

distance :: Floating a => IntMap a -> IntMap a -> a #

norm :: Floating a => IntMap a -> a #

signorm :: Floating a => IntMap a -> IntMap a #

Metric Plucker 
Instance details

Defined in Linear.Plucker

Methods

dot :: Num a => Plucker a -> Plucker a -> a #

quadrance :: Num a => Plucker a -> a #

qd :: Num a => Plucker a -> Plucker a -> a #

distance :: Floating a => Plucker a -> Plucker a -> a #

norm :: Floating a => Plucker a -> a #

signorm :: Floating a => Plucker a -> Plucker a #

Metric Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

dot :: Num a => Quaternion a -> Quaternion a -> a #

quadrance :: Num a => Quaternion a -> a #

qd :: Num a => Quaternion a -> Quaternion a -> a #

distance :: Floating a => Quaternion a -> Quaternion a -> a #

norm :: Floating a => Quaternion a -> a #

signorm :: Floating a => Quaternion a -> Quaternion a #

Metric V0 
Instance details

Defined in Linear.V0

Methods

dot :: Num a => V0 a -> V0 a -> a #

quadrance :: Num a => V0 a -> a #

qd :: Num a => V0 a -> V0 a -> a #

distance :: Floating a => V0 a -> V0 a -> a #

norm :: Floating a => V0 a -> a #

signorm :: Floating a => V0 a -> V0 a #

Metric V1 
Instance details

Defined in Linear.V1

Methods

dot :: Num a => V1 a -> V1 a -> a #

quadrance :: Num a => V1 a -> a #

qd :: Num a => V1 a -> V1 a -> a #

distance :: Floating a => V1 a -> V1 a -> a #

norm :: Floating a => V1 a -> a #

signorm :: Floating a => V1 a -> V1 a #

Metric V2 
Instance details

Defined in Linear.V2

Methods

dot :: Num a => V2 a -> V2 a -> a #

quadrance :: Num a => V2 a -> a #

qd :: Num a => V2 a -> V2 a -> a #

distance :: Floating a => V2 a -> V2 a -> a #

norm :: Floating a => V2 a -> a #

signorm :: Floating a => V2 a -> V2 a #

Metric V3 
Instance details

Defined in Linear.V3

Methods

dot :: Num a => V3 a -> V3 a -> a #

quadrance :: Num a => V3 a -> a #

qd :: Num a => V3 a -> V3 a -> a #

distance :: Floating a => V3 a -> V3 a -> a #

norm :: Floating a => V3 a -> a #

signorm :: Floating a => V3 a -> V3 a #

Metric V4 
Instance details

Defined in Linear.V4

Methods

dot :: Num a => V4 a -> V4 a -> a #

quadrance :: Num a => V4 a -> a #

qd :: Num a => V4 a -> V4 a -> a #

distance :: Floating a => V4 a -> V4 a -> a #

norm :: Floating a => V4 a -> a #

signorm :: Floating a => V4 a -> V4 a #

Metric Vector 
Instance details

Defined in Linear.Metric

Methods

dot :: Num a => Vector a -> Vector a -> a #

quadrance :: Num a => Vector a -> a #

qd :: Num a => Vector a -> Vector a -> a #

distance :: Floating a => Vector a -> Vector a -> a #

norm :: Floating a => Vector a -> a #

signorm :: Floating a => Vector a -> Vector a #

Metric Maybe 
Instance details

Defined in Linear.Metric

Methods

dot :: Num a => Maybe a -> Maybe a -> a #

quadrance :: Num a => Maybe a -> a #

qd :: Num a => Maybe a -> Maybe a -> a #

distance :: Floating a => Maybe a -> Maybe a -> a #

norm :: Floating a => Maybe a -> a #

signorm :: Floating a => Maybe a -> Maybe a #

Metric [] 
Instance details

Defined in Linear.Metric

Methods

dot :: Num a => [a] -> [a] -> a #

quadrance :: Num a => [a] -> a #

qd :: Num a => [a] -> [a] -> a #

distance :: Floating a => [a] -> [a] -> a #

norm :: Floating a => [a] -> a #

signorm :: Floating a => [a] -> [a] #

Ord k => Metric (Map k) 
Instance details

Defined in Linear.Metric

Methods

dot :: Num a => Map k a -> Map k a -> a #

quadrance :: Num a => Map k a -> a #

qd :: Num a => Map k a -> Map k a -> a #

distance :: Floating a => Map k a -> Map k a -> a #

norm :: Floating a => Map k a -> a #

signorm :: Floating a => Map k a -> Map k a #

Metric f => Metric (Point f) 
Instance details

Defined in Linear.Affine

Methods

dot :: Num a => Point f a -> Point f a -> a #

quadrance :: Num a => Point f a -> a #

qd :: Num a => Point f a -> Point f a -> a #

distance :: Floating a => Point f a -> Point f a -> a #

norm :: Floating a => Point f a -> a #

signorm :: Floating a => Point f a -> Point f a #

(Hashable k, Eq k) => Metric (HashMap k) 
Instance details

Defined in Linear.Metric

Methods

dot :: Num a => HashMap k a -> HashMap k a -> a #

quadrance :: Num a => HashMap k a -> a #

qd :: Num a => HashMap k a -> HashMap k a -> a #

distance :: Floating a => HashMap k a -> HashMap k a -> a #

norm :: Floating a => HashMap k a -> a #

signorm :: Floating a => HashMap k a -> HashMap k a #

Dim n => Metric (V n) 
Instance details

Defined in Linear.V

Methods

dot :: Num a => V n a -> V n a -> a #

quadrance :: Num a => V n a -> a #

qd :: Num a => V n a -> V n a -> a #

distance :: Floating a => V n a -> V n a -> a #

norm :: Floating a => V n a -> a #

signorm :: Floating a => V n a -> V n a #

(Metric f, Metric g) => Metric (Product f g) 
Instance details

Defined in Linear.Metric

Methods

dot :: Num a => Product f g a -> Product f g a -> a #

quadrance :: Num a => Product f g a -> a #

qd :: Num a => Product f g a -> Product f g a -> a #

distance :: Floating a => Product f g a -> Product f g a -> a #

norm :: Floating a => Product f g a -> a #

signorm :: Floating a => Product f g a -> Product f g a #

(Metric f, Metric g) => Metric (Compose f g) 
Instance details

Defined in Linear.Metric

Methods

dot :: Num a => Compose f g a -> Compose f g a -> a #

quadrance :: Num a => Compose f g a -> a #

qd :: Num a => Compose f g a -> Compose f g a -> a #

distance :: Floating a => Compose f g a -> Compose f g a -> a #

norm :: Floating a => Compose f g a -> a #

signorm :: Floating a => Compose f g a -> Compose f g a #

data V2 a #

A 2-dimensional vector

>>> pure 1 :: V2 Int
V2 1 1
>>> V2 1 2 + V2 3 4
V2 4 6
>>> V2 1 2 * V2 3 4
V2 3 8
>>> sum (V2 1 2)
3

Constructors

V2 !a !a 

Instances

Instances details
MonadFix V2 
Instance details

Defined in Linear.V2

Methods

mfix :: (a -> V2 a) -> V2 a #

MonadZip V2 
Instance details

Defined in Linear.V2

Methods

mzip :: V2 a -> V2 b -> V2 (a, b) #

mzipWith :: (a -> b -> c) -> V2 a -> V2 b -> V2 c #

munzip :: V2 (a, b) -> (V2 a, V2 b) #

Foldable V2 
Instance details

Defined in Linear.V2

Methods

fold :: Monoid m => V2 m -> m #

foldMap :: Monoid m => (a -> m) -> V2 a -> m #

foldMap' :: Monoid m => (a -> m) -> V2 a -> m #

foldr :: (a -> b -> b) -> b -> V2 a -> b #

foldr' :: (a -> b -> b) -> b -> V2 a -> b #

foldl :: (b -> a -> b) -> b -> V2 a -> b #

foldl' :: (b -> a -> b) -> b -> V2 a -> b #

foldr1 :: (a -> a -> a) -> V2 a -> a #

foldl1 :: (a -> a -> a) -> V2 a -> a #

toList :: V2 a -> [a] #

null :: V2 a -> Bool #

length :: V2 a -> Int #

elem :: Eq a => a -> V2 a -> Bool #

maximum :: Ord a => V2 a -> a #

minimum :: Ord a => V2 a -> a #

sum :: Num a => V2 a -> a #

product :: Num a => V2 a -> a #

Eq1 V2 
Instance details

Defined in Linear.V2

Methods

liftEq :: (a -> b -> Bool) -> V2 a -> V2 b -> Bool #

Ord1 V2 
Instance details

Defined in Linear.V2

Methods

liftCompare :: (a -> b -> Ordering) -> V2 a -> V2 b -> Ordering #

Read1 V2 
Instance details

Defined in Linear.V2

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V2 a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [V2 a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (V2 a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [V2 a] #

Show1 V2 
Instance details

Defined in Linear.V2

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V2 a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [V2 a] -> ShowS #

Traversable V2 
Instance details

Defined in Linear.V2

Methods

traverse :: Applicative f => (a -> f b) -> V2 a -> f (V2 b) #

sequenceA :: Applicative f => V2 (f a) -> f (V2 a) #

mapM :: Monad m => (a -> m b) -> V2 a -> m (V2 b) #

sequence :: Monad m => V2 (m a) -> m (V2 a) #

Applicative V2 
Instance details

Defined in Linear.V2

Methods

pure :: a -> V2 a #

(<*>) :: V2 (a -> b) -> V2 a -> V2 b #

liftA2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c #

(*>) :: V2 a -> V2 b -> V2 b #

(<*) :: V2 a -> V2 b -> V2 a #

Functor V2 
Instance details

Defined in Linear.V2

Methods

fmap :: (a -> b) -> V2 a -> V2 b #

(<$) :: a -> V2 b -> V2 a #

Monad V2 
Instance details

Defined in Linear.V2

Methods

(>>=) :: V2 a -> (a -> V2 b) -> V2 b #

(>>) :: V2 a -> V2 b -> V2 b #

return :: a -> V2 a #

Serial1 V2 
Instance details

Defined in Linear.V2

Methods

serializeWith :: MonadPut m => (a -> m ()) -> V2 a -> m () #

deserializeWith :: MonadGet m => m a -> m (V2 a) #

Representable V2 
Instance details

Defined in Linear.V2

Associated Types

type Rep V2 #

Methods

tabulate :: (Rep V2 -> a) -> V2 a #

index :: V2 a -> Rep V2 -> a #

Distributive V2 
Instance details

Defined in Linear.V2

Methods

distribute :: Functor f => f (V2 a) -> V2 (f a) #

collect :: Functor f => (a -> V2 b) -> f a -> V2 (f b) #

distributeM :: Monad m => m (V2 a) -> V2 (m a) #

collectM :: Monad m => (a -> V2 b) -> m a -> V2 (m b) #

Foldable1 V2 
Instance details

Defined in Linear.V2

Methods

fold1 :: Semigroup m => V2 m -> m #

foldMap1 :: Semigroup m => (a -> m) -> V2 a -> m #

foldMap1' :: Semigroup m => (a -> m) -> V2 a -> m #

toNonEmpty :: V2 a -> NonEmpty a #

maximum :: Ord a => V2 a -> a #

minimum :: Ord a => V2 a -> a #

head :: V2 a -> a #

last :: V2 a -> a #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> V2 a -> b #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> V2 a -> b #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> V2 a -> b #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> V2 a -> b #

Hashable1 V2 
Instance details

Defined in Linear.V2

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> V2 a -> Int #

Affine V2 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V2 :: Type -> Type #

Methods

(.-.) :: Num a => V2 a -> V2 a -> Diff V2 a #

(.+^) :: Num a => V2 a -> Diff V2 a -> V2 a #

(.-^) :: Num a => V2 a -> Diff V2 a -> V2 a #

Metric V2 
Instance details

Defined in Linear.V2

Methods

dot :: Num a => V2 a -> V2 a -> a #

quadrance :: Num a => V2 a -> a #

qd :: Num a => V2 a -> V2 a -> a #

distance :: Floating a => V2 a -> V2 a -> a #

norm :: Floating a => V2 a -> a #

signorm :: Floating a => V2 a -> V2 a #

Trace V2 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => V2 (V2 a) -> a #

diagonal :: V2 (V2 a) -> V2 a #

Finite V2 
Instance details

Defined in Linear.V2

Associated Types

type Size V2 :: Nat #

Methods

toV :: V2 a -> V (Size V2) a #

fromV :: V (Size V2) a -> V2 a #

R1 V2 
Instance details

Defined in Linear.V2

Methods

_x :: Lens' (V2 a) a #

R2 V2 
Instance details

Defined in Linear.V2

Methods

_y :: Lens' (V2 a) a #

_xy :: Lens' (V2 a) (V2 a) #

Additive V2 
Instance details

Defined in Linear.V2

Methods

zero :: Num a => V2 a #

(^+^) :: Num a => V2 a -> V2 a -> V2 a #

(^-^) :: Num a => V2 a -> V2 a -> V2 a #

lerp :: Num a => a -> V2 a -> V2 a -> V2 a #

liftU2 :: (a -> a -> a) -> V2 a -> V2 a -> V2 a #

liftI2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c #

Apply V2 
Instance details

Defined in Linear.V2

Methods

(<.>) :: V2 (a -> b) -> V2 a -> V2 b #

(.>) :: V2 a -> V2 b -> V2 b #

(<.) :: V2 a -> V2 b -> V2 a #

liftF2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c #

Bind V2 
Instance details

Defined in Linear.V2

Methods

(>>-) :: V2 a -> (a -> V2 b) -> V2 b #

join :: V2 (V2 a) -> V2 a #

Traversable1 V2 
Instance details

Defined in Linear.V2

Methods

traverse1 :: Apply f => (a -> f b) -> V2 a -> f (V2 b) #

sequence1 :: Apply f => V2 (f b) -> f (V2 b) #

Generic1 V2 
Instance details

Defined in Linear.V2

Associated Types

type Rep1 V2 :: k -> Type #

Methods

from1 :: forall (a :: k). V2 a -> Rep1 V2 a #

to1 :: forall (a :: k). Rep1 V2 a -> V2 a #

Num r => Coalgebra r (E V2) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V2 -> r) -> E V2 -> E V2 -> r #

counital :: (E V2 -> r) -> r #

Lift a => Lift (V2 a :: Type) 
Instance details

Defined in Linear.V2

Methods

lift :: Quote m => V2 a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => V2 a -> Code m (V2 a) #

Unbox a => Vector Vector (V2 a) 
Instance details

Defined in Linear.V2

Methods

basicUnsafeFreeze :: Mutable Vector s (V2 a) -> ST s (Vector (V2 a)) #

basicUnsafeThaw :: Vector (V2 a) -> ST s (Mutable Vector s (V2 a)) #

basicLength :: Vector (V2 a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V2 a) -> Vector (V2 a) #

basicUnsafeIndexM :: Vector (V2 a) -> Int -> Box (V2 a) #

basicUnsafeCopy :: Mutable Vector s (V2 a) -> Vector (V2 a) -> ST s () #

elemseq :: Vector (V2 a) -> V2 a -> b -> b #

Unbox a => MVector MVector (V2 a) 
Instance details

Defined in Linear.V2

Methods

basicLength :: MVector s (V2 a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V2 a) -> MVector s (V2 a) #

basicOverlaps :: MVector s (V2 a) -> MVector s (V2 a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (V2 a)) #

basicInitialize :: MVector s (V2 a) -> ST s () #

basicUnsafeReplicate :: Int -> V2 a -> ST s (MVector s (V2 a)) #

basicUnsafeRead :: MVector s (V2 a) -> Int -> ST s (V2 a) #

basicUnsafeWrite :: MVector s (V2 a) -> Int -> V2 a -> ST s () #

basicClear :: MVector s (V2 a) -> ST s () #

basicSet :: MVector s (V2 a) -> V2 a -> ST s () #

basicUnsafeCopy :: MVector s (V2 a) -> MVector s (V2 a) -> ST s () #

basicUnsafeMove :: MVector s (V2 a) -> MVector s (V2 a) -> ST s () #

basicUnsafeGrow :: MVector s (V2 a) -> Int -> ST s (MVector s (V2 a)) #

Data a => Data (V2 a) 
Instance details

Defined in Linear.V2

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V2 a -> c (V2 a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V2 a) #

toConstr :: V2 a -> Constr #

dataTypeOf :: V2 a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V2 a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V2 a)) #

gmapT :: (forall b. Data b => b -> b) -> V2 a -> V2 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V2 a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V2 a -> r #

gmapQ :: (forall d. Data d => d -> u) -> V2 a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> V2 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> V2 a -> m (V2 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V2 a -> m (V2 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V2 a -> m (V2 a) #

Storable a => Storable (V2 a) 
Instance details

Defined in Linear.V2

Methods

sizeOf :: V2 a -> Int #

alignment :: V2 a -> Int #

peekElemOff :: Ptr (V2 a) -> Int -> IO (V2 a) #

pokeElemOff :: Ptr (V2 a) -> Int -> V2 a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (V2 a) #

pokeByteOff :: Ptr b -> Int -> V2 a -> IO () #

peek :: Ptr (V2 a) -> IO (V2 a) #

poke :: Ptr (V2 a) -> V2 a -> IO () #

Monoid a => Monoid (V2 a) 
Instance details

Defined in Linear.V2

Methods

mempty :: V2 a #

mappend :: V2 a -> V2 a -> V2 a #

mconcat :: [V2 a] -> V2 a #

Semigroup a => Semigroup (V2 a) 
Instance details

Defined in Linear.V2

Methods

(<>) :: V2 a -> V2 a -> V2 a #

sconcat :: NonEmpty (V2 a) -> V2 a #

stimes :: Integral b => b -> V2 a -> V2 a #

Bounded a => Bounded (V2 a) 
Instance details

Defined in Linear.V2

Methods

minBound :: V2 a #

maxBound :: V2 a #

Floating a => Floating (V2 a) 
Instance details

Defined in Linear.V2

Methods

pi :: V2 a #

exp :: V2 a -> V2 a #

log :: V2 a -> V2 a #

sqrt :: V2 a -> V2 a #

(**) :: V2 a -> V2 a -> V2 a #

logBase :: V2 a -> V2 a -> V2 a #

sin :: V2 a -> V2 a #

cos :: V2 a -> V2 a #

tan :: V2 a -> V2 a #

asin :: V2 a -> V2 a #

acos :: V2 a -> V2 a #

atan :: V2 a -> V2 a #

sinh :: V2 a -> V2 a #

cosh :: V2 a -> V2 a #

tanh :: V2 a -> V2 a #

asinh :: V2 a -> V2 a #

acosh :: V2 a -> V2 a #

atanh :: V2 a -> V2 a #

log1p :: V2 a -> V2 a #

expm1 :: V2 a -> V2 a #

log1pexp :: V2 a -> V2 a #

log1mexp :: V2 a -> V2 a #

Generic (V2 a) 
Instance details

Defined in Linear.V2

Associated Types

type Rep (V2 a) :: Type -> Type #

Methods

from :: V2 a -> Rep (V2 a) x #

to :: Rep (V2 a) x -> V2 a #

Ix a => Ix (V2 a) 
Instance details

Defined in Linear.V2

Methods

range :: (V2 a, V2 a) -> [V2 a] #

index :: (V2 a, V2 a) -> V2 a -> Int #

unsafeIndex :: (V2 a, V2 a) -> V2 a -> Int #

inRange :: (V2 a, V2 a) -> V2 a -> Bool #

rangeSize :: (V2 a, V2 a) -> Int #

unsafeRangeSize :: (V2 a, V2 a) -> Int #

Num a => Num (V2 a) 
Instance details

Defined in Linear.V2

Methods

(+) :: V2 a -> V2 a -> V2 a #

(-) :: V2 a -> V2 a -> V2 a #

(*) :: V2 a -> V2 a -> V2 a #

negate :: V2 a -> V2 a #

abs :: V2 a -> V2 a #

signum :: V2 a -> V2 a #

fromInteger :: Integer -> V2 a #

Read a => Read (V2 a) 
Instance details

Defined in Linear.V2

Fractional a => Fractional (V2 a) 
Instance details

Defined in Linear.V2

Methods

(/) :: V2 a -> V2 a -> V2 a #

recip :: V2 a -> V2 a #

fromRational :: Rational -> V2 a #

Show a => Show (V2 a) 
Instance details

Defined in Linear.V2

Methods

showsPrec :: Int -> V2 a -> ShowS #

show :: V2 a -> String #

showList :: [V2 a] -> ShowS #

Binary a => Binary (V2 a) 
Instance details

Defined in Linear.V2

Methods

put :: V2 a -> Put #

get :: Get (V2 a) #

putList :: [V2 a] -> Put #

Serial a => Serial (V2 a) 
Instance details

Defined in Linear.V2

Methods

serialize :: MonadPut m => V2 a -> m () #

deserialize :: MonadGet m => m (V2 a) #

Serialize a => Serialize (V2 a) 
Instance details

Defined in Linear.V2

Methods

put :: Putter (V2 a) #

get :: Get (V2 a) #

NFData a => NFData (V2 a) 
Instance details

Defined in Linear.V2

Methods

rnf :: V2 a -> () #

Eq a => Eq (V2 a) 
Instance details

Defined in Linear.V2

Methods

(==) :: V2 a -> V2 a -> Bool #

(/=) :: V2 a -> V2 a -> Bool #

Ord a => Ord (V2 a) 
Instance details

Defined in Linear.V2

Methods

compare :: V2 a -> V2 a -> Ordering #

(<) :: V2 a -> V2 a -> Bool #

(<=) :: V2 a -> V2 a -> Bool #

(>) :: V2 a -> V2 a -> Bool #

(>=) :: V2 a -> V2 a -> Bool #

max :: V2 a -> V2 a -> V2 a #

min :: V2 a -> V2 a -> V2 a #

Hashable a => Hashable (V2 a) 
Instance details

Defined in Linear.V2

Methods

hashWithSalt :: Int -> V2 a -> Int #

hash :: V2 a -> Int #

Epsilon a => Epsilon (V2 a) 
Instance details

Defined in Linear.V2

Methods

nearZero :: V2 a -> Bool #

Ixed (V2 a) 
Instance details

Defined in Linear.V2

Methods

ix :: Index (V2 a) -> Traversal' (V2 a) (IxValue (V2 a)) #

Random a => Random (V2 a) 
Instance details

Defined in Linear.V2

Methods

randomR :: RandomGen g => (V2 a, V2 a) -> g -> (V2 a, g) #

random :: RandomGen g => g -> (V2 a, g) #

randomRs :: RandomGen g => (V2 a, V2 a) -> g -> [V2 a] #

randoms :: RandomGen g => g -> [V2 a] #

Unbox a => Unbox (V2 a) 
Instance details

Defined in Linear.V2

FoldableWithIndex (E V2) V2 
Instance details

Defined in Linear.V2

Methods

ifoldMap :: Monoid m => (E V2 -> a -> m) -> V2 a -> m #

ifoldMap' :: Monoid m => (E V2 -> a -> m) -> V2 a -> m #

ifoldr :: (E V2 -> a -> b -> b) -> b -> V2 a -> b #

ifoldl :: (E V2 -> b -> a -> b) -> b -> V2 a -> b #

ifoldr' :: (E V2 -> a -> b -> b) -> b -> V2 a -> b #

ifoldl' :: (E V2 -> b -> a -> b) -> b -> V2 a -> b #

FunctorWithIndex (E V2) V2 
Instance details

Defined in Linear.V2

Methods

imap :: (E V2 -> a -> b) -> V2 a -> V2 b #

TraversableWithIndex (E V2) V2 
Instance details

Defined in Linear.V2

Methods

itraverse :: Applicative f => (E V2 -> a -> f b) -> V2 a -> f (V2 b) #

Each (V2 a) (V2 b) a b 
Instance details

Defined in Linear.V2

Methods

each :: Traversal (V2 a) (V2 b) a b #

Field1 (V2 a) (V2 a) a a 
Instance details

Defined in Linear.V2

Methods

_1 :: Lens (V2 a) (V2 a) a a #

Field2 (V2 a) (V2 a) a a 
Instance details

Defined in Linear.V2

Methods

_2 :: Lens (V2 a) (V2 a) a a #

type Rep V2 
Instance details

Defined in Linear.V2

type Rep V2 = E V2
type Diff V2 
Instance details

Defined in Linear.Affine

type Diff V2 = V2
type Size V2 
Instance details

Defined in Linear.V2

type Size V2 = 2
type Rep1 V2 
Instance details

Defined in Linear.V2

data MVector s (V2 a) 
Instance details

Defined in Linear.V2

data MVector s (V2 a) = MV_V2 !Int !(MVector s a)
type Rep (V2 a) 
Instance details

Defined in Linear.V2

type Index (V2 a) 
Instance details

Defined in Linear.V2

type Index (V2 a) = E V2
type IxValue (V2 a) 
Instance details

Defined in Linear.V2

type IxValue (V2 a) = a
data Vector (V2 a) 
Instance details

Defined in Linear.V2

data Vector (V2 a) = V_V2 !Int !(Vector a)

class R2 t => R3 (t :: Type -> Type) where #

A space that distinguishes 3 orthogonal basis vectors: _x, _y, and _z. (It may have more)

Methods

_z :: Lens' (t a) a #

>>> V3 1 2 3 ^. _z
3

_xyz :: Lens' (t a) (V3 a) #

Instances

Instances details
R3 Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

_z :: Lens' (Quaternion a) a #

_xyz :: Lens' (Quaternion a) (V3 a) #

R3 V3 
Instance details

Defined in Linear.V3

Methods

_z :: Lens' (V3 a) a #

_xyz :: Lens' (V3 a) (V3 a) #

R3 V4 
Instance details

Defined in Linear.V4

Methods

_z :: Lens' (V4 a) a #

_xyz :: Lens' (V4 a) (V3 a) #

R3 f => R3 (Point f) 
Instance details

Defined in Linear.Affine

Methods

_z :: Lens' (Point f a) a #

_xyz :: Lens' (Point f a) (V3 a) #

data V3 a #

A 3-dimensional vector

Constructors

V3 !a !a !a 

Instances

Instances details
MonadFix V3 
Instance details

Defined in Linear.V3

Methods

mfix :: (a -> V3 a) -> V3 a #

MonadZip V3 
Instance details

Defined in Linear.V3

Methods

mzip :: V3 a -> V3 b -> V3 (a, b) #

mzipWith :: (a -> b -> c) -> V3 a -> V3 b -> V3 c #

munzip :: V3 (a, b) -> (V3 a, V3 b) #

Foldable V3 
Instance details

Defined in Linear.V3

Methods

fold :: Monoid m => V3 m -> m #

foldMap :: Monoid m => (a -> m) -> V3 a -> m #

foldMap' :: Monoid m => (a -> m) -> V3 a -> m #

foldr :: (a -> b -> b) -> b -> V3 a -> b #

foldr' :: (a -> b -> b) -> b -> V3 a -> b #

foldl :: (b -> a -> b) -> b -> V3 a -> b #

foldl' :: (b -> a -> b) -> b -> V3 a -> b #

foldr1 :: (a -> a -> a) -> V3 a -> a #

foldl1 :: (a -> a -> a) -> V3 a -> a #

toList :: V3 a -> [a] #

null :: V3 a -> Bool #

length :: V3 a -> Int #

elem :: Eq a => a -> V3 a -> Bool #

maximum :: Ord a => V3 a -> a #

minimum :: Ord a => V3 a -> a #

sum :: Num a => V3 a -> a #

product :: Num a => V3 a -> a #

Eq1 V3 
Instance details

Defined in Linear.V3

Methods

liftEq :: (a -> b -> Bool) -> V3 a -> V3 b -> Bool #

Ord1 V3 
Instance details

Defined in Linear.V3

Methods

liftCompare :: (a -> b -> Ordering) -> V3 a -> V3 b -> Ordering #

Read1 V3 
Instance details

Defined in Linear.V3

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V3 a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [V3 a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (V3 a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [V3 a] #

Show1 V3 
Instance details

Defined in Linear.V3

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V3 a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [V3 a] -> ShowS #

Traversable V3 
Instance details

Defined in Linear.V3

Methods

traverse :: Applicative f => (a -> f b) -> V3 a -> f (V3 b) #

sequenceA :: Applicative f => V3 (f a) -> f (V3 a) #

mapM :: Monad m => (a -> m b) -> V3 a -> m (V3 b) #

sequence :: Monad m => V3 (m a) -> m (V3 a) #

Applicative V3 
Instance details

Defined in Linear.V3

Methods

pure :: a -> V3 a #

(<*>) :: V3 (a -> b) -> V3 a -> V3 b #

liftA2 :: (a -> b -> c) -> V3 a -> V3 b -> V3 c #

(*>) :: V3 a -> V3 b -> V3 b #

(<*) :: V3 a -> V3 b -> V3 a #

Functor V3 
Instance details

Defined in Linear.V3

Methods

fmap :: (a -> b) -> V3 a -> V3 b #

(<$) :: a -> V3 b -> V3 a #

Monad V3 
Instance details

Defined in Linear.V3

Methods

(>>=) :: V3 a -> (a -> V3 b) -> V3 b #

(>>) :: V3 a -> V3 b -> V3 b #

return :: a -> V3 a #

Serial1 V3 
Instance details

Defined in Linear.V3

Methods

serializeWith :: MonadPut m => (a -> m ()) -> V3 a -> m () #

deserializeWith :: MonadGet m => m a -> m (V3 a) #

Representable V3 
Instance details

Defined in Linear.V3

Associated Types

type Rep V3 #

Methods

tabulate :: (Rep V3 -> a) -> V3 a #

index :: V3 a -> Rep V3 -> a #

Distributive V3 
Instance details

Defined in Linear.V3

Methods

distribute :: Functor f => f (V3 a) -> V3 (f a) #

collect :: Functor f => (a -> V3 b) -> f a -> V3 (f b) #

distributeM :: Monad m => m (V3 a) -> V3 (m a) #

collectM :: Monad m => (a -> V3 b) -> m a -> V3 (m b) #

Foldable1 V3 
Instance details

Defined in Linear.V3

Methods

fold1 :: Semigroup m => V3 m -> m #

foldMap1 :: Semigroup m => (a -> m) -> V3 a -> m #

foldMap1' :: Semigroup m => (a -> m) -> V3 a -> m #

toNonEmpty :: V3 a -> NonEmpty a #

maximum :: Ord a => V3 a -> a #

minimum :: Ord a => V3 a -> a #

head :: V3 a -> a #

last :: V3 a -> a #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> V3 a -> b #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> V3 a -> b #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> V3 a -> b #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> V3 a -> b #

Hashable1 V3 
Instance details

Defined in Linear.V3

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> V3 a -> Int #

Affine V3 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V3 :: Type -> Type #

Methods

(.-.) :: Num a => V3 a -> V3 a -> Diff V3 a #

(.+^) :: Num a => V3 a -> Diff V3 a -> V3 a #

(.-^) :: Num a => V3 a -> Diff V3 a -> V3 a #

Metric V3 
Instance details

Defined in Linear.V3

Methods

dot :: Num a => V3 a -> V3 a -> a #

quadrance :: Num a => V3 a -> a #

qd :: Num a => V3 a -> V3 a -> a #

distance :: Floating a => V3 a -> V3 a -> a #

norm :: Floating a => V3 a -> a #

signorm :: Floating a => V3 a -> V3 a #

Trace V3 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => V3 (V3 a) -> a #

diagonal :: V3 (V3 a) -> V3 a #

Finite V3 
Instance details

Defined in Linear.V3

Associated Types

type Size V3 :: Nat #

Methods

toV :: V3 a -> V (Size V3) a #

fromV :: V (Size V3) a -> V3 a #

R1 V3 
Instance details

Defined in Linear.V3

Methods

_x :: Lens' (V3 a) a #

R2 V3 
Instance details

Defined in Linear.V3

Methods

_y :: Lens' (V3 a) a #

_xy :: Lens' (V3 a) (V2 a) #

R3 V3 
Instance details

Defined in Linear.V3

Methods

_z :: Lens' (V3 a) a #

_xyz :: Lens' (V3 a) (V3 a) #

Additive V3 
Instance details

Defined in Linear.V3

Methods

zero :: Num a => V3 a #

(^+^) :: Num a => V3 a -> V3 a -> V3 a #

(^-^) :: Num a => V3 a -> V3 a -> V3 a #

lerp :: Num a => a -> V3 a -> V3 a -> V3 a #

liftU2 :: (a -> a -> a) -> V3 a -> V3 a -> V3 a #

liftI2 :: (a -> b -> c) -> V3 a -> V3 b -> V3 c #

Apply V3 
Instance details

Defined in Linear.V3

Methods

(<.>) :: V3 (a -> b) -> V3 a -> V3 b #

(.>) :: V3 a -> V3 b -> V3 b #

(<.) :: V3 a -> V3 b -> V3 a #

liftF2 :: (a -> b -> c) -> V3 a -> V3 b -> V3 c #

Bind V3 
Instance details

Defined in Linear.V3

Methods

(>>-) :: V3 a -> (a -> V3 b) -> V3 b #

join :: V3 (V3 a) -> V3 a #

Traversable1 V3 
Instance details

Defined in Linear.V3

Methods

traverse1 :: Apply f => (a -> f b) -> V3 a -> f (V3 b) #

sequence1 :: Apply f => V3 (f b) -> f (V3 b) #

Generic1 V3 
Instance details

Defined in Linear.V3

Associated Types

type Rep1 V3 :: k -> Type #

Methods

from1 :: forall (a :: k). V3 a -> Rep1 V3 a #

to1 :: forall (a :: k). Rep1 V3 a -> V3 a #

Num r => Coalgebra r (E V3) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V3 -> r) -> E V3 -> E V3 -> r #

counital :: (E V3 -> r) -> r #

Lift a => Lift (V3 a :: Type) 
Instance details

Defined in Linear.V3

Methods

lift :: Quote m => V3 a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => V3 a -> Code m (V3 a) #

Unbox a => Vector Vector (V3 a) 
Instance details

Defined in Linear.V3

Methods

basicUnsafeFreeze :: Mutable Vector s (V3 a) -> ST s (Vector (V3 a)) #

basicUnsafeThaw :: Vector (V3 a) -> ST s (Mutable Vector s (V3 a)) #

basicLength :: Vector (V3 a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V3 a) -> Vector (V3 a) #

basicUnsafeIndexM :: Vector (V3 a) -> Int -> Box (V3 a) #

basicUnsafeCopy :: Mutable Vector s (V3 a) -> Vector (V3 a) -> ST s () #

elemseq :: Vector (V3 a) -> V3 a -> b -> b #

Unbox a => MVector MVector (V3 a) 
Instance details

Defined in Linear.V3

Methods

basicLength :: MVector s (V3 a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V3 a) -> MVector s (V3 a) #

basicOverlaps :: MVector s (V3 a) -> MVector s (V3 a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (V3 a)) #

basicInitialize :: MVector s (V3 a) -> ST s () #

basicUnsafeReplicate :: Int -> V3 a -> ST s (MVector s (V3 a)) #

basicUnsafeRead :: MVector s (V3 a) -> Int -> ST s (V3 a) #

basicUnsafeWrite :: MVector s (V3 a) -> Int -> V3 a -> ST s () #

basicClear :: MVector s (V3 a) -> ST s () #

basicSet :: MVector s (V3 a) -> V3 a -> ST s () #

basicUnsafeCopy :: MVector s (V3 a) -> MVector s (V3 a) -> ST s () #

basicUnsafeMove :: MVector s (V3 a) -> MVector s (V3 a) -> ST s () #

basicUnsafeGrow :: MVector s (V3 a) -> Int -> ST s (MVector s (V3 a)) #

Data a => Data (V3 a) 
Instance details

Defined in Linear.V3

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V3 a -> c (V3 a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V3 a) #

toConstr :: V3 a -> Constr #

dataTypeOf :: V3 a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V3 a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V3 a)) #

gmapT :: (forall b. Data b => b -> b) -> V3 a -> V3 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V3 a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V3 a -> r #

gmapQ :: (forall d. Data d => d -> u) -> V3 a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> V3 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> V3 a -> m (V3 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V3 a -> m (V3 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V3 a -> m (V3 a) #

Storable a => Storable (V3 a) 
Instance details

Defined in Linear.V3

Methods

sizeOf :: V3 a -> Int #

alignment :: V3 a -> Int #

peekElemOff :: Ptr (V3 a) -> Int -> IO (V3 a) #

pokeElemOff :: Ptr (V3 a) -> Int -> V3 a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (V3 a) #

pokeByteOff :: Ptr b -> Int -> V3 a -> IO () #

peek :: Ptr (V3 a) -> IO (V3 a) #

poke :: Ptr (V3 a) -> V3 a -> IO () #

Monoid a => Monoid (V3 a) 
Instance details

Defined in Linear.V3

Methods

mempty :: V3 a #

mappend :: V3 a -> V3 a -> V3 a #

mconcat :: [V3 a] -> V3 a #

Semigroup a => Semigroup (V3 a) 
Instance details

Defined in Linear.V3

Methods

(<>) :: V3 a -> V3 a -> V3 a #

sconcat :: NonEmpty (V3 a) -> V3 a #

stimes :: Integral b => b -> V3 a -> V3 a #

Bounded a => Bounded (V3 a) 
Instance details

Defined in Linear.V3

Methods

minBound :: V3 a #

maxBound :: V3 a #

Floating a => Floating (V3 a) 
Instance details

Defined in Linear.V3

Methods

pi :: V3 a #

exp :: V3 a -> V3 a #

log :: V3 a -> V3 a #

sqrt :: V3 a -> V3 a #

(**) :: V3 a -> V3 a -> V3 a #

logBase :: V3 a -> V3 a -> V3 a #

sin :: V3 a -> V3 a #

cos :: V3 a -> V3 a #

tan :: V3 a -> V3 a #

asin :: V3 a -> V3 a #

acos :: V3 a -> V3 a #

atan :: V3 a -> V3 a #

sinh :: V3 a -> V3 a #

cosh :: V3 a -> V3 a #

tanh :: V3 a -> V3 a #

asinh :: V3 a -> V3 a #

acosh :: V3 a -> V3 a #

atanh :: V3 a -> V3 a #

log1p :: V3 a -> V3 a #

expm1 :: V3 a -> V3 a #

log1pexp :: V3 a -> V3 a #

log1mexp :: V3 a -> V3 a #

Generic (V3 a) 
Instance details

Defined in Linear.V3

Associated Types

type Rep (V3 a) :: Type -> Type #

Methods

from :: V3 a -> Rep (V3 a) x #

to :: Rep (V3 a) x -> V3 a #

Ix a => Ix (V3 a) 
Instance details

Defined in Linear.V3

Methods

range :: (V3 a, V3 a) -> [V3 a] #

index :: (V3 a, V3 a) -> V3 a -> Int #

unsafeIndex :: (V3 a, V3 a) -> V3 a -> Int #

inRange :: (V3 a, V3 a) -> V3 a -> Bool #

rangeSize :: (V3 a, V3 a) -> Int #

unsafeRangeSize :: (V3 a, V3 a) -> Int #

Num a => Num (V3 a) 
Instance details

Defined in Linear.V3

Methods

(+) :: V3 a -> V3 a -> V3 a #

(-) :: V3 a -> V3 a -> V3 a #

(*) :: V3 a -> V3 a -> V3 a #

negate :: V3 a -> V3 a #

abs :: V3 a -> V3 a #

signum :: V3 a -> V3 a #

fromInteger :: Integer -> V3 a #

Read a => Read (V3 a) 
Instance details

Defined in Linear.V3

Fractional a => Fractional (V3 a) 
Instance details

Defined in Linear.V3

Methods

(/) :: V3 a -> V3 a -> V3 a #

recip :: V3 a -> V3 a #

fromRational :: Rational -> V3 a #

Show a => Show (V3 a) 
Instance details

Defined in Linear.V3

Methods

showsPrec :: Int -> V3 a -> ShowS #

show :: V3 a -> String #

showList :: [V3 a] -> ShowS #

Binary a => Binary (V3 a) 
Instance details

Defined in Linear.V3

Methods

put :: V3 a -> Put #

get :: Get (V3 a) #

putList :: [V3 a] -> Put #

Serial a => Serial (V3 a) 
Instance details

Defined in Linear.V3

Methods

serialize :: MonadPut m => V3 a -> m () #

deserialize :: MonadGet m => m (V3 a) #

Serialize a => Serialize (V3 a) 
Instance details

Defined in Linear.V3

Methods

put :: Putter (V3 a) #

get :: Get (V3 a) #

NFData a => NFData (V3 a) 
Instance details

Defined in Linear.V3

Methods

rnf :: V3 a -> () #

Eq a => Eq (V3 a) 
Instance details

Defined in Linear.V3

Methods

(==) :: V3 a -> V3 a -> Bool #

(/=) :: V3 a -> V3 a -> Bool #

Ord a => Ord (V3 a) 
Instance details

Defined in Linear.V3

Methods

compare :: V3 a -> V3 a -> Ordering #

(<) :: V3 a -> V3 a -> Bool #

(<=) :: V3 a -> V3 a -> Bool #

(>) :: V3 a -> V3 a -> Bool #

(>=) :: V3 a -> V3 a -> Bool #

max :: V3 a -> V3 a -> V3 a #

min :: V3 a -> V3 a -> V3 a #

Hashable a => Hashable (V3 a) 
Instance details

Defined in Linear.V3

Methods

hashWithSalt :: Int -> V3 a -> Int #

hash :: V3 a -> Int #

Epsilon a => Epsilon (V3 a) 
Instance details

Defined in Linear.V3

Methods

nearZero :: V3 a -> Bool #

Ixed (V3 a) 
Instance details

Defined in Linear.V3

Methods

ix :: Index (V3 a) -> Traversal' (V3 a) (IxValue (V3 a)) #

Random a => Random (V3 a) 
Instance details

Defined in Linear.V3

Methods

randomR :: RandomGen g => (V3 a, V3 a) -> g -> (V3 a, g) #

random :: RandomGen g => g -> (V3 a, g) #

randomRs :: RandomGen g => (V3 a, V3 a) -> g -> [V3 a] #

randoms :: RandomGen g => g -> [V3 a] #

Unbox a => Unbox (V3 a) 
Instance details

Defined in Linear.V3

FoldableWithIndex (E V3) V3 
Instance details

Defined in Linear.V3

Methods

ifoldMap :: Monoid m => (E V3 -> a -> m) -> V3 a -> m #

ifoldMap' :: Monoid m => (E V3 -> a -> m) -> V3 a -> m #

ifoldr :: (E V3 -> a -> b -> b) -> b -> V3 a -> b #

ifoldl :: (E V3 -> b -> a -> b) -> b -> V3 a -> b #

ifoldr' :: (E V3 -> a -> b -> b) -> b -> V3 a -> b #

ifoldl' :: (E V3 -> b -> a -> b) -> b -> V3 a -> b #

FunctorWithIndex (E V3) V3 
Instance details

Defined in Linear.V3

Methods

imap :: (E V3 -> a -> b) -> V3 a -> V3 b #

TraversableWithIndex (E V3) V3 
Instance details

Defined in Linear.V3

Methods

itraverse :: Applicative f => (E V3 -> a -> f b) -> V3 a -> f (V3 b) #

Each (V3 a) (V3 b) a b 
Instance details

Defined in Linear.V3

Methods

each :: Traversal (V3 a) (V3 b) a b #

Field1 (V3 a) (V3 a) a a 
Instance details

Defined in Linear.V3

Methods

_1 :: Lens (V3 a) (V3 a) a a #

Field2 (V3 a) (V3 a) a a 
Instance details

Defined in Linear.V3

Methods

_2 :: Lens (V3 a) (V3 a) a a #

Field3 (V3 a) (V3 a) a a 
Instance details

Defined in Linear.V3

Methods

_3 :: Lens (V3 a) (V3 a) a a #

type Rep V3 
Instance details

Defined in Linear.V3

type Rep V3 = E V3
type Diff V3 
Instance details

Defined in Linear.Affine

type Diff V3 = V3
type Size V3 
Instance details

Defined in Linear.V3

type Size V3 = 3
type Rep1 V3 
Instance details

Defined in Linear.V3

data MVector s (V3 a) 
Instance details

Defined in Linear.V3

data MVector s (V3 a) = MV_V3 !Int !(MVector s a)
type Rep (V3 a) 
Instance details

Defined in Linear.V3

type Index (V3 a) 
Instance details

Defined in Linear.V3

type Index (V3 a) = E V3
type IxValue (V3 a) 
Instance details

Defined in Linear.V3

type IxValue (V3 a) = a
data Vector (V3 a) 
Instance details

Defined in Linear.V3

data Vector (V3 a) = V_V3 !Int !(Vector a)

class R3 t => R4 (t :: Type -> Type) where #

A space that distinguishes orthogonal basis vectors _x, _y, _z, _w. (It may have more.)

Methods

_w :: Lens' (t a) a #

>>> V4 1 2 3 4 ^._w
4

_xyzw :: Lens' (t a) (V4 a) #

Instances

Instances details
R4 Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

_w :: Lens' (Quaternion a) a #

_xyzw :: Lens' (Quaternion a) (V4 a) #

R4 V4 
Instance details

Defined in Linear.V4

Methods

_w :: Lens' (V4 a) a #

_xyzw :: Lens' (V4 a) (V4 a) #

R4 f => R4 (Point f) 
Instance details

Defined in Linear.Affine

Methods

_w :: Lens' (Point f a) a #

_xyzw :: Lens' (Point f a) (V4 a) #

data V4 a #

A 4-dimensional vector.

Constructors

V4 !a !a !a !a 

Instances

Instances details
MonadFix V4 
Instance details

Defined in Linear.V4

Methods

mfix :: (a -> V4 a) -> V4 a #

MonadZip V4 
Instance details

Defined in Linear.V4

Methods

mzip :: V4 a -> V4 b -> V4 (a, b) #

mzipWith :: (a -> b -> c) -> V4 a -> V4 b -> V4 c #

munzip :: V4 (a, b) -> (V4 a, V4 b) #

Foldable V4 
Instance details

Defined in Linear.V4

Methods

fold :: Monoid m => V4 m -> m #

foldMap :: Monoid m => (a -> m) -> V4 a -> m #

foldMap' :: Monoid m => (a -> m) -> V4 a -> m #

foldr :: (a -> b -> b) -> b -> V4 a -> b #

foldr' :: (a -> b -> b) -> b -> V4 a -> b #

foldl :: (b -> a -> b) -> b -> V4 a -> b #

foldl' :: (b -> a -> b) -> b -> V4 a -> b #

foldr1 :: (a -> a -> a) -> V4 a -> a #

foldl1 :: (a -> a -> a) -> V4 a -> a #

toList :: V4 a -> [a] #

null :: V4 a -> Bool #

length :: V4 a -> Int #

elem :: Eq a => a -> V4 a -> Bool #

maximum :: Ord a => V4 a -> a #

minimum :: Ord a => V4 a -> a #

sum :: Num a => V4 a -> a #

product :: Num a => V4 a -> a #

Eq1 V4 
Instance details

Defined in Linear.V4

Methods

liftEq :: (a -> b -> Bool) -> V4 a -> V4 b -> Bool #

Ord1 V4 
Instance details

Defined in Linear.V4

Methods

liftCompare :: (a -> b -> Ordering) -> V4 a -> V4 b -> Ordering #

Read1 V4 
Instance details

Defined in Linear.V4

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V4 a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [V4 a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (V4 a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [V4 a] #

Show1 V4 
Instance details

Defined in Linear.V4

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V4 a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [V4 a] -> ShowS #

Traversable V4 
Instance details

Defined in Linear.V4

Methods

traverse :: Applicative f => (a -> f b) -> V4 a -> f (V4 b) #

sequenceA :: Applicative f => V4 (f a) -> f (V4 a) #

mapM :: Monad m => (a -> m b) -> V4 a -> m (V4 b) #

sequence :: Monad m => V4 (m a) -> m (V4 a) #

Applicative V4 
Instance details

Defined in Linear.V4

Methods

pure :: a -> V4 a #

(<*>) :: V4 (a -> b) -> V4 a -> V4 b #

liftA2 :: (a -> b -> c) -> V4 a -> V4 b -> V4 c #

(*>) :: V4 a -> V4 b -> V4 b #

(<*) :: V4 a -> V4 b -> V4 a #

Functor V4 
Instance details

Defined in Linear.V4

Methods

fmap :: (a -> b) -> V4 a -> V4 b #

(<$) :: a -> V4 b -> V4 a #

Monad V4 
Instance details

Defined in Linear.V4

Methods

(>>=) :: V4 a -> (a -> V4 b) -> V4 b #

(>>) :: V4 a -> V4 b -> V4 b #

return :: a -> V4 a #

Serial1 V4 
Instance details

Defined in Linear.V4

Methods

serializeWith :: MonadPut m => (a -> m ()) -> V4 a -> m () #

deserializeWith :: MonadGet m => m a -> m (V4 a) #

Representable V4 
Instance details

Defined in Linear.V4

Associated Types

type Rep V4 #

Methods

tabulate :: (Rep V4 -> a) -> V4 a #

index :: V4 a -> Rep V4 -> a #

Distributive V4 
Instance details

Defined in Linear.V4

Methods

distribute :: Functor f => f (V4 a) -> V4 (f a) #

collect :: Functor f => (a -> V4 b) -> f a -> V4 (f b) #

distributeM :: Monad m => m (V4 a) -> V4 (m a) #

collectM :: Monad m => (a -> V4 b) -> m a -> V4 (m b) #

Foldable1 V4 
Instance details

Defined in Linear.V4

Methods

fold1 :: Semigroup m => V4 m -> m #

foldMap1 :: Semigroup m => (a -> m) -> V4 a -> m #

foldMap1' :: Semigroup m => (a -> m) -> V4 a -> m #

toNonEmpty :: V4 a -> NonEmpty a #

maximum :: Ord a => V4 a -> a #

minimum :: Ord a => V4 a -> a #

head :: V4 a -> a #

last :: V4 a -> a #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> V4 a -> b #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> V4 a -> b #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> V4 a -> b #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> V4 a -> b #

Hashable1 V4 
Instance details

Defined in Linear.V4

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> V4 a -> Int #

Affine V4 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V4 :: Type -> Type #

Methods

(.-.) :: Num a => V4 a -> V4 a -> Diff V4 a #

(.+^) :: Num a => V4 a -> Diff V4 a -> V4 a #

(.-^) :: Num a => V4 a -> Diff V4 a -> V4 a #

Metric V4 
Instance details

Defined in Linear.V4

Methods

dot :: Num a => V4 a -> V4 a -> a #

quadrance :: Num a => V4 a -> a #

qd :: Num a => V4 a -> V4 a -> a #

distance :: Floating a => V4 a -> V4 a -> a #

norm :: Floating a => V4 a -> a #

signorm :: Floating a => V4 a -> V4 a #

Trace V4 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => V4 (V4 a) -> a #

diagonal :: V4 (V4 a) -> V4 a #

Finite V4 
Instance details

Defined in Linear.V4

Associated Types

type Size V4 :: Nat #

Methods

toV :: V4 a -> V (Size V4) a #

fromV :: V (Size V4) a -> V4 a #

R1 V4 
Instance details

Defined in Linear.V4

Methods

_x :: Lens' (V4 a) a #

R2 V4 
Instance details

Defined in Linear.V4

Methods

_y :: Lens' (V4 a) a #

_xy :: Lens' (V4 a) (V2 a) #

R3 V4 
Instance details

Defined in Linear.V4

Methods

_z :: Lens' (V4 a) a #

_xyz :: Lens' (V4 a) (V3 a) #

R4 V4 
Instance details

Defined in Linear.V4

Methods

_w :: Lens' (V4 a) a #

_xyzw :: Lens' (V4 a) (V4 a) #

Additive V4 
Instance details

Defined in Linear.V4

Methods

zero :: Num a => V4 a #

(^+^) :: Num a => V4 a -> V4 a -> V4 a #

(^-^) :: Num a => V4 a -> V4 a -> V4 a #

lerp :: Num a => a -> V4 a -> V4 a -> V4 a #

liftU2 :: (a -> a -> a) -> V4 a -> V4 a -> V4 a #

liftI2 :: (a -> b -> c) -> V4 a -> V4 b -> V4 c #

Apply V4 
Instance details

Defined in Linear.V4

Methods

(<.>) :: V4 (a -> b) -> V4 a -> V4 b #

(.>) :: V4 a -> V4 b -> V4 b #

(<.) :: V4 a -> V4 b -> V4 a #

liftF2 :: (a -> b -> c) -> V4 a -> V4 b -> V4 c #

Bind V4 
Instance details

Defined in Linear.V4

Methods

(>>-) :: V4 a -> (a -> V4 b) -> V4 b #

join :: V4 (V4 a) -> V4 a #

Traversable1 V4 
Instance details

Defined in Linear.V4

Methods

traverse1 :: Apply f => (a -> f b) -> V4 a -> f (V4 b) #

sequence1 :: Apply f => V4 (f b) -> f (V4 b) #

Generic1 V4 
Instance details

Defined in Linear.V4

Associated Types

type Rep1 V4 :: k -> Type #

Methods

from1 :: forall (a :: k). V4 a -> Rep1 V4 a #

to1 :: forall (a :: k). Rep1 V4 a -> V4 a #

Num r => Coalgebra r (E V4) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V4 -> r) -> E V4 -> E V4 -> r #

counital :: (E V4 -> r) -> r #

Lift a => Lift (V4 a :: Type) 
Instance details

Defined in Linear.V4

Methods

lift :: Quote m => V4 a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => V4 a -> Code m (V4 a) #

Unbox a => Vector Vector (V4 a) 
Instance details

Defined in Linear.V4

Methods

basicUnsafeFreeze :: Mutable Vector s (V4 a) -> ST s (Vector (V4 a)) #

basicUnsafeThaw :: Vector (V4 a) -> ST s (Mutable Vector s (V4 a)) #

basicLength :: Vector (V4 a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V4 a) -> Vector (V4 a) #

basicUnsafeIndexM :: Vector (V4 a) -> Int -> Box (V4 a) #

basicUnsafeCopy :: Mutable Vector s (V4 a) -> Vector (V4 a) -> ST s () #

elemseq :: Vector (V4 a) -> V4 a -> b -> b #

Unbox a => MVector MVector (V4 a) 
Instance details

Defined in Linear.V4

Methods

basicLength :: MVector s (V4 a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V4 a) -> MVector s (V4 a) #

basicOverlaps :: MVector s (V4 a) -> MVector s (V4 a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (V4 a)) #

basicInitialize :: MVector s (V4 a) -> ST s () #

basicUnsafeReplicate :: Int -> V4 a -> ST s (MVector s (V4 a)) #

basicUnsafeRead :: MVector s (V4 a) -> Int -> ST s (V4 a) #

basicUnsafeWrite :: MVector s (V4 a) -> Int -> V4 a -> ST s () #

basicClear :: MVector s (V4 a) -> ST s () #

basicSet :: MVector s (V4 a) -> V4 a -> ST s () #

basicUnsafeCopy :: MVector s (V4 a) -> MVector s (V4 a) -> ST s () #

basicUnsafeMove :: MVector s (V4 a) -> MVector s (V4 a) -> ST s () #

basicUnsafeGrow :: MVector s (V4 a) -> Int -> ST s (MVector s (V4 a)) #

Data a => Data (V4 a) 
Instance details

Defined in Linear.V4

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V4 a -> c (V4 a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V4 a) #

toConstr :: V4 a -> Constr #

dataTypeOf :: V4 a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V4 a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V4 a)) #

gmapT :: (forall b. Data b => b -> b) -> V4 a -> V4 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V4 a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V4 a -> r #

gmapQ :: (forall d. Data d => d -> u) -> V4 a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> V4 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> V4 a -> m (V4 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V4 a -> m (V4 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V4 a -> m (V4 a) #

Storable a => Storable (V4 a) 
Instance details

Defined in Linear.V4

Methods

sizeOf :: V4 a -> Int #

alignment :: V4 a -> Int #

peekElemOff :: Ptr (V4 a) -> Int -> IO (V4 a) #

pokeElemOff :: Ptr (V4 a) -> Int -> V4 a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (V4 a) #

pokeByteOff :: Ptr b -> Int -> V4 a -> IO () #

peek :: Ptr (V4 a) -> IO (V4 a) #

poke :: Ptr (V4 a) -> V4 a -> IO () #

Monoid a => Monoid (V4 a) 
Instance details

Defined in Linear.V4

Methods

mempty :: V4 a #

mappend :: V4 a -> V4 a -> V4 a #

mconcat :: [V4 a] -> V4 a #

Semigroup a => Semigroup (V4 a) 
Instance details

Defined in Linear.V4

Methods

(<>) :: V4 a -> V4 a -> V4 a #

sconcat :: NonEmpty (V4 a) -> V4 a #

stimes :: Integral b => b -> V4 a -> V4 a #

Bounded a => Bounded (V4 a) 
Instance details

Defined in Linear.V4

Methods

minBound :: V4 a #

maxBound :: V4 a #

Floating a => Floating (V4 a) 
Instance details

Defined in Linear.V4

Methods

pi :: V4 a #

exp :: V4 a -> V4 a #

log :: V4 a -> V4 a #

sqrt :: V4 a -> V4 a #

(**) :: V4 a -> V4 a -> V4 a #

logBase :: V4 a -> V4 a -> V4 a #

sin :: V4 a -> V4 a #

cos :: V4 a -> V4 a #

tan :: V4 a -> V4 a #

asin :: V4 a -> V4 a #

acos :: V4 a -> V4 a #

atan :: V4 a -> V4 a #

sinh :: V4 a -> V4 a #

cosh :: V4 a -> V4 a #

tanh :: V4 a -> V4 a #

asinh :: V4 a -> V4 a #

acosh :: V4 a -> V4 a #

atanh :: V4 a -> V4 a #

log1p :: V4 a -> V4 a #

expm1 :: V4 a -> V4 a #

log1pexp :: V4 a -> V4 a #

log1mexp :: V4 a -> V4 a #

Generic (V4 a) 
Instance details

Defined in Linear.V4

Associated Types

type Rep (V4 a) :: Type -> Type #

Methods

from :: V4 a -> Rep (V4 a) x #

to :: Rep (V4 a) x -> V4 a #

Ix a => Ix (V4 a) 
Instance details

Defined in Linear.V4

Methods

range :: (V4 a, V4 a) -> [V4 a] #

index :: (V4 a, V4 a) -> V4 a -> Int #

unsafeIndex :: (V4 a, V4 a) -> V4 a -> Int #

inRange :: (V4 a, V4 a) -> V4 a -> Bool #

rangeSize :: (V4 a, V4 a) -> Int #

unsafeRangeSize :: (V4 a, V4 a) -> Int #

Num a => Num (V4 a) 
Instance details

Defined in Linear.V4

Methods

(+) :: V4 a -> V4 a -> V4 a #

(-) :: V4 a -> V4 a -> V4 a #

(*) :: V4 a -> V4 a -> V4 a #

negate :: V4 a -> V4 a #

abs :: V4 a -> V4 a #

signum :: V4 a -> V4 a #

fromInteger :: Integer -> V4 a #

Read a => Read (V4 a) 
Instance details

Defined in Linear.V4

Fractional a => Fractional (V4 a) 
Instance details

Defined in Linear.V4

Methods

(/) :: V4 a -> V4 a -> V4 a #

recip :: V4 a -> V4 a #

fromRational :: Rational -> V4 a #

Show a => Show (V4 a) 
Instance details

Defined in Linear.V4

Methods

showsPrec :: Int -> V4 a -> ShowS #

show :: V4 a -> String #

showList :: [V4 a] -> ShowS #

Binary a => Binary (V4 a) 
Instance details

Defined in Linear.V4

Methods

put :: V4 a -> Put #

get :: Get (V4 a) #

putList :: [V4 a] -> Put #

Serial a => Serial (V4 a) 
Instance details

Defined in Linear.V4

Methods

serialize :: MonadPut m => V4 a -> m () #

deserialize :: MonadGet m => m (V4 a) #

Serialize a => Serialize (V4 a) 
Instance details

Defined in Linear.V4

Methods

put :: Putter (V4 a) #

get :: Get (V4 a) #

NFData a => NFData (V4 a) 
Instance details

Defined in Linear.V4

Methods

rnf :: V4 a -> () #

Eq a => Eq (V4 a) 
Instance details

Defined in Linear.V4

Methods

(==) :: V4 a -> V4 a -> Bool #

(/=) :: V4 a -> V4 a -> Bool #

Ord a => Ord (V4 a) 
Instance details

Defined in Linear.V4

Methods

compare :: V4 a -> V4 a -> Ordering #

(<) :: V4 a -> V4 a -> Bool #

(<=) :: V4 a -> V4 a -> Bool #

(>) :: V4 a -> V4 a -> Bool #

(>=) :: V4 a -> V4 a -> Bool #

max :: V4 a -> V4 a -> V4 a #

min :: V4 a -> V4 a -> V4 a #

Hashable a => Hashable (V4 a) 
Instance details

Defined in Linear.V4

Methods

hashWithSalt :: Int -> V4 a -> Int #

hash :: V4 a -> Int #

Epsilon a => Epsilon (V4 a) 
Instance details

Defined in Linear.V4

Methods

nearZero :: V4 a -> Bool #

Ixed (V4 a) 
Instance details

Defined in Linear.V4

Methods

ix :: Index (V4 a) -> Traversal' (V4 a) (IxValue (V4 a)) #

Random a => Random (V4 a) 
Instance details

Defined in Linear.V4

Methods

randomR :: RandomGen g => (V4 a, V4 a) -> g -> (V4 a, g) #

random :: RandomGen g => g -> (V4 a, g) #

randomRs :: RandomGen g => (V4 a, V4 a) -> g -> [V4 a] #

randoms :: RandomGen g => g -> [V4 a] #

Unbox a => Unbox (V4 a) 
Instance details

Defined in Linear.V4

FoldableWithIndex (E V4) V4 
Instance details

Defined in Linear.V4

Methods

ifoldMap :: Monoid m => (E V4 -> a -> m) -> V4 a -> m #

ifoldMap' :: Monoid m => (E V4 -> a -> m) -> V4 a -> m #

ifoldr :: (E V4 -> a -> b -> b) -> b -> V4 a -> b #

ifoldl :: (E V4 -> b -> a -> b) -> b -> V4 a -> b #

ifoldr' :: (E V4 -> a -> b -> b) -> b -> V4 a -> b #

ifoldl' :: (E V4 -> b -> a -> b) -> b -> V4 a -> b #

FunctorWithIndex (E V4) V4 
Instance details

Defined in Linear.V4

Methods

imap :: (E V4 -> a -> b) -> V4 a -> V4 b #

TraversableWithIndex (E V4) V4 
Instance details

Defined in Linear.V4

Methods

itraverse :: Applicative f => (E V4 -> a -> f b) -> V4 a -> f (V4 b) #

Each (V4 a) (V4 b) a b 
Instance details

Defined in Linear.V4

Methods

each :: Traversal (V4 a) (V4 b) a b #

Field1 (V4 a) (V4 a) a a 
Instance details

Defined in Linear.V4

Methods

_1 :: Lens (V4 a) (V4 a) a a #

Field2 (V4 a) (V4 a) a a 
Instance details

Defined in Linear.V4

Methods

_2 :: Lens (V4 a) (V4 a) a a #

Field3 (V4 a) (V4 a) a a 
Instance details

Defined in Linear.V4

Methods

_3 :: Lens (V4 a) (V4 a) a a #

Field4 (V4 a) (V4 a) a a 
Instance details

Defined in Linear.V4

Methods

_4 :: Lens (V4 a) (V4 a) a a #

type Rep V4 
Instance details

Defined in Linear.V4

type Rep V4 = E V4
type Diff V4 
Instance details

Defined in Linear.Affine

type Diff V4 = V4
type Size V4 
Instance details

Defined in Linear.V4

type Size V4 = 4
type Rep1 V4 
Instance details

Defined in Linear.V4

data MVector s (V4 a) 
Instance details

Defined in Linear.V4

data MVector s (V4 a) = MV_V4 !Int !(MVector s a)
type Rep (V4 a) 
Instance details

Defined in Linear.V4

type Index (V4 a) 
Instance details

Defined in Linear.V4

type Index (V4 a) = E V4
type IxValue (V4 a) 
Instance details

Defined in Linear.V4

type IxValue (V4 a) = a
data Vector (V4 a) 
Instance details

Defined in Linear.V4

data Vector (V4 a) = V_V4 !Int !(Vector a)

data V0 a #

A 0-dimensional vector

>>> pure 1 :: V0 Int
V0
>>> V0 + V0
V0

Constructors

V0 

Instances

Instances details
MonadFix V0 
Instance details

Defined in Linear.V0

Methods

mfix :: (a -> V0 a) -> V0 a #

MonadZip V0 
Instance details

Defined in Linear.V0

Methods

mzip :: V0 a -> V0 b -> V0 (a, b) #

mzipWith :: (a -> b -> c) -> V0 a -> V0 b -> V0 c #

munzip :: V0 (a, b) -> (V0 a, V0 b) #

Foldable V0 
Instance details

Defined in Linear.V0

Methods

fold :: Monoid m => V0 m -> m #

foldMap :: Monoid m => (a -> m) -> V0 a -> m #

foldMap' :: Monoid m => (a -> m) -> V0 a -> m #

foldr :: (a -> b -> b) -> b -> V0 a -> b #

foldr' :: (a -> b -> b) -> b -> V0 a -> b #

foldl :: (b -> a -> b) -> b -> V0 a -> b #

foldl' :: (b -> a -> b) -> b -> V0 a -> b #

foldr1 :: (a -> a -> a) -> V0 a -> a #

foldl1 :: (a -> a -> a) -> V0 a -> a #

toList :: V0 a -> [a] #

null :: V0 a -> Bool #

length :: V0 a -> Int #

elem :: Eq a => a -> V0 a -> Bool #

maximum :: Ord a => V0 a -> a #

minimum :: Ord a => V0 a -> a #

sum :: Num a => V0 a -> a #

product :: Num a => V0 a -> a #

Eq1 V0 
Instance details

Defined in Linear.V0

Methods

liftEq :: (a -> b -> Bool) -> V0 a -> V0 b -> Bool #

Ord1 V0 
Instance details

Defined in Linear.V0

Methods

liftCompare :: (a -> b -> Ordering) -> V0 a -> V0 b -> Ordering #

Read1 V0 
Instance details

Defined in Linear.V0

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V0 a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [V0 a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (V0 a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [V0 a] #

Show1 V0 
Instance details

Defined in Linear.V0

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V0 a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [V0 a] -> ShowS #

Traversable V0 
Instance details

Defined in Linear.V0

Methods

traverse :: Applicative f => (a -> f b) -> V0 a -> f (V0 b) #

sequenceA :: Applicative f => V0 (f a) -> f (V0 a) #

mapM :: Monad m => (a -> m b) -> V0 a -> m (V0 b) #

sequence :: Monad m => V0 (m a) -> m (V0 a) #

Applicative V0 
Instance details

Defined in Linear.V0

Methods

pure :: a -> V0 a #

(<*>) :: V0 (a -> b) -> V0 a -> V0 b #

liftA2 :: (a -> b -> c) -> V0 a -> V0 b -> V0 c #

(*>) :: V0 a -> V0 b -> V0 b #

(<*) :: V0 a -> V0 b -> V0 a #

Functor V0 
Instance details

Defined in Linear.V0

Methods

fmap :: (a -> b) -> V0 a -> V0 b #

(<$) :: a -> V0 b -> V0 a #

Monad V0 
Instance details

Defined in Linear.V0

Methods

(>>=) :: V0 a -> (a -> V0 b) -> V0 b #

(>>) :: V0 a -> V0 b -> V0 b #

return :: a -> V0 a #

Serial1 V0 
Instance details

Defined in Linear.V0

Methods

serializeWith :: MonadPut m => (a -> m ()) -> V0 a -> m () #

deserializeWith :: MonadGet m => m a -> m (V0 a) #

Representable V0 
Instance details

Defined in Linear.V0

Associated Types

type Rep V0 #

Methods

tabulate :: (Rep V0 -> a) -> V0 a #

index :: V0 a -> Rep V0 -> a #

Distributive V0 
Instance details

Defined in Linear.V0

Methods

distribute :: Functor f => f (V0 a) -> V0 (f a) #

collect :: Functor f => (a -> V0 b) -> f a -> V0 (f b) #

distributeM :: Monad m => m (V0 a) -> V0 (m a) #

collectM :: Monad m => (a -> V0 b) -> m a -> V0 (m b) #

Hashable1 V0 
Instance details

Defined in Linear.V0

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> V0 a -> Int #

Affine V0 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V0 :: Type -> Type #

Methods

(.-.) :: Num a => V0 a -> V0 a -> Diff V0 a #

(.+^) :: Num a => V0 a -> Diff V0 a -> V0 a #

(.-^) :: Num a => V0 a -> Diff V0 a -> V0 a #

Metric V0 
Instance details

Defined in Linear.V0

Methods

dot :: Num a => V0 a -> V0 a -> a #

quadrance :: Num a => V0 a -> a #

qd :: Num a => V0 a -> V0 a -> a #

distance :: Floating a => V0 a -> V0 a -> a #

norm :: Floating a => V0 a -> a #

signorm :: Floating a => V0 a -> V0 a #

Trace V0 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => V0 (V0 a) -> a #

diagonal :: V0 (V0 a) -> V0 a #

Finite V0 
Instance details

Defined in Linear.V0

Associated Types

type Size V0 :: Nat #

Methods

toV :: V0 a -> V (Size V0) a #

fromV :: V (Size V0) a -> V0 a #

Additive V0 
Instance details

Defined in Linear.V0

Methods

zero :: Num a => V0 a #

(^+^) :: Num a => V0 a -> V0 a -> V0 a #

(^-^) :: Num a => V0 a -> V0 a -> V0 a #

lerp :: Num a => a -> V0 a -> V0 a -> V0 a #

liftU2 :: (a -> a -> a) -> V0 a -> V0 a -> V0 a #

liftI2 :: (a -> b -> c) -> V0 a -> V0 b -> V0 c #

Apply V0 
Instance details

Defined in Linear.V0

Methods

(<.>) :: V0 (a -> b) -> V0 a -> V0 b #

(.>) :: V0 a -> V0 b -> V0 b #

(<.) :: V0 a -> V0 b -> V0 a #

liftF2 :: (a -> b -> c) -> V0 a -> V0 b -> V0 c #

Bind V0 
Instance details

Defined in Linear.V0

Methods

(>>-) :: V0 a -> (a -> V0 b) -> V0 b #

join :: V0 (V0 a) -> V0 a #

Generic1 V0 
Instance details

Defined in Linear.V0

Associated Types

type Rep1 V0 :: k -> Type #

Methods

from1 :: forall (a :: k). V0 a -> Rep1 V0 a #

to1 :: forall (a :: k). Rep1 V0 a -> V0 a #

Num r => Algebra r (E V0) 
Instance details

Defined in Linear.Algebra

Methods

mult :: (E V0 -> E V0 -> r) -> E V0 -> r #

unital :: r -> E V0 -> r #

Num r => Coalgebra r (E V0) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V0 -> r) -> E V0 -> E V0 -> r #

counital :: (E V0 -> r) -> r #

Lift (V0 a :: Type) 
Instance details

Defined in Linear.V0

Methods

lift :: Quote m => V0 a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => V0 a -> Code m (V0 a) #

Vector Vector (V0 a) 
Instance details

Defined in Linear.V0

Methods

basicUnsafeFreeze :: Mutable Vector s (V0 a) -> ST s (Vector (V0 a)) #

basicUnsafeThaw :: Vector (V0 a) -> ST s (Mutable Vector s (V0 a)) #

basicLength :: Vector (V0 a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V0 a) -> Vector (V0 a) #

basicUnsafeIndexM :: Vector (V0 a) -> Int -> Box (V0 a) #

basicUnsafeCopy :: Mutable Vector s (V0 a) -> Vector (V0 a) -> ST s () #

elemseq :: Vector (V0 a) -> V0 a -> b -> b #

MVector MVector (V0 a) 
Instance details

Defined in Linear.V0

Methods

basicLength :: MVector s (V0 a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V0 a) -> MVector s (V0 a) #

basicOverlaps :: MVector s (V0 a) -> MVector s (V0 a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (V0 a)) #

basicInitialize :: MVector s (V0 a) -> ST s () #

basicUnsafeReplicate :: Int -> V0 a -> ST s (MVector s (V0 a)) #

basicUnsafeRead :: MVector s (V0 a) -> Int -> ST s (V0 a) #

basicUnsafeWrite :: MVector s (V0 a) -> Int -> V0 a -> ST s () #

basicClear :: MVector s (V0 a) -> ST s () #

basicSet :: MVector s (V0 a) -> V0 a -> ST s () #

basicUnsafeCopy :: MVector s (V0 a) -> MVector s (V0 a) -> ST s () #

basicUnsafeMove :: MVector s (V0 a) -> MVector s (V0 a) -> ST s () #

basicUnsafeGrow :: MVector s (V0 a) -> Int -> ST s (MVector s (V0 a)) #

Data a => Data (V0 a) 
Instance details

Defined in Linear.V0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V0 a -> c (V0 a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V0 a) #

toConstr :: V0 a -> Constr #

dataTypeOf :: V0 a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V0 a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V0 a)) #

gmapT :: (forall b. Data b => b -> b) -> V0 a -> V0 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V0 a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V0 a -> r #

gmapQ :: (forall d. Data d => d -> u) -> V0 a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> V0 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> V0 a -> m (V0 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V0 a -> m (V0 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V0 a -> m (V0 a) #

Storable (V0 a) 
Instance details

Defined in Linear.V0

Methods

sizeOf :: V0 a -> Int #

alignment :: V0 a -> Int #

peekElemOff :: Ptr (V0 a) -> Int -> IO (V0 a) #

pokeElemOff :: Ptr (V0 a) -> Int -> V0 a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (V0 a) #

pokeByteOff :: Ptr b -> Int -> V0 a -> IO () #

peek :: Ptr (V0 a) -> IO (V0 a) #

poke :: Ptr (V0 a) -> V0 a -> IO () #

Monoid (V0 a) 
Instance details

Defined in Linear.V0

Methods

mempty :: V0 a #

mappend :: V0 a -> V0 a -> V0 a #

mconcat :: [V0 a] -> V0 a #

Semigroup (V0 a) 
Instance details

Defined in Linear.V0

Methods

(<>) :: V0 a -> V0 a -> V0 a #

sconcat :: NonEmpty (V0 a) -> V0 a #

stimes :: Integral b => b -> V0 a -> V0 a #

Bounded (V0 a) 
Instance details

Defined in Linear.V0

Methods

minBound :: V0 a #

maxBound :: V0 a #

Enum (V0 a) 
Instance details

Defined in Linear.V0

Methods

succ :: V0 a -> V0 a #

pred :: V0 a -> V0 a #

toEnum :: Int -> V0 a #

fromEnum :: V0 a -> Int #

enumFrom :: V0 a -> [V0 a] #

enumFromThen :: V0 a -> V0 a -> [V0 a] #

enumFromTo :: V0 a -> V0 a -> [V0 a] #

enumFromThenTo :: V0 a -> V0 a -> V0 a -> [V0 a] #

Floating (V0 a) 
Instance details

Defined in Linear.V0

Methods

pi :: V0 a #

exp :: V0 a -> V0 a #

log :: V0 a -> V0 a #

sqrt :: V0 a -> V0 a #

(**) :: V0 a -> V0 a -> V0 a #

logBase :: V0 a -> V0 a -> V0 a #

sin :: V0 a -> V0 a #

cos :: V0 a -> V0 a #

tan :: V0 a -> V0 a #

asin :: V0 a -> V0 a #

acos :: V0 a -> V0 a #

atan :: V0 a -> V0 a #

sinh :: V0 a -> V0 a #

cosh :: V0 a -> V0 a #

tanh :: V0 a -> V0 a #

asinh :: V0 a -> V0 a #

acosh :: V0 a -> V0 a #

atanh :: V0 a -> V0 a #

log1p :: V0 a -> V0 a #

expm1 :: V0 a -> V0 a #

log1pexp :: V0 a -> V0 a #

log1mexp :: V0 a -> V0 a #

Generic (V0 a) 
Instance details

Defined in Linear.V0

Associated Types

type Rep (V0 a) :: Type -> Type #

Methods

from :: V0 a -> Rep (V0 a) x #

to :: Rep (V0 a) x -> V0 a #

Ix (V0 a) 
Instance details

Defined in Linear.V0

Methods

range :: (V0 a, V0 a) -> [V0 a] #

index :: (V0 a, V0 a) -> V0 a -> Int #

unsafeIndex :: (V0 a, V0 a) -> V0 a -> Int #

inRange :: (V0 a, V0 a) -> V0 a -> Bool #

rangeSize :: (V0 a, V0 a) -> Int #

unsafeRangeSize :: (V0 a, V0 a) -> Int #

Num (V0 a) 
Instance details

Defined in Linear.V0

Methods

(+) :: V0 a -> V0 a -> V0 a #

(-) :: V0 a -> V0 a -> V0 a #

(*) :: V0 a -> V0 a -> V0 a #

negate :: V0 a -> V0 a #

abs :: V0 a -> V0 a #

signum :: V0 a -> V0 a #

fromInteger :: Integer -> V0 a #

Read (V0 a) 
Instance details

Defined in Linear.V0

Fractional (V0 a) 
Instance details

Defined in Linear.V0

Methods

(/) :: V0 a -> V0 a -> V0 a #

recip :: V0 a -> V0 a #

fromRational :: Rational -> V0 a #

Show (V0 a) 
Instance details

Defined in Linear.V0

Methods

showsPrec :: Int -> V0 a -> ShowS #

show :: V0 a -> String #

showList :: [V0 a] -> ShowS #

Binary (V0 a) 
Instance details

Defined in Linear.V0

Methods

put :: V0 a -> Put #

get :: Get (V0 a) #

putList :: [V0 a] -> Put #

Serial (V0 a) 
Instance details

Defined in Linear.V0

Methods

serialize :: MonadPut m => V0 a -> m () #

deserialize :: MonadGet m => m (V0 a) #

Serialize (V0 a) 
Instance details

Defined in Linear.V0

Methods

put :: Putter (V0 a) #

get :: Get (V0 a) #

NFData (V0 a) 
Instance details

Defined in Linear.V0

Methods

rnf :: V0 a -> () #

Eq (V0 a) 
Instance details

Defined in Linear.V0

Methods

(==) :: V0 a -> V0 a -> Bool #

(/=) :: V0 a -> V0 a -> Bool #

Ord (V0 a) 
Instance details

Defined in Linear.V0

Methods

compare :: V0 a -> V0 a -> Ordering #

(<) :: V0 a -> V0 a -> Bool #

(<=) :: V0 a -> V0 a -> Bool #

(>) :: V0 a -> V0 a -> Bool #

(>=) :: V0 a -> V0 a -> Bool #

max :: V0 a -> V0 a -> V0 a #

min :: V0 a -> V0 a -> V0 a #

Hashable (V0 a) 
Instance details

Defined in Linear.V0

Methods

hashWithSalt :: Int -> V0 a -> Int #

hash :: V0 a -> Int #

Epsilon (V0 a) 
Instance details

Defined in Linear.V0

Methods

nearZero :: V0 a -> Bool #

Ixed (V0 a) 
Instance details

Defined in Linear.V0

Methods

ix :: Index (V0 a) -> Traversal' (V0 a) (IxValue (V0 a)) #

Random (V0 a) 
Instance details

Defined in Linear.V0

Methods

randomR :: RandomGen g => (V0 a, V0 a) -> g -> (V0 a, g) #

random :: RandomGen g => g -> (V0 a, g) #

randomRs :: RandomGen g => (V0 a, V0 a) -> g -> [V0 a] #

randoms :: RandomGen g => g -> [V0 a] #

Unbox (V0 a) 
Instance details

Defined in Linear.V0

FoldableWithIndex (E V0) V0 
Instance details

Defined in Linear.V0

Methods

ifoldMap :: Monoid m => (E V0 -> a -> m) -> V0 a -> m #

ifoldMap' :: Monoid m => (E V0 -> a -> m) -> V0 a -> m #

ifoldr :: (E V0 -> a -> b -> b) -> b -> V0 a -> b #

ifoldl :: (E V0 -> b -> a -> b) -> b -> V0 a -> b #

ifoldr' :: (E V0 -> a -> b -> b) -> b -> V0 a -> b #

ifoldl' :: (E V0 -> b -> a -> b) -> b -> V0 a -> b #

FunctorWithIndex (E V0) V0 
Instance details

Defined in Linear.V0

Methods

imap :: (E V0 -> a -> b) -> V0 a -> V0 b #

TraversableWithIndex (E V0) V0 
Instance details

Defined in Linear.V0

Methods

itraverse :: Applicative f => (E V0 -> a -> f b) -> V0 a -> f (V0 b) #

Each (V0 a) (V0 b) a b 
Instance details

Defined in Linear.V0

Methods

each :: Traversal (V0 a) (V0 b) a b #

type Rep V0 
Instance details

Defined in Linear.V0

type Rep V0 = E V0
type Diff V0 
Instance details

Defined in Linear.Affine

type Diff V0 = V0
type Size V0 
Instance details

Defined in Linear.V0

type Size V0 = 0
type Rep1 V0 
Instance details

Defined in Linear.V0

type Rep1 V0 = D1 ('MetaData "V0" "Linear.V0" "lnr-1.22-7520e77e" 'False) (C1 ('MetaCons "V0" 'PrefixI 'False) (U1 :: Type -> Type))
newtype MVector s (V0 a) 
Instance details

Defined in Linear.V0

newtype MVector s (V0 a) = MV_V0 Int
type Rep (V0 a) 
Instance details

Defined in Linear.V0

type Rep (V0 a) = D1 ('MetaData "V0" "Linear.V0" "lnr-1.22-7520e77e" 'False) (C1 ('MetaCons "V0" 'PrefixI 'False) (U1 :: Type -> Type))
type Index (V0 a) 
Instance details

Defined in Linear.V0

type Index (V0 a) = E V0
type IxValue (V0 a) 
Instance details

Defined in Linear.V0

type IxValue (V0 a) = a
newtype Vector (V0 a) 
Instance details

Defined in Linear.V0

newtype Vector (V0 a) = V_V0 Int

class Complicated t => Hamiltonian (t :: Type -> Type) where #

A vector space that includes the basis elements _e, _i, _j and _k

Methods

_j :: Lens' (t a) a #

_k :: Lens' (t a) a #

_ijk :: Lens' (t a) (V3 a) #

Instances

Instances details
Hamiltonian Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

_j :: Lens' (Quaternion a) a #

_k :: Lens' (Quaternion a) a #

_ijk :: Lens' (Quaternion a) (V3 a) #

class Complicated (t :: Type -> Type) where #

A vector space that includes the basis elements _e and _i

Methods

_e :: Lens' (t a) a #

_i :: Lens' (t a) a #

Instances

Instances details
Complicated Complex 
Instance details

Defined in Linear.Quaternion

Methods

_e :: Lens' (Complex a) a #

_i :: Lens' (Complex a) a #

Complicated Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

_e :: Lens' (Quaternion a) a #

_i :: Lens' (Quaternion a) a #

data Quaternion a #

Quaternions

Constructors

Quaternion !a !(V3 a) 

Instances

Instances details
MonadFix Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

mfix :: (a -> Quaternion a) -> Quaternion a #

MonadZip Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

mzip :: Quaternion a -> Quaternion b -> Quaternion (a, b) #

mzipWith :: (a -> b -> c) -> Quaternion a -> Quaternion b -> Quaternion c #

munzip :: Quaternion (a, b) -> (Quaternion a, Quaternion b) #

Foldable Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

fold :: Monoid m => Quaternion m -> m #

foldMap :: Monoid m => (a -> m) -> Quaternion a -> m #

foldMap' :: Monoid m => (a -> m) -> Quaternion a -> m #

foldr :: (a -> b -> b) -> b -> Quaternion a -> b #

foldr' :: (a -> b -> b) -> b -> Quaternion a -> b #

foldl :: (b -> a -> b) -> b -> Quaternion a -> b #

foldl' :: (b -> a -> b) -> b -> Quaternion a -> b #

foldr1 :: (a -> a -> a) -> Quaternion a -> a #

foldl1 :: (a -> a -> a) -> Quaternion a -> a #

toList :: Quaternion a -> [a] #

null :: Quaternion a -> Bool #

length :: Quaternion a -> Int #

elem :: Eq a => a -> Quaternion a -> Bool #

maximum :: Ord a => Quaternion a -> a #

minimum :: Ord a => Quaternion a -> a #

sum :: Num a => Quaternion a -> a #

product :: Num a => Quaternion a -> a #

Eq1 Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

liftEq :: (a -> b -> Bool) -> Quaternion a -> Quaternion b -> Bool #

Ord1 Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

liftCompare :: (a -> b -> Ordering) -> Quaternion a -> Quaternion b -> Ordering #

Read1 Quaternion 
Instance details

Defined in Linear.Quaternion

Show1 Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Quaternion a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Quaternion a] -> ShowS #

Traversable Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

traverse :: Applicative f => (a -> f b) -> Quaternion a -> f (Quaternion b) #

sequenceA :: Applicative f => Quaternion (f a) -> f (Quaternion a) #

mapM :: Monad m => (a -> m b) -> Quaternion a -> m (Quaternion b) #

sequence :: Monad m => Quaternion (m a) -> m (Quaternion a) #

Applicative Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

pure :: a -> Quaternion a #

(<*>) :: Quaternion (a -> b) -> Quaternion a -> Quaternion b #

liftA2 :: (a -> b -> c) -> Quaternion a -> Quaternion b -> Quaternion c #

(*>) :: Quaternion a -> Quaternion b -> Quaternion b #

(<*) :: Quaternion a -> Quaternion b -> Quaternion a #

Functor Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

fmap :: (a -> b) -> Quaternion a -> Quaternion b #

(<$) :: a -> Quaternion b -> Quaternion a #

Monad Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

(>>=) :: Quaternion a -> (a -> Quaternion b) -> Quaternion b #

(>>) :: Quaternion a -> Quaternion b -> Quaternion b #

return :: a -> Quaternion a #

Serial1 Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

serializeWith :: MonadPut m => (a -> m ()) -> Quaternion a -> m () #

deserializeWith :: MonadGet m => m a -> m (Quaternion a) #

Representable Quaternion 
Instance details

Defined in Linear.Quaternion

Associated Types

type Rep Quaternion #

Methods

tabulate :: (Rep Quaternion -> a) -> Quaternion a #

index :: Quaternion a -> Rep Quaternion -> a #

Distributive Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

distribute :: Functor f => f (Quaternion a) -> Quaternion (f a) #

collect :: Functor f => (a -> Quaternion b) -> f a -> Quaternion (f b) #

distributeM :: Monad m => m (Quaternion a) -> Quaternion (m a) #

collectM :: Monad m => (a -> Quaternion b) -> m a -> Quaternion (m b) #

Hashable1 Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Quaternion a -> Int #

Affine Quaternion 
Instance details

Defined in Linear.Affine

Associated Types

type Diff Quaternion :: Type -> Type #

Metric Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

dot :: Num a => Quaternion a -> Quaternion a -> a #

quadrance :: Num a => Quaternion a -> a #

qd :: Num a => Quaternion a -> Quaternion a -> a #

distance :: Floating a => Quaternion a -> Quaternion a -> a #

norm :: Floating a => Quaternion a -> a #

signorm :: Floating a => Quaternion a -> Quaternion a #

Complicated Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

_e :: Lens' (Quaternion a) a #

_i :: Lens' (Quaternion a) a #

Hamiltonian Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

_j :: Lens' (Quaternion a) a #

_k :: Lens' (Quaternion a) a #

_ijk :: Lens' (Quaternion a) (V3 a) #

Trace Quaternion 
Instance details

Defined in Linear.Trace

Finite Quaternion 
Instance details

Defined in Linear.Quaternion

Associated Types

type Size Quaternion :: Nat #

Methods

toV :: Quaternion a -> V (Size Quaternion) a #

fromV :: V (Size Quaternion) a -> Quaternion a #

R1 Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

_x :: Lens' (Quaternion a) a #

R2 Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

_y :: Lens' (Quaternion a) a #

_xy :: Lens' (Quaternion a) (V2 a) #

R3 Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

_z :: Lens' (Quaternion a) a #

_xyz :: Lens' (Quaternion a) (V3 a) #

R4 Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

_w :: Lens' (Quaternion a) a #

_xyzw :: Lens' (Quaternion a) (V4 a) #

Additive Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

zero :: Num a => Quaternion a #

(^+^) :: Num a => Quaternion a -> Quaternion a -> Quaternion a #

(^-^) :: Num a => Quaternion a -> Quaternion a -> Quaternion a #

lerp :: Num a => a -> Quaternion a -> Quaternion a -> Quaternion a #

liftU2 :: (a -> a -> a) -> Quaternion a -> Quaternion a -> Quaternion a #

liftI2 :: (a -> b -> c) -> Quaternion a -> Quaternion b -> Quaternion c #

Apply Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

(<.>) :: Quaternion (a -> b) -> Quaternion a -> Quaternion b #

(.>) :: Quaternion a -> Quaternion b -> Quaternion b #

(<.) :: Quaternion a -> Quaternion b -> Quaternion a #

liftF2 :: (a -> b -> c) -> Quaternion a -> Quaternion b -> Quaternion c #

Bind Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

(>>-) :: Quaternion a -> (a -> Quaternion b) -> Quaternion b #

join :: Quaternion (Quaternion a) -> Quaternion a #

Generic1 Quaternion 
Instance details

Defined in Linear.Quaternion

Associated Types

type Rep1 Quaternion :: k -> Type #

Methods

from1 :: forall (a :: k). Quaternion a -> Rep1 Quaternion a #

to1 :: forall (a :: k). Rep1 Quaternion a -> Quaternion a #

(Num r, TrivialConjugate r) => Algebra r (E Quaternion) 
Instance details

Defined in Linear.Algebra

Methods

mult :: (E Quaternion -> E Quaternion -> r) -> E Quaternion -> r #

unital :: r -> E Quaternion -> r #

(Num r, TrivialConjugate r) => Coalgebra r (E Quaternion) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E Quaternion -> r) -> E Quaternion -> E Quaternion -> r #

counital :: (E Quaternion -> r) -> r #

Lift a => Lift (Quaternion a :: Type) 
Instance details

Defined in Linear.Quaternion

Methods

lift :: Quote m => Quaternion a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Quaternion a -> Code m (Quaternion a) #

Unbox a => Vector Vector (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Unbox a => MVector MVector (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Data a => Data (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Quaternion a -> c (Quaternion a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Quaternion a) #

toConstr :: Quaternion a -> Constr #

dataTypeOf :: Quaternion a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Quaternion a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Quaternion a)) #

gmapT :: (forall b. Data b => b -> b) -> Quaternion a -> Quaternion a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Quaternion a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Quaternion a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Quaternion a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Quaternion a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Quaternion a -> m (Quaternion a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Quaternion a -> m (Quaternion a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Quaternion a -> m (Quaternion a) #

Storable a => Storable (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Methods

sizeOf :: Quaternion a -> Int #

alignment :: Quaternion a -> Int #

peekElemOff :: Ptr (Quaternion a) -> Int -> IO (Quaternion a) #

pokeElemOff :: Ptr (Quaternion a) -> Int -> Quaternion a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Quaternion a) #

pokeByteOff :: Ptr b -> Int -> Quaternion a -> IO () #

peek :: Ptr (Quaternion a) -> IO (Quaternion a) #

poke :: Ptr (Quaternion a) -> Quaternion a -> IO () #

Monoid a => Monoid (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Semigroup a => Semigroup (Quaternion a) 
Instance details

Defined in Linear.Quaternion

RealFloat a => Floating (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Generic (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Associated Types

type Rep (Quaternion a) :: Type -> Type #

Methods

from :: Quaternion a -> Rep (Quaternion a) x #

to :: Rep (Quaternion a) x -> Quaternion a #

Ix a => Ix (Quaternion a) 
Instance details

Defined in Linear.Quaternion

RealFloat a => Num (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Read a => Read (Quaternion a) 
Instance details

Defined in Linear.Quaternion

RealFloat a => Fractional (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Show a => Show (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Binary a => Binary (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Methods

put :: Quaternion a -> Put #

get :: Get (Quaternion a) #

putList :: [Quaternion a] -> Put #

Serial a => Serial (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Methods

serialize :: MonadPut m => Quaternion a -> m () #

deserialize :: MonadGet m => m (Quaternion a) #

Serialize a => Serialize (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Methods

put :: Putter (Quaternion a) #

get :: Get (Quaternion a) #

NFData a => NFData (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Methods

rnf :: Quaternion a -> () #

Eq a => Eq (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Methods

(==) :: Quaternion a -> Quaternion a -> Bool #

(/=) :: Quaternion a -> Quaternion a -> Bool #

Ord a => Ord (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Hashable a => Hashable (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Methods

hashWithSalt :: Int -> Quaternion a -> Int #

hash :: Quaternion a -> Int #

(Conjugate a, RealFloat a) => Conjugate (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Methods

conjugate :: Quaternion a -> Quaternion a #

(RealFloat a, Epsilon a) => Epsilon (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Methods

nearZero :: Quaternion a -> Bool #

Ixed (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Random a => Random (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Methods

randomR :: RandomGen g => (Quaternion a, Quaternion a) -> g -> (Quaternion a, g) #

random :: RandomGen g => g -> (Quaternion a, g) #

randomRs :: RandomGen g => (Quaternion a, Quaternion a) -> g -> [Quaternion a] #

randoms :: RandomGen g => g -> [Quaternion a] #

Unbox a => Unbox (Quaternion a) 
Instance details

Defined in Linear.Quaternion

FoldableWithIndex (E Quaternion) Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

ifoldMap :: Monoid m => (E Quaternion -> a -> m) -> Quaternion a -> m #

ifoldMap' :: Monoid m => (E Quaternion -> a -> m) -> Quaternion a -> m #

ifoldr :: (E Quaternion -> a -> b -> b) -> b -> Quaternion a -> b #

ifoldl :: (E Quaternion -> b -> a -> b) -> b -> Quaternion a -> b #

ifoldr' :: (E Quaternion -> a -> b -> b) -> b -> Quaternion a -> b #

ifoldl' :: (E Quaternion -> b -> a -> b) -> b -> Quaternion a -> b #

FunctorWithIndex (E Quaternion) Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

imap :: (E Quaternion -> a -> b) -> Quaternion a -> Quaternion b #

TraversableWithIndex (E Quaternion) Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

itraverse :: Applicative f => (E Quaternion -> a -> f b) -> Quaternion a -> f (Quaternion b) #

Each (Quaternion a) (Quaternion b) a b 
Instance details

Defined in Linear.Quaternion

Methods

each :: Traversal (Quaternion a) (Quaternion b) a b #

Field1 (Quaternion a) (Quaternion a) a a 
Instance details

Defined in Linear.Quaternion

Methods

_1 :: Lens (Quaternion a) (Quaternion a) a a #

Field2 (Quaternion a) (Quaternion a) a a 
Instance details

Defined in Linear.Quaternion

Methods

_2 :: Lens (Quaternion a) (Quaternion a) a a #

Field3 (Quaternion a) (Quaternion a) a a 
Instance details

Defined in Linear.Quaternion

Methods

_3 :: Lens (Quaternion a) (Quaternion a) a a #

Field4 (Quaternion a) (Quaternion a) a a 
Instance details

Defined in Linear.Quaternion

Methods

_4 :: Lens (Quaternion a) (Quaternion a) a a #

type Rep Quaternion 
Instance details

Defined in Linear.Quaternion

type Diff Quaternion 
Instance details

Defined in Linear.Affine

type Size Quaternion 
Instance details

Defined in Linear.Quaternion

type Size Quaternion = 4
type Rep1 Quaternion 
Instance details

Defined in Linear.Quaternion

type Rep1 Quaternion = D1 ('MetaData "Quaternion" "Linear.Quaternion" "lnr-1.22-7520e77e" 'False) (C1 ('MetaCons "Quaternion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec1 V3)))
data MVector s (Quaternion a) 
Instance details

Defined in Linear.Quaternion

type Rep (Quaternion a) 
Instance details

Defined in Linear.Quaternion

type Rep (Quaternion a) = D1 ('MetaData "Quaternion" "Linear.Quaternion" "lnr-1.22-7520e77e" 'False) (C1 ('MetaCons "Quaternion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 (V3 a))))
type Index (Quaternion a) 
Instance details

Defined in Linear.Quaternion

type IxValue (Quaternion a) 
Instance details

Defined in Linear.Quaternion

type IxValue (Quaternion a) = a
data Vector (Quaternion a) 
Instance details

Defined in Linear.Quaternion

class Functor m => Trace (m :: Type -> Type) where #

Minimal complete definition

Nothing

Methods

trace :: Num a => m (m a) -> a #

Compute the trace of a matrix

>>> trace (V2 (V2 a b) (V2 c d))
a + d

diagonal :: m (m a) -> m a #

Compute the diagonal of a matrix

>>> diagonal (V2 (V2 a b) (V2 c d))
V2 a d

Instances

Instances details
Trace Complex 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => Complex (Complex a) -> a #

diagonal :: Complex (Complex a) -> Complex a #

Trace IntMap 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => IntMap (IntMap a) -> a #

diagonal :: IntMap (IntMap a) -> IntMap a #

Trace Plucker 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => Plucker (Plucker a) -> a #

diagonal :: Plucker (Plucker a) -> Plucker a #

Trace Quaternion 
Instance details

Defined in Linear.Trace

Trace V0 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => V0 (V0 a) -> a #

diagonal :: V0 (V0 a) -> V0 a #

Trace V1 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => V1 (V1 a) -> a #

diagonal :: V1 (V1 a) -> V1 a #

Trace V2 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => V2 (V2 a) -> a #

diagonal :: V2 (V2 a) -> V2 a #

Trace V3 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => V3 (V3 a) -> a #

diagonal :: V3 (V3 a) -> V3 a #

Trace V4 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => V4 (V4 a) -> a #

diagonal :: V4 (V4 a) -> V4 a #

Ord k => Trace (Map k) 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => Map k (Map k a) -> a #

diagonal :: Map k (Map k a) -> Map k a #

(Eq k, Hashable k) => Trace (HashMap k) 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => HashMap k (HashMap k a) -> a #

diagonal :: HashMap k (HashMap k a) -> HashMap k a #

Dim n => Trace (V n) 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => V n (V n a) -> a #

diagonal :: V n (V n a) -> V n a #

(Trace f, Trace g) => Trace (Product f g) 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => Product f g (Product f g a) -> a #

diagonal :: Product f g (Product f g a) -> Product f g a #

(Distributive g, Trace g, Trace f) => Trace (Compose g f) 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => Compose g f (Compose g f a) -> a #

diagonal :: Compose g f (Compose g f a) -> Compose g f a #

type M44 a = V4 (V4 a) #

A 4x4 matrix with row-major representation

type M43 a = V4 (V3 a) #

A 4x3 matrix with row-major representation

type M42 a = V4 (V2 a) #

A 4x2 matrix with row-major representation

type M34 a = V3 (V4 a) #

A 3x4 matrix with row-major representation

type M33 a = V3 (V3 a) #

A 3x3 matrix with row-major representation

type M32 a = V3 (V2 a) #

A 3x2 matrix with row-major representation

type M24 a = V2 (V4 a) #

A 2x4 matrix with row-major representation

type M23 a = V2 (V3 a) #

A 2x3 matrix with row-major representation

type M22 a = V2 (V2 a) #

A 2x2 matrix with row-major representation

class Num r => Coalgebra r m where #

A coassociative counital coalgebra over a ring

Methods

comult :: (m -> r) -> m -> m -> r #

counital :: (m -> r) -> r #

Instances

Instances details
Num r => Coalgebra r Void 
Instance details

Defined in Linear.Algebra

Methods

comult :: (Void -> r) -> Void -> Void -> r #

counital :: (Void -> r) -> r #

Num r => Coalgebra r () 
Instance details

Defined in Linear.Algebra

Methods

comult :: (() -> r) -> () -> () -> r #

counital :: (() -> r) -> r #

Num r => Coalgebra r (E Complex) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E Complex -> r) -> E Complex -> E Complex -> r #

counital :: (E Complex -> r) -> r #

(Num r, TrivialConjugate r) => Coalgebra r (E Quaternion) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E Quaternion -> r) -> E Quaternion -> E Quaternion -> r #

counital :: (E Quaternion -> r) -> r #

Num r => Coalgebra r (E V0) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V0 -> r) -> E V0 -> E V0 -> r #

counital :: (E V0 -> r) -> r #

Num r => Coalgebra r (E V1) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V1 -> r) -> E V1 -> E V1 -> r #

counital :: (E V1 -> r) -> r #

Num r => Coalgebra r (E V2) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V2 -> r) -> E V2 -> E V2 -> r #

counital :: (E V2 -> r) -> r #

Num r => Coalgebra r (E V3) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V3 -> r) -> E V3 -> E V3 -> r #

counital :: (E V3 -> r) -> r #

Num r => Coalgebra r (E V4) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V4 -> r) -> E V4 -> E V4 -> r #

counital :: (E V4 -> r) -> r #

(Coalgebra r m, Coalgebra r n) => Coalgebra r (m, n) 
Instance details

Defined in Linear.Algebra

Methods

comult :: ((m, n) -> r) -> (m, n) -> (m, n) -> r #

counital :: ((m, n) -> r) -> r #

class Num r => Algebra r m where #

An associative unital algebra over a ring

Methods

mult :: (m -> m -> r) -> m -> r #

unital :: r -> m -> r #

Instances

Instances details
Num r => Algebra r Void 
Instance details

Defined in Linear.Algebra

Methods

mult :: (Void -> Void -> r) -> Void -> r #

unital :: r -> Void -> r #

Num r => Algebra r () 
Instance details

Defined in Linear.Algebra

Methods

mult :: (() -> () -> r) -> () -> r #

unital :: r -> () -> r #

Num r => Algebra r (E Complex) 
Instance details

Defined in Linear.Algebra

Methods

mult :: (E Complex -> E Complex -> r) -> E Complex -> r #

unital :: r -> E Complex -> r #

(Num r, TrivialConjugate r) => Algebra r (E Quaternion) 
Instance details

Defined in Linear.Algebra

Methods

mult :: (E Quaternion -> E Quaternion -> r) -> E Quaternion -> r #

unital :: r -> E Quaternion -> r #

Num r => Algebra r (E V0) 
Instance details

Defined in Linear.Algebra

Methods

mult :: (E V0 -> E V0 -> r) -> E V0 -> r #

unital :: r -> E V0 -> r #

Num r => Algebra r (E V1) 
Instance details

Defined in Linear.Algebra

Methods

mult :: (E V1 -> E V1 -> r) -> E V1 -> r #

unital :: r -> E V1 -> r #

(Algebra r a, Algebra r b) => Algebra r (a, b) 
Instance details

Defined in Linear.Algebra

Methods

mult :: ((a, b) -> (a, b) -> r) -> (a, b) -> r #

unital :: r -> (a, b) -> r #

newtype Covector r a #

Linear functionals from elements of an (infinite) free module to a scalar

Constructors

Covector 

Fields

Instances

Instances details
Num r => Alternative (Covector r) 
Instance details

Defined in Linear.Covector

Methods

empty :: Covector r a #

(<|>) :: Covector r a -> Covector r a -> Covector r a #

some :: Covector r a -> Covector r [a] #

many :: Covector r a -> Covector r [a] #

Applicative (Covector r) 
Instance details

Defined in Linear.Covector

Methods

pure :: a -> Covector r a #

(<*>) :: Covector r (a -> b) -> Covector r a -> Covector r b #

liftA2 :: (a -> b -> c) -> Covector r a -> Covector r b -> Covector r c #

(*>) :: Covector r a -> Covector r b -> Covector r b #

(<*) :: Covector r a -> Covector r b -> Covector r a #

Functor (Covector r) 
Instance details

Defined in Linear.Covector

Methods

fmap :: (a -> b) -> Covector r a -> Covector r b #

(<$) :: a -> Covector r b -> Covector r a #

Monad (Covector r) 
Instance details

Defined in Linear.Covector

Methods

(>>=) :: Covector r a -> (a -> Covector r b) -> Covector r b #

(>>) :: Covector r a -> Covector r b -> Covector r b #

return :: a -> Covector r a #

Num r => MonadPlus (Covector r) 
Instance details

Defined in Linear.Covector

Methods

mzero :: Covector r a #

mplus :: Covector r a -> Covector r a -> Covector r a #

Num r => Alt (Covector r) 
Instance details

Defined in Linear.Covector

Methods

(<!>) :: Covector r a -> Covector r a -> Covector r a #

some :: Applicative (Covector r) => Covector r a -> Covector r [a] #

many :: Applicative (Covector r) => Covector r a -> Covector r [a] #

Apply (Covector r) 
Instance details

Defined in Linear.Covector

Methods

(<.>) :: Covector r (a -> b) -> Covector r a -> Covector r b #

(.>) :: Covector r a -> Covector r b -> Covector r b #

(<.) :: Covector r a -> Covector r b -> Covector r a #

liftF2 :: (a -> b -> c) -> Covector r a -> Covector r b -> Covector r c #

Bind (Covector r) 
Instance details

Defined in Linear.Covector

Methods

(>>-) :: Covector r a -> (a -> Covector r b) -> Covector r b #

join :: Covector r (Covector r a) -> Covector r a #

Num r => Plus (Covector r) 
Instance details

Defined in Linear.Covector

Methods

zero :: Covector r a #

Coalgebra r m => Num (Covector r m) 
Instance details

Defined in Linear.Covector

Methods

(+) :: Covector r m -> Covector r m -> Covector r m #

(-) :: Covector r m -> Covector r m -> Covector r m #

(*) :: Covector r m -> Covector r m -> Covector r m #

negate :: Covector r m -> Covector r m #

abs :: Covector r m -> Covector r m #

signum :: Covector r m -> Covector r m #

fromInteger :: Integer -> Covector r m #

newtype Point (f :: Type -> Type) a #

A handy wrapper to help distinguish points from vectors at the type level

Constructors

P (f a) 

Instances

Instances details
Generic1 (Point f :: Type -> Type) 
Instance details

Defined in Linear.Affine

Associated Types

type Rep1 (Point f) :: k -> Type #

Methods

from1 :: forall (a :: k). Point f a -> Rep1 (Point f) a #

to1 :: forall (a :: k). Rep1 (Point f) a -> Point f a #

Unbox (f a) => Vector Vector (Point f a) 
Instance details

Defined in Linear.Affine

Methods

basicUnsafeFreeze :: Mutable Vector s (Point f a) -> ST s (Vector (Point f a)) #

basicUnsafeThaw :: Vector (Point f a) -> ST s (Mutable Vector s (Point f a)) #

basicLength :: Vector (Point f a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Point f a) -> Vector (Point f a) #

basicUnsafeIndexM :: Vector (Point f a) -> Int -> Box (Point f a) #

basicUnsafeCopy :: Mutable Vector s (Point f a) -> Vector (Point f a) -> ST s () #

elemseq :: Vector (Point f a) -> Point f a -> b -> b #

Unbox (f a) => MVector MVector (Point f a) 
Instance details

Defined in Linear.Affine

Methods

basicLength :: MVector s (Point f a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Point f a) -> MVector s (Point f a) #

basicOverlaps :: MVector s (Point f a) -> MVector s (Point f a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (Point f a)) #

basicInitialize :: MVector s (Point f a) -> ST s () #

basicUnsafeReplicate :: Int -> Point f a -> ST s (MVector s (Point f a)) #

basicUnsafeRead :: MVector s (Point f a) -> Int -> ST s (Point f a) #

basicUnsafeWrite :: MVector s (Point f a) -> Int -> Point f a -> ST s () #

basicClear :: MVector s (Point f a) -> ST s () #

basicSet :: MVector s (Point f a) -> Point f a -> ST s () #

basicUnsafeCopy :: MVector s (Point f a) -> MVector s (Point f a) -> ST s () #

basicUnsafeMove :: MVector s (Point f a) -> MVector s (Point f a) -> ST s () #

basicUnsafeGrow :: MVector s (Point f a) -> Int -> ST s (MVector s (Point f a)) #

Foldable f => Foldable (Point f) 
Instance details

Defined in Linear.Affine

Methods

fold :: Monoid m => Point f m -> m #

foldMap :: Monoid m => (a -> m) -> Point f a -> m #

foldMap' :: Monoid m => (a -> m) -> Point f a -> m #

foldr :: (a -> b -> b) -> b -> Point f a -> b #

foldr' :: (a -> b -> b) -> b -> Point f a -> b #

foldl :: (b -> a -> b) -> b -> Point f a -> b #

foldl' :: (b -> a -> b) -> b -> Point f a -> b #

foldr1 :: (a -> a -> a) -> Point f a -> a #

foldl1 :: (a -> a -> a) -> Point f a -> a #

toList :: Point f a -> [a] #

null :: Point f a -> Bool #

length :: Point f a -> Int #

elem :: Eq a => a -> Point f a -> Bool #

maximum :: Ord a => Point f a -> a #

minimum :: Ord a => Point f a -> a #

sum :: Num a => Point f a -> a #

product :: Num a => Point f a -> a #

Eq1 f => Eq1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

liftEq :: (a -> b -> Bool) -> Point f a -> Point f b -> Bool #

Ord1 f => Ord1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

liftCompare :: (a -> b -> Ordering) -> Point f a -> Point f b -> Ordering #

Read1 f => Read1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Point f a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Point f a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Point f a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Point f a] #

Show1 f => Show1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Point f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Point f a] -> ShowS #

Traversable f => Traversable (Point f) 
Instance details

Defined in Linear.Affine

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Point f a -> f0 (Point f b) #

sequenceA :: Applicative f0 => Point f (f0 a) -> f0 (Point f a) #

mapM :: Monad m => (a -> m b) -> Point f a -> m (Point f b) #

sequence :: Monad m => Point f (m a) -> m (Point f a) #

Applicative f => Applicative (Point f) 
Instance details

Defined in Linear.Affine

Methods

pure :: a -> Point f a #

(<*>) :: Point f (a -> b) -> Point f a -> Point f b #

liftA2 :: (a -> b -> c) -> Point f a -> Point f b -> Point f c #

(*>) :: Point f a -> Point f b -> Point f b #

(<*) :: Point f a -> Point f b -> Point f a #

Functor f => Functor (Point f) 
Instance details

Defined in Linear.Affine

Methods

fmap :: (a -> b) -> Point f a -> Point f b #

(<$) :: a -> Point f b -> Point f a #

Monad f => Monad (Point f) 
Instance details

Defined in Linear.Affine

Methods

(>>=) :: Point f a -> (a -> Point f b) -> Point f b #

(>>) :: Point f a -> Point f b -> Point f b #

return :: a -> Point f a #

Serial1 f => Serial1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

serializeWith :: MonadPut m => (a -> m ()) -> Point f a -> m () #

deserializeWith :: MonadGet m => m a -> m (Point f a) #

Representable f => Representable (Point f) 
Instance details

Defined in Linear.Affine

Associated Types

type Rep (Point f) #

Methods

tabulate :: (Rep (Point f) -> a) -> Point f a #

index :: Point f a -> Rep (Point f) -> a #

Distributive f => Distributive (Point f) 
Instance details

Defined in Linear.Affine

Methods

distribute :: Functor f0 => f0 (Point f a) -> Point f (f0 a) #

collect :: Functor f0 => (a -> Point f b) -> f0 a -> Point f (f0 b) #

distributeM :: Monad m => m (Point f a) -> Point f (m a) #

collectM :: Monad m => (a -> Point f b) -> m a -> Point f (m b) #

Hashable1 f => Hashable1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Point f a -> Int #

Additive f => Affine (Point f) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff (Point f) :: Type -> Type #

Methods

(.-.) :: Num a => Point f a -> Point f a -> Diff (Point f) a #

(.+^) :: Num a => Point f a -> Diff (Point f) a -> Point f a #

(.-^) :: Num a => Point f a -> Diff (Point f) a -> Point f a #

Metric f => Metric (Point f) 
Instance details

Defined in Linear.Affine

Methods

dot :: Num a => Point f a -> Point f a -> a #

quadrance :: Num a => Point f a -> a #

qd :: Num a => Point f a -> Point f a -> a #

distance :: Floating a => Point f a -> Point f a -> a #

norm :: Floating a => Point f a -> a #

signorm :: Floating a => Point f a -> Point f a #

Finite f => Finite (Point f) 
Instance details

Defined in Linear.Affine

Associated Types

type Size (Point f) :: Nat #

Methods

toV :: Point f a -> V (Size (Point f)) a #

fromV :: V (Size (Point f)) a -> Point f a #

R1 f => R1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

_x :: Lens' (Point f a) a #

R2 f => R2 (Point f) 
Instance details

Defined in Linear.Affine

Methods

_y :: Lens' (Point f a) a #

_xy :: Lens' (Point f a) (V2 a) #

R3 f => R3 (Point f) 
Instance details

Defined in Linear.Affine

Methods

_z :: Lens' (Point f a) a #

_xyz :: Lens' (Point f a) (V3 a) #

R4 f => R4 (Point f) 
Instance details

Defined in Linear.Affine

Methods

_w :: Lens' (Point f a) a #

_xyzw :: Lens' (Point f a) (V4 a) #

Additive f => Additive (Point f) 
Instance details

Defined in Linear.Affine

Methods

zero :: Num a => Point f a #

(^+^) :: Num a => Point f a -> Point f a -> Point f a #

(^-^) :: Num a => Point f a -> Point f a -> Point f a #

lerp :: Num a => a -> Point f a -> Point f a -> Point f a #

liftU2 :: (a -> a -> a) -> Point f a -> Point f a -> Point f a #

liftI2 :: (a -> b -> c) -> Point f a -> Point f b -> Point f c #

Apply f => Apply (Point f) 
Instance details

Defined in Linear.Affine

Methods

(<.>) :: Point f (a -> b) -> Point f a -> Point f b #

(.>) :: Point f a -> Point f b -> Point f b #

(<.) :: Point f a -> Point f b -> Point f a #

liftF2 :: (a -> b -> c) -> Point f a -> Point f b -> Point f c #

Bind f => Bind (Point f) 
Instance details

Defined in Linear.Affine

Methods

(>>-) :: Point f a -> (a -> Point f b) -> Point f b #

join :: Point f (Point f a) -> Point f a #

(Typeable f, Typeable a, Data (f a)) => Data (Point f a) 
Instance details

Defined in Linear.Affine

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Point f a -> c (Point f a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Point f a) #

toConstr :: Point f a -> Constr #

dataTypeOf :: Point f a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Point f a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Point f a)) #

gmapT :: (forall b. Data b => b -> b) -> Point f a -> Point f a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Point f a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Point f a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Point f a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Point f a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a) #

Storable (f a) => Storable (Point f a) 
Instance details

Defined in Linear.Affine

Methods

sizeOf :: Point f a -> Int #

alignment :: Point f a -> Int #

peekElemOff :: Ptr (Point f a) -> Int -> IO (Point f a) #

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

peekByteOff :: Ptr b -> Int -> IO (Point f a) #

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

peek :: Ptr (Point f a) -> IO (Point f a) #

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

Monoid (f a) => Monoid (Point f a) 
Instance details

Defined in Linear.Affine

Methods

mempty :: Point f a #

mappend :: Point f a -> Point f a -> Point f a #

mconcat :: [Point f a] -> Point f a #

Semigroup (f a) => Semigroup (Point f a) 
Instance details

Defined in Linear.Affine

Methods

(<>) :: Point f a -> Point f a -> Point f a #

sconcat :: NonEmpty (Point f a) -> Point f a #

stimes :: Integral b => b -> Point f a -> Point f a #

Generic (Point f a) 
Instance details

Defined in Linear.Affine

Associated Types

type Rep (Point f a) :: Type -> Type #

Methods

from :: Point f a -> Rep (Point f a) x #

to :: Rep (Point f a) x -> Point f a #

Ix (f a) => Ix (Point f a) 
Instance details

Defined in Linear.Affine

Methods

range :: (Point f a, Point f a) -> [Point f a] #

index :: (Point f a, Point f a) -> Point f a -> Int #

unsafeIndex :: (Point f a, Point f a) -> Point f a -> Int #

inRange :: (Point f a, Point f a) -> Point f a -> Bool #

rangeSize :: (Point f a, Point f a) -> Int #

unsafeRangeSize :: (Point f a, Point f a) -> Int #

Num (f a) => Num (Point f a) 
Instance details

Defined in Linear.Affine

Methods

(+) :: Point f a -> Point f a -> Point f a #

(-) :: Point f a -> Point f a -> Point f a #

(*) :: Point f a -> Point f a -> Point f a #

negate :: Point f a -> Point f a #

abs :: Point f a -> Point f a #

signum :: Point f a -> Point f a #

fromInteger :: Integer -> Point f a #

Read (f a) => Read (Point f a) 
Instance details

Defined in Linear.Affine

Fractional (f a) => Fractional (Point f a) 
Instance details

Defined in Linear.Affine

Methods

(/) :: Point f a -> Point f a -> Point f a #

recip :: Point f a -> Point f a #

fromRational :: Rational -> Point f a #

Show (f a) => Show (Point f a) 
Instance details

Defined in Linear.Affine

Methods

showsPrec :: Int -> Point f a -> ShowS #

show :: Point f a -> String #

showList :: [Point f a] -> ShowS #

Binary (f a) => Binary (Point f a) 
Instance details

Defined in Linear.Affine

Methods

put :: Point f a -> Put #

get :: Get (Point f a) #

putList :: [Point f a] -> Put #

Serial (f a) => Serial (Point f a) 
Instance details

Defined in Linear.Affine

Methods

serialize :: MonadPut m => Point f a -> m () #

deserialize :: MonadGet m => m (Point f a) #

Serialize (f a) => Serialize (Point f a) 
Instance details

Defined in Linear.Affine

Methods

put :: Putter (Point f a) #

get :: Get (Point f a) #

NFData (f a) => NFData (Point f a) 
Instance details

Defined in Linear.Affine

Methods

rnf :: Point f a -> () #

Eq (f a) => Eq (Point f a) 
Instance details

Defined in Linear.Affine

Methods

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

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

Ord (f a) => Ord (Point f a) 
Instance details

Defined in Linear.Affine

Methods

compare :: Point f a -> Point f a -> Ordering #

(<) :: Point f a -> Point f a -> Bool #

(<=) :: Point f a -> Point f a -> Bool #

(>) :: Point f a -> Point f a -> Bool #

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

max :: Point f a -> Point f a -> Point f a #

min :: Point f a -> Point f a -> Point f a #

Hashable (f a) => Hashable (Point f a) 
Instance details

Defined in Linear.Affine

Methods

hashWithSalt :: Int -> Point f a -> Int #

hash :: Point f a -> Int #

Epsilon (f a) => Epsilon (Point f a) 
Instance details

Defined in Linear.Affine

Methods

nearZero :: Point f a -> Bool #

Ixed (f a) => Ixed (Point f a) 
Instance details

Defined in Linear.Affine

Methods

ix :: Index (Point f a) -> Traversal' (Point f a) (IxValue (Point f a)) #

Wrapped (Point f a) 
Instance details

Defined in Linear.Affine

Associated Types

type Unwrapped (Point f a) #

Methods

_Wrapped' :: Iso' (Point f a) (Unwrapped (Point f a)) #

Random (f a) => Random (Point f a) 
Instance details

Defined in Linear.Affine

Methods

randomR :: RandomGen g => (Point f a, Point f a) -> g -> (Point f a, g) #

random :: RandomGen g => g -> (Point f a, g) #

randomRs :: RandomGen g => (Point f a, Point f a) -> g -> [Point f a] #

randoms :: RandomGen g => g -> [Point f a] #

Unbox (f a) => Unbox (Point f a) 
Instance details

Defined in Linear.Affine

t ~ Point g b => Rewrapped (Point f a) t 
Instance details

Defined in Linear.Affine

Traversable f => Each (Point f a) (Point f b) a b 
Instance details

Defined in Linear.Affine

Methods

each :: Traversal (Point f a) (Point f b) a b #

type Rep1 (Point f :: Type -> Type) 
Instance details

Defined in Linear.Affine

type Rep1 (Point f :: Type -> Type) = D1 ('MetaData "Point" "Linear.Affine" "lnr-1.22-7520e77e" 'True) (C1 ('MetaCons "P" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 f)))
newtype MVector s (Point f a) 
Instance details

Defined in Linear.Affine

newtype MVector s (Point f a) = MV_P (MVector s (f a))
type Rep (Point f) 
Instance details

Defined in Linear.Affine

type Rep (Point f) = Rep f
type Diff (Point f) 
Instance details

Defined in Linear.Affine

type Diff (Point f) = f
type Size (Point f) 
Instance details

Defined in Linear.Affine

type Size (Point f) = Size f
type Rep (Point f a) 
Instance details

Defined in Linear.Affine

type Rep (Point f a) = D1 ('MetaData "Point" "Linear.Affine" "lnr-1.22-7520e77e" 'True) (C1 ('MetaCons "P" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a))))
type Index (Point f a) 
Instance details

Defined in Linear.Affine

type Index (Point f a) = Index (f a)
type IxValue (Point f a) 
Instance details

Defined in Linear.Affine

type IxValue (Point f a) = IxValue (f a)
type Unwrapped (Point f a) 
Instance details

Defined in Linear.Affine

type Unwrapped (Point f a) = f a
newtype Vector (Point f a) 
Instance details

Defined in Linear.Affine

newtype Vector (Point f a) = V_P (Vector (f a))

class Additive (Diff p) => Affine (p :: Type -> Type) where #

An affine space is roughly a vector space in which we have forgotten or at least pretend to have forgotten the origin.

a .+^ (b .-. a)  =  b@
(a .+^ u) .+^ v  =  a .+^ (u ^+^ v)@
(a .-. b) ^+^ v  =  (a .+^ v) .-. q@

Minimal complete definition

(.-.), (.+^)

Associated Types

type Diff (p :: Type -> Type) :: Type -> Type #

Methods

(.-.) :: Num a => p a -> p a -> Diff p a infixl 6 #

Get the difference between two points as a vector offset.

(.+^) :: Num a => p a -> Diff p a -> p a infixl 6 #

Add a vector offset to a point.

(.-^) :: Num a => p a -> Diff p a -> p a infixl 6 #

Subtract a vector offset from a point.

Instances

Instances details
Affine ZipList 
Instance details

Defined in Linear.Affine

Associated Types

type Diff ZipList :: Type -> Type #

Methods

(.-.) :: Num a => ZipList a -> ZipList a -> Diff ZipList a #

(.+^) :: Num a => ZipList a -> Diff ZipList a -> ZipList a #

(.-^) :: Num a => ZipList a -> Diff ZipList a -> ZipList a #

Affine Complex 
Instance details

Defined in Linear.Affine

Associated Types

type Diff Complex :: Type -> Type #

Methods

(.-.) :: Num a => Complex a -> Complex a -> Diff Complex a #

(.+^) :: Num a => Complex a -> Diff Complex a -> Complex a #

(.-^) :: Num a => Complex a -> Diff Complex a -> Complex a #

Affine Identity 
Instance details

Defined in Linear.Affine

Associated Types

type Diff Identity :: Type -> Type #

Methods

(.-.) :: Num a => Identity a -> Identity a -> Diff Identity a #

(.+^) :: Num a => Identity a -> Diff Identity a -> Identity a #

(.-^) :: Num a => Identity a -> Diff Identity a -> Identity a #

Affine IntMap 
Instance details

Defined in Linear.Affine

Associated Types

type Diff IntMap :: Type -> Type #

Methods

(.-.) :: Num a => IntMap a -> IntMap a -> Diff IntMap a #

(.+^) :: Num a => IntMap a -> Diff IntMap a -> IntMap a #

(.-^) :: Num a => IntMap a -> Diff IntMap a -> IntMap a #

Affine Plucker 
Instance details

Defined in Linear.Affine

Associated Types

type Diff Plucker :: Type -> Type #

Methods

(.-.) :: Num a => Plucker a -> Plucker a -> Diff Plucker a #

(.+^) :: Num a => Plucker a -> Diff Plucker a -> Plucker a #

(.-^) :: Num a => Plucker a -> Diff Plucker a -> Plucker a #

Affine Quaternion 
Instance details

Defined in Linear.Affine

Associated Types

type Diff Quaternion :: Type -> Type #

Affine V0 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V0 :: Type -> Type #

Methods

(.-.) :: Num a => V0 a -> V0 a -> Diff V0 a #

(.+^) :: Num a => V0 a -> Diff V0 a -> V0 a #

(.-^) :: Num a => V0 a -> Diff V0 a -> V0 a #

Affine V1 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V1 :: Type -> Type #

Methods

(.-.) :: Num a => V1 a -> V1 a -> Diff V1 a #

(.+^) :: Num a => V1 a -> Diff V1 a -> V1 a #

(.-^) :: Num a => V1 a -> Diff V1 a -> V1 a #

Affine V2 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V2 :: Type -> Type #

Methods

(.-.) :: Num a => V2 a -> V2 a -> Diff V2 a #

(.+^) :: Num a => V2 a -> Diff V2 a -> V2 a #

(.-^) :: Num a => V2 a -> Diff V2 a -> V2 a #

Affine V3 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V3 :: Type -> Type #

Methods

(.-.) :: Num a => V3 a -> V3 a -> Diff V3 a #

(.+^) :: Num a => V3 a -> Diff V3 a -> V3 a #

(.-^) :: Num a => V3 a -> Diff V3 a -> V3 a #

Affine V4 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V4 :: Type -> Type #

Methods

(.-.) :: Num a => V4 a -> V4 a -> Diff V4 a #

(.+^) :: Num a => V4 a -> Diff V4 a -> V4 a #

(.-^) :: Num a => V4 a -> Diff V4 a -> V4 a #

Affine Vector 
Instance details

Defined in Linear.Affine

Associated Types

type Diff Vector :: Type -> Type #

Methods

(.-.) :: Num a => Vector a -> Vector a -> Diff Vector a #

(.+^) :: Num a => Vector a -> Diff Vector a -> Vector a #

(.-^) :: Num a => Vector a -> Diff Vector a -> Vector a #

Affine Maybe 
Instance details

Defined in Linear.Affine

Associated Types

type Diff Maybe :: Type -> Type #

Methods

(.-.) :: Num a => Maybe a -> Maybe a -> Diff Maybe a #

(.+^) :: Num a => Maybe a -> Diff Maybe a -> Maybe a #

(.-^) :: Num a => Maybe a -> Diff Maybe a -> Maybe a #

Affine [] 
Instance details

Defined in Linear.Affine

Associated Types

type Diff [] :: Type -> Type #

Methods

(.-.) :: Num a => [a] -> [a] -> Diff [] a #

(.+^) :: Num a => [a] -> Diff [] a -> [a] #

(.-^) :: Num a => [a] -> Diff [] a -> [a] #

Ord k => Affine (Map k) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff (Map k) :: Type -> Type #

Methods

(.-.) :: Num a => Map k a -> Map k a -> Diff (Map k) a #

(.+^) :: Num a => Map k a -> Diff (Map k) a -> Map k a #

(.-^) :: Num a => Map k a -> Diff (Map k) a -> Map k a #

Additive f => Affine (Point f) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff (Point f) :: Type -> Type #

Methods

(.-.) :: Num a => Point f a -> Point f a -> Diff (Point f) a #

(.+^) :: Num a => Point f a -> Diff (Point f) a -> Point f a #

(.-^) :: Num a => Point f a -> Diff (Point f) a -> Point f a #

(Eq k, Hashable k) => Affine (HashMap k) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff (HashMap k) :: Type -> Type #

Methods

(.-.) :: Num a => HashMap k a -> HashMap k a -> Diff (HashMap k) a #

(.+^) :: Num a => HashMap k a -> Diff (HashMap k) a -> HashMap k a #

(.-^) :: Num a => HashMap k a -> Diff (HashMap k) a -> HashMap k a #

Dim n => Affine (V n) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff (V n) :: Type -> Type #

Methods

(.-.) :: Num a => V n a -> V n a -> Diff (V n) a #

(.+^) :: Num a => V n a -> Diff (V n) a -> V n a #

(.-^) :: Num a => V n a -> Diff (V n) a -> V n a #

(Affine f, Affine g) => Affine (Product f g) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff (Product f g) :: Type -> Type #

Methods

(.-.) :: Num a => Product f g a -> Product f g a -> Diff (Product f g) a #

(.+^) :: Num a => Product f g a -> Diff (Product f g) a -> Product f g a #

(.-^) :: Num a => Product f g a -> Diff (Product f g) a -> Product f g a #

Affine ((->) b) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff ((->) b) :: Type -> Type #

Methods

(.-.) :: Num a => (b -> a) -> (b -> a) -> Diff ((->) b) a #

(.+^) :: Num a => (b -> a) -> Diff ((->) b) a -> b -> a #

(.-^) :: Num a => (b -> a) -> Diff ((->) b) a -> b -> a #

type family Diff (p :: Type -> Type) :: Type -> Type #

Instances

Instances details
type Diff ZipList 
Instance details

Defined in Linear.Affine

type Diff Complex 
Instance details

Defined in Linear.Affine

type Diff Identity 
Instance details

Defined in Linear.Affine

type Diff IntMap 
Instance details

Defined in Linear.Affine

type Diff Plucker 
Instance details

Defined in Linear.Affine

type Diff Quaternion 
Instance details

Defined in Linear.Affine

type Diff V0 
Instance details

Defined in Linear.Affine

type Diff V0 = V0
type Diff V1 
Instance details

Defined in Linear.Affine

type Diff V1 = V1
type Diff V2 
Instance details

Defined in Linear.Affine

type Diff V2 = V2
type Diff V3 
Instance details

Defined in Linear.Affine

type Diff V3 = V3
type Diff V4 
Instance details

Defined in Linear.Affine

type Diff V4 = V4
type Diff Vector 
Instance details

Defined in Linear.Affine

type Diff Maybe 
Instance details

Defined in Linear.Affine

type Diff [] 
Instance details

Defined in Linear.Affine

type Diff [] = []
type Diff (Map k) 
Instance details

Defined in Linear.Affine

type Diff (Map k) = Map k
type Diff (Point f) 
Instance details

Defined in Linear.Affine

type Diff (Point f) = f
type Diff (HashMap k) 
Instance details

Defined in Linear.Affine

type Diff (HashMap k) = HashMap k
type Diff (V n) 
Instance details

Defined in Linear.Affine

type Diff (V n) = V n
type Diff (Product f g) 
Instance details

Defined in Linear.Affine

type Diff (Product f g) = Product (Diff f) (Diff g)
type Diff ((->) b) 
Instance details

Defined in Linear.Affine

type Diff ((->) b) = (->) b

data family Vector a #

Instances

Instances details
NFData1 Vector

Since: vector-0.12.1.0

Instance details

Defined in Data.Vector.Unboxed.Base

Methods

liftRnf :: (a -> ()) -> Vector a -> () #

Vector Vector All 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Any 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector () 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: Mutable Vector s () -> ST s (Vector ()) #

basicUnsafeThaw :: Vector () -> ST s (Mutable Vector s ()) #

basicLength :: Vector () -> Int #

basicUnsafeSlice :: Int -> Int -> Vector () -> Vector () #

basicUnsafeIndexM :: Vector () -> Int -> Box () #

basicUnsafeCopy :: Mutable Vector s () -> Vector () -> ST s () #

elemseq :: Vector () -> () -> b -> b #

Vector Vector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Char 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Double 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Float 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Int 
Instance details

Defined in Data.Vector.Unboxed.Base

Vector Vector Word 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Vector Vector (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Vector Vector (Identity a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Vector Vector (Down a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: Mutable Vector s (Down a) -> ST s (Vector (Down a)) #

basicUnsafeThaw :: Vector (Down a) -> ST s (Mutable Vector s (Down a)) #

basicLength :: Vector (Down a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Down a) -> Vector (Down a) #

basicUnsafeIndexM :: Vector (Down a) -> Int -> Box (Down a) #

basicUnsafeCopy :: Mutable Vector s (Down a) -> Vector (Down a) -> ST s () #

elemseq :: Vector (Down a) -> Down a -> b -> b #

Unbox a => Vector Vector (First a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Vector Vector (Last a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: Mutable Vector s (Last a) -> ST s (Vector (Last a)) #

basicUnsafeThaw :: Vector (Last a) -> ST s (Mutable Vector s (Last a)) #

basicLength :: Vector (Last a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Last a) -> Vector (Last a) #

basicUnsafeIndexM :: Vector (Last a) -> Int -> Box (Last a) #

basicUnsafeCopy :: Mutable Vector s (Last a) -> Vector (Last a) -> ST s () #

elemseq :: Vector (Last a) -> Last a -> b -> b #

Unbox a => Vector Vector (Max a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: Mutable Vector s (Max a) -> ST s (Vector (Max a)) #

basicUnsafeThaw :: Vector (Max a) -> ST s (Mutable Vector s (Max a)) #

basicLength :: Vector (Max a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Max a) -> Vector (Max a) #

basicUnsafeIndexM :: Vector (Max a) -> Int -> Box (Max a) #

basicUnsafeCopy :: Mutable Vector s (Max a) -> Vector (Max a) -> ST s () #

elemseq :: Vector (Max a) -> Max a -> b -> b #

Unbox a => Vector Vector (Min a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: Mutable Vector s (Min a) -> ST s (Vector (Min a)) #

basicUnsafeThaw :: Vector (Min a) -> ST s (Mutable Vector s (Min a)) #

basicLength :: Vector (Min a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Min a) -> Vector (Min a) #

basicUnsafeIndexM :: Vector (Min a) -> Int -> Box (Min a) #

basicUnsafeCopy :: Mutable Vector s (Min a) -> Vector (Min a) -> ST s () #

elemseq :: Vector (Min a) -> Min a -> b -> b #

Unbox a => Vector Vector (WrappedMonoid a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Vector Vector (Dual a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: Mutable Vector s (Dual a) -> ST s (Vector (Dual a)) #

basicUnsafeThaw :: Vector (Dual a) -> ST s (Mutable Vector s (Dual a)) #

basicLength :: Vector (Dual a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Dual a) -> Vector (Dual a) #

basicUnsafeIndexM :: Vector (Dual a) -> Int -> Box (Dual a) #

basicUnsafeCopy :: Mutable Vector s (Dual a) -> Vector (Dual a) -> ST s () #

elemseq :: Vector (Dual a) -> Dual a -> b -> b #

Unbox a => Vector Vector (Product a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Vector Vector (Sum a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: Mutable Vector s (Sum a) -> ST s (Vector (Sum a)) #

basicUnsafeThaw :: Vector (Sum a) -> ST s (Mutable Vector s (Sum a)) #

basicLength :: Vector (Sum a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Sum a) -> Vector (Sum a) #

basicUnsafeIndexM :: Vector (Sum a) -> Int -> Box (Sum a) #

basicUnsafeCopy :: Mutable Vector s (Sum a) -> Vector (Sum a) -> ST s () #

elemseq :: Vector (Sum a) -> Sum a -> b -> b #

Unbox a => Vector Vector (Plucker a) 
Instance details

Defined in Linear.Plucker

Unbox a => Vector Vector (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Vector Vector (V0 a) 
Instance details

Defined in Linear.V0

Methods

basicUnsafeFreeze :: Mutable Vector s (V0 a) -> ST s (Vector (V0 a)) #

basicUnsafeThaw :: Vector (V0 a) -> ST s (Mutable Vector s (V0 a)) #

basicLength :: Vector (V0 a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V0 a) -> Vector (V0 a) #

basicUnsafeIndexM :: Vector (V0 a) -> Int -> Box (V0 a) #

basicUnsafeCopy :: Mutable Vector s (V0 a) -> Vector (V0 a) -> ST s () #

elemseq :: Vector (V0 a) -> V0 a -> b -> b #

Unbox a => Vector Vector (V1 a) 
Instance details

Defined in Linear.V1

Methods

basicUnsafeFreeze :: Mutable Vector s (V1 a) -> ST s (Vector (V1 a)) #

basicUnsafeThaw :: Vector (V1 a) -> ST s (Mutable Vector s (V1 a)) #

basicLength :: Vector (V1 a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V1 a) -> Vector (V1 a) #

basicUnsafeIndexM :: Vector (V1 a) -> Int -> Box (V1 a) #

basicUnsafeCopy :: Mutable Vector s (V1 a) -> Vector (V1 a) -> ST s () #

elemseq :: Vector (V1 a) -> V1 a -> b -> b #

Unbox a => Vector Vector (V2 a) 
Instance details

Defined in Linear.V2

Methods

basicUnsafeFreeze :: Mutable Vector s (V2 a) -> ST s (Vector (V2 a)) #

basicUnsafeThaw :: Vector (V2 a) -> ST s (Mutable Vector s (V2 a)) #

basicLength :: Vector (V2 a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V2 a) -> Vector (V2 a) #

basicUnsafeIndexM :: Vector (V2 a) -> Int -> Box (V2 a) #

basicUnsafeCopy :: Mutable Vector s (V2 a) -> Vector (V2 a) -> ST s () #

elemseq :: Vector (V2 a) -> V2 a -> b -> b #

Unbox a => Vector Vector (V3 a) 
Instance details

Defined in Linear.V3

Methods

basicUnsafeFreeze :: Mutable Vector s (V3 a) -> ST s (Vector (V3 a)) #

basicUnsafeThaw :: Vector (V3 a) -> ST s (Mutable Vector s (V3 a)) #

basicLength :: Vector (V3 a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V3 a) -> Vector (V3 a) #

basicUnsafeIndexM :: Vector (V3 a) -> Int -> Box (V3 a) #

basicUnsafeCopy :: Mutable Vector s (V3 a) -> Vector (V3 a) -> ST s () #

elemseq :: Vector (V3 a) -> V3 a -> b -> b #

Unbox a => Vector Vector (V4 a) 
Instance details

Defined in Linear.V4

Methods

basicUnsafeFreeze :: Mutable Vector s (V4 a) -> ST s (Vector (V4 a)) #

basicUnsafeThaw :: Vector (V4 a) -> ST s (Mutable Vector s (V4 a)) #

basicLength :: Vector (V4 a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V4 a) -> Vector (V4 a) #

basicUnsafeIndexM :: Vector (V4 a) -> Int -> Box (V4 a) #

basicUnsafeCopy :: Mutable Vector s (V4 a) -> Vector (V4 a) -> ST s () #

elemseq :: Vector (V4 a) -> V4 a -> b -> b #

Prim a => Vector Vector (UnboxViaPrim a) 
Instance details

Defined in Data.Vector.Unboxed.Base

(Unbox a, Unbox b) => Vector Vector (Arg a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: Mutable Vector s (Arg a b) -> ST s (Vector (Arg a b)) #

basicUnsafeThaw :: Vector (Arg a b) -> ST s (Mutable Vector s (Arg a b)) #

basicLength :: Vector (Arg a b) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Arg a b) -> Vector (Arg a b) #

basicUnsafeIndexM :: Vector (Arg a b) -> Int -> Box (Arg a b) #

basicUnsafeCopy :: Mutable Vector s (Arg a b) -> Vector (Arg a b) -> ST s () #

elemseq :: Vector (Arg a b) -> Arg a b -> b0 -> b0 #

Unbox (f a) => Vector Vector (Point f a) 
Instance details

Defined in Linear.Affine

Methods

basicUnsafeFreeze :: Mutable Vector s (Point f a) -> ST s (Vector (Point f a)) #

basicUnsafeThaw :: Vector (Point f a) -> ST s (Mutable Vector s (Point f a)) #

basicLength :: Vector (Point f a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Point f a) -> Vector (Point f a) #

basicUnsafeIndexM :: Vector (Point f a) -> Int -> Box (Point f a) #

basicUnsafeCopy :: Mutable Vector s (Point f a) -> Vector (Point f a) -> ST s () #

elemseq :: Vector (Point f a) -> Point f a -> b -> b #

(IsoUnbox a b, Unbox b) => Vector Vector (As a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: Mutable Vector s (As a b) -> ST s (Vector (As a b)) #

basicUnsafeThaw :: Vector (As a b) -> ST s (Mutable Vector s (As a b)) #

basicLength :: Vector (As a b) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (As a b) -> Vector (As a b) #

basicUnsafeIndexM :: Vector (As a b) -> Int -> Box (As a b) #

basicUnsafeCopy :: Mutable Vector s (As a b) -> Vector (As a b) -> ST s () #

elemseq :: Vector (As a b) -> As a b -> b0 -> b0 #

(Unbox a, Unbox b) => Vector Vector (a, b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: Mutable Vector s (a, b) -> ST s (Vector (a, b)) #

basicUnsafeThaw :: Vector (a, b) -> ST s (Mutable Vector s (a, b)) #

basicLength :: Vector (a, b) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (a, b) -> Vector (a, b) #

basicUnsafeIndexM :: Vector (a, b) -> Int -> Box (a, b) #

basicUnsafeCopy :: Mutable Vector s (a, b) -> Vector (a, b) -> ST s () #

elemseq :: Vector (a, b) -> (a, b) -> b0 -> b0 #

Unbox a => Vector Vector (Const a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: Mutable Vector s (Const a b) -> ST s (Vector (Const a b)) #

basicUnsafeThaw :: Vector (Const a b) -> ST s (Mutable Vector s (Const a b)) #

basicLength :: Vector (Const a b) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Const a b) -> Vector (Const a b) #

basicUnsafeIndexM :: Vector (Const a b) -> Int -> Box (Const a b) #

basicUnsafeCopy :: Mutable Vector s (Const a b) -> Vector (Const a b) -> ST s () #

elemseq :: Vector (Const a b) -> Const a b -> b0 -> b0 #

Unbox (f a) => Vector Vector (Alt f a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: Mutable Vector s (Alt f a) -> ST s (Vector (Alt f a)) #

basicUnsafeThaw :: Vector (Alt f a) -> ST s (Mutable Vector s (Alt f a)) #

basicLength :: Vector (Alt f a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Alt f a) -> Vector (Alt f a) #

basicUnsafeIndexM :: Vector (Alt f a) -> Int -> Box (Alt f a) #

basicUnsafeCopy :: Mutable Vector s (Alt f a) -> Vector (Alt f a) -> ST s () #

elemseq :: Vector (Alt f a) -> Alt f a -> b -> b #

(Dim n, Unbox a) => Vector Vector (V n a) 
Instance details

Defined in Linear.V

Methods

basicUnsafeFreeze :: Mutable Vector s (V n a) -> ST s (Vector (V n a)) #

basicUnsafeThaw :: Vector (V n a) -> ST s (Mutable Vector s (V n a)) #

basicLength :: Vector (V n a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V n a) -> Vector (V n a) #

basicUnsafeIndexM :: Vector (V n a) -> Int -> Box (V n a) #

basicUnsafeCopy :: Mutable Vector s (V n a) -> Vector (V n a) -> ST s () #

elemseq :: Vector (V n a) -> V n a -> b -> b #

(Unbox a, Unbox b, Unbox c) => Vector Vector (a, b, c) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: Mutable Vector s (a, b, c) -> ST s (Vector (a, b, c)) #

basicUnsafeThaw :: Vector (a, b, c) -> ST s (Mutable Vector s (a, b, c)) #

basicLength :: Vector (a, b, c) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (a, b, c) -> Vector (a, b, c) #

basicUnsafeIndexM :: Vector (a, b, c) -> Int -> Box (a, b, c) #

basicUnsafeCopy :: Mutable Vector s (a, b, c) -> Vector (a, b, c) -> ST s () #

elemseq :: Vector (a, b, c) -> (a, b, c) -> b0 -> b0 #

(Unbox a, Unbox b, Unbox c, Unbox d) => Vector Vector (a, b, c, d) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: Mutable Vector s (a, b, c, d) -> ST s (Vector (a, b, c, d)) #

basicUnsafeThaw :: Vector (a, b, c, d) -> ST s (Mutable Vector s (a, b, c, d)) #

basicLength :: Vector (a, b, c, d) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (a, b, c, d) -> Vector (a, b, c, d) #

basicUnsafeIndexM :: Vector (a, b, c, d) -> Int -> Box (a, b, c, d) #

basicUnsafeCopy :: Mutable Vector s (a, b, c, d) -> Vector (a, b, c, d) -> ST s () #

elemseq :: Vector (a, b, c, d) -> (a, b, c, d) -> b0 -> b0 #

Unbox (f (g a)) => Vector Vector (Compose f g a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: Mutable Vector s (Compose f g a) -> ST s (Vector (Compose f g a)) #

basicUnsafeThaw :: Vector (Compose f g a) -> ST s (Mutable Vector s (Compose f g a)) #

basicLength :: Vector (Compose f g a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Compose f g a) -> Vector (Compose f g a) #

basicUnsafeIndexM :: Vector (Compose f g a) -> Int -> Box (Compose f g a) #

basicUnsafeCopy :: Mutable Vector s (Compose f g a) -> Vector (Compose f g a) -> ST s () #

elemseq :: Vector (Compose f g a) -> Compose f g a -> b -> b #

(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => Vector Vector (a, b, c, d, e) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: Mutable Vector s (a, b, c, d, e) -> ST s (Vector (a, b, c, d, e)) #

basicUnsafeThaw :: Vector (a, b, c, d, e) -> ST s (Mutable Vector s (a, b, c, d, e)) #

basicLength :: Vector (a, b, c, d, e) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (a, b, c, d, e) -> Vector (a, b, c, d, e) #

basicUnsafeIndexM :: Vector (a, b, c, d, e) -> Int -> Box (a, b, c, d, e) #

basicUnsafeCopy :: Mutable Vector s (a, b, c, d, e) -> Vector (a, b, c, d, e) -> ST s () #

elemseq :: Vector (a, b, c, d, e) -> (a, b, c, d, e) -> b0 -> b0 #

(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => Vector Vector (a, b, c, d, e, f) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: Mutable Vector s (a, b, c, d, e, f) -> ST s (Vector (a, b, c, d, e, f)) #

basicUnsafeThaw :: Vector (a, b, c, d, e, f) -> ST s (Mutable Vector s (a, b, c, d, e, f)) #

basicLength :: Vector (a, b, c, d, e, f) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (a, b, c, d, e, f) -> Vector (a, b, c, d, e, f) #

basicUnsafeIndexM :: Vector (a, b, c, d, e, f) -> Int -> Box (a, b, c, d, e, f) #

basicUnsafeCopy :: Mutable Vector s (a, b, c, d, e, f) -> Vector (a, b, c, d, e, f) -> ST s () #

elemseq :: Vector (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> b0 -> b0 #

(Data a, Unbox a) => Data (Vector a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vector a -> c (Vector a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Vector a) #

toConstr :: Vector a -> Constr #

dataTypeOf :: Vector a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Vector a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Vector a)) #

gmapT :: (forall b. Data b => b -> b) -> Vector a -> Vector a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Vector a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Vector a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) #

NFData (Vector a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

rnf :: Vector a -> () #

Unbox a => Ixed (Vector a) 
Instance details

Defined in Control.Lens.At

Methods

ix :: Index (Vector a) -> Traversal' (Vector a) (IxValue (Vector a)) #

Unbox a => Wrapped (Vector a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Vector a) #

Methods

_Wrapped' :: Iso' (Vector a) (Unwrapped (Vector a)) #

(Unbox a, t ~ Vector a') => Rewrapped (Vector a) t 
Instance details

Defined in Control.Lens.Wrapped

type Mutable Vector 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector All 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector All = V_All (Vector Bool)
newtype Vector Any 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Any = V_Any (Vector Bool)
newtype Vector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector () 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector () = V_Unit Int
newtype Vector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Char 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Double 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Float 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int = V_Int (Vector Int)
newtype Vector Word 
Instance details

Defined in Data.Vector.Unboxed.Base

type Item (Vector e) 
Instance details

Defined in Data.Vector.Unboxed

type Item (Vector e) = e
type Index (Vector a) 
Instance details

Defined in Control.Lens.At

type Index (Vector a) = Int
type IxValue (Vector a) 
Instance details

Defined in Control.Lens.At

type IxValue (Vector a) = a
type Unwrapped (Vector a) 
Instance details

Defined in Control.Lens.Wrapped

type Unwrapped (Vector a) = [a]
newtype Vector (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Complex a) = V_Complex (Vector (a, a))
newtype Vector (Identity a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Identity a) = V_Identity (Vector a)
newtype Vector (Down a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Down a) = V_Down (Vector a)
newtype Vector (First a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (First a) = V_First (Vector a)
newtype Vector (Last a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Last a) = V_Last (Vector a)
newtype Vector (Max a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Max a) = V_Max (Vector a)
newtype Vector (Min a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Min a) = V_Min (Vector a)
newtype Vector (WrappedMonoid a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Dual a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Dual a) = V_Dual (Vector a)
newtype Vector (Product a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Product a) = V_Product (Vector a)
newtype Vector (Sum a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Sum a) = V_Sum (Vector a)
data Vector (Plucker a) 
Instance details

Defined in Linear.Plucker

data Vector (Quaternion a) 
Instance details

Defined in Linear.Quaternion

newtype Vector (V0 a) 
Instance details

Defined in Linear.V0

newtype Vector (V0 a) = V_V0 Int
newtype Vector (V1 a) 
Instance details

Defined in Linear.V1

newtype Vector (V1 a) = V_V1 (Vector a)
data Vector (V2 a) 
Instance details

Defined in Linear.V2

data Vector (V2 a) = V_V2 !Int !(Vector a)
data Vector (V3 a) 
Instance details

Defined in Linear.V3

data Vector (V3 a) = V_V3 !Int !(Vector a)
data Vector (V4 a) 
Instance details

Defined in Linear.V4

data Vector (V4 a) = V_V4 !Int !(Vector a)
newtype Vector (UnboxViaPrim a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Arg a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Arg a b) = V_Arg (Vector (a, b))
newtype Vector (Point f a) 
Instance details

Defined in Linear.Affine

newtype Vector (Point f a) = V_P (Vector (f a))
newtype Vector (As a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (As a b) = V_UnboxAs (Vector b)
data Vector (a, b) 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector (a, b) = V_2 !Int !(Vector a) !(Vector b)
newtype Vector (Const a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Const a b) = V_Const (Vector a)
newtype Vector (Alt f a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Alt f a) = V_Alt (Vector (f a))
data Vector (V n a) 
Instance details

Defined in Linear.V

data Vector (V n a) = V_VN !Int !(Vector a)
data Vector (a, b, c) 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector (a, b, c) = V_3 !Int !(Vector a) !(Vector b) !(Vector c)
data Vector (a, b, c, d) 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector (a, b, c, d) = V_4 !Int !(Vector a) !(Vector b) !(Vector c) !(Vector d)
newtype Vector (Compose f g a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Compose f g a) = V_Compose (Vector (f (g a)))
data Vector (a, b, c, d, e) 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector (a, b, c, d, e) = V_5 !Int !(Vector a) !(Vector b) !(Vector c) !(Vector d) !(Vector e)
data Vector (a, b, c, d, e, f) 
Instance details

Defined in Data.Vector.Unboxed.Base

data Vector (a, b, c, d, e, f) = V_6 !Int !(Vector a) !(Vector b) !(Vector c) !(Vector d) !(Vector e) !(Vector f)

data family MVector s a #

Instances

Instances details
MVector MVector All 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Any 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector () 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s () -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s () -> MVector s () #

basicOverlaps :: MVector s () -> MVector s () -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s ()) #

basicInitialize :: MVector s () -> ST s () #

basicUnsafeReplicate :: Int -> () -> ST s (MVector s ()) #

basicUnsafeRead :: MVector s () -> Int -> ST s () #

basicUnsafeWrite :: MVector s () -> Int -> () -> ST s () #

basicClear :: MVector s () -> ST s () #

basicSet :: MVector s () -> () -> ST s () #

basicUnsafeCopy :: MVector s () -> MVector s () -> ST s () #

basicUnsafeMove :: MVector s () -> MVector s () -> ST s () #

basicUnsafeGrow :: MVector s () -> Int -> ST s (MVector s ()) #

MVector MVector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Char 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Double 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Float 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => MVector MVector (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s (Complex a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Complex a) -> MVector s (Complex a) #

basicOverlaps :: MVector s (Complex a) -> MVector s (Complex a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (Complex a)) #

basicInitialize :: MVector s (Complex a) -> ST s () #

basicUnsafeReplicate :: Int -> Complex a -> ST s (MVector s (Complex a)) #

basicUnsafeRead :: MVector s (Complex a) -> Int -> ST s (Complex a) #

basicUnsafeWrite :: MVector s (Complex a) -> Int -> Complex a -> ST s () #

basicClear :: MVector s (Complex a) -> ST s () #

basicSet :: MVector s (Complex a) -> Complex a -> ST s () #

basicUnsafeCopy :: MVector s (Complex a) -> MVector s (Complex a) -> ST s () #

basicUnsafeMove :: MVector s (Complex a) -> MVector s (Complex a) -> ST s () #

basicUnsafeGrow :: MVector s (Complex a) -> Int -> ST s (MVector s (Complex a)) #

Unbox a => MVector MVector (Identity a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => MVector MVector (Down a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s (Down a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Down a) -> MVector s (Down a) #

basicOverlaps :: MVector s (Down a) -> MVector s (Down a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (Down a)) #

basicInitialize :: MVector s (Down a) -> ST s () #

basicUnsafeReplicate :: Int -> Down a -> ST s (MVector s (Down a)) #

basicUnsafeRead :: MVector s (Down a) -> Int -> ST s (Down a) #

basicUnsafeWrite :: MVector s (Down a) -> Int -> Down a -> ST s () #

basicClear :: MVector s (Down a) -> ST s () #

basicSet :: MVector s (Down a) -> Down a -> ST s () #

basicUnsafeCopy :: MVector s (Down a) -> MVector s (Down a) -> ST s () #

basicUnsafeMove :: MVector s (Down a) -> MVector s (Down a) -> ST s () #

basicUnsafeGrow :: MVector s (Down a) -> Int -> ST s (MVector s (Down a)) #

Unbox a => MVector MVector (First a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s (First a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (First a) -> MVector s (First a) #

basicOverlaps :: MVector s (First a) -> MVector s (First a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (First a)) #

basicInitialize :: MVector s (First a) -> ST s () #

basicUnsafeReplicate :: Int -> First a -> ST s (MVector s (First a)) #

basicUnsafeRead :: MVector s (First a) -> Int -> ST s (First a) #

basicUnsafeWrite :: MVector s (First a) -> Int -> First a -> ST s () #

basicClear :: MVector s (First a) -> ST s () #

basicSet :: MVector s (First a) -> First a -> ST s () #

basicUnsafeCopy :: MVector s (First a) -> MVector s (First a) -> ST s () #

basicUnsafeMove :: MVector s (First a) -> MVector s (First a) -> ST s () #

basicUnsafeGrow :: MVector s (First a) -> Int -> ST s (MVector s (First a)) #

Unbox a => MVector MVector (Last a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s (Last a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Last a) -> MVector s (Last a) #

basicOverlaps :: MVector s (Last a) -> MVector s (Last a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (Last a)) #

basicInitialize :: MVector s (Last a) -> ST s () #

basicUnsafeReplicate :: Int -> Last a -> ST s (MVector s (Last a)) #

basicUnsafeRead :: MVector s (Last a) -> Int -> ST s (Last a) #

basicUnsafeWrite :: MVector s (Last a) -> Int -> Last a -> ST s () #

basicClear :: MVector s (Last a) -> ST s () #

basicSet :: MVector s (Last a) -> Last a -> ST s () #

basicUnsafeCopy :: MVector s (Last a) -> MVector s (Last a) -> ST s () #

basicUnsafeMove :: MVector s (Last a) -> MVector s (Last a) -> ST s () #

basicUnsafeGrow :: MVector s (Last a) -> Int -> ST s (MVector s (Last a)) #

Unbox a => MVector MVector (Max a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s (Max a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Max a) -> MVector s (Max a) #

basicOverlaps :: MVector s (Max a) -> MVector s (Max a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (Max a)) #

basicInitialize :: MVector s (Max a) -> ST s () #

basicUnsafeReplicate :: Int -> Max a -> ST s (MVector s (Max a)) #

basicUnsafeRead :: MVector s (Max a) -> Int -> ST s (Max a) #

basicUnsafeWrite :: MVector s (Max a) -> Int -> Max a -> ST s () #

basicClear :: MVector s (Max a) -> ST s () #

basicSet :: MVector s (Max a) -> Max a -> ST s () #

basicUnsafeCopy :: MVector s (Max a) -> MVector s (Max a) -> ST s () #

basicUnsafeMove :: MVector s (Max a) -> MVector s (Max a) -> ST s () #

basicUnsafeGrow :: MVector s (Max a) -> Int -> ST s (MVector s (Max a)) #

Unbox a => MVector MVector (Min a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s (Min a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Min a) -> MVector s (Min a) #

basicOverlaps :: MVector s (Min a) -> MVector s (Min a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (Min a)) #

basicInitialize :: MVector s (Min a) -> ST s () #

basicUnsafeReplicate :: Int -> Min a -> ST s (MVector s (Min a)) #

basicUnsafeRead :: MVector s (Min a) -> Int -> ST s (Min a) #

basicUnsafeWrite :: MVector s (Min a) -> Int -> Min a -> ST s () #

basicClear :: MVector s (Min a) -> ST s () #

basicSet :: MVector s (Min a) -> Min a -> ST s () #

basicUnsafeCopy :: MVector s (Min a) -> MVector s (Min a) -> ST s () #

basicUnsafeMove :: MVector s (Min a) -> MVector s (Min a) -> ST s () #

basicUnsafeGrow :: MVector s (Min a) -> Int -> ST s (MVector s (Min a)) #

Unbox a => MVector MVector (WrappedMonoid a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => MVector MVector (Dual a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s (Dual a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Dual a) -> MVector s (Dual a) #

basicOverlaps :: MVector s (Dual a) -> MVector s (Dual a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (Dual a)) #

basicInitialize :: MVector s (Dual a) -> ST s () #

basicUnsafeReplicate :: Int -> Dual a -> ST s (MVector s (Dual a)) #

basicUnsafeRead :: MVector s (Dual a) -> Int -> ST s (Dual a) #

basicUnsafeWrite :: MVector s (Dual a) -> Int -> Dual a -> ST s () #

basicClear :: MVector s (Dual a) -> ST s () #

basicSet :: MVector s (Dual a) -> Dual a -> ST s () #

basicUnsafeCopy :: MVector s (Dual a) -> MVector s (Dual a) -> ST s () #

basicUnsafeMove :: MVector s (Dual a) -> MVector s (Dual a) -> ST s () #

basicUnsafeGrow :: MVector s (Dual a) -> Int -> ST s (MVector s (Dual a)) #

Unbox a => MVector MVector (Product a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s (Product a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Product a) -> MVector s (Product a) #

basicOverlaps :: MVector s (Product a) -> MVector s (Product a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (Product a)) #

basicInitialize :: MVector s (Product a) -> ST s () #

basicUnsafeReplicate :: Int -> Product a -> ST s (MVector s (Product a)) #

basicUnsafeRead :: MVector s (Product a) -> Int -> ST s (Product a) #

basicUnsafeWrite :: MVector s (Product a) -> Int -> Product a -> ST s () #

basicClear :: MVector s (Product a) -> ST s () #

basicSet :: MVector s (Product a) -> Product a -> ST s () #

basicUnsafeCopy :: MVector s (Product a) -> MVector s (Product a) -> ST s () #

basicUnsafeMove :: MVector s (Product a) -> MVector s (Product a) -> ST s () #

basicUnsafeGrow :: MVector s (Product a) -> Int -> ST s (MVector s (Product a)) #

Unbox a => MVector MVector (Sum a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s (Sum a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Sum a) -> MVector s (Sum a) #

basicOverlaps :: MVector s (Sum a) -> MVector s (Sum a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (Sum a)) #

basicInitialize :: MVector s (Sum a) -> ST s () #

basicUnsafeReplicate :: Int -> Sum a -> ST s (MVector s (Sum a)) #

basicUnsafeRead :: MVector s (Sum a) -> Int -> ST s (Sum a) #

basicUnsafeWrite :: MVector s (Sum a) -> Int -> Sum a -> ST s () #

basicClear :: MVector s (Sum a) -> ST s () #

basicSet :: MVector s (Sum a) -> Sum a -> ST s () #

basicUnsafeCopy :: MVector s (Sum a) -> MVector s (Sum a) -> ST s () #

basicUnsafeMove :: MVector s (Sum a) -> MVector s (Sum a) -> ST s () #

basicUnsafeGrow :: MVector s (Sum a) -> Int -> ST s (MVector s (Sum a)) #

Unbox a => MVector MVector (Plucker a) 
Instance details

Defined in Linear.Plucker

Methods

basicLength :: MVector s (Plucker a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Plucker a) -> MVector s (Plucker a) #

basicOverlaps :: MVector s (Plucker a) -> MVector s (Plucker a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (Plucker a)) #

basicInitialize :: MVector s (Plucker a) -> ST s () #

basicUnsafeReplicate :: Int -> Plucker a -> ST s (MVector s (Plucker a)) #

basicUnsafeRead :: MVector s (Plucker a) -> Int -> ST s (Plucker a) #

basicUnsafeWrite :: MVector s (Plucker a) -> Int -> Plucker a -> ST s () #

basicClear :: MVector s (Plucker a) -> ST s () #

basicSet :: MVector s (Plucker a) -> Plucker a -> ST s () #

basicUnsafeCopy :: MVector s (Plucker a) -> MVector s (Plucker a) -> ST s () #

basicUnsafeMove :: MVector s (Plucker a) -> MVector s (Plucker a) -> ST s () #

basicUnsafeGrow :: MVector s (Plucker a) -> Int -> ST s (MVector s (Plucker a)) #

Unbox a => MVector MVector (Quaternion a) 
Instance details

Defined in Linear.Quaternion

MVector MVector (V0 a) 
Instance details

Defined in Linear.V0

Methods

basicLength :: MVector s (V0 a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V0 a) -> MVector s (V0 a) #

basicOverlaps :: MVector s (V0 a) -> MVector s (V0 a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (V0 a)) #

basicInitialize :: MVector s (V0 a) -> ST s () #

basicUnsafeReplicate :: Int -> V0 a -> ST s (MVector s (V0 a)) #

basicUnsafeRead :: MVector s (V0 a) -> Int -> ST s (V0 a) #

basicUnsafeWrite :: MVector s (V0 a) -> Int -> V0 a -> ST s () #

basicClear :: MVector s (V0 a) -> ST s () #

basicSet :: MVector s (V0 a) -> V0 a -> ST s () #

basicUnsafeCopy :: MVector s (V0 a) -> MVector s (V0 a) -> ST s () #

basicUnsafeMove :: MVector s (V0 a) -> MVector s (V0 a) -> ST s () #

basicUnsafeGrow :: MVector s (V0 a) -> Int -> ST s (MVector s (V0 a)) #

Unbox a => MVector MVector (V1 a) 
Instance details

Defined in Linear.V1

Methods

basicLength :: MVector s (V1 a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V1 a) -> MVector s (V1 a) #

basicOverlaps :: MVector s (V1 a) -> MVector s (V1 a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (V1 a)) #

basicInitialize :: MVector s (V1 a) -> ST s () #

basicUnsafeReplicate :: Int -> V1 a -> ST s (MVector s (V1 a)) #

basicUnsafeRead :: MVector s (V1 a) -> Int -> ST s (V1 a) #

basicUnsafeWrite :: MVector s (V1 a) -> Int -> V1 a -> ST s () #

basicClear :: MVector s (V1 a) -> ST s () #

basicSet :: MVector s (V1 a) -> V1 a -> ST s () #

basicUnsafeCopy :: MVector s (V1 a) -> MVector s (V1 a) -> ST s () #

basicUnsafeMove :: MVector s (V1 a) -> MVector s (V1 a) -> ST s () #

basicUnsafeGrow :: MVector s (V1 a) -> Int -> ST s (MVector s (V1 a)) #

Unbox a => MVector MVector (V2 a) 
Instance details

Defined in Linear.V2

Methods

basicLength :: MVector s (V2 a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V2 a) -> MVector s (V2 a) #

basicOverlaps :: MVector s (V2 a) -> MVector s (V2 a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (V2 a)) #

basicInitialize :: MVector s (V2 a) -> ST s () #

basicUnsafeReplicate :: Int -> V2 a -> ST s (MVector s (V2 a)) #

basicUnsafeRead :: MVector s (V2 a) -> Int -> ST s (V2 a) #

basicUnsafeWrite :: MVector s (V2 a) -> Int -> V2 a -> ST s () #

basicClear :: MVector s (V2 a) -> ST s () #

basicSet :: MVector s (V2 a) -> V2 a -> ST s () #

basicUnsafeCopy :: MVector s (V2 a) -> MVector s (V2 a) -> ST s () #

basicUnsafeMove :: MVector s (V2 a) -> MVector s (V2 a) -> ST s () #

basicUnsafeGrow :: MVector s (V2 a) -> Int -> ST s (MVector s (V2 a)) #

Unbox a => MVector MVector (V3 a) 
Instance details

Defined in Linear.V3

Methods

basicLength :: MVector s (V3 a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V3 a) -> MVector s (V3 a) #

basicOverlaps :: MVector s (V3 a) -> MVector s (V3 a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (V3 a)) #

basicInitialize :: MVector s (V3 a) -> ST s () #

basicUnsafeReplicate :: Int -> V3 a -> ST s (MVector s (V3 a)) #

basicUnsafeRead :: MVector s (V3 a) -> Int -> ST s (V3 a) #

basicUnsafeWrite :: MVector s (V3 a) -> Int -> V3 a -> ST s () #

basicClear :: MVector s (V3 a) -> ST s () #

basicSet :: MVector s (V3 a) -> V3 a -> ST s () #

basicUnsafeCopy :: MVector s (V3 a) -> MVector s (V3 a) -> ST s () #

basicUnsafeMove :: MVector s (V3 a) -> MVector s (V3 a) -> ST s () #

basicUnsafeGrow :: MVector s (V3 a) -> Int -> ST s (MVector s (V3 a)) #

Unbox a => MVector MVector (V4 a) 
Instance details

Defined in Linear.V4

Methods

basicLength :: MVector s (V4 a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V4 a) -> MVector s (V4 a) #

basicOverlaps :: MVector s (V4 a) -> MVector s (V4 a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (V4 a)) #

basicInitialize :: MVector s (V4 a) -> ST s () #

basicUnsafeReplicate :: Int -> V4 a -> ST s (MVector s (V4 a)) #

basicUnsafeRead :: MVector s (V4 a) -> Int -> ST s (V4 a) #

basicUnsafeWrite :: MVector s (V4 a) -> Int -> V4 a -> ST s () #

basicClear :: MVector s (V4 a) -> ST s () #

basicSet :: MVector s (V4 a) -> V4 a -> ST s () #

basicUnsafeCopy :: MVector s (V4 a) -> MVector s (V4 a) -> ST s () #

basicUnsafeMove :: MVector s (V4 a) -> MVector s (V4 a) -> ST s () #

basicUnsafeGrow :: MVector s (V4 a) -> Int -> ST s (MVector s (V4 a)) #

Prim a => MVector MVector (UnboxViaPrim a) 
Instance details

Defined in Data.Vector.Unboxed.Base

(Unbox a, Unbox b) => MVector MVector (Arg a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s (Arg a b) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Arg a b) -> MVector s (Arg a b) #

basicOverlaps :: MVector s (Arg a b) -> MVector s (Arg a b) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (Arg a b)) #

basicInitialize :: MVector s (Arg a b) -> ST s () #

basicUnsafeReplicate :: Int -> Arg a b -> ST s (MVector s (Arg a b)) #

basicUnsafeRead :: MVector s (Arg a b) -> Int -> ST s (Arg a b) #

basicUnsafeWrite :: MVector s (Arg a b) -> Int -> Arg a b -> ST s () #

basicClear :: MVector s (Arg a b) -> ST s () #

basicSet :: MVector s (Arg a b) -> Arg a b -> ST s () #

basicUnsafeCopy :: MVector s (Arg a b) -> MVector s (Arg a b) -> ST s () #

basicUnsafeMove :: MVector s (Arg a b) -> MVector s (Arg a b) -> ST s () #

basicUnsafeGrow :: MVector s (Arg a b) -> Int -> ST s (MVector s (Arg a b)) #

Unbox (f a) => MVector MVector (Point f a) 
Instance details

Defined in Linear.Affine

Methods

basicLength :: MVector s (Point f a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Point f a) -> MVector s (Point f a) #

basicOverlaps :: MVector s (Point f a) -> MVector s (Point f a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (Point f a)) #

basicInitialize :: MVector s (Point f a) -> ST s () #

basicUnsafeReplicate :: Int -> Point f a -> ST s (MVector s (Point f a)) #

basicUnsafeRead :: MVector s (Point f a) -> Int -> ST s (Point f a) #

basicUnsafeWrite :: MVector s (Point f a) -> Int -> Point f a -> ST s () #

basicClear :: MVector s (Point f a) -> ST s () #

basicSet :: MVector s (Point f a) -> Point f a -> ST s () #

basicUnsafeCopy :: MVector s (Point f a) -> MVector s (Point f a) -> ST s () #

basicUnsafeMove :: MVector s (Point f a) -> MVector s (Point f a) -> ST s () #

basicUnsafeGrow :: MVector s (Point f a) -> Int -> ST s (MVector s (Point f a)) #

(IsoUnbox a b, Unbox b) => MVector MVector (As a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s (As a b) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (As a b) -> MVector s (As a b) #

basicOverlaps :: MVector s (As a b) -> MVector s (As a b) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (As a b)) #

basicInitialize :: MVector s (As a b) -> ST s () #

basicUnsafeReplicate :: Int -> As a b -> ST s (MVector s (As a b)) #

basicUnsafeRead :: MVector s (As a b) -> Int -> ST s (As a b) #

basicUnsafeWrite :: MVector s (As a b) -> Int -> As a b -> ST s () #

basicClear :: MVector s (As a b) -> ST s () #

basicSet :: MVector s (As a b) -> As a b -> ST s () #

basicUnsafeCopy :: MVector s (As a b) -> MVector s (As a b) -> ST s () #

basicUnsafeMove :: MVector s (As a b) -> MVector s (As a b) -> ST s () #

basicUnsafeGrow :: MVector s (As a b) -> Int -> ST s (MVector s (As a b)) #

(Unbox a, Unbox b) => MVector MVector (a, b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s (a, b) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (a, b) -> MVector s (a, b) #

basicOverlaps :: MVector s (a, b) -> MVector s (a, b) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (a, b)) #

basicInitialize :: MVector s (a, b) -> ST s () #

basicUnsafeReplicate :: Int -> (a, b) -> ST s (MVector s (a, b)) #

basicUnsafeRead :: MVector s (a, b) -> Int -> ST s (a, b) #

basicUnsafeWrite :: MVector s (a, b) -> Int -> (a, b) -> ST s () #

basicClear :: MVector s (a, b) -> ST s () #

basicSet :: MVector s (a, b) -> (a, b) -> ST s () #

basicUnsafeCopy :: MVector s (a, b) -> MVector s (a, b) -> ST s () #

basicUnsafeMove :: MVector s (a, b) -> MVector s (a, b) -> ST s () #

basicUnsafeGrow :: MVector s (a, b) -> Int -> ST s (MVector s (a, b)) #

Unbox a => MVector MVector (Const a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s (Const a b) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Const a b) -> MVector s (Const a b) #

basicOverlaps :: MVector s (Const a b) -> MVector s (Const a b) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (Const a b)) #

basicInitialize :: MVector s (Const a b) -> ST s () #

basicUnsafeReplicate :: Int -> Const a b -> ST s (MVector s (Const a b)) #

basicUnsafeRead :: MVector s (Const a b) -> Int -> ST s (Const a b) #

basicUnsafeWrite :: MVector s (Const a b) -> Int -> Const a b -> ST s () #

basicClear :: MVector s (Const a b) -> ST s () #

basicSet :: MVector s (Const a b) -> Const a b -> ST s () #

basicUnsafeCopy :: MVector s (Const a b) -> MVector s (Const a b) -> ST s () #

basicUnsafeMove :: MVector s (Const a b) -> MVector s (Const a b) -> ST s () #

basicUnsafeGrow :: MVector s (Const a b) -> Int -> ST s (MVector s (Const a b)) #

Unbox (f a) => MVector MVector (Alt f a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s (Alt f a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Alt f a) -> MVector s (Alt f a) #

basicOverlaps :: MVector s (Alt f a) -> MVector s (Alt f a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (Alt f a)) #

basicInitialize :: MVector s (Alt f a) -> ST s () #

basicUnsafeReplicate :: Int -> Alt f a -> ST s (MVector s (Alt f a)) #

basicUnsafeRead :: MVector s (Alt f a) -> Int -> ST s (Alt f a) #

basicUnsafeWrite :: MVector s (Alt f a) -> Int -> Alt f a -> ST s () #

basicClear :: MVector s (Alt f a) -> ST s () #

basicSet :: MVector s (Alt f a) -> Alt f a -> ST s () #

basicUnsafeCopy :: MVector s (Alt f a) -> MVector s (Alt f a) -> ST s () #

basicUnsafeMove :: MVector s (Alt f a) -> MVector s (Alt f a) -> ST s () #

basicUnsafeGrow :: MVector s (Alt f a) -> Int -> ST s (MVector s (Alt f a)) #

(Dim n, Unbox a) => MVector MVector (V n a) 
Instance details

Defined in Linear.V

Methods

basicLength :: MVector s (V n a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V n a) -> MVector s (V n a) #

basicOverlaps :: MVector s (V n a) -> MVector s (V n a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (V n a)) #

basicInitialize :: MVector s (V n a) -> ST s () #

basicUnsafeReplicate :: Int -> V n a -> ST s (MVector s (V n a)) #

basicUnsafeRead :: MVector s (V n a) -> Int -> ST s (V n a) #

basicUnsafeWrite :: MVector s (V n a) -> Int -> V n a -> ST s () #

basicClear :: MVector s (V n a) -> ST s () #

basicSet :: MVector s (V n a) -> V n a -> ST s () #

basicUnsafeCopy :: MVector s (V n a) -> MVector s (V n a) -> ST s () #

basicUnsafeMove :: MVector s (V n a) -> MVector s (V n a) -> ST s () #

basicUnsafeGrow :: MVector s (V n a) -> Int -> ST s (MVector s (V n a)) #

(Unbox a, Unbox b, Unbox c) => MVector MVector (a, b, c) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s (a, b, c) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (a, b, c) -> MVector s (a, b, c) #

basicOverlaps :: MVector s (a, b, c) -> MVector s (a, b, c) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (a, b, c)) #

basicInitialize :: MVector s (a, b, c) -> ST s () #

basicUnsafeReplicate :: Int -> (a, b, c) -> ST s (MVector s (a, b, c)) #

basicUnsafeRead :: MVector s (a, b, c) -> Int -> ST s (a, b, c) #

basicUnsafeWrite :: MVector s (a, b, c) -> Int -> (a, b, c) -> ST s () #

basicClear :: MVector s (a, b, c) -> ST s () #

basicSet :: MVector s (a, b, c) -> (a, b, c) -> ST s () #

basicUnsafeCopy :: MVector s (a, b, c) -> MVector s (a, b, c) -> ST s () #

basicUnsafeMove :: MVector s (a, b, c) -> MVector s (a, b, c) -> ST s () #

basicUnsafeGrow :: MVector s (a, b, c) -> Int -> ST s (MVector s (a, b, c)) #

(Unbox a, Unbox b, Unbox c, Unbox d) => MVector MVector (a, b, c, d) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s (a, b, c, d) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (a, b, c, d) -> MVector s (a, b, c, d) #

basicOverlaps :: MVector s (a, b, c, d) -> MVector s (a, b, c, d) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (a, b, c, d)) #

basicInitialize :: MVector s (a, b, c, d) -> ST s () #

basicUnsafeReplicate :: Int -> (a, b, c, d) -> ST s (MVector s (a, b, c, d)) #

basicUnsafeRead :: MVector s (a, b, c, d) -> Int -> ST s (a, b, c, d) #

basicUnsafeWrite :: MVector s (a, b, c, d) -> Int -> (a, b, c, d) -> ST s () #

basicClear :: MVector s (a, b, c, d) -> ST s () #

basicSet :: MVector s (a, b, c, d) -> (a, b, c, d) -> ST s () #

basicUnsafeCopy :: MVector s (a, b, c, d) -> MVector s (a, b, c, d) -> ST s () #

basicUnsafeMove :: MVector s (a, b, c, d) -> MVector s (a, b, c, d) -> ST s () #

basicUnsafeGrow :: MVector s (a, b, c, d) -> Int -> ST s (MVector s (a, b, c, d)) #

Unbox (f (g a)) => MVector MVector (Compose f g a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s (Compose f g a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Compose f g a) -> MVector s (Compose f g a) #

basicOverlaps :: MVector s (Compose f g a) -> MVector s (Compose f g a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (Compose f g a)) #

basicInitialize :: MVector s (Compose f g a) -> ST s () #

basicUnsafeReplicate :: Int -> Compose f g a -> ST s (MVector s (Compose f g a)) #

basicUnsafeRead :: MVector s (Compose f g a) -> Int -> ST s (Compose f g a) #

basicUnsafeWrite :: MVector s (Compose f g a) -> Int -> Compose f g a -> ST s () #

basicClear :: MVector s (Compose f g a) -> ST s () #

basicSet :: MVector s (Compose f g a) -> Compose f g a -> ST s () #

basicUnsafeCopy :: MVector s (Compose f g a) -> MVector s (Compose f g a) -> ST s () #

basicUnsafeMove :: MVector s (Compose f g a) -> MVector s (Compose f g a) -> ST s () #

basicUnsafeGrow :: MVector s (Compose f g a) -> Int -> ST s (MVector s (Compose f g a)) #

(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => MVector MVector (a, b, c, d, e) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s (a, b, c, d, e) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (a, b, c, d, e) -> MVector s (a, b, c, d, e) #

basicOverlaps :: MVector s (a, b, c, d, e) -> MVector s (a, b, c, d, e) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (a, b, c, d, e)) #

basicInitialize :: MVector s (a, b, c, d, e) -> ST s () #

basicUnsafeReplicate :: Int -> (a, b, c, d, e) -> ST s (MVector s (a, b, c, d, e)) #

basicUnsafeRead :: MVector s (a, b, c, d, e) -> Int -> ST s (a, b, c, d, e) #

basicUnsafeWrite :: MVector s (a, b, c, d, e) -> Int -> (a, b, c, d, e) -> ST s () #

basicClear :: MVector s (a, b, c, d, e) -> ST s () #

basicSet :: MVector s (a, b, c, d, e) -> (a, b, c, d, e) -> ST s () #

basicUnsafeCopy :: MVector s (a, b, c, d, e) -> MVector s (a, b, c, d, e) -> ST s () #

basicUnsafeMove :: MVector s (a, b, c, d, e) -> MVector s (a, b, c, d, e) -> ST s () #

basicUnsafeGrow :: MVector s (a, b, c, d, e) -> Int -> ST s (MVector s (a, b, c, d, e)) #

(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => MVector MVector (a, b, c, d, e, f) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s (a, b, c, d, e, f) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (a, b, c, d, e, f) -> MVector s (a, b, c, d, e, f) #

basicOverlaps :: MVector s (a, b, c, d, e, f) -> MVector s (a, b, c, d, e, f) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (a, b, c, d, e, f)) #

basicInitialize :: MVector s (a, b, c, d, e, f) -> ST s () #

basicUnsafeReplicate :: Int -> (a, b, c, d, e, f) -> ST s (MVector s (a, b, c, d, e, f)) #

basicUnsafeRead :: MVector s (a, b, c, d, e, f) -> Int -> ST s (a, b, c, d, e, f) #

basicUnsafeWrite :: MVector s (a, b, c, d, e, f) -> Int -> (a, b, c, d, e, f) -> ST s () #

basicClear :: MVector s (a, b, c, d, e, f) -> ST s () #

basicSet :: MVector s (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> ST s () #

basicUnsafeCopy :: MVector s (a, b, c, d, e, f) -> MVector s (a, b, c, d, e, f) -> ST s () #

basicUnsafeMove :: MVector s (a, b, c, d, e, f) -> MVector s (a, b, c, d, e, f) -> ST s () #

basicUnsafeGrow :: MVector s (a, b, c, d, e, f) -> Int -> ST s (MVector s (a, b, c, d, e, f)) #

NFData1 (MVector s)

Since: vector-0.12.1.0

Instance details

Defined in Data.Vector.Unboxed.Base

Methods

liftRnf :: (a -> ()) -> MVector s a -> () #

NFData (MVector s a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

rnf :: MVector s a -> () #

newtype MVector s All 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s All = MV_All (MVector s Bool)
newtype MVector s Any 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Any = MV_Any (MVector s Bool)
newtype MVector s Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int8 = MV_Int8 (MVector s Int8)
newtype MVector s Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s () 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s () = MV_Unit Int
newtype MVector s Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Bool = MV_Bool (MVector s Word8)
newtype MVector s Char 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Char = MV_Char (MVector s Char)
newtype MVector s Double 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Float 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int = MV_Int (MVector s Int)
newtype MVector s Word 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word = MV_Word (MVector s Word)
newtype MVector s (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Complex a) = MV_Complex (MVector s (a, a))
newtype MVector s (Identity a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Identity a) = MV_Identity (MVector s a)
newtype MVector s (Down a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Down a) = MV_Down (MVector s a)
newtype MVector s (First a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (First a) = MV_First (MVector s a)
newtype MVector s (Last a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Last a) = MV_Last (MVector s a)
newtype MVector s (Max a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Max a) = MV_Max (MVector s a)
newtype MVector s (Min a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Min a) = MV_Min (MVector s a)
newtype MVector s (WrappedMonoid a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Dual a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Dual a) = MV_Dual (MVector s a)
newtype MVector s (Product a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Product a) = MV_Product (MVector s a)
newtype MVector s (Sum a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Sum a) = MV_Sum (MVector s a)
data MVector s (Plucker a) 
Instance details

Defined in Linear.Plucker

data MVector s (Plucker a) = MV_Plucker !Int (MVector s a)
data MVector s (Quaternion a) 
Instance details

Defined in Linear.Quaternion

newtype MVector s (V0 a) 
Instance details

Defined in Linear.V0

newtype MVector s (V0 a) = MV_V0 Int
newtype MVector s (V1 a) 
Instance details

Defined in Linear.V1

newtype MVector s (V1 a) = MV_V1 (MVector s a)
data MVector s (V2 a) 
Instance details

Defined in Linear.V2

data MVector s (V2 a) = MV_V2 !Int !(MVector s a)
data MVector s (V3 a) 
Instance details

Defined in Linear.V3

data MVector s (V3 a) = MV_V3 !Int !(MVector s a)
data MVector s (V4 a) 
Instance details

Defined in Linear.V4

data MVector s (V4 a) = MV_V4 !Int !(MVector s a)
newtype MVector s (UnboxViaPrim a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Arg a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Arg a b) = MV_Arg (MVector s (a, b))
newtype MVector s (Point f a) 
Instance details

Defined in Linear.Affine

newtype MVector s (Point f a) = MV_P (MVector s (f a))
newtype MVector s (As a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (As a b) = MV_UnboxAs (MVector s b)
data MVector s (a, b) 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s (a, b) = MV_2 !Int !(MVector s a) !(MVector s b)
newtype MVector s (Const a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Const a b) = MV_Const (MVector s a)
newtype MVector s (Alt f a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Alt f a) = MV_Alt (MVector s (f a))
data MVector s (V n a) 
Instance details

Defined in Linear.V

data MVector s (V n a) = MV_VN !Int !(MVector s a)
data MVector s (a, b, c) 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s (a, b, c) = MV_3 !Int !(MVector s a) !(MVector s b) !(MVector s c)
data MVector s (a, b, c, d) 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s (a, b, c, d) = MV_4 !Int !(MVector s a) !(MVector s b) !(MVector s c) !(MVector s d)
newtype MVector s (Compose f g a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Compose f g a) = MV_Compose (MVector s (f (g a)))
data MVector s (a, b, c, d, e) 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s (a, b, c, d, e) = MV_5 !Int !(MVector s a) !(MVector s b) !(MVector s c) !(MVector s d) !(MVector s e)
data MVector s (a, b, c, d, e, f) 
Instance details

Defined in Data.Vector.Unboxed.Base

data MVector s (a, b, c, d, e, f) = MV_6 !Int !(MVector s a) !(MVector s b) !(MVector s c) !(MVector s d) !(MVector s e) !(MVector s f)

data SDLException #

Error details about a failure to call an SDL routine. Almost all functions in this library have the ability to produce exceptions of this type. Inspection should help you learn more about what has gone wrong.

Constructors

SDLCallFailed

A call to a low-level SDL C function failed unexpectedly.

Fields

SDLUnexpectedArgument

An SDL C function was called with an unexpected argument.

Fields

SDLUnknownHintValue

A hint was attempted to be set, but SDL does not know about this hint.

Fields

Instances

Instances details
Data SDLException 
Instance details

Defined in SDL.Exception

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SDLException -> c SDLException #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SDLException #

toConstr :: SDLException -> Constr #

dataTypeOf :: SDLException -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SDLException) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SDLException) #

gmapT :: (forall b. Data b => b -> b) -> SDLException -> SDLException #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SDLException -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SDLException -> r #

gmapQ :: (forall d. Data d => d -> u) -> SDLException -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SDLException -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SDLException -> m SDLException #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SDLException -> m SDLException #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SDLException -> m SDLException #

Exception SDLException 
Instance details

Defined in SDL.Exception

Generic SDLException 
Instance details

Defined in SDL.Exception

Associated Types

type Rep SDLException :: Type -> Type #

Read SDLException 
Instance details

Defined in SDL.Exception

Show SDLException 
Instance details

Defined in SDL.Exception

Eq SDLException 
Instance details

Defined in SDL.Exception

Ord SDLException 
Instance details

Defined in SDL.Exception

type Rep SDLException 
Instance details

Defined in SDL.Exception

type Rep SDLException = D1 ('MetaData "SDLException" "SDL.Exception" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "SDLCallFailed" 'PrefixI 'True) (S1 ('MetaSel ('Just "sdlExceptionCaller") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "sdlFunction") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "sdlExceptionError") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) :+: (C1 ('MetaCons "SDLUnexpectedArgument" 'PrefixI 'True) (S1 ('MetaSel ('Just "sdlExceptionCaller") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "sdlFunction") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "sdlUnknownValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String))) :+: C1 ('MetaCons "SDLUnknownHintValue" 'PrefixI 'True) (S1 ('MetaSel ('Just "sdlHint") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String) :*: S1 ('MetaSel ('Just "sdlUnknownValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String))))

newtype Scancode #

Constructors

Scancode 

Instances

Instances details
Data Scancode 
Instance details

Defined in SDL.Input.Keyboard.Codes

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Scancode -> c Scancode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Scancode #

toConstr :: Scancode -> Constr #

dataTypeOf :: Scancode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Scancode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scancode) #

gmapT :: (forall b. Data b => b -> b) -> Scancode -> Scancode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scancode -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scancode -> r #

gmapQ :: (forall d. Data d => d -> u) -> Scancode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Scancode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Scancode -> m Scancode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Scancode -> m Scancode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Scancode -> m Scancode #

Bounded Scancode 
Instance details

Defined in SDL.Input.Keyboard.Codes

Generic Scancode 
Instance details

Defined in SDL.Input.Keyboard.Codes

Associated Types

type Rep Scancode :: Type -> Type #

Methods

from :: Scancode -> Rep Scancode x #

to :: Rep Scancode x -> Scancode #

Read Scancode 
Instance details

Defined in SDL.Input.Keyboard.Codes

Show Scancode 
Instance details

Defined in SDL.Input.Keyboard.Codes

Eq Scancode 
Instance details

Defined in SDL.Input.Keyboard.Codes

Ord Scancode 
Instance details

Defined in SDL.Input.Keyboard.Codes

FromNumber Scancode Word32 
Instance details

Defined in SDL.Input.Keyboard.Codes

ToNumber Scancode Word32 
Instance details

Defined in SDL.Input.Keyboard.Codes

Methods

toNumber :: Scancode -> Word32 #

type Rep Scancode 
Instance details

Defined in SDL.Input.Keyboard.Codes

type Rep Scancode = D1 ('MetaData "Scancode" "SDL.Input.Keyboard.Codes" "sdl2-2.5.5.0-45393fc3" 'True) (C1 ('MetaCons "Scancode" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapScancode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))

data PowerState #

Information about the power supply for the user's environment

Constructors

Battery BatteryState Charge

The user is on a battery powered device. See BatteryState for charge information, and Charge for charge information

Mains

The user is on a device connected to the mains.

UnknownPowerState

SDL could not determine the power for the device.

Instances

Instances details
Generic PowerState 
Instance details

Defined in SDL.Power

Associated Types

type Rep PowerState :: Type -> Type #

Read PowerState 
Instance details

Defined in SDL.Power

Show PowerState 
Instance details

Defined in SDL.Power

Eq PowerState 
Instance details

Defined in SDL.Power

Ord PowerState 
Instance details

Defined in SDL.Power

type Rep PowerState 
Instance details

Defined in SDL.Power

type Rep PowerState = D1 ('MetaData "PowerState" "SDL.Power" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "Battery" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BatteryState) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Charge)) :+: (C1 ('MetaCons "Mains" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnknownPowerState" 'PrefixI 'False) (U1 :: Type -> Type)))

newtype Keycode #

Constructors

Keycode 

Fields

Instances

Instances details
Data Keycode 
Instance details

Defined in SDL.Input.Keyboard.Codes

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Keycode -> c Keycode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Keycode #

toConstr :: Keycode -> Constr #

dataTypeOf :: Keycode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Keycode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Keycode) #

gmapT :: (forall b. Data b => b -> b) -> Keycode -> Keycode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Keycode -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Keycode -> r #

gmapQ :: (forall d. Data d => d -> u) -> Keycode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Keycode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Keycode -> m Keycode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Keycode -> m Keycode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Keycode -> m Keycode #

Bounded Keycode 
Instance details

Defined in SDL.Input.Keyboard.Codes

Generic Keycode 
Instance details

Defined in SDL.Input.Keyboard.Codes

Associated Types

type Rep Keycode :: Type -> Type #

Methods

from :: Keycode -> Rep Keycode x #

to :: Rep Keycode x -> Keycode #

Read Keycode 
Instance details

Defined in SDL.Input.Keyboard.Codes

Show Keycode 
Instance details

Defined in SDL.Input.Keyboard.Codes

Eq Keycode 
Instance details

Defined in SDL.Input.Keyboard.Codes

Methods

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

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

Ord Keycode 
Instance details

Defined in SDL.Input.Keyboard.Codes

FromNumber Keycode Int32 
Instance details

Defined in SDL.Input.Keyboard.Codes

Methods

fromNumber :: Int32 -> Keycode #

ToNumber Keycode Int32 
Instance details

Defined in SDL.Input.Keyboard.Codes

Methods

toNumber :: Keycode -> Int32 #

type Rep Keycode 
Instance details

Defined in SDL.Input.Keyboard.Codes

type Rep Keycode = D1 ('MetaData "Keycode" "SDL.Input.Keyboard.Codes" "sdl2-2.5.5.0-45393fc3" 'True) (C1 ('MetaCons "Keycode" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapKeycode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32)))

data InitFlag #

Instances

Instances details
Data InitFlag 
Instance details

Defined in SDL.Init

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InitFlag -> c InitFlag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InitFlag #

toConstr :: InitFlag -> Constr #

dataTypeOf :: InitFlag -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InitFlag) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InitFlag) #

gmapT :: (forall b. Data b => b -> b) -> InitFlag -> InitFlag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InitFlag -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InitFlag -> r #

gmapQ :: (forall d. Data d => d -> u) -> InitFlag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InitFlag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InitFlag -> m InitFlag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InitFlag -> m InitFlag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InitFlag -> m InitFlag #

Bounded InitFlag 
Instance details

Defined in SDL.Init

Enum InitFlag 
Instance details

Defined in SDL.Init

Generic InitFlag 
Instance details

Defined in SDL.Init

Associated Types

type Rep InitFlag :: Type -> Type #

Methods

from :: InitFlag -> Rep InitFlag x #

to :: Rep InitFlag x -> InitFlag #

Read InitFlag 
Instance details

Defined in SDL.Init

Show InitFlag 
Instance details

Defined in SDL.Init

Eq InitFlag 
Instance details

Defined in SDL.Init

Ord InitFlag 
Instance details

Defined in SDL.Init

ToNumber InitFlag Word32 
Instance details

Defined in SDL.Init

Methods

toNumber :: InitFlag -> Word32 #

type Rep InitFlag 
Instance details

Defined in SDL.Init

type Rep InitFlag = D1 ('MetaData "InitFlag" "SDL.Init" "sdl2-2.5.5.0-45393fc3" 'False) ((C1 ('MetaCons "InitTimer" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "InitAudio" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InitVideo" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "InitJoystick" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InitHaptic" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "InitGameController" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InitEvents" 'PrefixI 'False) (U1 :: Type -> Type))))

data HintPriority #

How to deal with setting hints when an existing override or environment variable is present.

Constructors

DefaultPriority

Low priority, used for default values

NormalPriority

Medium priority

OverridePriority

High priority

Instances

Instances details
Data HintPriority 
Instance details

Defined in SDL.Hint

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HintPriority -> c HintPriority #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HintPriority #

toConstr :: HintPriority -> Constr #

dataTypeOf :: HintPriority -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HintPriority) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HintPriority) #

gmapT :: (forall b. Data b => b -> b) -> HintPriority -> HintPriority #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HintPriority -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HintPriority -> r #

gmapQ :: (forall d. Data d => d -> u) -> HintPriority -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HintPriority -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HintPriority -> m HintPriority #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HintPriority -> m HintPriority #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HintPriority -> m HintPriority #

Bounded HintPriority 
Instance details

Defined in SDL.Hint

Enum HintPriority 
Instance details

Defined in SDL.Hint

Generic HintPriority 
Instance details

Defined in SDL.Hint

Associated Types

type Rep HintPriority :: Type -> Type #

Read HintPriority 
Instance details

Defined in SDL.Hint

Show HintPriority 
Instance details

Defined in SDL.Hint

Eq HintPriority 
Instance details

Defined in SDL.Hint

Ord HintPriority 
Instance details

Defined in SDL.Hint

type Rep HintPriority 
Instance details

Defined in SDL.Hint

type Rep HintPriority = D1 ('MetaData "HintPriority" "SDL.Hint" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "DefaultPriority" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NormalPriority" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverridePriority" 'PrefixI 'False) (U1 :: Type -> Type)))

data BlendMode #

Blend modes used in copy and drawing operations.

Constructors

BlendNone

No blending

BlendAlphaBlend

Alpha blending.

dstRGB = (srcRGB * srcA) + (dstRGB * (1-srcA))
dstA = srcA + (dstA * (1-srcA))
BlendAdditive

Additive blending

dstRGB = (srcRGB * srcA) + dstRGB
dstA = dstA
BlendMod

Color modulate

@ dstRGB = srcRGB * dstRGB dstA = dstA

Instances

Instances details
Data BlendMode 
Instance details

Defined in SDL.Video.Renderer

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BlendMode -> c BlendMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BlendMode #

toConstr :: BlendMode -> Constr #

dataTypeOf :: BlendMode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BlendMode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BlendMode) #

gmapT :: (forall b. Data b => b -> b) -> BlendMode -> BlendMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BlendMode -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BlendMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> BlendMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BlendMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BlendMode -> m BlendMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BlendMode -> m BlendMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BlendMode -> m BlendMode #

Bounded BlendMode 
Instance details

Defined in SDL.Video.Renderer

Enum BlendMode 
Instance details

Defined in SDL.Video.Renderer

Generic BlendMode 
Instance details

Defined in SDL.Video.Renderer

Associated Types

type Rep BlendMode :: Type -> Type #

Read BlendMode 
Instance details

Defined in SDL.Video.Renderer

Show BlendMode 
Instance details

Defined in SDL.Video.Renderer

Eq BlendMode 
Instance details

Defined in SDL.Video.Renderer

Ord BlendMode 
Instance details

Defined in SDL.Video.Renderer

FromNumber BlendMode Word32 
Instance details

Defined in SDL.Video.Renderer

ToNumber BlendMode Word32 
Instance details

Defined in SDL.Video.Renderer

Methods

toNumber :: BlendMode -> Word32 #

type Rep BlendMode 
Instance details

Defined in SDL.Video.Renderer

type Rep BlendMode = D1 ('MetaData "BlendMode" "SDL.Video.Renderer" "sdl2-2.5.5.0-45393fc3" 'False) ((C1 ('MetaCons "BlendNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlendAlphaBlend" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BlendAdditive" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlendMod" 'PrefixI 'False) (U1 :: Type -> Type)))

data AudioFormat sampleType where #

Information about what format an audio bytestream is. The type variable t indicates the type used for audio buffer samples. It is determined by the choice of the provided SampleBitSize. For example:

AudioFormat UnsignedInteger Sample8Bit Native :: AudioFormat Word8

Indicating that an 8-bit audio format in the platforms native endianness uses a buffer of Word8 values.

Instances

Instances details
Show (AudioFormat sampleType) 
Instance details

Defined in SDL.Audio

Methods

showsPrec :: Int -> AudioFormat sampleType -> ShowS #

show :: AudioFormat sampleType -> String #

showList :: [AudioFormat sampleType] -> ShowS #

Eq (AudioFormat sampleType) 
Instance details

Defined in SDL.Audio

Methods

(==) :: AudioFormat sampleType -> AudioFormat sampleType -> Bool #

(/=) :: AudioFormat sampleType -> AudioFormat sampleType -> Bool #

Ord (AudioFormat sampleType) 
Instance details

Defined in SDL.Audio

Methods

compare :: AudioFormat sampleType -> AudioFormat sampleType -> Ordering #

(<) :: AudioFormat sampleType -> AudioFormat sampleType -> Bool #

(<=) :: AudioFormat sampleType -> AudioFormat sampleType -> Bool #

(>) :: AudioFormat sampleType -> AudioFormat sampleType -> Bool #

(>=) :: AudioFormat sampleType -> AudioFormat sampleType -> Bool #

max :: AudioFormat sampleType -> AudioFormat sampleType -> AudioFormat sampleType #

min :: AudioFormat sampleType -> AudioFormat sampleType -> AudioFormat sampleType #

data Surface #

Constructors

Surface (Ptr Surface) (Maybe (IOVector Word8)) 

data RendererInfo #

Information about an instantiated Renderer.

Constructors

RendererInfo 

Fields

Instances

Instances details
Generic RendererInfo 
Instance details

Defined in SDL.Video.Renderer

Associated Types

type Rep RendererInfo :: Type -> Type #

Read RendererInfo 
Instance details

Defined in SDL.Video.Renderer

Show RendererInfo 
Instance details

Defined in SDL.Video.Renderer

Eq RendererInfo 
Instance details

Defined in SDL.Video.Renderer

Ord RendererInfo 
Instance details

Defined in SDL.Video.Renderer

type Rep RendererInfo 
Instance details

Defined in SDL.Video.Renderer

type Rep RendererInfo = D1 ('MetaData "RendererInfo" "SDL.Video.Renderer" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "RendererInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "rendererInfoName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "rendererInfoFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RendererConfig) :*: S1 ('MetaSel ('Just "rendererInfoNumTextureFormats") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32))) :*: (S1 ('MetaSel ('Just "rendererInfoTextureFormats") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PixelFormat]) :*: (S1 ('MetaSel ('Just "rendererInfoMaxTextureWidth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt) :*: S1 ('MetaSel ('Just "rendererInfoMaxTextureHeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt)))))

data PixelFormat #

Instances

Instances details
Data PixelFormat 
Instance details

Defined in SDL.Video.Renderer

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PixelFormat -> c PixelFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PixelFormat #

toConstr :: PixelFormat -> Constr #

dataTypeOf :: PixelFormat -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PixelFormat) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PixelFormat) #

gmapT :: (forall b. Data b => b -> b) -> PixelFormat -> PixelFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PixelFormat -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PixelFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> PixelFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PixelFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PixelFormat -> m PixelFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PixelFormat -> m PixelFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PixelFormat -> m PixelFormat #

Generic PixelFormat 
Instance details

Defined in SDL.Video.Renderer

Associated Types

type Rep PixelFormat :: Type -> Type #

Read PixelFormat 
Instance details

Defined in SDL.Video.Renderer

Show PixelFormat 
Instance details

Defined in SDL.Video.Renderer

Eq PixelFormat 
Instance details

Defined in SDL.Video.Renderer

Ord PixelFormat 
Instance details

Defined in SDL.Video.Renderer

FromNumber PixelFormat Word32 
Instance details

Defined in SDL.Video.Renderer

ToNumber PixelFormat Word32 
Instance details

Defined in SDL.Video.Renderer

type Rep PixelFormat 
Instance details

Defined in SDL.Video.Renderer

type Rep PixelFormat = D1 ('MetaData "PixelFormat" "SDL.Video.Renderer" "sdl2-2.5.5.0-45393fc3" 'False) (((((C1 ('MetaCons "Unknown" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word32)) :+: C1 ('MetaCons "Index1LSB" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Index1MSB" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Index4LSB" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Index4MSB" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Index8" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RGB332" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RGB444" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RGB555" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "BGR555" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ARGB4444" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RGBA4444" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ABGR4444" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "BGRA4444" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ARGB1555" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RGBA5551" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ABGR1555" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BGRA5551" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "RGB565" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BGR565" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RGB24" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BGR24" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "RGB888" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RGBX8888" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BGR888" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BGRX8888" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ARGB8888" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "RGBA8888" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ABGR8888" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BGRA8888" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ARGB2101010" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "YV12" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IYUV" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "YUY2" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UYVY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "YVYU" 'PrefixI 'False) (U1 :: Type -> Type)))))))

data Palette #

Instances

Instances details
Eq Palette 
Instance details

Defined in SDL.Video.Renderer

Methods

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

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

data Keysym #

Information about a key press or key release event.

Constructors

Keysym 

Fields

Instances

Instances details
Data Keysym 
Instance details

Defined in SDL.Input.Keyboard

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Keysym -> c Keysym #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Keysym #

toConstr :: Keysym -> Constr #

dataTypeOf :: Keysym -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Keysym) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Keysym) #

gmapT :: (forall b. Data b => b -> b) -> Keysym -> Keysym #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Keysym -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Keysym -> r #

gmapQ :: (forall d. Data d => d -> u) -> Keysym -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Keysym -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Keysym -> m Keysym #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Keysym -> m Keysym #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Keysym -> m Keysym #

Generic Keysym 
Instance details

Defined in SDL.Input.Keyboard

Associated Types

type Rep Keysym :: Type -> Type #

Methods

from :: Keysym -> Rep Keysym x #

to :: Rep Keysym x -> Keysym #

Read Keysym 
Instance details

Defined in SDL.Input.Keyboard

Show Keysym 
Instance details

Defined in SDL.Input.Keyboard

Eq Keysym 
Instance details

Defined in SDL.Input.Keyboard

Methods

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

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

Ord Keysym 
Instance details

Defined in SDL.Input.Keyboard

type Rep Keysym 
Instance details

Defined in SDL.Input.Keyboard

type Rep Keysym = D1 ('MetaData "Keysym" "SDL.Input.Keyboard" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "Keysym" 'PrefixI 'True) (S1 ('MetaSel ('Just "keysymScancode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Scancode) :*: (S1 ('MetaSel ('Just "keysymKeycode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Keycode) :*: S1 ('MetaSel ('Just "keysymModifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KeyModifier))))

data DisplayMode #

Constructors

DisplayMode 

Fields

Instances

Instances details
Generic DisplayMode 
Instance details

Defined in SDL.Video

Associated Types

type Rep DisplayMode :: Type -> Type #

Read DisplayMode 
Instance details

Defined in SDL.Video

Show DisplayMode 
Instance details

Defined in SDL.Video

Eq DisplayMode 
Instance details

Defined in SDL.Video

Ord DisplayMode 
Instance details

Defined in SDL.Video

type Rep DisplayMode 
Instance details

Defined in SDL.Video

type Rep DisplayMode = D1 ('MetaData "DisplayMode" "SDL.Video" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "DisplayMode" 'PrefixI 'True) (S1 ('MetaSel ('Just "displayModeFormat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PixelFormat) :*: (S1 ('MetaSel ('Just "displayModeSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (V2 CInt)) :*: S1 ('MetaSel ('Just "displayModeRefreshRate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt))))

data AudioSpec #

AudioSpec is the concrete specification of how an AudioDevice was sucessfully opened. Unlike OpenDeviceSpec, which specifies what you want, AudioSpec specifies what you have.

Constructors

AudioSpec 

Fields

data Window #

Instances

Instances details
Data Window 
Instance details

Defined in SDL.Internal.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Window -> c Window #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Window #

toConstr :: Window -> Constr #

dataTypeOf :: Window -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Window) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Window) #

gmapT :: (forall b. Data b => b -> b) -> Window -> Window #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Window -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Window -> r #

gmapQ :: (forall d. Data d => d -> u) -> Window -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Window -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Window -> m Window #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Window -> m Window #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Window -> m Window #

Generic Window 
Instance details

Defined in SDL.Internal.Types

Associated Types

type Rep Window :: Type -> Type #

Methods

from :: Window -> Rep Window x #

to :: Rep Window x -> Window #

Show Window 
Instance details

Defined in SDL.Internal.Types

Eq Window 
Instance details

Defined in SDL.Internal.Types

Methods

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

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

Ord Window 
Instance details

Defined in SDL.Internal.Types

type Rep Window 
Instance details

Defined in SDL.Internal.Types

type Rep Window = D1 ('MetaData "Window" "SDL.Internal.Types" "sdl2-2.5.5.0-45393fc3" 'True) (C1 ('MetaCons "Window" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

data Texture #

Instances

Instances details
Eq Texture 
Instance details

Defined in SDL.Video.Renderer

Methods

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

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

data Renderer #

An SDL rendering device. This can be created with createRenderer.

Instances

Instances details
Data Renderer 
Instance details

Defined in SDL.Internal.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Renderer -> c Renderer #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Renderer #

toConstr :: Renderer -> Constr #

dataTypeOf :: Renderer -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Renderer) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Renderer) #

gmapT :: (forall b. Data b => b -> b) -> Renderer -> Renderer #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Renderer -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Renderer -> r #

gmapQ :: (forall d. Data d => d -> u) -> Renderer -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Renderer -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Renderer -> m Renderer #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Renderer -> m Renderer #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Renderer -> m Renderer #

Generic Renderer 
Instance details

Defined in SDL.Internal.Types

Associated Types

type Rep Renderer :: Type -> Type #

Methods

from :: Renderer -> Rep Renderer x #

to :: Rep Renderer x -> Renderer #

Show Renderer 
Instance details

Defined in SDL.Internal.Types

Eq Renderer 
Instance details

Defined in SDL.Internal.Types

Ord Renderer 
Instance details

Defined in SDL.Internal.Types

type Rep Renderer 
Instance details

Defined in SDL.Internal.Types

type Rep Renderer = D1 ('MetaData "Renderer" "SDL.Internal.Types" "sdl2-2.5.5.0-45393fc3" 'True) (C1 ('MetaCons "Renderer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Renderer)))

data Joystick #

Instances

Instances details
Data Joystick 
Instance details

Defined in SDL.Internal.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Joystick -> c Joystick #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Joystick #

toConstr :: Joystick -> Constr #

dataTypeOf :: Joystick -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Joystick) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Joystick) #

gmapT :: (forall b. Data b => b -> b) -> Joystick -> Joystick #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Joystick -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Joystick -> r #

gmapQ :: (forall d. Data d => d -> u) -> Joystick -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Joystick -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Joystick -> m Joystick #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Joystick -> m Joystick #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Joystick -> m Joystick #

Generic Joystick 
Instance details

Defined in SDL.Internal.Types

Associated Types

type Rep Joystick :: Type -> Type #

Methods

from :: Joystick -> Rep Joystick x #

to :: Rep Joystick x -> Joystick #

Show Joystick 
Instance details

Defined in SDL.Internal.Types

Eq Joystick 
Instance details

Defined in SDL.Internal.Types

Ord Joystick 
Instance details

Defined in SDL.Internal.Types

type Rep Joystick 
Instance details

Defined in SDL.Internal.Types

type Rep Joystick = D1 ('MetaData "Joystick" "SDL.Internal.Types" "sdl2-2.5.5.0-45393fc3" 'True) (C1 ('MetaCons "Joystick" 'PrefixI 'True) (S1 ('MetaSel ('Just "joystickPtr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Joystick)))

data GLContext #

A created OpenGL context.

Instances

Instances details
Eq GLContext 
Instance details

Defined in SDL.Video.OpenGL

data Cursor #

Instances

Instances details
Eq Cursor 
Instance details

Defined in SDL.Input.Mouse

Methods

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

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

type TimerCallback = Word32 -> IO RetriggerTimer #

A TimerCallback is called with the interval size of the callback. It can return information as to whether or not the timer should continue to exist.

data Charge #

Information about how much charge a battery has.

Constructors

Charge 

Fields

Instances

Instances details
Generic Charge 
Instance details

Defined in SDL.Power

Associated Types

type Rep Charge :: Type -> Type #

Methods

from :: Charge -> Rep Charge x #

to :: Rep Charge x -> Charge #

Read Charge 
Instance details

Defined in SDL.Power

Show Charge 
Instance details

Defined in SDL.Power

Eq Charge 
Instance details

Defined in SDL.Power

Methods

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

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

Ord Charge 
Instance details

Defined in SDL.Power

type Rep Charge 
Instance details

Defined in SDL.Power

type Rep Charge = D1 ('MetaData "Charge" "SDL.Power" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "Charge" 'PrefixI 'True) (S1 ('MetaSel ('Just "chargeSecondsLeft") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CInt)) :*: S1 ('MetaSel ('Just "chargePercent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CInt))))

data BatteryState #

Information on battery consumption for battery powered devices

Constructors

Draining

The battery is currently being drained.

Charged

The battery is fully charged.

Charging

The device is plugged in and the battery is charging.

Instances

Instances details
Data BatteryState 
Instance details

Defined in SDL.Power

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BatteryState -> c BatteryState #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BatteryState #

toConstr :: BatteryState -> Constr #

dataTypeOf :: BatteryState -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BatteryState) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BatteryState) #

gmapT :: (forall b. Data b => b -> b) -> BatteryState -> BatteryState #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BatteryState -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BatteryState -> r #

gmapQ :: (forall d. Data d => d -> u) -> BatteryState -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BatteryState -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BatteryState -> m BatteryState #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BatteryState -> m BatteryState #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BatteryState -> m BatteryState #

Bounded BatteryState 
Instance details

Defined in SDL.Power

Enum BatteryState 
Instance details

Defined in SDL.Power

Generic BatteryState 
Instance details

Defined in SDL.Power

Associated Types

type Rep BatteryState :: Type -> Type #

Read BatteryState 
Instance details

Defined in SDL.Power

Show BatteryState 
Instance details

Defined in SDL.Power

Eq BatteryState 
Instance details

Defined in SDL.Power

Ord BatteryState 
Instance details

Defined in SDL.Power

type Rep BatteryState 
Instance details

Defined in SDL.Power

type Rep BatteryState = D1 ('MetaData "BatteryState" "SDL.Power" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "Draining" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Charged" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Charging" 'PrefixI 'False) (U1 :: Type -> Type)))

data KeyModifier #

Information about which keys are currently held down. Use getModState to generate this information.

Instances

Instances details
Data KeyModifier 
Instance details

Defined in SDL.Input.Keyboard

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> KeyModifier -> c KeyModifier #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c KeyModifier #

toConstr :: KeyModifier -> Constr #

dataTypeOf :: KeyModifier -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c KeyModifier) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KeyModifier) #

gmapT :: (forall b. Data b => b -> b) -> KeyModifier -> KeyModifier #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KeyModifier -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KeyModifier -> r #

gmapQ :: (forall d. Data d => d -> u) -> KeyModifier -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> KeyModifier -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> KeyModifier -> m KeyModifier #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KeyModifier -> m KeyModifier #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KeyModifier -> m KeyModifier #

Generic KeyModifier 
Instance details

Defined in SDL.Input.Keyboard

Associated Types

type Rep KeyModifier :: Type -> Type #

Read KeyModifier 
Instance details

Defined in SDL.Input.Keyboard

Show KeyModifier 
Instance details

Defined in SDL.Input.Keyboard

Eq KeyModifier 
Instance details

Defined in SDL.Input.Keyboard

Ord KeyModifier 
Instance details

Defined in SDL.Input.Keyboard

FromNumber KeyModifier Word32 
Instance details

Defined in SDL.Input.Keyboard

ToNumber KeyModifier Word32 
Instance details

Defined in SDL.Input.Keyboard

type Rep KeyModifier 
Instance details

Defined in SDL.Input.Keyboard

type Rep KeyModifier = D1 ('MetaData "KeyModifier" "SDL.Input.Keyboard" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "KeyModifier" 'PrefixI 'True) (((S1 ('MetaSel ('Just "keyModifierLeftShift") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "keyModifierRightShift") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "keyModifierLeftCtrl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "keyModifierRightCtrl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "keyModifierLeftAlt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "keyModifierRightAlt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "keyModifierLeftGUI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "keyModifierRightGUI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: (S1 ('MetaSel ('Just "keyModifierNumLock") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "keyModifierCapsLock") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "keyModifierAltGr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))))

data AudioDriver #

An abstract description of an audio driver on the host machine.

Instances

Instances details
Show AudioDriver 
Instance details

Defined in SDL.Audio

Eq AudioDriver 
Instance details

Defined in SDL.Audio

data AudioDeviceStatus #

Opened devices are always Playing or Paused in normal circumstances. A failing device may change its status to Stopped at any time, and closing a device will progress to Stopped too.

Constructors

Playing

The AudioDevice is playing.

Paused

The AudioDevice is paused.

Stopped

The AudioDevice is stopped.

Instances

Instances details
Data AudioDeviceStatus 
Instance details

Defined in SDL.Audio

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AudioDeviceStatus -> c AudioDeviceStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AudioDeviceStatus #

toConstr :: AudioDeviceStatus -> Constr #

dataTypeOf :: AudioDeviceStatus -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AudioDeviceStatus) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AudioDeviceStatus) #

gmapT :: (forall b. Data b => b -> b) -> AudioDeviceStatus -> AudioDeviceStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AudioDeviceStatus -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AudioDeviceStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> AudioDeviceStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AudioDeviceStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AudioDeviceStatus -> m AudioDeviceStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AudioDeviceStatus -> m AudioDeviceStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AudioDeviceStatus -> m AudioDeviceStatus #

Bounded AudioDeviceStatus 
Instance details

Defined in SDL.Audio

Enum AudioDeviceStatus 
Instance details

Defined in SDL.Audio

Generic AudioDeviceStatus 
Instance details

Defined in SDL.Audio

Associated Types

type Rep AudioDeviceStatus :: Type -> Type #

Read AudioDeviceStatus 
Instance details

Defined in SDL.Audio

Show AudioDeviceStatus 
Instance details

Defined in SDL.Audio

Eq AudioDeviceStatus 
Instance details

Defined in SDL.Audio

Ord AudioDeviceStatus 
Instance details

Defined in SDL.Audio

type Rep AudioDeviceStatus 
Instance details

Defined in SDL.Audio

type Rep AudioDeviceStatus = D1 ('MetaData "AudioDeviceStatus" "SDL.Audio" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "Playing" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Paused" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Stopped" 'PrefixI 'False) (U1 :: Type -> Type)))

data PlaybackState #

Whether to allow an AudioDevice to play sound or remain paused.

Constructors

Pause

Pause the AudioDevice, which will stop producing/capturing audio.

Play

Resume the AudioDevice.

Instances

Instances details
Data PlaybackState 
Instance details

Defined in SDL.Audio

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlaybackState -> c PlaybackState #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlaybackState #

toConstr :: PlaybackState -> Constr #

dataTypeOf :: PlaybackState -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PlaybackState) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlaybackState) #

gmapT :: (forall b. Data b => b -> b) -> PlaybackState -> PlaybackState #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlaybackState -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlaybackState -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlaybackState -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlaybackState -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlaybackState -> m PlaybackState #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlaybackState -> m PlaybackState #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlaybackState -> m PlaybackState #

Bounded PlaybackState 
Instance details

Defined in SDL.Audio

Enum PlaybackState 
Instance details

Defined in SDL.Audio

Generic PlaybackState 
Instance details

Defined in SDL.Audio

Associated Types

type Rep PlaybackState :: Type -> Type #

Read PlaybackState 
Instance details

Defined in SDL.Audio

Show PlaybackState 
Instance details

Defined in SDL.Audio

Eq PlaybackState 
Instance details

Defined in SDL.Audio

Ord PlaybackState 
Instance details

Defined in SDL.Audio

type Rep PlaybackState 
Instance details

Defined in SDL.Audio

type Rep PlaybackState = D1 ('MetaData "PlaybackState" "SDL.Audio" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "Pause" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Play" 'PrefixI 'False) (U1 :: Type -> Type))

data LockState #

Whether a device should be locked or unlocked.

Constructors

Locked

Lock the device, preventing the callback from producing data.

Unlocked

Unlock the device, resuming calls to the callback.

Instances

Instances details
Data LockState 
Instance details

Defined in SDL.Audio

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LockState -> c LockState #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LockState #

toConstr :: LockState -> Constr #

dataTypeOf :: LockState -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LockState) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LockState) #

gmapT :: (forall b. Data b => b -> b) -> LockState -> LockState #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LockState -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LockState -> r #

gmapQ :: (forall d. Data d => d -> u) -> LockState -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LockState -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LockState -> m LockState #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LockState -> m LockState #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LockState -> m LockState #

Bounded LockState 
Instance details

Defined in SDL.Audio

Enum LockState 
Instance details

Defined in SDL.Audio

Generic LockState 
Instance details

Defined in SDL.Audio

Associated Types

type Rep LockState :: Type -> Type #

Read LockState 
Instance details

Defined in SDL.Audio

Show LockState 
Instance details

Defined in SDL.Audio

Eq LockState 
Instance details

Defined in SDL.Audio

Ord LockState 
Instance details

Defined in SDL.Audio

type Rep LockState 
Instance details

Defined in SDL.Audio

type Rep LockState = D1 ('MetaData "LockState" "SDL.Audio" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "Locked" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unlocked" 'PrefixI 'False) (U1 :: Type -> Type))

data Changeable a #

Used to indicate to SDL whether it is allowed to open other audio devices (if a property is marked as a Desire) or if it should fail if the device is unavailable (Mandate).

Constructors

Mandate !a

Mandate this exact property value, and fail if a matching audio device cannot be found.

Desire !a

Desire this property value, but allow other audio devices to be opened.

Instances

Instances details
Foldable Changeable 
Instance details

Defined in SDL.Audio

Methods

fold :: Monoid m => Changeable m -> m #

foldMap :: Monoid m => (a -> m) -> Changeable a -> m #

foldMap' :: Monoid m => (a -> m) -> Changeable a -> m #

foldr :: (a -> b -> b) -> b -> Changeable a -> b #

foldr' :: (a -> b -> b) -> b -> Changeable a -> b #

foldl :: (b -> a -> b) -> b -> Changeable a -> b #

foldl' :: (b -> a -> b) -> b -> Changeable a -> b #

foldr1 :: (a -> a -> a) -> Changeable a -> a #

foldl1 :: (a -> a -> a) -> Changeable a -> a #

toList :: Changeable a -> [a] #

null :: Changeable a -> Bool #

length :: Changeable a -> Int #

elem :: Eq a => a -> Changeable a -> Bool #

maximum :: Ord a => Changeable a -> a #

minimum :: Ord a => Changeable a -> a #

sum :: Num a => Changeable a -> a #

product :: Num a => Changeable a -> a #

Traversable Changeable 
Instance details

Defined in SDL.Audio

Methods

traverse :: Applicative f => (a -> f b) -> Changeable a -> f (Changeable b) #

sequenceA :: Applicative f => Changeable (f a) -> f (Changeable a) #

mapM :: Monad m => (a -> m b) -> Changeable a -> m (Changeable b) #

sequence :: Monad m => Changeable (m a) -> m (Changeable a) #

Functor Changeable 
Instance details

Defined in SDL.Audio

Methods

fmap :: (a -> b) -> Changeable a -> Changeable b #

(<$) :: a -> Changeable b -> Changeable a #

Data a => Data (Changeable a) 
Instance details

Defined in SDL.Audio

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Changeable a -> c (Changeable a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Changeable a) #

toConstr :: Changeable a -> Constr #

dataTypeOf :: Changeable a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Changeable a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Changeable a)) #

gmapT :: (forall b. Data b => b -> b) -> Changeable a -> Changeable a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Changeable a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Changeable a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Changeable a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Changeable a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Changeable a -> m (Changeable a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Changeable a -> m (Changeable a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Changeable a -> m (Changeable a) #

Generic (Changeable a) 
Instance details

Defined in SDL.Audio

Associated Types

type Rep (Changeable a) :: Type -> Type #

Methods

from :: Changeable a -> Rep (Changeable a) x #

to :: Rep (Changeable a) x -> Changeable a #

Read a => Read (Changeable a) 
Instance details

Defined in SDL.Audio

Show a => Show (Changeable a) 
Instance details

Defined in SDL.Audio

Eq a => Eq (Changeable a) 
Instance details

Defined in SDL.Audio

Methods

(==) :: Changeable a -> Changeable a -> Bool #

(/=) :: Changeable a -> Changeable a -> Bool #

type Rep (Changeable a) 
Instance details

Defined in SDL.Audio

type Rep (Changeable a) = D1 ('MetaData "Changeable" "SDL.Audio" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "Mandate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)) :+: C1 ('MetaCons "Desire" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))

data AudioDeviceUsage #

How you intend to use an AudioDevice

Constructors

ForPlayback

The device will be used for sample playback.

ForCapture

The device will be used for sample capture.

Instances

Instances details
Data AudioDeviceUsage 
Instance details

Defined in SDL.Audio

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AudioDeviceUsage -> c AudioDeviceUsage #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AudioDeviceUsage #

toConstr :: AudioDeviceUsage -> Constr #

dataTypeOf :: AudioDeviceUsage -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AudioDeviceUsage) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AudioDeviceUsage) #

gmapT :: (forall b. Data b => b -> b) -> AudioDeviceUsage -> AudioDeviceUsage #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AudioDeviceUsage -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AudioDeviceUsage -> r #

gmapQ :: (forall d. Data d => d -> u) -> AudioDeviceUsage -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AudioDeviceUsage -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AudioDeviceUsage -> m AudioDeviceUsage #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AudioDeviceUsage -> m AudioDeviceUsage #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AudioDeviceUsage -> m AudioDeviceUsage #

Bounded AudioDeviceUsage 
Instance details

Defined in SDL.Audio

Enum AudioDeviceUsage 
Instance details

Defined in SDL.Audio

Generic AudioDeviceUsage 
Instance details

Defined in SDL.Audio

Associated Types

type Rep AudioDeviceUsage :: Type -> Type #

Read AudioDeviceUsage 
Instance details

Defined in SDL.Audio

Show AudioDeviceUsage 
Instance details

Defined in SDL.Audio

Eq AudioDeviceUsage 
Instance details

Defined in SDL.Audio

Ord AudioDeviceUsage 
Instance details

Defined in SDL.Audio

type Rep AudioDeviceUsage 
Instance details

Defined in SDL.Audio

type Rep AudioDeviceUsage = D1 ('MetaData "AudioDeviceUsage" "SDL.Audio" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "ForPlayback" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ForCapture" 'PrefixI 'False) (U1 :: Type -> Type))

data Channels #

How many channels audio should be played on

Constructors

Mono

A single speaker configuration

Stereo

A traditional left/right stereo system

Quad 
FivePointOne
  1. 1 surround sound

Instances

Instances details
Data Channels 
Instance details

Defined in SDL.Audio

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Channels -> c Channels #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Channels #

toConstr :: Channels -> Constr #

dataTypeOf :: Channels -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Channels) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Channels) #

gmapT :: (forall b. Data b => b -> b) -> Channels -> Channels #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Channels -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Channels -> r #

gmapQ :: (forall d. Data d => d -> u) -> Channels -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Channels -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Channels -> m Channels #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Channels -> m Channels #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Channels -> m Channels #

Bounded Channels 
Instance details

Defined in SDL.Audio

Enum Channels 
Instance details

Defined in SDL.Audio

Generic Channels 
Instance details

Defined in SDL.Audio

Associated Types

type Rep Channels :: Type -> Type #

Methods

from :: Channels -> Rep Channels x #

to :: Rep Channels x -> Channels #

Read Channels 
Instance details

Defined in SDL.Audio

Show Channels 
Instance details

Defined in SDL.Audio

Eq Channels 
Instance details

Defined in SDL.Audio

Ord Channels 
Instance details

Defined in SDL.Audio

type Rep Channels 
Instance details

Defined in SDL.Audio

type Rep Channels = D1 ('MetaData "Channels" "SDL.Audio" "sdl2-2.5.5.0-45393fc3" 'False) ((C1 ('MetaCons "Mono" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Stereo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Quad" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FivePointOne" 'PrefixI 'False) (U1 :: Type -> Type)))

data AudioDevice #

An open audio device. These can be created via openAudioDevice and should be closed with closeAudioDevice

Instances

Instances details
Eq AudioDevice 
Instance details

Defined in SDL.Audio

data OpenDeviceSpec #

A specification to openAudioDevice, indicating the desired output format. Note that many of these properties are Changeable, meaning that you can choose whether or not SDL should interpret your specification as an unbreakable request (Mandate), or as an approximation Desire.

Constructors

OpenDeviceSpec 

Fields

data Hint v where #

The Hint type exports a well-typed interface to SDL's concept of hints. This type has instances for both HasGetter and HasSetter, allowing you to get and set hints. Note that the HasSetter interface is fairly relaxed - if a hint cannot be set, the failure will be silently discarded. For more feedback and control when setting hints, see setHintWithPriority.

Instances

Instances details
HasGetter (Hint v) v 
Instance details

Defined in SDL.Hint

Methods

get :: MonadIO m => Hint v -> m v #

HasSetter (Hint v) v 
Instance details

Defined in SDL.Hint

Methods

($=) :: MonadIO m => Hint v -> v -> m () #

data VideoWinD3DCompilerOptions #

A hint that specifies which shader compiler to preload when using the Chrome ANGLE binaries. By default d3dcompiler_46.dll will be used.

Constructors

D3DVistaOrLater

Use d3dcompiler_46.dll, best for Vista or later

D3DXPSupport

Use d3dcompiler_43.dll for XP support

D3DNone

Do not load any library, useful if you compiled ANGLE from source and included the compiler in your binaries

Instances

Instances details
Data VideoWinD3DCompilerOptions 
Instance details

Defined in SDL.Hint

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VideoWinD3DCompilerOptions -> c VideoWinD3DCompilerOptions #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VideoWinD3DCompilerOptions #

toConstr :: VideoWinD3DCompilerOptions -> Constr #

dataTypeOf :: VideoWinD3DCompilerOptions -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c VideoWinD3DCompilerOptions) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VideoWinD3DCompilerOptions) #

gmapT :: (forall b. Data b => b -> b) -> VideoWinD3DCompilerOptions -> VideoWinD3DCompilerOptions #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VideoWinD3DCompilerOptions -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VideoWinD3DCompilerOptions -> r #

gmapQ :: (forall d. Data d => d -> u) -> VideoWinD3DCompilerOptions -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VideoWinD3DCompilerOptions -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VideoWinD3DCompilerOptions -> m VideoWinD3DCompilerOptions #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VideoWinD3DCompilerOptions -> m VideoWinD3DCompilerOptions #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VideoWinD3DCompilerOptions -> m VideoWinD3DCompilerOptions #

Bounded VideoWinD3DCompilerOptions 
Instance details

Defined in SDL.Hint

Enum VideoWinD3DCompilerOptions 
Instance details

Defined in SDL.Hint

Generic VideoWinD3DCompilerOptions 
Instance details

Defined in SDL.Hint

Associated Types

type Rep VideoWinD3DCompilerOptions :: Type -> Type #

Read VideoWinD3DCompilerOptions 
Instance details

Defined in SDL.Hint

Show VideoWinD3DCompilerOptions 
Instance details

Defined in SDL.Hint

Eq VideoWinD3DCompilerOptions 
Instance details

Defined in SDL.Hint

Ord VideoWinD3DCompilerOptions 
Instance details

Defined in SDL.Hint

type Rep VideoWinD3DCompilerOptions 
Instance details

Defined in SDL.Hint

type Rep VideoWinD3DCompilerOptions = D1 ('MetaData "VideoWinD3DCompilerOptions" "SDL.Hint" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "D3DVistaOrLater" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "D3DXPSupport" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "D3DNone" 'PrefixI 'False) (U1 :: Type -> Type)))

data RenderVSyncOptions #

A hint that specifies whether sync to vertical refresh is enabled or disabled to avoid tearing. By default SDL uses the flag passed into calls to create renderers.

Constructors

DisableVSync 
EnableVSync 

Instances

Instances details
Data RenderVSyncOptions 
Instance details

Defined in SDL.Hint

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RenderVSyncOptions -> c RenderVSyncOptions #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RenderVSyncOptions #

toConstr :: RenderVSyncOptions -> Constr #

dataTypeOf :: RenderVSyncOptions -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RenderVSyncOptions) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RenderVSyncOptions) #

gmapT :: (forall b. Data b => b -> b) -> RenderVSyncOptions -> RenderVSyncOptions #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RenderVSyncOptions -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RenderVSyncOptions -> r #

gmapQ :: (forall d. Data d => d -> u) -> RenderVSyncOptions -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RenderVSyncOptions -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RenderVSyncOptions -> m RenderVSyncOptions #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RenderVSyncOptions -> m RenderVSyncOptions #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RenderVSyncOptions -> m RenderVSyncOptions #

Bounded RenderVSyncOptions 
Instance details

Defined in SDL.Hint

Enum RenderVSyncOptions 
Instance details

Defined in SDL.Hint

Generic RenderVSyncOptions 
Instance details

Defined in SDL.Hint

Associated Types

type Rep RenderVSyncOptions :: Type -> Type #

Read RenderVSyncOptions 
Instance details

Defined in SDL.Hint

Show RenderVSyncOptions 
Instance details

Defined in SDL.Hint

Eq RenderVSyncOptions 
Instance details

Defined in SDL.Hint

Ord RenderVSyncOptions 
Instance details

Defined in SDL.Hint

type Rep RenderVSyncOptions 
Instance details

Defined in SDL.Hint

type Rep RenderVSyncOptions = D1 ('MetaData "RenderVSyncOptions" "SDL.Hint" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "DisableVSync" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EnableVSync" 'PrefixI 'False) (U1 :: Type -> Type))

data RenderScaleQuality #

A hint that specifies scaling quality. By default nearest pixel sampling is used.

Constructors

ScaleNearest

Nearest pixel sampling

ScaleLinear

linear filtering (supported by OpenGL and Direct3D)

ScaleBest

Anisotropic filtering (supported by Direct3D)

Instances

Instances details
Data RenderScaleQuality 
Instance details

Defined in SDL.Hint

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RenderScaleQuality -> c RenderScaleQuality #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RenderScaleQuality #

toConstr :: RenderScaleQuality -> Constr #

dataTypeOf :: RenderScaleQuality -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RenderScaleQuality) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RenderScaleQuality) #

gmapT :: (forall b. Data b => b -> b) -> RenderScaleQuality -> RenderScaleQuality #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RenderScaleQuality -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RenderScaleQuality -> r #

gmapQ :: (forall d. Data d => d -> u) -> RenderScaleQuality -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RenderScaleQuality -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RenderScaleQuality -> m RenderScaleQuality #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RenderScaleQuality -> m RenderScaleQuality #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RenderScaleQuality -> m RenderScaleQuality #

Bounded RenderScaleQuality 
Instance details

Defined in SDL.Hint

Enum RenderScaleQuality 
Instance details

Defined in SDL.Hint

Generic RenderScaleQuality 
Instance details

Defined in SDL.Hint

Associated Types

type Rep RenderScaleQuality :: Type -> Type #

Read RenderScaleQuality 
Instance details

Defined in SDL.Hint

Show RenderScaleQuality 
Instance details

Defined in SDL.Hint

Eq RenderScaleQuality 
Instance details

Defined in SDL.Hint

Ord RenderScaleQuality 
Instance details

Defined in SDL.Hint

type Rep RenderScaleQuality 
Instance details

Defined in SDL.Hint

type Rep RenderScaleQuality = D1 ('MetaData "RenderScaleQuality" "SDL.Hint" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "ScaleNearest" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ScaleLinear" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ScaleBest" 'PrefixI 'False) (U1 :: Type -> Type)))

data RenderOpenGLShaderOptions #

A hint that specifies whether the OpenGL render driver uses shaders. By default shaders are used if OpenGL supports them.

Constructors

DisableShaders

Disable shaders

EnableShaders

Enable shaders, if they are available

Instances

Instances details
Data RenderOpenGLShaderOptions 
Instance details

Defined in SDL.Hint

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RenderOpenGLShaderOptions -> c RenderOpenGLShaderOptions #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RenderOpenGLShaderOptions #

toConstr :: RenderOpenGLShaderOptions -> Constr #

dataTypeOf :: RenderOpenGLShaderOptions -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RenderOpenGLShaderOptions) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RenderOpenGLShaderOptions) #

gmapT :: (forall b. Data b => b -> b) -> RenderOpenGLShaderOptions -> RenderOpenGLShaderOptions #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RenderOpenGLShaderOptions -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RenderOpenGLShaderOptions -> r #

gmapQ :: (forall d. Data d => d -> u) -> RenderOpenGLShaderOptions -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RenderOpenGLShaderOptions -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RenderOpenGLShaderOptions -> m RenderOpenGLShaderOptions #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RenderOpenGLShaderOptions -> m RenderOpenGLShaderOptions #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RenderOpenGLShaderOptions -> m RenderOpenGLShaderOptions #

Bounded RenderOpenGLShaderOptions 
Instance details

Defined in SDL.Hint

Enum RenderOpenGLShaderOptions 
Instance details

Defined in SDL.Hint

Generic RenderOpenGLShaderOptions 
Instance details

Defined in SDL.Hint

Associated Types

type Rep RenderOpenGLShaderOptions :: Type -> Type #

Read RenderOpenGLShaderOptions 
Instance details

Defined in SDL.Hint

Show RenderOpenGLShaderOptions 
Instance details

Defined in SDL.Hint

Eq RenderOpenGLShaderOptions 
Instance details

Defined in SDL.Hint

Ord RenderOpenGLShaderOptions 
Instance details

Defined in SDL.Hint

type Rep RenderOpenGLShaderOptions 
Instance details

Defined in SDL.Hint

type Rep RenderOpenGLShaderOptions = D1 ('MetaData "RenderOpenGLShaderOptions" "SDL.Hint" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "DisableShaders" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EnableShaders" 'PrefixI 'False) (U1 :: Type -> Type))

data RenderDrivers #

A hint that specifies which render driver to use. By default the first one in the list that is available on the current platform is chosen.

Instances

Instances details
Data RenderDrivers 
Instance details

Defined in SDL.Hint

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RenderDrivers -> c RenderDrivers #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RenderDrivers #

toConstr :: RenderDrivers -> Constr #

dataTypeOf :: RenderDrivers -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RenderDrivers) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RenderDrivers) #

gmapT :: (forall b. Data b => b -> b) -> RenderDrivers -> RenderDrivers #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RenderDrivers -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RenderDrivers -> r #

gmapQ :: (forall d. Data d => d -> u) -> RenderDrivers -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RenderDrivers -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RenderDrivers -> m RenderDrivers #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RenderDrivers -> m RenderDrivers #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RenderDrivers -> m RenderDrivers #

Bounded RenderDrivers 
Instance details

Defined in SDL.Hint

Enum RenderDrivers 
Instance details

Defined in SDL.Hint

Generic RenderDrivers 
Instance details

Defined in SDL.Hint

Associated Types

type Rep RenderDrivers :: Type -> Type #

Read RenderDrivers 
Instance details

Defined in SDL.Hint

Show RenderDrivers 
Instance details

Defined in SDL.Hint

Eq RenderDrivers 
Instance details

Defined in SDL.Hint

Ord RenderDrivers 
Instance details

Defined in SDL.Hint

type Rep RenderDrivers 
Instance details

Defined in SDL.Hint

type Rep RenderDrivers = D1 ('MetaData "RenderDrivers" "SDL.Hint" "sdl2-2.5.5.0-45393fc3" 'False) ((C1 ('MetaCons "Direct3D" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OpenGL" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OpenGLES" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OpenGLES2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Software" 'PrefixI 'False) (U1 :: Type -> Type))))

data MouseModeWarpOptions #

A hint that specifies whether relative mouse mode is implemented using mouse warping. By default SDL will use raw input for relative mouse mode

Constructors

MouseRawInput

Relative mouse mode uses the raw input

MouseWarping

Relative mouse mode uses mouse warping

Instances

Instances details
Data MouseModeWarpOptions 
Instance details

Defined in SDL.Hint

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MouseModeWarpOptions -> c MouseModeWarpOptions #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MouseModeWarpOptions #

toConstr :: MouseModeWarpOptions -> Constr #

dataTypeOf :: MouseModeWarpOptions -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MouseModeWarpOptions) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MouseModeWarpOptions) #

gmapT :: (forall b. Data b => b -> b) -> MouseModeWarpOptions -> MouseModeWarpOptions #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MouseModeWarpOptions -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MouseModeWarpOptions -> r #

gmapQ :: (forall d. Data d => d -> u) -> MouseModeWarpOptions -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MouseModeWarpOptions -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MouseModeWarpOptions -> m MouseModeWarpOptions #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseModeWarpOptions -> m MouseModeWarpOptions #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseModeWarpOptions -> m MouseModeWarpOptions #

Bounded MouseModeWarpOptions 
Instance details

Defined in SDL.Hint

Enum MouseModeWarpOptions 
Instance details

Defined in SDL.Hint

Generic MouseModeWarpOptions 
Instance details

Defined in SDL.Hint

Associated Types

type Rep MouseModeWarpOptions :: Type -> Type #

Read MouseModeWarpOptions 
Instance details

Defined in SDL.Hint

Show MouseModeWarpOptions 
Instance details

Defined in SDL.Hint

Eq MouseModeWarpOptions 
Instance details

Defined in SDL.Hint

Ord MouseModeWarpOptions 
Instance details

Defined in SDL.Hint

type Rep MouseModeWarpOptions 
Instance details

Defined in SDL.Hint

type Rep MouseModeWarpOptions = D1 ('MetaData "MouseModeWarpOptions" "SDL.Hint" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "MouseRawInput" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MouseWarping" 'PrefixI 'False) (U1 :: Type -> Type))

data MacCTRLClickOptions #

A hint that specifies whether ctrl+click should generate a right-click event on Mac. By default holding ctrl while left clicking will not generate a right click event when on Mac.

Constructors

NoRightClick

Disable emulating right click

EmulateRightClick

Enable emulating right click

Instances

Instances details
Data MacCTRLClickOptions 
Instance details

Defined in SDL.Hint

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MacCTRLClickOptions -> c MacCTRLClickOptions #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MacCTRLClickOptions #

toConstr :: MacCTRLClickOptions -> Constr #

dataTypeOf :: MacCTRLClickOptions -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MacCTRLClickOptions) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MacCTRLClickOptions) #

gmapT :: (forall b. Data b => b -> b) -> MacCTRLClickOptions -> MacCTRLClickOptions #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MacCTRLClickOptions -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MacCTRLClickOptions -> r #

gmapQ :: (forall d. Data d => d -> u) -> MacCTRLClickOptions -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MacCTRLClickOptions -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MacCTRLClickOptions -> m MacCTRLClickOptions #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MacCTRLClickOptions -> m MacCTRLClickOptions #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MacCTRLClickOptions -> m MacCTRLClickOptions #

Bounded MacCTRLClickOptions 
Instance details

Defined in SDL.Hint

Enum MacCTRLClickOptions 
Instance details

Defined in SDL.Hint

Generic MacCTRLClickOptions 
Instance details

Defined in SDL.Hint

Associated Types

type Rep MacCTRLClickOptions :: Type -> Type #

Read MacCTRLClickOptions 
Instance details

Defined in SDL.Hint

Show MacCTRLClickOptions 
Instance details

Defined in SDL.Hint

Eq MacCTRLClickOptions 
Instance details

Defined in SDL.Hint

Ord MacCTRLClickOptions 
Instance details

Defined in SDL.Hint

type Rep MacCTRLClickOptions 
Instance details

Defined in SDL.Hint

type Rep MacCTRLClickOptions = D1 ('MetaData "MacCTRLClickOptions" "SDL.Hint" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "NoRightClick" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EmulateRightClick" 'PrefixI 'False) (U1 :: Type -> Type))

data FramebufferAccelerationOptions #

A hint that specifies how 3D acceleration is used to accelerate the SDL screen surface. By default SDL tries to make a best guess whether to use acceleration or not on each platform.

Constructors

Disable3D

Disable 3D acceleration

Enable3DDefault

Enable 3D acceleration, using the default renderer

Enable3DDirect3D

Enable 3D acceleration using Direct3D

Enable3DOpenGL

Enable 3D acceleration using OpenGL

Enable3DOpenGLES

Enable 3D acceleration using OpenGLES

Enable3DOpenGLES2

Enable 3D acceleration using OpenGLES2

Enable3DSoftware

Enable 3D acceleration using software rendering

Instances

Instances details
Data FramebufferAccelerationOptions 
Instance details

Defined in SDL.Hint

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FramebufferAccelerationOptions -> c FramebufferAccelerationOptions #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FramebufferAccelerationOptions #

toConstr :: FramebufferAccelerationOptions -> Constr #

dataTypeOf :: FramebufferAccelerationOptions -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FramebufferAccelerationOptions) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FramebufferAccelerationOptions) #

gmapT :: (forall b. Data b => b -> b) -> FramebufferAccelerationOptions -> FramebufferAccelerationOptions #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FramebufferAccelerationOptions -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FramebufferAccelerationOptions -> r #

gmapQ :: (forall d. Data d => d -> u) -> FramebufferAccelerationOptions -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FramebufferAccelerationOptions -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FramebufferAccelerationOptions -> m FramebufferAccelerationOptions #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FramebufferAccelerationOptions -> m FramebufferAccelerationOptions #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FramebufferAccelerationOptions -> m FramebufferAccelerationOptions #

Bounded FramebufferAccelerationOptions 
Instance details

Defined in SDL.Hint

Enum FramebufferAccelerationOptions 
Instance details

Defined in SDL.Hint

Generic FramebufferAccelerationOptions 
Instance details

Defined in SDL.Hint

Associated Types

type Rep FramebufferAccelerationOptions :: Type -> Type #

Read FramebufferAccelerationOptions 
Instance details

Defined in SDL.Hint

Show FramebufferAccelerationOptions 
Instance details

Defined in SDL.Hint

Eq FramebufferAccelerationOptions 
Instance details

Defined in SDL.Hint

Ord FramebufferAccelerationOptions 
Instance details

Defined in SDL.Hint

type Rep FramebufferAccelerationOptions 
Instance details

Defined in SDL.Hint

type Rep FramebufferAccelerationOptions = D1 ('MetaData "FramebufferAccelerationOptions" "SDL.Hint" "sdl2-2.5.5.0-45393fc3" 'False) ((C1 ('MetaCons "Disable3D" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Enable3DDefault" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Enable3DDirect3D" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Enable3DOpenGL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Enable3DOpenGLES" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Enable3DOpenGLES2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Enable3DSoftware" 'PrefixI 'False) (U1 :: Type -> Type))))

data AccelerometerJoystickOptions #

A hint that specifies whether the Android/iOS built-in accelerometer should be listed as a joystick device, rather than listing actual joysticks only. By default SDL will list real joysticks along with the accelerometer as if it were a 3 axis joystick.

Constructors

AccelerometerNotJoystick

List only real joysticks and accept input from them

AccelerometerIsJoystick

List real joysticks along with the accelerometer as if it were a 3 axis joystick (the default)

Instances

Instances details
Data AccelerometerJoystickOptions 
Instance details

Defined in SDL.Hint

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccelerometerJoystickOptions -> c AccelerometerJoystickOptions #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccelerometerJoystickOptions #

toConstr :: AccelerometerJoystickOptions -> Constr #

dataTypeOf :: AccelerometerJoystickOptions -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AccelerometerJoystickOptions) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccelerometerJoystickOptions) #

gmapT :: (forall b. Data b => b -> b) -> AccelerometerJoystickOptions -> AccelerometerJoystickOptions #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccelerometerJoystickOptions -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccelerometerJoystickOptions -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccelerometerJoystickOptions -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccelerometerJoystickOptions -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccelerometerJoystickOptions -> m AccelerometerJoystickOptions #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccelerometerJoystickOptions -> m AccelerometerJoystickOptions #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccelerometerJoystickOptions -> m AccelerometerJoystickOptions #

Bounded AccelerometerJoystickOptions 
Instance details

Defined in SDL.Hint

Enum AccelerometerJoystickOptions 
Instance details

Defined in SDL.Hint

Generic AccelerometerJoystickOptions 
Instance details

Defined in SDL.Hint

Associated Types

type Rep AccelerometerJoystickOptions :: Type -> Type #

Read AccelerometerJoystickOptions 
Instance details

Defined in SDL.Hint

Show AccelerometerJoystickOptions 
Instance details

Defined in SDL.Hint

Eq AccelerometerJoystickOptions 
Instance details

Defined in SDL.Hint

Ord AccelerometerJoystickOptions 
Instance details

Defined in SDL.Hint

type Rep AccelerometerJoystickOptions 
Instance details

Defined in SDL.Hint

type Rep AccelerometerJoystickOptions = D1 ('MetaData "AccelerometerJoystickOptions" "SDL.Hint" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "AccelerometerNotJoystick" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AccelerometerIsJoystick" 'PrefixI 'False) (U1 :: Type -> Type))

data Timer #

A timer created by addTimer. This Timer can be removed with removeTimer.

data RetriggerTimer #

RetriggerTimer allows a callback to inform SDL if the timer should be retriggered or cancelled

Constructors

Reschedule Word32

Retrigger the timer again in a given number of milliseconds.

Cancel

Cancel future invocations of this timer.

Instances

Instances details
Data RetriggerTimer 
Instance details

Defined in SDL.Time

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RetriggerTimer -> c RetriggerTimer #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RetriggerTimer #

toConstr :: RetriggerTimer -> Constr #

dataTypeOf :: RetriggerTimer -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RetriggerTimer) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RetriggerTimer) #

gmapT :: (forall b. Data b => b -> b) -> RetriggerTimer -> RetriggerTimer #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RetriggerTimer -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RetriggerTimer -> r #

gmapQ :: (forall d. Data d => d -> u) -> RetriggerTimer -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RetriggerTimer -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RetriggerTimer -> m RetriggerTimer #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RetriggerTimer -> m RetriggerTimer #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RetriggerTimer -> m RetriggerTimer #

Generic RetriggerTimer 
Instance details

Defined in SDL.Time

Associated Types

type Rep RetriggerTimer :: Type -> Type #

Read RetriggerTimer 
Instance details

Defined in SDL.Time

Show RetriggerTimer 
Instance details

Defined in SDL.Time

Eq RetriggerTimer 
Instance details

Defined in SDL.Time

Ord RetriggerTimer 
Instance details

Defined in SDL.Time

type Rep RetriggerTimer 
Instance details

Defined in SDL.Time

type Rep RetriggerTimer = D1 ('MetaData "RetriggerTimer" "SDL.Time" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "Reschedule" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)) :+: C1 ('MetaCons "Cancel" 'PrefixI 'False) (U1 :: Type -> Type))

data JoyDeviceConnection #

Identifies whether a joystick has been connected or disconnected.

Instances

Instances details
Data JoyDeviceConnection 
Instance details

Defined in SDL.Input.Joystick

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JoyDeviceConnection -> c JoyDeviceConnection #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JoyDeviceConnection #

toConstr :: JoyDeviceConnection -> Constr #

dataTypeOf :: JoyDeviceConnection -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JoyDeviceConnection) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JoyDeviceConnection) #

gmapT :: (forall b. Data b => b -> b) -> JoyDeviceConnection -> JoyDeviceConnection #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JoyDeviceConnection -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JoyDeviceConnection -> r #

gmapQ :: (forall d. Data d => d -> u) -> JoyDeviceConnection -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JoyDeviceConnection -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JoyDeviceConnection -> m JoyDeviceConnection #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JoyDeviceConnection -> m JoyDeviceConnection #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JoyDeviceConnection -> m JoyDeviceConnection #

Generic JoyDeviceConnection 
Instance details

Defined in SDL.Input.Joystick

Associated Types

type Rep JoyDeviceConnection :: Type -> Type #

Read JoyDeviceConnection 
Instance details

Defined in SDL.Input.Joystick

Show JoyDeviceConnection 
Instance details

Defined in SDL.Input.Joystick

Eq JoyDeviceConnection 
Instance details

Defined in SDL.Input.Joystick

Ord JoyDeviceConnection 
Instance details

Defined in SDL.Input.Joystick

FromNumber JoyDeviceConnection Word32 
Instance details

Defined in SDL.Input.Joystick

type Rep JoyDeviceConnection 
Instance details

Defined in SDL.Input.Joystick

type Rep JoyDeviceConnection = D1 ('MetaData "JoyDeviceConnection" "SDL.Input.Joystick" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "JoyDeviceAdded" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JoyDeviceRemoved" 'PrefixI 'False) (U1 :: Type -> Type))

data JoyHatPosition #

Identifies the state of the POV hat on a joystick.

Constructors

HatCentered

Centered position

HatUp

Up position

HatRight

Right position

HatDown

Down position

HatLeft

Left position

HatRightUp

Right-up position

HatRightDown

Right-down position

HatLeftUp

Left-up position

HatLeftDown

Left-down position

Instances

Instances details
Data JoyHatPosition 
Instance details

Defined in SDL.Input.Joystick

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JoyHatPosition -> c JoyHatPosition #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JoyHatPosition #

toConstr :: JoyHatPosition -> Constr #

dataTypeOf :: JoyHatPosition -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JoyHatPosition) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JoyHatPosition) #

gmapT :: (forall b. Data b => b -> b) -> JoyHatPosition -> JoyHatPosition #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JoyHatPosition -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JoyHatPosition -> r #

gmapQ :: (forall d. Data d => d -> u) -> JoyHatPosition -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JoyHatPosition -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JoyHatPosition -> m JoyHatPosition #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JoyHatPosition -> m JoyHatPosition #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JoyHatPosition -> m JoyHatPosition #

Generic JoyHatPosition 
Instance details

Defined in SDL.Input.Joystick

Associated Types

type Rep JoyHatPosition :: Type -> Type #

Read JoyHatPosition 
Instance details

Defined in SDL.Input.Joystick

Show JoyHatPosition 
Instance details

Defined in SDL.Input.Joystick

Eq JoyHatPosition 
Instance details

Defined in SDL.Input.Joystick

Ord JoyHatPosition 
Instance details

Defined in SDL.Input.Joystick

FromNumber JoyHatPosition Word8 
Instance details

Defined in SDL.Input.Joystick

type Rep JoyHatPosition 
Instance details

Defined in SDL.Input.Joystick

type Rep JoyHatPosition = D1 ('MetaData "JoyHatPosition" "SDL.Input.Joystick" "sdl2-2.5.5.0-45393fc3" 'False) (((C1 ('MetaCons "HatCentered" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HatUp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HatRight" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HatDown" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "HatLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HatRightUp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HatRightDown" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HatLeftUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HatLeftDown" 'PrefixI 'False) (U1 :: Type -> Type)))))

data JoyButtonState #

Identifies the state of a joystick button.

Instances

Instances details
Data JoyButtonState 
Instance details

Defined in SDL.Input.Joystick

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JoyButtonState -> c JoyButtonState #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JoyButtonState #

toConstr :: JoyButtonState -> Constr #

dataTypeOf :: JoyButtonState -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JoyButtonState) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JoyButtonState) #

gmapT :: (forall b. Data b => b -> b) -> JoyButtonState -> JoyButtonState #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JoyButtonState -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JoyButtonState -> r #

gmapQ :: (forall d. Data d => d -> u) -> JoyButtonState -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JoyButtonState -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JoyButtonState -> m JoyButtonState #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JoyButtonState -> m JoyButtonState #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JoyButtonState -> m JoyButtonState #

Generic JoyButtonState 
Instance details

Defined in SDL.Input.Joystick

Associated Types

type Rep JoyButtonState :: Type -> Type #

Read JoyButtonState 
Instance details

Defined in SDL.Input.Joystick

Show JoyButtonState 
Instance details

Defined in SDL.Input.Joystick

Eq JoyButtonState 
Instance details

Defined in SDL.Input.Joystick

Ord JoyButtonState 
Instance details

Defined in SDL.Input.Joystick

FromNumber JoyButtonState Word8 
Instance details

Defined in SDL.Input.Joystick

type Rep JoyButtonState 
Instance details

Defined in SDL.Input.Joystick

type Rep JoyButtonState = D1 ('MetaData "JoyButtonState" "SDL.Input.Joystick" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "JoyButtonPressed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JoyButtonReleased" 'PrefixI 'False) (U1 :: Type -> Type))

data JoystickDevice #

A description of joystick that can be opened using openJoystick. To retrieve a list of connected joysticks, use availableJoysticks.

Instances

Instances details
Generic JoystickDevice 
Instance details

Defined in SDL.Input.Joystick

Associated Types

type Rep JoystickDevice :: Type -> Type #

Read JoystickDevice 
Instance details

Defined in SDL.Input.Joystick

Show JoystickDevice 
Instance details

Defined in SDL.Input.Joystick

Eq JoystickDevice 
Instance details

Defined in SDL.Input.Joystick

Ord JoystickDevice 
Instance details

Defined in SDL.Input.Joystick

type Rep JoystickDevice 
Instance details

Defined in SDL.Input.Joystick

type Rep JoystickDevice = D1 ('MetaData "JoystickDevice" "SDL.Input.Joystick" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "JoystickDevice" 'PrefixI 'True) (S1 ('MetaSel ('Just "joystickDeviceName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "joystickDeviceId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt)))

data SwapInterval #

The swap interval for the current OpenGL context.

Constructors

ImmediateUpdates

No vertical retrace synchronization

SynchronizedUpdates

The buffer swap is synchronized with the vertical retrace

LateSwapTearing 

Instances

Instances details
Data SwapInterval 
Instance details

Defined in SDL.Video.OpenGL

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SwapInterval -> c SwapInterval #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SwapInterval #

toConstr :: SwapInterval -> Constr #

dataTypeOf :: SwapInterval -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SwapInterval) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SwapInterval) #

gmapT :: (forall b. Data b => b -> b) -> SwapInterval -> SwapInterval #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SwapInterval -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SwapInterval -> r #

gmapQ :: (forall d. Data d => d -> u) -> SwapInterval -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SwapInterval -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SwapInterval -> m SwapInterval #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SwapInterval -> m SwapInterval #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SwapInterval -> m SwapInterval #

Bounded SwapInterval 
Instance details

Defined in SDL.Video.OpenGL

Enum SwapInterval 
Instance details

Defined in SDL.Video.OpenGL

Generic SwapInterval 
Instance details

Defined in SDL.Video.OpenGL

Associated Types

type Rep SwapInterval :: Type -> Type #

Read SwapInterval 
Instance details

Defined in SDL.Video.OpenGL

Show SwapInterval 
Instance details

Defined in SDL.Video.OpenGL

Eq SwapInterval 
Instance details

Defined in SDL.Video.OpenGL

Ord SwapInterval 
Instance details

Defined in SDL.Video.OpenGL

FromNumber SwapInterval CInt 
Instance details

Defined in SDL.Video.OpenGL

ToNumber SwapInterval CInt 
Instance details

Defined in SDL.Video.OpenGL

type Rep SwapInterval 
Instance details

Defined in SDL.Video.OpenGL

type Rep SwapInterval = D1 ('MetaData "SwapInterval" "SDL.Video.OpenGL" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "ImmediateUpdates" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SynchronizedUpdates" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LateSwapTearing" 'PrefixI 'False) (U1 :: Type -> Type)))

data Profile #

The profile a driver should use when creating an OpenGL context.

Constructors

Core Mode CInt CInt

Use the OpenGL core profile, with a given major and minor version

Compatibility Mode CInt CInt

Use the compatibilty profile with a given major and minor version. The compatibility profile allows you to use deprecated functions such as immediate mode

ES Mode CInt CInt

Use an OpenGL profile for embedded systems

Instances

Instances details
Generic Profile 
Instance details

Defined in SDL.Video.OpenGL

Associated Types

type Rep Profile :: Type -> Type #

Methods

from :: Profile -> Rep Profile x #

to :: Rep Profile x -> Profile #

Read Profile 
Instance details

Defined in SDL.Video.OpenGL

Show Profile 
Instance details

Defined in SDL.Video.OpenGL

Eq Profile 
Instance details

Defined in SDL.Video.OpenGL

Methods

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

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

Ord Profile 
Instance details

Defined in SDL.Video.OpenGL

type Rep Profile 
Instance details

Defined in SDL.Video.OpenGL

data OpenGLConfig #

Configuration used when creating an OpenGL rendering context.

Constructors

OpenGLConfig 

Fields

Instances

Instances details
Generic OpenGLConfig 
Instance details

Defined in SDL.Video.OpenGL

Associated Types

type Rep OpenGLConfig :: Type -> Type #

Read OpenGLConfig 
Instance details

Defined in SDL.Video.OpenGL

Show OpenGLConfig 
Instance details

Defined in SDL.Video.OpenGL

Eq OpenGLConfig 
Instance details

Defined in SDL.Video.OpenGL

Ord OpenGLConfig 
Instance details

Defined in SDL.Video.OpenGL

type Rep OpenGLConfig 
Instance details

Defined in SDL.Video.OpenGL

type Rep OpenGLConfig = D1 ('MetaData "OpenGLConfig" "SDL.Video.OpenGL" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "OpenGLConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "glColorPrecision") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (V4 CInt)) :*: S1 ('MetaSel ('Just "glDepthPrecision") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt)) :*: (S1 ('MetaSel ('Just "glStencilPrecision") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt) :*: (S1 ('MetaSel ('Just "glMultisampleSamples") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt) :*: S1 ('MetaSel ('Just "glProfile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Profile)))))

data RendererConfig #

The configuration data used when creating windows.

Constructors

RendererConfig 

Fields

Instances

Instances details
Data RendererConfig 
Instance details

Defined in SDL.Video.Renderer

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RendererConfig -> c RendererConfig #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RendererConfig #

toConstr :: RendererConfig -> Constr #

dataTypeOf :: RendererConfig -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RendererConfig) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RendererConfig) #

gmapT :: (forall b. Data b => b -> b) -> RendererConfig -> RendererConfig #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RendererConfig -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RendererConfig -> r #

gmapQ :: (forall d. Data d => d -> u) -> RendererConfig -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RendererConfig -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RendererConfig -> m RendererConfig #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RendererConfig -> m RendererConfig #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RendererConfig -> m RendererConfig #

Generic RendererConfig 
Instance details

Defined in SDL.Video.Renderer

Associated Types

type Rep RendererConfig :: Type -> Type #

Read RendererConfig 
Instance details

Defined in SDL.Video.Renderer

Show RendererConfig 
Instance details

Defined in SDL.Video.Renderer

Eq RendererConfig 
Instance details

Defined in SDL.Video.Renderer

Ord RendererConfig 
Instance details

Defined in SDL.Video.Renderer

FromNumber RendererConfig Word32 
Instance details

Defined in SDL.Video.Renderer

ToNumber RendererConfig Word32 
Instance details

Defined in SDL.Video.Renderer

type Rep RendererConfig 
Instance details

Defined in SDL.Video.Renderer

type Rep RendererConfig = D1 ('MetaData "RendererConfig" "SDL.Video.Renderer" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "RendererConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "rendererType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RendererType) :*: S1 ('MetaSel ('Just "rendererTargetTexture") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

data RendererType #

Renderer acceleration mode

Constructors

UnacceleratedRenderer

The renderer does not use hardware acceleration

AcceleratedRenderer

The renderer uses hardware acceleration and refresh rate is ignored

AcceleratedVSyncRenderer

The renderer uses hardware acceleration and present is synchronized with the refresh rate

SoftwareRenderer

The renderer is a software fallback

Instances

Instances details
Data RendererType 
Instance details

Defined in SDL.Video.Renderer

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RendererType -> c RendererType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RendererType #

toConstr :: RendererType -> Constr #

dataTypeOf :: RendererType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RendererType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RendererType) #

gmapT :: (forall b. Data b => b -> b) -> RendererType -> RendererType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RendererType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RendererType -> r #

gmapQ :: (forall d. Data d => d -> u) -> RendererType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RendererType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RendererType -> m RendererType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RendererType -> m RendererType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RendererType -> m RendererType #

Bounded RendererType 
Instance details

Defined in SDL.Video.Renderer

Enum RendererType 
Instance details

Defined in SDL.Video.Renderer

Generic RendererType 
Instance details

Defined in SDL.Video.Renderer

Associated Types

type Rep RendererType :: Type -> Type #

Read RendererType 
Instance details

Defined in SDL.Video.Renderer

Show RendererType 
Instance details

Defined in SDL.Video.Renderer

Eq RendererType 
Instance details

Defined in SDL.Video.Renderer

Ord RendererType 
Instance details

Defined in SDL.Video.Renderer

type Rep RendererType 
Instance details

Defined in SDL.Video.Renderer

type Rep RendererType = D1 ('MetaData "RendererType" "SDL.Video.Renderer" "sdl2-2.5.5.0-45393fc3" 'False) ((C1 ('MetaCons "UnacceleratedRenderer" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AcceleratedRenderer" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AcceleratedVSyncRenderer" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SoftwareRenderer" 'PrefixI 'False) (U1 :: Type -> Type)))

data Rectangle a #

Constructors

Rectangle (Point V2 a) (V2 a) 

Instances

Instances details
Functor Rectangle 
Instance details

Defined in SDL.Video.Renderer

Methods

fmap :: (a -> b) -> Rectangle a -> Rectangle b #

(<$) :: a -> Rectangle b -> Rectangle a #

Storable a => Storable (Rectangle a) 
Instance details

Defined in SDL.Video.Renderer

Methods

sizeOf :: Rectangle a -> Int #

alignment :: Rectangle a -> Int #

peekElemOff :: Ptr (Rectangle a) -> Int -> IO (Rectangle a) #

pokeElemOff :: Ptr (Rectangle a) -> Int -> Rectangle a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rectangle a) #

pokeByteOff :: Ptr b -> Int -> Rectangle a -> IO () #

peek :: Ptr (Rectangle a) -> IO (Rectangle a) #

poke :: Ptr (Rectangle a) -> Rectangle a -> IO () #

Generic (Rectangle a) 
Instance details

Defined in SDL.Video.Renderer

Associated Types

type Rep (Rectangle a) :: Type -> Type #

Methods

from :: Rectangle a -> Rep (Rectangle a) x #

to :: Rep (Rectangle a) x -> Rectangle a #

Read a => Read (Rectangle a) 
Instance details

Defined in SDL.Video.Renderer

Show a => Show (Rectangle a) 
Instance details

Defined in SDL.Video.Renderer

Eq a => Eq (Rectangle a) 
Instance details

Defined in SDL.Video.Renderer

Methods

(==) :: Rectangle a -> Rectangle a -> Bool #

(/=) :: Rectangle a -> Rectangle a -> Bool #

Ord a => Ord (Rectangle a) 
Instance details

Defined in SDL.Video.Renderer

type Rep (Rectangle a) 
Instance details

Defined in SDL.Video.Renderer

type Rep (Rectangle a) = D1 ('MetaData "Rectangle" "SDL.Video.Renderer" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "Rectangle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Point V2 a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (V2 a))))

data TextureInfo #

Constructors

TextureInfo 

Fields

Instances

Instances details
Generic TextureInfo 
Instance details

Defined in SDL.Video.Renderer

Associated Types

type Rep TextureInfo :: Type -> Type #

Read TextureInfo 
Instance details

Defined in SDL.Video.Renderer

Show TextureInfo 
Instance details

Defined in SDL.Video.Renderer

Eq TextureInfo 
Instance details

Defined in SDL.Video.Renderer

Ord TextureInfo 
Instance details

Defined in SDL.Video.Renderer

type Rep TextureInfo 
Instance details

Defined in SDL.Video.Renderer

type Rep TextureInfo = D1 ('MetaData "TextureInfo" "SDL.Video.Renderer" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "TextureInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "texturePixelFormat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PixelFormat) :*: S1 ('MetaSel ('Just "textureAccess") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TextureAccess)) :*: (S1 ('MetaSel ('Just "textureWidth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt) :*: S1 ('MetaSel ('Just "textureHeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt))))

data TextureAccess #

Information to the GPU about how you will use a texture.

Constructors

TextureAccessStatic

Changes rarely, cannot be locked

TextureAccessStreaming

changes frequently, can be locked

TextureAccessTarget

Can be used as a render target

Instances

Instances details
Data TextureAccess 
Instance details

Defined in SDL.Video.Renderer

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TextureAccess -> c TextureAccess #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TextureAccess #

toConstr :: TextureAccess -> Constr #

dataTypeOf :: TextureAccess -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TextureAccess) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TextureAccess) #

gmapT :: (forall b. Data b => b -> b) -> TextureAccess -> TextureAccess #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TextureAccess -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TextureAccess -> r #

gmapQ :: (forall d. Data d => d -> u) -> TextureAccess -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TextureAccess -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TextureAccess -> m TextureAccess #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TextureAccess -> m TextureAccess #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TextureAccess -> m TextureAccess #

Bounded TextureAccess 
Instance details

Defined in SDL.Video.Renderer

Enum TextureAccess 
Instance details

Defined in SDL.Video.Renderer

Generic TextureAccess 
Instance details

Defined in SDL.Video.Renderer

Associated Types

type Rep TextureAccess :: Type -> Type #

Read TextureAccess 
Instance details

Defined in SDL.Video.Renderer

Show TextureAccess 
Instance details

Defined in SDL.Video.Renderer

Eq TextureAccess 
Instance details

Defined in SDL.Video.Renderer

Ord TextureAccess 
Instance details

Defined in SDL.Video.Renderer

FromNumber TextureAccess CInt 
Instance details

Defined in SDL.Video.Renderer

ToNumber TextureAccess CInt 
Instance details

Defined in SDL.Video.Renderer

type Rep TextureAccess 
Instance details

Defined in SDL.Video.Renderer

type Rep TextureAccess = D1 ('MetaData "TextureAccess" "SDL.Video.Renderer" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "TextureAccessStatic" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TextureAccessStreaming" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TextureAccessTarget" 'PrefixI 'False) (U1 :: Type -> Type)))

data MessageKind #

Constructors

Error 
Warning 
Information 

Instances

Instances details
Data MessageKind 
Instance details

Defined in SDL.Video

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MessageKind -> c MessageKind #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MessageKind #

toConstr :: MessageKind -> Constr #

dataTypeOf :: MessageKind -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MessageKind) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MessageKind) #

gmapT :: (forall b. Data b => b -> b) -> MessageKind -> MessageKind #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MessageKind -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MessageKind -> r #

gmapQ :: (forall d. Data d => d -> u) -> MessageKind -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MessageKind -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MessageKind -> m MessageKind #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageKind -> m MessageKind #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageKind -> m MessageKind #

Bounded MessageKind 
Instance details

Defined in SDL.Video

Enum MessageKind 
Instance details

Defined in SDL.Video

Generic MessageKind 
Instance details

Defined in SDL.Video

Associated Types

type Rep MessageKind :: Type -> Type #

Read MessageKind 
Instance details

Defined in SDL.Video

Show MessageKind 
Instance details

Defined in SDL.Video

Eq MessageKind 
Instance details

Defined in SDL.Video

Ord MessageKind 
Instance details

Defined in SDL.Video

ToNumber MessageKind Word32 
Instance details

Defined in SDL.Video

type Rep MessageKind 
Instance details

Defined in SDL.Video

type Rep MessageKind = D1 ('MetaData "MessageKind" "SDL.Video" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "Error" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Warning" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Information" 'PrefixI 'False) (U1 :: Type -> Type)))

data VideoDriver #

Constructors

VideoDriver 

Instances

Instances details
Data VideoDriver 
Instance details

Defined in SDL.Video

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VideoDriver -> c VideoDriver #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VideoDriver #

toConstr :: VideoDriver -> Constr #

dataTypeOf :: VideoDriver -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c VideoDriver) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VideoDriver) #

gmapT :: (forall b. Data b => b -> b) -> VideoDriver -> VideoDriver #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VideoDriver -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VideoDriver -> r #

gmapQ :: (forall d. Data d => d -> u) -> VideoDriver -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VideoDriver -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VideoDriver -> m VideoDriver #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VideoDriver -> m VideoDriver #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VideoDriver -> m VideoDriver #

Generic VideoDriver 
Instance details

Defined in SDL.Video

Associated Types

type Rep VideoDriver :: Type -> Type #

Read VideoDriver 
Instance details

Defined in SDL.Video

Show VideoDriver 
Instance details

Defined in SDL.Video

Eq VideoDriver 
Instance details

Defined in SDL.Video

Ord VideoDriver 
Instance details

Defined in SDL.Video

type Rep VideoDriver 
Instance details

Defined in SDL.Video

type Rep VideoDriver = D1 ('MetaData "VideoDriver" "SDL.Video" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "VideoDriver" 'PrefixI 'True) (S1 ('MetaSel ('Just "videoDriverName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

data Display #

Constructors

Display 

Fields

Instances

Instances details
Generic Display 
Instance details

Defined in SDL.Video

Associated Types

type Rep Display :: Type -> Type #

Methods

from :: Display -> Rep Display x #

to :: Rep Display x -> Display #

Read Display 
Instance details

Defined in SDL.Video

Show Display 
Instance details

Defined in SDL.Video

Eq Display 
Instance details

Defined in SDL.Video

Methods

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

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

Ord Display 
Instance details

Defined in SDL.Video

type Rep Display 
Instance details

Defined in SDL.Video

type Rep Display = D1 ('MetaData "Display" "SDL.Video" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "Display" 'PrefixI 'True) ((S1 ('MetaSel ('Just "displayName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "displayBoundsPosition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Point V2 CInt))) :*: (S1 ('MetaSel ('Just "displayBoundsSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (V2 CInt)) :*: S1 ('MetaSel ('Just "displayModes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DisplayMode]))))

data WindowPosition #

Constructors

Centered 
Wherever

Let the window mananger decide where it's best to place the window.

Absolute (Point V2 CInt) 

Instances

Instances details
Generic WindowPosition 
Instance details

Defined in SDL.Video

Associated Types

type Rep WindowPosition :: Type -> Type #

Read WindowPosition 
Instance details

Defined in SDL.Video

Show WindowPosition 
Instance details

Defined in SDL.Video

Eq WindowPosition 
Instance details

Defined in SDL.Video

Ord WindowPosition 
Instance details

Defined in SDL.Video

type Rep WindowPosition 
Instance details

Defined in SDL.Video

type Rep WindowPosition = D1 ('MetaData "WindowPosition" "SDL.Video" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "Centered" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Wherever" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Absolute" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Point V2 CInt)))))

data WindowMode #

Constructors

Fullscreen

Real fullscreen with a video mode change

FullscreenDesktop

Fake fullscreen that takes the size of the desktop

Maximized 
Minimized 
Windowed 

Instances

Instances details
Data WindowMode 
Instance details

Defined in SDL.Video

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WindowMode -> c WindowMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WindowMode #

toConstr :: WindowMode -> Constr #

dataTypeOf :: WindowMode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WindowMode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WindowMode) #

gmapT :: (forall b. Data b => b -> b) -> WindowMode -> WindowMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WindowMode -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WindowMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> WindowMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WindowMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WindowMode -> m WindowMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WindowMode -> m WindowMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WindowMode -> m WindowMode #

Bounded WindowMode 
Instance details

Defined in SDL.Video

Enum WindowMode 
Instance details

Defined in SDL.Video

Generic WindowMode 
Instance details

Defined in SDL.Video

Associated Types

type Rep WindowMode :: Type -> Type #

Read WindowMode 
Instance details

Defined in SDL.Video

Show WindowMode 
Instance details

Defined in SDL.Video

Eq WindowMode 
Instance details

Defined in SDL.Video

Ord WindowMode 
Instance details

Defined in SDL.Video

FromNumber WindowMode Word32 
Instance details

Defined in SDL.Video

ToNumber WindowMode Word32 
Instance details

Defined in SDL.Video

type Rep WindowMode 
Instance details

Defined in SDL.Video

type Rep WindowMode = D1 ('MetaData "WindowMode" "SDL.Video" "sdl2-2.5.5.0-45393fc3" 'False) ((C1 ('MetaCons "Fullscreen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FullscreenDesktop" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Maximized" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Minimized" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Windowed" 'PrefixI 'False) (U1 :: Type -> Type))))

data WindowGraphicsContext #

Configuration of additional graphics context that will be created for window.

Can not be changed after window creation.

Constructors

NoGraphicsContext

Window will be created without any additional graphics context.

OpenGLContext OpenGLConfig

Window will be created with OpenGL support with parameters from OpenGLConfig.

VulkanContext

Window will be created with Vulkan support. The following functions will be implicitly called by SDL C library:

  1. analogue of vkLoadLibrary Nothing will be called automatically before first window creation;
  2. analogue of vkUnloadLibrary will be called after last window destruction.

Instances

Instances details
Generic WindowGraphicsContext 
Instance details

Defined in SDL.Video

Associated Types

type Rep WindowGraphicsContext :: Type -> Type #

Read WindowGraphicsContext 
Instance details

Defined in SDL.Video

Show WindowGraphicsContext 
Instance details

Defined in SDL.Video

Eq WindowGraphicsContext 
Instance details

Defined in SDL.Video

Ord WindowGraphicsContext 
Instance details

Defined in SDL.Video

type Rep WindowGraphicsContext 
Instance details

Defined in SDL.Video

type Rep WindowGraphicsContext = D1 ('MetaData "WindowGraphicsContext" "SDL.Video" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "NoGraphicsContext" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OpenGLContext" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OpenGLConfig)) :+: C1 ('MetaCons "VulkanContext" 'PrefixI 'False) (U1 :: Type -> Type)))

data WindowConfig #

Constructors

WindowConfig 

Fields

Instances

Instances details
Generic WindowConfig 
Instance details

Defined in SDL.Video

Associated Types

type Rep WindowConfig :: Type -> Type #

Read WindowConfig 
Instance details

Defined in SDL.Video

Show WindowConfig 
Instance details

Defined in SDL.Video

Eq WindowConfig 
Instance details

Defined in SDL.Video

Ord WindowConfig 
Instance details

Defined in SDL.Video

type Rep WindowConfig 
Instance details

Defined in SDL.Video

data WarpMouseOrigin #

Constructors

WarpInWindow Window

Move the mouse pointer within a given Window.

WarpCurrentFocus

Move the mouse pointer within whichever Window currently has focus.

WarpGlobal

Move the mouse pointer in global screen space.

Instances

Instances details
Data WarpMouseOrigin 
Instance details

Defined in SDL.Input.Mouse

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarpMouseOrigin -> c WarpMouseOrigin #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WarpMouseOrigin #

toConstr :: WarpMouseOrigin -> Constr #

dataTypeOf :: WarpMouseOrigin -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WarpMouseOrigin) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WarpMouseOrigin) #

gmapT :: (forall b. Data b => b -> b) -> WarpMouseOrigin -> WarpMouseOrigin #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarpMouseOrigin -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarpMouseOrigin -> r #

gmapQ :: (forall d. Data d => d -> u) -> WarpMouseOrigin -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarpMouseOrigin -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarpMouseOrigin -> m WarpMouseOrigin #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarpMouseOrigin -> m WarpMouseOrigin #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarpMouseOrigin -> m WarpMouseOrigin #

Generic WarpMouseOrigin 
Instance details

Defined in SDL.Input.Mouse

Associated Types

type Rep WarpMouseOrigin :: Type -> Type #

Show WarpMouseOrigin 
Instance details

Defined in SDL.Input.Mouse

Eq WarpMouseOrigin 
Instance details

Defined in SDL.Input.Mouse

Ord WarpMouseOrigin 
Instance details

Defined in SDL.Input.Mouse

type Rep WarpMouseOrigin 
Instance details

Defined in SDL.Input.Mouse

type Rep WarpMouseOrigin = D1 ('MetaData "WarpMouseOrigin" "SDL.Input.Mouse" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "WarpInWindow" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)) :+: (C1 ('MetaCons "WarpCurrentFocus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WarpGlobal" 'PrefixI 'False) (U1 :: Type -> Type)))

data MouseScrollDirection #

Identifies mouse scroll direction.

Instances

Instances details
Data MouseScrollDirection 
Instance details

Defined in SDL.Input.Mouse

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MouseScrollDirection -> c MouseScrollDirection #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MouseScrollDirection #

toConstr :: MouseScrollDirection -> Constr #

dataTypeOf :: MouseScrollDirection -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MouseScrollDirection) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MouseScrollDirection) #

gmapT :: (forall b. Data b => b -> b) -> MouseScrollDirection -> MouseScrollDirection #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MouseScrollDirection -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MouseScrollDirection -> r #

gmapQ :: (forall d. Data d => d -> u) -> MouseScrollDirection -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MouseScrollDirection -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MouseScrollDirection -> m MouseScrollDirection #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseScrollDirection -> m MouseScrollDirection #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseScrollDirection -> m MouseScrollDirection #

Bounded MouseScrollDirection 
Instance details

Defined in SDL.Input.Mouse

Enum MouseScrollDirection 
Instance details

Defined in SDL.Input.Mouse

Generic MouseScrollDirection 
Instance details

Defined in SDL.Input.Mouse

Associated Types

type Rep MouseScrollDirection :: Type -> Type #

Read MouseScrollDirection 
Instance details

Defined in SDL.Input.Mouse

Show MouseScrollDirection 
Instance details

Defined in SDL.Input.Mouse

Eq MouseScrollDirection 
Instance details

Defined in SDL.Input.Mouse

Ord MouseScrollDirection 
Instance details

Defined in SDL.Input.Mouse

FromNumber MouseScrollDirection Word32 
Instance details

Defined in SDL.Input.Mouse

type Rep MouseScrollDirection 
Instance details

Defined in SDL.Input.Mouse

type Rep MouseScrollDirection = D1 ('MetaData "MouseScrollDirection" "SDL.Input.Mouse" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "ScrollNormal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ScrollFlipped" 'PrefixI 'False) (U1 :: Type -> Type))

data MouseDevice #

Identifies what kind of mouse-like device this is.

Constructors

Mouse !Int

An actual mouse. The number identifies which mouse.

Touch

Some sort of touch device.

Instances

Instances details
Data MouseDevice 
Instance details

Defined in SDL.Input.Mouse

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MouseDevice -> c MouseDevice #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MouseDevice #

toConstr :: MouseDevice -> Constr #

dataTypeOf :: MouseDevice -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MouseDevice) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MouseDevice) #

gmapT :: (forall b. Data b => b -> b) -> MouseDevice -> MouseDevice #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MouseDevice -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MouseDevice -> r #

gmapQ :: (forall d. Data d => d -> u) -> MouseDevice -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MouseDevice -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MouseDevice -> m MouseDevice #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseDevice -> m MouseDevice #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseDevice -> m MouseDevice #

Generic MouseDevice 
Instance details

Defined in SDL.Input.Mouse

Associated Types

type Rep MouseDevice :: Type -> Type #

Read MouseDevice 
Instance details

Defined in SDL.Input.Mouse

Show MouseDevice 
Instance details

Defined in SDL.Input.Mouse

Eq MouseDevice 
Instance details

Defined in SDL.Input.Mouse

Ord MouseDevice 
Instance details

Defined in SDL.Input.Mouse

FromNumber MouseDevice Word32 
Instance details

Defined in SDL.Input.Mouse

type Rep MouseDevice 
Instance details

Defined in SDL.Input.Mouse

type Rep MouseDevice = D1 ('MetaData "MouseDevice" "SDL.Input.Mouse" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "Mouse" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int)) :+: C1 ('MetaCons "Touch" 'PrefixI 'False) (U1 :: Type -> Type))

data MouseButton #

Constructors

ButtonLeft 
ButtonMiddle 
ButtonRight 
ButtonX1 
ButtonX2 
ButtonExtra !Int

An unknown mouse button.

Instances

Instances details
Data MouseButton 
Instance details

Defined in SDL.Input.Mouse

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MouseButton -> c MouseButton #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MouseButton #

toConstr :: MouseButton -> Constr #

dataTypeOf :: MouseButton -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MouseButton) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MouseButton) #

gmapT :: (forall b. Data b => b -> b) -> MouseButton -> MouseButton #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MouseButton -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MouseButton -> r #

gmapQ :: (forall d. Data d => d -> u) -> MouseButton -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MouseButton -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MouseButton -> m MouseButton #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseButton -> m MouseButton #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseButton -> m MouseButton #

Generic MouseButton 
Instance details

Defined in SDL.Input.Mouse

Associated Types

type Rep MouseButton :: Type -> Type #

Read MouseButton 
Instance details

Defined in SDL.Input.Mouse

Show MouseButton 
Instance details

Defined in SDL.Input.Mouse

Eq MouseButton 
Instance details

Defined in SDL.Input.Mouse

Ord MouseButton 
Instance details

Defined in SDL.Input.Mouse

FromNumber MouseButton Word8 
Instance details

Defined in SDL.Input.Mouse

ToNumber MouseButton Word8 
Instance details

Defined in SDL.Input.Mouse

type Rep MouseButton 
Instance details

Defined in SDL.Input.Mouse

type Rep MouseButton = D1 ('MetaData "MouseButton" "SDL.Input.Mouse" "sdl2-2.5.5.0-45393fc3" 'False) ((C1 ('MetaCons "ButtonLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ButtonMiddle" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ButtonRight" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ButtonX1" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ButtonX2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ButtonExtra" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int)))))

data ModalLocation #

Instances

Instances details
Generic ModalLocation 
Instance details

Defined in SDL.Input.Mouse

Associated Types

type Rep ModalLocation :: Type -> Type #

Read ModalLocation 
Instance details

Defined in SDL.Input.Mouse

Show ModalLocation 
Instance details

Defined in SDL.Input.Mouse

Eq ModalLocation 
Instance details

Defined in SDL.Input.Mouse

Ord ModalLocation 
Instance details

Defined in SDL.Input.Mouse

type Rep ModalLocation 
Instance details

Defined in SDL.Input.Mouse

type Rep ModalLocation = D1 ('MetaData "ModalLocation" "SDL.Input.Mouse" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "AbsoluteModalLocation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Point V2 CInt))) :+: C1 ('MetaCons "RelativeModalLocation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (V2 CInt))))

data LocationMode #

Instances

Instances details
Data LocationMode 
Instance details

Defined in SDL.Input.Mouse

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LocationMode -> c LocationMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LocationMode #

toConstr :: LocationMode -> Constr #

dataTypeOf :: LocationMode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LocationMode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LocationMode) #

gmapT :: (forall b. Data b => b -> b) -> LocationMode -> LocationMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LocationMode -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LocationMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> LocationMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LocationMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LocationMode -> m LocationMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LocationMode -> m LocationMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LocationMode -> m LocationMode #

Bounded LocationMode 
Instance details

Defined in SDL.Input.Mouse

Enum LocationMode 
Instance details

Defined in SDL.Input.Mouse

Generic LocationMode 
Instance details

Defined in SDL.Input.Mouse

Associated Types

type Rep LocationMode :: Type -> Type #

Read LocationMode 
Instance details

Defined in SDL.Input.Mouse

Show LocationMode 
Instance details

Defined in SDL.Input.Mouse

Eq LocationMode 
Instance details

Defined in SDL.Input.Mouse

Ord LocationMode 
Instance details

Defined in SDL.Input.Mouse

type Rep LocationMode 
Instance details

Defined in SDL.Input.Mouse

type Rep LocationMode = D1 ('MetaData "LocationMode" "SDL.Input.Mouse" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "AbsoluteLocation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RelativeLocation" 'PrefixI 'False) (U1 :: Type -> Type))

type EventWatchCallback = Event -> IO () #

An EventWatchCallback can process and respond to an event when it is added to the event queue.

data EventPushResult #

Possible results of an attempted push of an event to the queue.

Instances

Instances details
Data EventPushResult 
Instance details

Defined in SDL.Event

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EventPushResult -> c EventPushResult #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EventPushResult #

toConstr :: EventPushResult -> Constr #

dataTypeOf :: EventPushResult -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EventPushResult) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EventPushResult) #

gmapT :: (forall b. Data b => b -> b) -> EventPushResult -> EventPushResult #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EventPushResult -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EventPushResult -> r #

gmapQ :: (forall d. Data d => d -> u) -> EventPushResult -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EventPushResult -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EventPushResult -> m EventPushResult #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EventPushResult -> m EventPushResult #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EventPushResult -> m EventPushResult #

Generic EventPushResult 
Instance details

Defined in SDL.Event

Associated Types

type Rep EventPushResult :: Type -> Type #

Read EventPushResult 
Instance details

Defined in SDL.Event

Show EventPushResult 
Instance details

Defined in SDL.Event

Eq EventPushResult 
Instance details

Defined in SDL.Event

Ord EventPushResult 
Instance details

Defined in SDL.Event

type Rep EventPushResult 
Instance details

Defined in SDL.Event

type Rep EventPushResult = D1 ('MetaData "EventPushResult" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "EventPushSuccess" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EventPushFiltered" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EventPushFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

data RegisteredEventData #

A record used to convert between SDL Events and user-defined data structures.

Used for registerEvent, below.

Constructors

RegisteredEventData 

Fields

Instances

Instances details
Generic RegisteredEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep RegisteredEventData :: Type -> Type #

Show RegisteredEventData 
Instance details

Defined in SDL.Event

Eq RegisteredEventData 
Instance details

Defined in SDL.Event

Ord RegisteredEventData 
Instance details

Defined in SDL.Event

type Rep RegisteredEventData 
Instance details

Defined in SDL.Event

type Rep RegisteredEventData = D1 ('MetaData "RegisteredEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "RegisteredEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "registeredEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Window)) :*: S1 ('MetaSel ('Just "registeredEventCode") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int32)) :*: (S1 ('MetaSel ('Just "registeredEventData1") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 (Ptr ())) :*: S1 ('MetaSel ('Just "registeredEventData2") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 (Ptr ())))))

data RegisteredEventType a #

A user defined event structure that has been registered with SDL.

Use registerEvent, below, to obtain an instance.

data InputMotion #

Constructors

Released 
Pressed 

Instances

Instances details
Data InputMotion 
Instance details

Defined in SDL.Event

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InputMotion -> c InputMotion #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InputMotion #

toConstr :: InputMotion -> Constr #

dataTypeOf :: InputMotion -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InputMotion) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InputMotion) #

gmapT :: (forall b. Data b => b -> b) -> InputMotion -> InputMotion #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InputMotion -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InputMotion -> r #

gmapQ :: (forall d. Data d => d -> u) -> InputMotion -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InputMotion -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InputMotion -> m InputMotion #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InputMotion -> m InputMotion #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InputMotion -> m InputMotion #

Bounded InputMotion 
Instance details

Defined in SDL.Event

Enum InputMotion 
Instance details

Defined in SDL.Event

Generic InputMotion 
Instance details

Defined in SDL.Event

Associated Types

type Rep InputMotion :: Type -> Type #

Read InputMotion 
Instance details

Defined in SDL.Event

Show InputMotion 
Instance details

Defined in SDL.Event

Eq InputMotion 
Instance details

Defined in SDL.Event

Ord InputMotion 
Instance details

Defined in SDL.Event

type Rep InputMotion 
Instance details

Defined in SDL.Event

type Rep InputMotion = D1 ('MetaData "InputMotion" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "Released" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pressed" 'PrefixI 'False) (U1 :: Type -> Type))

newtype UnknownEventData #

SDL reported an unknown event type.

Constructors

UnknownEventData 

Fields

newtype DropEventData #

An event used to request a file open by the system

Constructors

DropEventData 

Fields

Instances

Instances details
Generic DropEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep DropEventData :: Type -> Type #

Show DropEventData 
Instance details

Defined in SDL.Event

Eq DropEventData 
Instance details

Defined in SDL.Event

Ord DropEventData 
Instance details

Defined in SDL.Event

type Rep DropEventData 
Instance details

Defined in SDL.Event

type Rep DropEventData = D1 ('MetaData "DropEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'True) (C1 ('MetaCons "DropEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "dropEventFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CString)))

data DollarGestureEventData #

Complex gesture event information.

Constructors

DollarGestureEventData 

Fields

Instances

Instances details
Generic DollarGestureEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep DollarGestureEventData :: Type -> Type #

Show DollarGestureEventData 
Instance details

Defined in SDL.Event

Eq DollarGestureEventData 
Instance details

Defined in SDL.Event

Ord DollarGestureEventData 
Instance details

Defined in SDL.Event

type Rep DollarGestureEventData 
Instance details

Defined in SDL.Event

type Rep DollarGestureEventData = D1 ('MetaData "DollarGestureEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "DollarGestureEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "dollarGestureEventTouchID") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 TouchID) :*: S1 ('MetaSel ('Just "dollarGestureEventGestureID") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 GestureID)) :*: (S1 ('MetaSel ('Just "dollarGestureEventNumFingers") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word32) :*: (S1 ('MetaSel ('Just "dollarGestureEventError") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 CFloat) :*: S1 ('MetaSel ('Just "dollarGestureEventPos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Point V2 CFloat))))))

data MultiGestureEventData #

Multiple finger gesture event information

Constructors

MultiGestureEventData 

Fields

Instances

Instances details
Generic MultiGestureEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep MultiGestureEventData :: Type -> Type #

Show MultiGestureEventData 
Instance details

Defined in SDL.Event

Eq MultiGestureEventData 
Instance details

Defined in SDL.Event

Ord MultiGestureEventData 
Instance details

Defined in SDL.Event

type Rep MultiGestureEventData 
Instance details

Defined in SDL.Event

type Rep MultiGestureEventData = D1 ('MetaData "MultiGestureEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "MultiGestureEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "multiGestureEventTouchID") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 TouchID) :*: S1 ('MetaSel ('Just "multiGestureEventDTheta") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 CFloat)) :*: (S1 ('MetaSel ('Just "multiGestureEventDDist") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 CFloat) :*: (S1 ('MetaSel ('Just "multiGestureEventPos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Point V2 CFloat)) :*: S1 ('MetaSel ('Just "multiGestureEventNumFingers") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word16)))))

data TouchFingerMotionEventData #

Finger motion event information.

Constructors

TouchFingerMotionEventData 

Fields

Instances

Instances details
Generic TouchFingerMotionEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep TouchFingerMotionEventData :: Type -> Type #

Show TouchFingerMotionEventData 
Instance details

Defined in SDL.Event

Eq TouchFingerMotionEventData 
Instance details

Defined in SDL.Event

Ord TouchFingerMotionEventData 
Instance details

Defined in SDL.Event

type Rep TouchFingerMotionEventData 
Instance details

Defined in SDL.Event

type Rep TouchFingerMotionEventData = D1 ('MetaData "TouchFingerMotionEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "TouchFingerMotionEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "touchFingerMotionEventTouchID") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 TouchID) :*: S1 ('MetaSel ('Just "touchFingerMotionEventFingerID") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 FingerID)) :*: (S1 ('MetaSel ('Just "touchFingerMotionEventPos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Point V2 CFloat)) :*: (S1 ('MetaSel ('Just "touchFingerMotionEventRelMotion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V2 CFloat)) :*: S1 ('MetaSel ('Just "touchFingerMotionEventPressure") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 CFloat)))))

data TouchFingerEventData #

Finger touch event information.

Constructors

TouchFingerEventData 

Fields

Instances

Instances details
Generic TouchFingerEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep TouchFingerEventData :: Type -> Type #

Show TouchFingerEventData 
Instance details

Defined in SDL.Event

Eq TouchFingerEventData 
Instance details

Defined in SDL.Event

Ord TouchFingerEventData 
Instance details

Defined in SDL.Event

type Rep TouchFingerEventData 
Instance details

Defined in SDL.Event

type Rep TouchFingerEventData = D1 ('MetaData "TouchFingerEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "TouchFingerEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "touchFingerEventTouchID") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 TouchID) :*: S1 ('MetaSel ('Just "touchFingerEventFingerID") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 FingerID)) :*: (S1 ('MetaSel ('Just "touchFingerEventMotion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 InputMotion) :*: (S1 ('MetaSel ('Just "touchFingerEventPos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Point V2 CFloat)) :*: S1 ('MetaSel ('Just "touchFingerEventPressure") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 CFloat)))))

newtype SysWMEventData #

A video driver dependent system event

Constructors

SysWMEventData 

Instances

Instances details
Generic SysWMEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep SysWMEventData :: Type -> Type #

Show SysWMEventData 
Instance details

Defined in SDL.Event

Eq SysWMEventData 
Instance details

Defined in SDL.Event

Ord SysWMEventData 
Instance details

Defined in SDL.Event

type Rep SysWMEventData 
Instance details

Defined in SDL.Event

type Rep SysWMEventData = D1 ('MetaData "SysWMEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'True) (C1 ('MetaCons "SysWMEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "sysWMEventMsg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SysWMmsg)))

data UserEventData #

Event data for application-defined events.

Constructors

UserEventData 

Fields

Instances

Instances details
Generic UserEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep UserEventData :: Type -> Type #

Show UserEventData 
Instance details

Defined in SDL.Event

Eq UserEventData 
Instance details

Defined in SDL.Event

Ord UserEventData 
Instance details

Defined in SDL.Event

type Rep UserEventData 
Instance details

Defined in SDL.Event

type Rep UserEventData = D1 ('MetaData "UserEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "UserEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "userEventType") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word32) :*: S1 ('MetaSel ('Just "userEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Window))) :*: (S1 ('MetaSel ('Just "userEventCode") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int32) :*: (S1 ('MetaSel ('Just "userEventData1") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 (Ptr ())) :*: S1 ('MetaSel ('Just "userEventData2") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 (Ptr ()))))))

data AudioDeviceEventData #

Constructors

AudioDeviceEventData 

Fields

Instances

Instances details
Generic AudioDeviceEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep AudioDeviceEventData :: Type -> Type #

Show AudioDeviceEventData 
Instance details

Defined in SDL.Event

Eq AudioDeviceEventData 
Instance details

Defined in SDL.Event

Ord AudioDeviceEventData 
Instance details

Defined in SDL.Event

type Rep AudioDeviceEventData 
Instance details

Defined in SDL.Event

type Rep AudioDeviceEventData = D1 ('MetaData "AudioDeviceEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "AudioDeviceEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "audioDeviceEventIsAddition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "audioDeviceEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word32) :*: S1 ('MetaSel ('Just "audioDeviceEventIsCapture") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))))

data ControllerDeviceEventData #

Controller device event information

Constructors

ControllerDeviceEventData 

Fields

Instances

Instances details
Generic ControllerDeviceEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep ControllerDeviceEventData :: Type -> Type #

Show ControllerDeviceEventData 
Instance details

Defined in SDL.Event

Eq ControllerDeviceEventData 
Instance details

Defined in SDL.Event

Ord ControllerDeviceEventData 
Instance details

Defined in SDL.Event

type Rep ControllerDeviceEventData 
Instance details

Defined in SDL.Event

type Rep ControllerDeviceEventData = D1 ('MetaData "ControllerDeviceEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "ControllerDeviceEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "controllerDeviceEventConnection") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ControllerDeviceConnection) :*: S1 ('MetaSel ('Just "controllerDeviceEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 JoystickID)))

data ControllerButtonEventData #

Game controller button event information

Constructors

ControllerButtonEventData 

Fields

Instances

Instances details
Generic ControllerButtonEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep ControllerButtonEventData :: Type -> Type #

Show ControllerButtonEventData 
Instance details

Defined in SDL.Event

Eq ControllerButtonEventData 
Instance details

Defined in SDL.Event

Ord ControllerButtonEventData 
Instance details

Defined in SDL.Event

type Rep ControllerButtonEventData 
Instance details

Defined in SDL.Event

type Rep ControllerButtonEventData = D1 ('MetaData "ControllerButtonEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "ControllerButtonEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "controllerButtonEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 JoystickID) :*: (S1 ('MetaSel ('Just "controllerButtonEventButton") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ControllerButton) :*: S1 ('MetaSel ('Just "controllerButtonEventState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ControllerButtonState))))

data ControllerAxisEventData #

Game controller axis motion event information.

Constructors

ControllerAxisEventData 

Fields

Instances

Instances details
Generic ControllerAxisEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep ControllerAxisEventData :: Type -> Type #

Show ControllerAxisEventData 
Instance details

Defined in SDL.Event

Eq ControllerAxisEventData 
Instance details

Defined in SDL.Event

Ord ControllerAxisEventData 
Instance details

Defined in SDL.Event

type Rep ControllerAxisEventData 
Instance details

Defined in SDL.Event

type Rep ControllerAxisEventData = D1 ('MetaData "ControllerAxisEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "ControllerAxisEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "controllerAxisEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 JoystickID) :*: (S1 ('MetaSel ('Just "controllerAxisEventAxis") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ControllerAxis) :*: S1 ('MetaSel ('Just "controllerAxisEventValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int16))))

data JoyDeviceEventData #

Joystick device event information.

Constructors

JoyDeviceEventData 

Fields

Instances

Instances details
Generic JoyDeviceEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep JoyDeviceEventData :: Type -> Type #

Show JoyDeviceEventData 
Instance details

Defined in SDL.Event

Eq JoyDeviceEventData 
Instance details

Defined in SDL.Event

Ord JoyDeviceEventData 
Instance details

Defined in SDL.Event

type Rep JoyDeviceEventData 
Instance details

Defined in SDL.Event

type Rep JoyDeviceEventData = D1 ('MetaData "JoyDeviceEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "JoyDeviceEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "joyDeviceEventConnection") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 JoyDeviceConnection) :*: S1 ('MetaSel ('Just "joyDeviceEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 JoystickID)))

data JoyButtonEventData #

Joystick button event information.

Constructors

JoyButtonEventData 

Fields

Instances

Instances details
Generic JoyButtonEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep JoyButtonEventData :: Type -> Type #

Show JoyButtonEventData 
Instance details

Defined in SDL.Event

Eq JoyButtonEventData 
Instance details

Defined in SDL.Event

Ord JoyButtonEventData 
Instance details

Defined in SDL.Event

type Rep JoyButtonEventData 
Instance details

Defined in SDL.Event

type Rep JoyButtonEventData = D1 ('MetaData "JoyButtonEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "JoyButtonEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "joyButtonEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 JoystickID) :*: (S1 ('MetaSel ('Just "joyButtonEventButton") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word8) :*: S1 ('MetaSel ('Just "joyButtonEventState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 JoyButtonState))))

data JoyHatEventData #

Joystick hat position change event information

Constructors

JoyHatEventData 

Fields

Instances

Instances details
Generic JoyHatEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep JoyHatEventData :: Type -> Type #

Show JoyHatEventData 
Instance details

Defined in SDL.Event

Eq JoyHatEventData 
Instance details

Defined in SDL.Event

Ord JoyHatEventData 
Instance details

Defined in SDL.Event

type Rep JoyHatEventData 
Instance details

Defined in SDL.Event

type Rep JoyHatEventData = D1 ('MetaData "JoyHatEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "JoyHatEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "joyHatEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 JoystickID) :*: (S1 ('MetaSel ('Just "joyHatEventHat") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word8) :*: S1 ('MetaSel ('Just "joyHatEventValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 JoyHatPosition))))

data JoyBallEventData #

Joystick trackball motion event information.

Constructors

JoyBallEventData 

Fields

Instances

Instances details
Generic JoyBallEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep JoyBallEventData :: Type -> Type #

Show JoyBallEventData 
Instance details

Defined in SDL.Event

Eq JoyBallEventData 
Instance details

Defined in SDL.Event

Ord JoyBallEventData 
Instance details

Defined in SDL.Event

type Rep JoyBallEventData 
Instance details

Defined in SDL.Event

type Rep JoyBallEventData = D1 ('MetaData "JoyBallEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "JoyBallEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "joyBallEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 JoystickID) :*: (S1 ('MetaSel ('Just "joyBallEventBall") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word8) :*: S1 ('MetaSel ('Just "joyBallEventRelMotion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V2 Int16)))))

data JoyAxisEventData #

Joystick axis motion event information

Constructors

JoyAxisEventData 

Fields

Instances

Instances details
Generic JoyAxisEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep JoyAxisEventData :: Type -> Type #

Show JoyAxisEventData 
Instance details

Defined in SDL.Event

Eq JoyAxisEventData 
Instance details

Defined in SDL.Event

Ord JoyAxisEventData 
Instance details

Defined in SDL.Event

type Rep JoyAxisEventData 
Instance details

Defined in SDL.Event

type Rep JoyAxisEventData = D1 ('MetaData "JoyAxisEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "JoyAxisEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "joyAxisEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 JoystickID) :*: (S1 ('MetaSel ('Just "joyAxisEventAxis") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word8) :*: S1 ('MetaSel ('Just "joyAxisEventValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int16))))

data MouseWheelEventData #

Mouse wheel event information.

Constructors

MouseWheelEventData 

Fields

Instances

Instances details
Generic MouseWheelEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep MouseWheelEventData :: Type -> Type #

Show MouseWheelEventData 
Instance details

Defined in SDL.Event

Eq MouseWheelEventData 
Instance details

Defined in SDL.Event

Ord MouseWheelEventData 
Instance details

Defined in SDL.Event

type Rep MouseWheelEventData 
Instance details

Defined in SDL.Event

type Rep MouseWheelEventData = D1 ('MetaData "MouseWheelEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "MouseWheelEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "mouseWheelEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Window)) :*: S1 ('MetaSel ('Just "mouseWheelEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MouseDevice)) :*: (S1 ('MetaSel ('Just "mouseWheelEventPos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V2 Int32)) :*: S1 ('MetaSel ('Just "mouseWheelEventDirection") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MouseScrollDirection))))

data MouseButtonEventData #

A mouse or pointer device button was pressed or released.

Constructors

MouseButtonEventData 

Fields

Instances

Instances details
Generic MouseButtonEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep MouseButtonEventData :: Type -> Type #

Show MouseButtonEventData 
Instance details

Defined in SDL.Event

Eq MouseButtonEventData 
Instance details

Defined in SDL.Event

Ord MouseButtonEventData 
Instance details

Defined in SDL.Event

type Rep MouseButtonEventData 
Instance details

Defined in SDL.Event

type Rep MouseButtonEventData = D1 ('MetaData "MouseButtonEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "MouseButtonEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "mouseButtonEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Window)) :*: (S1 ('MetaSel ('Just "mouseButtonEventMotion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 InputMotion) :*: S1 ('MetaSel ('Just "mouseButtonEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MouseDevice))) :*: (S1 ('MetaSel ('Just "mouseButtonEventButton") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MouseButton) :*: (S1 ('MetaSel ('Just "mouseButtonEventClicks") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word8) :*: S1 ('MetaSel ('Just "mouseButtonEventPos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Point V2 Int32))))))

data MouseMotionEventData #

A mouse or pointer device was moved.

Constructors

MouseMotionEventData 

Fields

Instances

Instances details
Generic MouseMotionEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep MouseMotionEventData :: Type -> Type #

Show MouseMotionEventData 
Instance details

Defined in SDL.Event

Eq MouseMotionEventData 
Instance details

Defined in SDL.Event

Ord MouseMotionEventData 
Instance details

Defined in SDL.Event

type Rep MouseMotionEventData 
Instance details

Defined in SDL.Event

type Rep MouseMotionEventData = D1 ('MetaData "MouseMotionEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "MouseMotionEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "mouseMotionEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Window)) :*: S1 ('MetaSel ('Just "mouseMotionEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MouseDevice)) :*: (S1 ('MetaSel ('Just "mouseMotionEventState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [MouseButton]) :*: (S1 ('MetaSel ('Just "mouseMotionEventPos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Point V2 Int32)) :*: S1 ('MetaSel ('Just "mouseMotionEventRelMotion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V2 Int32))))))

data TextInputEventData #

Keyboard text input event information.

Constructors

TextInputEventData 

Fields

Instances

Instances details
Generic TextInputEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep TextInputEventData :: Type -> Type #

Show TextInputEventData 
Instance details

Defined in SDL.Event

Eq TextInputEventData 
Instance details

Defined in SDL.Event

Ord TextInputEventData 
Instance details

Defined in SDL.Event

type Rep TextInputEventData 
Instance details

Defined in SDL.Event

type Rep TextInputEventData = D1 ('MetaData "TextInputEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "TextInputEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "textInputEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Window)) :*: S1 ('MetaSel ('Just "textInputEventText") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))

data TextEditingEventData #

Keyboard text editing event information.

Constructors

TextEditingEventData 

Fields

Instances

Instances details
Generic TextEditingEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep TextEditingEventData :: Type -> Type #

Show TextEditingEventData 
Instance details

Defined in SDL.Event

Eq TextEditingEventData 
Instance details

Defined in SDL.Event

Ord TextEditingEventData 
Instance details

Defined in SDL.Event

type Rep TextEditingEventData 
Instance details

Defined in SDL.Event

type Rep TextEditingEventData = D1 ('MetaData "TextEditingEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "TextEditingEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "textEditingEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Window)) :*: S1 ('MetaSel ('Just "textEditingEventText") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "textEditingEventStart") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int32) :*: S1 ('MetaSel ('Just "textEditingEventLength") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int32))))

data KeyboardEventData #

A keyboard key has been pressed or released.

Constructors

KeyboardEventData 

Fields

Instances

Instances details
Generic KeyboardEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep KeyboardEventData :: Type -> Type #

Show KeyboardEventData 
Instance details

Defined in SDL.Event

Eq KeyboardEventData 
Instance details

Defined in SDL.Event

Ord KeyboardEventData 
Instance details

Defined in SDL.Event

type Rep KeyboardEventData 
Instance details

Defined in SDL.Event

type Rep KeyboardEventData = D1 ('MetaData "KeyboardEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "KeyboardEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "keyboardEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Window)) :*: S1 ('MetaSel ('Just "keyboardEventKeyMotion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 InputMotion)) :*: (S1 ('MetaSel ('Just "keyboardEventRepeat") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "keyboardEventKeysym") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Keysym))))

newtype WindowClosedEventData #

The window manager requests that the window be closed.

Constructors

WindowClosedEventData 

Fields

Instances

Instances details
Generic WindowClosedEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowClosedEventData :: Type -> Type #

Show WindowClosedEventData 
Instance details

Defined in SDL.Event

Eq WindowClosedEventData 
Instance details

Defined in SDL.Event

Ord WindowClosedEventData 
Instance details

Defined in SDL.Event

type Rep WindowClosedEventData 
Instance details

Defined in SDL.Event

type Rep WindowClosedEventData = D1 ('MetaData "WindowClosedEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'True) (C1 ('MetaCons "WindowClosedEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowClosedEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

newtype WindowLostKeyboardFocusEventData #

The window has lost keyboard focus.

Instances

Instances details
Generic WindowLostKeyboardFocusEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowLostKeyboardFocusEventData :: Type -> Type #

Show WindowLostKeyboardFocusEventData 
Instance details

Defined in SDL.Event

Eq WindowLostKeyboardFocusEventData 
Instance details

Defined in SDL.Event

Ord WindowLostKeyboardFocusEventData 
Instance details

Defined in SDL.Event

type Rep WindowLostKeyboardFocusEventData 
Instance details

Defined in SDL.Event

type Rep WindowLostKeyboardFocusEventData = D1 ('MetaData "WindowLostKeyboardFocusEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'True) (C1 ('MetaCons "WindowLostKeyboardFocusEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowLostKeyboardFocusEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

newtype WindowGainedKeyboardFocusEventData #

The window has gained keyboard focus.

Instances

Instances details
Generic WindowGainedKeyboardFocusEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowGainedKeyboardFocusEventData :: Type -> Type #

Show WindowGainedKeyboardFocusEventData 
Instance details

Defined in SDL.Event

Eq WindowGainedKeyboardFocusEventData 
Instance details

Defined in SDL.Event

Ord WindowGainedKeyboardFocusEventData 
Instance details

Defined in SDL.Event

type Rep WindowGainedKeyboardFocusEventData 
Instance details

Defined in SDL.Event

type Rep WindowGainedKeyboardFocusEventData = D1 ('MetaData "WindowGainedKeyboardFocusEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'True) (C1 ('MetaCons "WindowGainedKeyboardFocusEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowGainedKeyboardFocusEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

newtype WindowLostMouseFocusEventData #

The window has lost mouse focus.

Instances

Instances details
Generic WindowLostMouseFocusEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowLostMouseFocusEventData :: Type -> Type #

Show WindowLostMouseFocusEventData 
Instance details

Defined in SDL.Event

Eq WindowLostMouseFocusEventData 
Instance details

Defined in SDL.Event

Ord WindowLostMouseFocusEventData 
Instance details

Defined in SDL.Event

type Rep WindowLostMouseFocusEventData 
Instance details

Defined in SDL.Event

type Rep WindowLostMouseFocusEventData = D1 ('MetaData "WindowLostMouseFocusEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'True) (C1 ('MetaCons "WindowLostMouseFocusEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowLostMouseFocusEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

newtype WindowGainedMouseFocusEventData #

The window has gained mouse focus.

Instances

Instances details
Generic WindowGainedMouseFocusEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowGainedMouseFocusEventData :: Type -> Type #

Show WindowGainedMouseFocusEventData 
Instance details

Defined in SDL.Event

Eq WindowGainedMouseFocusEventData 
Instance details

Defined in SDL.Event

Ord WindowGainedMouseFocusEventData 
Instance details

Defined in SDL.Event

type Rep WindowGainedMouseFocusEventData 
Instance details

Defined in SDL.Event

type Rep WindowGainedMouseFocusEventData = D1 ('MetaData "WindowGainedMouseFocusEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'True) (C1 ('MetaCons "WindowGainedMouseFocusEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowGainedMouseFocusEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

newtype WindowRestoredEventData #

The window has been restored to normal size and position.

Constructors

WindowRestoredEventData 

Fields

Instances

Instances details
Generic WindowRestoredEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowRestoredEventData :: Type -> Type #

Show WindowRestoredEventData 
Instance details

Defined in SDL.Event

Eq WindowRestoredEventData 
Instance details

Defined in SDL.Event

Ord WindowRestoredEventData 
Instance details

Defined in SDL.Event

type Rep WindowRestoredEventData 
Instance details

Defined in SDL.Event

type Rep WindowRestoredEventData = D1 ('MetaData "WindowRestoredEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'True) (C1 ('MetaCons "WindowRestoredEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowRestoredEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

newtype WindowMaximizedEventData #

The window has been maximized.

Instances

Instances details
Generic WindowMaximizedEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowMaximizedEventData :: Type -> Type #

Show WindowMaximizedEventData 
Instance details

Defined in SDL.Event

Eq WindowMaximizedEventData 
Instance details

Defined in SDL.Event

Ord WindowMaximizedEventData 
Instance details

Defined in SDL.Event

type Rep WindowMaximizedEventData 
Instance details

Defined in SDL.Event

type Rep WindowMaximizedEventData = D1 ('MetaData "WindowMaximizedEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'True) (C1 ('MetaCons "WindowMaximizedEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowMaximizedEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

newtype WindowMinimizedEventData #

The window has been minimized.

Instances

Instances details
Generic WindowMinimizedEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowMinimizedEventData :: Type -> Type #

Show WindowMinimizedEventData 
Instance details

Defined in SDL.Event

Eq WindowMinimizedEventData 
Instance details

Defined in SDL.Event

Ord WindowMinimizedEventData 
Instance details

Defined in SDL.Event

type Rep WindowMinimizedEventData 
Instance details

Defined in SDL.Event

type Rep WindowMinimizedEventData = D1 ('MetaData "WindowMinimizedEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'True) (C1 ('MetaCons "WindowMinimizedEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowMinimizedEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

data WindowSizeChangedEventData #

The window size has changed, either as a result of an API call or through the system or user changing the window size; this event is followed by WindowResizedEvent if the size was changed by an external event, i.e. the user or the window manager.

Constructors

WindowSizeChangedEventData 

Fields

Instances

Instances details
Generic WindowSizeChangedEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowSizeChangedEventData :: Type -> Type #

Show WindowSizeChangedEventData 
Instance details

Defined in SDL.Event

Eq WindowSizeChangedEventData 
Instance details

Defined in SDL.Event

Ord WindowSizeChangedEventData 
Instance details

Defined in SDL.Event

type Rep WindowSizeChangedEventData 
Instance details

Defined in SDL.Event

type Rep WindowSizeChangedEventData = D1 ('MetaData "WindowSizeChangedEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "WindowSizeChangedEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowSizeChangedEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Window) :*: S1 ('MetaSel ('Just "windowSizeChangedEventSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V2 Int32))))

data WindowResizedEventData #

Window has been resized. This is event is always preceded by WindowSizeChangedEvent.

Constructors

WindowResizedEventData 

Fields

Instances

Instances details
Generic WindowResizedEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowResizedEventData :: Type -> Type #

Show WindowResizedEventData 
Instance details

Defined in SDL.Event

Eq WindowResizedEventData 
Instance details

Defined in SDL.Event

Ord WindowResizedEventData 
Instance details

Defined in SDL.Event

type Rep WindowResizedEventData 
Instance details

Defined in SDL.Event

type Rep WindowResizedEventData = D1 ('MetaData "WindowResizedEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "WindowResizedEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowResizedEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Window) :*: S1 ('MetaSel ('Just "windowResizedEventSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V2 Int32))))

data WindowMovedEventData #

A Window has been moved.

Constructors

WindowMovedEventData 

Fields

Instances

Instances details
Generic WindowMovedEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowMovedEventData :: Type -> Type #

Show WindowMovedEventData 
Instance details

Defined in SDL.Event

Eq WindowMovedEventData 
Instance details

Defined in SDL.Event

Ord WindowMovedEventData 
Instance details

Defined in SDL.Event

type Rep WindowMovedEventData 
Instance details

Defined in SDL.Event

type Rep WindowMovedEventData = D1 ('MetaData "WindowMovedEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (C1 ('MetaCons "WindowMovedEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowMovedEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Window) :*: S1 ('MetaSel ('Just "windowMovedEventPosition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Point V2 Int32))))

newtype WindowExposedEventData #

A part of a window has been exposed - where exposure means to become visible (for example, an overlapping window no longer overlaps with the window).

Constructors

WindowExposedEventData 

Fields

Instances

Instances details
Generic WindowExposedEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowExposedEventData :: Type -> Type #

Show WindowExposedEventData 
Instance details

Defined in SDL.Event

Eq WindowExposedEventData 
Instance details

Defined in SDL.Event

Ord WindowExposedEventData 
Instance details

Defined in SDL.Event

type Rep WindowExposedEventData 
Instance details

Defined in SDL.Event

type Rep WindowExposedEventData = D1 ('MetaData "WindowExposedEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'True) (C1 ('MetaCons "WindowExposedEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowExposedEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

newtype WindowHiddenEventData #

A window has been hidden.

Constructors

WindowHiddenEventData 

Fields

Instances

Instances details
Generic WindowHiddenEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowHiddenEventData :: Type -> Type #

Show WindowHiddenEventData 
Instance details

Defined in SDL.Event

Eq WindowHiddenEventData 
Instance details

Defined in SDL.Event

Ord WindowHiddenEventData 
Instance details

Defined in SDL.Event

type Rep WindowHiddenEventData 
Instance details

Defined in SDL.Event

type Rep WindowHiddenEventData = D1 ('MetaData "WindowHiddenEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'True) (C1 ('MetaCons "WindowHiddenEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowHiddenEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

newtype WindowShownEventData #

A window has been shown.

Constructors

WindowShownEventData 

Fields

Instances

Instances details
Generic WindowShownEventData 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowShownEventData :: Type -> Type #

Show WindowShownEventData 
Instance details

Defined in SDL.Event

Eq WindowShownEventData 
Instance details

Defined in SDL.Event

Ord WindowShownEventData 
Instance details

Defined in SDL.Event

type Rep WindowShownEventData 
Instance details

Defined in SDL.Event

type Rep WindowShownEventData = D1 ('MetaData "WindowShownEventData" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'True) (C1 ('MetaCons "WindowShownEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowShownEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

data EventPayload #

An enumeration of all possible SDL event types. This data type pairs up event types with their payload, where possible.

Constructors

WindowShownEvent !WindowShownEventData 
WindowHiddenEvent !WindowHiddenEventData 
WindowExposedEvent !WindowExposedEventData 
WindowMovedEvent !WindowMovedEventData 
WindowResizedEvent !WindowResizedEventData 
WindowSizeChangedEvent !WindowSizeChangedEventData 
WindowMinimizedEvent !WindowMinimizedEventData 
WindowMaximizedEvent !WindowMaximizedEventData 
WindowRestoredEvent !WindowRestoredEventData 
WindowGainedMouseFocusEvent !WindowGainedMouseFocusEventData 
WindowLostMouseFocusEvent !WindowLostMouseFocusEventData 
WindowGainedKeyboardFocusEvent !WindowGainedKeyboardFocusEventData 
WindowLostKeyboardFocusEvent !WindowLostKeyboardFocusEventData 
WindowClosedEvent !WindowClosedEventData 
KeyboardEvent !KeyboardEventData 
TextEditingEvent !TextEditingEventData 
TextInputEvent !TextInputEventData 
KeymapChangedEvent 
MouseMotionEvent !MouseMotionEventData 
MouseButtonEvent !MouseButtonEventData 
MouseWheelEvent !MouseWheelEventData 
JoyAxisEvent !JoyAxisEventData 
JoyBallEvent !JoyBallEventData 
JoyHatEvent !JoyHatEventData 
JoyButtonEvent !JoyButtonEventData 
JoyDeviceEvent !JoyDeviceEventData 
ControllerAxisEvent !ControllerAxisEventData 
ControllerButtonEvent !ControllerButtonEventData 
ControllerDeviceEvent !ControllerDeviceEventData 
AudioDeviceEvent !AudioDeviceEventData 
QuitEvent 
UserEvent !UserEventData 
SysWMEvent !SysWMEventData 
TouchFingerEvent !TouchFingerEventData 
TouchFingerMotionEvent !TouchFingerMotionEventData 
MultiGestureEvent !MultiGestureEventData 
DollarGestureEvent !DollarGestureEventData 
DropEvent !DropEventData 
ClipboardUpdateEvent 
UnknownEvent !UnknownEventData 

Instances

Instances details
Generic EventPayload 
Instance details

Defined in SDL.Event

Associated Types

type Rep EventPayload :: Type -> Type #

Show EventPayload 
Instance details

Defined in SDL.Event

Eq EventPayload 
Instance details

Defined in SDL.Event

Ord EventPayload 
Instance details

Defined in SDL.Event

type Rep EventPayload 
Instance details

Defined in SDL.Event

type Rep EventPayload = D1 ('MetaData "EventPayload" "SDL.Event" "sdl2-2.5.5.0-45393fc3" 'False) (((((C1 ('MetaCons "WindowShownEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 WindowShownEventData)) :+: C1 ('MetaCons "WindowHiddenEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 WindowHiddenEventData))) :+: (C1 ('MetaCons "WindowExposedEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 WindowExposedEventData)) :+: (C1 ('MetaCons "WindowMovedEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WindowMovedEventData)) :+: C1 ('MetaCons "WindowResizedEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WindowResizedEventData))))) :+: ((C1 ('MetaCons "WindowSizeChangedEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WindowSizeChangedEventData)) :+: C1 ('MetaCons "WindowMinimizedEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 WindowMinimizedEventData))) :+: (C1 ('MetaCons "WindowMaximizedEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 WindowMaximizedEventData)) :+: (C1 ('MetaCons "WindowRestoredEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 WindowRestoredEventData)) :+: C1 ('MetaCons "WindowGainedMouseFocusEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 WindowGainedMouseFocusEventData)))))) :+: (((C1 ('MetaCons "WindowLostMouseFocusEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 WindowLostMouseFocusEventData)) :+: C1 ('MetaCons "WindowGainedKeyboardFocusEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 WindowGainedKeyboardFocusEventData))) :+: (C1 ('MetaCons "WindowLostKeyboardFocusEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 WindowLostKeyboardFocusEventData)) :+: (C1 ('MetaCons "WindowClosedEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 WindowClosedEventData)) :+: C1 ('MetaCons "KeyboardEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 KeyboardEventData))))) :+: ((C1 ('MetaCons "TextEditingEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TextEditingEventData)) :+: C1 ('MetaCons "TextInputEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TextInputEventData))) :+: (C1 ('MetaCons "KeymapChangedEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MouseMotionEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MouseMotionEventData)) :+: C1 ('MetaCons "MouseButtonEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MouseButtonEventData))))))) :+: ((((C1 ('MetaCons "MouseWheelEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MouseWheelEventData)) :+: C1 ('MetaCons "JoyAxisEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 JoyAxisEventData))) :+: (C1 ('MetaCons "JoyBallEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 JoyBallEventData)) :+: (C1 ('MetaCons "JoyHatEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 JoyHatEventData)) :+: C1 ('MetaCons "JoyButtonEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 JoyButtonEventData))))) :+: ((C1 ('MetaCons "JoyDeviceEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 JoyDeviceEventData)) :+: C1 ('MetaCons "ControllerAxisEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ControllerAxisEventData))) :+: (C1 ('MetaCons "ControllerButtonEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ControllerButtonEventData)) :+: (C1 ('MetaCons "ControllerDeviceEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ControllerDeviceEventData)) :+: C1 ('MetaCons "AudioDeviceEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AudioDeviceEventData)))))) :+: (((C1 ('MetaCons "QuitEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UserEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UserEventData))) :+: (C1 ('MetaCons "SysWMEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 SysWMEventData)) :+: (C1 ('MetaCons "TouchFingerEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TouchFingerEventData)) :+: C1 ('MetaCons "TouchFingerMotionEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TouchFingerMotionEventData))))) :+: ((C1 ('MetaCons "MultiGestureEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MultiGestureEventData)) :+: C1 ('MetaCons "DollarGestureEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DollarGestureEventData))) :+: (C1 ('MetaCons "DropEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 DropEventData)) :+: (C1 ('MetaCons "ClipboardUpdateEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnknownEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 UnknownEventData))))))))

pattern KeycodeMail :: Keycode #

pattern KeycodeWWW :: Keycode #

pattern KeycodeMode :: Keycode #

pattern KeycodeRGUI :: Keycode #

pattern KeycodeRAlt :: Keycode #

pattern KeycodeLGUI :: Keycode #

pattern KeycodeLAlt :: Keycode #

pattern KeycodeKPAt :: Keycode #

pattern KeycodeKPF :: Keycode #

pattern KeycodeKPE :: Keycode #

pattern KeycodeKPD :: Keycode #

pattern KeycodeKPC :: Keycode #

pattern KeycodeKPB :: Keycode #

pattern KeycodeKPA :: Keycode #

pattern KeycodeKP00 :: Keycode #

pattern KeycodeOper :: Keycode #

pattern KeycodeOut :: Keycode #

pattern KeycodeMute :: Keycode #

pattern KeycodeFind :: Keycode #

pattern KeycodeCopy :: Keycode #

pattern KeycodeCut :: Keycode #

pattern KeycodeUndo :: Keycode #

pattern KeycodeStop :: Keycode #

pattern KeycodeMenu :: Keycode #

pattern KeycodeHelp :: Keycode #

pattern KeycodeF24 :: Keycode #

pattern KeycodeF23 :: Keycode #

pattern KeycodeF22 :: Keycode #

pattern KeycodeF21 :: Keycode #

pattern KeycodeF20 :: Keycode #

pattern KeycodeF19 :: Keycode #

pattern KeycodeF18 :: Keycode #

pattern KeycodeF17 :: Keycode #

pattern KeycodeF16 :: Keycode #

pattern KeycodeF15 :: Keycode #

pattern KeycodeF14 :: Keycode #

pattern KeycodeF13 :: Keycode #

pattern KeycodeKP0 :: Keycode #

pattern KeycodeKP9 :: Keycode #

pattern KeycodeKP8 :: Keycode #

pattern KeycodeKP7 :: Keycode #

pattern KeycodeKP6 :: Keycode #

pattern KeycodeKP5 :: Keycode #

pattern KeycodeKP4 :: Keycode #

pattern KeycodeKP3 :: Keycode #

pattern KeycodeKP2 :: Keycode #

pattern KeycodeKP1 :: Keycode #

pattern KeycodeUp :: Keycode #

pattern KeycodeDown :: Keycode #

pattern KeycodeLeft :: Keycode #

pattern KeycodeEnd :: Keycode #

pattern KeycodeHome :: Keycode #

pattern KeycodeF12 :: Keycode #

pattern KeycodeF11 :: Keycode #

pattern KeycodeF10 :: Keycode #

pattern KeycodeF9 :: Keycode #

pattern KeycodeF8 :: Keycode #

pattern KeycodeF7 :: Keycode #

pattern KeycodeF6 :: Keycode #

pattern KeycodeF5 :: Keycode #

pattern KeycodeF4 :: Keycode #

pattern KeycodeF3 :: Keycode #

pattern KeycodeF2 :: Keycode #

pattern KeycodeF1 :: Keycode #

pattern KeycodeZ :: Keycode #

pattern KeycodeY :: Keycode #

pattern KeycodeX :: Keycode #

pattern KeycodeW :: Keycode #

pattern KeycodeV :: Keycode #

pattern KeycodeU :: Keycode #

pattern KeycodeT :: Keycode #

pattern KeycodeS :: Keycode #

pattern KeycodeR :: Keycode #

pattern KeycodeQ :: Keycode #

pattern KeycodeP :: Keycode #

pattern KeycodeO :: Keycode #

pattern KeycodeN :: Keycode #

pattern KeycodeM :: Keycode #

pattern KeycodeL :: Keycode #

pattern KeycodeK :: Keycode #

pattern KeycodeJ :: Keycode #

pattern KeycodeI :: Keycode #

pattern KeycodeH :: Keycode #

pattern KeycodeG :: Keycode #

pattern KeycodeF :: Keycode #

pattern KeycodeE :: Keycode #

pattern KeycodeD :: Keycode #

pattern KeycodeC :: Keycode #

pattern KeycodeB :: Keycode #

pattern KeycodeA :: Keycode #

pattern KeycodeAt :: Keycode #

pattern KeycodeLess :: Keycode #

pattern Keycode9 :: Keycode #

pattern Keycode8 :: Keycode #

pattern Keycode7 :: Keycode #

pattern Keycode6 :: Keycode #

pattern Keycode5 :: Keycode #

pattern Keycode4 :: Keycode #

pattern Keycode3 :: Keycode #

pattern Keycode2 :: Keycode #

pattern Keycode1 :: Keycode #

pattern Keycode0 :: Keycode #

pattern KeycodePlus :: Keycode #

pattern KeycodeHash :: Keycode #

pattern KeycodeTab :: Keycode #

pattern ScancodeUp :: Scancode #

pattern ScancodeF9 :: Scancode #

pattern ScancodeF8 :: Scancode #

pattern ScancodeF7 :: Scancode #

pattern ScancodeF6 :: Scancode #

pattern ScancodeF5 :: Scancode #

pattern ScancodeF4 :: Scancode #

pattern ScancodeF3 :: Scancode #

pattern ScancodeF2 :: Scancode #

pattern ScancodeF1 :: Scancode #

pattern Scancode0 :: Scancode #

pattern Scancode9 :: Scancode #

pattern Scancode8 :: Scancode #

pattern Scancode7 :: Scancode #

pattern Scancode6 :: Scancode #

pattern Scancode5 :: Scancode #

pattern Scancode4 :: Scancode #

pattern Scancode3 :: Scancode #

pattern Scancode2 :: Scancode #

pattern Scancode1 :: Scancode #

pattern ScancodeZ :: Scancode #

pattern ScancodeY :: Scancode #

pattern ScancodeX :: Scancode #

pattern ScancodeW :: Scancode #

pattern ScancodeV :: Scancode #

pattern ScancodeU :: Scancode #

pattern ScancodeT :: Scancode #

pattern ScancodeS :: Scancode #

pattern ScancodeR :: Scancode #

pattern ScancodeQ :: Scancode #

pattern ScancodeP :: Scancode #

pattern ScancodeO :: Scancode #

pattern ScancodeN :: Scancode #

pattern ScancodeM :: Scancode #

pattern ScancodeL :: Scancode #

pattern ScancodeK :: Scancode #

pattern ScancodeJ :: Scancode #

pattern ScancodeI :: Scancode #

pattern ScancodeH :: Scancode #

pattern ScancodeG :: Scancode #

pattern ScancodeF :: Scancode #

pattern ScancodeE :: Scancode #

pattern ScancodeD :: Scancode #

pattern ScancodeC :: Scancode #

pattern ScancodeB :: Scancode #

pattern ScancodeA :: Scancode #

time :: (Fractional a, MonadIO m) => m a #

The current time in seconds since some arbitrary starting point (consist over the life of the application).

This time is derived from the system's performance counter - see SDL_GetPerformanceFrequency and SDL_GetPerformanceCounter for C documentation about the implementation.

vector :: Num a => V3 a -> V4 a #

Convert a 3-dimensional affine vector into a 4-dimensional homogeneous vector, i.e. sets the w coordinate to 0.

get :: (HasGetter t a, MonadIO m) => t -> m a #

($~) :: (HasUpdate t a b, MonadIO m) => t -> (a -> b) -> m () infixr 2 #

Transform the contents of a state variable with a given funtion.

($~!) :: (HasUpdate t a b, MonadIO m) => t -> (a -> b) -> m () infixr 2 #

This is a variant of $~ which is strict in the transformed value.

($=) :: (HasSetter t a, MonadIO m) => t -> a -> m () infixr 2 #

Write a new value into a state variable.

($=!) :: (HasSetter t a, MonadIO m) => t -> a -> m () infixr 2 #

This is a variant of $= which is strict in the value to be set.

transpose :: (Distributive g, Functor f) => f (g a) -> g (f a) #

transpose is just an alias for distribute

transpose (V3 (V2 1 2) (V2 3 4) (V2 5 6))

V2 (V3 1 3 5) (V3 2 4 6)

rotate :: (Conjugate a, RealFloat a) => Quaternion a -> V3 a -> V3 a #

Apply a rotation to a vector.

outer :: (Functor f, Functor g, Num a) => f a -> g a -> f (g a) #

Outer (tensor) product of two vectors

(#.) :: Coercible c b => (b -> c) -> (a -> b) -> a -> c #

copy #

Arguments

:: MonadIO m 
=> Renderer

The rendering context

-> Texture

The source texture

-> Maybe (Rectangle CInt)

The source rectangle to copy, or Nothing for the whole texture

-> Maybe (Rectangle CInt)

The destination rectangle to copy to, or Nothing for the whole rendering target. The texture will be stretched to fill the given rectangle.

-> m () 

Copy a portion of the texture to the current rendering target.

See SDL_RenderCopy for C documentation.

clear :: (Functor m, MonadIO m) => Renderer -> m () #

Clear the current rendering target with the drawing color.

See SDL_RenderClear for C documentation.

version :: (Integral a, MonadIO m) => m (a, a, a) #

The major, minor, and patch versions of the SDL library linked with. Does not require initialization.

(.#) :: Coercible b a => (b -> c) -> (a -> b) -> a -> c #

unit :: (Additive t, Num a) => ASetter' (t a) a -> t a #

Create a unit vector.

>>> unit _x :: V2 Int
V2 1 0

adjoint :: (Functor m, Distributive n, Conjugate a) => m (n a) -> n (m a) #

Hermitian conjugate or conjugate transpose

>>> adjoint (V2 (V2 (1 :+ 2) (3 :+ 4)) (V2 (5 :+ 6) (7 :+ 8)))
V2 (V2 (1.0 :+ (-2.0)) (5.0 :+ (-6.0))) (V2 (3.0 :+ (-4.0)) (7.0 :+ (-8.0)))

putLinear :: (Binary a, Foldable t) => t a -> Put #

Serialize a linear type.

getLinear :: (Binary a, Applicative t, Traversable t) => Get (t a) #

Deserialize a linear type.

negated :: (Functor f, Num a) => f a -> f a #

Compute the negation of a vector

>>> negated (V2 2 4)
V2 (-2) (-4)

sumV :: (Foldable f, Additive v, Num a) => f (v a) -> v a #

Sum over multiple vectors

>>> sumV [V2 1 1, V2 3 4]
V2 4 5

(*^) :: (Functor f, Num a) => a -> f a -> f a infixl 7 #

Compute the left scalar product

>>> 2 *^ V2 3 4
V2 6 8

(^*) :: (Functor f, Num a) => f a -> a -> f a infixl 7 #

Compute the right scalar product

>>> V2 3 4 ^* 2
V2 6 8

(^/) :: (Functor f, Fractional a) => f a -> a -> f a infixl 7 #

Compute division by a scalar on the right.

basis :: (Additive t, Traversable t, Num a) => [t a] #

Produce a default basis for a vector space. If the dimensionality of the vector space is not statically known, see basisFor.

basisFor :: (Traversable t, Num a) => t b -> [t a] #

Produce a default basis for a vector space from which the argument is drawn.

scaled :: (Traversable t, Num a) => t a -> t (t a) #

Produce a diagonal (scale) matrix from a vector.

>>> scaled (V2 2 3)
V2 (V2 2 0) (V2 0 3)

normalize :: (Floating a, Metric f, Epsilon a) => f a -> f a #

Normalize a Metric functor to have unit norm. This function does not change the functor if its norm is 0 or 1.

project :: (Metric v, Fractional a) => v a -> v a -> v a #

project u v computes the projection of v onto u.

ex :: forall (t :: Type -> Type). R1 t => E t #

_yx :: forall (t :: Type -> Type) a. R2 t => Lens' (t a) (V2 a) #

>>> V2 1 2 ^. _yx
V2 2 1

ey :: forall (t :: Type -> Type). R2 t => E t #

perp :: Num a => V2 a -> V2 a #

the counter-clockwise perpendicular vector

>>> perp $ V2 10 20
V2 (-20) 10

angle :: Floating a => a -> V2 a #

unangle :: (Floating a, Ord a) => V2 a -> a #

crossZ :: Num a => V2 a -> V2 a -> a #

The Z-component of the cross product of two vectors in the XY-plane.

>>> crossZ (V2 1 0) (V2 0 1)
1

_xz :: forall (t :: Type -> Type) a. R3 t => Lens' (t a) (V2 a) #

_yz :: forall (t :: Type -> Type) a. R3 t => Lens' (t a) (V2 a) #

_zx :: forall (t :: Type -> Type) a. R3 t => Lens' (t a) (V2 a) #

_zy :: forall (t :: Type -> Type) a. R3 t => Lens' (t a) (V2 a) #

_xzy :: forall (t :: Type -> Type) a. R3 t => Lens' (t a) (V3 a) #

_yxz :: forall (t :: Type -> Type) a. R3 t => Lens' (t a) (V3 a) #

_yzx :: forall (t :: Type -> Type) a. R3 t => Lens' (t a) (V3 a) #

_zxy :: forall (t :: Type -> Type) a. R3 t => Lens' (t a) (V3 a) #

_zyx :: forall (t :: Type -> Type) a. R3 t => Lens' (t a) (V3 a) #

ez :: forall (t :: Type -> Type). R3 t => E t #

cross :: Num a => V3 a -> V3 a -> V3 a #

cross product

triple :: Num a => V3 a -> V3 a -> V3 a -> a #

scalar triple product

_xw :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V2 a) #

_yw :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V2 a) #

_zw :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V2 a) #

_wx :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V2 a) #

_wy :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V2 a) #

_wz :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V2 a) #

_xyw :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V3 a) #

_xzw :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V3 a) #

_xwy :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V3 a) #

_xwz :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V3 a) #

_yxw :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V3 a) #

_yzw :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V3 a) #

_ywx :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V3 a) #

_ywz :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V3 a) #

_zxw :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V3 a) #

_zyw :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V3 a) #

_zwx :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V3 a) #

_zwy :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V3 a) #

_wxy :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V3 a) #

_wxz :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V3 a) #

_wyx :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V3 a) #

_wyz :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V3 a) #

_wzx :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V3 a) #

_wzy :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V3 a) #

_xywz :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_xzyw :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_xzwy :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_xwyz :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_xwzy :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_yxzw :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_yxwz :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_yzxw :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_yzwx :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_ywxz :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_ywzx :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_zxyw :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_zxwy :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_zyxw :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_zywx :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_zwxy :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_zwyx :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_wxyz :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_wxzy :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_wyxz :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_wyzx :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_wzxy :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

_wzyx :: forall (t :: Type -> Type) a. R4 t => Lens' (t a) (V4 a) #

ew :: forall (t :: Type -> Type). R4 t => E t #

point :: Num a => V3 a -> V4 a #

Convert a 3-dimensional affine point into a 4-dimensional homogeneous vector, i.e. sets the w coordinate to 1.

normalizePoint :: Fractional a => V4 a -> V3 a #

Convert 4-dimensional projective coordinates to a 3-dimensional point. This operation may be denoted, euclidean [x:y:z:w] = (x/w, y/w, z/w) where the projective, homogenous, coordinate [x:y:z:w] is one of many associated with a single point (x/w, y/w, z/w).

ee :: forall (t :: Type -> Type). Complicated t => E t #

ei :: forall (t :: Type -> Type). Complicated t => E t #

ej :: forall (t :: Type -> Type). Hamiltonian t => E t #

ek :: forall (t :: Type -> Type). Hamiltonian t => E t #

absi :: Floating a => Quaternion a -> a #

norm of the imaginary component

pow :: RealFloat a => Quaternion a -> a -> Quaternion a #

raise a Quaternion to a scalar power

asinq :: RealFloat a => Quaternion a -> Quaternion a -> Quaternion a #

asin with a specified branch cut.

acosq :: RealFloat a => Quaternion a -> Quaternion a -> Quaternion a #

acos with a specified branch cut.

atanq :: RealFloat a => Quaternion a -> Quaternion a -> Quaternion a #

atan with a specified branch cut.

asinhq :: RealFloat a => Quaternion a -> Quaternion a -> Quaternion a #

asinh with a specified branch cut.

acoshq :: RealFloat a => Quaternion a -> Quaternion a -> Quaternion a #

acosh with a specified branch cut.

atanhq :: RealFloat a => Quaternion a -> Quaternion a -> Quaternion a #

atanh with a specified branch cut.

slerp :: RealFloat a => Quaternion a -> Quaternion a -> a -> Quaternion a #

Spherical linear interpolation between two quaternions.

axisAngle :: (Epsilon a, Floating a) => V3 a -> a -> Quaternion a #

axisAngle axis theta builds a Quaternion representing a rotation of theta radians about axis.

frobenius :: (Num a, Foldable f, Additive f, Additive g, Distributive g, Trace g) => f (g a) -> a #

Compute the Frobenius norm of a matrix.

column :: forall (f :: Type -> Type) a b s t. Representable f => LensLike (Context a b) s t a b -> Lens (f s) (f t) (f a) (f b) #

This is a generalization of inside to work over any corepresentable Functor.

column :: Representable f => ReifiedLens s t a b -> ReifiedLens (f s) (f t) (f a) (f b)

In practice it is used to access a column of a matrix.

>>> V2 (V3 1 2 3) (V3 4 5 6) ^._x
V3 1 2 3
>>> V2 (V3 1 2 3) (V3 4 5 6) ^.column _x
V2 1 4

(!*!) :: (Functor m, Foldable t, Additive t, Additive n, Num a) => m (t a) -> t (n a) -> m (n a) infixl 7 #

Matrix product. This can compute any combination of sparse and dense multiplication.

>>> V2 (V3 1 2 3) (V3 4 5 6) !*! V3 (V2 1 2) (V2 3 4) (V2 4 5)
V2 (V2 19 25) (V2 43 58)
>>> V2 (IntMap.fromList [(1,2)]) (IntMap.fromList [(2,3)]) !*! IntMap.fromList [(1,V3 0 0 1), (2, V3 0 0 5)]
V2 (V3 0 0 2) (V3 0 0 15)

(!+!) :: (Additive m, Additive n, Num a) => m (n a) -> m (n a) -> m (n a) infixl 6 #

Entry-wise matrix addition.

>>> V2 (V3 1 2 3) (V3 4 5 6) !+! V2 (V3 7 8 9) (V3 1 2 3)
V2 (V3 8 10 12) (V3 5 7 9)

(!-!) :: (Additive m, Additive n, Num a) => m (n a) -> m (n a) -> m (n a) infixl 6 #

Entry-wise matrix subtraction.

>>> V2 (V3 1 2 3) (V3 4 5 6) !-! V2 (V3 7 8 9) (V3 1 2 3)
V2 (V3 (-6) (-6) (-6)) (V3 3 3 3)

(!*) :: (Functor m, Foldable r, Additive r, Num a) => m (r a) -> r a -> m a infixl 7 #

Matrix * column vector

>>> V2 (V3 1 2 3) (V3 4 5 6) !* V3 7 8 9
V2 50 122

(*!) :: (Num a, Foldable t, Additive f, Additive t) => t a -> t (f a) -> f a infixl 7 #

Row vector * matrix

>>> V2 1 2 *! V2 (V3 3 4 5) (V3 6 7 8)
V3 15 18 21

(*!!) :: (Functor m, Functor r, Num a) => a -> m (r a) -> m (r a) infixl 7 #

Scalar-matrix product

>>> 5 *!! V2 (V2 1 2) (V2 3 4)
V2 (V2 5 10) (V2 15 20)

(!!*) :: (Functor m, Functor r, Num a) => m (r a) -> a -> m (r a) infixl 7 #

Matrix-scalar product

>>> V2 (V2 1 2) (V2 3 4) !!* 5
V2 (V2 5 10) (V2 15 20)

(!!/) :: (Functor m, Functor r, Fractional a) => m (r a) -> a -> m (r a) infixl 7 #

Matrix-scalar division

fromQuaternion :: Num a => Quaternion a -> M33 a #

Build a rotation matrix from a unit Quaternion.

mkTransformationMat :: Num a => M33 a -> V3 a -> M44 a #

Build a transformation matrix from a rotation matrix and a translation vector.

mkTransformation :: Num a => Quaternion a -> V3 a -> M44 a #

Build a transformation matrix from a rotation expressed as a Quaternion and a translation vector.

m43_to_m44 :: Num a => M43 a -> M44 a #

Convert from a 4x3 matrix to a 4x4 matrix, extending it with the [ 0 0 0 1 ] column vector

m33_to_m44 :: Num a => M33 a -> M44 a #

Convert a 3x3 matrix to a 4x4 matrix extending it with 0's in the new row and column.

identity :: (Num a, Traversable t, Applicative t) => t (t a) #

The identity matrix for any dimension vector.

>>> identity :: M44 Int
V4 (V4 1 0 0 0) (V4 0 1 0 0) (V4 0 0 1 0) (V4 0 0 0 1)
>>> identity :: V3 (V3 Int)
V3 (V3 1 0 0) (V3 0 1 0) (V3 0 0 1)

translation :: forall (t :: Type -> Type) (v :: Type -> Type) a. (Representable t, R3 t, R4 v) => Lens' (t (v a)) (V3 a) #

Extract the translation vector (first three entries of the last column) from a 3x4 or 4x4 matrix.

_m22 :: forall (t :: Type -> Type) (v :: Type -> Type) a. (Representable t, R2 t, R2 v) => Lens' (t (v a)) (M22 a) #

Extract a 2x2 matrix from a matrix of higher dimensions by dropping excess rows and columns.

_m23 :: forall (t :: Type -> Type) (v :: Type -> Type) a. (Representable t, R2 t, R3 v) => Lens' (t (v a)) (M23 a) #

Extract a 2x3 matrix from a matrix of higher dimensions by dropping excess rows and columns.

_m24 :: forall (t :: Type -> Type) (v :: Type -> Type) a. (Representable t, R2 t, R4 v) => Lens' (t (v a)) (M24 a) #

Extract a 2x4 matrix from a matrix of higher dimensions by dropping excess rows and columns.

_m32 :: forall (t :: Type -> Type) (v :: Type -> Type) a. (Representable t, R3 t, R2 v) => Lens' (t (v a)) (M32 a) #

Extract a 3x2 matrix from a matrix of higher dimensions by dropping excess rows and columns.

_m33 :: forall (t :: Type -> Type) (v :: Type -> Type) a. (Representable t, R3 t, R3 v) => Lens' (t (v a)) (M33 a) #

Extract a 3x3 matrix from a matrix of higher dimensions by dropping excess rows and columns.

_m34 :: forall (t :: Type -> Type) (v :: Type -> Type) a. (Representable t, R3 t, R4 v) => Lens' (t (v a)) (M34 a) #

Extract a 3x4 matrix from a matrix of higher dimensions by dropping excess rows and columns.

_m42 :: forall (t :: Type -> Type) (v :: Type -> Type) a. (Representable t, R4 t, R2 v) => Lens' (t (v a)) (M42 a) #

Extract a 4x2 matrix from a matrix of higher dimensions by dropping excess rows and columns.

_m43 :: forall (t :: Type -> Type) (v :: Type -> Type) a. (Representable t, R4 t, R3 v) => Lens' (t (v a)) (M43 a) #

Extract a 4x3 matrix from a matrix of higher dimensions by dropping excess rows and columns.

_m44 :: forall (t :: Type -> Type) (v :: Type -> Type) a. (Representable t, R4 t, R4 v) => Lens' (t (v a)) (M44 a) #

Extract a 4x4 matrix from a matrix of higher dimensions by dropping excess rows and columns.

det22 :: Num a => M22 a -> a #

2x2 matrix determinant.

>>> det22 (V2 (V2 a b) (V2 c d))
a * d - b * c

det33 :: Num a => M33 a -> a #

3x3 matrix determinant.

>>> det33 (V3 (V3 a b c) (V3 d e f) (V3 g h i))
a * (e * i - f * h) - d * (b * i - c * h) + g * (b * f - c * e)

det44 :: Num a => M44 a -> a #

4x4 matrix determinant.

inv22 :: Fractional a => M22 a -> M22 a #

2x2 matrix inverse.

>>> inv22 $ V2 (V2 1 2) (V2 3 4)
V2 (V2 (-2.0) 1.0) (V2 1.5 (-0.5))

inv33 :: Fractional a => M33 a -> M33 a #

3x3 matrix inverse.

>>> inv33 $ V3 (V3 1 2 4) (V3 4 2 2) (V3 1 1 1)
V3 (V3 0.0 0.5 (-1.0)) (V3 (-0.5) (-0.75) 3.5) (V3 0.5 0.25 (-1.5))

inv44 :: Fractional a => M44 a -> M44 a #

4x4 matrix inverse.

lu :: (Num a, Fractional a, Foldable m, Traversable m, Applicative m, Additive m, Ixed (m a), Ixed (m (m a)), i ~ Index (m a), i ~ Index (m (m a)), Eq i, Integral i, a ~ IxValue (m a), m a ~ IxValue (m (m a)), Num (m a)) => m (m a) -> (m (m a), m (m a)) #

Compute the (L, U) decomposition of a square matrix using Crout's algorithm. The Index of the vectors must be Integral.

luFinite :: forall a m (n :: Nat). (Num a, Fractional a, Functor m, Finite m, n ~ Size m, KnownNat n, Num (m a)) => m (m a) -> (m (m a), m (m a)) #

Compute the (L, U) decomposition of a square matrix using Crout's algorithm, using the vector's Finite instance to provide an index.

forwardSub :: (Num a, Fractional a, Foldable m, Additive m, Ixed (m a), Ixed (m (m a)), i ~ Index (m a), i ~ Index (m (m a)), Eq i, Ord i, Integral i, a ~ IxValue (m a), m a ~ IxValue (m (m a))) => m (m a) -> m a -> m a #

Solve a linear system with a lower-triangular matrix of coefficients with forwards substitution.

forwardSubFinite :: forall a m (n :: Nat). (Num a, Fractional a, Foldable m, n ~ Size m, KnownNat n, Additive m, Finite m) => m (m a) -> m a -> m a #

Solve a linear system with a lower-triangular matrix of coefficients with forwards substitution, using the vector's Finite instance to provide an index.

backwardSub :: (Num a, Fractional a, Foldable m, Additive m, Ixed (m a), Ixed (m (m a)), i ~ Index (m a), i ~ Index (m (m a)), Eq i, Ord i, Integral i, a ~ IxValue (m a), m a ~ IxValue (m (m a))) => m (m a) -> m a -> m a #

Solve a linear system with an upper-triangular matrix of coefficients with backwards substitution.

backwardSubFinite :: forall a m (n :: Nat). (Num a, Fractional a, Foldable m, n ~ Size m, KnownNat n, Additive m, Finite m) => m (m a) -> m a -> m a #

Solve a linear system with an upper-triangular matrix of coefficients with backwards substitution, using the vector's Finite instance to provide an index.

luSolve :: (Num a, Fractional a, Foldable m, Traversable m, Applicative m, Additive m, Ixed (m a), Ixed (m (m a)), i ~ Index (m a), i ~ Index (m (m a)), Eq i, Integral i, a ~ IxValue (m a), m a ~ IxValue (m (m a)), Num (m a)) => m (m a) -> m a -> m a #

Solve a linear system with LU decomposition.

luSolveFinite :: forall a m (n :: Nat). (Num a, Fractional a, Functor m, Finite m, n ~ Size m, KnownNat n, Num (m a)) => m (m a) -> m a -> m a #

Solve a linear system with LU decomposition, using the vector's Finite instance to provide an index.

luInv :: (Num a, Fractional a, Foldable m, Traversable m, Applicative m, Additive m, Distributive m, Ixed (m a), Ixed (m (m a)), i ~ Index (m a), i ~ Index (m (m a)), Eq i, Integral i, a ~ IxValue (m a), m a ~ IxValue (m (m a)), Num (m a)) => m (m a) -> m (m a) #

Invert a matrix with LU decomposition.

luInvFinite :: forall a m (n :: Nat). (Num a, Fractional a, Functor m, Finite m, n ~ Size m, KnownNat n, Num (m a)) => m (m a) -> m (m a) #

Invert a matrix with LU decomposition, using the vector's Finite instance to provide an index.

luDet :: (Num a, Fractional a, Foldable m, Traversable m, Applicative m, Additive m, Trace m, Ixed (m a), Ixed (m (m a)), i ~ Index (m a), i ~ Index (m (m a)), Eq i, Integral i, a ~ IxValue (m a), m a ~ IxValue (m (m a)), Num (m a)) => m (m a) -> a #

Compute the determinant of a matrix using LU decomposition.

luDetFinite :: forall a m (n :: Nat). (Num a, Fractional a, Functor m, Finite m, n ~ Size m, KnownNat n, Num (m a)) => m (m a) -> a #

Compute the determinant of a matrix using LU decomposition, using the vector's Finite instance to provide an index.

lookAt #

Arguments

:: (Epsilon a, Floating a) 
=> V3 a

Eye

-> V3 a

Center

-> V3 a

Up

-> M44 a 

Build a look at view matrix

perspective #

Arguments

:: Floating a 
=> a

FOV (y direction, in radians)

-> a

Aspect ratio

-> a

Near plane

-> a

Far plane

-> M44 a 

Build a matrix for a symmetric perspective-view frustum

inversePerspective #

Arguments

:: Floating a 
=> a

FOV (y direction, in radians)

-> a

Aspect ratio

-> a

Near plane

-> a

Far plane

-> M44 a 

Build an inverse perspective matrix

frustum #

Arguments

:: Floating a 
=> a

Left

-> a

Right

-> a

Bottom

-> a

Top

-> a

Near

-> a

Far

-> M44 a 

Build a perspective matrix per the classic glFrustum arguments.

inverseFrustum #

Arguments

:: Floating a 
=> a

Left

-> a

Right

-> a

Bottom

-> a

Top

-> a

Near

-> a

Far

-> M44 a 

infinitePerspective #

Arguments

:: Floating a 
=> a

FOV (y direction, in radians)

-> a

Aspect Ratio

-> a

Near plane

-> M44 a 

Build a matrix for a symmetric perspective-view frustum with a far plane at infinite

inverseInfinitePerspective #

Arguments

:: Floating a 
=> a

FOV (y direction, in radians)

-> a

Aspect Ratio

-> a

Near plane

-> M44 a 

ortho #

Arguments

:: Fractional a 
=> a

Left

-> a

Right

-> a

Bottom

-> a

Top

-> a

Near

-> a

Far

-> M44 a 

Build an orthographic perspective matrix from 6 clipping planes. This matrix takes the region delimited by these planes and maps it to normalized device coordinates between [-1,1]

This call is designed to mimic the parameters to the OpenGL glOrtho call, so it has a slightly strange convention: Notably: the near and far planes are negated.

Consequently:

ortho l r b t n f !* V4 l b (-n) 1 = V4 (-1) (-1) (-1) 1
ortho l r b t n f !* V4 r t (-f) 1 = V4 1 1 1 1

Examples:

>>> ortho 1 2 3 4 5 6 !* V4 1 3 (-5) 1
V4 (-1.0) (-1.0) (-1.0) 1.0
>>> ortho 1 2 3 4 5 6 !* V4 2 4 (-6) 1
V4 1.0 1.0 1.0 1.0

inverseOrtho #

Arguments

:: Fractional a 
=> a

Left

-> a

Right

-> a

Bottom

-> a

Top

-> a

Near

-> a

Far

-> M44 a 

Build an inverse orthographic perspective matrix from 6 clipping planes

multRep :: (Representable f, Algebra r (Rep f)) => f (f r) -> f r #

unitalRep :: (Representable f, Algebra r (Rep f)) => r -> f r #

comultRep :: (Representable f, Coalgebra r (Rep f)) => f r -> f (f r) #

counitalRep :: (Representable f, Coalgebra r (Rep f)) => f r -> r #

($*) :: Representable f => Covector r (Rep f) -> f r -> r infixr 0 #

qdA :: (Affine p, Foldable (Diff p), Num a) => p a -> p a -> a #

Compute the quadrance of the difference (the square of the distance)

distanceA :: (Floating a, Foldable (Diff p), Affine p) => p a -> p a -> a #

Distance between two points in an affine space

lensP :: forall f1 a g b f2. Functor f2 => (f1 a -> f2 (g b)) -> Point f1 a -> f2 (Point g b) #

_Point :: forall f1 a g b p f2. (Profunctor p, Functor f2) => p (f1 a) (f2 (g b)) -> p (Point f1 a) (f2 (Point g b)) #

unP :: Point f a -> f a #

origin :: forall (f :: Type -> Type) a. (Additive f, Num a) => Point f a #

Vector spaces have origins.

relative :: forall (f :: Type -> Type) a. (Additive f, Num a) => Point f a -> Iso' (Point f a) (f a) #

An isomorphism between points and vectors, given a reference point.

windowSize :: Window -> StateVar (V2 CInt) #

Get or set the size of a window's client area. Values beyond the maximum supported size are clamped.

If window was created with windowHighDPI flag, this size may differ from the size in pixels. Use glGetDrawableSize or vkGetDrawableSize to get size in pixels.

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_SetWindowSize and SDL_GetWindowSize for C documentation.

initialize :: (Foldable f, Functor m, MonadIO m) => f InitFlag -> m () #

Initializes SDL and the given subsystems. Do not call any SDL functions prior to this one, unless otherwise documented that you may do so.

You may call this function again with additional subsystems to initialize.

Throws SDLException if initialization fails.

getPowerInfo :: (Functor m, MonadIO m) => m PowerState #

Current power supply details.

Throws SDLException if the current power state can not be determined.

See SDL_GetPowerInfo for C documentation.

surfaceFormat :: MonadIO m => Surface -> m SurfacePixelFormat #

Inspect the pixel format under a surface.

surfacePixels :: MonadIO m => Surface -> m (Ptr ()) #

Obtain the pointer to the underlying pixels in a surface. You should bracket this call with lockSurface and unlockSurface, respectively.

eventTimestamp :: Event -> Timestamp #

The time the event occurred.

eventPayload :: Event -> EventPayload #

Data pertaining to this event.

addTimer :: MonadIO m => Word32 -> TimerCallback -> m Timer #

Set up a callback function to be run on a separate thread after the specified number of milliseconds has elapsed.

See SDL_AddTimer for C documentation.

removeTimer :: MonadIO m => Timer -> m Bool #

Remove a Timer.

See SDL_RemoveTimer for C documentation.

getBasePath :: MonadIO m => m Text #

An absolute path to the application data directory.

The path is guaranteed to end with a path separator.

Throws SDLException on failure, or if the platform does not implement this functionality.

getPrefPath :: MonadIO m => Text -> Text -> m Text #

A path to a unique per user and per application directory for the given organization and application name, intended for writing preferences and other personal files.

The path is guaranteed to end with a path separator.

You should assume the path returned by this function is the only safe place to write files to.

Throws SDLException on failure.

addEventWatch :: MonadIO m => EventWatchCallback -> m EventWatch #

Trigger an EventWatchCallback when an event is added to the SDL event queue.

See https://wiki.libsdl.org/SDL_AddEventWatch for C documentation.

delEventWatch :: MonadIO m => EventWatch -> m () #

Remove an EventWatch.

See https://wiki.libsdl.org/SDL_DelEventWatch for C documentation.

pollEvent :: MonadIO m => m (Maybe Event) #

Poll for currently pending events. You can only call this function in the OS thread that set the video mode.

pumpEvents :: MonadIO m => m () #

Pump the event loop, gathering events from the input devices.

This function updates the event queue and internal input device state.

This should only be run in the OS thread that initialized the video subsystem, and for extra safety, you should consider only doing those things on the main thread in any case.

pumpEvents gathers all the pending input information from devices and places it in the event queue. Without calls to pumpEvents no events would ever be placed on the queue. Often the need for calls to pumpEvents is hidden from the user since pollEvent and waitEvent implicitly call pumpEvents. However, if you are not polling or waiting for events (e.g. you are filtering them), then you must call pumpEvents to force an event queue update.

See SDL_PumpEvents for C documentation.

waitEvent :: MonadIO m => m Event #

Wait indefinitely for the next available event.

waitEventTimeout #

Arguments

:: MonadIO m 
=> CInt

The maximum amount of time to wait, in milliseconds.

-> m (Maybe Event) 

Wait until the specified timeout for the next available amount.

getKeyboardState :: MonadIO m => m (Scancode -> Bool) #

Get a snapshot of the current state of the keyboard.

This computation generates a mapping from Scancode to Bool - evaluating the function at specific Scancodes will inform you as to whether or not that key was held down when getKeyboardState was called.

See SDL_GetKeyboardState for C documentation.

getModState :: (Functor m, MonadIO m) => m KeyModifier #

Get the current key modifier state for the keyboard. The key modifier state is a mask special keys that are held down.

See SDL_GetModState for C documentation.

getScancodeName :: MonadIO m => Scancode -> m String #

Get a human-readable name for a scancode. If the scancode doesn't have a name this function returns the empty string.

See SDL_GetScancodeName for C documentation.

hasScreenKeyboardSupport :: MonadIO m => m Bool #

Check whether the platform has screen keyboard support.

See SDL_HasScreenKeyboardSupport for C documentation.

isScreenKeyboardShown :: MonadIO m => Window -> m Bool #

Check whether the screen keyboard is shown for the given window.

See SDL_IsScreenKeyboardShown for C documentation.

startTextInput :: MonadIO m => Rect -> m () #

Set the rectangle used to type text inputs and start accepting text input events.

See SDL_StartTextInput for C documentation.

stopTextInput :: MonadIO m => m () #

Stop receiving any text input events.

See SDL_StopTextInput for C documentation.

createColorCursor #

Arguments

:: MonadIO m 
=> Surface 
-> Point V2 CInt

The location of the cursor hot spot

-> m Cursor 

Create a color cursor.

See SDL_CreateColorCursor for C documentation.

createCursor #

Arguments

:: MonadIO m 
=> Vector Word8

Whether this part of the cursor is black. Use False for white and True for black.

-> Vector Word8

Whether or not pixels are visible. Use True for visible and False for transparent.

-> V2 CInt

The width and height of the cursor.

-> Point V2 CInt

The X- and Y-axis location of the upper left corner of the cursor relative to the actual mouse position

-> m Cursor 

Create a cursor using the specified bitmap data and mask (in MSB format).

createSystemCursor :: MonadIO m => SystemCursor -> m Cursor #

Create system cursor.

See SDL_CreateSystemCursor for C documentation.

freeCursor :: MonadIO m => Cursor -> m () #

Free a cursor created with createCursor, createColorCusor and createSystemCursor.

See SDL_FreeCursor for C documentation.

numJoysticks :: MonadIO m => m CInt #

Count the number of joysticks attached to the system.

See SDL_NumJoysticks for C documentation.

quit :: MonadIO m => m () #

Quit and shutdown SDL, freeing any resources that may have been in use. Do not call any SDL functions after you've called this function, unless otherwise documented that you may do so.

clearHints :: MonadIO m => m () #

setHintWithPriority :: MonadIO m => HintPriority -> Hint v -> v -> m Bool #

Set the value of a hint, applying priority rules for when there is a conflict. Ordinarily, a hint will not be set if there is an existing override hint or environment variable that takes precedence.

audioInit :: MonadIO m => AudioDriver -> m () #

Explicitly initialize the audio system against a specific AudioDriver. Note that most users will not need to do this, as the normal initialization routines will already take care of this for you.

closeAudioDevice :: MonadIO m => AudioDevice -> m () #

See SDL_CloseAudioDevice for C documentation.

openAudioDevice :: MonadIO m => OpenDeviceSpec -> m (AudioDevice, AudioSpec) #

Attempt to open the closest matching AudioDevice, as specified by the given OpenDeviceSpec.

See SDL_OpenAudioDevice for C documentation.

createWindow :: MonadIO m => Text -> WindowConfig -> m Window #

Create a window with the given title and configuration.

Throws SDLException on failure.

destroyWindow :: MonadIO m => Window -> m () #

Destroy the given window. The Window handler may not be used afterwards.

glBindTexture #

Arguments

:: (Functor m, MonadIO m) 
=> Texture

The texture to bind to the current OpenGL/ES/ES2 context

-> m () 

Bind an OpenGL/ES/ES2 texture to the current context for use with when rendering OpenGL primitives directly.

See SDL_GL_BindTexture for C documentation.

glCreateContext :: (Functor m, MonadIO m) => Window -> m GLContext #

Create a new OpenGL context and makes it the current context for the window.

Throws SDLException if the window wasn't configured with OpenGL support, or if context creation fails.

See SDL_GL_CreateContext for C documentation.

glDeleteContext :: MonadIO m => GLContext -> m () #

Delete the given OpenGL context.

You must make sure that there are no pending commands in the OpenGL command queue, the driver may still be processing commands even if you have stopped issuing them!

The glFinish command will block until the command queue has been fully processed. You should call that function before deleting a context.

See SDL_GL_DeleteContext for C documentation.

glGetDrawableSize :: MonadIO m => Window -> m (V2 CInt) #

Get the size of a window's underlying drawable area in pixels (for use with glViewport).

It may differ from windowSize if window was created with windowHighDPI flag.

glMakeCurrent :: (Functor m, MonadIO m) => Window -> GLContext -> m () #

Set up an OpenGL context for rendering into an OpenGL window.

Throws SDLException on failure.

See SDL_GL_MakeCurrent for C documentation.

glSwapWindow :: MonadIO m => Window -> m () #

Replace the contents of the front buffer with the back buffer's. The contents of the back buffer are undefined, clear them with glClear or equivalent before drawing to them again.

See SDL_GL_SwapWindow for C documentation.

glUnbindTexture #

Arguments

:: (Functor m, MonadIO m) 
=> Texture

The texture to unbind from the current OpenGL/ES/ES2 context

-> m () 

Unbind an OpenGL/ES/ES2 texture from the current context.

See SDL_GL_UnbindTexture for C documentation.

getWindowBordersSize :: MonadIO m => Window -> m (Maybe (V4 CInt)) #

Get the size of a window's borders (decorations) around the client area (top, left, bottom, right).

See SDL_GetWindowBordersSize for C documentation.

getWindowPixelFormat :: MonadIO m => Window -> m PixelFormat #

Get the pixel format that is used for the given window.

getWindowSurface :: (Functor m, MonadIO m) => Window -> m Surface #

Get the SDL surface associated with the window.

See SDL_GetWindowSurface for C documentation.

hideWindow :: MonadIO m => Window -> m () #

Hide a window.

See SDL_HideWindow for C documentation.

raiseWindow :: MonadIO m => Window -> m () #

Raise the window above other windows and set the input focus.

See SDL_RaiseWindow for C documentation.

setWindowIcon :: MonadIO m => Window -> Surface -> m () #

Set the icon for a window.

setWindowPosition :: MonadIO m => Window -> WindowPosition -> m () #

Set the position of the window.

showSimpleMessageBox :: MonadIO m => Maybe Window -> MessageKind -> Text -> Text -> m () #

Show a simple message box with the given title and a message. Consider writing your messages to stderr too.

Throws SDLException if there are no available video targets.

showWindow :: MonadIO m => Window -> m () #

Show a window.

See SDL_ShowWindow for C documentation.

updateWindowSurface :: (Functor m, MonadIO m) => Window -> m () #

Copy the window surface to the screen.

This is the function you use to reflect any changes to the surface on the screen.

See SDL_UpdateWindowSurface for C documentation.

createSoftwareRenderer :: MonadIO m => Surface -> m Renderer #

Create a 2D software rendering context for the given surface.

See https://wiki.libsdl.org/SDL_CreateSoftwareRenderer

createTexture #

Arguments

:: (Functor m, MonadIO m) 
=> Renderer

The rendering context.

-> PixelFormat 
-> TextureAccess 
-> V2 CInt

The size of the texture.

-> m Texture 

Create a texture for a rendering context.

See SDL_CreateTexture for C documentation.

createTextureFromSurface #

Arguments

:: (Functor m, MonadIO m) 
=> Renderer

The rendering context

-> Surface

The surface containing pixel data used to fill the texture

-> m Texture 

Create a texture from an existing surface.

See SDL_CreateTextureFromSurface for C documentation.

destroyTexture :: MonadIO m => Texture -> m () #

Destroy the specified texture.

See SDL_DestroyTexture for the C documentation.

getRenderDriverInfo :: MonadIO m => m [RendererInfo] #

Enumerate all known render drivers on the system, and determine their supported features.

See SDL_GetRenderDriverInfo for C documentation.

getRendererInfo :: MonadIO m => Renderer -> m RendererInfo #

Get information about a rendering context.

See SDL_GetRendererInfo for C documentation.

lockTexture #

Arguments

:: MonadIO m 
=> Texture

The Texture to lock for access, which must have been created with TextureAccessStreaming

-> Maybe (Rectangle CInt)

The area to lock for access; Nothing to lock the entire texture

-> m (Ptr (), CInt)

A pointer to the locked pixels, appropriately offset by the locked area, and the pitch of the locked pixels (the pitch is the length of one row in bytes).

Lock a portion of the texture for *write-only* pixel access.

See SDL_LockTexture for C documentation.

queryTexture :: MonadIO m => Texture -> m TextureInfo #

Query the attributes of a texture.

See SDL_QueryTexture for C documentation.

renderGeometry :: MonadIO m => Renderer -> Maybe Texture -> Vector Vertex -> Vector CInt -> m () #

Render a list of triangles, optionally using a texture and indices into the vertex array Color and alpha modulation is done per vertex (SDL_SetTextureColorMod and SDL_SetTextureAlphaMod are ignored).

renderGeometryRaw :: (Storable ix, MonadIO m) => Renderer -> Maybe Texture -> Ptr FPoint -> CInt -> Ptr Color -> CInt -> Ptr FPoint -> CInt -> CInt -> Vector ix -> m () #

Render a list of triangles, optionally using a texture and indices into the vertex array Color and alpha modulation is done per vertex (SDL_SetTextureColorMod and SDL_SetTextureAlphaMod are ignored).

This version allows storeing vertex data in arbitrary types, but you have to provide pointers and strides yourself.

renderTargetSupported :: MonadIO m => Renderer -> m Bool #

Determine whether a window supports the use of render targets.

See SDL_RenderTargetSupported for C documentation.

unlockTexture :: MonadIO m => Texture -> m () #

Unlock a texture, uploading the changes to video memory, if needed.

Warning: See Bug No. 1586 before using this function!

See SDL_UnlockTexture for C documentation.

updateTexture #

Arguments

:: (Functor m, MonadIO m) 
=> Texture

The Texture to be updated

-> Maybe (Rectangle CInt)

The area to update, Nothing for entire texture

-> ByteString

The raw pixel data

-> CInt

The number of bytes in a row of pixel data, including padding between lines

-> m () 

Updates texture rectangle with new pixel data.

See SDL_UpdateTexture for C documentation.

setPaletteColors #

Arguments

:: MonadIO m 
=> Palette

The Palette to modify

-> Vector (V4 Word8)

A Vector of colours to copy into the palette

-> CInt

The index of the first palette entry to modify

-> m () 

Set a range of colors in a palette.

See SDL_SetPaletteColors for C documentation.

convertSurface #

Arguments

:: (Functor m, MonadIO m) 
=> Surface

The Surface to convert

-> SurfacePixelFormat

The pixel format that the new surface is optimized for

-> m Surface 

Copy an existing surface into a new one that is optimized for blitting to a surface of a specified pixel format.

This function is used to optimize images for faster repeat blitting. This is accomplished by converting the original and storing the result as a new surface. The new, optimized surface can then be used as the source for future blits, making them faster.

See SDL_ConvertSurface for C documentation.

createRGBSurface #

Arguments

:: (Functor m, MonadIO m) 
=> V2 CInt

The size of the surface

-> PixelFormat

The bit depth, red, green, blue and alpha mask for the pixels

-> m Surface 

Allocate a new RGB surface.

See SDL_CreateRGBSurface for C documentation.

createRGBSurfaceFrom #

Arguments

:: (Functor m, MonadIO m) 
=> IOVector Word8

The existing pixel data

-> V2 CInt

The size of the surface

-> CInt

The pitch - the length of a row of pixels in bytes

-> PixelFormat

The bit depth, red, green, blue and alpha mask for the pixels

-> m Surface 

Allocate a new RGB surface with existing pixel data.

See SDL_CreateRGBSurfaceFrom for C documentation.

fillRect #

Arguments

:: MonadIO m 
=> Renderer 
-> Maybe (Rectangle CInt)

The rectangle to fill.

-> m () 

Fill a rectangle on the current rendering target with the drawing color.

See SDL_RenderFillRect for C documentation.

fillRects :: MonadIO m => Renderer -> Vector (Rectangle CInt) -> m () #

Fill some number of rectangles on the current rendering target with the drawing color.

See SDL_RenderFillRects for C documentation.

freeSurface :: MonadIO m => Surface -> m () #

Free an RGB surface.

If the surface was created using createRGBSurfaceFrom then the pixel data is not freed.

See SDL_FreeSurface for the C documentation.

loadBMP :: MonadIO m => FilePath -> m Surface #

Load a surface from a BMP file.

See SDL_LoadBMP for C documentation.

lockSurface :: MonadIO m => Surface -> m () #

Set up a surface for directly accessing the pixels.

See SDL_LockSurface for C documentation.

unlockSurface :: MonadIO m => Surface -> m () #

Release a surface after directly accessing the pixels.

See SDL_UnlockSurface for C documentation.

getClipboardText :: MonadIO m => m Text #

Get the text from the clipboard.

Throws SDLException on failure.

hasClipboardText :: MonadIO m => m Bool #

Checks if the clipboard exists, and has some text in it.

setClipboardText :: MonadIO m => Text -> m () #

Replace the contents of the clipboard with the given text.

Throws SDLException on failure.

getAudioDeviceNames :: MonadIO m => AudioDeviceUsage -> m (Maybe (Vector Text)) #

Enumerate all AudioDevices attached to this system, that can be used as specified by the given AudioDeviceUsage. SDL cannot always guarantee that this list can be produced, in which case Nothing will be returned.

setAudioDeviceLocked :: MonadIO m => AudioDevice -> LockState -> m () #

Lock an AudioDevice such that its associated callback will not be called until the device is unlocked.

setAudioDevicePlaybackState :: MonadIO m => AudioDevice -> PlaybackState -> m () #

Change the playback state of an AudioDevice.

audioDriverName :: AudioDriver -> Text #

Get the human readable name of an AudioDriver

getAudioDrivers :: MonadIO m => m (Vector AudioDriver) #

Obtain a list of all possible audio drivers for this system. These drivers can be used to specificially initialize the audio system.

currentAudioDriver :: MonadIO m => m (Maybe Text) #

Query SDL for the name of the currently initialized audio driver, if possible. This will return Nothing if no driver has been initialized.

initializeAll :: (Functor m, MonadIO m) => m () #

Equivalent to initialize [minBound .. maxBound].

ticks :: MonadIO m => m Word32 #

Number of milliseconds since library initialization.

See SDL_GetTicks for C documentation.

availableJoysticks :: MonadIO m => m (Vector JoystickDevice) #

Enumerate all connected joysticks, retrieving a description of each.

openJoystick #

Arguments

:: (Functor m, MonadIO m) 
=> JoystickDevice

The device to open. Use availableJoysticks to find JoystickDevicess

-> m Joystick 

Open a joystick so that you can start receiving events from interaction with this joystick.

See SDL_JoystickOpen for C documentation.

closeJoystick :: MonadIO m => Joystick -> m () #

Close a joystick previously opened with openJoystick.

See SDL_JoystickClose for C documentation.

getJoystickID :: MonadIO m => Joystick -> m JoystickID #

Get the instance ID of an opened joystick. The instance ID is used to identify the joystick in future SDL events.

See SDL_JoystickInstanceID for C documentation.

buttonPressed #

Arguments

:: (Functor m, MonadIO m) 
=> Joystick 
-> CInt

The index of the button. You can use numButtons to determine how many buttons a given joystick has.

-> m Bool 

Determine if a given button is currently held.

See SDL_JoystickGetButton for C documentation.

ballDelta #

Arguments

:: MonadIO m 
=> Joystick 
-> CInt

The index of the joystick ball. You can use numBalls to determine how many balls a given joystick has.

-> m (V2 CInt) 

Get the ball axis change since the last poll.

See SDL_JoystickGetBall for C documentation.

axisPosition :: MonadIO m => Joystick -> CInt -> m Int16 #

Get the current state of an axis control on a joystick.

Returns a 16-bit signed integer representing the current position of the axis. The state is a value ranging from -32768 to 32767.

On most modern joysticks the x-axis is usually represented by axis 0 and the y-axis by axis 1. The value returned by axisPosition is a signed integer (-32768 to 32767) representing the current position of the axis. It may be necessary to impose certain tolerances on these values to account for jitter.

Some joysticks use axes 2 and 3 for extra buttons.

See SDL_JoystickGetAxis for C documentation.

numAxes :: MonadIO m => Joystick -> m CInt #

Get the number of general axis controls on a joystick.

See SDL_JoystickNumAxes for C documentation.

numButtons :: MonadIO m => Joystick -> m CInt #

Get the number of buttons on a joystick.

See SDL_JoystickNumButtons for C documentation.

numBalls :: MonadIO m => Joystick -> m CInt #

Get the number of trackballs on a joystick.

See SDL_JoystickNumBalls for C documentation.

getHat #

Arguments

:: (Functor m, MonadIO m) 
=> Joystick 
-> CInt

The index of the POV hat. You can use numHats to determine how many POV hats a given joystick has.

-> m JoyHatPosition 

Get current position of a POV hat on a joystick.

See SDL_JoystickGetHat for C documentation.

numHats :: MonadIO m => Joystick -> m CInt #

Get the number of POV hats on a joystick.

See SDL_JoystickNumHats for C documentation.

swapInterval :: StateVar SwapInterval #

Get or set the swap interval for the current OpenGL context.

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_GL_SetSwapInterval and SDL_GL_GetSwapInterval for C documentation.

surfaceBlit #

Arguments

:: MonadIO m 
=> Surface

The Surface to be copied from

-> Maybe (Rectangle CInt)

The rectangle to be copied, or Nothing to copy the entire surface

-> Surface

The Surface that is the blit target

-> Maybe (Point V2 CInt)

The position to blit to

-> m (Maybe (Rectangle CInt)) 

Perform a fast surface copy to a destination surface.

See SDL_BlitSurface for C documentation.

surfaceFillRect #

Arguments

:: MonadIO m 
=> Surface

The Surface that is the drawing target.

-> Maybe (Rectangle CInt)

The rectangle to fill, or Nothing to fill the entire surface.

-> V4 Word8

The color to fill with. If the color value contains an alpha component then the destination is simply filled with that alpha information, no blending takes place. This colour will be implictly mapped to the closest approximation that matches the surface's pixel format.

-> m () 

Perform a fast fill of a rectangle with a specific color.

If there is a clip rectangle set on the destination (set via clipRect), then this function will fill based on the intersection of the clip rectangle and the given Rectangle.

See SDL_FillRect for C documentation.

surfaceFillRects #

Arguments

:: MonadIO m 
=> Surface

The Surface that is the drawing target.

-> Vector (Rectangle CInt)

A Vector of Rectangles to be filled.

-> V4 Word8

The color to fill with. If the color value contains an alpha component then the destination is simply filled with that alpha information, no blending takes place. This colour will be implictly mapped to the closest approximation that matches the surface's pixel format.

-> m () 

Perform a fast fill of a set of rectangles with a specific color.

If there is a clip rectangle set on any of the destinations (set via clipRect), then this function will fill based on the intersection of the clip rectangle and the given Rectangles.

See SDL_FillRects for C documentation.

surfaceDimensions :: MonadIO m => Surface -> m (V2 CInt) #

Retrive the width and height of a Surface.

rendererDrawBlendMode :: Renderer -> StateVar BlendMode #

Get or set the blend mode used for drawing operations (fill and line).

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_SetRenderDrawBlendMode and SDL_GetRenderDrawBlendMode for C documentation.

rendererDrawColor :: Renderer -> StateVar (V4 Word8) #

Get or set the color used for drawing operations (rect, line and clear).

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_SetRenderDrawColor and SDL_GetRenderDrawColor for C documentation.

drawRect #

Arguments

:: MonadIO m 
=> Renderer 
-> Maybe (Rectangle CInt)

The rectangle outline to draw. Nothing for the entire rendering context.

-> m () 

Draw a rectangle outline on the current rendering target.

See SDL_RenderDrawRect for C documentation.

drawRects :: MonadIO m => Renderer -> Vector (Rectangle CInt) -> m () #

Draw some number of rectangles on the current rendering target.

See SDL_RenderDrawRects for C documentation.

copyF :: MonadIO m => Renderer -> Texture -> Maybe (Rectangle CInt) -> Maybe (Rectangle CFloat) -> m () #

Copy a portion of the texture to the current rendering target.

copyExF #

Arguments

:: MonadIO m 
=> Renderer

The rendering context

-> Texture

The source texture

-> Maybe (Rectangle CInt)

The source rectangle to copy, or Nothing for the whole texture

-> Maybe (Rectangle CFloat)

The destination rectangle to copy to, or Nothing for the whole rendering target. The texture will be stretched to fill the given rectangle.

-> CDouble

The angle of rotation in degrees. The rotation will be performed clockwise.

-> Maybe (Point V2 CFloat)

The point indicating the center of the rotation, or Nothing to rotate around the center of the destination rectangle

-> V2 Bool

Whether to flip the texture on the X and/or Y axis

-> m () 

Copy a portion of the texture to the current rendering target, optionally rotating it by angle around the given center and also flipping it top-bottom and/or left-right.

drawLineF :: MonadIO m => Renderer -> Point V2 CFloat -> Point V2 CFloat -> m () #

Draw a line between two points on the current rendering target.

drawLinesF :: MonadIO m => Renderer -> Vector (Point V2 CFloat) -> m () #

Draw a series of connected lines on the current rendering target.

drawPointF :: MonadIO m => Renderer -> Point V2 CFloat -> m () #

Draw a point on the current rendering target.

drawPointsF :: MonadIO m => Renderer -> Vector (Point V2 CFloat) -> m () #

Draw a collection of points on the current rendering target.

drawRectF :: MonadIO m => Renderer -> Rectangle CFloat -> m () #

Draw the outline of a rectangle on the current rendering target.

drawRectsF :: MonadIO m => Renderer -> Vector (Rectangle CFloat) -> m () #

Draw a series of rectangle outlines on the current rendering target.

fillRectF :: MonadIO m => Renderer -> Rectangle CFloat -> m () #

Draw a filled rectangle on the current rendering target.

fillRectsF :: MonadIO m => Renderer -> Vector (Rectangle CFloat) -> m () #

Draw a series of filled rectangles on the current rendering target.

rendererScale :: Renderer -> StateVar (V2 CFloat) #

Get or set the drawing scale for rendering on the current target.

The drawing coordinates are scaled by the x/y scaling factors before they are used by the renderer. This allows resolution independent drawing with a single coordinate system.

If this results in scaling or subpixel drawing by the rendering backend, it will be handled using the appropriate quality hints. For best results use integer scaling factors.

See SDL_RenderSetScale and SDL_RenderGetScale for C documentation.

rendererClipRect :: Renderer -> StateVar (Maybe (Rectangle CInt)) #

Get or set the clip rectangle for rendering on the specified target.

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_RenderSetClipRect and SDL_RenderGetClipRect for C documentation.

rendererViewport :: Renderer -> StateVar (Maybe (Rectangle CInt)) #

Get or set the drawing area for rendering on the current target.

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_RenderSetViewport and SDL_RenderGetViewport for C documentation.

present :: MonadIO m => Renderer -> m () #

Update the screen with any rendering performed since the previous call.

SDL's rendering functions operate on a backbuffer; that is, calling a rendering function such as drawLine does not directly put a line on the screen, but rather updates the backbuffer. As such, you compose your entire scene and present the composed backbuffer to the screen as a complete picture.

Therefore, when using SDL's rendering API, one does all drawing intended for the frame, and then calls this function once per frame to present the final drawing to the user.

The backbuffer should be considered invalidated after each present; do not assume that previous contents will exist between frames. You are strongly encouraged to call clear to initialize the backbuffer before starting each new frame's drawing, even if you plan to overwrite every pixel.

See SDL_RenderPresent for C documentation.

copyEx #

Arguments

:: MonadIO m 
=> Renderer

The rendering context

-> Texture

The source texture

-> Maybe (Rectangle CInt)

The source rectangle to copy, or Nothing for the whole texture

-> Maybe (Rectangle CInt)

The destination rectangle to copy to, or Nothing for the whole rendering target. The texture will be stretched to fill the given rectangle.

-> CDouble

The angle of rotation in degrees. The rotation will be performed clockwise.

-> Maybe (Point V2 CInt)

The point indicating the center of the rotation, or Nothing to rotate around the center of the destination rectangle

-> V2 Bool

Whether to flip the texture on the X and/or Y axis

-> m () 

Copy a portion of the texture to the current rendering target, optionally rotating it by angle around the given center and also flipping it top-bottom and/or left-right.

See SDL_RenderCopyEx for C documentation.

drawLine #

Arguments

:: (Functor m, MonadIO m) 
=> Renderer 
-> Point V2 CInt

The start point of the line

-> Point V2 CInt

The end point of the line

-> m () 

Draw a line on the current rendering target.

See SDL_RenderDrawLine for C documentation.

drawLines #

Arguments

:: MonadIO m 
=> Renderer 
-> Vector (Point V2 CInt)

A Vector of points along the line. SDL will draw lines between these points.

-> m () 

Draw a series of connected lines on the current rendering target.

See SDL_RenderDrawLines for C documentation.

drawPoint :: (Functor m, MonadIO m) => Renderer -> Point V2 CInt -> m () #

Draw a point on the current rendering target.

See SDL_RenderDrawPoint for C documentation.

drawPoints :: MonadIO m => Renderer -> Vector (Point V2 CInt) -> m () #

Draw multiple points on the current rendering target.

See SDL_RenderDrawPoints for C documentation.

surfaceBlitScaled #

Arguments

:: MonadIO m 
=> Surface

The Surface to be copied from

-> Maybe (Rectangle CInt)

The rectangle to be copied, or Nothing to copy the entire surface

-> Surface

The Surface that is the blit target

-> Maybe (Rectangle CInt)

The rectangle that is copied into, or Nothing to copy into the entire surface

-> m () 

Perform a scaled surface copy to a destination surface.

See SDL_BlitScaled for C documentation.

surfaceColorKey :: Surface -> StateVar (Maybe (V4 Word8)) #

Get or set the color key (transparent pixel color) for a surface.

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_SetColorKey and SDL_GetColorKey for C documentation.

textureColorMod :: Texture -> StateVar (V3 Word8) #

Get or set the additional color value multiplied into render copy operations.

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_SetTextureColorMod and SDL_GetTextureColorMod for C documentation.

textureAlphaMod :: Texture -> StateVar Word8 #

Get or set the additional alpha value multiplied into render copy operations.

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_SetTextureAlphaMod and SDL_GetTextureAlphaMod for C documentation.

textureBlendMode :: Texture -> StateVar BlendMode #

Get or set the blend mode used for texture copy operations.

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_SetTextureBlendMode and SDL_GetTextureBlendMode for C documentation.

surfaceBlendMode :: Surface -> StateVar BlendMode #

Get or set the blend mode used for blit operations.

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_SetSurfaceBlendMode and SDL_GetSurfaceBlendMode for C documentation.

rendererRenderTarget :: Renderer -> StateVar (Maybe Texture) #

Get or set the current render target. Nothing corresponds to the default render target.

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_SetRenderTarget and SDL_GetRenderTarget for C documentation.

rendererLogicalSize :: Renderer -> StateVar (Maybe (V2 CInt)) #

Get or set the device independent resolution for rendering.

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_RenderSetLogicalSize and SDL_RenderGetLogicalSize for C documentation.

pixelFormatToMasks :: MonadIO m => PixelFormat -> m (CInt, V4 Word32) #

Convert the given the enumerated pixel format to a bpp value and RGBA masks.

See SDL_PixelFormatEnumToMasks for C documentation.

masksToPixelFormat :: MonadIO m => CInt -> V4 Word32 -> m PixelFormat #

Convert a bpp value and RGBA masks to an enumerated pixel format.

See SDL_MasksToPixelFormatEnum for C documentation.

defaultWindow :: WindowConfig #

Default configuration for windows. Use the record update syntax to override any of the defaults.

defaultWindow = WindowConfig
  { windowBorder          = True
  , windowHighDPI         = False
  , windowInputGrabbed    = False
  , windowMode            = Windowed
  , windowGraphicsContext = NoGraphicsContext
  , windowPosition        = Wherever
  , windowResizable       = False
  , windowInitialSize     = V2 800 600
  , windowVisible         = True
  }

windowBordered :: Window -> StateVar Bool #

Get or set if the window should have a border.

This StateVar can be modified using $= and the current value retrieved with get.

windowBrightness :: Window -> StateVar Float #

Get or set the window's brightness, where 0.0 is completely dark and 1.0 is normal brightness.

Throws SDLException if the hardware does not support gamma correction, or if the system has run out of memory.

This StateVar can be modified using $= and the current value retrieved with get.

windowGrab :: Window -> StateVar Bool #

Get or set whether the mouse shall be confined to the window.

This StateVar can be modified using $= and the current value retrieved with get.

setWindowMode :: MonadIO m => Window -> WindowMode -> m () #

Change between window modes.

Throws SDLException on failure.

getWindowAbsolutePosition :: MonadIO m => Window -> m (V2 CInt) #

Get the position of the window.

windowTitle :: Window -> StateVar Text #

Get or set the title of the window. If the window has no title, then an empty string is returned.

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_SetWindowTitle and SDL_GetWindowTitle for C documentation.

windowData :: Window -> CString -> StateVar (Ptr ()) #

Get or set the pointer to arbitrary user data associated with the given window and name.

This StateVar can be modified using $= and the current value retrieved with get.

getWindowConfig :: MonadIO m => Window -> m WindowConfig #

Retrieve the configuration of the given window.

Note that NoGraphicsContext will be returned instead of potential OpenGL parameters used during the creation of the window.

screenSaverEnabled :: StateVar Bool #

Get or set whether to allow the screen to be blanked by a screen saver.

Screen savers are re-enabled, if needed, when SDL quits.

windowGammaRamp :: Window -> StateVar (V3 (Vector Word16)) #

Gets or sets the gamma ramp for the display that owns a given window.

Note that the data for the gamma ramp - the V3 (Vector Word16) - must contain 256 element arrays. This triple is a set of translation vectors for each of the 16-bit red, green and blue channels.

This StateVar can be modified using $= and the current value retrieved with get.

Despite the name and signature, this method retrieves the gamma ramp of the entire display, not an individual window. A window is considered to be owned by the display that contains the window's center pixel.

getDisplays :: MonadIO m => m [Display] #

Throws SDLException on failure.

windowMaximumSize :: Window -> StateVar (V2 CInt) #

Get or set the maximum size of a window's client area.

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_SetWindowMaximumSize and SDL_GetWindowMaximumSize for C documentation.

windowMinimumSize :: Window -> StateVar (V2 CInt) #

Get or set the minimum size of a window's client area.

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_SetWindowMinimumSize and SDL_GetWindowMinimumSize for C documentation.

windowOpacity :: Window -> StateVar CFloat #

Get or set the opacity of a window.

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_SetWindowOpacity and SDL_GetWindowOpacity for C documentation.

setMouseLocationMode :: (Functor m, MonadIO m) => LocationMode -> m LocationMode #

Sets the current relative mouse mode.

When relative mouse mode is enabled, cursor is hidden and mouse position will not change. However, you will be delivered relative mouse position change events.

getMouseLocationMode :: MonadIO m => m LocationMode #

Check which mouse location mode is currently active.

getModalMouseLocation :: MonadIO m => m ModalLocation #

Return proper mouse location depending on mouse mode

warpMouse :: MonadIO m => WarpMouseOrigin -> Point V2 CInt -> m () #

Move the current location of a mouse pointer. The WarpMouseOrigin specifies the origin for the given warp coordinates.

cursorVisible :: StateVar Bool #

Get or set whether the cursor is currently visible.

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_ShowCursor and SDL_HideCursor for C documentation.

getAbsoluteMouseLocation :: MonadIO m => m (Point V2 CInt) #

Retrieve the current location of the mouse, relative to the currently focused window.

getRelativeMouseLocation :: MonadIO m => m (V2 CInt) #

Retrieve mouse motion

getMouseButtons :: MonadIO m => m (MouseButton -> Bool) #

Retrieve a mapping of which buttons are currently held down.

activeCursor :: StateVar Cursor #

Get or set the currently active cursor. You can create new Cursors with createCursor.

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_SetCursor and SDL_GetCursor for C documentation.

createCursorFrom #

Arguments

:: MonadIO m 
=> Point V2 CInt

The X- and Y-axis location of the upper left corner of the cursor relative to the actual mouse position

-> [[Char]] 
-> m Cursor 

Create a cursor from a bit art painting of it.

The number of columns must be a multiple of 8.

Symbols used: (space) - transparent, . - visible black, # (or anything else) - visible white.

A minimal cursor template: source8x8 :: [[Char]] source8x8 = [ " " , " " , " " , " " , " " , " " , " " , " " ]

pollEvents :: MonadIO m => m [Event] #

Clear the event queue by polling for all pending events.

Like pollEvent this function should only be called in the OS thread which set the video mode.

mapEvents :: MonadIO m => (Event -> m ()) -> m () #

Run a monadic computation, accumulating over all known Events.

This can be useful when used with a state monad, allowing you to fold all events together.

emptyRegisteredEvent :: RegisteredEventData #

A registered event with no associated data.

This is a resonable baseline to modify for converting to RegisteredEventData.

registerEvent :: MonadIO m => (RegisteredEventData -> Timestamp -> IO (Maybe a)) -> (a -> IO RegisteredEventData) -> m (Maybe (RegisteredEventType a)) #

Register a new event type with SDL.

Provide functions that convert between UserEventData and your structure. You can then use pushRegisteredEvent to add a custom event of the registered type to the queue, and getRegisteredEvent to test for such events in the main loop.

class Monad m => MonadIO (m :: Type -> Type) #

Monads in which IO computations may be embedded. Any monad built by applying a sequence of monad transformers to the IO monad will be an instance of this class.

Instances should satisfy the following laws, which state that liftIO is a transformer of monads:

Minimal complete definition

liftIO

Instances

Instances details
MonadIO IO

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.IO.Class

Methods

liftIO :: IO a -> IO a #

MonadIO Q 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

liftIO :: IO a -> Q a #

MonadIO (SpiderHost x) 
Instance details

Defined in Reflex.Spider.Internal

Methods

liftIO :: IO a -> SpiderHost x a #

MonadIO (SpiderHostFrame x) 
Instance details

Defined in Reflex.Spider.Internal

Methods

liftIO :: IO a -> SpiderHostFrame x a #

MonadIO (SpiderPullM x) 
Instance details

Defined in Reflex.Spider.Internal

Methods

liftIO :: IO a -> SpiderPullM x a #

MonadIO (SpiderPushM x) 
Instance details

Defined in Reflex.Spider.Internal

Methods

liftIO :: IO a -> SpiderPushM x a #

MonadIO m => MonadIO (ExceptionT m) 
Instance details

Defined in Control.Monad.Exception

Methods

liftIO :: IO a -> ExceptionT m a #

(Functor f, MonadIO m) => MonadIO (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

liftIO :: IO a -> FreeT f m a #

(ReflexHost t, MonadIO m) => MonadIO (ReflexSDL2T t m) Source # 
Instance details

Defined in Reflex.SDL2.Base

Methods

liftIO :: IO a -> ReflexSDL2T t m a #

MonadIO m => MonadIO (PostBuildT t m) 
Instance details

Defined in Reflex.PostBuild.Base

Methods

liftIO :: IO a -> PostBuildT t m a #

MonadIO m => MonadIO (ProfiledM m) 
Instance details

Defined in Reflex.Profiled

Methods

liftIO :: IO a -> ProfiledM m a #

MonadIO (BehaviorM x) 
Instance details

Defined in Reflex.Spider.Internal

Methods

liftIO :: IO a -> BehaviorM x a #

MonadIO (EventM x) 
Instance details

Defined in Reflex.Spider.Internal

Methods

liftIO :: IO a -> EventM x a #

MonadIO m => MonadIO (TriggerEventT t m) 
Instance details

Defined in Reflex.TriggerEvent.Base

Methods

liftIO :: IO a -> TriggerEventT t m a #

(Error e, MonadIO m) => MonadIO (ErrorT e m) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

liftIO :: IO a -> ErrorT e m a #

MonadIO m => MonadIO (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

liftIO :: IO a -> ReaderT r m a #

MonadIO m => MonadIO (BehaviorWriterT t w m) 
Instance details

Defined in Reflex.BehaviorWriter.Base

Methods

liftIO :: IO a -> BehaviorWriterT t w m a #

MonadIO m => MonadIO (DynamicWriterT t w m) 
Instance details

Defined in Reflex.DynamicWriter.Base

Methods

liftIO :: IO a -> DynamicWriterT t w m a #

MonadIO m => MonadIO (EventWriterT t w m) 
Instance details

Defined in Reflex.EventWriter.Base

Methods

liftIO :: IO a -> EventWriterT t w m a #

(ReflexHost t, MonadIO (HostFrame t)) => MonadIO (PerformEventT t m) 
Instance details

Defined in Reflex.PerformEvent.Base

Methods

liftIO :: IO a -> PerformEventT t m a #

MonadIO m => MonadIO (QueryT t q m) 
Instance details

Defined in Reflex.Query.Base

Methods

liftIO :: IO a -> QueryT t q m a #

MonadIO m => MonadIO (RequesterT t request response m) 
Instance details

Defined in Reflex.Requester.Base.Internal

Methods

liftIO :: IO a -> RequesterT t request response m a #

liftIO :: MonadIO m => IO a -> m a #

Lift a computation from the IO monad. This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations (i.e. IO is the base monad for the stack).

Example

Expand
import Control.Monad.Trans.State -- from the "transformers" library

printState :: Show s => StateT s IO ()
printState = do
  state <- get
  liftIO $ print state

Had we omitted liftIO, we would have ended up with this error:

• Couldn't match type ‘IO’ with ‘StateT s IO’
 Expected type: StateT s IO ()
   Actual type: IO ()

The important part here is the mismatch between StateT s IO () and IO ().

Luckily, we know of a function that takes an IO a and returns an (m a): liftIO, enabling us to run the program and see the expected results:

> evalStateT printState "hello"
"hello"

> evalStateT printState 3
3