gore-and-ash-1.1.0.1: Core of FRP game engine called Gore&Ash

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

Game.GoreAndAsh.Core.Arrow

Contents

Description

The module defines GameWire type as fundamental type for all applications arrows. Also there are utilities for lifting GameMonadT actions to GameWire, event processing helpers and some other utilities.

Synopsis

Documentation

type GameWire m a b = Wire GameTime () (GameMonadT m) a b Source

Game wire with given API m and input value a and output value b.

Typically end point application defines a type synonyms:

-- | Arrow that is build over the monad stack
type AppWire a b = GameWire AppMonad a b

Lifting monad to arrow

liftGameMonad :: Monad m => GameMonadT m b -> GameWire m a b Source

Takes game monad and wraps it into game wire.

Note: Result of wire is calclulated each frame.

liftGameMonad1 :: Monad m => (a -> GameMonadT m b) -> GameWire m a b Source

Takes game monad and wraps it into game wire.

Note: Result of wire is calclulated each frame.

liftGameMonad2 :: Monad m => (a -> b -> GameMonadT m c) -> GameWire m (a, b) c Source

Takes game monad and wraps it into game wire.

Note: Result of wire is calclulated each frame.

liftGameMonad3 :: Monad m => (a -> b -> c -> GameMonadT m d) -> GameWire m (a, b, c) d Source

Takes game monad and wraps it into game wire.

Note: Result of wire is calclulated each frame.

liftGameMonad4 :: Monad m => (a -> b -> c -> d -> GameMonadT m e) -> GameWire m (a, b, c, d) e Source

Takes game monad and wraps it into game wire.

Note: Result of wire is calclulated each frame.

liftGameMonadOnce :: Monad m => GameMonadT m b -> GameWire m a b Source

Takes game monad and wraps it into game wire.

Note: Result of wire is calculated ONCE and next execution returns cached value

liftGameMonad1Once :: Monad m => (a -> GameMonadT m b) -> GameWire m a b Source

Takes game monad and wraps it into game wire.

Note: Result of wire is calculated ONCE and next execution returns cached value

liftGameMonad2Once :: Monad m => (a -> b -> GameMonadT m c) -> GameWire m (a, b) c Source

Takes game monad and wraps it into game wire.

Note: Result of wire is calculated ONCE and next execution returns cached value

liftGameMonad3Once :: Monad m => (a -> b -> c -> GameMonadT m d) -> GameWire m (a, b, c) d Source

Takes game monad and wraps it into game wire.

Note: Result of wire is calculated ONCE and next execution returns cached value

liftGameMonad4Once :: Monad m => (a -> b -> c -> d -> GameMonadT m e) -> GameWire m (a, b, c, d) e Source

Takes game monad and wraps it into game wire.

Note: Result of wire is calculated ONCE and next execution returns cached value

Event functions

once' :: Monad m => GameWire m a (Event b) -> GameWire m a (Event b) Source

Pass through first occurence and then forget about event producer.

Note: netwire once combinator still holds it event producer when event is produced.

mapE :: Monad m => (a -> b) -> GameWire m (Event a) (Event b) Source

Mapping events as a wire.

It is semantically equal to:

>>> arr (fmap f)

filterE :: (a -> Bool) -> Wire s e m (Event a) (Event a) Source

Forget all occurrences for which the given predicate is false.

  • Depends: now.

filterEG Source

Arguments

:: (Foldable f, Filterable f, FilterConstraint f a, Monad m) 
=> (a -> Bool)

Predicate to test elements that are left in collection

-> GameWire m (Event (f a)) (Event (f a))

Wire that leaves only non empty collections

Same as filterE but for generic Foldable and Filterable.

filterEGM Source

Arguments

:: (Foldable f, Filterable f, FilterConstraint f a, Monad m) 
=> (a -> GameMonadT m Bool)

Predicate to test elements that are left in collection

-> GameWire m (Event (f a)) (Event (f a))

Wire that leaves only non empty collections

Same as filterEG but with monadic action.

filterJustE :: Monad m => GameWire m (Event (Maybe a)) (Event a) Source

Filters only Just events

Shortcut for:

>>> mapE fromJust . filterE isJust

filterJustLE :: (Monad m, Filterable f, FilterConstraint f (Maybe a), Functor f) => GameWire m (Event (f (Maybe a))) (Event (f a)) Source

Filters only Just events in foldable struct

liftGameMonadEvent1 :: Monad m => (a -> GameMonadT m b) -> GameWire m (Event a) (Event b) Source

Lifting game monad action to event processing arrow

Synonym for onEventM from Control.Wire.Core.Unsafe.Event.

changes :: (Monad m, Eq a) => GameWire m a (Event a) Source

Fires when input value changes

Helpers

stateWire :: MonadFix m => b -> GameWire m (a, b) b -> GameWire m a b Source

Loops output of wire to it input, first parameter is start value of state

Common combinator for build game actors.

chainWires :: Monad m => [GameWire m a a] -> GameWire m a a Source

Sequence compose list of wires (right to left order)

dispense :: Monad m => [a] -> GameWire m (Event b) a Source

Infinitely dispense given elements and switches to next item on event.

Note: is not defined on empty list.

Note: not delayed version, new item is returned on same frame when input event occurs.

dDispense :: Monad m => [a] -> GameWire m (Event b) a Source

Infinitely dispense given elements and switches to next item on event.

Note: is not defined on empty list.

Note: delayed version, new item is returned on frame after input event occurs.

Time

deltaTime :: (Fractional b, Monad m) => GameWire m a b Source

Returns delta time scince last frame.