dyna-gloss-0.1.0.0: FRP for gloss graphics and animation library
Safe HaskellNone
LanguageHaskell2010

Dyna.Gloss.Run

Description

Run the game application.

Synopsis

App execution

data Run a Source #

Monad that drives the application

Instances

Instances details
Monad Run Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

(>>=) :: Run a -> (a -> Run b) -> Run b #

(>>) :: Run a -> Run b -> Run b #

return :: a -> Run a #

Functor Run Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

fmap :: (a -> b) -> Run a -> Run b #

(<$) :: a -> Run b -> Run a #

Applicative Run Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

pure :: a -> Run a #

(<*>) :: Run (a -> b) -> Run a -> Run b #

liftA2 :: (a -> b -> c) -> Run a -> Run b -> Run c #

(*>) :: Run a -> Run b -> Run b #

(<*) :: Run a -> Run b -> Run a #

MonadIO Run Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

liftIO :: IO a -> Run a #

MonadRandom Run Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

getRandomR :: Random a => (a, a) -> Run a #

getRandom :: Random a => Run a #

getRandomRs :: Random a => (a, a) -> Run [a] #

getRandoms :: Random a => Run [a] #

Frp Run Source # 
Instance details

Defined in Dyna.Gloss.Types

Associated Types

type Ref Run :: Type -> Type #

MonadBase IO Run Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

liftBase :: IO α -> Run α #

MonadBaseControl IO Run Source # 
Instance details

Defined in Dyna.Gloss.Types

Associated Types

type StM Run a #

Methods

liftBaseWith :: (RunInBase Run IO -> IO a) -> Run a #

restoreM :: StM Run a -> Run a #

type Ref Run Source # 
Instance details

Defined in Dyna.Gloss.Types

type Ref Run = IORef
type StM Run a Source # 
Instance details

Defined in Dyna.Gloss.Types

type StM Run a

data Spec Source #

Initial parameters for the Game.

Constructors

Spec 

Fields

defSpec :: Spec Source #

Default settings. Runs in ullscreen mode.

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

mouse :: Dyn Vec Source #

Read mouse positions. It produces dynamic of vectors. (0, 0) is a center of the screen.

mouseV :: Dyn Vec Source #

Mouse velocity or displacement

drag :: MouseButton -> Dyn Vec Source #

Position of the mouse during drag, if no drag it becomes zero

dragV :: MouseButton -> Dyn Vec Source #

Displacement on drag, if no drag it becomes zero

mouseA :: Dyn Vec Source #

Mouse accelartion or speed of displacement

mouseRight :: Evt Vec Source #

Event stream of clicks of the mouse right button

mouseLeft :: Evt Vec Source #

Event stream of clicks of the mouse left button

mouseWheel :: Evt Float Source #

Mouse wheel displacement. If positive then it goes up, if negative then it goes down.

data Click Source #

All sorts of clicks

getClicks :: Evt Click Source #

Reads generic click events

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.

getResize :: Evt (Int, Int) Source #

Reads window resize events

keyUp :: Key -> Evt Modifiers Source #

Event stream of key up actions

keyDown :: Key -> Evt Modifiers Source #

Event stream of key down actions

charUp :: Char -> Evt Modifiers Source #

Event stream of char press up actions

charDown :: Char -> Evt Modifiers Source #

Event stream of char press down actions

Re-exports

data Key #

Instances

Instances details
Eq Key 
Instance details

Defined in Graphics.Gloss.Internals.Interface.Backend.Types

Methods

(==) :: Key -> Key -> Bool #

(/=) :: Key -> Key -> Bool #

Ord Key 
Instance details

Defined in Graphics.Gloss.Internals.Interface.Backend.Types

Methods

compare :: Key -> Key -> Ordering #

(<) :: Key -> Key -> Bool #

(<=) :: Key -> Key -> Bool #

(>) :: Key -> Key -> Bool #

(>=) :: Key -> Key -> Bool #

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Show Key 
Instance details

Defined in Graphics.Gloss.Internals.Interface.Backend.Types

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #