diff options
author | Xavier Leroy <xavier.leroy@inria.fr> | 1995-05-04 10:15:53 +0000 |
---|---|---|
committer | Xavier Leroy <xavier.leroy@inria.fr> | 1995-05-04 10:15:53 +0000 |
commit | 61bd8ace6bdb2652f4d51d64e3239a7105f56c26 (patch) | |
tree | e8b957df0957c1b483d41d68973824e280445548 /stdlib/queue.ml | |
parent | 8f9ea2a7b886e3e0a5cfd76b11fe79d083a7f20c (diff) |
Passage a la version bootstrappee (franchissement du Rubicon)
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@2 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/queue.ml')
-rw-r--r-- | stdlib/queue.ml | 58 |
1 files changed, 58 insertions, 0 deletions
diff --git a/stdlib/queue.ml b/stdlib/queue.ml new file mode 100644 index 000000000..977a26338 --- /dev/null +++ b/stdlib/queue.ml @@ -0,0 +1,58 @@ +exception Empty + +type 'a queue_cell = + Nil + | Cons of 'a * 'a queue_cell ref + +type 'a t = + { mutable head: 'a queue_cell; + mutable tail: 'a queue_cell } + +let new () = + { head = Nil; tail = Nil } + +let clear q = + q.head <- Nil; q.tail <- Nil + +let add x q = + match q.tail with + Nil -> (* if tail = Nil then head = Nil *) + let c = Cons(x, ref Nil) in + q.head <- c; q.tail <- c + | Cons(_, newtailref) -> + let c = Cons(x, ref Nil) in + newtailref := c; + q.tail <- c + +let peek q = + match q.head with + Nil -> + raise Empty + | Cons(x, _) -> + x + +let take q = + match q.head with + Nil -> + raise Empty + | Cons(x, rest) -> + q.head <- !rest; + begin match !rest with + Nil -> q.tail <- Nil + | _ -> () + end; + x + +let rec length_aux = function + Nil -> 0 + | Cons(_, rest) -> succ (length_aux !rest) + +let length q = length_aux q.head + +let rec iter_aux f = function + Nil -> + () + | Cons(x, rest) -> + f x; iter_aux f !rest + +let iter f q = iter_aux f q.head |