Module queue

Data Types

queue()


queue() = queue(term())

queue()

abstract datatype: queue(Item)

Function Index

all/2 Returns true if Pred(Item) returns true for all items Item in Q, otherwise false.
any/2 Returns true if Pred(Item) returns true for at least one item Item in Q, otherwise false.
delete/2 Returns a copy of Q1 where the first item matching Item is deleted, if there is such an item.
delete_r/2 Returns a copy of Q1 where the last item matching Item is deleted, if there is such an item.
delete_with/2 Returns a copy of Q1 where the first item for which Pred returns true is deleted, if there is such an item.
delete_with_r/2 Returns a copy of Q1 where the last item for which Pred returns true is deleted, if there is such an item.
drop/1 Returns a queue Q2 that is the result of removing the front item from Q1.
drop_r/1 Returns a queue Q2 that is the result of removing the rear item from Q1.
filter/2 Returns a queue Q2 that is the result of calling Fun(Item) on all items in Q1.
filtermap/2 Returns a queue Q2 that is the result of calling Fun(Item) on all items in Q1.
fold/3 Calls Fun(Item, AccIn) on successive items Item of Queue, starting with AccIn == Acc0.
from_list/1 Returns a queue containing the items in L in the same order; the head item of the list becomes the front item of the queue.
get/1 Returns Item at the front of queue Q.
get_r/1 Returns Item at the rear of queue Q.
in/2 Inserts Item at the rear of queue Q1.
in_r/2 Inserts Item at the front of queue Q1.
is_empty/1 Tests if Q is empty and returns true if so, otherwise false.
is_queue/1 Tests if Term is a queue and returns true if so, otherwise false.
join/2 Returns a queue Q3 that is the result of joining Q1 and Q2 with Q1 in front of Q2.
len/1 Calculates and returns the length of queue Q.
member/2 Returns true if Item matches some element in Q, otherwise false.
new/0 This function returns an empty queue.
out/1 Removes the item at the front of queue Q1.
out_r/1 Removes the item at the rear of queue Q1.
peek/1 Returns tuple {value, Item}, where Item is the front item of Q, or empty if Q is empty.
peek_r/1 Returns tuple {value, Item}, where Item is the rear item of Q, or empty if Q is empty.
reverse/1 Returns a queue Q2 containing the items of Q1 in reverse order.
split/2 Splits Q1 in two.
to_list/1 Returns a list of the items in the queue in the same order; the front item of the queue becomes the head of the list.

Function Details

all/2


all(Pred, Q::queue(Item)) -> boolean()
  • Pred = fun((Item) -> boolean())

Pred: the predicate function to apply to each item
Q: the queue to check against the predicate

returns: Returns true if Pred(Item) returns true for all items Item in Q, otherwise false.

Returns true if Pred(Item) returns true for all items Item in Q, otherwise false.

Example: 1> Queue = queue:from_list([1,2,3,4,5]). 2> queue:all(fun (E) -> E > 3 end, Queue). false 3> queue:all(fun (E) -> E > 0 end, Queue). true

any/2


any(Pred, Q::queue(Item)) -> boolean()
  • Pred = fun((Item) -> boolean())

Pred: the predicate function to apply to each item
Q: the queue to check against the predicate

returns: Returns true if Pred(Item) returns true for at least one item Item in Q, otherwise false.

Returns true if Pred(Item) returns true for at least one item Item in Q, otherwise false.

Example: 1> Queue = queue:from_list([1,2,3,4,5]). 2> queue:any(fun (E) -> E > 10 end, Queue). false 3> queue:any(fun (E) -> E > 3 end, Queue). true

delete/2


delete(Item, Q1) -> Q2

Item: the item to delete from the queue
Q1: the queue from which the item will be deleted

returns: Returns a copy of Q1 where the first item matching Item is deleted, if there is such an item.

Returns a copy of Q1 where the first item matching Item is deleted, if there is such an item.

Example: 1> Queue = queue:from_list([1,2,3,4,5]). 2> Queue1 = queue:delete(3, Queue). 3> queue:member(3, Queue1). false

delete_r/2


delete_r(Item, Q1) -> Q2

Item: the item to delete from the queue
Q1: the queue from which the item will be deleted

returns: Returns a copy of Q1 where the last item matching Item is deleted, if there is such an item.

Returns a copy of Q1 where the last item matching Item is deleted, if there is such an item.

Example: 1> Queue = queue:from_list([1,2,3,4,3,5]). 2> Queue1 = queue:delete_r(3, Queue). 3> queue:to_list(Queue1). [1,2,3,4,5]

delete_with/2


delete_with(Pred, Q1) -> Q2
  • Pred = fun((Item) -> boolean())
  • Q1 = queue(Item)
  • Q2 = queue(Item)
  • Item = term()

Pred: the predicate function to apply to each item
Q1: the queue from which the item will be deleted

returns: Returns a copy of Q1 where the first item for which Pred returns true is deleted, if there is such an item.

Returns a copy of Q1 where the first item for which Pred returns true is deleted, if there is such an item.

Example: 1> Queue = queue:from_list([100,1,2,3,4,5]). 2> Queue1 = queue:delete_with(fun (E) -> E > 0, Queue). 3> queue:to_list(Queue1). [1,2,3,4,5]

delete_with_r/2


delete_with_r(Pred, Q1) -> Q2
  • Pred = fun((Item) -> boolean())
  • Q1 = queue(Item)
  • Q2 = queue(Item)
  • Item = term()

Pred: the predicate function to apply to each item
Q1: the queue from which the item will be deleted

returns: Returns a copy of Q1 where the last item for which Pred returns true is deleted, if there is such an item.

Returns a copy of Q1 where the last item for which Pred returns true is deleted, if there is such an item.

Example: 1> Queue = queue:from_list([1,2,3,4,5,100]). 2> Queue1 = queue:delete_with_r(fun (E) -> E > 10, Queue). 3> queue:to_list(Queue1). [1,2,3,4,5]

drop/1


drop(Q1::queue(Item)) -> Q2::queue(Item)

Q1: the queue from which the first element will be removed

returns: Returns a queue Q2 that is the result of removing the front item from Q1. Fails with reason empty if Q1 is empty

Returns a queue Q2 that is the result of removing the front item from Q1. Fails with reason empty if Q1 is empty.

Example: 1> Queue = queue:from_list([1,2,3,4,5]). {[5,4,3],[1,2]} 2> Queue = queue:drop(Queue). {[5,4,3],[2]} 3> queue:to_list(Queue1). [2,3,4,5]

drop_r/1


drop_r(Q1::queue(Item)) -> Q2::queue(Item)

Q1: the queue from which the last element will be removed

returns: Returns a queue Q2 that is the result of removing the rear item from Q1. Fails with reason empty if Q1 is empty

Returns a queue Q2 that is the result of removing the rear item from Q1. Fails with reason empty if Q1 is empty.

Example: 1> Queue = queue:from_list([1,2,3,4,5]). {[5,4,3],[1,2]} 2> Queue = queue:drop_r(Queue). {[4,3],[1,2]} 3> queue:to_list(Queue1). [1,2,3,4]

filter/2


filter(Fun, Q1::queue(Item)) -> Q2::queue(Item)
  • Fun = fun((Item) -> boolean() | [Item])

Fun: the function to be applied to each item in the queue
Q1: the queue where the function will be applied

returns: Returns a queue Q2 that is the result of calling Fun(Item) on all items in Q1

Returns a queue Q2 that is the result of calling Fun(Item) on all items in Q1. If Fun(Item) returns true, Item is copied to the result queue. If it returns false, Item is not copied. If it returns a list, the list elements are inserted instead of Item in the result queue.

Example 1: 1> Queue = queue:from_list([1,2,3,4,5]). {[5,4,3],[1,2]} 2> Queue1 = queue:filter(fun (E) -> E > 2 end, Queue). {[5],[3,4]} 3> queue:to_list(Queue1). [3,4,5]

Example 2: 1> Queue = queue:from_list([1,2,3,4,5]). {[5,4,3],[1,2]} 2> Queue1 = queue:filter(fun (E) -> [E, E+1] end, Queue). {[6,5,5,4,4,3],[1,2,2,3]} 3> queue:to_list(Queue1). [1,2,2,3,3,4,4,5,5,6]

filtermap/2


filtermap(Fun, Q1) -> Q2
  • Fun = fun((Item) -> boolean() | {true, Value})
  • Q1 = queue(Item)
  • Q2 = queue(Item | Value)
  • Item = term()
  • Value = term()

Fun: the function to be applied to each item in the queue
Q1: the queue where the function will be applied

returns: Returns a queue Q2 that is the result of calling Fun(Item) on all items in Q1

Returns a queue Q2 that is the result of calling Fun(Item) on all items in Q1. If Fun(Item) returns true, Item is copied to the result queue. If it returns false, Item is not copied. If it returns {true, NewItem}, the queue element at this position is replaced with NewItem in the result queue.

Example 1: 1> Queue = queue:from_list([1,2,3,4,5]). {[5,4,3],[1,2]} 2> Queue1 = queue:filtermap(fun (E) -> E > 2 end, Queue). {[5],[3,4]} 3> queue:to_list(Queue1). [3,4,5] 4> Queue1 = queue:filtermap(fun (E) -> {true, E+100} end, Queue). {[105,104,103],[101,102]} 5> queue:to_list(Queue1). [101,102,103,104,105]

fold/3


fold(Fun, Acc0, Q::queue(Item)) -> Acc1
  • Fun = fun((Item, AccIn) -> AccOut)
  • Acc0 = term()
  • Acc1 = term()
  • AccIn = term()
  • AccOut = term()

Fun: the function to be applied to each item and accumulator
Acc0: the initial accumulator value
Q: the queue over which the function will be folded

returns: Returns the final value of the accumulator after folding over the queue

Calls Fun(Item, AccIn) on successive items Item of Queue, starting with AccIn == Acc0. The queue is traversed in queue order, that is, from front to rear. Fun/2 must return a new accumulator, which is passed to the next call. The function returns the final value of the accumulator. Acc0 is returned if the queue is empty.

Example: 1> queue:fold(fun(X, Sum) -> X + Sum end, 0, queue:from_list([1,2,3,4,5])). 15 2> queue:fold(fun(X, Prod) -> X * Prod end, 1, queue:from_list([1,2,3,4,5])). 120

from_list/1


from_list(L::[Item]) -> queue(Item)

L: the list to be converted to a queue

returns: Returns a queue containing the items in L in the same order

Returns a queue containing the items in L in the same order; the head item of the list becomes the front item of the queue. This function is part of the Original API.

get/1


get(Q::queue(Item)) -> Item

Q: the queue from which the first element will be returned

returns: Returns Item at the front of queue Q. Fails with reason empty if Q is empty

Returns Item at the front of queue Q. Fails with reason empty if Q is empty.

Example: 1> Queue = queue:from_list([1,2,3,4,5]). {[5,4,3],[1,2]} 2> 1 == queue:get(Queue). true

get_r/1


get_r(Q::queue(Item)) -> Item

Q: the queue from which the last element will be returned

returns: Returns Item at the rear of queue Q. Fails with reason empty if Q is empty

Returns Item at the rear of queue Q. Fails with reason empty if Q is empty.

Example: 1> Queue = queue:from_list([1,2,3,4,5]). {[5,4,3],[1,2]} 2> 5 == queue:get_r(Queue). true

in/2


in(Item, Q1::queue(Item)) -> Q2::queue(Item)

Item: the item that will be enqueued (inserted at the rear of the queue)
Q1: the queue where the item will be inserted in

returns: Returns the queue with Item inserted at the rear of the queue

Inserts Item at the rear of queue Q1. Returns the resulting queue Q2. This function is part of the Original API

Example: 1> Queue = queue:from_list([1,2,3,4,5]). {[5,4,3],[1,2]} 2> Queue1 = queue:in(100, Queue). {[100,5,4,3],[1,2]} 3> queue:to_list(Queue1). [1,2,3,4,5,100]

in_r/2


in_r(Item, Q1::queue(Item)) -> Q2::queue(Item)

Item: the item that will be enqueued (inserted at the front of the queue)
Q1: the queue where the item will be inserted in

returns: Returns the queue with Item inserted at the front of the queue

Inserts Item at the front of queue Q1. Returns the resulting queue Q2. This function is part of the Original API

Example: 1> Queue = queue:from_list([1,2,3,4,5]). {[5,4,3],[1,2]} 2> Queue1 = queue:in_r(100, Queue). {[5,4,3],[100,1,2]} 3> queue:to_list(Queue1). [100,1,2,3,4,5]

is_empty/1


is_empty(Q::queue()) -> boolean()

Q: the queue to be tested

returns: Returns true if Q is empty, otherwise false

Tests if Q is empty and returns true if so, otherwise false. This function is part of the Original API.

is_queue/1


is_queue(Term::term()) -> boolean()

Term: the term to be tested

returns: Returns true if Term is a queue, otherwise false

Tests if Term is a queue and returns true if so, otherwise false. Note that the test will return true for a term coinciding with the representation of a queue, even when not constructed by this module. This function is part of the Original API.

join/2


join(Q1::queue(Item), Q2::queue(Item)) -> Q3::queue(Item)

Q1: the first queue to be joined
Q2: the second queue to be joined

returns: Returns a queue Q3 that is the result of joining Q1 and Q2 with Q1 in front of Q2

Returns a queue Q3 that is the result of joining Q1 and Q2 with Q1 in front of Q2. This function is part of the Original API

Example: 1> Queue1 = queue:from_list([1,3]). {[3],[1]} 2> Queue2 = queue:from_list([2,4]). {[4],[2]} 3> queue:to_list(queue:join(Queue1, Queue2)). [1,3,2,4]

len/1


len(Q::queue()) -> non_neg_integer()

Q: the queue whose length is to be calculated

returns: Returns the length of queue Q

Calculates and returns the length of queue Q. This function is part of the Original API.

member/2


member(Item, Q::queue(Item)) -> boolean()

Item: the item to be searched in the queue
Q: the queue to be searched

returns: Returns true if Item matches some element in Q, otherwise false

Returns true if Item matches some element in Q, otherwise false. This function is part of the Original API.

new/0


new() -> queue(none())

returns: Returns an empty queue.

This function returns an empty queue. This function is part of the Original API.

out/1


out(Q1::queue(Item)) -> {{value, Item}, Q2::queue(Item)} | {empty, Q1::queue(Item)}

Q1: the queue from which the item will be dequeued (removed from the front)

returns: Returns a tuple {{value, Item}, Q2} where Item is the item removed and Q2 is the resulting queue. If Q1 is empty, tuple {empty, Q1} is returned

Removes the item at the front of queue Q1. Returns tuple {{value, Item}, Q2}, where Item is the item removed and Q2 is the resulting queue. If Q1 is empty, tuple {empty, Q1} is returned. This function is part of the Original API

Example: 1> Queue = queue:from_list([1,2,3,4,5]). {[5,4,3],[1,2]} 2> {{value, 1=Item}, Queue1} = queue:out(Queue). {{value,1},{[5,4,3],[2]}} 3> queue:to_list(Queue1). [2,3,4,5]

out_r/1


out_r(Q1::queue(Item)) -> {{value, Item}, Q2::queue(Item)} | {empty, Q1::queue(Item)}

Q1: the queue from which the item will be dequeued (removed from the rear)

returns: Returns a tuple {{value, Item}, Q2} where Item is the item removed and Q2 is the resulting queue. If Q1 is empty, tuple {empty, Q1} is returned

Removes the item at the rear of queue Q1. Returns tuple {{value, Item}, Q2}, where Item is the item removed and Q2 is the new queue. If Q1 is empty, tuple {empty, Q1} is returned. This function is part of the Original API

Example: 1> Queue = queue:from_list([1,2,3,4,5]). {[5,4,3],[1,2]} 2> {{value, 5=Item}, Queue1} = queue:out_r(Queue). {{value,5},{[4,3],[1,2]}} 3> queue:to_list(Queue1). [1,2,3,4]

peek/1


peek(Q::queue(Item)) -> empty | {value, Item}

Q: the queue from which the first element will be returned

returns: Returns tuple {value, Item}, where Item is the front item of Q, or empty if Q is empty

Returns tuple {value, Item}, where Item is the front item of Q, or empty if Q is empty.

Example: 1> queue:peek(queue:new()). empty 2> Queue = queue:from_list([1,2,3,4,5]). {[5,4,3],[1,2]} 3> queue:peek(Queue). {value, 1}

peek_r/1


peek_r(Q::queue(Item)) -> empty | {value, Item}

Q: the queue from which the last element will be returned

returns: Returns tuple {value, Item}, where Item is the rear item of Q, or empty if Q is empty

Returns tuple {value, Item}, where Item is the rear item of Q, or empty if Q is empty.

Example: 1> queue:peek_r(queue:new()). empty 2> Queue = queue:from_list([1,2,3,4,5]). {[5,4,3],[1,2]} 3> queue:peek_r(Queue). {value, 5}

reverse/1


reverse(Q1::queue(Item)) -> Q2::queue(Item)

Q1: the queue to be reversed

returns: Returns a queue Q2 containing the items of Q1 in reverse order

Returns a queue Q2 containing the items of Q1 in reverse order. This function is part of the Original API

Example: 1> Queue = queue:from_list([1,2,3,4,5]). {[5,4,3],[1,2]} 2> Queue1 = queue:reverse(Queue). {[2,1],[3,4,5]}

split/2


split(N::non_neg_integer(), Q1::queue(Item)) -> {Q2::queue(Item), Q3::queue(Item)}

N: the number of items to be put in the first resulting queue Q2
Q1: the queue to be split

returns: Returns a tuple {Q2, Q3} where Q2 contains the first N items of Q1 and Q3 contains the remaining items

Splits Q1 in two. The N front items are put in Q2 and the rest in Q3. This function is part of the Original API

to_list/1


to_list(Q::queue(Item)) -> [Item]

Q: the queue to be converted to a list

returns: Returns a list of the items in the queue

Returns a list of the items in the queue in the same order; the front item of the queue becomes the head of the list.

Example: 1> Queue = queue:from_list([1,2,3,4,5]). {[5,4,3],[1,2]} 2> List == queue:to_list(Queue). true This function is part of the Original API.