Queue/Definition

From Rosetta Code
Task
Queue/Definition
You are encouraged to solve this task according to the task description, using any language you may know.

Data Structure
This illustrates a data structure, a means of storing data within a program.

You may see other such structures in the Data Structures category.

Illustration of FIFO behavior

Implement a FIFO queue. Elements are added at one side and popped from the other in the order of insertion.

Operations:

  • push (aka enqueue) - add element
  • pop (aka dequeue) - pop first element
  • empty - return truth value when empty

Errors:

  • handle the error of trying to pop from an empty queue (behavior depends on the language and platform)


Ada

The first example below demonstrates a FIFO created for single-threaded computing. This version has the advantage of using a minimum of memory per FIFO element, and being very fast.

The interface specification for a FIFO is described in the package specification.

generic
   type Element_Type is private;
package Fifo is
   type Fifo_Type is private;
   procedure Push(List : in out Fifo_Type; Item : in Element_Type);
   procedure Pop(List : in out Fifo_Type; Item : out Element_Type);
   function Is_Empty(List : Fifo_Type) return Boolean;
   Empty_Error : exception;
private
   type Fifo_Element;
   type Fifo_Ptr is access Fifo_Element;
   type Fifo_Type is record
      Head : Fifo_Ptr := null;
      Tail : Fifo_Ptr := null;
   end record;
   type Fifo_Element is record
      Value : Element_Type;
      Next  : Fifo_Ptr := null;
   end record;
end Fifo;

The FIFO implementation is described in the package body:

with Ada.Unchecked_Deallocation;

package body Fifo is 

   ----------
   -- Push --
   ----------

   procedure Push (List : in out Fifo_Type; Item : in Element_Type) is
      Temp : Fifo_Ptr := new Fifo_Element'(Item, null);
   begin
      if List.Tail = null then
         List.Tail := Temp;
      end if;
      if List.Head /= null then
        List.Head.Next := Temp;
      end if;
      List.Head := Temp;
   end Push;

   ---------
   -- Pop --
   ---------

   procedure Pop (List : in out Fifo_Type; Item : out Element_Type) is
      procedure Free is new Ada.Unchecked_Deallocation(Fifo_Element, Fifo_Ptr);
      Temp : Fifo_Ptr := List.Tail;
   begin
      if List.Head = null then
         raise Empty_Error;
      end if;
      Item := List.Tail.Value;
      List.Tail := List.Tail.Next;
      if List.Tail = null then
         List.Head := null;
      end if;
      Free(Temp);
   end Pop;

   --------------
   -- Is_Empty --
   --------------

   function Is_Empty (List : Fifo_Type) return Boolean is
   begin
      return List.Head = null;
   end Is_Empty; 

end Fifo;

A "main" procedure for this program is:

with Fifo;
with Ada.Text_Io; use Ada.Text_Io;

procedure Fifo_Test is
   package Int_Fifo is new Fifo(Integer);
   use Int_Fifo;
   My_Fifo : Fifo_Type;
   Val : Integer;
begin
   for I in 1..10 loop
      Push(My_Fifo, I);
   end loop;
   while not Is_Empty(My_Fifo) loop
      Pop(My_Fifo, Val);
      Put_Line(Integer'Image(Val));
   end loop;
end Fifo_Test;

The following implementation produces equivalent functionality by deriving from the standard Ada Container type Doubly_Linked_Lists.

This example needs fewer lines of code on the part of the application programmer, but the implementation is less efficient than the previous example. Each element has all the data members needed for a doubly linked list. It also links in all the functionality of a doubly linked list. Most of that functionality is unneeded in a FIFO.

with Ada.Containers.Doubly_Linked_Lists;
generic
   type Element_Type is private;
package Generic_Fifo is
   type Fifo_Type is tagged private;
   procedure Push(The_Fifo : in out Fifo_Type; Item : in Element_Type);
   procedure Pop(The_Fifo : in out Fifo_Type; Item : out Element_Type);
   Empty_Error : Exception;
private
   package List_Pkg is new Ada.Containers.Doubly_Linked_Lists(Element_Type);
   use List_Pkg;
   Type Fifo_Type is new List with null record;
end Generic_Fifo;
package body Generic_Fifo is

   ----------
   -- Push --
   ---------- 

   procedure Push (The_Fifo : in out Fifo_Type; Item : in Element_Type) is
   begin
      The_Fifo.Prepend(Item);
   end Push;

   ---------
   -- Pop --
   ---------

   procedure Pop (The_Fifo : in out Fifo_Type; Item : out Element_Type) is
   begin
      if Is_Empty(The_Fifo) then
         raise Empty_Error;
      end if;
      Item := The_Fifo.Last_Element;
      The_Fifo.Delete_Last;
   end Pop;

end Generic_Fifo;
with Generic_Fifo;
with Ada.Text_Io; use Ada.Text_Io;

procedure Generic_Fifo_Test is
   package Int_Fifo is new Generic_Fifo(Integer);
   use Int_Fifo;
   My_Fifo : Fifo_Type;
   Val : Integer;
begin
   for I in 1..10 loop
      My_Fifo.Push(I);
   end loop;
   while not My_Fifo.Is_Empty loop
      My_Fifo.Pop(Val);
      Put_Line(Integer'Image(Val));
   end loop;
end Generic_Fifo_Test;

The function Is_Empty is inherited from the Lists type.

The next two examples provide simple FIFO functionality for concurrent tasks. The buffer in each example holds a single value. When running concurrent tasks, one writing to the buffer, and one reading from the buffer, either the writer will be faster than the reader, or the reader will be faster than the writer. If the writer is faster a dynamic FIFO will grow to consume all available memory on the computer. If the reader is faster the FIFO will either contain a single value or it will be empty. In either case, no implementation is more efficient than a single element buffer.

If we wish for the reader to read every value written by the writer we must synchronize the tasks. The writer can only write a new value when the buffer contains a stale value. The reader can only read a value when the value is fresh. This synchronization forces the two tasks to run at the same speed.

generic
   type Element_Type is private;
package Synchronous_Fifo is
   protected type Fifo is
      entry Push(Item : Element_Type);
      entry Pop(Item : out Element_Type);
   private
      Value : Element_Type;
      Is_New : Boolean := False;
   end Fifo;
end Synchronous_Fifo;
package body Synchronous_Fifo is

   ----------
   -- Fifo --
   ----------

   protected body Fifo is 

      ---------
      -- Push --
      ---------

      entry Push (Item : Element_Type) when not Is_New is
      begin
         Value := Item;
         Is_New := True;
      end Push; 

      ---------
      -- Pop --
      ---------

      entry Pop (Item : out Element_Type) when Is_New is
      begin
         Item := Value;
         Is_New := False;
      end Pop; 

   end Fifo;

end Synchronous_Fifo;

with Synchronous_Fifo; with Ada.Text_Io; use Ada.Text_Io;

procedure Synchronous_Fifo_Test is
   package Int_Fifo is new Synchronous_Fifo(Integer);
   use Int_Fifo;
   Buffer : Fifo;
   
   task Writer is
      entry Stop;
   end Writer;
   
   task body Writer is
      Val : Positive := 1;
   begin
      loop
         select
            accept Stop;
            exit;
         else
            select
               Buffer.Push(Val);
               Val := Val + 1;
            or
               delay 1.0;
            end select;
         end select;
      end loop;
   end Writer;
   
   task Reader is
      entry Stop;
   end Reader;
   
   task body Reader is
      Val : Positive;
   begin
      loop
         select
            accept Stop;
            exit;
         else
            select
               Buffer.Pop(Val);
               Put_Line(Integer'Image(Val));
            or
                delay 1.0;
           end select;
         end select;
      end loop;
   end Reader;
begin
   delay 0.1;
   Writer.Stop;
   Reader.Stop;
end Synchronous_Fifo_Test;

Another choice is to cause the two tasks to run independently. The writer can write whenever it is scheduled. The reader reads whenever it is scheduled, after the writer writes the first valid value.

In this example the writer writes several values before the reader reads a value. The reader will then read that same value several times before the writer is scheduled to write more values.

In a fully asynchronous system the reader only samples the values written by the writer. There is no control over the number of values not sampled by the reader, or over the number of times the reader reads the same value.

generic
   type Element_Type is private;
package Asynchronous_Fifo is
   protected type Fifo is
      procedure Push(Item : Element_Type);
      entry Pop(Item : out Element_Type);
   private
      Value : Element_Type;
      Valid : Boolean := False;
   end Fifo;
end Asynchronous_Fifo;

You may notice that the protected type specification is remarkably similar to the synchronous example above. The only important difference is that Push is declared to be an Entry in the synchronous example while it is a procedure in the asynchronous example. Entries only execute when their boundary condition evaluates to TRUE. Procedures execute unconditionally.

package body Asynchronous_Fifo is

   ----------
   -- Fifo --
   ----------

   protected body Fifo is 

      ----------
      -- Push --
      ----------

      procedure Push (Item : Element_Type) is
      begin
          Value := Item;
         Valid := True;
      end Push;

      ---------
      -- Pop --
      ---------

      entry Pop (Item : out Element_Type) when Valid is
      begin
         Item := Value;
      end Pop;

   end Fifo; 

end Asynchronous_Fifo;
with Asynchronous_Fifo;
with Ada.Text_Io; use Ada.Text_Io; 

 procedure Asynchronous_Fifo_Test is
    package Int_Fifo is new Asynchronous_Fifo(Integer);
    use Int_Fifo;
    Buffer : Fifo;
    
    task Writer is
       entry Stop;
    end Writer;
    
    task body Writer is
       Val : Positive := 1;
    begin
       loop
          select
             accept Stop;
             exit;
          else
             Buffer.Push(Val);
             Val := Val + 1;
          end select;
       end loop;
    end Writer;
    
    task Reader is
       entry Stop;
    end Reader;
    
    task body Reader is
       Val : Positive;
    begin
       loop
          select 
             accept Stop;
             exit;
          else
             Buffer.Pop(Val);
             Put_Line(Integer'Image(Val));
          end select;
       end loop;
    end Reader;
 begin
    delay 0.1;
    Writer.Stop;
    Reader.Stop;
 end Asynchronous_Fifo_Test;

C++

Works with: g++ version 4.1.2 20061115 (prerelease) (Debian 4.1.1-21)

C++ already has a class queue in the standard library, however the following is a simple implementation based on a singly linkes list. Note that an empty queue is internally represented by head == 0, therefore it doesn't matter that the tail value is invalid in that case. <cpp> namespace rosettacode {

 template<typename T> class queue
 {
 public:
   queue();
   ~queue();
   void push(T const& t);
   T pop();
   bool empty();
 private:
   void drop();
   struct node;
   node* head;
   node* tail;
 };
 template<typename T> struct queue<T>::node
 {
   T data;
   node* next;
   node(T const& t): data(t), next(0) {}
 };
 template<typename T>
  queue<T>::queue():
   head(0)
 {
 }
 template<typename T>
  inline void queue<T>::drop()
 {
   node* n = head;
   head = head->next;
   delete n;
 }
 template<typename T>
  queue<T>::~queue()
 {
   while (!empty())
     drop();
 }
 template<typename T>
  void queue<T>::push(T const& t)
 {
   node*& next = head? tail->next : head;
   next = new node(t);
   tail = next;
 }
 template<typename T>
  T queue<T>::pop()
 {
   T tmp = head->data;
   drop();
   return tmp;
 }
 template<typename T>
  bool queue<T>::empty()
 {
   return head == 0;
 }

} </cpp>

D

Implemented a queue class, by reusing previous stack class definition. See Stack#D.

module stack ;
class Stack(T){
...
  void push(T top) { ... }
  T pop() { ... }
  bool empty() { ... } 
}
module fifo ;
import stack ;
class FIFO(T) : Stack!(T){
  override T pop() {
    if (empty)
      throw new Exception("FIFO Empty") ;
    T top = content[0] ;
    content = content[1..$] ;
    return top ;
  }
  alias push enqueue ;
  alias pop dequeue ;
}

Statement content = content[1..$] is efficient enough, because no array content is moved/copyed, but pointer modified.
The following is a linked implementation:

module fifolink ;
class FIFOLinked(T) {
  class Node {
    T content ;
    Node next ;
    this(T data, Node prevNode) { 
      content = data ;
      if (prevNode)
        prevNode.next = this ;
      next = null ;
    }
  }
  private Node head = null ;
  private Node tail = null ;
  void push(T last) {
    tail = new Node(last, tail) ;
    if(empty)
      head = tail ;
  }
  T pop() {
    if(empty)
      throw new Exception("FIFO Empty") ;
    T first = head.content ;
    if (head is tail) // is last one?
      tail = null ;   // release tail reference so that GC can collect afterward
    head = head.next ;
    return first ;
  }
  bool empty() { return head is null ; }
  alias push enqueue ;
  alias pop dequeue ;
}

Forth

This is a FIFO implemented as a circular buffer, as is often found between communicating processes such the interrupt and user parts of a device driver. In practice, the get/put actions would block instead of aborting if the queue is empty/full.

1024 constant size
create buffer size cells allot
here constant end
variable head  buffer head !
variable tail  buffer tail !
variable used       0 used !

: empty?  used @ 0= ;
: full?   used @ size = ;

: next ( ptr -- ptr )
  cell+  dup end = if drop buffer then ;

: put ( n -- )
  full? abort" buffer full"
  \ begin full? while pause repeat
  tail @ !  tail @ next tail !   1 used +! ;

: get ( -- n )
  empty? abort" buffer empty"
  \ begin empty? while pause repeat
  head @ @  head @ next head !  -1 used +! ;

Haskell

The standard way to manage fifo in functional programming is to use a pair of list for the fifo queue, one is the input, the other is the output. When the output is empty just take the input list and reverse it.

data Fifo a = F [a] [a]

emptyFifo :: Fifo a
emptyFifo = F [] []

push :: Fifo a -> a -> Fifo a
push (F input output) item = F (item:input) output

pop :: Fifo a -> (Maybe a, Fifo a)
pop (F input (item:output)) = (Just item, F input output)
pop (F []    []           ) = (Nothing, F [] [])
pop (F input []           ) = pop (F [] (reverse input))

isEmpty :: Fifo a -> Bool
isEmpty (F [] []) = True
isEmpty _         = False

and a session in the interactive interpreter:

Prelude> :l fifo.hs
[1 of 1] Compiling Main             ( fifo.hs, interpreted )
Ok, modules loaded: Main.
*Main> let q = emptyFifo
*Main> isEmpty q
True
*Main> let q' = push q 1
*Main> isEmpty q'
False
*Main> let q'' = foldl push q' [2..4]
*Main> let (v,q''') = pop q''
*Main> v
Just 1
*Main> let (v',q'''') = pop q'''
*Main> v'
Just 2
*Main> let (v'',q''''') = pop q''''
*Main> v''
Just 3
*Main> let (v''',q'''''') = pop q'''''
*Main> v'''
Just 4
*Main> let (v'''',q''''''') = pop q''''''
*Main> v''''
Nothing

Java

Works with: Java version 1.5+

This task could be done using a LinkedList from java.util, but here is a user-defined version with generics: <java>public class Queue<E>{ Node<E> head, tail;

static class Node<E>{ E value; Node<E> next;

public Node(){ this(0, null); }

public Node(E value, Node<E> next){ this.value= value; this.next= next; }

public Node<E> getNext(){ return next; }

public void setNext(Node<E> next){ this.next= next; }

}

public Queue(){ head= tail= null; }

public void enqueue(E value){ //standard queue name for "push" Node<E> newNode= new Node<E>(value, null); if(empty()){ head= newNode; }else{ tail.setNext(newNode); } tail= newNode; }

public E dequeue() throws java.util.NoSuchElementException{//standard queue name for "pop" if(empty()){ throw new java.util.NoSuchElementException("No more elements."); } E retVal= head.value; head= head.getNext(); return retVal; }

public boolean empty(){ return head == null; } }</java>

OCaml

The standard way to manage fifo in functional programming is to use a pair of list for the fifo queue, one is the input, the other is the output. When the output is empty just take the input list and reverse it.

<ocaml>module FIFO : sig

 type 'a fifo
 val empty: 'a fifo
 val push: fifo:'a fifo -> item:'a -> 'a fifo
 val pop: fifo:'a fifo -> 'a * 'a fifo
 val is_empty: fifo:'a fifo -> bool

end = struct

 type 'a fifo = 'a list * 'a list
 let empty = [], []
 let push ~fifo:(input,output) ~item = (item::input,output)
 let is_empty ~fifo =
   match fifo with
   | [], [] -> true
   | _ -> false
 let rec pop ~fifo =
   match fifo with
   | input, item :: output -> item, (input,output)
   | [], [] -> failwith "empty fifo"
   | input, [] -> pop ([], List.rev input)

end</ocaml>

and a session in the top-level:

<ocaml># open FIFO;;

  1. let q = empty ;;

val q : '_a FIFO.fifo = <abstr>

  1. is_empty q ;;

- : bool = true

  1. let q = push q 1 ;;

val q : int FIFO.fifo = <abstr>

  1. is_empty q ;;

- : bool = false

  1. let q =
   List.fold_left push q [2;3;4] ;;

val q : int FIFO.fifo = <abstr>

  1. let v, q = pop q ;;

val v : int = 1 val q : int FIFO.fifo = <abstr>

  1. let v, q = pop q ;;

val v : int = 2 val q : int FIFO.fifo = <abstr>

  1. let v, q = pop q ;;

val v : int = 3 val q : int FIFO.fifo = <abstr>

  1. let v, q = pop q ;;

val v : int = 4 val q : int FIFO.fifo = <abstr>

  1. let v, q = pop q ;;

Exception: Failure "empty fifo".</ocaml>

The standard ocaml library also provides a FIFO module, but it is imperative, unlike the implementation above which is functional.

Pascal

Works with: Free Pascal version 2.2.0
Works with: GNU Pascal version 20060325, based on gcc-3.4.4

This program should be Standard Pascal compliant (i.e. it doesn't make use of the advanced/non-standard features of FreePascal or GNU Pascal).

<pascal> program fifo(input, output);

type

pNode = ^tNode;
tNode = record
         value: integer;
         next:  pNode;
        end;
tFifo = record
         first, last: pNode;
        end;           

procedure initFifo(var fifo: tFifo);

begin
 fifo.first := nil;
 fifo.last := nil
end;

procedure pushFifo(var fifo: tFifo; value: integer);

var
 node: pNode;
begin
 new(node);
 node^.value := value;
 node^.next := nil;
 if fifo.first = nil
  then
   fifo.first := node
  else
   fifo.last^.next := node;
 fifo.last := node
end;

function popFifo(var fifo: tFifo; var value: integer): boolean;

var
 node: pNode;
begin
 if fifo.first = nil
  then
   popFifo := false
  else
   begin
    node := fifo.first;
    fifo.first := fifo.first^.next;
    value := node^.value;
    dispose(node);
    popFifo := true
   end
end;

procedure testFifo;

var
 fifo: tFifo;
procedure testpop(expectEmpty: boolean; expectedValue: integer);
 var
  i: integer;
 begin
  if popFifo(fifo, i)
   then
    if expectEmpty
     then
      writeln('Error! Expected empty, got ', i, '.')
     else
      if i = expectedValue
       then
        writeln('Ok, got ', i, '.')
       else
        writeln('Error! Expected ', expectedValue, ', got ', i, '.')
   else
    if expectEmpty
      then
       writeln('Ok, fifo is empty.')
      else
       writeln('Error! Expected ', expectedValue, ', found fifo empty.')
 end;
begin
 initFifo(fifo);
 pushFifo(fifo, 2);
 pushFifo(fifo, 3);
 pushFifo(fifo, 5);
 testpop(false, 2);
 pushFifo(fifo, 7);
 testpop(false, 3);
 testpop(false, 5);
 pushFifo(fifo, 11);
 testpop(false, 7);
 testpop(false, 11);
 pushFifo(fifo, 13);
 testpop(false, 13);
 testpop(true, 0);
 pushFifo(fifo, 17);
 testpop(false, 17);
 testpop(true, 0)
end;

begin

writeln('Testing fifo implementation ...');
testFifo;
writeln('Testing finished.')

end. </pascal>

Python

A python list can be used as a simple FIFO by simply using only it's .append() and .pop() methods and only using .pop(0) to consistently pull the head off the list. (The default .pop() pulls off the tail, and using that would treat the list as a stack.

To encapsulate this behavior into a class and provide the task's specific API we can simply use:

<python>

  class FIFO(object):
      def __init__(self, *args):
          self.contents = list()
          if len(args):
              self.contents.extend(*args)
      def __call__(self):
          return self.pop()
      def __len__(self):
          return len(self.contents)
      def pop(self):
          return self.contents.pop(0)
      def push(self, item):
          self.contents.append(item)
      def extend(self,*itemlist):
          self.contents.extend(*itemlist)
      def empty(self):
          if len(self.contents):
              return True
          else:
              return False
      def __iter__(self):
          return self
      def next(self):
          if self.empty():
              raise StopIteration
          return self.pop()

if __name__ == "__main__":

   # Sample usage:
   f = FIFO()
   f.push(3)
   f.push(2)
   f.push(1)
   while not f.empty():
       print f.pop(),
   # >>> 3 2 1
   # Another simple example gives the same results:
   f = FIFO(3,2,1)
   while not f.empty():
       print f(),
   # Another using the default "truth" value of the object
   # (implicitly calls on the length() of the object after
   # checking for a __nonzero__ method
   f = FIFO(3,2,1)
   while f:
       print f(),
   # Yet another, using more Pythonic iteration:
   f = FIFO(3,2,1)
   for i in f:
       print i,

</python>

This example does add to a couple of features which are easy in Python and allow this FIFO class to be used in ways that Python programmers might find more natural. Our __init__ accepts and optional list of initial values, we add __len__ and extend methods which simply wrap the corresponding list methods; we define a __call__ method to show how one can make objects "callable" as functions, and we define __iter__ and next() methods to facilitate using these FIFO objects with Python's prevalent iteration syntax (the for loop). The empty method could be implemented as simply an alias for __len__ --- but we've chosen to have it more strictly conform to the task specification. Implementing the __len__ method allows code using this object to test of emptiness using normal Python idioms for "truth" (any non-empty container is considered to be "true" and any empty container evaluates as "false").

These additional methods could be omitted and some could have been dispatched to the "contents" object by defining a __getattr__ method. (All methods that are note defined could be relayed to the contained list). This would allow us to skip our definitions of extend, __iter__, and __len__, and would allow contents of these objects to be access by indexes and slices as well as supporting all other list methods.

That sort of wrapper looks like:

<python>

class FIFO:  ## NOT a new-style class, must not derive from "object"
   def __init__(self,*args):
       self.contents = list()
       if len(args):
           for i in args:
               self.contents.append(i)
   def __call__(self):
       return self.pop()
   def empty(self):
       if self.contents:
           return True
       else:
           return False
   def pop(self):
           return self.contents.pop(0)
   def __getattr__(self, attr):
       return getattr(self.contents,attr)
   def next(self):
       if not self:
           raise StopIteration
       return self.pop()

</python>

As noted in the contents this must NOT be a new-style class, it must NOT but sub-classed from object nor any of its descendents. (A new-style implementation using __getattribute__ would be possible)

Works with: Python version 2.4+

Python 2.4 and later includes a deque class, supporting thread-safe, memory efficient appends and pops from either side of the deque with approximately the same O(1) performance in either direction. For other options see Python Cookbook.

from collections import deque
fifo = deque()
fifo. appendleft(value) # push
value = fifo.pop()
not fifo # empty
fifo.pop() -> raises IndexError when empty

V

V doesn't have mutable data. Below is an function interface for a fifo.

[fifo_create []].
[fifo_push swap cons].
[fifo_pop [[*rest a] : [*rest] a] view].
[fifo_empty? dup empty?].

Using it

|fifo_create 3 fifo_push 4 fifo_push 5 fifo_push ??
=[5 4 3]
|fifo_empty? puts
=false
|fifo_pop put fifo_pop put fifo_pop put
=3 4 5
|fifo_empty? puts
=true