-- Copyright 1993-1998, by the Cecil Project -- Department of Computer Science and Engineering, University of Washington -- See the LICENSE file for license information. (--DOC `arrays' are extensible mutable indexed collections. Arrays support both indexing behavior (`fetch', `store', `find_index', etc.) and extensible sequence behavior (`add_first', `add_last', `remove_first', etc.). `add' adds to the end of the array. The `new_array()' function returns a new empty array, as does the `new_array(max_size)' function (which additionally accepts a non-binding guess as to the default maximum size of the array). The other `new_array' functions are analogues of the corresponding `new_*_vector' functions, but return an array instead of a vector. --) template object array[T] isa m_indexed[T], extensible_sequence[T]; extend array[`T <= comparable[T]] isa removable_collection[T]; -- the default contents and first_elem values must be overridden together! private var field contents(@:array[`T]):m_vector[T] := new_m_vector[T](default_array_size); -- position of first element in contents private var field first_elem(t@:array[`T]):int := t.contents.length / 3; private put var field length(@:array[`T]):int := 0; -- creation behavior let default_array_size:int := 8; method new_array[T]():array[T] { new_array[T](default_array_size) } method new_array[T](size:int):array[T] { concrete object isa array[T] { contents := new_m_vector[T](size) } } method new_array[T](size:int, filler:T):array[T] { let v:m_vector[T] := new_m_vector[T](size, filler); concrete object isa array[T] { contents := v, first_elem := 0, length := v.length } } method new_array_init[T](size:int, cl:&(int):T):array[T] { let v:m_vector[T] := new_m_vector_init[T](size, cl); concrete object isa array[T] { contents := v, first_elem := 0, length := v.length } } method new_array_init_from[T2](c@:indexed[`T1], cl:&(T1):T2):array[T2] { new_array_init[T2](c.length, &(i:int){ eval(cl, c!i) }) } method new_array_init_from[T2](c@:ordered_collection[`T1], cl:&(T1):T2):array[T2] { let s:stream[T1] := view_stream(c); new_array_init[T2](c.length, &(i:int){ eval(cl, s.next) }) } method as_array(c@:ordered_collection[`T]):array[T] { as_array[T](c) } -- an alternative interface for setting explicitly the result type parameter: method as_array[T](c@:ordered_collection[T]):array[T] { new_array_init_from[T](c, &(elm:T){ elm }) } method new_array():array[dynamic] { new_array[dynamic]() } method new_array(size:int):array[dynamic] { new_array[dynamic](size) } method new_array(size:int, filler:dynamic):array[dynamic] { new_array[dynamic](size, filler) } -- Fetching / storing method fetch(a@:array[`T], index:int, if_absent:&():T):T { if(index < 0 | {index >= a.length}, { ^ eval(if_absent) }); a.contents ! (index + a.first_elem) } method fetch(a@:array[`T], index:int):T { fetch(a, index, { error("index not found in array") }) } method store(a@:array[`T], index:int, x:T, if_absent:&():void):void { if(index < 0 | {index >= a.length}, { eval(if_absent); ^ }); a.contents ! (index + a.first_elem) := x; } -- Resizing private method grow (a@:array[`T]):void { replace_contents(a, a.length * 2); } private method shrink(a@:array[`T]):void { replace_contents(a, a.length * 3 / 2); } private method replace_contents(a@:array[`T], size:int):void { -- backing vector should have at least two spare spaces, -- one at the front and one at the end, for expansion let new_size:int := max(size, a.length + 2); let first_elem:int := max((new_size - a.length) / 3, 1); let t:m_vector[T] := new_m_vector_init[T](new_size, &(i:int){ if(i >= first_elem & { i < first_elem + a.length }, { a!(i - first_elem) }, { cast[T](not_defined) }) }); a.first_elem := first_elem; a.contents := t; } -- Adding method add_first(a@:array[`T], x:T):void { if(a.first_elem = 0, { a.grow; }); a.first_elem := a.first_elem.pred; a.length := a.length.succ; a!0 := x; } method add_last(a@:array[`T], x:T):void { if(a.first_elem + a.length = a.contents.length, { a.grow; }); a.length := a.length.succ; a!a.length.pred := x; } -- Concatenating method ||(a1@:array[`T], a2@:array[T]):array[T] { let size1:int := a1.length; let size2:int := a2.length; let v:m_vector[T] := new_m_vector[T](size1 + size2); size1.do(&(i:int){ v!i := a1!i }); size2.do(&(i:int){ v!(i+size1) := a2!i }); concrete object isa array[T] { contents := v, first_elem := 0, length := v.length } } -- Removing method remove_key(a@:array[`T], index:int):T { remove_key(a, index, { error("key not found") }) } method remove_key(a@:array[`T], index:int, if_absent:&():`S):T|S { if(index < 0 | { index >= a.length }, { ^ eval(if_absent) }); let x:T := a!index; if(index < a.length / 2, { -- remove from front of array; copy elements up let var i:int := index; while({ i > 0 }, { a!i := a!i.pred; i := i.pred; }); -- null out removed element?? a.first_elem := a.first_elem.succ; }, { -- remove from back of array; copy elements down let var i:int := index.succ; while({ i < a.length }, { a!i.pred := a!i; i := i.succ; }); -- null out removed element?? }); a.length := a.length.pred; if(a.length < a.contents.length / 3, { a.shrink; }); x } method remove_first(a@:array[`T], if_empty:&():`S):T|S { if(is_empty(a), { ^ eval(if_empty) }); remove_key(a, 0) } method remove_last(a@:array[`T], if_empty:&():`S):T|S { if(is_empty(a), { ^ eval(if_empty) }); remove_key(a, a.length.pred) } method remove_last_N(a@:array[`T], n:int):void { if(n >= a.length, { ^ a.remove_all; }); a.length := a.length - n; if(a.length < a.contents.length / 3, { a.shrink; }); } method remove(a@:array[`T <= comparable[T]], x:T, if_absent:&():void):void { let index:int := find_key(a, x, { eval(if_absent); ^ }); remove_key(a, index); void } method remove_all(a@:array[`T]):void { if(a.non_empty, { a.length := 0; a.shrink; }); } -- Copying behavior method copy_empty(a@:array[`T]):array[T] { new_array[T]() } method copy(a@:array[`T]):array[T] { new_array_init_from[T](a, &(x:T){ x }) } -- Printing behavior method collection_name(@:array[`T]):string { "array" }