gore-and-ash-glfw-1.1.0.0: Core module for Gore&Ash engine for GLFW input events

Copyright(c) Anton Gushcha, 2015-2016
LicenseBSD3
Maintainerncrashed@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Game.GoreAndAsh.GLFW

Contents

Description

The core module contains API for GLFW library integration. The module doesn't depends on others core modules and could be place in any place in game monad stack.

The module is NOT pure within first phase (see ModuleStack docs), therefore currently only IO end monad can handler the module.

Example of embedding:

-- | Application monad is monad stack build from given list of modules over base monad (IO)
type AppStack = ModuleStack [GLFWT, ... other modules ... ] IO
newtype AppState = AppState (ModuleState AppStack)
  deriving (Generic)

instance NFData AppState 

-- | Wrapper around type family
newtype AppMonad a = AppMonad (AppStack a)
  deriving (Functor, Applicative, Monad, MonadFix, MonadIO, MonadThrow, MonadCatch, MonadGLFW, ... other modules monads ... )
  
instance GameModule AppMonad AppState where 
  type ModuleState AppMonad = AppState
  runModule (AppMonad m) (AppState s) = do 
    (a, s') <- runModule m s 
    return (a, AppState s')
  newModuleState = AppState $ newModuleState
  withModule _ = withModule (Proxy :: Proxy AppStack)
  cleanupModule (AppState s) = cleanupModule s 

-- | Arrow that is build over the monad stack
type AppWire a b = GameWire AppMonad a b
-- | Action that makes indexed app wire
type AppActor i a b = GameActor AppMonad i a b

Synopsis

Low-level API

data GLFWState s Source

Module inner state

s
- State of next module, the states are chained via nesting.

Instances

Generic (GLFWState s) Source 
NFData s => NFData (GLFWState s) Source 
Monad m => MonadState (GLFWState s) (GLFWT s m) 
type Rep (GLFWState s) Source 

data GLFWT s m a Source

Monad transformer that handles GLFW specific API

s
- State of next core module in modules chain;
m
- Next monad in modules monad stack;
a
- Type of result value;

How to embed module:

type AppStack = ModuleStack [GLFWT, ... other modules ... ] IO

newtype AppMonad a = AppMonad (AppStack a)
  deriving (Functor, Applicative, Monad, MonadFix, MonadIO, MonadThrow, MonadCatch, MonadSDL)

The module is NOT pure within first phase (see ModuleStack docs), therefore currently only IO end monad can handler the module.

Instances

MonadTrans (GLFWT s) Source 
Monad m => MonadState (GLFWState s) (GLFWT s m) Source 
Monad m => Monad (GLFWT s m) Source 
Functor m => Functor (GLFWT s m) Source 
MonadFix m => MonadFix (GLFWT s m) Source 
Monad m => Applicative (GLFWT s m) Source 
MonadIO m => MonadIO (GLFWT s m) Source 
MonadThrow m => MonadThrow (GLFWT s m) Source 
MonadMask m => MonadMask (GLFWT s m) Source 
MonadCatch m => MonadCatch (GLFWT s m) Source 
Monad m => MonadGLFW (GLFWT s m) Source 
type ModuleState (GLFWT s m) = GLFWState s Source 

class Monad m => MonadGLFW m where Source

Module low-level API

Methods

keyStatusM :: Key -> m (Maybe (KeyState, ModifierKeys)) Source

Returns state of given keyboard's key

mouseButtonM :: MouseButton -> m (Maybe (MouseButtonState, ModifierKeys)) Source

Returns state of given mouse button

mousePosM :: m (Double, Double) Source

Returns current position of mouse cursor

mouseScrollM :: m [(Double, Double)] Source

Returns current scroll values of mouse

windowSizeM :: m (Maybe (Double, Double)) Source

Returns current size of window

windowClosingM :: m Bool Source

Returns True when close button is pushed

setCurrentWindowM :: Maybe Window -> m () Source

Setups current window for input catch

getCurrentWindowM :: m (Maybe Window) Source

Returns current window

setBufferSizeM :: Int -> m () Source

Setup maximum size of inner buffers for keys, mouse buttons

Instances

(Monad (mt m), MonadGLFW m, MonadTrans mt) => MonadGLFW (mt m) Source 
Monad m => MonadGLFW (GLFWT s m) Source 

Arrow API

Keyboard API

keyStatus :: MonadGLFW m => Key -> GameWire m a (Event (KeyState, ModifierKeys)) Source

Produces event when key state changes

keyStatusDyn :: MonadGLFW m => GameWire m Key (Event (KeyState, ModifierKeys)) Source

Produces event when key state changes, get key as arrow argument

keyPressed :: MonadGLFW m => Key -> GameWire m a (Event ModifierKeys) Source

Fires when keyboard key is pressed

keyPressedDyn :: MonadGLFW m => GameWire m Key (Event ModifierKeys) Source

Version of keyPressed that takes key at runtime

keyReleased :: MonadGLFW m => Key -> GameWire m a (Event ModifierKeys) Source

Fires when keyboard key is released

keyReleasedDyn :: MonadGLFW m => GameWire m Key (Event ModifierKeys) Source

Version of keyReleased that takes key at runtime

keyRepeating :: MonadGLFW m => Key -> GameWire m a (Event ModifierKeys) Source

Fires when keyboard key is entered into repeating mode

keyRepeatingDyn :: MonadGLFW m => GameWire m Key (Event ModifierKeys) Source

Version of keyRepeating that takes key at runtime

keyPressing :: MonadGLFW m => Key -> GameWire m a (Event ModifierKeys) Source

Fires event from moment of press until release of given key

keyPressingDyn :: MonadGLFW m => GameWire m Key (Event ModifierKeys) Source

Version of keyPressing that takes key at runtime

Mouse buttons API

mouseButton :: MonadGLFW m => MouseButton -> GameWire m a (Event (MouseButtonState, ModifierKeys)) Source

Produces event when mouse button state changes

mouseButtonDyn :: MonadGLFW m => GameWire m MouseButton (Event (MouseButtonState, ModifierKeys)) Source

Produces event when key state changes, get key as arrow argument

mouseButtonPressed :: MonadGLFW m => MouseButton -> GameWire m a (Event ModifierKeys) Source

Fires when mouse button is pressed

mouseButtonPressedDyn :: MonadGLFW m => GameWire m MouseButton (Event ModifierKeys) Source

Version of mouseButtonPressed that takes button at runtime

mouseButtonReleased :: MonadGLFW m => MouseButton -> GameWire m a (Event ModifierKeys) Source

Fires when mouse button is released

mouseButtonReleasedDyn :: MonadGLFW m => GameWire m MouseButton (Event ModifierKeys) Source

Version of mouseButtonReleased that takes button at runtime

Cursor position

mousePosition :: MonadGLFW m => GameWire m a (Double, Double) Source

Returns current position of mouse

mousePositionChange :: MonadGLFW m => GameWire m a (Event (Double, Double)) Source

Fires event when mouse position changes

mouseXChange :: MonadGLFW m => GameWire m a (Event Double) Source

Fires event when mouse X axis changes

mouseYChange :: MonadGLFW m => GameWire m a (Event Double) Source

Fires event when mouse Y axis changes

mouseDelta :: MonadGLFW m => GameWire m a (Double, Double) Source

Returns mouse delta moves

mouseDeltaChange :: MonadGLFW m => GameWire m a (Event (Double, Double)) Source

Fires when mouse moves, holds delta move

mouseDeltaXChange :: MonadGLFW m => GameWire m a (Event Double) Source

Fires when mouse X axis changes, holds delta move

mouseDeltaYChange :: MonadGLFW m => GameWire m a (Event Double) Source

Fires when mouse Y axis changes, holds delta move

Mouse scroll

mouseScroll :: MonadGLFW m => GameWire m a (Event (Double, Double)) Source

Fires when user scrolls

mouseScrollX :: MonadGLFW m => GameWire m a (Event Double) Source

Fires when user scrolls X axis

mouseScrollY :: MonadGLFW m => GameWire m a (Event Double) Source

Fires when user scrolls Y axis

Window API

windowSize :: MonadGLFW m => GameWire m a (Event (Double, Double)) Source

Fires when windows size is changed

windowClosing :: MonadGLFW m => GameWire m a (Event ()) Source

Fires when user hits close button of window

Reexports

data Key :: *

Instances

Enum Key 
Eq Key 
Data Key 
Ord Key 
Read Key 
Show Key 
Generic Key 
type Rep Key = D1 D1Key ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 C1_0Key U1) ((:+:) (C1 C1_1Key U1) (C1 C1_2Key U1))) ((:+:) ((:+:) (C1 C1_3Key U1) (C1 C1_4Key U1)) ((:+:) (C1 C1_5Key U1) (C1 C1_6Key U1)))) ((:+:) ((:+:) ((:+:) (C1 C1_7Key U1) (C1 C1_8Key U1)) ((:+:) (C1 C1_9Key U1) (C1 C1_10Key U1))) ((:+:) ((:+:) (C1 C1_11Key U1) (C1 C1_12Key U1)) ((:+:) (C1 C1_13Key U1) (C1 C1_14Key U1))))) ((:+:) ((:+:) ((:+:) (C1 C1_15Key U1) ((:+:) (C1 C1_16Key U1) (C1 C1_17Key U1))) ((:+:) ((:+:) (C1 C1_18Key U1) (C1 C1_19Key U1)) ((:+:) (C1 C1_20Key U1) (C1 C1_21Key U1)))) ((:+:) ((:+:) ((:+:) (C1 C1_22Key U1) (C1 C1_23Key U1)) ((:+:) (C1 C1_24Key U1) (C1 C1_25Key U1))) ((:+:) ((:+:) (C1 C1_26Key U1) (C1 C1_27Key U1)) ((:+:) (C1 C1_28Key U1) (C1 C1_29Key U1)))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 C1_30Key U1) ((:+:) (C1 C1_31Key U1) (C1 C1_32Key U1))) ((:+:) ((:+:) (C1 C1_33Key U1) (C1 C1_34Key U1)) ((:+:) (C1 C1_35Key U1) (C1 C1_36Key U1)))) ((:+:) ((:+:) ((:+:) (C1 C1_37Key U1) (C1 C1_38Key U1)) ((:+:) (C1 C1_39Key U1) (C1 C1_40Key U1))) ((:+:) ((:+:) (C1 C1_41Key U1) (C1 C1_42Key U1)) ((:+:) (C1 C1_43Key U1) (C1 C1_44Key U1))))) ((:+:) ((:+:) ((:+:) (C1 C1_45Key U1) ((:+:) (C1 C1_46Key U1) (C1 C1_47Key U1))) ((:+:) ((:+:) (C1 C1_48Key U1) (C1 C1_49Key U1)) ((:+:) (C1 C1_50Key U1) (C1 C1_51Key U1)))) ((:+:) ((:+:) ((:+:) (C1 C1_52Key U1) (C1 C1_53Key U1)) ((:+:) (C1 C1_54Key U1) (C1 C1_55Key U1))) ((:+:) ((:+:) (C1 C1_56Key U1) (C1 C1_57Key U1)) ((:+:) (C1 C1_58Key U1) (C1 C1_59Key U1))))))) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 C1_60Key U1) ((:+:) (C1 C1_61Key U1) (C1 C1_62Key U1))) ((:+:) ((:+:) (C1 C1_63Key U1) (C1 C1_64Key U1)) ((:+:) (C1 C1_65Key U1) (C1 C1_66Key U1)))) ((:+:) ((:+:) ((:+:) (C1 C1_67Key U1) (C1 C1_68Key U1)) ((:+:) (C1 C1_69Key U1) (C1 C1_70Key U1))) ((:+:) ((:+:) (C1 C1_71Key U1) (C1 C1_72Key U1)) ((:+:) (C1 C1_73Key U1) (C1 C1_74Key U1))))) ((:+:) ((:+:) ((:+:) (C1 C1_75Key U1) ((:+:) (C1 C1_76Key U1) (C1 C1_77Key U1))) ((:+:) ((:+:) (C1 C1_78Key U1) (C1 C1_79Key U1)) ((:+:) (C1 C1_80Key U1) (C1 C1_81Key U1)))) ((:+:) ((:+:) ((:+:) (C1 C1_82Key U1) (C1 C1_83Key U1)) ((:+:) (C1 C1_84Key U1) (C1 C1_85Key U1))) ((:+:) ((:+:) (C1 C1_86Key U1) (C1 C1_87Key U1)) ((:+:) (C1 C1_88Key U1) (C1 C1_89Key U1)))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 C1_90Key U1) ((:+:) (C1 C1_91Key U1) (C1 C1_92Key U1))) ((:+:) ((:+:) (C1 C1_93Key U1) (C1 C1_94Key U1)) ((:+:) (C1 C1_95Key U1) (C1 C1_96Key U1)))) ((:+:) ((:+:) ((:+:) (C1 C1_97Key U1) (C1 C1_98Key U1)) ((:+:) (C1 C1_99Key U1) (C1 C1_100Key U1))) ((:+:) ((:+:) (C1 C1_101Key U1) (C1 C1_102Key U1)) ((:+:) (C1 C1_103Key U1) (C1 C1_104Key U1))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 C1_105Key U1) (C1 C1_106Key U1)) ((:+:) (C1 C1_107Key U1) (C1 C1_108Key U1))) ((:+:) ((:+:) (C1 C1_109Key U1) (C1 C1_110Key U1)) ((:+:) (C1 C1_111Key U1) (C1 C1_112Key U1)))) ((:+:) ((:+:) ((:+:) (C1 C1_113Key U1) (C1 C1_114Key U1)) ((:+:) (C1 C1_115Key U1) (C1 C1_116Key U1))) ((:+:) ((:+:) (C1 C1_117Key U1) (C1 C1_118Key U1)) ((:+:) (C1 C1_119Key U1) (C1 C1_120Key U1)))))))) 

data KeyState :: *

Instances

Enum KeyState 
Eq KeyState 
Data KeyState 
Ord KeyState 
Read KeyState 
Show KeyState 
Generic KeyState 
type Rep KeyState = D1 D1KeyState ((:+:) (C1 C1_0KeyState U1) ((:+:) (C1 C1_1KeyState U1) (C1 C1_2KeyState U1))) 

data MouseButton :: *

Instances

Enum MouseButton 
Eq MouseButton 
Data MouseButton 
Ord MouseButton 
Read MouseButton 
Show MouseButton 
Generic MouseButton 
type Rep MouseButton = D1 D1MouseButton ((:+:) ((:+:) ((:+:) (C1 C1_0MouseButton U1) (C1 C1_1MouseButton U1)) ((:+:) (C1 C1_2MouseButton U1) (C1 C1_3MouseButton U1))) ((:+:) ((:+:) (C1 C1_4MouseButton U1) (C1 C1_5MouseButton U1)) ((:+:) (C1 C1_6MouseButton U1) (C1 C1_7MouseButton U1)))) 

data ModifierKeys :: *

Instances

Eq ModifierKeys 
Data ModifierKeys 
Ord ModifierKeys 
Read ModifierKeys 
Show ModifierKeys 
Generic ModifierKeys 
type Rep ModifierKeys = D1 D1ModifierKeys (C1 C1_0ModifierKeys ((:*:) ((:*:) (S1 S1_0_0ModifierKeys (Rec0 Bool)) (S1 S1_0_1ModifierKeys (Rec0 Bool))) ((:*:) (S1 S1_0_2ModifierKeys (Rec0 Bool)) (S1 S1_0_3ModifierKeys (Rec0 Bool)))))