Visible 2D entity in the game world or UI

Similar to Actor which is in 3D.

Each sprite associates a texture to the position center. The appearance is modified by rotation, invert_x, scale, red, green, blue and alpha. These values can be changed at any time and will trigger an update of the data on the GPU side, having a small performance cost.

For a sprite to be visible, it must be added to either the world sprites or the ui_sprites. However, an instance of Sprite can only belong to a single SpriteSet at a time. The final on-screen position depends on the camera associated to the SpriteSet.

var texture = new Texture("path/in/assets.png")
var sprite = new Sprite(texture, new Point3d[Float](0.0, 0.0, 0.0))

# Add sprite to the visible game world
app.sprites.add sprite

# Extra configuration of the sprite
sprite.rotation = pi/2.0
sprite.scale = 2.0

# Show only the blue colors
sprite.red = 0.0
sprite.green = 0.0

To add a sprite to the UI it can be anchored to screen borders with ui_camera.top_left and the likes.

var pos = app.ui_camera.top_left.offset(128.0, -128.0, 0)

# Load texture and create sprite
var texture = new Texture("path/in/assets.png")
var sprite = new Sprite(texture, pos)

# Add it to the UI (above world sprites)
app.ui_sprites.add sprite

Introduced properties

fun alpha: Float

gamnit :: Sprite :: alpha

Transparency applied to texture on draw
fun alpha=(value: Float)

gamnit :: Sprite :: alpha=

Transparency applied to texture on draw
fun animate(animation: Animation, n_loops: nullable Float)

gamnit :: Sprite :: animate

Start the animation for n_loops, replacing the static texture
fun animate_stop

gamnit :: Sprite :: animate_stop

Stop any active animation to display the static texture
fun animation: nullable Animation

gamnit :: Sprite :: animation

Last animation set with animate
protected fun animation=(animation: nullable Animation)

gamnit :: Sprite :: animation=

Last animation set with animate
fun blue: Float

gamnit :: Sprite :: blue

Blue tint applied to texture on draw
fun blue=(value: Float)

gamnit :: Sprite :: blue=

Blue tint applied to texture on draw
fun center: Point3d[Float]

gamnit :: Sprite :: center

Center position of this sprite in world coordinates
fun center=(center: Point3d[Float])

gamnit :: Sprite :: center=

Center position of this sprite in world coordinates
fun center_direct=(center: Point3d[Float])

gamnit :: Sprite :: center_direct=

Center position of this sprite in world coordinates
init defaultinit(texture: Texture, center: Point3d[Float])

gamnit :: Sprite :: defaultinit

fun draw_order: Int

gamnit :: Sprite :: draw_order

Draw order, higher values cause this sprite to be drawn latter
fun draw_order=(value: Int)

gamnit :: Sprite :: draw_order=

Set draw order, see draw_order
fun draw_order_direct=(draw_order: Int)

gamnit :: Sprite :: draw_order_direct=

Draw order, higher values cause this sprite to be drawn latter
fun green: Float

gamnit :: Sprite :: green

Green tint applied to texture on draw
fun green=(value: Float)

gamnit :: Sprite :: green=

Green tint applied to texture on draw
fun invert_x: Bool

gamnit :: Sprite :: invert_x

Mirror texture horizontally, inverting each pixel on the X axis
fun invert_x=(value: Bool)

gamnit :: Sprite :: invert_x=

Mirror texture horizontally, inverting each pixel on the X axis
fun invert_x_direct=(invert_x: Bool)

gamnit :: Sprite :: invert_x_direct=

Mirror texture horizontally, inverting each pixel on the X axis
fun needs_remap

gamnit :: Sprite :: needs_remap

Request a resorting of this sprite in its sprite list
fun needs_update

gamnit :: Sprite :: needs_update

Request an update on the CPU
fun red: Float

gamnit :: Sprite :: red

Red tint applied to texture on draw
fun red=(value: Float)

gamnit :: Sprite :: red=

Red tint applied to texture on draw
fun rotation: Float

gamnit :: Sprite :: rotation

Rotation on the Z axis, positive values turn counterclockwise
fun rotation=(value: Float)

gamnit :: Sprite :: rotation=

Rotation on the Z axis, positive values turn counterclockwise
fun rotation_direct=(rotation: Float)

gamnit :: Sprite :: rotation_direct=

Rotation on the Z axis, positive values turn counterclockwise
fun scale: Float

gamnit :: Sprite :: scale

Scale applied to this sprite
fun scale=(value: Float)

gamnit :: Sprite :: scale=

Scale applied to this sprite
fun scale_direct=(scale: Float)

gamnit :: Sprite :: scale_direct=

Scale applied to this sprite
fun static: Bool

gamnit :: Sprite :: static

Is this sprite static and added in bulk?
fun static=(value: Bool)

gamnit :: Sprite :: static=

Is this sprite static and added in bulk? see static
fun static_direct=(static: Bool)

gamnit :: Sprite :: static_direct=

Is this sprite static and added in bulk?
fun texture: Texture

gamnit :: Sprite :: texture

Texture drawn to screen
fun texture=(texture: Texture)

gamnit :: Sprite :: texture=

Texture drawn to screen
fun texture_direct=(texture: Texture)

gamnit :: Sprite :: texture_direct=

Texture drawn to screen
fun tint: Array[Float]

gamnit :: Sprite :: tint

Tint applied to texture on draw
fun tint=(value: Array[Float])

gamnit :: Sprite :: tint=

Tint applied to texture on draw, see tint
fun tint_direct=(tint: Array[Float])

gamnit :: Sprite :: tint_direct=

Tint applied to texture on draw

Redefined properties

redef type SELF: Sprite

gamnit $ Sprite :: SELF

Type of this instance, automatically specialized in every class

All properties

fun !=(other: nullable Object): Bool

core :: Object :: !=

Have self and other different values?
fun ==(other: nullable Object): Bool

core :: Object :: ==

Have self and other the same value?
type CLASS: Class[SELF]

core :: Object :: CLASS

The type of the class of self.
type SELF: Object

core :: Object :: SELF

Type of this instance, automatically specialized in every class
fun alpha: Float

gamnit :: Sprite :: alpha

Transparency applied to texture on draw
fun alpha=(value: Float)

gamnit :: Sprite :: alpha=

Transparency applied to texture on draw
fun animate(animation: Animation, n_loops: nullable Float)

gamnit :: Sprite :: animate

Start the animation for n_loops, replacing the static texture
fun animate_stop

gamnit :: Sprite :: animate_stop

Stop any active animation to display the static texture
fun animation: nullable Animation

gamnit :: Sprite :: animation

Last animation set with animate
protected fun animation=(animation: nullable Animation)

gamnit :: Sprite :: animation=

Last animation set with animate
fun blue: Float

gamnit :: Sprite :: blue

Blue tint applied to texture on draw
fun blue=(value: Float)

gamnit :: Sprite :: blue=

Blue tint applied to texture on draw
fun center: Point3d[Float]

gamnit :: Sprite :: center

Center position of this sprite in world coordinates
fun center=(center: Point3d[Float])

gamnit :: Sprite :: center=

Center position of this sprite in world coordinates
fun center_direct=(center: Point3d[Float])

gamnit :: Sprite :: center_direct=

Center position of this sprite in world coordinates
protected fun class_factory(name: String): CLASS

core :: Object :: class_factory

Implementation used by get_class to create the specific class.
fun class_name: String

core :: Object :: class_name

The class name of the object.
init defaultinit(texture: Texture, center: Point3d[Float])

gamnit :: Sprite :: defaultinit

fun draw_order: Int

gamnit :: Sprite :: draw_order

Draw order, higher values cause this sprite to be drawn latter
fun draw_order=(value: Int)

gamnit :: Sprite :: draw_order=

Set draw order, see draw_order
fun draw_order_direct=(draw_order: Int)

gamnit :: Sprite :: draw_order_direct=

Draw order, higher values cause this sprite to be drawn latter
fun get_class: CLASS

core :: Object :: get_class

The meta-object representing the dynamic type of self.
fun green: Float

gamnit :: Sprite :: green

Green tint applied to texture on draw
fun green=(value: Float)

gamnit :: Sprite :: green=

Green tint applied to texture on draw
fun hash: Int

core :: Object :: hash

The hash code of the object.
init init

core :: Object :: init

fun inspect: String

core :: Object :: inspect

Developer readable representation of self.
protected fun inspect_head: String

core :: Object :: inspect_head

Return "CLASSNAME:#OBJECTID".
fun invert_x: Bool

gamnit :: Sprite :: invert_x

Mirror texture horizontally, inverting each pixel on the X axis
fun invert_x=(value: Bool)

gamnit :: Sprite :: invert_x=

Mirror texture horizontally, inverting each pixel on the X axis
fun invert_x_direct=(invert_x: Bool)

gamnit :: Sprite :: invert_x_direct=

Mirror texture horizontally, inverting each pixel on the X axis
intern fun is_same_instance(other: nullable Object): Bool

core :: Object :: is_same_instance

Return true if self and other are the same instance (i.e. same identity).
fun is_same_serialized(other: nullable Object): Bool

core :: Object :: is_same_serialized

Is self the same as other in a serialization context?
intern fun is_same_type(other: Object): Bool

core :: Object :: is_same_type

Return true if self and other have the same dynamic type.
fun needs_remap

gamnit :: Sprite :: needs_remap

Request a resorting of this sprite in its sprite list
fun needs_update

gamnit :: Sprite :: needs_update

Request an update on the CPU
intern fun object_id: Int

core :: Object :: object_id

An internal hash code for the object based on its identity.
fun output

core :: Object :: output

Display self on stdout (debug only).
intern fun output_class_name

core :: Object :: output_class_name

Display class name on stdout (debug only).
fun red: Float

gamnit :: Sprite :: red

Red tint applied to texture on draw
fun red=(value: Float)

gamnit :: Sprite :: red=

Red tint applied to texture on draw
fun rotation: Float

gamnit :: Sprite :: rotation

Rotation on the Z axis, positive values turn counterclockwise
fun rotation=(value: Float)

gamnit :: Sprite :: rotation=

Rotation on the Z axis, positive values turn counterclockwise
fun rotation_direct=(rotation: Float)

gamnit :: Sprite :: rotation_direct=

Rotation on the Z axis, positive values turn counterclockwise
fun scale: Float

gamnit :: Sprite :: scale

Scale applied to this sprite
fun scale=(value: Float)

gamnit :: Sprite :: scale=

Scale applied to this sprite
fun scale_direct=(scale: Float)

gamnit :: Sprite :: scale_direct=

Scale applied to this sprite
fun serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
fun static: Bool

gamnit :: Sprite :: static

Is this sprite static and added in bulk?
fun static=(value: Bool)

gamnit :: Sprite :: static=

Is this sprite static and added in bulk? see static
fun static_direct=(static: Bool)

gamnit :: Sprite :: static_direct=

Is this sprite static and added in bulk?
intern fun sys: Sys

core :: Object :: sys

Return the global sys object, the only instance of the Sys class.
fun texture: Texture

gamnit :: Sprite :: texture

Texture drawn to screen
fun texture=(texture: Texture)

gamnit :: Sprite :: texture=

Texture drawn to screen
fun texture_direct=(texture: Texture)

gamnit :: Sprite :: texture_direct=

Texture drawn to screen
fun tint: Array[Float]

gamnit :: Sprite :: tint

Tint applied to texture on draw
fun tint=(value: Array[Float])

gamnit :: Sprite :: tint=

Tint applied to texture on draw, see tint
fun tint_direct=(tint: Array[Float])

gamnit :: Sprite :: tint_direct=

Tint applied to texture on draw
abstract fun to_jvalue(env: JniEnv): JValue

core :: Object :: to_jvalue

fun to_s: String

core :: Object :: to_s

User readable representation of self.
package_diagram gamnit::Sprite Sprite core::Object Object gamnit::Sprite->core::Object

Parents

interface Object

core :: Object

The root of the class hierarchy.

Class definitions

gamnit $ Sprite
# Visible 2D entity in the game world or UI
#
# Similar to `gamnit::Actor` which is in 3D.
#
# Each sprite associates a `texture` to the position `center`.
# The appearance is modified by `rotation`, `invert_x`,
# `scale`, `red`, `green`, `blue` and `alpha`.
# These values can be changed at any time and will trigger an update
# of the data on the GPU side, having a small performance cost.
#
# For a sprite to be visible, it must be added to either the world `sprites`
# or the `ui_sprites`.
# However, an instance of `Sprite` can only belong to a single `SpriteSet`
# at a time. The final on-screen position depends on the camera associated
# to the `SpriteSet`.
#
# ~~~
# # Load texture and create sprite
# var texture = new Texture("path/in/assets.png")
# var sprite = new Sprite(texture, new Point3d[Float](0.0, 0.0, 0.0))
#
# # Add sprite to the visible game world
# app.sprites.add sprite
#
# # Extra configuration of the sprite
# sprite.rotation = pi/2.0
# sprite.scale = 2.0
#
# # Show only the blue colors
# sprite.red = 0.0
# sprite.green = 0.0
# ~~~
#
# To add a sprite to the UI it can be anchored to screen borders
# with `ui_camera.top_left` and the likes.
#
# ~~~nitish
# # Place it a bit off the top left of the screen
# var pos = app.ui_camera.top_left.offset(128.0, -128.0, 0)
#
# # Load texture and create sprite
# var texture = new Texture("path/in/assets.png")
# var sprite = new Sprite(texture, pos)
#
# # Add it to the UI (above world sprites)
# app.ui_sprites.add sprite
# ~~~
class Sprite

	# Texture drawn to screen
	var texture: Texture is writable(texture_direct=)

	# Texture drawn to screen
	fun texture=(texture: Texture)
	do
		if isset _texture and texture != self.texture then
			needs_update
			if texture.root != self.texture.root then needs_remap
		end
		texture_direct = texture
	end

	# Center position of this sprite in world coordinates
	var center: Point3d[Float] is writable(center_direct=), noautoinit

	# Center position of this sprite in world coordinates
	fun center=(center: Point3d[Float]) is autoinit do
		if isset _center and center != self.center then
			needs_update
			self.center.sprites_remove self
		end

		center.sprites_add self
		center_direct = center
	end

	# Last animation set with `animate`
	var animation: nullable Animation = null

	# Animation on the shader, if this changes it `needs_remap`
	private var shader_animation: nullable Animation = null

	# Animation start time, relative to `sprite_set.time`
	#
	# At -1.0 if animation started before being assigned a `sprite_set`.
	private var animation_start = 0.0

	# Number of loops to show `animation`
	private var animation_loops = 0.0

	# Start the `animation` for `n_loops`, replacing the static `texture`
	#
	# By default, if `n_loops` is not set, the animation plays once.
	# If `n_loops == -1.0` then the animation loops infinitely.
	# Otherwise, the animation repeats, e.g. it repeats twice and a half
	# if `n_loops == 2.5`.
	#
	# The animation can be stopped using `animate_stop`.
	fun animate(animation: Animation, n_loops: nullable Float)
	do
		if not animation.valid then print_error "{class_name}::animate: invalid animation {animation}"

		var shader_animation = shader_animation
		if shader_animation == null or animation.frames.first.root != shader_animation.frames.first.root then
			# Resort with the new animation texture
			needs_remap
		else
			needs_update
		end

		var sprite_set = sprite_set
		animation_start = if sprite_set != null then sprite_set.time else -1.0
		animation_loops = n_loops or else 1.0
		self.shader_animation = animation
		self.animation = animation
	end

	# Stop any active `animation` to display the static `texture`
	fun animate_stop
	do
		if animation == null then return
		needs_update
		animation = null
	end

	# Rotation on the Z axis, positive values turn counterclockwise
	var rotation = 0.0 is writable(rotation_direct=)

	# Rotation on the Z axis, positive values turn counterclockwise
	fun rotation=(value: Float)
	do
		if isset _rotation and value != rotation then needs_update
		rotation_direct = value
	end

	# Mirror `texture` horizontally, inverting each pixel on the X axis
	var invert_x = false is writable(invert_x_direct=)

	# Mirror `texture` horizontally, inverting each pixel on the X axis
	fun invert_x=(value: Bool)
	do
		if isset _invert_x and value != invert_x then needs_update
		invert_x_direct = value
	end

	# Scale applied to this sprite
	#
	# The basic size of `self` depends on the size in pixels of `texture`.
	var scale = 1.0 is writable(scale_direct=)

	# Scale applied to this sprite
	#
	# The basic size of `self` depends on the size in pixels of `texture`.
	fun scale=(value: Float)
	do
		if isset _scale and value != scale then needs_update
		scale_direct = value
	end

	# Red tint applied to `texture` on draw
	fun red: Float do return tint[0]

	# Red tint applied to `texture` on draw
	fun red=(value: Float)
	do
		if isset _tint and value != red then needs_update
		tint[0] = value
	end

	# Green tint applied to `texture` on draw
	fun green: Float do return tint[1]

	# Green tint applied to `texture` on draw
	fun green=(value: Float)
	do
		if isset _tint and value != green then needs_update
		tint[1] = value
	end

	# Blue tint applied to `texture` on draw
	fun blue: Float do return tint[2]

	# Blue tint applied to `texture` on draw
	fun blue=(value: Float)
	do
		if isset _tint and value != blue then needs_update
		tint[2] = value
	end

	# Transparency applied to `texture` on draw
	fun alpha: Float do return tint[3]

	# Transparency applied to `texture` on draw
	fun alpha=(value: Float)
	do
		if isset _tint and value != alpha then needs_update
		tint[3] = value
	end

	# Tint applied to `texture` on draw
	#
	# Alternative to the accessors `red, green, blue & alpha`.
	# Changes inside the array do not automatically set `needs_update`.
	#
	# Require: `tint.length == 4`
	var tint: Array[Float] = [1.0, 1.0, 1.0, 1.0] is writable(tint_direct=)

	# Tint applied to `texture` on draw, see `tint`
	fun tint=(value: Array[Float])
	do
		if isset _tint and value != tint then needs_update
		tint_direct = value
	end

	# Draw order, higher values cause this sprite to be drawn latter
	#
	# Change this value to avoid artifacts when drawing non-opaque sprites.
	# In general, sprites with a non-opaque `texture` and sprites closer to
	# the camera should have a higher value to be drawn last.
	#
	# Sprites sharing a `draw_order` are drawn in the same pass.
	# The sprite to sprite draw order is undefined and may change when adding
	# and removing sprites, or changing their attributes.
	#
	# ### Warning
	#
	# Changing this value may have a negative performance impact if there are
	# many different `draw_order` values across many sprites.
	# Sprites sharing some attributes are drawn as group to reduce
	# the communication overhead between the CPU and GPU,
	# and changing `draw_order` may break up large groups into smaller groups.
	var draw_order = 0 is writable(draw_order_direct=)

	# Set draw order,  see `draw_order`
	fun draw_order=(value: Int)
	do
		if isset _draw_order and value != draw_order then needs_remap
		draw_order_direct = value
	end

	# Is this sprite static and added in bulk?
	#
	# Set to `true` to give a hint to the framework that this sprite won't
	# change often and that it is added in bulk with other static sprites.
	# This value can be ignored in the prototyping phase of a game and
	# added only when better performance are needed.
	var static = false is writable(static_direct=)

	# Is this sprite static and added in bulk? see `static`
	fun static=(value: Bool)
	do
		if isset _static and value != static then needs_remap
		static_direct = value
	end

	# Request an update on the CPU
	#
	# This is called automatically on modification of any value of `Sprite`.
	# However, it can still be set manually if a modification can't be
	# detected or by subclasses.
	fun needs_update
	do
		var c = context
		if c == null then return
		if c.last_sprite_to_update == self then return
		c.sprites_to_update.add self
		c.last_sprite_to_update = self
	end

	# Request a resorting of this sprite in its sprite list
	#
	# Resorting is required when `static` or the root of `texture` changes.
	# This is called automatically when such changes are detected.
	# However, it can still be set manually if a modification can't be
	# detected or by subclasses.
	fun needs_remap
	do
		var l = sprite_set
		if l != null then l.sprites_to_remap.add self
	end

	# Current context to which `self` was sorted
	private var context: nullable SpriteContext = null

	# Index in `context`
	private var context_index: Int = -1

	# Current context to which `self` belongs
	private var sprite_set: nullable SpriteSet = null
end
lib/gamnit/flat/flat_core.nit:30,1--319,3