{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
module SDL.Input.Mouse
(
LocationMode(..)
, setMouseLocationMode
, getMouseLocationMode
, MouseButton(..)
, MouseDevice(..)
, MouseScrollDirection(..)
, ModalLocation(..)
, getModalMouseLocation
, getAbsoluteMouseLocation
, getRelativeMouseLocation
, getMouseButtons
, WarpMouseOrigin(..)
, warpMouse
, cursorVisible
, Cursor
, SystemCursor(..)
, activeCursor
, createCursor
, createCursorFrom
, freeCursor
, createColorCursor
, createSystemCursor
) where
import Control.Monad (void)
import Control.Monad.IO.Class (MonadIO, liftIO)
import Data.Bits
import Data.Bool
import Data.Data (Data)
import Data.List (nub)
import Data.StateVar
import Data.Typeable
import Data.Word
import Foreign.C
import Foreign.Marshal.Alloc
import Foreign.Ptr
import Foreign.Storable
import GHC.Generics (Generic)
import SDL.Vect
import SDL.Internal.Exception
import SDL.Internal.Numbered
import SDL.Internal.Types (Window(Window))
import SDL.Video.Renderer (Surface(Surface))
import qualified Data.Vector.Storable as V
import qualified SDL.Raw.Enum as Raw
import qualified SDL.Raw.Event as Raw
import qualified SDL.Raw.Types as Raw
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
#endif
data LocationMode
= AbsoluteLocation
| RelativeLocation
deriving (LocationMode
forall a. a -> a -> Bounded a
maxBound :: LocationMode
$cmaxBound :: LocationMode
minBound :: LocationMode
$cminBound :: LocationMode
Bounded, Typeable LocationMode
LocationMode -> DataType
LocationMode -> Constr
(forall b. Data b => b -> b) -> LocationMode -> LocationMode
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> LocationMode -> u
forall u. (forall d. Data d => d -> u) -> LocationMode -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LocationMode -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LocationMode -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> LocationMode -> m LocationMode
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LocationMode -> m LocationMode
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LocationMode
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LocationMode -> c LocationMode
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LocationMode)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LocationMode)
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LocationMode -> m LocationMode
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LocationMode -> m LocationMode
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LocationMode -> m LocationMode
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LocationMode -> m LocationMode
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> LocationMode -> m LocationMode
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> LocationMode -> m LocationMode
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> LocationMode -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> LocationMode -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> LocationMode -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> LocationMode -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LocationMode -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LocationMode -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LocationMode -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LocationMode -> r
gmapT :: (forall b. Data b => b -> b) -> LocationMode -> LocationMode
$cgmapT :: (forall b. Data b => b -> b) -> LocationMode -> LocationMode
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LocationMode)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LocationMode)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LocationMode)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LocationMode)
dataTypeOf :: LocationMode -> DataType
$cdataTypeOf :: LocationMode -> DataType
toConstr :: LocationMode -> Constr
$ctoConstr :: LocationMode -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LocationMode
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LocationMode
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LocationMode -> c LocationMode
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LocationMode -> c LocationMode
Data, LocationMode -> LocationMode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LocationMode -> LocationMode -> Bool
$c/= :: LocationMode -> LocationMode -> Bool
== :: LocationMode -> LocationMode -> Bool
$c== :: LocationMode -> LocationMode -> Bool
Eq, Int -> LocationMode
LocationMode -> Int
LocationMode -> [LocationMode]
LocationMode -> LocationMode
LocationMode -> LocationMode -> [LocationMode]
LocationMode -> LocationMode -> LocationMode -> [LocationMode]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: LocationMode -> LocationMode -> LocationMode -> [LocationMode]
$cenumFromThenTo :: LocationMode -> LocationMode -> LocationMode -> [LocationMode]
enumFromTo :: LocationMode -> LocationMode -> [LocationMode]
$cenumFromTo :: LocationMode -> LocationMode -> [LocationMode]
enumFromThen :: LocationMode -> LocationMode -> [LocationMode]
$cenumFromThen :: LocationMode -> LocationMode -> [LocationMode]
enumFrom :: LocationMode -> [LocationMode]
$cenumFrom :: LocationMode -> [LocationMode]
fromEnum :: LocationMode -> Int
$cfromEnum :: LocationMode -> Int
toEnum :: Int -> LocationMode
$ctoEnum :: Int -> LocationMode
pred :: LocationMode -> LocationMode
$cpred :: LocationMode -> LocationMode
succ :: LocationMode -> LocationMode
$csucc :: LocationMode -> LocationMode
Enum, forall x. Rep LocationMode x -> LocationMode
forall x. LocationMode -> Rep LocationMode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LocationMode x -> LocationMode
$cfrom :: forall x. LocationMode -> Rep LocationMode x
Generic, Eq LocationMode
LocationMode -> LocationMode -> Bool
LocationMode -> LocationMode -> Ordering
LocationMode -> LocationMode -> LocationMode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LocationMode -> LocationMode -> LocationMode
$cmin :: LocationMode -> LocationMode -> LocationMode
max :: LocationMode -> LocationMode -> LocationMode
$cmax :: LocationMode -> LocationMode -> LocationMode
>= :: LocationMode -> LocationMode -> Bool
$c>= :: LocationMode -> LocationMode -> Bool
> :: LocationMode -> LocationMode -> Bool
$c> :: LocationMode -> LocationMode -> Bool
<= :: LocationMode -> LocationMode -> Bool
$c<= :: LocationMode -> LocationMode -> Bool
< :: LocationMode -> LocationMode -> Bool
$c< :: LocationMode -> LocationMode -> Bool
compare :: LocationMode -> LocationMode -> Ordering
$ccompare :: LocationMode -> LocationMode -> Ordering
Ord, ReadPrec [LocationMode]
ReadPrec LocationMode
Int -> ReadS LocationMode
ReadS [LocationMode]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LocationMode]
$creadListPrec :: ReadPrec [LocationMode]
readPrec :: ReadPrec LocationMode
$creadPrec :: ReadPrec LocationMode
readList :: ReadS [LocationMode]
$creadList :: ReadS [LocationMode]
readsPrec :: Int -> ReadS LocationMode
$creadsPrec :: Int -> ReadS LocationMode
Read, Int -> LocationMode -> ShowS
[LocationMode] -> ShowS
LocationMode -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [LocationMode] -> ShowS
$cshowList :: [LocationMode] -> ShowS
show :: LocationMode -> [Char]
$cshow :: LocationMode -> [Char]
showsPrec :: Int -> LocationMode -> ShowS
$cshowsPrec :: Int -> LocationMode -> ShowS
Show, Typeable)
setMouseLocationMode :: (Functor m, MonadIO m) => LocationMode -> m LocationMode
setMouseLocationMode :: forall (m :: Type -> Type).
(Functor m, MonadIO m) =>
LocationMode -> m LocationMode
setMouseLocationMode LocationMode
mode =
forall (m :: Type -> Type). MonadIO m => Bool -> m CInt
Raw.setRelativeMouseMode (LocationMode
mode forall a. Eq a => a -> a -> Bool
== LocationMode
RelativeLocation) forall (m :: Type -> Type) a b. Monad m => m a -> m b -> m b
>> forall (m :: Type -> Type). MonadIO m => m LocationMode
getMouseLocationMode
getMouseLocationMode :: MonadIO m => m LocationMode
getMouseLocationMode :: forall (m :: Type -> Type). MonadIO m => m LocationMode
getMouseLocationMode = do
Bool
relativeMode <- forall (m :: Type -> Type). MonadIO m => m Bool
Raw.getRelativeMouseMode
forall (m :: Type -> Type) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ if Bool
relativeMode then LocationMode
RelativeLocation else LocationMode
AbsoluteLocation
data ModalLocation
= AbsoluteModalLocation (Point V2 CInt)
| RelativeModalLocation (V2 CInt)
deriving (ModalLocation -> ModalLocation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModalLocation -> ModalLocation -> Bool
$c/= :: ModalLocation -> ModalLocation -> Bool
== :: ModalLocation -> ModalLocation -> Bool
$c== :: ModalLocation -> ModalLocation -> Bool
Eq, forall x. Rep ModalLocation x -> ModalLocation
forall x. ModalLocation -> Rep ModalLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ModalLocation x -> ModalLocation
$cfrom :: forall x. ModalLocation -> Rep ModalLocation x
Generic, Eq ModalLocation
ModalLocation -> ModalLocation -> Bool
ModalLocation -> ModalLocation -> Ordering
ModalLocation -> ModalLocation -> ModalLocation
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ModalLocation -> ModalLocation -> ModalLocation
$cmin :: ModalLocation -> ModalLocation -> ModalLocation
max :: ModalLocation -> ModalLocation -> ModalLocation
$cmax :: ModalLocation -> ModalLocation -> ModalLocation
>= :: ModalLocation -> ModalLocation -> Bool
$c>= :: ModalLocation -> ModalLocation -> Bool
> :: ModalLocation -> ModalLocation -> Bool
$c> :: ModalLocation -> ModalLocation -> Bool
<= :: ModalLocation -> ModalLocation -> Bool
$c<= :: ModalLocation -> ModalLocation -> Bool
< :: ModalLocation -> ModalLocation -> Bool
$c< :: ModalLocation -> ModalLocation -> Bool
compare :: ModalLocation -> ModalLocation -> Ordering
$ccompare :: ModalLocation -> ModalLocation -> Ordering
Ord, ReadPrec [ModalLocation]
ReadPrec ModalLocation
Int -> ReadS ModalLocation
ReadS [ModalLocation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModalLocation]
$creadListPrec :: ReadPrec [ModalLocation]
readPrec :: ReadPrec ModalLocation
$creadPrec :: ReadPrec ModalLocation
readList :: ReadS [ModalLocation]
$creadList :: ReadS [ModalLocation]
readsPrec :: Int -> ReadS ModalLocation
$creadsPrec :: Int -> ReadS ModalLocation
Read, Int -> ModalLocation -> ShowS
[ModalLocation] -> ShowS
ModalLocation -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [ModalLocation] -> ShowS
$cshowList :: [ModalLocation] -> ShowS
show :: ModalLocation -> [Char]
$cshow :: ModalLocation -> [Char]
showsPrec :: Int -> ModalLocation -> ShowS
$cshowsPrec :: Int -> ModalLocation -> ShowS
Show, Typeable)
getModalMouseLocation :: MonadIO m => m ModalLocation
getModalMouseLocation :: forall (m :: Type -> Type). MonadIO m => m ModalLocation
getModalMouseLocation = do
LocationMode
mode <- forall (m :: Type -> Type). MonadIO m => m LocationMode
getMouseLocationMode
case LocationMode
mode of
LocationMode
AbsoluteLocation -> do
Point V2 CInt
location <- forall (m :: Type -> Type). MonadIO m => m (Point V2 CInt)
getAbsoluteMouseLocation
forall (m :: Type -> Type) a. Monad m => a -> m a
return (Point V2 CInt -> ModalLocation
AbsoluteModalLocation Point V2 CInt
location)
LocationMode
RelativeLocation -> do
V2 CInt
location <- forall (m :: Type -> Type). MonadIO m => m (V2 CInt)
getRelativeMouseLocation
forall (m :: Type -> Type) a. Monad m => a -> m a
return (V2 CInt -> ModalLocation
RelativeModalLocation V2 CInt
location)
data MouseButton
= ButtonLeft
| ButtonMiddle
| ButtonRight
| ButtonX1
| ButtonX2
| !Int
deriving (Typeable MouseButton
MouseButton -> DataType
MouseButton -> Constr
(forall b. Data b => b -> b) -> MouseButton -> MouseButton
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> MouseButton -> u
forall u. (forall d. Data d => d -> u) -> MouseButton -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MouseButton -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MouseButton -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> MouseButton -> m MouseButton
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MouseButton -> m MouseButton
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MouseButton
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MouseButton -> c MouseButton
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MouseButton)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MouseButton)
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MouseButton -> m MouseButton
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MouseButton -> m MouseButton
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MouseButton -> m MouseButton
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MouseButton -> m MouseButton
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> MouseButton -> m MouseButton
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> MouseButton -> m MouseButton
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MouseButton -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MouseButton -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> MouseButton -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> MouseButton -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MouseButton -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MouseButton -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MouseButton -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MouseButton -> r
gmapT :: (forall b. Data b => b -> b) -> MouseButton -> MouseButton
$cgmapT :: (forall b. Data b => b -> b) -> MouseButton -> MouseButton
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MouseButton)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MouseButton)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MouseButton)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MouseButton)
dataTypeOf :: MouseButton -> DataType
$cdataTypeOf :: MouseButton -> DataType
toConstr :: MouseButton -> Constr
$ctoConstr :: MouseButton -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MouseButton
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MouseButton
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MouseButton -> c MouseButton
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MouseButton -> c MouseButton
Data, MouseButton -> MouseButton -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MouseButton -> MouseButton -> Bool
$c/= :: MouseButton -> MouseButton -> Bool
== :: MouseButton -> MouseButton -> Bool
$c== :: MouseButton -> MouseButton -> Bool
Eq, forall x. Rep MouseButton x -> MouseButton
forall x. MouseButton -> Rep MouseButton x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MouseButton x -> MouseButton
$cfrom :: forall x. MouseButton -> Rep MouseButton x
Generic, Eq MouseButton
MouseButton -> MouseButton -> Bool
MouseButton -> MouseButton -> Ordering
MouseButton -> MouseButton -> MouseButton
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MouseButton -> MouseButton -> MouseButton
$cmin :: MouseButton -> MouseButton -> MouseButton
max :: MouseButton -> MouseButton -> MouseButton
$cmax :: MouseButton -> MouseButton -> MouseButton
>= :: MouseButton -> MouseButton -> Bool
$c>= :: MouseButton -> MouseButton -> Bool
> :: MouseButton -> MouseButton -> Bool
$c> :: MouseButton -> MouseButton -> Bool
<= :: MouseButton -> MouseButton -> Bool
$c<= :: MouseButton -> MouseButton -> Bool
< :: MouseButton -> MouseButton -> Bool
$c< :: MouseButton -> MouseButton -> Bool
compare :: MouseButton -> MouseButton -> Ordering
$ccompare :: MouseButton -> MouseButton -> Ordering
Ord, ReadPrec [MouseButton]
ReadPrec MouseButton
Int -> ReadS MouseButton
ReadS [MouseButton]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MouseButton]
$creadListPrec :: ReadPrec [MouseButton]
readPrec :: ReadPrec MouseButton
$creadPrec :: ReadPrec MouseButton
readList :: ReadS [MouseButton]
$creadList :: ReadS [MouseButton]
readsPrec :: Int -> ReadS MouseButton
$creadsPrec :: Int -> ReadS MouseButton
Read, Int -> MouseButton -> ShowS
[MouseButton] -> ShowS
MouseButton -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [MouseButton] -> ShowS
$cshowList :: [MouseButton] -> ShowS
show :: MouseButton -> [Char]
$cshow :: MouseButton -> [Char]
showsPrec :: Int -> MouseButton -> ShowS
$cshowsPrec :: Int -> MouseButton -> ShowS
Show, Typeable)
instance FromNumber MouseButton Word8 where
fromNumber :: Word8 -> MouseButton
fromNumber Word8
Raw.SDL_BUTTON_LEFT = MouseButton
ButtonLeft
fromNumber Word8
Raw.SDL_BUTTON_MIDDLE = MouseButton
ButtonMiddle
fromNumber Word8
Raw.SDL_BUTTON_RIGHT = MouseButton
ButtonRight
fromNumber Word8
Raw.SDL_BUTTON_X1 = MouseButton
ButtonX1
fromNumber Word8
Raw.SDL_BUTTON_X2 = MouseButton
ButtonX2
fromNumber Word8
buttonCode = Int -> MouseButton
ButtonExtra forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
buttonCode
instance ToNumber MouseButton Word8 where
toNumber :: MouseButton -> Word8
toNumber MouseButton
ButtonLeft = forall {a}. (Eq a, Num a) => a
Raw.SDL_BUTTON_LEFT
toNumber MouseButton
ButtonMiddle = forall {a}. (Eq a, Num a) => a
Raw.SDL_BUTTON_MIDDLE
toNumber MouseButton
ButtonRight = forall {a}. (Eq a, Num a) => a
Raw.SDL_BUTTON_RIGHT
toNumber MouseButton
ButtonX1 = forall {a}. (Eq a, Num a) => a
Raw.SDL_BUTTON_X1
toNumber MouseButton
ButtonX2 = forall {a}. (Eq a, Num a) => a
Raw.SDL_BUTTON_X2
toNumber (ButtonExtra Int
i) = forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i
data MouseDevice
= Mouse !Int
| Touch
deriving (Typeable MouseDevice
MouseDevice -> DataType
MouseDevice -> Constr
(forall b. Data b => b -> b) -> MouseDevice -> MouseDevice
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> MouseDevice -> u
forall u. (forall d. Data d => d -> u) -> MouseDevice -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MouseDevice -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MouseDevice -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> MouseDevice -> m MouseDevice
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MouseDevice -> m MouseDevice
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MouseDevice
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MouseDevice -> c MouseDevice
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MouseDevice)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MouseDevice)
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MouseDevice -> m MouseDevice
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MouseDevice -> m MouseDevice
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MouseDevice -> m MouseDevice
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MouseDevice -> m MouseDevice
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> MouseDevice -> m MouseDevice
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> MouseDevice -> m MouseDevice
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MouseDevice -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MouseDevice -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> MouseDevice -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> MouseDevice -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MouseDevice -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MouseDevice -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MouseDevice -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MouseDevice -> r
gmapT :: (forall b. Data b => b -> b) -> MouseDevice -> MouseDevice
$cgmapT :: (forall b. Data b => b -> b) -> MouseDevice -> MouseDevice
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MouseDevice)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MouseDevice)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MouseDevice)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MouseDevice)
dataTypeOf :: MouseDevice -> DataType
$cdataTypeOf :: MouseDevice -> DataType
toConstr :: MouseDevice -> Constr
$ctoConstr :: MouseDevice -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MouseDevice
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MouseDevice
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MouseDevice -> c MouseDevice
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MouseDevice -> c MouseDevice
Data, MouseDevice -> MouseDevice -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MouseDevice -> MouseDevice -> Bool
$c/= :: MouseDevice -> MouseDevice -> Bool
== :: MouseDevice -> MouseDevice -> Bool
$c== :: MouseDevice -> MouseDevice -> Bool
Eq, forall x. Rep MouseDevice x -> MouseDevice
forall x. MouseDevice -> Rep MouseDevice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MouseDevice x -> MouseDevice
$cfrom :: forall x. MouseDevice -> Rep MouseDevice x
Generic, Eq MouseDevice
MouseDevice -> MouseDevice -> Bool
MouseDevice -> MouseDevice -> Ordering
MouseDevice -> MouseDevice -> MouseDevice
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MouseDevice -> MouseDevice -> MouseDevice
$cmin :: MouseDevice -> MouseDevice -> MouseDevice
max :: MouseDevice -> MouseDevice -> MouseDevice
$cmax :: MouseDevice -> MouseDevice -> MouseDevice
>= :: MouseDevice -> MouseDevice -> Bool
$c>= :: MouseDevice -> MouseDevice -> Bool
> :: MouseDevice -> MouseDevice -> Bool
$c> :: MouseDevice -> MouseDevice -> Bool
<= :: MouseDevice -> MouseDevice -> Bool
$c<= :: MouseDevice -> MouseDevice -> Bool
< :: MouseDevice -> MouseDevice -> Bool
$c< :: MouseDevice -> MouseDevice -> Bool
compare :: MouseDevice -> MouseDevice -> Ordering
$ccompare :: MouseDevice -> MouseDevice -> Ordering
Ord, ReadPrec [MouseDevice]
ReadPrec MouseDevice
Int -> ReadS MouseDevice
ReadS [MouseDevice]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MouseDevice]
$creadListPrec :: ReadPrec [MouseDevice]
readPrec :: ReadPrec MouseDevice
$creadPrec :: ReadPrec MouseDevice
readList :: ReadS [MouseDevice]
$creadList :: ReadS [MouseDevice]
readsPrec :: Int -> ReadS MouseDevice
$creadsPrec :: Int -> ReadS MouseDevice
Read, Int -> MouseDevice -> ShowS
[MouseDevice] -> ShowS
MouseDevice -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [MouseDevice] -> ShowS
$cshowList :: [MouseDevice] -> ShowS
show :: MouseDevice -> [Char]
$cshow :: MouseDevice -> [Char]
showsPrec :: Int -> MouseDevice -> ShowS
$cshowsPrec :: Int -> MouseDevice -> ShowS
Show, Typeable)
instance FromNumber MouseDevice Word32 where
fromNumber :: Word32 -> MouseDevice
fromNumber Word32
n' = case Word32
n' of
Word32
Raw.SDL_TOUCH_MOUSEID -> MouseDevice
Touch
Word32
n -> Int -> MouseDevice
Mouse forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
n
data MouseScrollDirection
= ScrollNormal
| ScrollFlipped
deriving (MouseScrollDirection
forall a. a -> a -> Bounded a
maxBound :: MouseScrollDirection
$cmaxBound :: MouseScrollDirection
minBound :: MouseScrollDirection
$cminBound :: MouseScrollDirection
Bounded, Typeable MouseScrollDirection
MouseScrollDirection -> DataType
MouseScrollDirection -> Constr
(forall b. Data b => b -> b)
-> MouseScrollDirection -> MouseScrollDirection
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> MouseScrollDirection -> u
forall u.
(forall d. Data d => d -> u) -> MouseScrollDirection -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MouseScrollDirection -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MouseScrollDirection -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> MouseScrollDirection -> m MouseScrollDirection
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MouseScrollDirection -> m MouseScrollDirection
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MouseScrollDirection
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> MouseScrollDirection
-> c MouseScrollDirection
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MouseScrollDirection)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MouseScrollDirection)
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MouseScrollDirection -> m MouseScrollDirection
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MouseScrollDirection -> m MouseScrollDirection
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MouseScrollDirection -> m MouseScrollDirection
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MouseScrollDirection -> m MouseScrollDirection
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> MouseScrollDirection -> m MouseScrollDirection
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> MouseScrollDirection -> m MouseScrollDirection
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> MouseScrollDirection -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> MouseScrollDirection -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> MouseScrollDirection -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> MouseScrollDirection -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MouseScrollDirection -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MouseScrollDirection -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MouseScrollDirection -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MouseScrollDirection -> r
gmapT :: (forall b. Data b => b -> b)
-> MouseScrollDirection -> MouseScrollDirection
$cgmapT :: (forall b. Data b => b -> b)
-> MouseScrollDirection -> MouseScrollDirection
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MouseScrollDirection)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MouseScrollDirection)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MouseScrollDirection)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MouseScrollDirection)
dataTypeOf :: MouseScrollDirection -> DataType
$cdataTypeOf :: MouseScrollDirection -> DataType
toConstr :: MouseScrollDirection -> Constr
$ctoConstr :: MouseScrollDirection -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MouseScrollDirection
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MouseScrollDirection
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> MouseScrollDirection
-> c MouseScrollDirection
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> MouseScrollDirection
-> c MouseScrollDirection
Data, MouseScrollDirection -> MouseScrollDirection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MouseScrollDirection -> MouseScrollDirection -> Bool
$c/= :: MouseScrollDirection -> MouseScrollDirection -> Bool
== :: MouseScrollDirection -> MouseScrollDirection -> Bool
$c== :: MouseScrollDirection -> MouseScrollDirection -> Bool
Eq, Int -> MouseScrollDirection
MouseScrollDirection -> Int
MouseScrollDirection -> [MouseScrollDirection]
MouseScrollDirection -> MouseScrollDirection
MouseScrollDirection
-> MouseScrollDirection -> [MouseScrollDirection]
MouseScrollDirection
-> MouseScrollDirection
-> MouseScrollDirection
-> [MouseScrollDirection]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: MouseScrollDirection
-> MouseScrollDirection
-> MouseScrollDirection
-> [MouseScrollDirection]
$cenumFromThenTo :: MouseScrollDirection
-> MouseScrollDirection
-> MouseScrollDirection
-> [MouseScrollDirection]
enumFromTo :: MouseScrollDirection
-> MouseScrollDirection -> [MouseScrollDirection]
$cenumFromTo :: MouseScrollDirection
-> MouseScrollDirection -> [MouseScrollDirection]
enumFromThen :: MouseScrollDirection
-> MouseScrollDirection -> [MouseScrollDirection]
$cenumFromThen :: MouseScrollDirection
-> MouseScrollDirection -> [MouseScrollDirection]
enumFrom :: MouseScrollDirection -> [MouseScrollDirection]
$cenumFrom :: MouseScrollDirection -> [MouseScrollDirection]
fromEnum :: MouseScrollDirection -> Int
$cfromEnum :: MouseScrollDirection -> Int
toEnum :: Int -> MouseScrollDirection
$ctoEnum :: Int -> MouseScrollDirection
pred :: MouseScrollDirection -> MouseScrollDirection
$cpred :: MouseScrollDirection -> MouseScrollDirection
succ :: MouseScrollDirection -> MouseScrollDirection
$csucc :: MouseScrollDirection -> MouseScrollDirection
Enum, forall x. Rep MouseScrollDirection x -> MouseScrollDirection
forall x. MouseScrollDirection -> Rep MouseScrollDirection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MouseScrollDirection x -> MouseScrollDirection
$cfrom :: forall x. MouseScrollDirection -> Rep MouseScrollDirection x
Generic, Eq MouseScrollDirection
MouseScrollDirection -> MouseScrollDirection -> Bool
MouseScrollDirection -> MouseScrollDirection -> Ordering
MouseScrollDirection
-> MouseScrollDirection -> MouseScrollDirection
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MouseScrollDirection
-> MouseScrollDirection -> MouseScrollDirection
$cmin :: MouseScrollDirection
-> MouseScrollDirection -> MouseScrollDirection
max :: MouseScrollDirection
-> MouseScrollDirection -> MouseScrollDirection
$cmax :: MouseScrollDirection
-> MouseScrollDirection -> MouseScrollDirection
>= :: MouseScrollDirection -> MouseScrollDirection -> Bool
$c>= :: MouseScrollDirection -> MouseScrollDirection -> Bool
> :: MouseScrollDirection -> MouseScrollDirection -> Bool
$c> :: MouseScrollDirection -> MouseScrollDirection -> Bool
<= :: MouseScrollDirection -> MouseScrollDirection -> Bool
$c<= :: MouseScrollDirection -> MouseScrollDirection -> Bool
< :: MouseScrollDirection -> MouseScrollDirection -> Bool
$c< :: MouseScrollDirection -> MouseScrollDirection -> Bool
compare :: MouseScrollDirection -> MouseScrollDirection -> Ordering
$ccompare :: MouseScrollDirection -> MouseScrollDirection -> Ordering
Ord, ReadPrec [MouseScrollDirection]
ReadPrec MouseScrollDirection
Int -> ReadS MouseScrollDirection
ReadS [MouseScrollDirection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MouseScrollDirection]
$creadListPrec :: ReadPrec [MouseScrollDirection]
readPrec :: ReadPrec MouseScrollDirection
$creadPrec :: ReadPrec MouseScrollDirection
readList :: ReadS [MouseScrollDirection]
$creadList :: ReadS [MouseScrollDirection]
readsPrec :: Int -> ReadS MouseScrollDirection
$creadsPrec :: Int -> ReadS MouseScrollDirection
Read, Int -> MouseScrollDirection -> ShowS
[MouseScrollDirection] -> ShowS
MouseScrollDirection -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [MouseScrollDirection] -> ShowS
$cshowList :: [MouseScrollDirection] -> ShowS
show :: MouseScrollDirection -> [Char]
$cshow :: MouseScrollDirection -> [Char]
showsPrec :: Int -> MouseScrollDirection -> ShowS
$cshowsPrec :: Int -> MouseScrollDirection -> ShowS
Show, Typeable)
instance FromNumber MouseScrollDirection Word32 where
fromNumber :: Word32 -> MouseScrollDirection
fromNumber Word32
n' = case Word32
n' of
Word32
Raw.SDL_MOUSEWHEEL_NORMAL -> MouseScrollDirection
ScrollNormal
Word32
Raw.SDL_MOUSEWHEEL_FLIPPED -> MouseScrollDirection
ScrollFlipped
Word32
_ -> MouseScrollDirection
ScrollNormal
data WarpMouseOrigin
= WarpInWindow Window
| WarpCurrentFocus
| WarpGlobal
deriving (Typeable WarpMouseOrigin
WarpMouseOrigin -> DataType
WarpMouseOrigin -> Constr
(forall b. Data b => b -> b) -> WarpMouseOrigin -> WarpMouseOrigin
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> WarpMouseOrigin -> u
forall u. (forall d. Data d => d -> u) -> WarpMouseOrigin -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WarpMouseOrigin -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WarpMouseOrigin -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> WarpMouseOrigin -> m WarpMouseOrigin
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> WarpMouseOrigin -> m WarpMouseOrigin
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WarpMouseOrigin
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WarpMouseOrigin -> c WarpMouseOrigin
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WarpMouseOrigin)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c WarpMouseOrigin)
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> WarpMouseOrigin -> m WarpMouseOrigin
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> WarpMouseOrigin -> m WarpMouseOrigin
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> WarpMouseOrigin -> m WarpMouseOrigin
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> WarpMouseOrigin -> m WarpMouseOrigin
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> WarpMouseOrigin -> m WarpMouseOrigin
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d)
-> WarpMouseOrigin -> m WarpMouseOrigin
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> WarpMouseOrigin -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> WarpMouseOrigin -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> WarpMouseOrigin -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> WarpMouseOrigin -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WarpMouseOrigin -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WarpMouseOrigin -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WarpMouseOrigin -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WarpMouseOrigin -> r
gmapT :: (forall b. Data b => b -> b) -> WarpMouseOrigin -> WarpMouseOrigin
$cgmapT :: (forall b. Data b => b -> b) -> WarpMouseOrigin -> WarpMouseOrigin
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c WarpMouseOrigin)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c WarpMouseOrigin)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WarpMouseOrigin)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WarpMouseOrigin)
dataTypeOf :: WarpMouseOrigin -> DataType
$cdataTypeOf :: WarpMouseOrigin -> DataType
toConstr :: WarpMouseOrigin -> Constr
$ctoConstr :: WarpMouseOrigin -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WarpMouseOrigin
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WarpMouseOrigin
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WarpMouseOrigin -> c WarpMouseOrigin
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WarpMouseOrigin -> c WarpMouseOrigin
Data, WarpMouseOrigin -> WarpMouseOrigin -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WarpMouseOrigin -> WarpMouseOrigin -> Bool
$c/= :: WarpMouseOrigin -> WarpMouseOrigin -> Bool
== :: WarpMouseOrigin -> WarpMouseOrigin -> Bool
$c== :: WarpMouseOrigin -> WarpMouseOrigin -> Bool
Eq, forall x. Rep WarpMouseOrigin x -> WarpMouseOrigin
forall x. WarpMouseOrigin -> Rep WarpMouseOrigin x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WarpMouseOrigin x -> WarpMouseOrigin
$cfrom :: forall x. WarpMouseOrigin -> Rep WarpMouseOrigin x
Generic, Eq WarpMouseOrigin
WarpMouseOrigin -> WarpMouseOrigin -> Bool
WarpMouseOrigin -> WarpMouseOrigin -> Ordering
WarpMouseOrigin -> WarpMouseOrigin -> WarpMouseOrigin
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WarpMouseOrigin -> WarpMouseOrigin -> WarpMouseOrigin
$cmin :: WarpMouseOrigin -> WarpMouseOrigin -> WarpMouseOrigin
max :: WarpMouseOrigin -> WarpMouseOrigin -> WarpMouseOrigin
$cmax :: WarpMouseOrigin -> WarpMouseOrigin -> WarpMouseOrigin
>= :: WarpMouseOrigin -> WarpMouseOrigin -> Bool
$c>= :: WarpMouseOrigin -> WarpMouseOrigin -> Bool
> :: WarpMouseOrigin -> WarpMouseOrigin -> Bool
$c> :: WarpMouseOrigin -> WarpMouseOrigin -> Bool
<= :: WarpMouseOrigin -> WarpMouseOrigin -> Bool
$c<= :: WarpMouseOrigin -> WarpMouseOrigin -> Bool
< :: WarpMouseOrigin -> WarpMouseOrigin -> Bool
$c< :: WarpMouseOrigin -> WarpMouseOrigin -> Bool
compare :: WarpMouseOrigin -> WarpMouseOrigin -> Ordering
$ccompare :: WarpMouseOrigin -> WarpMouseOrigin -> Ordering
Ord, Int -> WarpMouseOrigin -> ShowS
[WarpMouseOrigin] -> ShowS
WarpMouseOrigin -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [WarpMouseOrigin] -> ShowS
$cshowList :: [WarpMouseOrigin] -> ShowS
show :: WarpMouseOrigin -> [Char]
$cshow :: WarpMouseOrigin -> [Char]
showsPrec :: Int -> WarpMouseOrigin -> ShowS
$cshowsPrec :: Int -> WarpMouseOrigin -> ShowS
Show, Typeable)
warpMouse :: MonadIO m => WarpMouseOrigin -> Point V2 CInt -> m ()
warpMouse :: forall (m :: Type -> Type).
MonadIO m =>
WarpMouseOrigin -> Point V2 CInt -> m ()
warpMouse (WarpInWindow (Window Window
w)) (P (V2 CInt
x CInt
y)) = forall (m :: Type -> Type).
MonadIO m =>
Window -> CInt -> CInt -> m ()
Raw.warpMouseInWindow Window
w CInt
x CInt
y
warpMouse WarpMouseOrigin
WarpCurrentFocus (P (V2 CInt
x CInt
y)) = forall (m :: Type -> Type).
MonadIO m =>
Window -> CInt -> CInt -> m ()
Raw.warpMouseInWindow forall a. Ptr a
nullPtr CInt
x CInt
y
warpMouse WarpMouseOrigin
WarpGlobal (P (V2 CInt
x CInt
y)) = forall (m :: Type -> Type) a.
(MonadIO m, Num a, Ord a) =>
Text -> Text -> m a -> m ()
throwIfNeg_ Text
"SDL.Mouse.warpMouse" Text
"SDL_WarpMouseGlobal" forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type). MonadIO m => CInt -> CInt -> m CInt
Raw.warpMouseGlobal CInt
x CInt
y
cursorVisible :: StateVar Bool
cursorVisible :: StateVar Bool
cursorVisible = forall a. IO a -> (a -> IO ()) -> StateVar a
makeStateVar forall (m :: Type -> Type). (Functor m, MonadIO m) => m Bool
getCursorVisible forall (m :: Type -> Type). (Functor m, MonadIO m) => Bool -> m ()
setCursorVisible
where
setCursorVisible :: (Functor m, MonadIO m) => Bool -> m ()
setCursorVisible :: forall (m :: Type -> Type). (Functor m, MonadIO m) => Bool -> m ()
setCursorVisible Bool
True = forall (f :: Type -> Type) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall (m :: Type -> Type). MonadIO m => CInt -> m CInt
Raw.showCursor CInt
1
setCursorVisible Bool
False = forall (f :: Type -> Type) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall (m :: Type -> Type). MonadIO m => CInt -> m CInt
Raw.showCursor CInt
0
getCursorVisible :: (Functor m, MonadIO m) => m Bool
getCursorVisible :: forall (m :: Type -> Type). (Functor m, MonadIO m) => m Bool
getCursorVisible = (forall a. Eq a => a -> a -> Bool
== CInt
1) forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: Type -> Type). MonadIO m => CInt -> m CInt
Raw.showCursor (-CInt
1)
getAbsoluteMouseLocation :: MonadIO m => m (Point V2 CInt)
getAbsoluteMouseLocation :: forall (m :: Type -> Type). MonadIO m => m (Point V2 CInt)
getAbsoluteMouseLocation = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr CInt
x ->
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr CInt
y -> do
Word32
_ <- forall (m :: Type -> Type).
MonadIO m =>
Ptr CInt -> Ptr CInt -> m Word32
Raw.getMouseState Ptr CInt
x Ptr CInt
y
forall (f :: Type -> Type) a. f a -> Point f a
P forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. a -> a -> V2 a
V2 forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
x forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
y)
getRelativeMouseLocation :: MonadIO m => m (V2 CInt)
getRelativeMouseLocation :: forall (m :: Type -> Type). MonadIO m => m (V2 CInt)
getRelativeMouseLocation = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr CInt
x ->
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr CInt
y -> do
Word32
_ <- forall (m :: Type -> Type).
MonadIO m =>
Ptr CInt -> Ptr CInt -> m Word32
Raw.getRelativeMouseState Ptr CInt
x Ptr CInt
y
forall a. a -> a -> V2 a
V2 forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
x forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
y
getMouseButtons :: MonadIO m => m (MouseButton -> Bool)
getMouseButtons :: forall (m :: Type -> Type). MonadIO m => m (MouseButton -> Bool)
getMouseButtons = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
forall {a} {a} {a}. (Bits a, ToNumber a a) => a -> a -> Bool
convert forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: Type -> Type).
MonadIO m =>
Ptr CInt -> Ptr CInt -> m Word32
Raw.getMouseState forall a. Ptr a
nullPtr forall a. Ptr a
nullPtr
where
convert :: a -> a -> Bool
convert a
w a
b = a
w forall a. Bits a => a -> Int -> Bool
`testBit` forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a b. ToNumber a b => a -> b
toNumber a
b forall a. Num a => a -> a -> a
- a
1)
newtype Cursor = Cursor { Cursor -> Window
unwrapCursor :: Raw.Cursor }
deriving (Cursor -> Cursor -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Cursor -> Cursor -> Bool
$c/= :: Cursor -> Cursor -> Bool
== :: Cursor -> Cursor -> Bool
$c== :: Cursor -> Cursor -> Bool
Eq, Typeable)
data SystemCursor
= SystemCursorArrow
| SystemCursorIBeam
| SystemCursorWait
| SystemCursorCrossHair
| SystemCursorWaitArrow
| SystemCursorSizeNWSE
| SystemCursorSizeNESW
| SystemCursorSizeWE
| SystemCursorSizeNS
| SystemCursorSizeAll
| SystemCursorNo
| SystemCursorHand
instance ToNumber SystemCursor Word32 where
toNumber :: SystemCursor -> Word32
toNumber SystemCursor
SystemCursorArrow = Word32
Raw.SDL_SYSTEM_CURSOR_ARROW
toNumber SystemCursor
SystemCursorIBeam = Word32
Raw.SDL_SYSTEM_CURSOR_IBEAM
toNumber SystemCursor
SystemCursorWait = Word32
Raw.SDL_SYSTEM_CURSOR_WAIT
toNumber SystemCursor
SystemCursorCrossHair = Word32
Raw.SDL_SYSTEM_CURSOR_CROSSHAIR
toNumber SystemCursor
SystemCursorWaitArrow = Word32
Raw.SDL_SYSTEM_CURSOR_WAITARROW
toNumber SystemCursor
SystemCursorSizeNWSE = Word32
Raw.SDL_SYSTEM_CURSOR_SIZENWSE
toNumber SystemCursor
SystemCursorSizeNESW = Word32
Raw.SDL_SYSTEM_CURSOR_SIZENESW
toNumber SystemCursor
SystemCursorSizeWE = Word32
Raw.SDL_SYSTEM_CURSOR_SIZEWE
toNumber SystemCursor
SystemCursorSizeNS = Word32
Raw.SDL_SYSTEM_CURSOR_SIZENS
toNumber SystemCursor
SystemCursorSizeAll = Word32
Raw.SDL_SYSTEM_CURSOR_SIZEALL
toNumber SystemCursor
SystemCursorNo = Word32
Raw.SDL_SYSTEM_CURSOR_NO
toNumber SystemCursor
SystemCursorHand = Word32
Raw.SDL_SYSTEM_CURSOR_HAND
activeCursor :: StateVar Cursor
activeCursor :: StateVar Cursor
activeCursor = forall a. IO a -> (a -> IO ()) -> StateVar a
makeStateVar forall (m :: Type -> Type). MonadIO m => m Cursor
getCursor forall (m :: Type -> Type). MonadIO m => Cursor -> m ()
setCursor
where
getCursor :: MonadIO m => m Cursor
getCursor :: forall (m :: Type -> Type). MonadIO m => m Cursor
getCursor = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap Window -> Cursor
Cursor forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type) a.
MonadIO m =>
Text -> Text -> m (Ptr a) -> m (Ptr a)
throwIfNull Text
"SDL.Input.Mouse.getCursor" Text
"SDL_getCursor"
forall (m :: Type -> Type). MonadIO m => m Window
Raw.getCursor
setCursor :: MonadIO m => Cursor -> m ()
setCursor :: forall (m :: Type -> Type). MonadIO m => Cursor -> m ()
setCursor = forall (m :: Type -> Type). MonadIO m => Window -> m ()
Raw.setCursor forall b c a. (b -> c) -> (a -> b) -> a -> c
. Cursor -> Window
unwrapCursor
createCursor :: MonadIO m
=> V.Vector Word8
-> V.Vector Word8
-> V2 CInt
-> Point V2 CInt
-> m Cursor
createCursor :: forall (m :: Type -> Type).
MonadIO m =>
Vector Word8
-> Vector Word8 -> V2 CInt -> Point V2 CInt -> m Cursor
createCursor Vector Word8
dta Vector Word8
msk (V2 CInt
w CInt
h) (P (V2 CInt
hx CInt
hy)) =
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap Window -> Cursor
Cursor forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type) a.
MonadIO m =>
Text -> Text -> m (Ptr a) -> m (Ptr a)
throwIfNull Text
"SDL.Input.Mouse.createCursor" Text
"SDL_createCursor" forall a b. (a -> b) -> a -> b
$
forall a b. Storable a => Vector a -> (Ptr a -> IO b) -> IO b
V.unsafeWith Vector Word8
dta forall a b. (a -> b) -> a -> b
$ \Ptr Word8
unsafeDta ->
forall a b. Storable a => Vector a -> (Ptr a -> IO b) -> IO b
V.unsafeWith Vector Word8
msk forall a b. (a -> b) -> a -> b
$ \Ptr Word8
unsafeMsk ->
forall (m :: Type -> Type).
MonadIO m =>
Ptr Word8 -> Ptr Word8 -> CInt -> CInt -> CInt -> CInt -> m Window
Raw.createCursor Ptr Word8
unsafeDta Ptr Word8
unsafeMsk CInt
w CInt
h CInt
hx CInt
hy
createCursorFrom :: MonadIO m
=> Point V2 CInt
-> [[Char]]
-> m Cursor
createCursorFrom :: forall (m :: Type -> Type).
MonadIO m =>
Point V2 CInt -> [[Char]] -> m Cursor
createCursorFrom Point V2 CInt
point [[Char]]
source = do
forall (m :: Type -> Type).
MonadIO m =>
Vector Word8
-> Vector Word8 -> V2 CInt -> Point V2 CInt -> m Cursor
createCursor Vector Word8
color Vector Word8
mask (forall a. a -> a -> V2 a
V2 CInt
w CInt
h) Point V2 CInt
point
where
h :: CInt
h = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (t :: Type -> Type) a. Foldable t => t a -> Int
length [[Char]]
source)
w :: CInt
w = case forall a. Eq a => [a] -> [a]
nub forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall (t :: Type -> Type) a. Foldable t => t a -> Int
length [[Char]]
source of
[Int
okay] ->
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
okay
[Int]
mismatch ->
forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"Inconsistent row widths: " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> [Char]
show [Int]
mismatch
color :: Vector Word8
color = [Bool] -> Vector Word8
packBools [Bool]
colorBits
mask :: Vector Word8
mask = [Bool] -> Vector Word8
packBools [Bool]
maskBits
([Bool]
colorBits, [Bool]
maskBits) = forall a b. [(a, b)] -> ([a], [b])
unzip forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map Char -> (Bool, Bool)
charToBool forall a b. (a -> b) -> a -> b
$ forall (t :: Type -> Type) a. Foldable t => t [a] -> [a]
concat [[Char]]
source
packBools :: [Bool] -> Vector Word8
packBools = forall a. Storable a => [a] -> Vector a
V.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a}. Num a => [Bool] -> [a]
boolListToWord8List
charToBool :: Char -> (Bool, Bool)
charToBool Char
' ' = (Bool
False, Bool
False)
charToBool Char
'.' = (Bool
True, Bool
True)
charToBool Char
_ = (Bool
True, Bool
False)
boolListToWord8List :: [Bool] -> [a]
boolListToWord8List [Bool]
xs =
case [Bool]
xs of
Bool
b1 : Bool
b2 : Bool
b3 : Bool
b4 : Bool
b5 : Bool
b6 : Bool
b7 : Bool
b8 : [Bool]
rest ->
let
packed :: a
packed =
forall {p}. Num p => Bool -> p -> p
i Bool
b1 a
128 forall a. Num a => a -> a -> a
+
forall {p}. Num p => Bool -> p -> p
i Bool
b2 a
64 forall a. Num a => a -> a -> a
+
forall {p}. Num p => Bool -> p -> p
i Bool
b3 a
32 forall a. Num a => a -> a -> a
+
forall {p}. Num p => Bool -> p -> p
i Bool
b4 a
16 forall a. Num a => a -> a -> a
+
forall {p}. Num p => Bool -> p -> p
i Bool
b5 a
8 forall a. Num a => a -> a -> a
+
forall {p}. Num p => Bool -> p -> p
i Bool
b6 a
4 forall a. Num a => a -> a -> a
+
forall {p}. Num p => Bool -> p -> p
i Bool
b7 a
2 forall a. Num a => a -> a -> a
+
forall {p}. Num p => Bool -> p -> p
i Bool
b8 a
1
in
a
packed forall a. a -> [a] -> [a]
: [Bool] -> [a]
boolListToWord8List [Bool]
rest
[] ->
[]
[Bool]
_leftovers ->
forall a. HasCallStack => [Char] -> a
error [Char]
"The number of columns must be a multiple of 8."
where
i :: Bool -> p -> p
i Bool
True p
multiple = p
multiple
i Bool
False p
_ = p
0
freeCursor :: MonadIO m => Cursor -> m ()
freeCursor :: forall (m :: Type -> Type). MonadIO m => Cursor -> m ()
freeCursor = forall (m :: Type -> Type). MonadIO m => Window -> m ()
Raw.freeCursor forall b c a. (b -> c) -> (a -> b) -> a -> c
. Cursor -> Window
unwrapCursor
createColorCursor :: MonadIO m
=> Surface
-> Point V2 CInt
-> m Cursor
createColorCursor :: forall (m :: Type -> Type).
MonadIO m =>
Surface -> Point V2 CInt -> m Cursor
createColorCursor (Surface Ptr Surface
surfPtr Maybe (IOVector Word8)
_) (P (V2 CInt
hx CInt
hy)) =
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap Window -> Cursor
Cursor forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type) a.
MonadIO m =>
Text -> Text -> m (Ptr a) -> m (Ptr a)
throwIfNull Text
"SDL.Input.Mouse.createColorCursor" Text
"SDL_createColorCursor" forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type).
MonadIO m =>
Ptr Surface -> CInt -> CInt -> m Window
Raw.createColorCursor Ptr Surface
surfPtr CInt
hx CInt
hy
createSystemCursor :: MonadIO m => SystemCursor -> m Cursor
createSystemCursor :: forall (m :: Type -> Type). MonadIO m => SystemCursor -> m Cursor
createSystemCursor SystemCursor
sc =
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap Window -> Cursor
Cursor forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type) a.
MonadIO m =>
Text -> Text -> m (Ptr a) -> m (Ptr a)
throwIfNull Text
"SDL.Input.Mouse.createSystemCursor" Text
"SDL_CreateSystemCursor" forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type). MonadIO m => Word32 -> m Window
Raw.createSystemCursor (forall a b. ToNumber a b => a -> b
toNumber SystemCursor
sc)