animate-0.5.0: Animation for sprites

Safe HaskellNone
LanguageHaskell2010

Animate

Synopsis

Documentation

type Color = (Word8, Word8, Word8) Source #

Alias for RGB (8bit, 8bit, 8bit)

data Frame loc delay Source #

Constructors

Frame 

Fields

  • fLocation :: loc

    User defined reference to the location of a sprite. For example, a sprite sheet clip.

  • fDelay :: delay

    Minimium amount of units for the frame to last.

Instances

(Eq delay, Eq loc) => Eq (Frame loc delay) Source # 

Methods

(==) :: Frame loc delay -> Frame loc delay -> Bool #

(/=) :: Frame loc delay -> Frame loc delay -> Bool #

(Show delay, Show loc) => Show (Frame loc delay) Source # 

Methods

showsPrec :: Int -> Frame loc delay -> ShowS #

show :: Frame loc delay -> String #

showList :: [Frame loc delay] -> ShowS #

Generic (Frame loc delay) Source # 

Associated Types

type Rep (Frame loc delay) :: * -> * #

Methods

from :: Frame loc delay -> Rep (Frame loc delay) x #

to :: Rep (Frame loc delay) x -> Frame loc delay #

type Rep (Frame loc delay) Source # 
type Rep (Frame loc delay) = D1 * (MetaData "Frame" "Animate" "animate-0.5.0-IhyJIpSANEn2x4YVGpp1kr" False) (C1 * (MetaCons "Frame" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "fLocation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * loc)) (S1 * (MetaSel (Just Symbol "fDelay") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * delay))))

newtype Animations key loc delay Source #

Type safe animation set. Use a sum type with an Enum and Bounded instance for the animation, a.

Constructors

Animations 

Fields

Instances

(Eq loc, Eq delay) => Eq (Animations key loc delay) Source # 

Methods

(==) :: Animations key loc delay -> Animations key loc delay -> Bool #

(/=) :: Animations key loc delay -> Animations key loc delay -> Bool #

(Show loc, Show delay) => Show (Animations key loc delay) Source # 

Methods

showsPrec :: Int -> Animations key loc delay -> ShowS #

show :: Animations key loc delay -> String #

showList :: [Animations key loc delay] -> ShowS #

data Loop Source #

Constructors

Loop'Always

Never stop looping. Animation can never be completed.

Loop'Count Int

Count down loops to below zero. 0 = no loop. 1 = one loop. 2 = two loops. etc.

Instances

Eq Loop Source # 

Methods

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

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

Show Loop Source # 

Methods

showsPrec :: Int -> Loop -> ShowS #

show :: Loop -> String #

showList :: [Loop] -> ShowS #

Generic Loop Source # 

Associated Types

type Rep Loop :: * -> * #

Methods

from :: Loop -> Rep Loop x #

to :: Rep Loop x -> Loop #

type Rep Loop Source # 
type Rep Loop = D1 * (MetaData "Loop" "Animate" "animate-0.5.0-IhyJIpSANEn2x4YVGpp1kr" False) ((:+:) * (C1 * (MetaCons "Loop'Always" PrefixI False) (U1 *)) (C1 * (MetaCons "Loop'Count" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))))

data Position key delay Source #

State for progression through an animation

example = Position minBound 0 0 Loop'Always

Constructors

Position 

Fields

  • pKey :: key

    Index for the animation.

  • pFrameIndex :: FrameIndex

    Index wihin the animation. WARNING: Modifying to below zero or equal-to-or-greater-than-the-frame-count will throw out of bounds errors.

  • pCounter :: delay

    Accumulated units to end of the frame. Will continue to compound if animation is completed.

  • pLoop :: Loop

    How to loop through an animation. Loop'Count is a count down.

Instances

(Eq delay, Eq key) => Eq (Position key delay) Source # 

Methods

(==) :: Position key delay -> Position key delay -> Bool #

(/=) :: Position key delay -> Position key delay -> Bool #

(Show delay, Show key) => Show (Position key delay) Source # 

Methods

showsPrec :: Int -> Position key delay -> ShowS #

show :: Position key delay -> String #

showList :: [Position key delay] -> ShowS #

Generic (Position key delay) Source # 

Associated Types

type Rep (Position key delay) :: * -> * #

Methods

from :: Position key delay -> Rep (Position key delay) x #

to :: Rep (Position key delay) x -> Position key delay #

type Rep (Position key delay) Source # 

data FrameStep delay Source #

You can ignore. An intermediate type for stepPosition to judge how to increment the current frame.

Constructors

FrameStep'Counter delay

New counter to compare against the frame's delay.

FrameStep'Delta delay

How much delta to carry over into the next frame.

Instances

Eq delay => Eq (FrameStep delay) Source # 

Methods

(==) :: FrameStep delay -> FrameStep delay -> Bool #

(/=) :: FrameStep delay -> FrameStep delay -> Bool #

Show delay => Show (FrameStep delay) Source # 

Methods

showsPrec :: Int -> FrameStep delay -> ShowS #

show :: FrameStep delay -> String #

showList :: [FrameStep delay] -> ShowS #

Generic (FrameStep delay) Source # 

Associated Types

type Rep (FrameStep delay) :: * -> * #

Methods

from :: FrameStep delay -> Rep (FrameStep delay) x #

to :: Rep (FrameStep delay) x -> FrameStep delay #

type Rep (FrameStep delay) Source # 
type Rep (FrameStep delay) = D1 * (MetaData "FrameStep" "Animate" "animate-0.5.0-IhyJIpSANEn2x4YVGpp1kr" False) ((:+:) * (C1 * (MetaCons "FrameStep'Counter" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * delay))) (C1 * (MetaCons "FrameStep'Delta" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * delay))))

class KeyName key where Source #

Animation Keyframe. keyName is used for JSON parsing.

Minimal complete definition

keyName

Methods

keyName :: key -> Text Source #

data SpriteClip Source #

Describe the boxed area of the 2d sprite inside a sprite sheet

Constructors

SpriteClip 

Fields

data SpriteSheet key img delay Source #

Generalized sprite sheet data structure

Constructors

SpriteSheet 

Fields

Instances

Generic (SpriteSheet key img delay) Source # 

Associated Types

type Rep (SpriteSheet key img delay) :: * -> * #

Methods

from :: SpriteSheet key img delay -> Rep (SpriteSheet key img delay) x #

to :: Rep (SpriteSheet key img delay) x -> SpriteSheet key img delay #

type Rep (SpriteSheet key img delay) Source # 
type Rep (SpriteSheet key img delay) = D1 * (MetaData "SpriteSheet" "Animate" "animate-0.5.0-IhyJIpSANEn2x4YVGpp1kr" False) (C1 * (MetaCons "SpriteSheet" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "ssAnimations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Animations key SpriteClip delay))) (S1 * (MetaSel (Just Symbol "ssImage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * img))))

data SpriteSheetInfo delay Source #

One way to represent sprite sheet information. JSON loading is included.

Instances

Eq delay => Eq (SpriteSheetInfo delay) Source # 

Methods

(==) :: SpriteSheetInfo delay -> SpriteSheetInfo delay -> Bool #

(/=) :: SpriteSheetInfo delay -> SpriteSheetInfo delay -> Bool #

Show delay => Show (SpriteSheetInfo delay) Source # 
Generic (SpriteSheetInfo delay) Source # 

Associated Types

type Rep (SpriteSheetInfo delay) :: * -> * #

Methods

from :: SpriteSheetInfo delay -> Rep (SpriteSheetInfo delay) x #

to :: Rep (SpriteSheetInfo delay) x -> SpriteSheetInfo delay #

ToJSON delay => ToJSON (SpriteSheetInfo delay) Source # 
FromJSON delay => FromJSON (SpriteSheetInfo delay) Source # 
type Rep (SpriteSheetInfo delay) Source # 

animations :: (Enum key, Bounded key) => (key -> [Frame loc delay]) -> Animations key loc delay Source #

Generate animations given each constructor

framesByAnimation :: Enum key => Animations key loc delay -> key -> Vector (Frame loc delay) Source #

Lookup the frames of an animation

initPosition :: Num delay => key -> Position key delay Source #

New Position with its animation key to loop forever

initPositionLoops :: Num delay => key -> Int -> Position key delay Source #

New Position with its animation key with a limited loop

initPositionWithLoop :: Num delay => key -> Loop -> Position key delay Source #

stepFrame :: (Num delay, Ord delay) => Frame loc delay -> Position key delay -> delay -> FrameStep delay Source #

Intermediate function for how a frame should be step through.

stepPosition :: (Enum key, Num delay, Ord delay) => Animations key loc delay -> Position key delay -> delay -> Position key delay Source #

Step through the animation resulting a new position.

isAnimationComplete :: (Enum key, Num delay, Ord delay) => Animations key loc delay -> Position key delay -> Bool Source #

The animation has finished all its frames. Useful for signalling into switching to another animation. With a Loop'Always, the animation will never be completed.

positionHasLooped Source #

Arguments

:: Position key delay

Previous

-> Position key delay

Next

-> Bool 

Simple function diff'ing the position for loop change.

currentFrame :: (Enum key, Num delay) => Animations key loc delay -> Position key delay -> Frame loc delay Source #

Use the position to find the current frame of the animation.

currentLocation :: (Enum key, Num delay) => Animations key loc delay -> Position key delay -> loc Source #

Use the position to find the current location, lik a sprite sheet clip, of the animation.

nextKey :: (Bounded key, Enum key, Eq key) => key -> key Source #

Cycle through the next animation key.

prevKey :: (Bounded key, Enum key, Eq key) => key -> key Source #

Cycle through the previous animation key.

readSpriteSheetInfoJSON Source #

Arguments

:: FromJSON delay 
=> FilePath

Path of the sprite sheet info JSON file

-> IO (SpriteSheetInfo delay) 

Quick function for loading SpriteSheetInfo. Check the example.

readSpriteSheetJSON Source #

Arguments

:: (KeyName key, Ord key, Bounded key, Enum key, FromJSON delay) 
=> (FilePath -> Maybe Color -> IO img)

Inject an image loading function

-> FilePath

Path of the sprite sheet info JSON file

-> IO (SpriteSheet key img delay) 

Quick function for loading SpriteSheetInfo, then using it to load its image for a SpriteSheet. Check the example.