Safe Haskell | None |
---|---|
Language | Haskell2010 |
Dyna.Gloss.Run
Description
Run the game application.
Synopsis
- data Run a
- data Spec = Spec {}
- defSpec :: Spec
- runApp :: Spec -> Run (Dyn Picture) -> IO ()
- mouse :: Dyn Vec
- mouseV :: Dyn Vec
- isDrag :: MouseButton -> Dyn Bool
- drag :: MouseButton -> Dyn Vec
- dragV :: MouseButton -> Dyn Vec
- mouseA :: Dyn Vec
- mouseRight :: Evt Vec
- mouseLeft :: Evt Vec
- mouseWheel :: Evt Float
- data Click = Click Key KeyState Modifiers Vec
- getClicks :: Evt Click
- getFrames :: Evt Float
- getResize :: Evt (Int, Int)
- keyUp :: Key -> Evt Modifiers
- keyDown :: Key -> Evt Modifiers
- charUp :: Char -> Evt Modifiers
- charDown :: Char -> Evt Modifiers
- data Key
- data SpecialKey
- = KeyUnknown
- | KeySpace
- | KeyEsc
- | KeyF1
- | KeyF2
- | KeyF3
- | KeyF4
- | KeyF5
- | KeyF6
- | KeyF7
- | KeyF8
- | KeyF9
- | KeyF10
- | KeyF11
- | KeyF12
- | KeyF13
- | KeyF14
- | KeyF15
- | KeyF16
- | KeyF17
- | KeyF18
- | KeyF19
- | KeyF20
- | KeyF21
- | KeyF22
- | KeyF23
- | KeyF24
- | KeyF25
- | KeyUp
- | KeyDown
- | KeyLeft
- | KeyRight
- | KeyTab
- | KeyEnter
- | KeyBackspace
- | KeyInsert
- | KeyNumLock
- | KeyBegin
- | KeyDelete
- | KeyPageUp
- | KeyPageDown
- | KeyHome
- | KeyEnd
- | KeyShiftL
- | KeyShiftR
- | KeyCtrlL
- | KeyCtrlR
- | KeyAltL
- | KeyAltR
- | KeyPad0
- | KeyPad1
- | KeyPad2
- | KeyPad3
- | KeyPad4
- | KeyPad5
- | KeyPad6
- | KeyPad7
- | KeyPad8
- | KeyPad9
- | KeyPadDivide
- | KeyPadMultiply
- | KeyPadSubtract
- | KeyPadAdd
- | KeyPadDecimal
- | KeyPadEqual
- | KeyPadEnter
- data MouseButton
- data KeyState
- data Modifiers = Modifiers {}
App execution
Monad that drives the application
Instances
Monad Run Source # | |
Functor Run Source # | |
Applicative Run Source # | |
MonadIO Run Source # | |
Defined in Dyna.Gloss.Types | |
MonadRandom Run Source # | |
Defined in Dyna.Gloss.Types | |
Frp Run Source # | |
MonadBase IO Run Source # | |
Defined in Dyna.Gloss.Types | |
MonadBaseControl IO Run Source # | |
type Ref Run Source # | |
Defined in Dyna.Gloss.Types | |
type StM Run a Source # | |
Defined in Dyna.Gloss.Types |
Initial parameters for the Game.
Constructors
Spec | |
Fields
|
runApp :: Spec -> Run (Dyn Picture) -> IO () Source #
Run the aplication. It accepts initial settings and the dynamic value of pictures wrapped in the Run monad.
Note that to work properly we need to compile to executable with options -O2 and -threaded. The function does not work in ghci or with runhaskell because it requires support for multiple threads.
Define the application with the Main module. Then compie it:
stack exec -- ghc -O2 -threaded dyna-gloss/examples/Ball.hs
And run the result:
./dyna-gloss/examples/Ball
How it works? It runs the dynamic process at the background thread and every time the gloss function requests new frame it takes a snapshot of the current value of the main dynamic process which produces pictures. It's exactly what gloss simulation function needs to render it on the screen.
IO interface
Read mouse positions. It produces dynamic of vectors. (0, 0)
is a center of the screen.
drag :: MouseButton -> Dyn Vec Source #
Position of the mouse during drag, if no drag it becomes zero
mouseRight :: Evt Vec Source #
Event stream of clicks of the mouse right button
mouseWheel :: Evt Float Source #
Mouse wheel displacement. If positive then it goes up, if negative then it goes down.
getFrames :: Evt Float Source #
Reads frame updates. Value of the event is a time that has passed since the previous frame.
Note that if we want to use the sort of event stream as a timeline for the game or simulation
we can also use time utilities from the FRP library: clock
, pulse
, ticks
, timer
.
Re-exports
Constructors
Char Char | |
SpecialKey SpecialKey | |
MouseButton MouseButton |
data SpecialKey #
Constructors
Instances
Eq SpecialKey | |
Ord SpecialKey | |
Defined in Graphics.Gloss.Internals.Interface.Backend.Types Methods compare :: SpecialKey -> SpecialKey -> Ordering # (<) :: SpecialKey -> SpecialKey -> Bool # (<=) :: SpecialKey -> SpecialKey -> Bool # (>) :: SpecialKey -> SpecialKey -> Bool # (>=) :: SpecialKey -> SpecialKey -> Bool # max :: SpecialKey -> SpecialKey -> SpecialKey # min :: SpecialKey -> SpecialKey -> SpecialKey # | |
Show SpecialKey | |
Defined in Graphics.Gloss.Internals.Interface.Backend.Types Methods showsPrec :: Int -> SpecialKey -> ShowS # show :: SpecialKey -> String # showList :: [SpecialKey] -> ShowS # |
data MouseButton #
Constructors
LeftButton | |
MiddleButton | |
RightButton | |
WheelUp | |
WheelDown | |
AdditionalButton Int |
Instances
Eq MouseButton | |
Ord MouseButton | |
Defined in Graphics.Gloss.Internals.Interface.Backend.Types Methods compare :: MouseButton -> MouseButton -> Ordering # (<) :: MouseButton -> MouseButton -> Bool # (<=) :: MouseButton -> MouseButton -> Bool # (>) :: MouseButton -> MouseButton -> Bool # (>=) :: MouseButton -> MouseButton -> Bool # max :: MouseButton -> MouseButton -> MouseButton # min :: MouseButton -> MouseButton -> MouseButton # | |
Show MouseButton | |
Defined in Graphics.Gloss.Internals.Interface.Backend.Types Methods showsPrec :: Int -> MouseButton -> ShowS # show :: MouseButton -> String # showList :: [MouseButton] -> ShowS # |
Instances
Eq Modifiers | |
Ord Modifiers | |
Show Modifiers | |