Copyright | © 2017-2019 Francesco Ariis |
---|---|
License | GPLv3 (see LICENSE file) |
Maintainer | Francesco Ariis <fa-ml@ariis.it> |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Terminal.Game
Description
Machinery and utilities for 2D terminal games.
New? Start from Game
.
Synopsis
- type TPS = Integer
- data Event
- data Game s = Game {
- gScreenWidth :: Width
- gScreenHeight :: Height
- gTPS :: TPS
- gInitState :: s
- gLogicFunction :: s -> Event -> s
- gDrawFunction :: s -> Plane
- gQuitFunction :: s -> Bool
- playGame :: Game s -> IO ()
- data Timed a
- creaTimer :: a -> a -> Integer -> Timed a
- creaBoolTimer :: Integer -> Timed Bool
- creaTimerLoop :: a -> a -> Integer -> Timed a
- creaBoolTimerLoop :: Integer -> Timed Bool
- type Animation = Timed Plane
- creaAnimation :: [(Integer, Plane)] -> Animation
- creaLoopAnimation :: [(Integer, Plane)] -> Animation
- creaStaticAnimation :: Plane -> Animation
- tick :: Timed a -> Timed a
- ticks :: Integer -> Timed a -> Timed a
- reset :: Timed a -> Timed a
- lapse :: Timed a -> Timed a
- fetchFrame :: Timed a -> a
- isExpired :: Timed a -> Bool
- getFrames :: Timed a -> [(Integer, a)]
- data StdGen
- getStdGen :: MonadIO m => m StdGen
- mkStdGen :: Int -> StdGen
- getRandom :: Random a => (a, a) -> StdGen -> (a, StdGen)
- getRandomList :: Random a => (a, a) -> StdGen -> [a]
- class Random a
- data Plane
- type Coords = (Row, Column)
- type Row = Int
- type Column = Int
- type Width = Int
- type Height = Int
- blankPlane :: Width -> Height -> Plane
- stringPlane :: String -> Plane
- stringPlaneTrans :: Char -> String -> Plane
- makeTransparent :: Char -> Plane -> Plane
- makeOpaque :: Plane -> Plane
- planePaper :: Plane -> String
- planeSize :: Plane -> (Width, Height)
- type Draw = Plane -> Plane
- (%) :: Coords -> Plane -> Draw
- (&) :: a -> (a -> b) -> b
- (#) :: Plane -> Draw -> Plane
- subPlane :: Plane -> Coords -> Coords -> Plane
- mergePlanes :: Plane -> [(Coords, Plane)] -> Plane
- cell :: Char -> Plane
- word :: String -> Plane
- box :: Width -> Height -> Char -> Plane
- data Color
- data ColorIntensity
- color :: Color -> ColorIntensity -> Plane -> Plane
- bold :: Plane -> Plane
- invert :: Plane -> Plane
- (%^>) :: Coords -> Plane -> Draw
- (%.<) :: Coords -> Plane -> Draw
- (%.>) :: Coords -> Plane -> Draw
- textBox :: Width -> Height -> String -> Plane
- textBoxLiquid :: Width -> String -> Plane
- textBoxHyphen :: Hyphenator -> Width -> Height -> String -> Plane
- textBoxHyphenLiquid :: Hyphenator -> Width -> String -> Plane
- data Hyphenator
- english_GB :: Hyphenator
- english_US :: Hyphenator
- esperanto :: Hyphenator
- french :: Hyphenator
- german_1996 :: Hyphenator
- italian :: Hyphenator
- spanish :: Hyphenator
- (|||) :: Plane -> Plane -> Plane
- (===) :: Plane -> Plane -> Plane
- (***) :: Plane -> Plane -> Plane
- hcat :: [Plane] -> Plane
- vcat :: [Plane] -> Plane
- testGame :: Game s -> [Event] -> s
- setupGame :: Game s -> [Event] -> Game s
- recordGame :: Game s -> FilePath -> IO ()
- readRecord :: FilePath -> IO [Event]
- narrateGame :: Game s -> [Event] -> IO s
- playGameS :: Game s -> IO s
- displaySize :: IO (Width, Height)
- errorPress :: IO a -> IO a
- data ATGException
Running
The number of Tick
s 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.).
Instances
Arbitrary Event Source # | |
Generic Event Source # | |
Show Event Source # | |
Serialize Event Source # | |
Eq Event Source # | |
type Rep Event Source # | |
Defined in Terminal.Game.Layer.Object.Interface type Rep Event = D1 ('MetaData "Event" "Terminal.Game.Layer.Object.Interface" "ansi-terminal-game-1.4.0.0-66S5RkcyDOb292TA6FSLkR" 'False) (C1 ('MetaCons "Tick" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyPress" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char))) |
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!
Throws DisplayTooSmall
if game widht/height cannot be accomodated
by terminal.
Game logic
Some convenient function dealing with
Timers (Timed
) and Animation
s.
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
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
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"!
creaTimerLoop :: a -> a -> Integer -> Timed a #
A looped version of creaTimer
.
creaBoolTimerLoop :: Integer -> Timed Bool #
Shorthand for:
.creaTimerLoop
False True i
Animations
T/A interface
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
The standard pseudo-random number generator.
Instances
Show StdGen | |
NFData StdGen | |
Defined in System.Random.Internal | |
Eq StdGen | |
RandomGen StdGen | |
Defined in System.Random.Internal Methods next :: StdGen -> (Int, StdGen) # genWord8 :: StdGen -> (Word8, StdGen) # genWord16 :: StdGen -> (Word16, StdGen) # genWord32 :: StdGen -> (Word32, StdGen) # genWord64 :: StdGen -> (Word64, StdGen) # genWord32R :: Word32 -> StdGen -> (Word32, StdGen) # genWord64R :: Word64 -> StdGen -> (Word64, StdGen) # genShortByteString :: Int -> StdGen -> (ShortByteString, StdGen) # |
getStdGen :: MonadIO m => m StdGen #
Gets the global pseudo-random number generator. Extracts the contents of
globalStdGen
Since: random-1.0.0
getRandomList :: Random a => (a, a) -> StdGen -> [a] Source #
Returns an infinite list of random values.
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
Random CBool | |
Random CChar | |
Random CDouble | Note - |
Random CFloat | Note - |
Random CInt | |
Random CIntMax | |
Random CIntPtr | |
Random CLLong | |
Random CLong | |
Random CPtrdiff | |
Random CSChar | |
Random CShort | |
Random CSigAtomic | |
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 CSize | |
Random CUChar | |
Random CUInt | |
Random CUIntMax | |
Random CUIntPtr | |
Random CULLong | |
Random CULong | |
Random CUShort | |
Random CWchar | |
Random Int16 | |
Random Int32 | |
Random Int64 | |
Random Int8 | |
Random Word16 | |
Random Word32 | |
Random Word64 | |
Random Word8 | |
Random Integer | |
Random Bool | |
Random Char | |
Random Double | Note - |
Random Float | Note - |
Random Int | |
Random Word | |
(Random a, Random b) => Random (a, b) | Note - |
(Random a, Random b, Random c) => Random (a, b, c) | Note - |
(Random a, Random b, Random c, Random d) => Random (a, b, c, d) | Note - |
(Random a, Random b, Random c, Random d, Random e) => Random (a, b, c, d, e) | Note - |
Defined in System.Random | |
(Random a, Random b, Random c, Random d, Random e, Random f) => Random (a, b, c, d, e, f) | Note - |
(Random a, Random b, Random c, Random d, Random e, Random f, Random g) => Random (a, b, c, d, e, f, g) | Note - |
Defined in System.Random |
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
A two-dimensional surface (Row, Column) where to blit stuff.
stringPlane :: String -> Plane Source #
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.
Draw
subPlane :: Plane -> Coords -> Coords -> Plane Source #
Cut out a plane by top-left and bottom-right coordinates.
word :: String -> Plane Source #
1xn
Plane
with a word in it. If you need to import multiline
ASCII art, check stringPlane
and stringPlaneTrans
.
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.
data ColorIntensity #
ANSI's standard colors come in two intensities
Instances
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: bottom-left).
(%.>) :: Coords -> Plane -> Draw infixl 4 Source #
Pastes a plane onto another (origin: bottom-right).
Text boxes
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.
textBoxHyphenLiquid :: Hyphenator -> Width -> String -> Plane Source #
As textBoxLiquid
, but hypenated.
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.
>>>
hyphenate english_GB "supercalifragilisticexpialadocious"
["su","per","cal","i","fra","gil","istic","ex","pi","alado","cious"]
favors UK hyphenation
>>>
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"]
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
Testing
testGame :: Game s -> [Event] -> s Source #
Tests a game in a pure environment. You can
supply the Event
s yourself or use recordGame
to obtain them.
recordGame :: Game s -> FilePath -> IO () Source #
Play as in playGame
and write the session to file
. Useful to
produce input for testGame
and narrateGame
. Session will be
recorded even if an exception happens while playing.
Utility
displaySize :: IO (Width, Height) Source #
Usable terminal display size (on Win32 console the last line is
set aside for input). Throws CannotGetDisplaySize
on error.
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.
data ATGException Source #
ATGException
s are thrown synchronously for easier catching.
Constructors
CannotGetDisplaySize | |
DisplayTooSmall Coords Coords | Required size and actual size. |
Instances
Exception ATGException Source # | |
Defined in Terminal.Game.Layer.Object.Interface Methods toException :: ATGException -> SomeException # fromException :: SomeException -> Maybe ATGException # displayException :: ATGException -> String # | |
Show ATGException Source # | |
Defined in Terminal.Game.Layer.Object.Interface Methods showsPrec :: Int -> ATGException -> ShowS # show :: ATGException -> String # showList :: [ATGException] -> ShowS # |
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.