free-game-1.1.80: Create games for free

Copyright(C) 2013 Fumiaki Kinoshita
LicenseBSD-style (see the file LICENSE)
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Stabilityprovisional
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

FreeGame

Contents

Description

 

Synopsis

Game

runGame :: WindowMode -> BoundingBox2 -> Game a -> IO (Maybe a) Source

Game is a kind of procedure but you can also use it like a value. free-game's design is based on free structures, however, you don't have to mind it -- Just apply runGame, and enjoy.

For more examples, see https://github.com/fumieval/free-game/tree/master/examples.

reGame :: (FreeGame m, Monad m) => Game a -> m a Source

Generalize Game to any monad based on FreeGame.

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.

delay :: (Monad f, MonadFree f m) => m a -> m a

Adds an extra layer to a free monad value.

In particular, for the iterative monad Iter, this makes the computation require one more step, without changing its final result.

runIter (delay ma) == Right ma

tick :: (Monad f, MonadFree f m) => m () Source

Delimit the computation to yield a frame.

foreverFrame :: (Monad f, Monad m, MonadTrans t, MonadFree f (t m)) => m a -> t m any Source

foreverFrame :: Frame a -> Game any

untick :: (Monad m, FreeGame m) => IterT Frame a -> m (Either (IterT Frame a) a) Source

Extract the next frame of the action.

untickInfinite :: (Monad m, FreeGame m) => IterT Frame Void -> m (IterT Frame Void) Source

An infinite version of untick.

Frame

type Frame = F UI Source

reFrame :: (FreeGame m, Monad m) => Frame a -> m a Source

Generalize Frame to any monad based on FreeGame.

class (Picture2D m, Local m, Keyboard m, Mouse m, FromFinalizer m) => FreeGame m where Source

Methods

draw :: (forall f. (Applicative f, Monad f, Picture2D f, Local f) => f a) -> m a Source

Draw an action that consist of Picture2D's methods.

preloadBitmap :: Bitmap -> m () Source

Load a Bitmap to avoid the cost of the first invocation of bitmap.

bracket :: Frame a -> m a Source

Run a Frame, and release all the matter happened.

forkFrame :: Frame () -> m () Source

Run a Frame action concurrently. Do not use this function to draw pictures.

takeScreenshot :: m Bitmap Source

Generate a Bitmap from the front buffer.

setFPS :: Double -> m () Source

Set the goal FPS.

setTitle :: String -> m () Source

showCursor :: m () Source

hideCursor :: m () Source

clearColor :: Color -> m () Source

getFPS :: m Int Source

Get the actual FPS value.

getBoundingBox :: m BoundingBox2 Source

setBoundingBox :: BoundingBox2 -> m () Source

Instances

FreeGame UI 
(FreeGame m, Monad m) => FreeGame (IdentityT m) 
(FreeGame m, Functor m) => FreeGame (F m) 
(FreeGame m, Functor m) => FreeGame (Free m) 
(FreeGame m, Monad m) => FreeGame (IterT m) 
(FreeGame m, Monad m) => FreeGame (ListT m) 
(FreeGame m, Monad m) => FreeGame (MaybeT m) 
(FreeGame m, Monad m) => FreeGame (ContT r m) 
(FreeGame m, Monad m) => FreeGame (StateT s m) 
(FreeGame m, Monad m) => FreeGame (StateT s m) 
(FreeGame m, Monad m) => FreeGame (ExceptT e m) 
(FreeGame m, Monad m, Monoid w) => FreeGame (WriterT w m) 
(FreeGame m, Monad m, Monoid w) => FreeGame (WriterT w m) 
(FreeGame m, Monad m, Monoid w) => FreeGame (RWST r w s m) 
(FreeGame m, Monad m, Monoid w) => FreeGame (RWST r w s m) 

Transformations

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

Affine Location 
Affine UI 
(Affine m, Monad m) => Affine (IdentityT m) 
(Affine m, Functor m) => Affine (F m) 
(Affine m, Functor m) => Affine (Free m) 
(Affine m, Monad m) => Affine (IterT m) 
(Affine m, Monad m) => Affine (ListT m) 
(Affine m, Monad m) => Affine (MaybeT m) 
(Affine m, Monad m) => Affine (ContT r m) 
(Affine m, Monad m) => Affine (ReaderT r m) 
(Affine m, Monad m) => Affine (StateT s m) 
(Affine m, Monad m) => Affine (StateT s m) 
(Affine m, Monad m) => Affine (ExceptT e m) 
(Affine m, Monad m, Monoid w) => Affine (WriterT w m) 
(Affine m, Monad m, Monoid w) => Affine (WriterT w m) 
(Affine m, Monad m, Monoid w) => Affine (RWST r w s m) 
(Affine m, Monad m, Monoid w) => Affine (RWST r w s m) 

class Affine p => Local p Source

Minimal complete definition

getLocation

Instances

Local UI 
(Local m, Monad m) => Local (IdentityT m) 
(Local m, Functor m) => Local (F m) 
(Local m, Functor m) => Local (Free m) 
(Local m, Monad m) => Local (IterT m) 
(Local m, Monad m) => Local (ListT m) 
(Local m, Monad m) => Local (MaybeT m) 
(Local m, Monad m) => Local (ContT r m) 
(Local m, Monad m) => Local (ReaderT s m) 
(Local m, Monad m) => Local (StateT s m) 
(Local m, Monad m) => Local (StateT s m) 
(Local m, Monad m) => Local (ExceptT e m) 
(Local m, Monad m, Monoid w) => Local (WriterT w m) 
(Local m, Monad m, Monoid w) => Local (WriterT w m) 
(Local m, Monad m, Monoid w) => Local (RWST r w s m) 
(Local m, Monad m, Monoid w) => Local (RWST r w s m) 

Pictures

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

Picture2D UI 
(Picture2D m, Monad m) => Picture2D (IdentityT m) 
(Picture2D m, Functor m) => Picture2D (F m) 
(Picture2D m, Functor m) => Picture2D (Free m) 
(Picture2D m, Monad m) => Picture2D (IterT m) 
(Picture2D m, Monad m) => Picture2D (ListT m) 
(Picture2D m, Monad m) => Picture2D (MaybeT m) 
(Picture2D m, Monad m) => Picture2D (ContT r m) 
(Picture2D m, Monad m) => Picture2D (ReaderT r m) 
(Picture2D m, Monad m) => Picture2D (StateT s m) 
(Picture2D m, Monad m) => Picture2D (StateT s m) 
(Picture2D m, Monad m) => Picture2D (ExceptT e m) 
(Picture2D m, Monad m, Monoid w) => Picture2D (WriterT w m) 
(Picture2D m, Monad m, Monoid w) => Picture2D (WriterT w m) 
(Picture2D m, Monad m, Monoid w) => Picture2D (RWST r w s m) 
(Picture2D m, Monad m, Monoid w) => Picture2D (RWST r w s m) 

bitmapSize :: Bitmap -> (Int, Int) Source

Get the size of the Bitmap.

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

Load an image file.

cropBitmap Source

Arguments

:: Bitmap

original bitmap

-> (Int, Int)

width and height

-> (Int, Int)

x and y

-> Bitmap

result

Extract a Bitmap from the specified range.

loadBitmaps :: FilePath -> Q [Dec] Source

Load and define all pictures in the specified directory. On base >= 4.6, file paths to actually load will be respect to the directory of the executable. Otherwise it will be based on the current directory.

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.

writeBitmap :: MonadIO m => FilePath -> Bitmap -> m () Source

Save Bitmap into a file.

Text

data Font Source

Font object

text :: (FromFinalizer m, Monad m, Picture2D m) => Font -> Double -> String -> m () Source

Render a String.

Keyboard

class Functor f => Keyboard f where Source

Instances

Keyboard UI 
(Keyboard m, Monad m) => Keyboard (IdentityT m) 
(Keyboard m, Functor m) => Keyboard (F m) 
(Keyboard m, Functor m) => Keyboard (Free m) 
(Keyboard m, Monad m) => Keyboard (IterT m) 
(Keyboard m, Monad m) => Keyboard (ListT m) 
(Keyboard m, Monad m) => Keyboard (MaybeT m) 
(Keyboard m, Monad m) => Keyboard (ContT r m) 
(Keyboard m, Monad m) => Keyboard (ReaderT s m) 
(Keyboard m, Monad m) => Keyboard (StateT s m) 
(Keyboard m, Monad m) => Keyboard (StateT s m) 
(Keyboard m, Monad m) => Keyboard (ExceptT e m) 
(Keyboard m, Monad m, Monoid w) => Keyboard (WriterT w m) 
(Keyboard m, Monad m, Monoid w) => Keyboard (WriterT w m) 
(Keyboard m, Monad m, Monoid w) => Keyboard (RWST r w s m) 
(Keyboard m, Monad m, Monoid w) => Keyboard (RWST r w s m) 

Mouse

class Functor f => Mouse f where Source

Instances

Mouse UI 
(Mouse m, Monad m) => Mouse (IdentityT m) 
(Mouse m, Functor m) => Mouse (F m) 
(Mouse m, Functor m) => Mouse (Free m) 
(Mouse m, Monad m) => Mouse (IterT m) 
(Mouse m, Monad m) => Mouse (ListT m) 
(Mouse m, Monad m) => Mouse (MaybeT m) 
(Mouse m, Monad m) => Mouse (ContT r m) 
(Mouse m, Monad m) => Mouse (ReaderT r m) 
(Mouse m, Monad m) => Mouse (StateT s m) 
(Mouse m, Monad m) => Mouse (StateT s m) 
(Mouse m, Monad m) => Mouse (ExceptT e m) 
(Mouse m, Monad m, Monoid w) => Mouse (WriterT w m) 
(Mouse m, Monad m, Monoid w) => Mouse (WriterT w m) 
(Mouse m, Monad m, Monoid w) => Mouse (RWST r w s m) 
(Mouse m, Monad m, Monoid w) => Mouse (RWST r w s m) 

mousePosition :: (Applicative f, Mouse f, Local f) => f Vec2 Source

Returns the relative coordinate of the cursor.

IO

embedIO :: FromFinalizer m => IO a -> m a Source

liftIO variety for FromFinalizer.

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

Lift a computation from the IO monad.

randomness :: (Random r, FromFinalizer m) => (r, r) -> m r Source

Get a given range of value.

Utility functions

unitV2 :: Floating a => a -> V2 a Source

An unit vector with the specified angle.

angleV2 :: RealFloat a => V2 a -> a Source

An angle of the given vector.

degrees :: Floating a => a -> a Source

Convert radians to degrees.

radians :: Floating a => a -> a Source

Convert degrees to radians.

Reexports

module Data.Color

module Linear

Deprecated

keySpecial :: Keyboard f => Key -> f Bool Source

Deprecated: use keyPress instead