module Graphics.GPipe.Context.GLFW.Input (
GLFW.postEmptyEvent,
setKeyCallback,
getKey,
setStickyKeysInputMode,
getStickyKeysInputMode,
setCharCallback,
setCursorPosCallback,
getCursorPos,
setCursorInputMode,
getCursorInputMode,
GLFW.createCursor,
GLFW.createStandardCursor,
GLFW.destroyCursor,
setCursor,
setCursorEnterCallback,
setMouseButtonCallback,
getMouseButton,
setStickyMouseButtonsInputMode,
getStickyMouseButtonsInputMode,
setScrollCallback,
GLFW.joystickPresent,
GLFW.getJoystickAxes,
GLFW.getJoystickButtons,
GLFW.getJoystickName,
GLFW.getTime,
GLFW.setTime,
getClipboardString,
setClipboardString,
setDropCallback,
Key(..),
KeyState(..),
ModifierKeys(..),
StickyKeysInputMode(..),
CursorInputMode(..),
StandardCursorShape(..),
CursorState(..),
StickyMouseButtonsInputMode(..),
MouseButton(..),
MouseButtonState(..),
Joystick(..),
JoystickButtonState(..),
) where
import Control.Monad.IO.Class (MonadIO)
import qualified Graphics.GPipe.Context as GPipe (ContextT,
Window)
import Graphics.UI.GLFW (Cursor (..),
CursorInputMode (..),
CursorState (..),
Joystick (..),
JoystickButtonState (..),
Key (..), KeyState (..),
ModifierKeys (..),
MouseButton (..),
MouseButtonState (..),
StandardCursorShape (..),
StickyKeysInputMode (..),
StickyMouseButtonsInputMode (..))
import qualified Graphics.UI.GLFW as GLFW
import qualified Graphics.GPipe.Context.GLFW.Calls as Call
import Graphics.GPipe.Context.GLFW.Handler (Handle (..))
import Graphics.GPipe.Context.GLFW.Wrappers (withWindowRPC,
wrapCallbackSetter,
wrapWindowFun)
setKeyCallback :: MonadIO m => GPipe.Window os c ds -> Maybe (Key -> Int -> KeyState -> ModifierKeys -> IO ()) -> GPipe.ContextT Handle os m (Maybe ())
setKeyCallback :: Window os c ds
-> Maybe (Key -> Int -> KeyState -> ModifierKeys -> IO ())
-> ContextT Handle os m (Maybe ())
setKeyCallback = (OnMain ()
-> Window
-> Maybe
(Window -> Key -> Int -> KeyState -> ModifierKeys -> IO ())
-> IO ())
-> Window os c ds
-> Maybe (Key -> Int -> KeyState -> ModifierKeys -> IO ())
-> ContextT Handle os m (Maybe ())
forall (m :: * -> *) (g :: * -> *) a b os c ds.
(MonadIO m, Functor g) =>
(OnMain a -> Window -> g (Window -> b) -> IO a)
-> Window os c ds -> g b -> ContextT Handle os m (Maybe a)
wrapCallbackSetter OnMain ()
-> Window
-> Maybe
(Window -> Key -> Int -> KeyState -> ModifierKeys -> IO ())
-> IO ()
Call.setKeyCallback
getKey :: MonadIO m => GPipe.Window os c ds -> Key -> GPipe.ContextT Handle os m (Maybe KeyState)
getKey :: Window os c ds -> Key -> ContextT Handle os m (Maybe KeyState)
getKey = (OnMain KeyState -> Window -> Key -> IO KeyState)
-> Window os c ds -> Key -> ContextT Handle os m (Maybe KeyState)
forall (m :: * -> *) b a os c ds.
MonadIO m =>
(OnMain b -> Window -> a -> IO b)
-> Window os c ds -> a -> ContextT Handle os m (Maybe b)
wrapWindowFun OnMain KeyState -> Window -> Key -> IO KeyState
Call.getKey
setStickyKeysInputMode :: MonadIO m => GPipe.Window os c ds -> StickyKeysInputMode -> GPipe.ContextT Handle os m (Maybe ())
setStickyKeysInputMode :: Window os c ds
-> StickyKeysInputMode -> ContextT Handle os m (Maybe ())
setStickyKeysInputMode = (OnMain () -> Window -> StickyKeysInputMode -> IO ())
-> Window os c ds
-> StickyKeysInputMode
-> ContextT Handle os m (Maybe ())
forall (m :: * -> *) b a os c ds.
MonadIO m =>
(OnMain b -> Window -> a -> IO b)
-> Window os c ds -> a -> ContextT Handle os m (Maybe b)
wrapWindowFun OnMain () -> Window -> StickyKeysInputMode -> IO ()
Call.setStickyKeysInputMode
getStickyKeysInputMode :: MonadIO m => GPipe.Window os c ds -> GPipe.ContextT Handle os m (Maybe StickyKeysInputMode)
getStickyKeysInputMode :: Window os c ds -> ContextT Handle os m (Maybe StickyKeysInputMode)
getStickyKeysInputMode = (OnMain StickyKeysInputMode -> Window -> IO StickyKeysInputMode)
-> Window os c ds
-> ContextT Handle os m (Maybe StickyKeysInputMode)
forall (m :: * -> *) a os c ds.
MonadIO m =>
(OnMain a -> Window -> IO a)
-> Window os c ds -> ContextT Handle os m (Maybe a)
withWindowRPC OnMain StickyKeysInputMode -> Window -> IO StickyKeysInputMode
Call.getStickyKeysInputMode
setCharCallback :: MonadIO m => GPipe.Window os c ds -> Maybe (Char -> IO ()) -> GPipe.ContextT Handle os m (Maybe ())
setCharCallback :: Window os c ds
-> Maybe (Char -> IO ()) -> ContextT Handle os m (Maybe ())
setCharCallback = (OnMain () -> Window -> Maybe (Window -> Char -> IO ()) -> IO ())
-> Window os c ds
-> Maybe (Char -> IO ())
-> ContextT Handle os m (Maybe ())
forall (m :: * -> *) (g :: * -> *) a b os c ds.
(MonadIO m, Functor g) =>
(OnMain a -> Window -> g (Window -> b) -> IO a)
-> Window os c ds -> g b -> ContextT Handle os m (Maybe a)
wrapCallbackSetter OnMain () -> Window -> Maybe (Window -> Char -> IO ()) -> IO ()
Call.setCharCallback
setCursorPosCallback :: MonadIO m => GPipe.Window os c ds -> Maybe (Double -> Double -> IO ()) -> GPipe.ContextT Handle os m (Maybe ())
setCursorPosCallback :: Window os c ds
-> Maybe (Double -> Double -> IO ())
-> ContextT Handle os m (Maybe ())
setCursorPosCallback = (OnMain ()
-> Window -> Maybe (Window -> Double -> Double -> IO ()) -> IO ())
-> Window os c ds
-> Maybe (Double -> Double -> IO ())
-> ContextT Handle os m (Maybe ())
forall (m :: * -> *) (g :: * -> *) a b os c ds.
(MonadIO m, Functor g) =>
(OnMain a -> Window -> g (Window -> b) -> IO a)
-> Window os c ds -> g b -> ContextT Handle os m (Maybe a)
wrapCallbackSetter OnMain ()
-> Window -> Maybe (Window -> Double -> Double -> IO ()) -> IO ()
Call.setCursorPosCallback
getCursorPos :: MonadIO m => GPipe.Window os c ds -> GPipe.ContextT Handle os m (Maybe (Double, Double))
getCursorPos :: Window os c ds -> ContextT Handle os m (Maybe (Double, Double))
getCursorPos = (OnMain (Double, Double) -> Window -> IO (Double, Double))
-> Window os c ds -> ContextT Handle os m (Maybe (Double, Double))
forall (m :: * -> *) a os c ds.
MonadIO m =>
(OnMain a -> Window -> IO a)
-> Window os c ds -> ContextT Handle os m (Maybe a)
withWindowRPC OnMain (Double, Double) -> Window -> IO (Double, Double)
Call.getCursorPos
setCursorInputMode :: MonadIO m => GPipe.Window os c ds -> CursorInputMode -> GPipe.ContextT Handle os m (Maybe ())
setCursorInputMode :: Window os c ds
-> CursorInputMode -> ContextT Handle os m (Maybe ())
setCursorInputMode = (OnMain () -> Window -> CursorInputMode -> IO ())
-> Window os c ds
-> CursorInputMode
-> ContextT Handle os m (Maybe ())
forall (m :: * -> *) b a os c ds.
MonadIO m =>
(OnMain b -> Window -> a -> IO b)
-> Window os c ds -> a -> ContextT Handle os m (Maybe b)
wrapWindowFun OnMain () -> Window -> CursorInputMode -> IO ()
Call.setCursorInputMode
getCursorInputMode :: MonadIO m => GPipe.Window os c ds -> GPipe.ContextT Handle os m (Maybe CursorInputMode)
getCursorInputMode :: Window os c ds -> ContextT Handle os m (Maybe CursorInputMode)
getCursorInputMode = (OnMain CursorInputMode -> Window -> IO CursorInputMode)
-> Window os c ds -> ContextT Handle os m (Maybe CursorInputMode)
forall (m :: * -> *) a os c ds.
MonadIO m =>
(OnMain a -> Window -> IO a)
-> Window os c ds -> ContextT Handle os m (Maybe a)
withWindowRPC OnMain CursorInputMode -> Window -> IO CursorInputMode
Call.getCursorInputMode
setCursor :: MonadIO m => GPipe.Window os c ds -> Cursor -> GPipe.ContextT Handle os m (Maybe ())
setCursor :: Window os c ds -> Cursor -> ContextT Handle os m (Maybe ())
setCursor = (OnMain () -> Window -> Cursor -> IO ())
-> Window os c ds -> Cursor -> ContextT Handle os m (Maybe ())
forall (m :: * -> *) b a os c ds.
MonadIO m =>
(OnMain b -> Window -> a -> IO b)
-> Window os c ds -> a -> ContextT Handle os m (Maybe b)
wrapWindowFun OnMain () -> Window -> Cursor -> IO ()
Call.setCursor
setCursorEnterCallback :: MonadIO m => GPipe.Window os c ds -> Maybe (CursorState -> IO ()) -> GPipe.ContextT Handle os m (Maybe ())
setCursorEnterCallback :: Window os c ds
-> Maybe (CursorState -> IO ()) -> ContextT Handle os m (Maybe ())
setCursorEnterCallback = (OnMain ()
-> Window -> Maybe (Window -> CursorState -> IO ()) -> IO ())
-> Window os c ds
-> Maybe (CursorState -> IO ())
-> ContextT Handle os m (Maybe ())
forall (m :: * -> *) (g :: * -> *) a b os c ds.
(MonadIO m, Functor g) =>
(OnMain a -> Window -> g (Window -> b) -> IO a)
-> Window os c ds -> g b -> ContextT Handle os m (Maybe a)
wrapCallbackSetter OnMain ()
-> Window -> Maybe (Window -> CursorState -> IO ()) -> IO ()
Call.setCursorEnterCallback
setMouseButtonCallback :: MonadIO m => GPipe.Window os c ds -> Maybe (MouseButton -> MouseButtonState -> ModifierKeys -> IO ()) -> GPipe.ContextT Handle os m (Maybe ())
setMouseButtonCallback :: Window os c ds
-> Maybe (MouseButton -> MouseButtonState -> ModifierKeys -> IO ())
-> ContextT Handle os m (Maybe ())
setMouseButtonCallback = (OnMain ()
-> Window
-> Maybe
(Window
-> MouseButton -> MouseButtonState -> ModifierKeys -> IO ())
-> IO ())
-> Window os c ds
-> Maybe (MouseButton -> MouseButtonState -> ModifierKeys -> IO ())
-> ContextT Handle os m (Maybe ())
forall (m :: * -> *) (g :: * -> *) a b os c ds.
(MonadIO m, Functor g) =>
(OnMain a -> Window -> g (Window -> b) -> IO a)
-> Window os c ds -> g b -> ContextT Handle os m (Maybe a)
wrapCallbackSetter OnMain ()
-> Window
-> Maybe
(Window
-> MouseButton -> MouseButtonState -> ModifierKeys -> IO ())
-> IO ()
Call.setMouseButtonCallback
getMouseButton :: MonadIO m => GPipe.Window os c ds -> MouseButton -> GPipe.ContextT Handle os m (Maybe MouseButtonState)
getMouseButton :: Window os c ds
-> MouseButton -> ContextT Handle os m (Maybe MouseButtonState)
getMouseButton = (OnMain MouseButtonState
-> Window -> MouseButton -> IO MouseButtonState)
-> Window os c ds
-> MouseButton
-> ContextT Handle os m (Maybe MouseButtonState)
forall (m :: * -> *) b a os c ds.
MonadIO m =>
(OnMain b -> Window -> a -> IO b)
-> Window os c ds -> a -> ContextT Handle os m (Maybe b)
wrapWindowFun OnMain MouseButtonState
-> Window -> MouseButton -> IO MouseButtonState
Call.getMouseButton
setStickyMouseButtonsInputMode :: MonadIO m => GPipe.Window os c ds -> StickyMouseButtonsInputMode -> GPipe.ContextT Handle os m (Maybe ())
setStickyMouseButtonsInputMode :: Window os c ds
-> StickyMouseButtonsInputMode -> ContextT Handle os m (Maybe ())
setStickyMouseButtonsInputMode = (OnMain () -> Window -> StickyMouseButtonsInputMode -> IO ())
-> Window os c ds
-> StickyMouseButtonsInputMode
-> ContextT Handle os m (Maybe ())
forall (m :: * -> *) b a os c ds.
MonadIO m =>
(OnMain b -> Window -> a -> IO b)
-> Window os c ds -> a -> ContextT Handle os m (Maybe b)
wrapWindowFun OnMain () -> Window -> StickyMouseButtonsInputMode -> IO ()
Call.setStickyMouseButtonsInputMode
getStickyMouseButtonsInputMode :: MonadIO m => GPipe.Window os c ds -> GPipe.ContextT Handle os m (Maybe StickyMouseButtonsInputMode)
getStickyMouseButtonsInputMode :: Window os c ds
-> ContextT Handle os m (Maybe StickyMouseButtonsInputMode)
getStickyMouseButtonsInputMode = (OnMain StickyMouseButtonsInputMode
-> Window -> IO StickyMouseButtonsInputMode)
-> Window os c ds
-> ContextT Handle os m (Maybe StickyMouseButtonsInputMode)
forall (m :: * -> *) a os c ds.
MonadIO m =>
(OnMain a -> Window -> IO a)
-> Window os c ds -> ContextT Handle os m (Maybe a)
withWindowRPC OnMain StickyMouseButtonsInputMode
-> Window -> IO StickyMouseButtonsInputMode
Call.getStickyMouseButtonsInputMode
setScrollCallback :: MonadIO m => GPipe.Window os c ds -> Maybe (Double -> Double -> IO ()) -> GPipe.ContextT Handle os m (Maybe ())
setScrollCallback :: Window os c ds
-> Maybe (Double -> Double -> IO ())
-> ContextT Handle os m (Maybe ())
setScrollCallback = (OnMain ()
-> Window -> Maybe (Window -> Double -> Double -> IO ()) -> IO ())
-> Window os c ds
-> Maybe (Double -> Double -> IO ())
-> ContextT Handle os m (Maybe ())
forall (m :: * -> *) (g :: * -> *) a b os c ds.
(MonadIO m, Functor g) =>
(OnMain a -> Window -> g (Window -> b) -> IO a)
-> Window os c ds -> g b -> ContextT Handle os m (Maybe a)
wrapCallbackSetter OnMain ()
-> Window -> Maybe (Window -> Double -> Double -> IO ()) -> IO ()
Call.setScrollCallback
getClipboardString :: MonadIO m => GPipe.Window os c ds -> GPipe.ContextT Handle os m (Maybe (Maybe String))
getClipboardString :: Window os c ds -> ContextT Handle os m (Maybe (Maybe String))
getClipboardString = (OnMain (Maybe String) -> Window -> IO (Maybe String))
-> Window os c ds -> ContextT Handle os m (Maybe (Maybe String))
forall (m :: * -> *) a os c ds.
MonadIO m =>
(OnMain a -> Window -> IO a)
-> Window os c ds -> ContextT Handle os m (Maybe a)
withWindowRPC OnMain (Maybe String) -> Window -> IO (Maybe String)
Call.getClipboardString
setClipboardString :: MonadIO m => GPipe.Window os c ds -> String -> GPipe.ContextT Handle os m (Maybe ())
setClipboardString :: Window os c ds -> String -> ContextT Handle os m (Maybe ())
setClipboardString = (OnMain () -> Window -> String -> IO ())
-> Window os c ds -> String -> ContextT Handle os m (Maybe ())
forall (m :: * -> *) b a os c ds.
MonadIO m =>
(OnMain b -> Window -> a -> IO b)
-> Window os c ds -> a -> ContextT Handle os m (Maybe b)
wrapWindowFun OnMain () -> Window -> String -> IO ()
Call.setClipboardString
setDropCallback :: MonadIO m => GPipe.Window os c ds -> Maybe ([String] -> IO ()) -> GPipe.ContextT Handle os m (Maybe ())
setDropCallback :: Window os c ds
-> Maybe ([String] -> IO ()) -> ContextT Handle os m (Maybe ())
setDropCallback = (OnMain ()
-> Window -> Maybe (Window -> [String] -> IO ()) -> IO ())
-> Window os c ds
-> Maybe ([String] -> IO ())
-> ContextT Handle os m (Maybe ())
forall (m :: * -> *) (g :: * -> *) a b os c ds.
(MonadIO m, Functor g) =>
(OnMain a -> Window -> g (Window -> b) -> IO a)
-> Window os c ds -> g b -> ContextT Handle os m (Maybe a)
wrapCallbackSetter OnMain () -> Window -> Maybe (Window -> [String] -> IO ()) -> IO ()
Call.setDropCallback