ansi-terminal-game-1.9.3.0: cross-platform library for terminal games
Copyright© 2017-2023 Francesco Ariis et al.
LicenseGPLv3 (see COPYING)
MaintainerFrancesco Ariis <fa-ml@ariis.it>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Terminal.Game

Description

Machinery and utilities for 2D terminal games.

New? Start from Game.

Synopsis

Running

type TPS = Integer Source #

The number of Ticks fed each second to the logic function; constant on every machine. Frames per second might be lower (depending on drawing function onerousness, terminal refresh rate, etc.).

type FPS = Integer Source #

The number of frames blit to terminal per second. Frames might be dropped, but game speed will remain constant. Check balls (cabal run -f examples balls) to see how to display FPS. For obvious reasons (blits would be wasted) max FPS = TPS.

data Event Source #

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

Note that all Keypresses are recorded and fed to your game-logic function. This means you will not lose a single character, no matter how fast your player is at typing or how low you set FPS to be.

Example: in a game where you are controlling a hot-air baloon and have direction and position variables, you most likely want direction to change at every KeyPress, while having position only change at Ticks.

Constructors

Tick 
KeyPress Char 

Instances

Instances details
Arbitrary Event Source # 
Instance details

Defined in Terminal.Game.Layer.Object.Primitive

Methods

arbitrary :: Gen Event #

shrink :: Event -> [Event] #

Generic Event Source # 
Instance details

Defined in Terminal.Game.Layer.Object.Primitive

Associated Types

type Rep Event :: Type -> Type #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

Show Event Source # 
Instance details

Defined in Terminal.Game.Layer.Object.Primitive

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Serialize Event Source # 
Instance details

Defined in Terminal.Game.Layer.Object.Primitive

Methods

put :: Putter Event #

get :: Get Event #

Eq Event Source # 
Instance details

Defined in Terminal.Game.Layer.Object.Primitive

Methods

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

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

type Rep Event Source # 
Instance details

Defined in Terminal.Game.Layer.Object.Primitive

type Rep Event = D1 ('MetaData "Event" "Terminal.Game.Layer.Object.Primitive" "ansi-terminal-game-1.9.3.0-3qdozKVVk7c6jqzxkAevSZ" '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 GEnv Source #

Game environment with current terminal dimensions and current display rate.

Constructors

GEnv 

Fields

Instances

Instances details
Show GEnv Source # 
Instance details

Defined in Terminal.Game.Layer.Object.Primitive

Methods

showsPrec :: Int -> GEnv -> ShowS #

show :: GEnv -> String #

showList :: [GEnv] -> ShowS #

Eq GEnv Source # 
Instance details

Defined in Terminal.Game.Layer.Object.Primitive

Methods

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

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

data Game s r Source #

Game definition datatype, parametrised on:

  • your gamestate s; and
  • a result when the game is finished r. Simple games do not need this, just fill r with ().

The two most important elements are the function dealing with logic and the drawing one. Check alone demo (cabal run -f examples alone) to see a basic game in action.

Constructors

Game 

Fields

  • gTPS :: TPS

    Game speed in ticks per second. You do not need high values, since the 2D canvas is coarse (e.g. 13 TPS is enough for action games).

  • gInitState :: s

    Initial state of the game.

  • gLogicFunction :: GEnv -> s -> Event -> Either r s

    Logic function. If gLogicFunction returns Right s the game will continue with state s; if it returns Left the game is over (quit condition).

    Curious to see how r can be useful? Check cabal run -f examples balls and example/MainBalls.hs.

  • gDrawFunction :: GEnv -> s -> Plane

    Draw function. Just want to blit your game in the middle? Check centerFull.

playGame :: Game s r -> IO r 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!

Helpers

playGame_ :: Game s r -> IO () Source #

As playGame, but ignore the result r.

displaySize :: IO Dimensions Source #

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

assertTermDims :: Width -> Height -> IO () Source #

Check if terminal can accomodate Dimensions, otherwise throws DisplayTooSmall with a helpful message for the player.

errorPress :: IO a -> IO a Source #

Wraps an IO computation so that any ATGException or 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.

blankPlaneFull :: GEnv -> Plane Source #

A blank plane as big as the terminal.

centerFull :: GEnv -> Plane -> Plane Source #

Blits plane in the middle of terminal.

  draw :: GEnv -> MyState -> Plane
  draw ev s =
      centerFull ev $
        ⁝

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/Animations

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 #

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 #

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 #

Eq a => Eq (Timed a) 
Instance details

Defined in Control.Timer.Tick

Methods

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

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

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

Random numbers

data StdGen #

The standard pseudo-random number generator.

Instances

Instances details
Show StdGen 
Instance details

Defined in System.Random.Internal

NFData StdGen 
Instance details

Defined in System.Random.Internal

Methods

rnf :: StdGen -> () #

Eq StdGen 
Instance details

Defined in System.Random.Internal

Methods

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

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

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 :: UniformRange a => (a, a) -> StdGen -> (a, StdGen) Source #

Simple, pure pseudo-random generator.

pickRandom :: [a] -> StdGen -> (a, StdGen) Source #

Picks at random from list.

class UniformRange a #

The class of types for which a uniformly distributed value can be drawn from a range.

Since: random-1.2.0

Minimal complete definition

uniformRM

Instances

Instances details
UniformRange CBool 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CBool, CBool) -> g -> m CBool #

UniformRange CChar 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CChar, CChar) -> g -> m CChar #

UniformRange CDouble

See Floating point number caveats.

Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CDouble, CDouble) -> g -> m CDouble #

UniformRange CFloat

See Floating point number caveats.

Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CFloat, CFloat) -> g -> m CFloat #

UniformRange CInt 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CInt, CInt) -> g -> m CInt #

UniformRange CIntMax 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CIntMax, CIntMax) -> g -> m CIntMax #

UniformRange CIntPtr 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CIntPtr, CIntPtr) -> g -> m CIntPtr #

UniformRange CLLong 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CLLong, CLLong) -> g -> m CLLong #

UniformRange CLong 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CLong, CLong) -> g -> m CLong #

UniformRange CPtrdiff 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CPtrdiff, CPtrdiff) -> g -> m CPtrdiff #

UniformRange CSChar 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CSChar, CSChar) -> g -> m CSChar #

UniformRange CShort 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CShort, CShort) -> g -> m CShort #

UniformRange CSigAtomic 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CSigAtomic, CSigAtomic) -> g -> m CSigAtomic #

UniformRange CSize 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CSize, CSize) -> g -> m CSize #

UniformRange CUChar 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CUChar, CUChar) -> g -> m CUChar #

UniformRange CUInt 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CUInt, CUInt) -> g -> m CUInt #

UniformRange CUIntMax 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CUIntMax, CUIntMax) -> g -> m CUIntMax #

UniformRange CUIntPtr 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CUIntPtr, CUIntPtr) -> g -> m CUIntPtr #

UniformRange CULLong 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CULLong, CULLong) -> g -> m CULLong #

UniformRange CULong 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CULong, CULong) -> g -> m CULong #

UniformRange CUShort 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CUShort, CUShort) -> g -> m CUShort #

UniformRange CWchar 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CWchar, CWchar) -> g -> m CWchar #

UniformRange Int16 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int16, Int16) -> g -> m Int16 #

UniformRange Int32 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int32, Int32) -> g -> m Int32 #

UniformRange Int64 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int64, Int64) -> g -> m Int64 #

UniformRange Int8 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int8, Int8) -> g -> m Int8 #

UniformRange Word16 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word16, Word16) -> g -> m Word16 #

UniformRange Word32 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word32, Word32) -> g -> m Word32 #

UniformRange Word64 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word64, Word64) -> g -> m Word64 #

UniformRange Word8 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word8, Word8) -> g -> m Word8 #

UniformRange Integer 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Integer, Integer) -> g -> m Integer #

UniformRange Natural 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Natural, Natural) -> g -> m Natural #

UniformRange () 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => ((), ()) -> g -> m () #

UniformRange Bool 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Bool, Bool) -> g -> m Bool #

UniformRange Char 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Char, Char) -> g -> m Char #

UniformRange Double

See Floating point number caveats.

Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Double, Double) -> g -> m Double #

UniformRange Float

See Floating point number caveats.

Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Float, Float) -> g -> m Float #

UniformRange Int 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int, Int) -> g -> m Int #

UniformRange Word 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word, Word) -> g -> m Word #

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

Show Plane Source # 
Instance details

Defined in Terminal.Game.Plane

Methods

showsPrec :: Int -> Plane -> ShowS #

show :: Plane -> String #

showList :: [Plane] -> ShowS #

Eq Plane Source # 
Instance details

Defined in Terminal.Game.Plane

Methods

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

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

type Rep Plane Source # 
Instance details

Defined in Terminal.Game.Plane

type Rep Plane

type Dimensions = (Width, Height) Source #

Size of a surface in Rows and Columns.

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. Returns a 1×1 transparent plane on empty string.

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

Same as stringPlane, but with transparent Char. Returns a 1×1 transparent plane on empty string.

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 -> Dimensions 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. Returns a 1×1 transparent plane when r1>r2 or c1>c2.

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

Ix Color 
Instance details

Defined in System.Console.ANSI.Types

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 #

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 #

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

Ix 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

Eq ColorIntensity 
Instance details

Defined in System.Console.ANSI.Types

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

Alternative origins

Placing a plane is sometimes more convenient if the coordinates origin is a corner other than top-left (e.g. “Paste this plane one row from bottom-left corner”). These combinators — meant to be used instead of % — allow you to do so. Example:

prova :: Plane
prova = let rect = box 6 3  '.'
            letters = word "ab"
        in            rect &
           (1, 1) %.> letters         -- start from bottom-right

    -- λ> putStr (planePaper prova)
    -- ......
    -- ......
    -- ....ab

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

Pastes a plane onto another (origin: top-right).

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

Pastes a plane onto another (origin: bottom-left).

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

Pastes a plane onto another (origin: bottom-right).

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:

(normal textbox)                        (hyphenated textbox)
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              del fornello a gas, su cui sobbol-
sobbolliva quieta la pentola.           liva quieta la pentola.

Notice how in the right 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. Returns a 1×1 transparent plane on empty list.

vcat :: [Plane] -> Plane Source #

Place a list of Planes side-by-side, vertically. Returns a 1×1 transparent plane on empty list.

Non-standard colors

Non-standard RGB and xterm colors. These are prettier, but work on a minority of terminal emulators/multiplexers. Use them only on your machine or when you are sure of the terminal you are targetting.

data Colour a #

This type represents the human preception of colour. The a parameter is a numeric type used internally for the representation.

The Monoid instance allows one to add colours, but beware that adding colours can take you out of gamut. Consider using blend whenever possible.

Instances

Instances details
AffineSpace Colour 
Instance details

Defined in Data.Colour.Internal

Methods

affineCombo :: Num a => [(a, Colour a)] -> Colour a -> Colour a #

ColourOps Colour 
Instance details

Defined in Data.Colour.Internal

Methods

over :: Num a => AlphaColour a -> Colour a -> Colour a #

darken :: Num a => a -> Colour a -> Colour a #

Num a => Monoid (Colour a) 
Instance details

Defined in Data.Colour.Internal

Methods

mempty :: Colour a #

mappend :: Colour a -> Colour a -> Colour a #

mconcat :: [Colour a] -> Colour a #

Num a => Semigroup (Colour a) 
Instance details

Defined in Data.Colour.Internal

Methods

(<>) :: Colour a -> Colour a -> Colour a #

sconcat :: NonEmpty (Colour a) -> Colour a #

stimes :: Integral b => b -> Colour a -> Colour a #

Eq a => Eq (Colour a) 
Instance details

Defined in Data.Colour.Internal

Methods

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

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

rgbColor :: Colour Float -> Plane -> Plane Source #

Set RGB color

paletteColor :: Word8 -> Plane -> Plane Source #

Set Palette color

sRGB24 :: (Ord b, Floating b) => Word8 -> Word8 -> Word8 -> Colour b #

Construct a colour from a 24-bit (three 8-bit words) sRGB specification.

sRGBBounded :: (Ord b, Floating b, Integral a, Bounded a) => a -> a -> a -> Colour b #

Construct a colour from an sRGB specification. Input components are expected to be in the range [0..maxBound].

sRGB :: (Ord b, Floating b) => b -> b -> b -> Colour b #

Construct a colour from an sRGB specification. Input components are expected to be in the range [0..1].

sRGB24read :: (Ord b, Floating b) => String -> Colour b #

Read a colour in hexadecimal form, e.g. "#00aaff" or "00aaff"

xterm6LevelRGB :: Int -> Int -> Int -> Word8 #

Given xterm's standard protocol for a 256-color palette, returns the index to that part of the palette which is a 6 level (6x6x6) color cube of 216 RGB colors. Throws an error if any of the red, green or blue channels is outside the range 0 to 5. An example of use is:

>>> setSGR [ SetPaletteColor $ xterm6LevelRGB 5 2 0 ] -- Dark Orange

Since: ansi-terminal-types-0.9

xterm24LevelGray :: Int -> Word8 #

Given xterm's standard protocol for a 256-color palette, returns the index to that part of the palette which is a spectrum of 24 grays, from dark gray (0) to near white (23) (black and white are themselves excluded). Throws an error if the gray is outside of the range 0 to 23. An example of use is:

>>> setSGR [ SetPaletteColor $ xterm24LevelGray 12 ] -- Gray50

Since: ansi-terminal-types-0.9

xtermSystem :: ColorIntensity -> Color -> Word8 #

Given xterm's standard protocol for a 256-color palette, returns the index to that part of the palette which corresponds to the 'ANSI' standards' 16 standard, or 'system', colors (eight colors in two intensities). An example of use is:

>>> setSGR [ SetPaletteColor $ xtermSystem Vivid Green ]

Since: ansi-terminal-types-0.9

Testing

data GRec Source #

Opaque data type with recorded game input, for testing purposes.

Instances

Instances details
Generic GRec Source # 
Instance details

Defined in Terminal.Game.Layer.Object.Primitive

Associated Types

type Rep GRec :: Type -> Type #

Methods

from :: GRec -> Rep GRec x #

to :: Rep GRec x -> GRec #

Show GRec Source # 
Instance details

Defined in Terminal.Game.Layer.Object.Primitive

Methods

showsPrec :: Int -> GRec -> ShowS #

show :: GRec -> String #

showList :: [GRec] -> ShowS #

Serialize GRec Source # 
Instance details

Defined in Terminal.Game.Layer.Object.Primitive

Methods

put :: Putter GRec #

get :: Get GRec #

Eq GRec Source # 
Instance details

Defined in Terminal.Game.Layer.Object.Primitive

Methods

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

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

type Rep GRec Source # 
Instance details

Defined in Terminal.Game.Layer.Object.Primitive

type Rep GRec = D1 ('MetaData "GRec" "Terminal.Game.Layer.Object.Primitive" "ansi-terminal-game-1.9.3.0-3qdozKVVk7c6jqzxkAevSZ" 'False) (C1 ('MetaCons "GRec" 'PrefixI 'True) (S1 ('MetaSel ('Just "aPolled") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq [Event])) :*: S1 ('MetaSel ('Just "aTermSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq (Maybe Dimensions)))))

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

Play as in playGame and write the session (input stream, etc.) to file. Then you can use this with testGame and narrateGame. Session will be recorded even if an exception happens while playing.

readRecord :: FilePath -> IO GRec Source #

Reads a file containing a recorded session. Throws MalformedGRec on failure.

testGame :: Game s r -> GRec -> Either r s Source #

Tests a game in a pure environment. Aims to accurately emulate GEnv changes (screen size, FPS) too. Returns a result r or a state s in case the Event stream is exhausted before the game exits.

A useful trick is to call recordGame and press Ctrl-C while playing (instead of quitting properly). This way testGame will return Left s, a state that you can then inspect.

setupGame :: Game s r -> GRec -> Game s r Source #

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

narrateGame :: Game s r -> GRec -> IO () Source #

Similar to testGame, runs the game given a GRec. 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.

Notice that GEnv will be provided at run-time, and not record-time; this can make emulation slightly inaccurate if — e.g. — you replay the game on a smaller terminal than the one you recorded the session on.

A quick and dirty way to have hot reload (autorestarting your game when source files change) is illustrated in example/MainHotReload.hs.

Embedding files

Embedding files is convenient when working on assets separately and still wanting to ship a single binary. Remember to add this pragma to the top of your module:

{-# LANGUAGE TemplateHaskell #-}

embedFile :: FilePath -> Q Exp #

Embed a single file in your source code.

import qualified Data.ByteString

myFile :: Data.ByteString.ByteString
myFile = $(embedFile "dirName/fileName")

embedDir :: FilePath -> Q Exp #

Embed a directory recursively in your source code.

import qualified Data.ByteString

myDir :: [(FilePath, Data.ByteString.ByteString)]
myDir = $(embedDir "dirName")

data ByteString #

A space-efficient representation of a Word8 vector, supporting many efficient operations.

A ByteString contains 8-bit bytes, or by using the operations from Data.ByteString.Char8 it can be interpreted as containing 8-bit characters.

Instances

Instances details
Data ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteString -> c ByteString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteString #

toConstr :: ByteString -> Constr #

dataTypeOf :: ByteString -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ByteString) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteString) #

gmapT :: (forall b. Data b => b -> b) -> ByteString -> ByteString #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r #

gmapQ :: (forall d. Data d => d -> u) -> ByteString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

IsString ByteString

Beware: fromString truncates multi-byte characters to octets. e.g. "枯朶に烏のとまりけり秋の暮" becomes �6k�nh~�Q��n�

Instance details

Defined in Data.ByteString.Internal.Type

Monoid ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Semigroup ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

IsList ByteString

Since: bytestring-0.10.12.0

Instance details

Defined in Data.ByteString.Internal.Type

Associated Types

type Item ByteString #

Read ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Show ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Serialize ByteString 
Instance details

Defined in Data.Serialize

NFData ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Methods

rnf :: ByteString -> () #

Eq ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Ord ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Hashable ByteString 
Instance details

Defined in Data.Hashable.Class

Lift ByteString

Since: bytestring-0.11.2.0

Instance details

Defined in Data.ByteString.Internal.Type

Methods

lift :: Quote m => ByteString -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => ByteString -> Code m ByteString #

type Item ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

unpack :: ByteString -> [Char] #

O(n) Converts a ByteString to a String.

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, others do not display bold; do not base your game mechanics on that difference.
  • If you use WASD for movement, you can readily gain compatibility with AZERTY keyboard layout by mapping “up” to both W and Z and “left” to A and Q. Users from France, Belgium, and Québec will thank you.