Copyright | © 2017-2019 Francesco Ariis |
---|---|
License | GPLv3 (see LICENSE file) |
Maintainer | Francesco Ariis <fa-ml@ariis.it> |
Stability | provisional |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Machinery and utilities for 2D terminal games.
New? Start from Game
.
Synopsis
- type FPS = Integer
- data Event
- data Game s = Game {
- gScreenWidth :: Width
- gScreenHeight :: Height
- gFPS :: FPS
- 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 = Integer
- type Column = Integer
- type Width = Integer
- type Height = Integer
- blankPlane :: Width -> Height -> Plane
- stringPlane :: String -> Plane
- stringPlaneTrans :: Char -> String -> Plane
- makeTransparent :: Char -> Plane -> Plane
- makeOpaque :: Plane -> Plane
- paperPlane :: 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 :: Char -> Width -> Height -> Plane
- textBox :: String -> Width -> Height -> Plane
- textBoxLiquid :: String -> Width -> Plane
- data Color
- data ColorIntensity
- color :: Color -> ColorIntensity -> Plane -> Plane
- bold :: Plane -> Plane
- invert :: Plane -> Plane
- (|||) :: 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
Running
Instances
Eq Event Source # | |
Show Event Source # | |
Generic Event Source # | |
Arbitrary Event Source # | |
Serialize 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.1.1.0-CZVAojmpoWB8GqKb2Hppz1" '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.
Game | |
|
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 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
Eq StdGen | |
Show StdGen | |
NFData StdGen | |
Defined in System.Random.Internal | |
RandomGen StdGen | |
Defined in System.Random.Internal 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 Bool | |
Random Char | |
Random Double | Note - |
Random Float | Note - |
Random Int | |
Random Int8 | |
Random Int16 | |
Random Int32 | |
Random Int64 | |
Random Integer | |
Random Word | |
Random Word8 | |
Random Word16 | |
Random Word32 | |
Random Word64 | |
Random CChar | |
Random CSChar | |
Random CUChar | |
Random CShort | |
Random CUShort | |
Random CInt | |
Random CUInt | |
Random CLong | |
Random CULong | |
Random CLLong | |
Random CULLong | |
Random CBool | |
Random CFloat | Note - |
Random CDouble | Note - |
Random CPtrdiff | |
Random CSize | |
Random CWchar | |
Random CSigAtomic | |
Defined in System.Random 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 | |
Random CUIntPtr | |
Random CIntMax | |
Random CUIntMax | |
(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.
paperPlane :: 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
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.
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 #
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.