anitomata: Composable sprite animation

[ game, library, mit ] [ Propose Tags ]

Composable 2D sprite animation in Haskell.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0
Change log CHANGELOG.md
Dependencies base (>=4.17 && <4.20), vector (>=0.13.1.0 && <0.14) [details]
License MIT
Author Jason Shipman
Maintainer Jason Shipman
Category Game
Home page https://sr.ht/~jship/anitomata/
Source repo head: git clone https://git.sr.ht/~jship/anitomata/
Uploaded by jship at 2024-03-26T15:16:05Z
Distributions NixOS:0.1.0.0
Downloads 19 total (8 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2024-03-26 [all 1 reports]

Readme for anitomata-0.1.0.0

[back to package description]

anitomata

Version badge

Synopsis

anitomata is a pure implementation of 2D sprite animation intended for use in gamedev.

In this example, anim is an animation for an NPC celebrating a victory. The animation sequence plays the NPC's idle animation two times then the jump animation one time, and the entire sequence is looped indefinitely:

import Anitomata
import qualified Data.Vector.Unboxed as U

anim :: Anim
anim =
  buildAnim AnimDurationDefault
    $ repeatAnim AnimRepeatForever
    $ repeatAnim (AnimRepeatCount 1) idle <> jump

idle :: AnimBuilder
idle = fromAnimSlice idleSlice

jump :: AnimBuilder
jump = fromAnimSlice jumpSlice

idleSlice :: AnimSlice
idleSlice =
  AnimSlice
    { animSliceDir = AnimDirBackward
    , animSliceFrameDurs = U.replicate 4 0.1 -- Each frame is 100ms
    , animSliceFrames = U.fromListN 4 [{- ... AnimFrame values ... -}]
    }

jumpSlice :: AnimSlice
jumpSlice =
  AnimSlice
    { animSliceDir = AnimDirForward
      -- Second frame is 500ms, rest are 100ms
    , animSliceFrameDurs = U.generate 8 $ \i -> if i == 1 then 0.5 else 0.1
    , animSliceFrames = U.fromListN 8 [{- ... AnimFrame values ... -}]
    }

AnimSlice is the smallest building block of an animation. Slices are a minimal sequence of frames that capture a logical chunk of animation. Slices are converted to AnimBuilder values and then the builders can be combined using the Semigroup interface. Values of the core animation type - Anim - are created from builders.

A game can play an animation by stepping it using stepAnim each simulation frame, passing the time elapsed since the last step:

stepAnim :: Double -> Anim -> SteppedAnim

data SteppedAnim = SteppedAnim
  { steppedAnimStatus :: AnimStatus
  , steppedAnimValue :: Anim
  }

An animation can be rendered using animFrame in conjunction with a spritesheet that is managed separately by the game. animFrame provides the current frame of the animation:

animFrame :: Anim -> AnimFrame

Note that the types in the library are more general than what is shown above. For example, there is no requirement of using Double as a duration type, unboxed Vector as the vector type, etc.

The animation building blocks can be defined manually, but this is tedious and error-prone. Instead, the base slices and builders are typically defined automatically by feeding a design file - e.g. output from Aseprite - into a code generator or parsing some translated representation of a design file. Packages providing this functionality may be found by visiting the project's homepage or by searching Hackage (all official packages of the anitomata project are named anitomata-*).

For additional detail on the library, please see the Haddocks and the announcement post.