imj-base-0.1.0.2: Game engine with geometry, easing, animated text, delta rendering.

Safe HaskellNone
LanguageHaskell2010

Imj.Graphics.Render.Delta

Contents

Description

The purpose of this module is to render games and animations in the terminal without screen tearing.

It supports 8-bit Colors and Unicode characters.

In short, screen tearing is mitigated by:

  • Using double buffering techniques (back and front buffers)
  • Rendering in each frame only the locations that have changed, in an order that allows to omit many byte-expensive commands,
  • Chosing the smallest rendering command among equivalent alternatives.

A more detailed overview can be seen at the end of this documentation.

Synopsis

Usage

  • from a MonadIO monad (see this example):

    import Imj.Graphics.Class.Draw(drawStr')
    import Imj.Graphics.Class.Render(renderToScreen')
    
    helloWorld :: (MonadIO m) => DeltaEnv -> m ()
    helloWorld env = do
      drawStr' env "Hello World" (Coords 10 10) (onBlack green)
      renderToScreen' env
    
    main = runThenRestoreConsoleSettings $ newDefaultEnv >>= helloWorld
    
  • from a MonadIO, MonadReader DeltaEnv monad (see this example):

    import Imj.Graphics.Render.FromMonadReader(drawStr, renderToScreen)
    
    -- Note that we omit 'Draw e', which is implied by 'Render e':
    helloWorld :: (Render e, MonadReader e m, MonadIO m) => m ()
    helloWorld = do
      drawStr "Hello World" (Coords 10 10) (onBlack green)
      renderToScreen
    
    main = runThenRestoreConsoleSettings $ newDefaultEnv >>= runReaderT helloWorld
    
  • from a MonadIO, MonadReader YourEnv monad (see this example):

    import YourApp(createYourEnv)
    import Imj.Graphics.Render.FromMonadReader(drawStr, renderToScreen)
    
    -- Note that we omit 'Draw e', which is implied by 'Render e':
    helloWorld :: (Render e, MonadReader e m, MonadIO m) => m ()
    helloWorld = do
      drawStr "Hello World" (Coords 10 10) (onBlack green)
      renderToScreen
    
    main = runThenRestoreConsoleSettings $ newDefaultEnv >>= createYourEnv >>= runReaderT helloWorld
    

Environment

Back and front buffers are persisted in the delta-rendering environment: DeltaEnv.

Environment creation

newDefaultEnv :: IO DeltaEnv Source #

Creates an environment using default policies.

newEnv Source #

Creates an environment with policies.

Policies

Note that policy changes take effect after the next render.

Resize

data ResizePolicy Source #

When and how to resize buffers.

Constructors

MatchTerminalSize

After each render, buffers are resized (if needed) to match terminal size.

FixedSize !(Dim Width) !(Dim Height)

Buffers have a fixed size. If they are vertically or horizontally bigger than the terminal, rendering artefacts will be visible.

setResizePolicy :: Maybe ResizePolicy -> DeltaEnv -> IO () Source #

Sets the ResizePolicy for back and front buffers. Defaults to defaultResizePolicy when Nothing is passed.

Clear after render

data ClearPolicy Source #

Specifies when to clear the back-buffer.

Constructors

ClearAtEveryFrame

Clears the back-buffer after allocation and after each frame render.

ClearOnAllocationOnly

Clears the back-buffer after allocation only. Typically, you will use it if at every frame you draw at every screen location. If you don't redraw every screen location at every frame, it is safer to use ClearAtEveryFrame, else you will see previous frame elements in the rendered frame (unless you intend to have this behaviour).

setClearPolicy :: Maybe ClearPolicy -> DeltaEnv -> IO () Source #

Sets the ClearPolicy. | Defaults to defaultClearPolicy when Nothing is passed.

setClearColor :: Maybe (Color8 Background) -> DeltaEnv -> IO () Source #

Sets the Color8 to use when clearing. Defaults to defaultClearColor when Nothing is passed.

Stdout BufferMode

setStdoutBufferMode :: Maybe BufferMode -> IO () Source #

Sets stdout's BufferMode. Defaults to defaultStdoutMode when Nothing is passed.

Draw and render

The functions below present drawing and rendering functions in a MonadReader monad, which is the recommended way to use delta rendering.

More alternatives are presented in this module:

Draw char(s)

drawChars :: (Draw e, MonadReader e m, MonadIO m) => Int -> Char -> Coords Pos -> LayeredColor -> m () Source #

Draws a Char multiple times, starting at the given coordinates and then moving to the right.

Draw text

Draw aligned text

drawAlignedTxt_ :: (Draw e, MonadReader e m, MonadIO m) => Text -> LayeredColor -> Alignment -> m () Source #

Draws text with Alignment.

drawAlignedTxt :: (Draw e, MonadReader e m, MonadIO m) => Text -> LayeredColor -> Alignment -> m Alignment Source #

Draws text with Alignment.

Returns the Alignment projected on the next line.

Render to the physical device

renderToScreen :: (Render e, MonadReader e m, MonadIO m) => m () Source #

Render the drawing to {the screen, the console, etc...}.

Cleanup

runThenRestoreConsoleSettings :: IO a -> IO a Source #

Helper function to run an action and restore the console settings when it is finished or when an exception was thrown.

Reexports

data BufferMode :: * #

Three kinds of buffering are supported: line-buffering, block-buffering or no-buffering. These modes have the following effects. For output, items are written out, or flushed, from the internal buffer according to the buffer mode:

  • line-buffering: the entire output buffer is flushed whenever a newline is output, the buffer overflows, a hFlush is issued, or the handle is closed.
  • block-buffering: the entire buffer is written out whenever it overflows, a hFlush is issued, or the handle is closed.
  • no-buffering: output is written immediately, and never stored in the buffer.

An implementation is free to flush the buffer more frequently, but not less frequently, than specified above. The output buffer is emptied as soon as it has been written out.

Similarly, input occurs according to the buffer mode for the handle:

  • line-buffering: when the buffer for the handle is not empty, the next item is obtained from the buffer; otherwise, when the buffer is empty, characters up to and including the next newline character are read into the buffer. No characters are available until the newline character is available or the buffer is full.
  • block-buffering: when the buffer for the handle becomes empty, the next block of data is read into the buffer.
  • no-buffering: the next input item is read and returned. The hLookAhead operation implies that even a no-buffered handle may require a one-character buffer.

The default buffering mode when a handle is opened is implementation-dependent and may depend on the file system object which is attached to that handle. For most implementations, physical files will normally be block-buffered and terminals will normally be line-buffered.

Constructors

NoBuffering

buffering is disabled if possible.

LineBuffering

line-buffering should be enabled if possible.

BlockBuffering (Maybe Int)

block-buffering should be enabled if possible. The size of the buffer is n items if the argument is Just n and is otherwise implementation-dependent.

Motivations and technical overview

Screen tearing

Screen tearing occurs in the terminal when, for a given frame, rendering commands exceed the capacity of stdout buffer. To avoid overflowing stdout, the system flushes it, thereby triggering a partial frame render.

Motivations

At the beginning of the development of hamazed, I was clearing the terminal screen at every frame and filling stdout with rendering commands for every game element and animation.

As the complexity of animations grew, screen tearing occured, so I looked for ways to fix it. This package is the result of this research.

My first idea to mitigate screen tearing was to maximize the size of stdout buffer:

hSetBuffering stdout $ BlockBuffering $ Just maxBound

I developped imj-measure-stdout-exe to measure the size of stdout buffer and found that the size had quadrupled, from 2048 to 8192 bytes.

But it solved the problem only very temporarily. As I introduced more animations in the game, screen tearing was back : I needed not only to maximize stdout size but also to reduce the amount of data that I was writing in it. This is when I discovered the delta rendering approach.

Delta rendering

Delta rendering is the approach Rafael Ibraim took when writing this code for his own game.

The idea was to introduce two in-memory buffers:

  • a front buffer containing what is currently displayed on the terminal
  • a back buffer containing what we want to draw in the next frame.

At every frame, we would draw all game elements and animations, this time not to the terminal directly, but to the back buffer.

At the the end of the frame, the difference between front and back buffer would be rendered to the terminal.

Further optimizations

Minimizing the total size of rendering commands

The initial implementation was fixing the screen tearing for my game, yet I wanted to optimize things to be able to support even richer frame changes in the future. I added the following optimizations:

  • We group locations by color before rendering them, to issue one color change per group instead of one per element (an 8-bit color change command is 20 bytes: "ESC[48;5;167;38;5;255m").
  • We render the "color group" elements by increasing screen positions, and when two consecutive elements are found, we omit the position change command, because putChar already moved the cursor position to the right (a 2-D position change command is 9 bytes: "ESC[150;42H").

We can still improve on this by using a one-dimensional relative position change commands (3 to 6 bytes : "ESC[C", "ESC[183C") when the next location is either on the same column or on the same line.

Minimizing the run-time overhead and memory footprint

I wanted not only to avoid screen tearing, but also to be fast, to allow for higher framerates. So I refactored the datastructures to use continuous blocks of memory, and to encode every important information in the smallest form possible, to improve cache usage.

These answers on reddit helped in the process.

I use Vectors of unpacked Word64 (the most efficient Haskell type in terms of "information quantity / memory usage" ratio) and an efficient encoding to stores 4 different informations in a Word64:

[from higher bits to lower bits]

  • background color (8 bits)
  • foreground color (8 bits)
  • buffer position (16 bits)
  • unicode character (32 bits)

I also introduced a third in-memory vector, the Delta vector, which contains just the differences to render. Due to the previously described encoding, when sorting the delta vector, same-color locations end up being grouped in the same slice of the vector, and are sorted by increasing position, which is exactly what we want to implement the optimizations I mentionned earlier.