anitomata-0.1.0.0: Composable sprite animation
Safe HaskellSafe-Inferred
LanguageGHC2021

Anitomata

Synopsis

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 = replicate 4 0.1 -- Each frame is 100ms
    , animSliceFrames = fromListN 4 [{- ... AnimFrame values ... -}]
    }

jumpSlice :: AnimSlice
jumpSlice =
  AnimSlice
    { animSliceDir = AnimDirForward
      -- Second frame is 500ms, rest are 100ms
    , animSliceFrameDurs = generate 8 $ \i -> if i == 1 then 0.5 else 0.1
    , animSliceFrames = 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-*).

Naming conventions

This library uses a naming convention on type constructors. Consider Anim and Anim_: Anim_ is the type constructor and so is suffixed with an underscore. Anim is a type alias for Anim_ with sensible defaults filled in for all the type parameters. If you are getting started with the library, it is recommended to use the type aliases. When looking at type signatures in the documentation, it may be helpful to mentally substitute the simpler type aliases in for the more general type constructor applications. If the docs mention the "default config", this is shorthand for the prescribed defaults from the aliases.

The library also aims to be consistent with its naming of type parameters:

NameMeaningDefault config
vA vector type constructorUnboxed Vector
tA duration typeDouble
fA frame typeAnimFrame
iAn integral typeInt32

Animations

type Anim = Anim_ Vector Double AnimFrame Source #

The core animation type.

data Anim_ v t f Source #

Instances

Instances details
(Show t, Show (v t), Show (v f)) => Show (Anim_ v t f) Source # 
Instance details

Defined in Anitomata

Methods

showsPrec :: Int -> Anim_ v t f -> ShowS #

show :: Anim_ v t f -> String #

showList :: [Anim_ v t f] -> ShowS #

Playing

stepAnim Source #

Arguments

:: forall v t f. (Vector v t, Vector v f, RealFrac t) 
=> t

An amount of time.

-> Anim_ v t f 
-> SteppedAnim_ v t f 

Advance an animation by the given amount of time.

type SteppedAnim = SteppedAnim_ Vector Double AnimFrame Source #

SteppedAnim wraps the animation's status and the updated animation value.

data SteppedAnim_ v t f Source #

Constructors

SteppedAnim 

Fields

Instances

Instances details
(Show t, Show (v t), Show (v f)) => Show (SteppedAnim_ v t f) Source # 
Instance details

Defined in Anitomata

Methods

showsPrec :: Int -> SteppedAnim_ v t f -> ShowS #

show :: SteppedAnim_ v t f -> String #

showList :: [SteppedAnim_ v t f] -> ShowS #

data AnimStatus Source #

Constructors

AnimStatusFinished

The animation has finished. Any additional calls to stepAnim will be no-ops. Stepping an infinitely repeating animation will never produce this status.

AnimStatusPlaying

The animation is actively playing. Stepping an infinitely repeating animation always produces this status.

Instances

Instances details
Show AnimStatus Source # 
Instance details

Defined in Anitomata

Eq AnimStatus Source # 
Instance details

Defined in Anitomata

Rendering

animFrame :: forall v t f. Vector v f => Anim_ v t f -> f Source #

The animation's current frame. Use the frame in conjunction with your game's spritesheet(s) to render an animation.

In the default config, the result type is AnimFrame. You are free to use any frame type you'd like though.

type AnimFrame = AnimFrame_ Int32 Source #

A source rectangle into a spritesheet.

The rectangle is defined via the coordinates of its top-left point and its extents.

data AnimFrame_ i Source #

Constructors

AnimFrame 

Fields

Instances

Instances details
Unbox a => Vector Vector (AnimFrame_ a) Source # 
Instance details

Defined in Anitomata

Unbox a => MVector MVector (AnimFrame_ a) Source # 
Instance details

Defined in Anitomata

Show i => Show (AnimFrame_ i) Source # 
Instance details

Defined in Anitomata

Eq i => Eq (AnimFrame_ i) Source # 
Instance details

Defined in Anitomata

Methods

(==) :: AnimFrame_ i -> AnimFrame_ i -> Bool #

(/=) :: AnimFrame_ i -> AnimFrame_ i -> Bool #

Unbox a => Unbox (AnimFrame_ a) Source # 
Instance details

Defined in Anitomata

data MVector s (AnimFrame_ a) Source # 
Instance details

Defined in Anitomata

data Vector (AnimFrame_ a) Source # 
Instance details

Defined in Anitomata

Building

buildAnim :: forall v t f. (Vector v f, Fractional t) => AnimDuration_ t -> AnimBuilder_ v t f -> Anim_ v t f Source #

Build an animation with a specified duration.

type AnimDuration = AnimDuration_ Double Source #

A means for customizing an animation's duration.

By default (i.e. when using AnimDurationDefault), an animation's duration is dictated by the durations of each individual frame. This is often what you want, as playing the animation in your game will match the timing of playing the animation in your design tool. Sometimes you may want to tweak an animation's duration without redoing or duplicating work in your design tool though, so in these cases, you may find the other branches in this type useful.

data AnimDuration_ t Source #

Constructors

AnimDurationDefault

Use each frame's default duration.

AnimDurationScaled !t

Scale each frame's default duration by the specified value.

For example, you can play an animation twice as fast with AnimDurationScaled 0.5.

AnimDurationTotal !t

Scale each frame's default duration such that the time required to play the animation matches the specified total duration.

buildAnim will generate a runtime error if this is used with an infinitely repeating animation.

AnimDurationEachFrame !t

Ignore each frame's default duration, using the specified constant duration instead.

AnimDurationEachFrameFromTotal !t

Ignore each frame's default duration, using a constant duration for each frame derived from the specified total duration instead.

buildAnim will generate a runtime error if this is used with an infinitely repeating animation.

Instances

Instances details
Show t => Show (AnimDuration_ t) Source # 
Instance details

Defined in Anitomata

Eq t => Eq (AnimDuration_ t) Source # 
Instance details

Defined in Anitomata

type AnimBuilder = AnimBuilder_ Vector Double AnimFrame Source #

An animation builder.

Convert slices to builders via fromAnimSlice and pingpongAnimSlice. Builders may then be combined via the Semigroup interface and their animation sequences may be repeated via repeatAnim.

data AnimBuilder_ v t f Source #

Instances

Instances details
RealFrac t => Semigroup (AnimBuilder_ v t f) Source # 
Instance details

Defined in Anitomata

Methods

(<>) :: AnimBuilder_ v t f -> AnimBuilder_ v t f -> AnimBuilder_ v t f #

sconcat :: NonEmpty (AnimBuilder_ v t f) -> AnimBuilder_ v t f #

stimes :: Integral b => b -> AnimBuilder_ v t f -> AnimBuilder_ v t f #

(Show t, Show (v t), Show (v f)) => Show (AnimBuilder_ v t f) Source # 
Instance details

Defined in Anitomata

Methods

showsPrec :: Int -> AnimBuilder_ v t f -> ShowS #

show :: AnimBuilder_ v t f -> String #

showList :: [AnimBuilder_ v t f] -> ShowS #

(Eq t, Eq (v t), Eq (v f)) => Eq (AnimBuilder_ v t f) Source # 
Instance details

Defined in Anitomata

Methods

(==) :: AnimBuilder_ v t f -> AnimBuilder_ v t f -> Bool #

(/=) :: AnimBuilder_ v t f -> AnimBuilder_ v t f -> Bool #

fromAnimSlice :: forall v t f. (Vector v t, Vector v f, RealFrac t) => AnimSlice_ v t f -> AnimBuilder_ v t f Source #

Create a builder from a single slice.

pingpongAnimSlice :: forall v t f. (Vector v t, Vector v f, RealFrac t) => AnimSlice_ v t f -> AnimBuilder_ v t f Source #

Create a builder from a single slice, where the animation sequence is the slice first played in its defined direction and then played in its opposite direction.

This is provided for convenience. You may achieve the same result using the Semigroup interface and futzing with the animation directions:

builder :: AnimBuilder
builder = fromAnimSlice slice <> fromAnimSlice slice
  { animSliceDir =
      case animSliceDir slice of
        AnimDirForward -> AnimDirBackward
        AnimDirBackward -> AnimDirForward
  }

slice :: AnimSlice

repeatAnim :: forall v t f. RealFrac t => AnimRepeat -> AnimBuilder_ v t f -> AnimBuilder_ v t f Source #

Repeat a builder's animation sequence.

data AnimRepeat Source #

Constructors

AnimRepeatForever

Repeat the animation sequence infinitely.

AnimRepeatCount !Int

Repeat the animation sequence a finite number of times

Instances

Instances details
Show AnimRepeat Source # 
Instance details

Defined in Anitomata

Slices

type AnimSlice = AnimSlice_ Vector Double AnimFrame Source #

A single, logical sequence of animation frames. A slice captures a direction, a vector of frames, and a vector of frame durations. The sizes of the two vectors must match.

While you are technically free to create an animation out of a bunch of single-frame slices, it is recommended for performance's sake that each slice is defined with as many frames as necessary to capture a logical chunk of animation.

If you use a code generator or parser to produce your slices, additional performance gains are available. These utilities typically produce a single vector of frames and a single vector of durations encompassing all the animation slices in your spritesheet. Then the produced animation slices refer to these two "megavectors" via vector slices (mind the overloaded "slice" word) and avoid copying any frame and duration data. This makes the use and reuse of animation slices very cheap.

data AnimSlice_ v t f Source #

Constructors

AnimSlice 

Fields

Instances

Instances details
(Show (v t), Show (v f)) => Show (AnimSlice_ v t f) Source # 
Instance details

Defined in Anitomata

Methods

showsPrec :: Int -> AnimSlice_ v t f -> ShowS #

show :: AnimSlice_ v t f -> String #

showList :: [AnimSlice_ v t f] -> ShowS #

(Eq (v t), Eq (v f)) => Eq (AnimSlice_ v t f) Source # 
Instance details

Defined in Anitomata

Methods

(==) :: AnimSlice_ v t f -> AnimSlice_ v t f -> Bool #

(/=) :: AnimSlice_ v t f -> AnimSlice_ v t f -> Bool #

data AnimDir Source #

Constructors

AnimDirForward

The slice is to be played forward.

AnimDirBackward

The slice is to be played in reverse.

Instances

Instances details
Show AnimDir Source # 
Instance details

Defined in Anitomata

Eq AnimDir Source # 
Instance details

Defined in Anitomata

Methods

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

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

Metadata

animMeta :: forall v t f. Anim_ v t f -> Maybe (AnimMeta_ t) Source #

The animation's metadata.

This function produces Nothing if the animation is infinitely repeating.

type AnimMeta = AnimMeta_ Double Source #

Animation metadata.

data AnimMeta_ t Source #

Instances

Instances details
RealFrac t => Semigroup (AnimMeta_ t) Source # 
Instance details

Defined in Anitomata

Methods

(<>) :: AnimMeta_ t -> AnimMeta_ t -> AnimMeta_ t #

sconcat :: NonEmpty (AnimMeta_ t) -> AnimMeta_ t #

stimes :: Integral b => b -> AnimMeta_ t -> AnimMeta_ t #

Show t => Show (AnimMeta_ t) Source # 
Instance details

Defined in Anitomata

Eq t => Eq (AnimMeta_ t) Source # 
Instance details

Defined in Anitomata

Methods

(==) :: AnimMeta_ t -> AnimMeta_ t -> Bool #

(/=) :: AnimMeta_ t -> AnimMeta_ t -> Bool #

Testing

You really shouldn't need anything from this section! These functions are only provided to aid in testing and debugging.

iterateAnim :: forall v t f. (Vector v t, Vector v f, RealFrac t) => t -> Anim_ v t f -> [SteppedAnim_ v t f] Source #

Repeatedly step an animation using a fixed timestep, producing a stream of updated animations until the animation is finished.

If the input animation is infinitely repeating, this function produces an infinite list.

animSlice :: forall v t f. Anim_ v t f -> AnimSlice_ v t f Source #

The animation's current slice.

The slice returned is the original slice specified at animation build time and its frame durations are not modified to take the animation's specified duration into account.

animSequence :: forall v t f. Anim_ v t f -> NonEmpty (AnimSlice_ v t f) Source #

The animation's current sequence of slices.

The slices returned are the original slices specified at animation build time and their frame durations are not modified to take the animation's specified duration into account.