module queue_class !------------------------------------------------------------------------------ !Program: Queue Class !Author: Chris Harper !Date: 4/15/2008 !------------------------------------------------------------------------------ implicit none type node integer :: data type(node), pointer :: next end type type queue type(node), pointer :: front type(node), pointer :: back integer :: count end type contains !constructor function new_queue() type(queue) :: new_queue nullify(new_queue%front) nullify(new_queue%back) new_queue%count = 0 end function !test for empty queue function is_empty(q) logical :: is_empty type(queue) :: q if (.not. associated(q%front)) then is_empty = .true. else is_empty = .false. end if end function !pushes an integer to the back of the queue subroutine push(q, a) type(queue) :: q integer :: a type(node), pointer :: new !make new node allocate(new) new%data = a !link new node if (.not. associated(q%front)) q%front => new if (associated(q%back)) q%back%next => new q%back => new q%count = q%count + 1 end subroutine !pops an integer from the front of the queue function pop(q) type(queue) :: q integer :: pop type(node), pointer :: t if (.not. is_empty(q)) then pop = q%front%data !update link if (associated(q%front%next)) then t => q%front q%front => q%front%next nullify(t%next) else nullify(q%front) nullify(q%back) end if q%count = q%count - 1 else !throwing an exception here would be better pop = -1 end if end function !converts a queue to an array !can be used to print queue contents function to_array(q) type(queue) :: q integer :: to_array(q%count) type(node), pointer :: i integer :: k i => q%front k = 1 !iterate through the queue do if (.not. associated(i)) exit to_array(k) = i%data i => i%next k = k + 1 end do end function end module