| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Imj.Graphics.Animation
Contents
- gravityFallGeo :: Vec2 Vel -> CanInteract -> Coords Pos -> Frame -> [AnimatedPoint]
 - simpleExplosionGeo :: Int -> CanInteract -> Coords Pos -> Frame -> [AnimatedPoint]
 - quantitativeExplosionGeo :: Int -> CanInteract -> Coords Pos -> Frame -> [AnimatedPoint]
 - animatePolygonGeo :: Int -> Coords Pos -> Frame -> [AnimatedPoint]
 - laserAnimationGeo :: LaserRay Actual -> Coords Pos -> Frame -> [AnimatedPoint]
 - data Animation
 - data AnimatedPoint = AnimatedPoint {}
 - data CanInteract
 - data InteractionResult
 - data AnimatedPoints = AnimatedPoints {}
 - mkAnimation :: Coords Pos -> [Coords Pos -> Frame -> [AnimatedPoint]] -> Speed -> (Coords Pos -> InteractionResult) -> Either SystemTime KeyTime -> Maybe Char -> Maybe Animation
 - simpleExplosion :: Int -> Coords Pos -> (Coords Pos -> InteractionResult) -> Speed -> Either SystemTime KeyTime -> Char -> Maybe Animation
 - quantitativeExplosionThenSimpleExplosion :: Int -> Coords Pos -> (Coords Pos -> InteractionResult) -> Speed -> Either SystemTime KeyTime -> Char -> Maybe Animation
 - freeFall :: Vec2 Vel -> Coords Pos -> (Coords Pos -> InteractionResult) -> Speed -> Either SystemTime KeyTime -> Char -> Maybe Animation
 - freeFallThenExplode :: Vec2 Vel -> Coords Pos -> (Coords Pos -> InteractionResult) -> Speed -> Either SystemTime KeyTime -> Char -> Maybe Animation
 - fragmentsFreeFall :: Vec2 Vel -> Coords Pos -> (Coords Pos -> InteractionResult) -> Speed -> Either SystemTime KeyTime -> Char -> [Animation]
 - fragmentsFreeFallThenExplode :: Vec2 Vel -> Coords Pos -> (Coords Pos -> InteractionResult) -> Speed -> Either SystemTime KeyTime -> Char -> [Animation]
 - animatedPolygon :: Int -> Coords Pos -> (Coords Pos -> InteractionResult) -> Speed -> Either SystemTime KeyTime -> Char -> Maybe Animation
 - laserAnimation :: LaserRay Actual -> (Coords Pos -> InteractionResult) -> Either SystemTime KeyTime -> Maybe Animation
 - niceChar :: Word8 -> Char
 - getDeadline :: Animation -> KeyTime
 - shouldUpdate :: Animation -> KeyTime -> Bool
 - updateAnimation :: Animation -> Maybe Animation
 - renderAnim :: (Draw e, MonadReader e m, MonadIO m) => Animation -> Coords Pos -> m ()
 - module Imj.Graphics.Animation.Internal
 - module Imj.Timing
 - module Imj.Iteration
 - data Coords a :: * -> *
 
Animation functions
Animation functions are used by Animations to update AnimatedPoints.
Arguments
| :: Vec2 Vel | Initial speed  | 
| -> CanInteract | |
| -> Coords Pos | Initial position  | 
| -> Frame | |
| -> [AnimatedPoint] | 
Gravity free-fall
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
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.
Arguments
| :: LaserRay Actual | |
| -> Coords Pos | Unused, because the   | 
| -> Frame | |
| -> [AnimatedPoint] | 
Note that the Coords parameter is unused.
Animation
An Animation generates AnimatedPoints: 
data AnimatedPoint Source #
Constructors
| AnimatedPoint | |
Fields 
  | |
Instances
AnimatedPoints can interact with their environment:
data CanInteract Source #
Constructors
| DontInteract | The  To ensure that the   | 
| Interact | The  For the animation to be finite in time,  Hence, assuming the environment has a finite size,
 animation functions returning   | 
Instances
The result of an interaction between an AnimatedPoint and its environment
 can trigger a mutation:
data InteractionResult Source #
Constructors
| Mutation | The   | 
| Stable | The   | 
Instances
AnimatedPoints live in a
      tree-like structure:
data AnimatedPoints Source #
Constructors
| AnimatedPoints | |
Fields 
  | |
Instances
Create
Arguments
| :: Coords Pos | Center of the root   | 
| -> [Coords Pos -> Frame -> [AnimatedPoint]] | List of animation functions. Every animation function generates
             The k-th animation function generates  Animation functions are expected to return the same number of   | 
| -> Speed | Animation discrete speed. Tells by how much the   | 
| -> (Coords Pos -> InteractionResult) | The environmental interaction function. During update,  During render,   | 
| -> Either SystemTime KeyTime | 
  | 
| -> Maybe Char | The default   | 
| -> Maybe Animation | Depending on animation functions, the created   | 
Creates an animation and initializes it by updating it once.
Predefined animations
Explosive
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 | 
  | 
| -> 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 | 
  | 
| -> 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).
Arguments
| :: Vec2 Vel | Initial speed  | 
| -> Coords Pos | Initial position  | 
| -> (Coords Pos -> InteractionResult) | Environment interaction function  | 
| -> Speed | Animation speed  | 
| -> Either SystemTime KeyTime | 
  | 
| -> Char | Character used when drawing the animation.  | 
| -> Maybe Animation | 
A gravity-based free-falling animation.
Arguments
| :: Vec2 Vel | Initial speed  | 
| -> Coords Pos | Initial position  | 
| -> (Coords Pos -> InteractionResult) | Environment interaction function  | 
| -> Speed | Animation speed  | 
| -> Either SystemTime KeyTime | 
  | 
| -> 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).
Arguments
| :: Vec2 Vel | Initial speed  | 
| -> Coords Pos | Initial position  | 
| -> (Coords Pos -> InteractionResult) | Environment interaction function  | 
| -> Speed | Animation speed  | 
| -> Either SystemTime KeyTime | 
  | 
| -> 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 | 
  | 
| -> 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
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 | 
  | 
| -> 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.
Arguments
| :: LaserRay Actual | The laser ray  | 
| -> (Coords Pos -> InteractionResult) | Environment interaction function  | 
| -> Either SystemTime KeyTime | 
  | 
| -> Maybe Animation | 
A laser ray animation, with a fade-out effect.
Nice chars
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.
Returns True if the KeyTime is beyond the Animation deadline or if the
time difference is within animationUpdateMargin. 
Render
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
module Imj.Iteration