imj-animation-0.1.0.2: Animation Framework

Safe HaskellNone
LanguageHaskell2010

Imj.Graphics.Animation

Contents

Synopsis

Animation functions

Animation functions are used by Animations to update AnimatedPoints.

gravityFallGeo Source #

Arguments

:: Vec2 Vel

Initial speed

-> CanInteract 
-> Coords Pos

Initial position

-> Frame 
-> [AnimatedPoint] 

Gravity free-fall

simpleExplosionGeo Source #

Arguments

:: Int

Number of points per quarter arc.

-> CanInteract 
-> Coords Pos

Center

-> Frame 
-> [AnimatedPoint] 

Circular explosion by copying quarter arcs.

quantitativeExplosionGeo Source #

Arguments

:: Int

The number of points of the circle

-> CanInteract 
-> Coords Pos

Center

-> Frame 
-> [AnimatedPoint] 

Circular explosion

animatePolygonGeo Source #

Arguments

:: Int

number of extremities of the polygon (if 1, draw a circle instead)

-> Coords Pos

Center

-> Frame

Used to compute the radius.

-> [AnimatedPoint] 

Expanding then shrinking geometric figure.

laserAnimationGeo Source #

Arguments

:: LaserRay Actual 
-> Coords Pos

Unused, because the LaserRay encodes the origin already

-> Frame 
-> [AnimatedPoint] 

Note that the Coords parameter is unused.

Animation

An Animation generates AnimatedPoints:

data AnimatedPoint Source #

Constructors

AnimatedPoint 

Fields

AnimatedPoints can interact with their environment:

data CanInteract Source #

Constructors

DontInteract

The AnimatedPoint can't interact with the environment.

To ensure that the Animation is finite in time, animation functions returning AnimatedPoints that DontInteract should return an empty list of AnimatedPoints for each Frame after a given Frame.

Interact

The AnimatedPoint can be mutated after an interaction with the environment.

For the animation to be finite in time, AnimatedPoints that Interact must eventually be mutated by the environment.

Hence, assuming the environment has a finite size, animation functions returning AnimatedPoints that Interact can guarantee animation finitude by computing their coordinates using functions diverging in the Frame argument.

The result of an interaction between an AnimatedPoint and its environment can trigger a mutation:

data AnimatedPoints Source #

Constructors

AnimatedPoints 

Fields

Create

mkAnimation Source #

Arguments

:: Coords Pos

Center of the root AnimatedPoints.

-> [Coords Pos -> Frame -> [AnimatedPoint]]

List of animation functions. Every animation function generates AnimatedPoints for a given level of the root AnimatedPoints:

The k-th animation function generates AnimatedPoints living in the (k+2)-th level, and takes the center of a (k+1)-th level AnimatedPoints in its Coords argument.

Animation functions are expected to return the same number of AnimatedPoints at each iteration, or none after a given iteration to indicate that their animation is over.

-> Speed

Animation discrete speed. Tells by how much the Frame, passed to animation functions, is incremented during an update.

-> (Coords Pos -> InteractionResult)

The environmental interaction function.

During update, AnimatedPoints for which this function returns Mutation can mutate if they are allowed to.

During render, AnimatedPoints for which this function returns Stable are drawn. Others are not drawn because they would overlap with the environment.

-> Either SystemTime KeyTime

Right KeyTime of the event's deadline that triggered this animation, or Left SystemTime of the current time if a player action triggered this animation

-> Maybe Char

The default Char to draw an AnimatedPoint with, if an AnimatedPoint of that Animation doesn't specify one (i.e if one of the animation functions passed as argument don't set the Char of the AnimatedPoint they generate).

-> Maybe Animation

Depending on animation functions, the created Animation may be over after the first update, hence Nothing would be returned.

Creates an animation and initializes it by updating it once.

Predefined animations

Explosive

simpleExplosion Source #

Arguments

:: Int

Number of points in the explosion

-> Coords Pos

Center of the explosion

-> (Coords Pos -> InteractionResult)

Environment interaction function

-> Speed

Animation speed

-> Either SystemTime KeyTime

Right KeyTime of the event's deadline that triggered this animation, or Left SystemTime of the current time if a player action triggered this animation

-> Char

Character used when drawing the animation.

-> Maybe Animation 

A circular explosion configurable in number of points

quantitativeExplosionThenSimpleExplosion Source #

Arguments

:: Int

Number of points in the first explosion

-> Coords Pos

Center of the first explosion

-> (Coords Pos -> InteractionResult)

Environment interaction function

-> Speed

Animation speed

-> Either SystemTime KeyTime

Right KeyTime of the event's deadline that triggered this animation, or Left SystemTime of the current time if a player action triggered this animation

-> Char

Character used when drawing the animation.

-> Maybe Animation 

An animation chaining two circular explosions, the first explosion can be configured in number of points, the second has 4*8=32 points.

Free fall

freeFall simulates the effect of gravity on an object that has an initial speed.

freeFallThenExplode adds an explosion when the falling object hits the environment (ie when the InteractionResult of an interaction between the object and the environment is Mutation).

freeFall Source #

Arguments

:: Vec2 Vel

Initial speed

-> Coords Pos

Initial position

-> (Coords Pos -> InteractionResult)

Environment interaction function

-> Speed

Animation speed

-> Either SystemTime KeyTime

Right KeyTime of the event's deadline that triggered this animation, or Left SystemTime of the current time if a player action triggered this animation

-> Char

Character used when drawing the animation.

-> Maybe Animation 

A gravity-based free-falling animation.

freeFallThenExplode Source #

Arguments

:: Vec2 Vel

Initial speed

-> Coords Pos

Initial position

-> (Coords Pos -> InteractionResult)

Environment interaction function

-> Speed

Animation speed

-> Either SystemTime KeyTime

Right KeyTime of the event's deadline that triggered this animation, or Left SystemTime of the current time if a player action triggered this animation

-> Char

Character used when drawing the animation.

-> Maybe Animation 

An animation chaining a gravity-based free-fall and a circular explosion of 4*8 points.

Fragments

fragmentsFreeFall gives the impression that the object disintegrated in multiple pieces before falling.

fragmentsFreeFallThenExplode adds an explosion when the falling object hits the environment (ie when the InteractionResult of an interaction between the object and the environment is Mutation).

fragmentsFreeFall Source #

Arguments

:: Vec2 Vel

Initial speed

-> Coords Pos

Initial position

-> (Coords Pos -> InteractionResult)

Environment interaction function

-> Speed

Animation speed

-> Either SystemTime KeyTime

Right KeyTime of the event's deadline that triggered this animation, or Left SystemTime of the current time if a player action triggered this animation

-> Char

Character used when drawing the animation.

-> [Animation] 

Animation representing an object with an initial velocity disintegrating in 4 different parts.

fragmentsFreeFallThenExplode Source #

Arguments

:: Vec2 Vel

Initial speed

-> Coords Pos

Initial position

-> (Coords Pos -> InteractionResult)

Environment interaction function

-> Speed

Animation speed

-> Either SystemTime KeyTime

Right KeyTime of the event's deadline that triggered this animation, or Left SystemTime of the current time if a player action triggered this animation

-> Char

Character used when drawing the animation.

-> [Animation] 

Animation representing an object with an initial velocity disintegrating in 4 different parts free-falling and then exploding.

Geometric

animatedPolygon Source #

Arguments

:: Int

If n==1, the geometric figure is a circle, else if n>1, a n-sided polygon

-> Coords Pos

Center of the polygon (or circle)

-> (Coords Pos -> InteractionResult)

Environment interaction function

-> Speed

Animation speed

-> Either SystemTime KeyTime

Right KeyTime of the event's deadline that triggered this animation, or Left SystemTime of the current time if a player action triggered this animation

-> Char

Character used when drawing the animation.

-> Maybe Animation 

An animation where a geometric figure (polygon or circle) expands then shrinks, and doesn't interact with the environment.

laserAnimation Source #

Arguments

:: LaserRay Actual

The laser ray

-> (Coords Pos -> InteractionResult)

Environment interaction function

-> Either SystemTime KeyTime

Right KeyTime of the event's deadline that triggered this animation, or Left SystemTime of the current time if a player action triggered this animation

-> Maybe Animation 

A laser ray animation, with a fade-out effect.

Nice chars

niceChar presents a list of Chars that look good when used in explosive and free fall animations.

niceChar Source #

Arguments

:: Word8

We take the modulo of that value

-> Char 

Returns one of the characters that look good for explosive animations.

Update

getDeadline :: Animation -> KeyTime Source #

Returns the time at which an Animation should be updated.

shouldUpdate Source #

Arguments

:: Animation 
-> KeyTime

The current KeyTime

-> Bool 

Returns True if the KeyTime is beyond the Animation deadline or if the time difference is within animationUpdateMargin.

updateAnimation Source #

Arguments

:: Animation

The current animation

-> Maybe Animation

The updated animation, or Nothing if the Animation is over.

Render

renderAnim Source #

Arguments

:: (Draw e, MonadReader e m, MonadIO m) 
=> Animation 
-> Coords Pos

Reference coordinates.

-> m () 

If an AnimatedPoint has no specific Char to be rendered with, it will be rendered with the Char of the Animation.

Hence, if neither AnimatedPoint nor Animation contain a Char, this function errors.

Internal

Reexports

module Imj.Timing

data Coords a :: * -> * #

Two-dimensional discrete coordinates. We use phantom types Pos, Vel to distinguish positions from speeds.

Instances

Eq (Coords a) 

Methods

(==) :: Coords a -> Coords a -> Bool #

(/=) :: Coords a -> Coords a -> Bool #

Ord (Coords a) 

Methods

compare :: Coords a -> Coords a -> Ordering #

(<) :: Coords a -> Coords a -> Bool #

(<=) :: Coords a -> Coords a -> Bool #

(>) :: Coords a -> Coords a -> Bool #

(>=) :: Coords a -> Coords a -> Bool #

max :: Coords a -> Coords a -> Coords a #

min :: Coords a -> Coords a -> Coords a #

Show (Coords a) 

Methods

showsPrec :: Int -> Coords a -> ShowS #

show :: Coords a -> String #

showList :: [Coords a] -> ShowS #

DiscreteInterpolation (Coords Pos)

 Using bresenham 2d line algorithm.

DiscreteDistance (Coords Pos)

 Using bresenham 2d line algorithm.