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

Terminal.Game

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

Instances details
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-1.2.1.0-8cyn8APlr3kKvx3WJLhRu1" '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 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 mandatory: 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

Instances details
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 standard pseudo-random number generator.

Instances

Instances details
Eq StdGen 
Instance details

Defined in System.Random.Internal

Methods

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

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

Show StdGen 
Instance details

Defined in System.Random.Internal

NFData StdGen 
Instance details

Defined in System.Random.Internal

Methods

rnf :: StdGen -> () #

RandomGen StdGen 
Instance details

Defined in System.Random.Internal

getStdGen :: MonadIO m => m StdGen #

Gets the global pseudo-random number generator. Extracts the contents of globalStdGen

Since: random-1.0.0

mkStdGen :: Int -> StdGen #

Constructs a StdGen deterministically.

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 #

The class of types for which random values can be generated. Most instances of Random will produce values that are uniformly distributed on the full range, but for those types without a well-defined "full range" some sensible default subrange will be selected.

Random exists primarily for backwards compatibility with version 1.1 of this library. In new code, use the better specified Uniform and UniformRange instead.

Since: random-1.0.0

Instances

Instances details
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] #

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] #

Random Double

Note - random produces values in the closed range [0,1].

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] #

Random Float

Note - random produces values in the closed range [0,1].

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] #

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] #

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] #

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] #

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] #

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] #

Random Integer

Note - random generates values in the Int range

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] #

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] #

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] #

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] #

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] #

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] #

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] #

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] #

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] #

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] #

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] #

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] #

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] #

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] #

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] #

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] #

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] #

Random CBool 
Instance details

Defined in System.Random

Methods

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

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

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

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

Random CFloat

Note - random produces values in the closed range [0,1].

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] #

Random CDouble

Note - random produces values in the closed range [0,1].

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] #

Random CPtrdiff 
Instance details

Defined in System.Random

Methods

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

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

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

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

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] #

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] #

Random CSigAtomic 
Instance details

Defined in System.Random

Methods

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

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

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

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

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] #

Random CUIntPtr 
Instance details

Defined in System.Random

Methods

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

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

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

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

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] #

Random CUIntMax 
Instance details

Defined in System.Random

Methods

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

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

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

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

(Random a, Random b) => Random (a, b)

Note - randomR treats a and b types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => ((a, b), (a, b)) -> g -> ((a, b), g) #

random :: RandomGen g => g -> ((a, b), g) #

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

randoms :: RandomGen g => g -> [(a, b)] #

(Random a, Random b, Random c) => Random (a, b, c)

Note - randomR treats a, b and c types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => ((a, b, c), (a, b, c)) -> g -> ((a, b, c), g) #

random :: RandomGen g => g -> ((a, b, c), g) #

randomRs :: RandomGen g => ((a, b, c), (a, b, c)) -> g -> [(a, b, c)] #

randoms :: RandomGen g => g -> [(a, b, c)] #

(Random a, Random b, Random c, Random d) => Random (a, b, c, d)

Note - randomR treats a, b, c and d types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => ((a, b, c, d), (a, b, c, d)) -> g -> ((a, b, c, d), g) #

random :: RandomGen g => g -> ((a, b, c, d), g) #

randomRs :: RandomGen g => ((a, b, c, d), (a, b, c, d)) -> g -> [(a, b, c, d)] #

randoms :: RandomGen g => g -> [(a, b, c, d)] #

(Random a, Random b, Random c, Random d, Random e) => Random (a, b, c, d, e)

Note - randomR treats a, b, c, d and e types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => ((a, b, c, d, e), (a, b, c, d, e)) -> g -> ((a, b, c, d, e), g) #

random :: RandomGen g => g -> ((a, b, c, d, e), g) #

randomRs :: RandomGen g => ((a, b, c, d, e), (a, b, c, d, e)) -> g -> [(a, b, c, d, e)] #

randoms :: RandomGen g => g -> [(a, b, c, d, e)] #

(Random a, Random b, Random c, Random d, Random e, Random f) => Random (a, b, c, d, e, f)

Note - randomR treats a, b, c, d, e and f types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => ((a, b, c, d, e, f), (a, b, c, d, e, f)) -> g -> ((a, b, c, d, e, f), g) #

random :: RandomGen g => g -> ((a, b, c, d, e, f), g) #

randomRs :: RandomGen g => ((a, b, c, d, e, f), (a, b, c, d, e, f)) -> g -> [(a, b, c, d, e, f)] #

randoms :: RandomGen g => g -> [(a, b, c, d, e, f)] #

(Random a, Random b, Random c, Random d, Random e, Random f, Random g) => Random (a, b, c, d, e, f, g)

Note - randomR treats a, b, c, d, e, f and g types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g0 => ((a, b, c, d, e, f, g), (a, b, c, d, e, f, g)) -> g0 -> ((a, b, c, d, e, f, g), g0) #

random :: RandomGen g0 => g0 -> ((a, b, c, d, e, f, g), g0) #

randomRs :: RandomGen g0 => ((a, b, c, d, e, f, g), (a, b, c, d, e, f, g)) -> g0 -> [(a, b, c, d, e, f, g)] #

randoms :: RandomGen g0 => g0 -> [(a, b, c, d, e, f, g)] #

Drawing

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

Blitting on screen is double-buffered and diff'd (at each frame, only cells with changed character will be redrawn).

Plane

data Plane Source #

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

Instances

Instances details
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 Row = Int Source #

type Width = Int Source #

Expressed in Columns.

type Height = Int 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.

planePaper :: 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

(&) :: 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

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

Apply style to plane, e.g.

cell 'w' # bold

subPlane :: Plane -> Coords -> Coords -> Plane Source #

Cut out a plane by top-left and bottom-right coordinates.

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 1×1 Plane.

word :: String -> Plane Source #

1xn Plane with a word in it. If you need to import multiline ASCII art, check stringPlane and stringPlaneTrans.

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

A box of dimensions w h.

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

Instances details
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

Instances details
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.

Text boxes

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

A text-box. Assumes ' 's are transparent.

textBoxLiquid :: Width -> String -> Plane Source #

Like textBox, but tall enough to fit String.

textBoxHyphen :: Hyphenator -> Width -> Height -> String -> Plane Source #

As textBox, but hypenated. Example:

Rimasi un po’ a meditare nel buio       Rimasi un po’ a meditare nel buio
velato appena dal barlume azzurrino     velato appena dal barlume azzurrino
del fornello a gas, su cui sobbol-      del fornello a gas, su cui
liva quieta la pentola.                 sobbolliva quieta la pentola.

Notice how in the left box «sobbolliva» is broken in two. This can be useful and aesthetically pleasing when textboxes are narrow.

data Hyphenator #

A Hyphenator is combination of an alphabet normalization scheme, a set of Patterns, a set of Exceptions to those patterns and a number of characters at each end to skip hyphenating.

Eurocentric convenience reexports. Check Text.Hyphenation.Language for more languages.

english_GB :: Hyphenator #

>>> hyphenate english_GB "supercalifragilisticexpialadocious"
["su","per","cal","i","fra","gil","istic","ex","pi","alado","cious"]

favors UK hyphenation

english_US :: Hyphenator #

>>> hyphenate english_US "supercalifragilisticexpialadocious"
["su","per","cal","ifrag","ilis","tic","ex","pi","al","ado","cious"]

favors US hyphenation

esperanto :: Hyphenator #

Hyphenators for a wide array of languages.

french :: Hyphenator #

>>> hyphenate french "anticonstitutionnellement"
["an","ti","cons","ti","tu","tion","nel","le","ment"]

german_1996 :: Hyphenator #

Hyphenators for a wide array of languages.

italian :: Hyphenator #

Hyphenators for a wide array of languages.

spanish :: Hyphenator #

Hyphenators for a wide array of languages.

Declarative drawing

(|||) :: Plane -> Plane -> Plane infixl 6 Source #

Place two Planes side-by-side, horizontally.

(===) :: Plane -> Plane -> Plane infixl 6 Source #

Place two Planes side-by-side, vertically.

(***) :: Plane -> Plane -> Plane infixl 6 Source #

a *** b blits b in the centre of a.

hcat :: [Plane] -> Plane Source #

Place a list of Planes side-by-side, horizontally.

vcat :: [Plane] -> Plane Source #

Place a list of Planes side-by-side, vertically.

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 run -f examples alone-playback.

playGameS :: Game s -> IO s Source #

As playGame, but do not discard state.

Utility

displaySize :: IO (Width, Height) Source #

Usable terminal display size (on Win32 console the last line is set aside for input).

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; adding errorPress to playGame 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.