Gamepad on touch screen bound to keyboard keys

Fires VirtualGamepadEvent which implement KeyEvent so it behaves like a keyboard.

Introduced properties

fun add_button(name: String, texture: Texture): nullable RoundButton

gamnit :: VirtualGamepad :: add_button

Add and return a round button to a default location
fun add_dpad(names: nullable Array[String]): nullable DPad

gamnit :: VirtualGamepad :: add_dpad

Add and return a directional pad (DPad) to a default location
fun controls: Array[RoundControl]

gamnit :: VirtualGamepad :: controls

Controls composing this gamepad
protected fun controls=(controls: Array[RoundControl])

gamnit :: VirtualGamepad :: controls=

Controls composing this gamepad
fun visible: Bool

gamnit :: VirtualGamepad :: visible

Is this control visible?
fun visible=(value: Bool)

gamnit :: VirtualGamepad :: visible=

Set this control to visible or not

Redefined properties

redef type SELF: VirtualGamepad

gamnit $ VirtualGamepad :: 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 add_button(name: String, texture: Texture): nullable RoundButton

gamnit :: VirtualGamepad :: add_button

Add and return a round button to a default location
fun add_dpad(names: nullable Array[String]): nullable DPad

gamnit :: VirtualGamepad :: add_dpad

Add and return a directional pad (DPad) to a default location
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.
fun controls: Array[RoundControl]

gamnit :: VirtualGamepad :: controls

Controls composing this gamepad
protected fun controls=(controls: Array[RoundControl])

gamnit :: VirtualGamepad :: controls=

Controls composing this gamepad
fun get_class: CLASS

core :: Object :: get_class

The meta-object representing the dynamic type of self.
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".
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.
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 serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
intern fun sys: Sys

core :: Object :: sys

Return the global sys object, the only instance of the Sys class.
abstract fun to_jvalue(env: JniEnv): JValue

core :: Object :: to_jvalue

fun to_s: String

core :: Object :: to_s

User readable representation of self.
fun visible: Bool

gamnit :: VirtualGamepad :: visible

Is this control visible?
fun visible=(value: Bool)

gamnit :: VirtualGamepad :: visible=

Set this control to visible or not
package_diagram gamnit::VirtualGamepad VirtualGamepad core::Object Object gamnit::VirtualGamepad->core::Object

Parents

interface Object

core :: Object

The root of the class hierarchy.

Class definitions

gamnit $ VirtualGamepad
# Gamepad on touch screen bound to keyboard keys
#
# Fires `VirtualGamepadEvent` which implement `KeyEvent` so it behaves like a keyboard.
class VirtualGamepad

	private var sprites = new Array[Sprite]

	# Controls composing this gamepad
	#
	# Controls can be added directly to this array or using `add_dpad`
	# and `add_button`.
	var controls = new Array[RoundControl]

	# Add and return a directional pad (`DPad`) to a default location
	#
	# The 4 buttons fire events with the corresponding name in `names`.
	# Items in `names` should be in order of top, left, down and right.
	# If `null`, defaults to WASD.
	#
	# If this method is called, it should be before `add_button` to
	# avoid overlapping controls.
	#
	# A maximum of 2 `DPad` may be added using this method.
	# The first `DPad` is placed on the left of the screen.
	# The second `DPad` is on the right and replaces some buttons
	# added by `add_button`.
	#
	# Require: `names == null or names.length == 4`
	fun add_dpad(names: nullable Array[String]): nullable DPad
	do
		if names == null then names = ["w","a","s","d"]
		assert names.length == 4

		if n_dpads == 0 then
			var dpad = new DPad(app.ui_camera.bottom_left.offset(200.0, 100.0, 0.0), names)
			controls.add dpad
			return dpad
		else if n_dpads == 1 then
			var dpad = new DPad(app.ui_camera.bottom_right.offset(-200.0, 100.0, 0.0), names)
			controls.add dpad
			return dpad
		else
			print_error "Too many DPad ({n_dpads}) in {self}"
			return null
		end
	end

	# Number of `DPad` in `controls`
	private fun n_dpads: Int
	do
		var n_dpads = 0
		for c in controls do if c isa DPad then n_dpads += 1
		return n_dpads
	end

	# Button positions for `add_button`, offsets from the bottom right
	private var button_positions = new Array[Point[Float]].with_items(
		new Point[Float](-150.0, 150.0),
		new Point[Float](-150.0, 350.0),
		new Point[Float](-150.0, 550.0),
		new Point[Float](-350.0, 150.0),
		new Point[Float](-350.0, 350.0),
		new Point[Float](-350.0, 550.0))

	# Add and return a round button to a default location
	#
	# Fired events use `name`, it should usually correspond to a
	# keyboard key like "space" or "a".
	# `texture` is displayed at the button position, it also sets the
	# touchable surface of the button.
	#
	# If this method is called, it should be after `add_dpad` to
	# avoid overlapping controls.
	#
	# A maximum of 6 buttons may be added using this method when
	# there is less than 2 `DPad`. Otherwise, only 2 buttons can be added.
	fun add_button(name: String, texture: Texture): nullable RoundButton
	do
		if n_dpads == 2 and button_positions.length == 6 then
			# Drop the bottom 4 buttons
			button_positions.remove_at 4
			button_positions.remove_at 3
			button_positions.remove_at 1
			button_positions.remove_at 0
		end

		assert button_positions.not_empty else print_error "Too many buttons in {self}"
		var pos = button_positions.shift
		var but = new RoundButton(
			app.ui_camera.bottom_right.offset(pos.x, pos.y, 0.0), name, texture)
		controls.add but
		return but
	end

	private fun prepare
	do
		var display = app.display
		assert display != null

		for control in controls do
			var sprites = control.sprites
			app.ui_sprites.add_all sprites
		end
	end

	# Is this control visible?
	var visible = false is private writable(visible_direct=)

	# Set this control to visible or not
	fun visible=(value: Bool)
	do
		visible_direct = value
		if value then show else hide
	end

	private fun show
	do
		if sprites.is_empty then prepare
		app.ui_sprites.add_all sprites
	end

	private fun hide do for s in sprites do app.ui_sprites.remove_all s

	private var control_under_pointer = new Map[Int, RoundControl]

	private fun accept_event(event: InputEvent): Bool
	do
		if not visible then return false

		var display = app.display
		if display == null then return false

		if event isa PointerEvent then
			var ui_pos = app.ui_camera.camera_to_ui(event.x, event.y)

			for control in controls do
				if control.accept_event(event, ui_pos) then
					var prev_control = control_under_pointer.get_or_null(event.pointer_id)
					if prev_control != null and prev_control != control then
						prev_control.depressed_down
					end
					control_under_pointer[event.pointer_id] = control
					return true
				end
			end

			var prev_control = control_under_pointer.get_or_null(event.pointer_id)
			if prev_control != null then prev_control.depressed_down
			control_under_pointer.keys.remove event.pointer_id
		end

		return false
	end
end
lib/gamnit/virtual_gamepad/virtual_gamepad.nit:76,1--229,3