Introduces thread-safe concurrent collections

This module offers new thread-safe collections. If you want to render basic collections thread-safe and don't mind the overhead cost, you can use threads::redef_collections.

Concurrent collections:

Introduced collections specialize their critical methods according to the current implementation in the standard library. If additional services are added to the underlying collections by refinement or evolution, they might need to be covered in the concurrent version.

Introduced classes

class BlockingQueue[E: nullable Object]

pthreads :: BlockingQueue

A Blocking queue implemented from a ConcurrentList
class ConcurrentArray[E: nullable Object]

pthreads :: ConcurrentArray

A concurrent variant to the standard Array
abstract class ConcurrentCollection[E: nullable Object]

pthreads :: ConcurrentCollection

A concurrent variant to the standard Collection
class ConcurrentList[E: nullable Object]

pthreads :: ConcurrentList

A concurrent variant to the standard List
abstract class ConcurrentSequence[E: nullable Object]

pthreads :: ConcurrentSequence

A concurrent variant to the standard Sequence
abstract class ConcurrentSequenceRead[E: nullable Object]

pthreads :: ConcurrentSequenceRead

A concurrent variant to the standard SequenceRead
class ReverseBlockingQueue[E: nullable Object]

pthreads :: ReverseBlockingQueue

A collection which is_empty method blocks until it's empty

Redefined classes

redef class Array[E: nullable Object]

pthreads :: concurrent_collections $ Array

Resizable one dimension array of objects.
redef interface Collection[E: nullable Object]

pthreads :: concurrent_collections $ Collection

The root of the collection hierarchy.
redef class List[E: nullable Object]

pthreads :: concurrent_collections $ List

Double linked lists.
redef interface Sequence[E: nullable Object]

pthreads :: concurrent_collections $ Sequence

Sequence are indexed collection.
redef interface SequenceRead[E: nullable Object]

pthreads :: concurrent_collections $ SequenceRead

Sequences are indexed collections.

All class definitions

redef class Array[E: nullable Object]

pthreads :: concurrent_collections $ Array

Resizable one dimension array of objects.
class BlockingQueue[E: nullable Object]

pthreads $ BlockingQueue

A Blocking queue implemented from a ConcurrentList
redef interface Collection[E: nullable Object]

pthreads :: concurrent_collections $ Collection

The root of the collection hierarchy.
class ConcurrentArray[E: nullable Object]

pthreads $ ConcurrentArray

A concurrent variant to the standard Array
abstract class ConcurrentCollection[E: nullable Object]

pthreads $ ConcurrentCollection

A concurrent variant to the standard Collection
class ConcurrentList[E: nullable Object]

pthreads $ ConcurrentList

A concurrent variant to the standard List
abstract class ConcurrentSequence[E: nullable Object]

pthreads $ ConcurrentSequence

A concurrent variant to the standard Sequence
abstract class ConcurrentSequenceRead[E: nullable Object]

pthreads $ ConcurrentSequenceRead

A concurrent variant to the standard SequenceRead
redef class List[E: nullable Object]

pthreads :: concurrent_collections $ List

Double linked lists.
class ReverseBlockingQueue[E: nullable Object]

pthreads $ ReverseBlockingQueue

A collection which is_empty method blocks until it's empty
redef interface Sequence[E: nullable Object]

pthreads :: concurrent_collections $ Sequence

Sequence are indexed collection.
redef interface SequenceRead[E: nullable Object]

pthreads :: concurrent_collections $ SequenceRead

Sequences are indexed collections.
package_diagram pthreads::concurrent_collections concurrent_collections pthreads pthreads pthreads::concurrent_collections->pthreads core core pthreads->core ...core ... ...core->core actors::actors actors actors::actors->pthreads::concurrent_collections pthreads::threadpool threadpool pthreads::threadpool->pthreads::concurrent_collections pthreads::concurrent_array_and_barrier concurrent_array_and_barrier pthreads::concurrent_array_and_barrier->pthreads::concurrent_collections actors::agent_simulation agent_simulation actors::agent_simulation->actors::actors actors::chameneosredux chameneosredux actors::chameneosredux->actors::actors actors::fannkuchredux fannkuchredux actors::fannkuchredux->actors::actors actors::mandelbrot mandelbrot actors::mandelbrot->actors::actors actors::simple simple actors::simple->actors::actors actors::thread_ring thread_ring actors::thread_ring->actors::actors actors::agent_simulation... ... actors::agent_simulation...->actors::agent_simulation actors::chameneosredux... ... actors::chameneosredux...->actors::chameneosredux actors::fannkuchredux... ... actors::fannkuchredux...->actors::fannkuchredux actors::mandelbrot... ... actors::mandelbrot...->actors::mandelbrot actors::simple... ... actors::simple...->actors::simple actors::thread_ring... ... actors::thread_ring...->actors::thread_ring nitcorn::restful restful nitcorn::restful->pthreads::threadpool pthreads::jointask_example jointask_example pthreads::jointask_example->pthreads::threadpool pthreads::threadpool_example threadpool_example pthreads::threadpool_example->pthreads::threadpool nitcorn::restful... ... nitcorn::restful...->nitcorn::restful pthreads::jointask_example... ... pthreads::jointask_example...->pthreads::jointask_example pthreads::threadpool_example... ... pthreads::threadpool_example...->pthreads::threadpool_example a_star-m a_star-m a_star-m->pthreads::concurrent_array_and_barrier 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 core

core :: core

Standard classes and methods used by default by Nit programs and libraries.
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 pthreads

pthreads :: pthreads

Main POSIX threads support and intro the classes Thread, Mutex and Barrier

Children

module actors

actors :: actors

Abstraction of the actors concepts
module concurrent_array_and_barrier

pthreads :: concurrent_array_and_barrier

A basic usage example of the modules pthreads and pthreads::cocurrent_collections
module threadpool

pthreads :: threadpool

Introduces a minimal ThreadPool implementation using Tasks

Descendants

module a_star-m

a_star-m

module agent_simulation

actors :: agent_simulation

a "Framework" to make Multi-Agent Simulations in Nit
module chameneosredux

actors :: chameneosredux

Example implemented from "The computer Language Benchmarks Game" - Chameneos-Redux
module fannkuchredux

actors :: fannkuchredux

Example implemented from "The computer Language Benchmarks Game" - Fannkuch-Redux
module jointask_example

pthreads :: jointask_example

Simple example of joinable task using threadpool
module mandelbrot

actors :: mandelbrot

Example implemented from "The computer Language Benchmarks Game" - Mandelbrot
module restful

nitcorn :: restful

Support module for the nitrestful tool and the restful annotation
module restful_annot

nitcorn :: restful_annot

Example for the restful annotation documented at lib/nitcorn/restful.nit
module simple

actors :: simple

A very simple example of the actor model
module simple_simulation

actors :: simple_simulation

Using agent_simulation by refining the Agent class to make
module thread_ring

actors :: thread_ring

Example implemented from "The computer Language Benchmarks Game" - Thread-Ring
module threadpool_example

pthreads :: threadpool_example

Simple example using threadpool
# Introduces thread-safe concurrent collections
#
# This module offers new thread-safe collections. If you want to
# render basic collections thread-safe and don't mind the overhead cost,
# you can use `threads::redef_collections`.
#
# Concurrent collections:
#
# - [x] `ConcurrentArray`
# - [x] `ConcurrentList`
# - [ ] `ConcurrentHashMap`
# - [ ] `ConcurrentHashSet`
# - [ ] `ConcurrentRef`
# - [ ] `ConcurrentQueue`
#
# Introduced collections specialize their critical methods according to the
# current implementation in the standard library. If additional services
# are added to the underlying collections by refinement or evolution, they
# might need to be covered in the concurrent version.
module concurrent_collections

import pthreads

redef class Collection[E]
	# Type of the concurrent variant of this collection
	type CONCURRENT: ConcurrentCollection[E]

	# Wraps `self` in a thread-safe collection
	fun to_concurrent: CONCURRENT is abstract
end

redef class SequenceRead[E]
	redef type CONCURRENT: ConcurrentSequenceRead[E]
end

redef class Sequence[E]
	redef type CONCURRENT: ConcurrentSequence[E]
end

redef class Array[E]
	redef type CONCURRENT: ConcurrentArray[E]

	redef fun to_concurrent do return new ConcurrentArray[E].wrap(self)
end

redef class List[E]
	redef type CONCURRENT: ConcurrentList[E]

	redef fun to_concurrent do return new ConcurrentList[E].wrap(self)
end

# A concurrent variant to the standard `Collection`
abstract class ConcurrentCollection[E]
	super Collection[E]

	# Type of the equivalent non thread-safe collection
	type REAL: Collection[E]

	# Collection wrapped by `self`
	var real_collection: REAL is noinit

	# `Mutex` used to synchronize access to `self`
	#
	# It is used by the implementation on each protected methods. It can also
	# be used externally to ensure that no other `Thread` modify this object.
	var mutex = new Mutex

	redef fun count(e)
	do
		mutex.lock
		var r = real_collection.count(e)
		mutex.unlock
		return r
	end

	redef fun first
	do
		mutex.lock
		var r = real_collection.first
		mutex.unlock
		return r
	end

	redef fun has(e)
	do
		mutex.lock
		var r = real_collection.has(e)
		mutex.unlock
		return r
	end

	redef fun has_all(e)
	do
		mutex.lock
		var r = real_collection.has_all(e)
		mutex.unlock
		return r
	end

	redef fun has_only(e)
	do
		mutex.lock
		var r = real_collection.has_only(e)
		mutex.unlock
		return r
	end

	redef fun is_empty
	do
		mutex.lock
		var r = real_collection.is_empty
		mutex.unlock
		return r
	end

	redef fun iterator
	do
		mutex.lock
		var r = real_collection.iterator
		mutex.unlock
		return r
	end

	redef fun length
	do
		mutex.lock
		var r = real_collection.length
		mutex.unlock
		return r
	end

	redef fun to_a
	do
		mutex.lock
		var r = real_collection.to_a
		mutex.unlock
		return r
	end

	redef fun rand
	do
		mutex.lock
		var r = real_collection.rand
		mutex.unlock
		return r
	end

	redef fun join(sep, last_sep)
	do
		mutex.lock
		var r = real_collection.join(sep, last_sep)
		mutex.unlock
		return r
	end

	redef fun to_s
	do
		mutex.lock
		var r = real_collection.to_s
		mutex.unlock
		return r
	end
end

# A concurrent variant to the standard `SequenceRead`
abstract class ConcurrentSequenceRead[E]
	super ConcurrentCollection[E]
	super SequenceRead[E]

	redef type REAL: SequenceRead[E]

	redef fun ==(o)
	do
		mutex.lock
		var r = real_collection == o
		mutex.unlock
		return r
	end

	redef fun [](index)
	do
		mutex.lock
		var r = real_collection[index]
		mutex.unlock
		return r
	end

	redef fun hash
	do
		mutex.lock
		var r = real_collection.hash
		mutex.unlock
		return r
	end

	redef fun index_of(index)
	do
		mutex.lock
		var r = real_collection.index_of(index)
		mutex.unlock
		return r
	end

	redef fun index_of_from(index, from)
	do
		mutex.lock
		var r = real_collection.index_of_from(index, from)
		mutex.unlock
		return r
	end

	redef fun iterator_from(index)
	do
		mutex.lock
		var r = real_collection.iterator_from(index)
		mutex.unlock
		return r
	end

	redef fun last
	do
		mutex.lock
		var r = real_collection.last
		mutex.unlock
		return r
	end

	redef fun last_index_of(e)
	do
		mutex.lock
		var r = real_collection.last_index_of(e)
		mutex.unlock
		return r
	end

	redef fun last_index_of_from(e, from)
	do
		mutex.lock
		var r = real_collection.last_index_of_from(e, from)
		mutex.unlock
		return r
	end

	redef fun reverse_iterator
	do
		mutex.lock
		var r = real_collection.reverse_iterator
		mutex.unlock
		return r
	end

	redef fun reverse_iterator_from(from)
	do
		mutex.lock
		var r = real_collection.reverse_iterator_from(from)
		mutex.unlock
		return r
	end
end

# A concurrent variant to the standard `Sequence`
abstract class ConcurrentSequence[E]
	super ConcurrentSequenceRead[E]
	super Sequence[E]

	redef type REAL: Sequence[E]

	redef fun []=(index, e)
	do
		mutex.lock
		real_collection[index] = e
		mutex.unlock
	end

	redef fun add(e)
	do
		mutex.lock
		real_collection.add e
		mutex.unlock
	end

	redef fun append(e)
	do
		mutex.lock
		real_collection.append e
		mutex.unlock
	end

	redef fun first=(e)
	do
		mutex.lock
		real_collection.first = e
		mutex.unlock
	end

	redef fun insert(e, i)
	do
		mutex.lock
		real_collection.insert(e, i)
		mutex.unlock
	end

	redef fun insert_all(from, pos)
	do
		mutex.lock
		real_collection
		mutex.unlock
	end

	redef fun last=(e)
	do
		mutex.lock
		real_collection.last = e
		mutex.unlock
	end

	redef fun pop
	do
		mutex.lock
		var r = real_collection.pop
		mutex.unlock
		return r
	end

	redef fun prepend(e)
	do
		mutex.lock
		real_collection.prepend e
		mutex.unlock
	end

	redef fun push(e)
	do
		mutex.lock
		real_collection.push e
		mutex.unlock
	end

	redef fun remove_at(index)
	do
		mutex.lock
		real_collection.remove_at(index)
		mutex.unlock
	end

	redef fun shift
	do
		mutex.lock
		var r = real_collection.shift
		mutex.unlock
		return r
	end

	redef fun unshift(e)
	do
		mutex.lock
		real_collection.unshift(e)
		mutex.unlock
	end

	redef fun subarray(start, len)
	do
		mutex.lock
		var r = real_collection.subarray(start, len)
		mutex.unlock
		return r
	end
end

# A concurrent variant to the standard `Array`
class ConcurrentArray[E]
	super ConcurrentSequence[E]
	super Array[E]

	redef type REAL: Array[E]

	init wrap(real_collection: REAL) do self.real_collection = real_collection
	init do self.real_collection = new Array[E]

	redef fun clear
	do
		mutex.lock
		real_collection.clear
		mutex.unlock
	end

	redef fun enlarge(cap)
	do
		mutex.lock
		real_collection.enlarge(cap)
		mutex.unlock
	end

	redef fun remove_all(e)
	do
		mutex.lock
		real_collection.remove_all(e)
		mutex.unlock
	end

	redef fun swap_at(a, b)
	do
		mutex.lock
		real_collection.swap_at(a, b)
		mutex.unlock
	end

	redef fun has(e)
	do
		mutex.lock
		var result = real_collection.has(e)
		mutex.unlock
		return result
	end

	#
	## The following method defs are conflict resolutions
	#

	redef fun add(e)
	do
		mutex.lock
		real_collection.add e
		mutex.unlock
	end

	redef fun length
	do
		mutex.lock
		var r = real_collection.length
		mutex.unlock
		return r
	end
end

# A concurrent variant to the standard `List`
class ConcurrentList[E]
	super ConcurrentSequence[E]
	super List[E]

	redef type REAL: List[E]

	init wrap(real_collection: REAL) do self.real_collection = real_collection
	init do self.real_collection = new List[E]

	redef fun link(l)
	do
		mutex.lock
		real_collection.link(l)
		mutex.unlock
	end

	redef fun slice(from, to)
	do
		mutex.lock
		var r = real_collection.slice(from, to)
		mutex.unlock
		return r
	end

	#
	## The following method defs are conflict resolutions
	#

	redef fun pop
	do
		mutex.lock
		var r = real_collection.pop
		mutex.unlock
		return r
	end

	redef fun is_empty
	do
		mutex.lock
		var r = real_collection.is_empty
		mutex.unlock
		return r
	end

	redef fun unshift(e)
	do
		mutex.lock
		real_collection.unshift(e)
		mutex.unlock
	end

	redef fun push(e)
	do
		mutex.lock
		real_collection.push(e)
		mutex.unlock
	end

	redef fun shift
	do
		mutex.lock
		var value = real_collection.shift
		mutex.unlock
		return value
	end
end

# A collection which `is_empty` method blocks until it's empty
class ReverseBlockingQueue[E]
	super ConcurrentList[E]

	# Used to block or signal on waiting threads
	private var cond = new PthreadCond

	# Adding the signal to release eventual waiting thread(s)
	redef fun push(e) do
		mutex.lock
		real_collection.push(e)
		mutex.unlock
	end

	# When the Queue is empty, signal any possible waiting thread
	redef fun remove(e) do
		mutex.lock
		real_collection.remove(e)
		if real_collection.is_empty then cond.signal
		mutex.unlock
	end

	# Wait until the Queue is empty
	redef fun is_empty do
		mutex.lock
		while not real_collection.is_empty do self.cond.wait(mutex)
		mutex.unlock
		return true
	end
end

# A Blocking queue implemented from a `ConcurrentList`
# `shift` is blocking if there isn't any element in `self`
# `push` or `unshift` releases every blocking threads
class BlockingQueue[E]
	super ConcurrentList[E]

	# Used to block or signal on waiting threads
	private var cond = new PthreadCond

	# Adding the signal to release eventual waiting thread(s)
	redef fun push(e) do
		mutex.lock
		real_collection.push(e)
		self.cond.signal
		real_collection.push(e)
		mutex.unlock
	end

	redef fun unshift(e) do
		mutex.lock
		real_collection.unshift(e)
		self.cond.signal
		mutex.unlock
	end

	# If empty, blocks until an item is inserted with `push` or `unshift`
	redef fun shift do
		mutex.lock
		while real_collection.is_empty do self.cond.wait(mutex)
		var r = real_collection.shift
		mutex.unlock
		return r
	end

	redef fun is_empty do
		mutex.lock
		var r = real_collection.is_empty
		mutex.unlock
		return r
	end
end
lib/pthreads/concurrent_collections.nit:17,1--591,3