ansi-terminal-game-0.3.1.0: sdl-like functions for terminal applications, based on ansi-terminal

Copyright© 2017-2019 Francesco Ariis
LicenseGPLv3 (see LICENSE file)
MaintainerFrancesco Ariis <fa-ml@ariis.it>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Terminal.Game

Contents

Description

Machinery and utilities for 2D terminal games.

Before continuing, please read this: to use ansi-terminal-game, you need to compile your programs with -threaded; if you do not do this the program will crash at start-up. Just add:

     ghc-options:      -threaded

in your .cabal file and you will be fine!

Synopsis

Game Loop

type MonadGameIO m = (MonadInput m, MonadTimer m, MonadDisplay m) Source #

type FPS = Integer Source #

Frames per second.

runGame Source #

Arguments

:: MonadGameIO m 
=> s

Initial state of the game.

-> (s -> Event -> s)

Logic function.

-> (s -> Plane)

Draw function.

-> (s -> Bool)

"Should I quit?" function.

-> FPS

Frames per second.

-> m s 

Entry point for the game, should be called in main. The two most important functions are the one dealing with logic and the blitting one. Check alone-in-a-room (you can compiler it with cabal new-build -f examples) to see a simple game in action.

data Event Source #

An Event is a Tick (time passes) or a KeyPress.

Constructors

Tick 
KeyPress Char 

Plane

data Plane Source #

A two-dimensional surface (Row, Column) where to blit stuff.

Instances
Eq Plane Source # 
Instance details

Defined in Terminal.Game.Plane

Methods

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

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

Show Plane Source # 
Instance details

Defined in Terminal.Game.Plane

Methods

showsPrec :: Int -> Plane -> ShowS #

show :: Plane -> String #

showList :: [Plane] -> ShowS #

Generic Plane Source # 
Instance details

Defined in Terminal.Game.Plane

Associated Types

type Rep Plane :: Type -> Type #

Methods

from :: Plane -> Rep Plane x #

to :: Rep Plane x -> Plane #

type Rep Plane Source # 
Instance details

Defined in Terminal.Game.Plane

type Rep Plane

stringPlane :: String -> Plane Source #

Creates Plane from String, good way to import ASCII art/diagrams.

stringPlaneTrans :: Char -> String -> Plane Source #

Same as stringPlane, but with transparent Char.

blankPlane :: Width -> Height -> Plane Source #

Creates an empty, opaque Plane.

Draw

type Draw = Plane -> Plane Source #

(%) :: Coords -> Plane -> Draw infixl 4 Source #

Pastes one Plane onto another. To be used along with & like this:

 d :: Plane
 d =          blankPlane (100, 100) &
     (3, 4) % box '_' (3, 5)        &
     (a, b) % cell 'A' # bold

(#) :: Plane -> Draw -> Plane infixl 8 Source #

Apply style to plane, e.g.

cell 'w' # bold

(&) :: a -> (a -> b) -> b infixl 1 #

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

>>> 5 & (+1) & show
"6"

Since: base-4.8.0.0

mergePlanes :: Plane -> [(Coords, Plane)] -> Plane Source #

Shorthand for sequencing Planes, e.g.

          firstPlane  &
 (3, 4) % secondPlane &
 (1, 9) % thirdPlane

is equal to

 mergePlanes firstPlane [((3,4), secondPlane),
                         ((1,9), thirdPlane)]

cell :: Char -> Plane Source #

A 1x1 cell.

box :: Char -> Width -> Height -> Plane Source #

A box of dimensions w h.

bold :: Plane -> Plane Source #

Apply bold style to Plane.

invert :: Plane -> Plane Source #

Swap foreground and background colours of Plane.

Animations

data Loop #

Number of times to repeat the animation.

Constructors

AlwaysLoop

Loops forever, never expires.

Times Integer ExpBehaviour

Repeats the cycle for a fixed number of times.

Instances
Eq Loop 
Instance details

Defined in Control.Timer.Tick

Methods

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

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

Show Loop 
Instance details

Defined in Control.Timer.Tick

Methods

showsPrec :: Int -> Loop -> ShowS #

show :: Loop -> String #

showList :: [Loop] -> ShowS #

Generic Loop 
Instance details

Defined in Control.Timer.Tick

Associated Types

type Rep Loop :: Type -> Type #

Methods

from :: Loop -> Rep Loop x #

to :: Rep Loop x -> Loop #

type Rep Loop 
Instance details

Defined in Control.Timer.Tick

type Rep Loop = D1 (MetaData "Loop" "Control.Timer.Tick" "timers-tick-0.4.0.0-4YT45JnkKST1JU1nhPkPXb" False) (C1 (MetaCons "AlwaysLoop" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Times" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ExpBehaviour)))

tick :: Timed a -> Timed a #

Ticks the timer (one step).

reset :: Timed a -> Timed a #

Resets the timer to its original state.

getFrames :: Timed a -> [(Integer, a)] #

Return a list of all frames plus their duration.

Timers

data Timed a #

A timed resource is a timer which, at any given moment, points to a specific item (like an animation).

Example:

timer = creaTimedRes (Times 1 Elapse) [(2, "a "), (1, "b "), (2, "c ")]
test t | isExpired t = putStrLn "Fine."
       | otherwise   = do putStr (fetchFrame t)
                          test (tick t)

   -- λ> test timer
   -- a a b c c Fine.
Instances
Functor Timed

Mapping on frames.

Instance details

Defined in Control.Timer.Tick

Methods

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

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

Eq a => Eq (Timed a) 
Instance details

Defined in Control.Timer.Tick

Methods

(==) :: Timed a -> Timed a -> Bool #

(/=) :: Timed a -> Timed a -> Bool #

Show a => Show (Timed a) 
Instance details

Defined in Control.Timer.Tick

Methods

showsPrec :: Int -> Timed a -> ShowS #

show :: Timed a -> String #

showList :: [Timed a] -> ShowS #

Generic (Timed a) 
Instance details

Defined in Control.Timer.Tick

Associated Types

type Rep (Timed a) :: Type -> Type #

Methods

from :: Timed a -> Rep (Timed a) x #

to :: Rep (Timed a) x -> Timed a #

type Rep (Timed a) 
Instance details

Defined in Control.Timer.Tick

data ExpBehaviour #

Expire behaviour.

Constructors

Reach

Expires upon reaching last frame.

Elapse

Expires when last frame is over.

Instances
Eq ExpBehaviour 
Instance details

Defined in Control.Timer.Tick

Show ExpBehaviour 
Instance details

Defined in Control.Timer.Tick

Generic ExpBehaviour 
Instance details

Defined in Control.Timer.Tick

Associated Types

type Rep ExpBehaviour :: Type -> Type #

type Rep ExpBehaviour 
Instance details

Defined in Control.Timer.Tick

type Rep ExpBehaviour = D1 (MetaData "ExpBehaviour" "Control.Timer.Tick" "timers-tick-0.4.0.0-4YT45JnkKST1JU1nhPkPXb" False) (C1 (MetaCons "Reach" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Elapse" PrefixI False) (U1 :: Type -> Type))

creaTimer :: a -> a -> Integer -> Timed a #

A simple off/on timer expiring in fixed number of ticks.

Example:

timer = creaTimer Nothing (Just "Over!") 4
test t | isExpired t = print (fetchFrame t)
       | otherwise   = do print (fetchFrame t)
                          test (tick t)

   -- λ> test timer
   -- Nothing
   -- Nothing
   -- Nothing
   -- Nothing
   -- Just "Over"!

creaBoolTimer :: Integer -> Timed Bool #

Shorthand for: creaTimer False True i.

fetchFrame :: Timed a -> a #

Fetches the current resource of the timer.

isExpired :: Timed a -> Bool #

Checks wheter the timer is expired (an expired timer will not respond to tick).

Utils