Services to keep time of the wall clock time

Introduced classes

class Clock

realtime :: Clock

Keeps track of real time

All class definitions

class Clock

realtime $ Clock

Keeps track of real time
package_diagram realtime::realtime realtime core core realtime::realtime->core ai::search search ai::search->realtime::realtime gamnit::gamnit_android gamnit_android gamnit::gamnit_android->realtime::realtime performance_analysis::performance_analysis performance_analysis performance_analysis::performance_analysis->realtime::realtime gamnit::limit_fps limit_fps gamnit::limit_fps->realtime::realtime popcorn::pop_logging pop_logging popcorn::pop_logging->realtime::realtime glesv2::opengles2_hello_triangle opengles2_hello_triangle glesv2::opengles2_hello_triangle->realtime::realtime ai::puzzle puzzle ai::puzzle->ai::search ai::puzzle... ... ai::puzzle...->ai::puzzle android::sensors sensors android::sensors->gamnit::gamnit_android gamnit::android19 android19 gamnit::android19->gamnit::gamnit_android gamnit::camera_control_android camera_control_android gamnit::camera_control_android->gamnit::gamnit_android android::sensors... ... android::sensors...->android::sensors gamnit::android19... ... gamnit::android19...->gamnit::android19 gamnit::camera_control_android... ... gamnit::camera_control_android...->gamnit::camera_control_android gamnit::dynamic_resolution dynamic_resolution gamnit::dynamic_resolution->performance_analysis::performance_analysis nitcorn::log log nitcorn::log->performance_analysis::performance_analysis gamnit::dynamic_resolution... ... gamnit::dynamic_resolution...->gamnit::dynamic_resolution nitcorn::log... ... nitcorn::log...->nitcorn::log gamnit::flat flat gamnit::flat->gamnit::limit_fps gamnit::flat... ... gamnit::flat...->gamnit::flat github::loader loader github::loader->popcorn::pop_logging popcorn::popcorn popcorn popcorn::popcorn->popcorn::pop_logging github::loader... ... github::loader...->github::loader popcorn::popcorn... ... popcorn::popcorn...->popcorn::popcorn a_star-m a_star-m a_star-m->glesv2::opengles2_hello_triangle a_star-m... ... a_star-m...->a_star-m

Ancestors

module abstract_collection

core :: abstract_collection

Abstract collection classes and services.
module abstract_text

core :: abstract_text

Abstract class for manipulation of sequences of characters
module array

core :: array

This module introduces the standard array structure.
module bitset

core :: bitset

Services to handle BitSet
module bytes

core :: bytes

Services for byte streams and arrays
module circular_array

core :: circular_array

Efficient data structure to access both end of the sequence.
module codec_base

core :: codec_base

Base for codecs to use with streams
module codecs

core :: codecs

Group module for all codec-related manipulations
module collection

core :: collection

This module define several collection classes.
module environ

core :: environ

Access to the environment variables of the process
module error

core :: error

Standard error-management infrastructure.
module exec

core :: exec

Invocation and management of operating system sub-processes.
module file

core :: file

File manipulations (create, read, write, etc.)
module fixed_ints

core :: fixed_ints

Basic integers of fixed-precision
module fixed_ints_text

core :: fixed_ints_text

Text services to complement fixed_ints
module flat

core :: flat

All the array-based text representations
module gc

core :: gc

Access to the Nit internal garbage collection mechanism
module hash_collection

core :: hash_collection

Introduce HashMap and HashSet.
module iso8859_1

core :: iso8859_1

Codec for ISO8859-1 I/O
module kernel

core :: kernel

Most basic classes and methods.
module list

core :: list

This module handle double linked lists
module math

core :: math

Mathematical operations
module native

core :: native

Native structures for text and bytes
module numeric

core :: numeric

Advanced services for Numeric types
module protocol

core :: protocol

module queue

core :: queue

Queuing data structures and wrappers
module range

core :: range

Module for range of discrete objects.
module re

core :: re

Regular expression support for all services based on Pattern
module ropes

core :: ropes

Tree-based representation of a String.
module sorter

core :: sorter

This module contains classes used to compare things and sorts arrays.
module stream

core :: stream

Input and output streams of characters
module text

core :: text

All the classes and methods related to the manipulation of text entities
module time

core :: time

Management of time and dates
module union_find

core :: union_find

union–find algorithm using an efficient disjoint-set data structure
module utf8

core :: utf8

Codec for UTF-8 I/O

Parents

module core

core :: core

Standard classes and methods used by default by Nit programs and libraries.

Children

module gamnit_android

gamnit :: gamnit_android

Support services for Gamnit on Android
module limit_fps

gamnit :: limit_fps

Frame-rate control for applications
module opengles2_hello_triangle

glesv2 :: opengles2_hello_triangle

Basic example of OpenGL ES 2.0 usage using SDL 2
module performance_analysis

performance_analysis :: performance_analysis

Services to gather information on the performance of events by categories
module search

ai :: search

Basic framework for search problems and solver.

Descendants

module a_star-m

a_star-m

module android19

gamnit :: android19

Variation using features from Android API 19
module bmfont

gamnit :: bmfont

Parse Angel Code BMFont format and draw text
module camera_control_android

gamnit :: camera_control_android

Two fingers camera manipulation, pinch to zoom and slide to scroll
module cardboard

gamnit :: cardboard

Update the orientation of world_camera at each frame using the head position given by android::cardboard
module depth

gamnit :: depth

Framework for 3D games in Nit
module depth_core

gamnit :: depth_core

Base entities of the depth 3D game framework
module dynamic_resolution

gamnit :: dynamic_resolution

Virtual screen with a resolution independent from the real screen
module example_angular

popcorn :: example_angular

This is an example of how to use angular.js with popcorn
module flat

gamnit :: flat

Simple API for 2D games, built around Sprite and App::update
module flat_core

gamnit :: flat_core

Core services for the flat API for 2D games
module font

gamnit :: font

Abstract font drawing services, implemented by bmfont and tileset
module loader

github :: loader

module log

nitcorn :: log

Services inserting a timestamp in all prints and to log each requests
module model_dimensions

gamnit :: model_dimensions

Dimensions related services for Model and Mesh
module more_lights

gamnit :: more_lights

More implementations of Light
module more_materials

gamnit :: more_materials

Various material implementations
module more_meshes

gamnit :: more_meshes

More simple geometric meshes
module more_models

gamnit :: more_models

Services to load models from the assets folder
module particles

gamnit :: particles

Particle effects
module pop_tests

popcorn :: pop_tests

Popcorn testing services
module popcorn

popcorn :: popcorn

Application server abstraction on top of nitcorn.
module puzzle

ai :: puzzle

The N-puzzle problem, modeled naively as a SearchProblem.
module selection

gamnit :: selection

Select Actor from a screen coordinate
module sensors

android :: sensors

Access Android sensors
module shadow

gamnit :: shadow

Shadow mapping using a depth texture
module stereoscopic_view

gamnit :: stereoscopic_view

Refine EulerCamera and App::frame_core_draw to get a stereoscopic view
module tileset

gamnit :: tileset

Support for TileSet, TileSetFont and drawing text with TextSprites
module virtual_gamepad

gamnit :: virtual_gamepad

Virtual gamepad mapped to keyboard keys for quick and dirty mobile support
module vr

gamnit :: vr

VR support for gamnit depth, for Android only
# Services to keep time of the wall clock time
module realtime is ldflags "-lrt"

in "C header" `{
#ifdef _POSIX_C_SOURCE
	#undef _POSIX_C_SOURCE
#endif
#define _POSIX_C_SOURCE 199309L
#include <time.h>
`}

in "C" `{

#ifdef __APPLE__
	#include <TargetConditionals.h>
	#if defined(TARGET_OS_IPHONE) && __IPHONE_OS_VERSION_MIN_REQUIRED < 100000
		// Preserve compatibility with pre-iOS 10 devices where there is no clock_get_time.
		#undef CLOCK_REALTIME
	#endif
#endif

#if (defined(__MACH__) || defined(TARGET_OS_IPHONE)) && !defined(CLOCK_REALTIME)
/* OS X does not have clock_gettime, mascarade it and use clock_get_time
 * cf http://stackoverflow.com/questions/11680461/monotonic-clock-on-osx
*/
#include <mach/clock.h>
#include <mach/mach.h>
#undef CLOCK_REALTIME
#undef CLOCK_MONOTONIC
#define CLOCK_REALTIME CALENDAR_CLOCK
#define CLOCK_MONOTONIC SYSTEM_CLOCK
void nit_clock_gettime(clock_t clock_name, struct timespec *ts) {
	clock_serv_t cclock;
	mach_timespec_t mts;
	host_get_clock_service(mach_host_self(), clock_name, &cclock);
	clock_get_time(cclock, &mts);
	mach_port_deallocate(mach_task_self(), cclock);
	ts->tv_sec = mts.tv_sec;
	ts->tv_nsec = mts.tv_nsec;
}
#else
	#define nit_clock_gettime clock_gettime
#endif
`}

# Elapsed time representation.
private extern class Timespec `{struct timespec*`}

	# Init a new Timespec from `s` seconds and `ns` nanoseconds.
	new ( s, ns : Int ) `{
		struct timespec* tv = malloc( sizeof(struct timespec) );
		tv->tv_sec = s; tv->tv_nsec = ns;
		return tv;
	`}

	# Init a new Timespec from now.
	new monotonic_now `{
		struct timespec* tv = malloc( sizeof(struct timespec) );
		nit_clock_gettime( CLOCK_MONOTONIC, tv );
		return tv;
	`}

	# Init a new Timespec copied from another.
	new copy_of( other : Timespec ) `{
		struct timespec* tv = malloc( sizeof(struct timespec) );
		tv->tv_sec = other->tv_sec;
		tv->tv_nsec = other->tv_nsec;
		return tv;
	`}

	# Update `self` clock.
	fun update `{
		nit_clock_gettime(CLOCK_MONOTONIC, self);
	`}

	# Subtract `other` from `self`
	fun -(other: Timespec): Timespec `{
		time_t s = self->tv_sec - other->tv_sec;
		long ns = self->tv_nsec - other->tv_nsec;
		if (ns < 0) {
			s -= 1;
			ns += 1000000000l;
		}
		struct timespec* tv = malloc(sizeof(struct timespec));
		tv->tv_sec = s; tv->tv_nsec = ns;
		return tv;
	`}

	# Set `self` to `a` - `b`
	fun minus(a, b: Timespec) `{
		time_t s = a->tv_sec - b->tv_sec;
		long ns = a->tv_nsec - b->tv_nsec;
		if (ns < 0) {
			s -= 1;
			ns += 1000000000l;
		}
		self->tv_sec = s;
		self->tv_nsec = ns;
	`}

	# Number of whole seconds of elapsed time.
	fun sec : Int `{
		return self->tv_sec;
	`}

	# Rest of the elapsed time (a fraction of a second).
	#
	# Number of nanoseconds.
	fun nanosec : Int `{
		return self->tv_nsec;
	`}

	# Elapsed time in microseconds, with both whole seconds and the rest
	#
	# May cause an `Int` overflow, use only with a low number of seconds.
	fun microsec: Int `{
		return self->tv_sec*1000000 + self->tv_nsec/1000;
	`}

	# Elapsed time in milliseconds, with both whole seconds and the rest
	#
	# May cause an `Int` overflow, use only with a low number of seconds.
	fun millisec: Int `{
		return self->tv_sec*1000 + self->tv_nsec/1000000;
	`}

	# Number of seconds as a `Float`
	#
	# Incurs a loss of precision, but the result is pretty to print.
	fun to_f: Float `{
		return (double)self->tv_sec + 0.000000001 * self->tv_nsec;
	`}

	redef fun to_s do return "{to_f}s"
end

# Keeps track of real time
#
# ~~~
# var clock = new Clock
#
# # sleeping at least 1s
# 1.0.sleep
# assert clock.total >= 1.0
# assert clock.lapse >= 1.0
#
# # sleeping at least 5ms
# 0.005.sleep
# assert clock.total >= 1.005
# assert clock.lapse >= 0.005
# ~~~
class Clock
	super FinalizableOnce

	# TODO use less mallocs

	# Time at creation
	private var time_at_beginning = new Timespec.monotonic_now

	# Time at last time a lapse method was called
	private var time_at_last_lapse = new Timespec.monotonic_now

	private var temp = new Timespec.monotonic_now

	# Smallest time frame reported by clock
	private fun resolution: Timespec `{
		struct timespec* tv = malloc( sizeof(struct timespec) );
#if (defined(__MACH__) || defined(TARGET_OS_IPHONE)) && !defined(CLOCK_REALTIME)
		clock_serv_t cclock;
		int nsecs;
		mach_msg_type_number_t count;
		host_get_clock_service(mach_host_self(), SYSTEM_CLOCK, &cclock);
		clock_get_attributes(cclock, CLOCK_GET_TIME_RES, (clock_attr_t)&nsecs, &count);
		mach_port_deallocate(mach_task_self(), cclock);
		tv->tv_sec = 0;
		tv->tv_nsec = nsecs;
#else
		clock_getres( CLOCK_MONOTONIC, tv );
#endif
		return tv;
	`}

	# Seconds since the creation of this instance
	fun total: Float
	do
		var now = temp
		now.update
		now.minus(now, time_at_beginning)
		return now.to_f
	end

	# Seconds since the last call to `lapse`
	fun lapse: Float
	do
		var time_at_last_lapse = time_at_last_lapse
		var now = temp
		now.update
		time_at_last_lapse.minus(now, time_at_last_lapse)
		var r = time_at_last_lapse.to_f

		self.temp = time_at_last_lapse
		self.time_at_last_lapse = now

		return r
	end

	# Seconds since the last call to `lapse`, without resetting the lapse counter
	fun peek_lapse: Float
	do
		var now = temp
		now.update
		now.minus(now, time_at_last_lapse)
		return now.to_f
	end

	redef fun finalize_once
	do
		time_at_beginning.free
		time_at_last_lapse.free
		temp.free
	end
end
lib/realtime/realtime.nit:13,1--234,3