gore-and-ash-glfw-1.1.2.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.State

Contents

Description

 

Synopsis

Documentation

type KeyChannel = IORef [(Key, KeyState, ModifierKeys)] Source #

Channel to connect core and callback with key states

type ButtonChannel = IORef [(MouseButton, MouseButtonState, ModifierKeys)] Source #

Channel to connect core and callback with mouse button states

type MouseChannel = IORef (Double, Double) Source #

Channel to connect core and callback with mouse position

type WindowSizeChannel = IORef (Maybe (Double, Double)) Source #

Channel to connect core and callback with window resizing

type ScrollChannel = IORef [(Double, Double)] Source #

Channel to connect core and callback with mouse scrolling

type CloseChannel = IORef Bool Source #

Channel to connect core and callback for window closing

data GLFWState s Source #

Module inner state

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

Instances

Generic (GLFWState s) Source # 

Associated Types

type Rep (GLFWState s) :: * -> * #

Methods

from :: GLFWState s -> Rep (GLFWState s) x #

to :: Rep (GLFWState s) x -> GLFWState s #

NFData s => NFData (GLFWState s) Source # 

Methods

rnf :: GLFWState s -> () #

Monad m => MonadState (GLFWState s) (GLFWT s m) 

Methods

get :: GLFWT s m (GLFWState s)

put :: GLFWState s -> GLFWT s m ()

state :: (GLFWState s -> (a, GLFWState s)) -> GLFWT s m a

type Rep (GLFWState s) Source # 
type Rep (GLFWState s) = D1 (MetaData "GLFWState" "Game.GoreAndAsh.GLFW.State" "gore-and-ash-glfw-1.1.2.0-A24f2sdDXdx1sN23WBbBFN" False) (C1 (MetaCons "GLFWState" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "glfwNextState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 s)) (S1 (MetaSel (Just Symbol "glfwKeys") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap Key (KeyState, ModifierKeys))))) ((:*:) (S1 (MetaSel (Just Symbol "glfwKeyChannel") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 KeyChannel)) (S1 (MetaSel (Just Symbol "glfwMouseButtons") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap MouseButton (MouseButtonState, ModifierKeys)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "glfwMouseButtonChannel") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 ButtonChannel)) (S1 (MetaSel (Just Symbol "glfwMousePos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Double, Double)))) ((:*:) (S1 (MetaSel (Just Symbol "glfwMousePosChannel") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 MouseChannel)) (S1 (MetaSel (Just Symbol "glfwWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Window)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "glfwPrevWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Window))) (S1 (MetaSel (Just Symbol "glfwWindowSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Double, Double))))) ((:*:) (S1 (MetaSel (Just Symbol "glfwWindowSizeChannel") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 WindowSizeChannel)) (S1 (MetaSel (Just Symbol "glfwScroll") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [(Double, Double)])))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "glfwScrollChannel") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 ScrollChannel)) (S1 (MetaSel (Just Symbol "glfwClose") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool))) ((:*:) (S1 (MetaSel (Just Symbol "glfwCloseChannel") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 CloseChannel)) (S1 (MetaSel (Just Symbol "glfwBufferSize") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Int)))))))

Orphan instances

NFData MouseButtonState Source # 

Methods

rnf :: MouseButtonState -> () #

NFData MouseButton Source # 

Methods

rnf :: MouseButton -> () #

NFData ModifierKeys Source # 

Methods

rnf :: ModifierKeys -> () #

NFData KeyState Source # 

Methods

rnf :: KeyState -> () #

NFData Key Source # 

Methods

rnf :: Key -> () #

Hashable MouseButton Source # 
Hashable Key Source # 

Methods

hashWithSalt :: Int -> Key -> Int

hash :: Key -> Int