call-0.0: The call game engine

Safe HaskellNone
LanguageHaskell2010

Call

Contents

Synopsis

System

class Monad m => MonadObjective m where

Associated Types

data Address e m

type Residence m :: * -> *

Methods

(.-) :: Address e m -> e a -> m a infix 3

Send a message to the pointed one.

new :: Object e (Residence m) -> m (Address e m)

Add an object to the environment.

(.&) :: (MonadObjective m, Stateful s e) => Address e m -> StateT s m a -> m a infix 3

data System s a Source

runSystem :: WindowMode -> BoundingBox2 -> (forall s. System s a) -> IO (Maybe a) Source

runSystemDefault :: (forall s. System s a) -> IO (Maybe a) Source

class (MonadIO m, MonadObjective m) => MonadSystem m where Source

Methods

linkMouse :: Mouse e => Address e m -> m () Source

linkKeyboard :: Keyboard e => Address e m -> m () Source

linkGraphic :: Graphic e => Address e m -> m () Source

linkAudio :: Audio e => Address e m -> m () Source

unlinkMouse :: Address e m -> m () Source

unlinkKeyboard :: Address e m -> m () Source

unlinkGraphic :: Address e m -> m () Source

unlinkAudio :: Address e m -> m () Source

stand :: m () Source

wait :: Double -> m () Source

Instances

Component crafting

class Mouse f where Source

Methods

cursorEvent :: Vec2 -> f () Source

scrollEvent :: Vec2 -> f () Source

mouseButtonEvent :: Int -> Bool -> f () Source

Instances

class Keyboard f where Source

Methods

keyEvent :: Key -> Bool -> f () Source

Instances

class Graphic e where Source

Methods

pullGraphic :: Time -> e (Picture ()) Source

Instances

class Audio e where Source

Methods

pullAudio :: Time -> Int -> e [V2 Float] Source

Instances

Free instances

data PullGraphic a Source

Constructors

PullGraphic !Time (Picture () -> a) 

data PullAudio a Source

Constructors

PullAudio !Time !Int ([V2 Float] -> a) 

data KeyEvent a Source

Constructors

KeyEvent !Key !Bool a 

Concrete types

data Box f a :: (* -> *) -> * -> *

The type of bounding box for arbitrary vector f. The functions for this type assume that f is a "zipping" Applicative.

Constructors

Box (f a) (f a) 

Instances

Monad f => Monad (Box f) 
Functor f => Functor (Box f) 
Applicative f => Applicative (Box f) 
Foldable f => Foldable (Box f) 
Traversable f => Traversable (Box f) 
Eq (f a) => Eq (Box f a) 
Ord (f a) => Ord (Box f a) 
Read (f a) => Read (Box f a) 
Show (f a) => Show (Box f a) 

isInside :: (Applicative f, Foldable f, Ord a) => f a -> Box f a -> Bool

check whether the point is in the box.

newtype Picture a Source

Constructors

Picture 

Fields

runPicture :: forall m. (Applicative m, Monad m, Picture2D m) => m a
 

readBitmap :: MonadIO m => FilePath -> m Bitmap Source

Load an image file.

class Functor p => Affine p where Source

Minimal complete definition

scale, translate

Methods

rotateR :: Double -> p a -> p a infixr 5 Source

(radians)

rotateD :: Double -> p a -> p a infixr 5 Source

(degrees)

scale :: Vec2 -> p a -> p a infixr 5 Source

translate :: Vec2 -> p a -> p a infixr 5 Source

Instances

class Affine p => Picture2D p where Source

The class of types that can be regarded as a kind of picture.

Methods

bitmap :: Bitmap -> p () Source

Construct a Picture2D from a Bitmap.

bitmapOnce :: Bitmap -> p () Source

Same as bitmap, but it does not create a cache.

line :: [Vec2] -> p () Source

polygon :: [Vec2] -> p () Source

polygonOutline :: [Vec2] -> p () Source

circle :: Double -> p () Source

circleOutline :: Double -> p () Source

thickness :: Float -> p a -> p a infixr 5 Source

color :: Color -> p a -> p a infixr 5 Source

blendMode :: BlendMode -> p a -> p a infixr 5 Source

Instances

Given TextureStorage => Picture2D IO 
Picture2D Picture 

newtype Source a Source

Constructors

Source (Time -> a) 

IO

liftIO :: MonadIO m => forall a. IO a -> m a

Lift a computation from the IO monad.

loadBitmapsWith :: ExpQ -> FilePath -> Q [Dec] Source

The type of the given ExpQ must be FilePath -> IO FilePath FIXME: This may cause name duplication if there are multiple non-alphanumeric file names.

Reexports

module Data.Color

module Linear