netwire-input-0.0.6: Input handling abstractions for netwire

Copyright(c) Pavel Krajcevski 2014
LicenseMIT
MaintainerKrajcevski@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

FRP.Netwire.Input

Contents

Description

This module contains definitions for typeclasses and wires to be used in FRP programs that use netwire. In order to use this module, an implementation that provides an instance of one of the underlying typeclasses MonadMouse or MonadKeyboard must be used. In order to not require the GLFW or SDL libraries as dependencies, these instances are provided in separate libraries.

Synopsis

Mouse input

class MouseButton a Source #

Mouse button typeclass. This is used to constrain the type of Monad used | to provide mouse input.

data CursorMode Source #

The mouse cursor mode. This mode is usually dependent on whether or not the mouse is in the bounds of the application window.

Constructors

CursorMode'Disabled

The mouse cursor is disabled

CursorMode'Reset

Reset the cursor to zero between computations

CursorMode'Hidden

The mouse cursor is hidden when over the application

CursorMode'Enabled

The mouse cursor is enabed and visible over the application

Mouse input

class (MouseButton mb, Monad m) => MonadMouse mb m | m -> mb where Source #

This monad describes computations that involve mouse input.

Minimal complete definition

setCursorMode, mbIsPressed, releaseButton, cursor, scroll

Methods

setCursorMode :: CursorMode -> m () Source #

Sets the cursor mode for all subsequent computations. Note, that many | implementations require some sort of "poll" to read the IO

mbIsPressed :: mb -> m Bool Source #

Returns true if the given mouse button is pressed

releaseButton :: mb -> m () Source #

Resets the pressed state of the mouse button

cursor :: m (Float, Float) Source #

Get the current cursor location

scroll :: m (Double, Double) Source #

Get the amount of scrolling done in the x and y directions

Mouse input wires

mouseCursor :: MonadMouse mb m => Wire s e m a (Float, Float) Source #

Ignores its input and returns the current normalized mouse coordinates. Regardless of window size, each of the returned coordinates will be in the range [-1, 1].

  • Depends: now
  • Inhibits: never

mouseDelta :: (MonadFix m, MonadMouse mb m) => Wire s e m a (Float, Float) Source #

Returns the change in mouse coordinates between subsequent time instants

  • Depends: before now
  • Inhibits: never

mouseMickies :: MonadMouse mb m => Wire s e m a (Float, Float) Source #

The mouse mickies are the offset from zero at each time instant. If this wire is being used, then it is assuming that the cursor mode is set to CursorMode'Reset

  • Depends: now
  • Inhibits: never

mousePressed :: (Monoid e, MonadMouse mb m) => mb -> Wire s e m a a Source #

Behaves like the identity wire when the mouse button is pressed and inhibits otherwise

  • Inhibits: when the mouse button is not pressed

isMousePressed :: MonadMouse mb m => mb -> Wire s e m a Bool Source #

Ignores its input and returns True whenever the mouse button is pressed, False otherwise.

  • Inhibits: never

mouseDebounced :: (Monoid e, MonadMouse mb m) => mb -> Wire s e m a a Source #

Behaves like the identity wire for a signle instant when the mouse button is pressed and otherwise inhibits. Note that this wire causing the button to be treated as released by all other wires after the instant when it is pressed.

  • Depends: the instant at which the mouse button is pressed
  • Inhibits: when the mouse button is not pressed or after it has been pressed

mousePressedEvent :: MonadMouse mb m => mb -> Wire s e m a (Event a) Source #

Fires an event the instant the given mouse button is pressed after not being pressed.

  • Inhibits: never

mouseReleasedEvent :: MonadMouse mb m => mb -> Wire s e m a (Event a) Source #

Fires an event the instant the given mouse button is released after being pressed.

  • Inhibits: never

mouseScroll :: (Monoid e, MonadMouse mb m) => Wire s e m a (Double, Double) Source #

The mouse scroll is the offset from zero at each time instant.

  • Depends: now
  • Inhibits: never

mouseScrolled :: (Monoid e, MonadMouse mb m) => Wire s e m a (Double, Double) Source #

The amount that the mouse has scrolled over the course of the entire wire.

  • Depends: now
  • Inhibits: never

cursorMode :: (MonadMouse mb m, Monoid e) => CursorMode -> Wire s e m a a Source #

Behaves like the identity wire, and inhibits immediately after setting the cursor mode. Common uses of this wire are to switch it to the identity wire: cursorMode CursorMode'Disabled --> mkId

  • Inhibits: after now

Keyboard input

class Key a Source #

Key typeclass. This is used to constrain the type of Monad used | to provide keyboard input.

class (Key k, Monad m) => MonadKeyboard k m | m -> k where Source #

This monad describes computations that involve keyboard input.

Minimal complete definition

keyIsPressed, releaseKey

Methods

keyIsPressed :: k -> m Bool Source #

Returns true if the given key is currently pressed

releaseKey :: k -> m () Source #

Resets the pressed state of the given key.

Keyboard input wires

keyPressed :: (Monoid e, MonadKeyboard k m) => k -> Wire s e m a a Source #

Behaves like the identity wire when the key is pressed and inhibits otherwise

  • Inhibits: when the key is not pressed

keyNotPressed :: (Monoid e, MonadKeyboard k m) => k -> Wire s e m a a Source #

Behaves like the identity wire when the key is not pressed and inhibits otherwise

  • Inhibits: when the key is pressed

isKeyPressed :: MonadKeyboard k m => k -> Wire s e m a Bool Source #

Ignores its input and returns True whenever the key is pressed, False otherwise.

  • Inhibits: never

keyDebounced :: (Monoid e, MonadKeyboard k m) => k -> Wire s e m a a Source #

Behaves like the identity wire for a single instant when the key is pressed and otherwise inhibits. Note that this wire causes the key to be treated as released by all other wires after the instant when it is pressed.

  • Inhibits: when the key is not pressed or after it has been pressed

keyPressedEvent :: MonadKeyboard k m => k -> Wire s e m a (Event a) Source #

Fires an event the instant the given key is pressed after not being pressed.

  • Inhibits: never

keyReleasedEvent :: MonadKeyboard k m => k -> Wire s e m a (Event a) Source #

Fires an event the instant the given key is released after being pressed.

  • Inhibits: never