ansi-terminal-game-0.7.2.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 HaskellNone
LanguageHaskell2010

Terminal.Game

Contents

Description

Machinery and utilities for 2D terminal games.

New? Start from Game.

Synopsis

Running

type FPS = Integer Source #

Frames per second.

data Event Source #

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

Constructors

Tick 
KeyPress Char 
Instances
Eq Event Source # 
Instance details

Defined in Terminal.Game.Layer.Object.Interface

Methods

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

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

Show Event Source # 
Instance details

Defined in Terminal.Game.Layer.Object.Interface

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event Source # 
Instance details

Defined in Terminal.Game.Layer.Object.Interface

Associated Types

type Rep Event :: Type -> Type #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

Arbitrary Event Source # 
Instance details

Defined in Terminal.Game.Layer.Object.Interface

Methods

arbitrary :: Gen Event #

shrink :: Event -> [Event] #

Serialize Event Source # 
Instance details

Defined in Terminal.Game.Layer.Object.Interface

Methods

put :: Putter Event #

get :: Get Event #

type Rep Event Source # 
Instance details

Defined in Terminal.Game.Layer.Object.Interface

type Rep Event = D1 (MetaData "Event" "Terminal.Game.Layer.Object.Interface" "ansi-terminal-game-0.7.2.0-FxT1OqzQYj6EKvqhrF47Ct" False) (C1 (MetaCons "Tick" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "KeyPress" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char)))

data Game s Source #

Game definition datatype, parametrised on your gamestate. The two most important elements are the function dealing with logic and the drawing one. Check alone (you can compile it with cabal new-run -f examples alone) to see a simple game in action.

Constructors

Game 

Fields

playGame :: Game s -> IO () Source #

Entry point for the game execution, should be called in main.

You must compile your programs with -threaded; if you do not do this the game will crash at start-up. Just add:

ghc-options:      -threaded

in your .cabal file and you will be fine!

Game logic

Some convenient function dealing with Timers (Timed) and Animations.

Usage of these is not mandatry: Game is parametrised over any state s, you are free to implement game logic as you prefer.

Timers/Animation

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

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.

creaTimerLoop :: a -> a -> Integer -> Timed a #

A looped version of creaTimer.

creaBoolTimerLoop :: Integer -> Timed Bool #

Shorthand for: creaTimerLoop False True i.

Animations

type Animation = Timed Plane Source #

An Animation is a series of timed time-separated Planes.

T/A interface

tick :: Timed a -> Timed a #

Ticks the timer (one step).

ticks :: Integer -> Timed a -> Timed a #

Ticks the timer (multiple steps).

reset :: Timed a -> Timed a #

Resets the timer to its original state.

lapse :: Timed a -> Timed a #

Ticks the timer until isExpired is True.

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).

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

Return a list of all frames plus their duration.

Random numbers

data StdGen #

The StdGen instance of RandomGen has a genRange of at least 30 bits.

The result of repeatedly using next should be at least as statistically robust as the Minimal Standard Random Number Generator described by [System.Random, System.Random]. Until more is known about implementations of split, all we require is that split deliver generators that are (a) not identical and (b) independently robust in the sense just given.

The Show and Read instances of StdGen provide a primitive way to save the state of a random number generator. It is required that read (show g) == g.

In addition, reads may be used to map an arbitrary string (not necessarily one produced by show) onto a value of type StdGen. In general, the Read instance of StdGen has the following properties:

  • It guarantees to succeed on any string.
  • It guarantees to consume only a finite portion of the string.
  • Different argument strings are likely to result in different results.
Instances
Read StdGen 
Instance details

Defined in System.Random

Show StdGen 
Instance details

Defined in System.Random

RandomGen StdGen 
Instance details

Defined in System.Random

Methods

next :: StdGen -> (Int, StdGen) #

genRange :: StdGen -> (Int, Int) #

split :: StdGen -> (StdGen, StdGen) #

getStdGen :: IO StdGen #

Gets the global random number generator.

mkStdGen :: Int -> StdGen #

The function mkStdGen provides an alternative way of producing an initial generator, by mapping an Int into a generator. Again, distinct arguments should be likely to produce distinct generators.

getRandom :: Random a => (a, a) -> StdGen -> (a, StdGen) Source #

Simple pseudo-random generator.

getRandomList :: Random a => (a, a) -> StdGen -> [a] Source #

Returns an infinite list of random values.

class Random a #

With a source of random number supply in hand, the Random class allows the programmer to extract random values of a variety of types.

Minimal complete definition: randomR and random.

Minimal complete definition

randomR, random

Instances
Random Bool 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Bool, Bool) -> g -> (Bool, g) #

random :: RandomGen g => g -> (Bool, g) #

randomRs :: RandomGen g => (Bool, Bool) -> g -> [Bool] #

randoms :: RandomGen g => g -> [Bool] #

randomRIO :: (Bool, Bool) -> IO Bool #

randomIO :: IO Bool #

Random Char 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Char, Char) -> g -> (Char, g) #

random :: RandomGen g => g -> (Char, g) #

randomRs :: RandomGen g => (Char, Char) -> g -> [Char] #

randoms :: RandomGen g => g -> [Char] #

randomRIO :: (Char, Char) -> IO Char #

randomIO :: IO Char #

Random Double 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Double, Double) -> g -> (Double, g) #

random :: RandomGen g => g -> (Double, g) #

randomRs :: RandomGen g => (Double, Double) -> g -> [Double] #

randoms :: RandomGen g => g -> [Double] #

randomRIO :: (Double, Double) -> IO Double #

randomIO :: IO Double #

Random Float 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Float, Float) -> g -> (Float, g) #

random :: RandomGen g => g -> (Float, g) #

randomRs :: RandomGen g => (Float, Float) -> g -> [Float] #

randoms :: RandomGen g => g -> [Float] #

randomRIO :: (Float, Float) -> IO Float #

randomIO :: IO Float #

Random Int 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int, Int) -> g -> (Int, g) #

random :: RandomGen g => g -> (Int, g) #

randomRs :: RandomGen g => (Int, Int) -> g -> [Int] #

randoms :: RandomGen g => g -> [Int] #

randomRIO :: (Int, Int) -> IO Int #

randomIO :: IO Int #

Random Int8 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int8, Int8) -> g -> (Int8, g) #

random :: RandomGen g => g -> (Int8, g) #

randomRs :: RandomGen g => (Int8, Int8) -> g -> [Int8] #

randoms :: RandomGen g => g -> [Int8] #

randomRIO :: (Int8, Int8) -> IO Int8 #

randomIO :: IO Int8 #

Random Int16 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int16, Int16) -> g -> (Int16, g) #

random :: RandomGen g => g -> (Int16, g) #

randomRs :: RandomGen g => (Int16, Int16) -> g -> [Int16] #

randoms :: RandomGen g => g -> [Int16] #

randomRIO :: (Int16, Int16) -> IO Int16 #

randomIO :: IO Int16 #

Random Int32 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int32, Int32) -> g -> (Int32, g) #

random :: RandomGen g => g -> (Int32, g) #

randomRs :: RandomGen g => (Int32, Int32) -> g -> [Int32] #

randoms :: RandomGen g => g -> [Int32] #

randomRIO :: (Int32, Int32) -> IO Int32 #

randomIO :: IO Int32 #

Random Int64 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int64, Int64) -> g -> (Int64, g) #

random :: RandomGen g => g -> (Int64, g) #

randomRs :: RandomGen g => (Int64, Int64) -> g -> [Int64] #

randoms :: RandomGen g => g -> [Int64] #

randomRIO :: (Int64, Int64) -> IO Int64 #

randomIO :: IO Int64 #

Random Integer 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Integer, Integer) -> g -> (Integer, g) #

random :: RandomGen g => g -> (Integer, g) #

randomRs :: RandomGen g => (Integer, Integer) -> g -> [Integer] #

randoms :: RandomGen g => g -> [Integer] #

randomRIO :: (Integer, Integer) -> IO Integer #

randomIO :: IO Integer #

Random Word 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word, Word) -> g -> (Word, g) #

random :: RandomGen g => g -> (Word, g) #

randomRs :: RandomGen g => (Word, Word) -> g -> [Word] #

randoms :: RandomGen g => g -> [Word] #

randomRIO :: (Word, Word) -> IO Word #

randomIO :: IO Word #

Random Word8 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word8, Word8) -> g -> (Word8, g) #

random :: RandomGen g => g -> (Word8, g) #

randomRs :: RandomGen g => (Word8, Word8) -> g -> [Word8] #

randoms :: RandomGen g => g -> [Word8] #

randomRIO :: (Word8, Word8) -> IO Word8 #

randomIO :: IO Word8 #

Random Word16 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word16, Word16) -> g -> (Word16, g) #

random :: RandomGen g => g -> (Word16, g) #

randomRs :: RandomGen g => (Word16, Word16) -> g -> [Word16] #

randoms :: RandomGen g => g -> [Word16] #

randomRIO :: (Word16, Word16) -> IO Word16 #

randomIO :: IO Word16 #

Random Word32 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word32, Word32) -> g -> (Word32, g) #

random :: RandomGen g => g -> (Word32, g) #

randomRs :: RandomGen g => (Word32, Word32) -> g -> [Word32] #

randoms :: RandomGen g => g -> [Word32] #

randomRIO :: (Word32, Word32) -> IO Word32 #

randomIO :: IO Word32 #

Random Word64 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word64, Word64) -> g -> (Word64, g) #

random :: RandomGen g => g -> (Word64, g) #

randomRs :: RandomGen g => (Word64, Word64) -> g -> [Word64] #

randoms :: RandomGen g => g -> [Word64] #

randomRIO :: (Word64, Word64) -> IO Word64 #

randomIO :: IO Word64 #

Random CChar 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CChar, CChar) -> g -> (CChar, g) #

random :: RandomGen g => g -> (CChar, g) #

randomRs :: RandomGen g => (CChar, CChar) -> g -> [CChar] #

randoms :: RandomGen g => g -> [CChar] #

randomRIO :: (CChar, CChar) -> IO CChar #

randomIO :: IO CChar #

Random CSChar 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CSChar, CSChar) -> g -> (CSChar, g) #

random :: RandomGen g => g -> (CSChar, g) #

randomRs :: RandomGen g => (CSChar, CSChar) -> g -> [CSChar] #

randoms :: RandomGen g => g -> [CSChar] #

randomRIO :: (CSChar, CSChar) -> IO CSChar #

randomIO :: IO CSChar #

Random CUChar 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CUChar, CUChar) -> g -> (CUChar, g) #

random :: RandomGen g => g -> (CUChar, g) #

randomRs :: RandomGen g => (CUChar, CUChar) -> g -> [CUChar] #

randoms :: RandomGen g => g -> [CUChar] #

randomRIO :: (CUChar, CUChar) -> IO CUChar #

randomIO :: IO CUChar #

Random CShort 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CShort, CShort) -> g -> (CShort, g) #

random :: RandomGen g => g -> (CShort, g) #

randomRs :: RandomGen g => (CShort, CShort) -> g -> [CShort] #

randoms :: RandomGen g => g -> [CShort] #

randomRIO :: (CShort, CShort) -> IO CShort #

randomIO :: IO CShort #

Random CUShort 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CUShort, CUShort) -> g -> (CUShort, g) #

random :: RandomGen g => g -> (CUShort, g) #

randomRs :: RandomGen g => (CUShort, CUShort) -> g -> [CUShort] #

randoms :: RandomGen g => g -> [CUShort] #

randomRIO :: (CUShort, CUShort) -> IO CUShort #

randomIO :: IO CUShort #

Random CInt 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CInt, CInt) -> g -> (CInt, g) #

random :: RandomGen g => g -> (CInt, g) #

randomRs :: RandomGen g => (CInt, CInt) -> g -> [CInt] #

randoms :: RandomGen g => g -> [CInt] #

randomRIO :: (CInt, CInt) -> IO CInt #

randomIO :: IO CInt #

Random CUInt 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CUInt, CUInt) -> g -> (CUInt, g) #

random :: RandomGen g => g -> (CUInt, g) #

randomRs :: RandomGen g => (CUInt, CUInt) -> g -> [CUInt] #

randoms :: RandomGen g => g -> [CUInt] #

randomRIO :: (CUInt, CUInt) -> IO CUInt #

randomIO :: IO CUInt #

Random CLong 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CLong, CLong) -> g -> (CLong, g) #

random :: RandomGen g => g -> (CLong, g) #

randomRs :: RandomGen g => (CLong, CLong) -> g -> [CLong] #

randoms :: RandomGen g => g -> [CLong] #

randomRIO :: (CLong, CLong) -> IO CLong #

randomIO :: IO CLong #

Random CULong 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CULong, CULong) -> g -> (CULong, g) #

random :: RandomGen g => g -> (CULong, g) #

randomRs :: RandomGen g => (CULong, CULong) -> g -> [CULong] #

randoms :: RandomGen g => g -> [CULong] #

randomRIO :: (CULong, CULong) -> IO CULong #

randomIO :: IO CULong #

Random CLLong 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CLLong, CLLong) -> g -> (CLLong, g) #

random :: RandomGen g => g -> (CLLong, g) #

randomRs :: RandomGen g => (CLLong, CLLong) -> g -> [CLLong] #

randoms :: RandomGen g => g -> [CLLong] #

randomRIO :: (CLLong, CLLong) -> IO CLLong #

randomIO :: IO CLLong #

Random CULLong 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CULLong, CULLong) -> g -> (CULLong, g) #

random :: RandomGen g => g -> (CULLong, g) #

randomRs :: RandomGen g => (CULLong, CULLong) -> g -> [CULLong] #

randoms :: RandomGen g => g -> [CULLong] #

randomRIO :: (CULLong, CULLong) -> IO CULLong #

randomIO :: IO CULLong #

Random CFloat 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CFloat, CFloat) -> g -> (CFloat, g) #

random :: RandomGen g => g -> (CFloat, g) #

randomRs :: RandomGen g => (CFloat, CFloat) -> g -> [CFloat] #

randoms :: RandomGen g => g -> [CFloat] #

randomRIO :: (CFloat, CFloat) -> IO CFloat #

randomIO :: IO CFloat #

Random CDouble 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CDouble, CDouble) -> g -> (CDouble, g) #

random :: RandomGen g => g -> (CDouble, g) #

randomRs :: RandomGen g => (CDouble, CDouble) -> g -> [CDouble] #

randoms :: RandomGen g => g -> [CDouble] #

randomRIO :: (CDouble, CDouble) -> IO CDouble #

randomIO :: IO CDouble #

Random CPtrdiff 
Instance details

Defined in System.Random

Random CSize 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CSize, CSize) -> g -> (CSize, g) #

random :: RandomGen g => g -> (CSize, g) #

randomRs :: RandomGen g => (CSize, CSize) -> g -> [CSize] #

randoms :: RandomGen g => g -> [CSize] #

randomRIO :: (CSize, CSize) -> IO CSize #

randomIO :: IO CSize #

Random CWchar 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CWchar, CWchar) -> g -> (CWchar, g) #

random :: RandomGen g => g -> (CWchar, g) #

randomRs :: RandomGen g => (CWchar, CWchar) -> g -> [CWchar] #

randoms :: RandomGen g => g -> [CWchar] #

randomRIO :: (CWchar, CWchar) -> IO CWchar #

randomIO :: IO CWchar #

Random CSigAtomic 
Instance details

Defined in System.Random

Random CIntPtr 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CIntPtr, CIntPtr) -> g -> (CIntPtr, g) #

random :: RandomGen g => g -> (CIntPtr, g) #

randomRs :: RandomGen g => (CIntPtr, CIntPtr) -> g -> [CIntPtr] #

randoms :: RandomGen g => g -> [CIntPtr] #

randomRIO :: (CIntPtr, CIntPtr) -> IO CIntPtr #

randomIO :: IO CIntPtr #

Random CUIntPtr 
Instance details

Defined in System.Random

Random CIntMax 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CIntMax, CIntMax) -> g -> (CIntMax, g) #

random :: RandomGen g => g -> (CIntMax, g) #

randomRs :: RandomGen g => (CIntMax, CIntMax) -> g -> [CIntMax] #

randoms :: RandomGen g => g -> [CIntMax] #

randomRIO :: (CIntMax, CIntMax) -> IO CIntMax #

randomIO :: IO CIntMax #

Random CUIntMax 
Instance details

Defined in System.Random

Drawing

To get to the gist of drawing, check the documentation for %.

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

type Coords = (Row, Column) Source #

Rows and Columns are 1-based (top-left position is 1 1).

type Width = Integer Source #

Expressed in Columns.

type Height = Integer Source #

Expressed in Rows.

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

Creates an empty, opaque 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.

makeTransparent :: Char -> Plane -> Plane Source #

Adds transparency to a plane, matching a given character

makeOpaque :: Plane -> Plane Source #

Changes every transparent cell in the Plane to an opaque ' ' character.

paperPlane :: Plane -> String Source #

A String (n divided and ended) representing the Plane. Useful for debugging/testing purposes.

planeSize :: Plane -> (Width, Height) Source #

Dimensions or a plane.

Draw

type Draw = Plane -> Plane Source #

A drawing function, usually executed with the help of %.

(%) :: 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.

textBox :: String -> Width -> Height -> Plane Source #

A text-box. Assumes ' ' are transparent.

data Color #

ANSI's eight standard colors. They come in two intensities, which are controlled by ColorIntensity. Many terminals allow the colors of the standard palette to be customised, so that, for example, setSGR [ SetColor Foreground Vivid Green ] may not result in bright green characters.

Constructors

Black 
Red 
Green 
Yellow 
Blue 
Magenta 
Cyan 
White 
Instances
Bounded Color 
Instance details

Defined in System.Console.ANSI.Types

Enum Color 
Instance details

Defined in System.Console.ANSI.Types

Eq Color 
Instance details

Defined in System.Console.ANSI.Types

Methods

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

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

Ord Color 
Instance details

Defined in System.Console.ANSI.Types

Methods

compare :: Color -> Color -> Ordering #

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

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

(>) :: Color -> Color -> Bool #

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

max :: Color -> Color -> Color #

min :: Color -> Color -> Color #

Read Color 
Instance details

Defined in System.Console.ANSI.Types

Show Color 
Instance details

Defined in System.Console.ANSI.Types

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Ix Color 
Instance details

Defined in System.Console.ANSI.Types

data ColorIntensity #

ANSI's standard colors come in two intensities

Constructors

Dull 
Vivid 
Instances
Bounded ColorIntensity 
Instance details

Defined in System.Console.ANSI.Types

Enum ColorIntensity 
Instance details

Defined in System.Console.ANSI.Types

Eq ColorIntensity 
Instance details

Defined in System.Console.ANSI.Types

Ord ColorIntensity 
Instance details

Defined in System.Console.ANSI.Types

Read ColorIntensity 
Instance details

Defined in System.Console.ANSI.Types

Show ColorIntensity 
Instance details

Defined in System.Console.ANSI.Types

Ix ColorIntensity 
Instance details

Defined in System.Console.ANSI.Types

color :: Color -> ColorIntensity -> Plane -> Plane Source #

Set foreground color.

bold :: Plane -> Plane Source #

Apply bold style to Plane.

invert :: Plane -> Plane Source #

Swap foreground and background colours of Plane.

Testing

testGame :: Game s -> [Event] -> s Source #

Tests a game in a pure environment. You can supply the Events yourself or use recordGame to obtain them.

setupGame :: Game s -> [Event] -> Game s Source #

As testGame, but returns Game instead of a bare state. Useful to fast-forward (e.g.: skip menus) before invoking playGame.

recordGame :: Game s -> FilePath -> IO () Source #

Play as in playGame and write the session to file. Useful to produce input for testGame and replayGame. Session will be recorded even if an exception happens while playing.

readRecord :: FilePath -> IO [Event] Source #

Reads a file containing a recorded session.

narrateGame :: Game s -> [Event] -> IO s Source #

Similar to testGame, runs the game given a list of Events. Unlike testGame, the playthrough will be displayed on screen. Useful when a test fails and you want to see how.

See this in action with cabal new-run -f examples alone-playback.

errorPress :: IO a -> IO a Source #

Wraps an IO computation so that any error gets displayed along with a <press any key to quit> prompt. Some terminals shut-down immediately upon program end: errorPress makes it easier to beta-test games on those terminals.

Cross platform

Good practices for cross-compatibility:

  • choose game dimensions of no more than 24 rows and 80 columns. This ensures compatibility with the trickiest terminals (i.e. Win32 console);
  • use ASCII characters only. Again this is for Win32 console compatibility, until this GHC bug gets fixed;
  • employ colour sparingly: as some users will play your game in a light-background terminal and some in a dark one, choose only colours that go well with either (blue, red, etc.);
  • some terminals/multiplexers (i.e. tmux) do not make a distinction between vivid/dull; do not base your game mechanics on that difference.