GPR#243: Faster test suite
(Xavier Leroy) git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@16466 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
54ace9943b
commit
3397e7ff16
|
@ -12,7 +12,7 @@
|
|||
|
||||
case $XARCH in
|
||||
i386)
|
||||
./configure
|
||||
myconfigure
|
||||
make world.opt
|
||||
sudo make install
|
||||
(cd testsuite && make all)
|
||||
|
|
7
Changes
7
Changes
|
@ -326,10 +326,6 @@ Libraries:
|
|||
- PR#6834: Add Obj.{first,last}_non_constant_constructor_tag
|
||||
(Mark Shinwell, request by Gabriel Scherer)
|
||||
|
||||
Libraries:
|
||||
- PR#6285: Add support for nanosecond precision in Unix.stat()
|
||||
(Jérémie Dimino, report by user 'gfxmonk')
|
||||
|
||||
Runtime:
|
||||
- PR#6078: Release the runtime system when calling caml_dlopen
|
||||
(Jérémie Dimino)
|
||||
|
@ -504,8 +500,6 @@ Feature wishes:
|
|||
(Christophe Troestler, review by Damien Doligez)
|
||||
- GPR#171: allow custom warning printers / catchers
|
||||
(Benjamin Canou, review by Damien Doligez)
|
||||
- Misplaced assertion in major_gc.c for no-naked-pointers mode
|
||||
(Stephen Dolan, Mark Shinwell)
|
||||
- GPR#191: Making gc.h and some part of memory.h public
|
||||
(Thomas Refis)
|
||||
|
||||
|
@ -517,6 +511,7 @@ OCaml 4.02.1 (14 Oct 2014):
|
|||
Standard library:
|
||||
* Add optional argument ?limit to Arg.align.
|
||||
|
||||
Bug Fixes:
|
||||
- PR#4099: Bug in Makefile.nt: won't stop on error
|
||||
(George Necula)
|
||||
- PR#6181: Improve MSVC build
|
||||
|
|
|
@ -302,4 +302,6 @@ CAMLextern value caml_set_oo_id(value obj);
|
|||
}
|
||||
#endif
|
||||
|
||||
extern intnat caml_stat_top_heap_wsz;
|
||||
|
||||
#endif /* CAML_MLVALUES_H */
|
||||
|
|
|
@ -178,6 +178,7 @@ again:
|
|||
}
|
||||
}
|
||||
if (retcode == -1) caml_sys_io_error(NO_ARG);
|
||||
CAMLassert (retcode > 0);
|
||||
return retcode;
|
||||
}
|
||||
|
||||
|
|
|
@ -197,7 +197,8 @@
|
|||
(insert-file-contents file))
|
||||
(message "Module %s not found" module))
|
||||
(while (re-search-forward
|
||||
"\\([ \t]*val\\|let\\|exception\\|external\\| [|]\\) \\([a-zA-Z_0-9'][a-zA-Z_0-9']*\\)\\|^ *[{]* \\([a-z_][A-Za-z_0-9]*\\) : [^;\n][^;\n]*;"
|
||||
(concat "\\([ \t]*val\\|let\\|exception\\|external\\| [|]\\) \\([a-zA-Z_0-9'][a-zA-Z_0-9']*\\)"
|
||||
"\\|^ *[{]* \\([a-z_][A-Za-z_0-9]*\\) : [^;\n][^;\n]*;")
|
||||
(point-max) 'move)
|
||||
(pop-to-buffer (current-buffer))
|
||||
(setq alist (cons (or (match-string 2) (match-string 3)) alist)))
|
||||
|
|
|
@ -215,7 +215,9 @@ module Scanning : SCANNING = struct
|
|||
;;
|
||||
|
||||
let char_count ib =
|
||||
if ib.ic_current_char_is_valid then ib.ic_char_count - 1 else ib.ic_char_count
|
||||
if ib.ic_current_char_is_valid
|
||||
then ib.ic_char_count - 1
|
||||
else ib.ic_char_count
|
||||
;;
|
||||
|
||||
let line_count ib = ib.ic_line_count;;
|
||||
|
@ -413,7 +415,7 @@ module Scanning : SCANNING = struct
|
|||
Memo.fold
|
||||
(fun ib opt ->
|
||||
match opt with
|
||||
| None -> if ib.ic_input_name == ic_name then Some ib else opt
|
||||
| None -> if ib.ic_input_name = ic_name then Some ib else opt
|
||||
| opt -> opt)
|
||||
memo_table None in
|
||||
match ib_option with
|
||||
|
|
|
@ -1,3 +1,15 @@
|
|||
(***********************************************************************)
|
||||
(* *)
|
||||
(* OCaml *)
|
||||
(* *)
|
||||
(* Mark Shinwell, Jane Street Europe *)
|
||||
(* *)
|
||||
(* Copyright 2014 Institut National de Recherche en Informatique et *)
|
||||
(* en Automatique. All rights reserved. This file is distributed *)
|
||||
(* under the terms of the Q Public License version 1.0. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
let () = Printexc.record_backtrace true
|
||||
|
||||
let finaliser _ = try raise Exit with _ -> ()
|
||||
|
|
|
@ -1,3 +1,15 @@
|
|||
(***********************************************************************)
|
||||
(* *)
|
||||
(* OCaml *)
|
||||
(* *)
|
||||
(* Xavier Leroy, projet Gallium, INRIA Rocquencourt *)
|
||||
(* *)
|
||||
(* Copyright 2014 Institut National de Recherche en Informatique et *)
|
||||
(* en Automatique. All rights reserved. This file is distributed *)
|
||||
(* under the terms of the Q Public License version 1.0. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
open Printf
|
||||
|
||||
let bug () =
|
||||
|
|
|
@ -1,3 +1,15 @@
|
|||
(***********************************************************************)
|
||||
(* *)
|
||||
(* OCaml *)
|
||||
(* *)
|
||||
(* Jacques Garrigue, Nagoya University *)
|
||||
(* *)
|
||||
(* Copyright 2013 Institut National de Recherche en Informatique et *)
|
||||
(* en Automatique. All rights reserved. This file is distributed *)
|
||||
(* under the terms of the Q Public License version 1.0. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
(* PR6216: wrong inlining of GADT match *)
|
||||
|
||||
type _ t =
|
||||
|
|
|
@ -1,3 +1,15 @@
|
|||
#(***********************************************************************)
|
||||
#(* *)
|
||||
#(* OCaml *)
|
||||
#(* *)
|
||||
#(* Mark Shinwell, Jane Street Europe *)
|
||||
#(* *)
|
||||
#(* Copyright 2014 Institut National de Recherche en Informatique et *)
|
||||
#(* en Automatique. All rights reserved. This file is distributed *)
|
||||
#(* under the terms of the Q Public License version 1.0. *)
|
||||
#(* *)
|
||||
#(***********************************************************************)
|
||||
|
||||
BASEDIR=../..
|
||||
MODULES=
|
||||
MAIN_MODULE=float_subst_boxed_number
|
||||
|
|
|
@ -1,3 +1,15 @@
|
|||
(***********************************************************************)
|
||||
(* *)
|
||||
(* OCaml *)
|
||||
(* *)
|
||||
(* Mark Shinwell, Jane Street Europe *)
|
||||
(* *)
|
||||
(* Copyright 2015 Institut National de Recherche en Informatique et *)
|
||||
(* en Automatique. All rights reserved. This file is distributed *)
|
||||
(* under the terms of the Q Public License version 1.0. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
module PR_6686 = struct
|
||||
type t =
|
||||
| A of float
|
||||
|
|
|
@ -189,9 +189,9 @@ let list_data data =
|
|||
|
||||
let _ =
|
||||
printf "-- Random integers, large range\n%!";
|
||||
TI1.test (random_integers 100_000 1_000_000);
|
||||
TI1.test (random_integers 20_000 1_000_000);
|
||||
printf "-- Random integers, narrow range\n%!";
|
||||
TI2.test (random_integers 100_000 1_000);
|
||||
TI2.test (random_integers 20_000 1_000);
|
||||
let d =
|
||||
try file_data "../../LICENSE" with Sys_error _ -> string_data in
|
||||
printf "-- Strings, generic interface\n%!";
|
||||
|
|
|
@ -131,4 +131,4 @@ let rmap() =
|
|||
|
||||
let _ =
|
||||
Random.init 42;
|
||||
for i = 1 to 25000 do test (rkey()) (rdata()) (rmap()) (rmap()) done
|
||||
for i = 1 to 10000 do test (rkey()) (rdata()) (rmap()) (rmap()) done
|
||||
|
|
|
@ -129,7 +129,7 @@ let rset() =
|
|||
|
||||
let _ =
|
||||
Random.init 42;
|
||||
for i = 1 to 25000 do test (relt()) (rset()) (rset()) done
|
||||
for i = 1 to 10000 do test (relt()) (rset()) (rset()) done
|
||||
|
||||
let () =
|
||||
(* #6645: check that adding an element to set that already contains
|
||||
|
|
|
@ -10,22 +10,30 @@
|
|||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
(* The bank account example, using events and channels *)
|
||||
|
||||
open Printf
|
||||
open Event
|
||||
|
||||
let ch = (new_channel() : string channel)
|
||||
type account = int channel * int channel
|
||||
|
||||
let rec sender msg =
|
||||
sync (send ch msg);
|
||||
sender msg
|
||||
let account (put_ch, get_ch) =
|
||||
let rec acc balance =
|
||||
select [
|
||||
wrap (send get_ch balance) (fun () -> acc balance);
|
||||
wrap (receive put_ch) (fun amount ->
|
||||
if balance + amount < 0 then failwith "negative balance";
|
||||
acc (balance + amount))
|
||||
]
|
||||
in acc 0
|
||||
|
||||
let rec receiver name =
|
||||
print_string (name ^ ": " ^ sync (receive ch) ^ "\n");
|
||||
flush stdout;
|
||||
receiver name
|
||||
let get ((put_ch, get_ch): account) = sync (receive get_ch)
|
||||
let put ((put_ch, get_ch): account) amount = sync (send put_ch amount)
|
||||
|
||||
let _ =
|
||||
Thread.create sender "hello";
|
||||
Thread.create sender "world";
|
||||
Thread.create receiver "A";
|
||||
receiver "B";
|
||||
exit 0
|
||||
let a : account = (new_channel(), new_channel()) in
|
||||
ignore (Thread.create account a);
|
||||
put a 100;
|
||||
printf "Current balance: %d\n" (get a);
|
||||
for i = 1 to 99 do put a (-2); put a 1 done;
|
||||
printf "Final balance: %d\n" (get a)
|
|
@ -0,0 +1,2 @@
|
|||
Current balance: 100
|
||||
Final balance: 1
|
|
@ -10,11 +10,22 @@
|
|||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
let print_message delay c =
|
||||
(* Test Thread.delay and its scheduling *)
|
||||
|
||||
open Printf
|
||||
|
||||
let tick (delay, count) =
|
||||
while true do
|
||||
print_char c; flush stdout; Thread.delay delay
|
||||
Thread.delay delay;
|
||||
incr count
|
||||
done
|
||||
|
||||
let _ =
|
||||
Thread.create (print_message 0.6666666666) 'a';
|
||||
print_message 1.0 'b'
|
||||
let c1 = ref 0 and c2 = ref 0 in
|
||||
ignore (Thread.create tick (0.333333333, c1));
|
||||
ignore (Thread.create tick (0.5, c2));
|
||||
Thread.delay 3.0;
|
||||
let n1 = !c1 and n2 = !c2 in
|
||||
if n1 >= 8 && n1 <= 10 && n2 >= 5 && n2 <= 7
|
||||
then printf "passed\n"
|
||||
else printf "FAILED (n1 = %d, n2 = %d)\n" n1 n2
|
|
@ -0,0 +1 @@
|
|||
passed
|
|
@ -98,7 +98,7 @@ let test_trunc_line ofile =
|
|||
(* The test *)
|
||||
|
||||
let main() =
|
||||
let ifile = try Sys.argv.(1) with _ -> "testio.ml" in
|
||||
let ifile = if Array.length Sys.argv > 1 then Sys.argv.(1) else "fileio.ml" in
|
||||
let ofile = Filename.temp_file "testio" "" in
|
||||
test "256-byte chunks, 256-byte chunks"
|
||||
(copy_file 256) (copy_file 256) ifile ofile;
|
||||
|
@ -118,15 +118,12 @@ let main() =
|
|||
(copy_file 613) (copy_file 1027) ifile ofile;
|
||||
test "0...8192 byte chunks"
|
||||
(copy_random 8192) (copy_random 8192) ifile ofile;
|
||||
test "line per line, short lines"
|
||||
copy_line copy_line "test-file-short-lines" ofile;
|
||||
let linesfile = Filename.temp_file "lines" "" in
|
||||
make_lines linesfile;
|
||||
test "line per line, short and long lines"
|
||||
test "line per line"
|
||||
copy_line copy_line linesfile ofile;
|
||||
test_trunc_line ofile;
|
||||
Sys.remove linesfile;
|
||||
Sys.remove ofile;
|
||||
exit 0
|
||||
Sys.remove ofile
|
||||
|
||||
let _ = Unix.handle_unix_error main (); exit 0
|
|
@ -16,9 +16,7 @@ passed
|
|||
passed
|
||||
0...8192 byte chunks
|
||||
passed
|
||||
line per line, short lines
|
||||
passed
|
||||
line per line, short and long lines
|
||||
line per line
|
||||
passed
|
||||
truncated line
|
||||
passed
|
|
@ -28,8 +28,6 @@ let create size init =
|
|||
notempty = Condition.create();
|
||||
notfull = Condition.create() }
|
||||
|
||||
let output_lock = Mutex.create()
|
||||
|
||||
let put p data =
|
||||
Mutex.lock p.lock;
|
||||
while (p.writepos + 1) mod Array.length p.buffer = p.readpos do
|
||||
|
@ -53,23 +51,24 @@ let get p =
|
|||
|
||||
(* Test *)
|
||||
|
||||
let buff = create 20 0
|
||||
|
||||
let rec produce n =
|
||||
Mutex.lock output_lock;
|
||||
print_int n; print_string "-->"; print_newline();
|
||||
Mutex.unlock output_lock;
|
||||
let rec produce buff n max =
|
||||
put buff n;
|
||||
if n < 10000 then produce (n+1)
|
||||
if n < max then produce buff (n+1) max
|
||||
|
||||
let rec consume () =
|
||||
let rec consume buff cur max =
|
||||
let n = get buff in
|
||||
Mutex.lock output_lock;
|
||||
print_string "-->"; print_int n; print_newline();
|
||||
Mutex.unlock output_lock;
|
||||
if n < 10000 then consume ()
|
||||
if n <> cur then false
|
||||
else if n = max then true
|
||||
else consume buff (cur + 1) max
|
||||
|
||||
let t1 = Thread.create produce 0
|
||||
let _ = consume ()
|
||||
|
||||
;;
|
||||
let _ =
|
||||
let buff1 = create 20 0 and buff2 = create 30 0 in
|
||||
let ok1 = ref false and ok2 = ref false in
|
||||
let _p1 = Thread.create (fun () -> produce buff1 0 10000) ()
|
||||
and _p2 = Thread.create (fun () -> produce buff2 0 8000) ()
|
||||
and c1 = Thread.create (fun () -> ok1 := consume buff1 0 10000) () in
|
||||
ok2 := consume buff2 0 8000;
|
||||
Thread.join c1;
|
||||
if !ok1 && !ok2
|
||||
then print_string "passed\n"
|
||||
else print_string "FAILED\n"
|
|
@ -0,0 +1 @@
|
|||
passed
|
|
@ -0,0 +1,45 @@
|
|||
(***********************************************************************)
|
||||
(* *)
|
||||
(* OCaml *)
|
||||
(* *)
|
||||
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
||||
(* *)
|
||||
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
||||
(* en Automatique. All rights reserved. This file is distributed *)
|
||||
(* under the terms of the Q Public License version 1.0. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
(* Producer-consumer with events and multiple producers *)
|
||||
|
||||
open Event
|
||||
|
||||
let rec produce chan n max =
|
||||
sync (send chan n);
|
||||
if n < max then produce chan (n + 1) max else sync (send chan (-1))
|
||||
|
||||
let rec consume chans sum =
|
||||
let rec mkreceive prev = function
|
||||
| [] -> []
|
||||
| chan :: rem as chans ->
|
||||
wrap (receive chan) (fun n ->
|
||||
if n < 0
|
||||
then consume (List.rev_append rem prev) sum
|
||||
else consume (List.rev_append chans prev) (sum + n))
|
||||
:: mkreceive (chan :: prev) rem
|
||||
in
|
||||
if chans = [] then sum else select (mkreceive [] chans)
|
||||
|
||||
let sum_0_n n = n * (n + 1) / 2
|
||||
|
||||
let _ =
|
||||
let chan1 = new_channel()
|
||||
and chan2 = new_channel()
|
||||
and chan3 = new_channel() in
|
||||
ignore (Thread.create (fun () -> produce chan1 0 5000) ());
|
||||
ignore (Thread.create (fun () -> produce chan2 0 2000) ());
|
||||
ignore (Thread.create (fun () -> produce chan3 0 1000) ());
|
||||
let n = consume [chan1; chan2; chan3] 0 in
|
||||
if n = sum_0_n 5000 + sum_0_n 2000 + sum_0_n 1000
|
||||
then print_string "passed\n"
|
||||
else print_string "FAILED\n"
|
|
@ -0,0 +1 @@
|
|||
passed
|
|
@ -10,36 +10,31 @@
|
|||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
open Printf
|
||||
open Thread
|
||||
let sieve primes =
|
||||
Event.sync (Event.send primes 2);
|
||||
let integers = Event.new_channel () in
|
||||
let rec enumerate n =
|
||||
Event.sync (Event.send integers n);
|
||||
enumerate (n + 2)
|
||||
and filter input =
|
||||
let n = Event.sync (Event.receive input)
|
||||
and output = Event.new_channel () in
|
||||
Event.sync (Event.send primes n);
|
||||
ignore(Thread.create filter output);
|
||||
(* On elimine de la sortie ceux qui sont des multiples de n *)
|
||||
while true do
|
||||
let m = Event.sync (Event.receive input) in
|
||||
(* print_int n; print_string ": "; print_int m; print_newline(); *)
|
||||
if m mod n <> 0 then Event.sync (Event.send output m)
|
||||
done in
|
||||
ignore(Thread.create filter integers);
|
||||
ignore(Thread.create enumerate 3)
|
||||
|
||||
let rec integers n ch =
|
||||
Event.sync (Event.send ch n);
|
||||
integers (n+1) ch
|
||||
let primes = Event.new_channel ()
|
||||
|
||||
let rec sieve n chin chout =
|
||||
let m = Event.sync (Event.receive chin)
|
||||
in if m mod n = 0
|
||||
then sieve n chin chout
|
||||
else Event.sync (Event.send chout m);
|
||||
sieve n chin chout
|
||||
|
||||
let rec print_primes ch max =
|
||||
let n = Event.sync (Event.receive ch)
|
||||
in if n > max
|
||||
then ()
|
||||
else begin
|
||||
printf "%d\n" n; flush stdout;
|
||||
let ch_after_n = Event.new_channel ()
|
||||
in Thread.create (sieve n ch) ch_after_n;
|
||||
print_primes ch_after_n max
|
||||
end
|
||||
|
||||
let go max =
|
||||
let ch = Event.new_channel ()
|
||||
in Thread.create (integers 2) ch;
|
||||
print_primes ch max;;
|
||||
|
||||
let _ = go 500
|
||||
|
||||
;;
|
||||
let _ =
|
||||
ignore(Thread.create sieve primes);
|
||||
for i = 1 to 50 do
|
||||
let n = Event.sync (Event.receive primes) in
|
||||
print_int n; print_newline()
|
||||
done
|
||||
|
|
|
@ -48,48 +48,3 @@
|
|||
223
|
||||
227
|
||||
229
|
||||
233
|
||||
239
|
||||
241
|
||||
251
|
||||
257
|
||||
263
|
||||
269
|
||||
271
|
||||
277
|
||||
281
|
||||
283
|
||||
293
|
||||
307
|
||||
311
|
||||
313
|
||||
317
|
||||
331
|
||||
337
|
||||
347
|
||||
349
|
||||
353
|
||||
359
|
||||
367
|
||||
373
|
||||
379
|
||||
383
|
||||
389
|
||||
397
|
||||
401
|
||||
409
|
||||
419
|
||||
421
|
||||
431
|
||||
433
|
||||
439
|
||||
443
|
||||
449
|
||||
457
|
||||
461
|
||||
463
|
||||
467
|
||||
479
|
||||
487
|
||||
491
|
||||
499
|
||||
|
|
|
@ -10,4 +10,4 @@
|
|||
# #
|
||||
#########################################################################
|
||||
|
||||
LC_ALL=C $SORT test1.result | $DIFF test1.reference -
|
||||
sed -e 1q signal.result | grep -q '^[ab]*Got ctrl-C, exiting...$'
|
|
@ -20,6 +20,6 @@ let print_message delay c =
|
|||
done
|
||||
|
||||
let _ =
|
||||
Sys.signal Sys.sigint (Sys.Signal_handle sighandler);
|
||||
Thread.create (print_message 0.6666666666) 'a';
|
||||
ignore (Sys.signal Sys.sigint (Sys.Signal_handle sighandler));
|
||||
ignore (Thread.create (print_message 0.6666666666) 'a');
|
||||
print_message 1.0 'b'
|
|
@ -10,7 +10,7 @@
|
|||
# #
|
||||
#########################################################################
|
||||
|
||||
$RUNTIME ./program >testsignal.result &
|
||||
$RUNTIME ./program >signal.result &
|
||||
pid=$!
|
||||
sleep 3
|
||||
sleep 2
|
||||
kill -INT $pid
|
|
@ -10,4 +10,4 @@
|
|||
# #
|
||||
#########################################################################
|
||||
|
||||
sed -e 1q test2.result | grep -q '^[ab]*'
|
||||
sed -e 1q signal2.result | grep -q '^[ab]*'
|
|
@ -16,8 +16,8 @@ let print_message delay c =
|
|||
done
|
||||
|
||||
let _ =
|
||||
Thread.sigmask Unix.SIG_BLOCK [Sys.sigint; Sys.sigterm];
|
||||
let th1 = Thread.create (print_message 0.6666666666) 'a' in
|
||||
let th2 = Thread.create (print_message 1.0) 'b' in
|
||||
ignore (Thread.sigmask Unix.SIG_BLOCK [Sys.sigint; Sys.sigterm]);
|
||||
ignore (Thread.create (print_message 0.6666666666) 'a');
|
||||
ignore (Thread.create (print_message 1.0) 'b');
|
||||
let s = Thread.wait_signal [Sys.sigint; Sys.sigterm] in
|
||||
Printf.printf "Got signal %d, exiting...\n" s
|
|
@ -10,9 +10,9 @@
|
|||
# #
|
||||
#########################################################################
|
||||
|
||||
$RUNTIME ./program >testsignal2.result &
|
||||
$RUNTIME ./program >signal2.result &
|
||||
pid=$!
|
||||
sleep 3
|
||||
sleep 2
|
||||
kill -INT $pid
|
||||
sleep 1
|
||||
kill -9 $pid 2>&- || true
|
|
@ -0,0 +1,52 @@
|
|||
(***********************************************************************)
|
||||
(* *)
|
||||
(* OCaml *)
|
||||
(* *)
|
||||
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
||||
(* *)
|
||||
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
||||
(* en Automatique. All rights reserved. This file is distributed *)
|
||||
(* under the terms of the Q Public License version 1.0. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
open Printf
|
||||
|
||||
(* Threads and sockets *)
|
||||
|
||||
let serve_connection s =
|
||||
let buf = String.make 1024 '>' in
|
||||
let n = Unix.read s buf 2 (String.length buf - 2) in
|
||||
Thread.delay 1.0;
|
||||
ignore (Unix.write s buf 0 (n + 2));
|
||||
Unix.close s
|
||||
|
||||
let server sock =
|
||||
while true do
|
||||
let (s, _) = Unix.accept sock in
|
||||
ignore(Thread.create serve_connection s)
|
||||
done
|
||||
|
||||
let client (addr, msg) =
|
||||
let sock =
|
||||
Unix.socket (Unix.domain_of_sockaddr addr) Unix.SOCK_STREAM 0 in
|
||||
Unix.connect sock addr;
|
||||
let buf = String.make 1024 ' ' in
|
||||
ignore(Unix.write sock msg 0 (String.length msg));
|
||||
let n = Unix.read sock buf 0 (String.length buf) in
|
||||
print_string (String.sub buf 0 n); flush stdout
|
||||
|
||||
let _ =
|
||||
let addr = Unix.ADDR_INET(Unix.inet_addr_loopback, 9876) in
|
||||
let sock =
|
||||
Unix.socket (Unix.domain_of_sockaddr addr) Unix.SOCK_STREAM 0 in
|
||||
Unix.setsockopt sock Unix.SO_REUSEADDR true;
|
||||
Unix.bind sock addr;
|
||||
Unix.listen sock 5;
|
||||
ignore (Thread.create server sock);
|
||||
ignore (Thread.create client (addr, "Client #1\n"));
|
||||
Thread.delay 0.5;
|
||||
client (addr, "Client #2\n")
|
||||
|
||||
|
||||
|
|
@ -0,0 +1,2 @@
|
|||
>>Client #1
|
||||
>>Client #2
|
|
@ -1,2 +1,2 @@
|
|||
f G
|
||||
g F
|
||||
f G
|
|
@ -1,10 +0,0 @@
|
|||
##
|
||||
# Host Database
|
||||
#
|
||||
# localhost is used to configure the loopback interface
|
||||
# when the system is booting. Do not change this entry.
|
||||
##
|
||||
127.0.0.1 localhost
|
||||
255.255.255.255 broadcasthost
|
||||
::1 localhost
|
||||
fe80::1%lo0 localhost
|
File diff suppressed because it is too large
Load Diff
|
@ -1,27 +0,0 @@
|
|||
(***********************************************************************)
|
||||
(* *)
|
||||
(* OCaml *)
|
||||
(* *)
|
||||
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
||||
(* *)
|
||||
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
||||
(* en Automatique. All rights reserved. This file is distributed *)
|
||||
(* under the terms of the Q Public License version 1.0. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
let yield = ref false
|
||||
|
||||
let print_message c =
|
||||
for i = 1 to 10000 do
|
||||
print_char c; flush stdout;
|
||||
if !yield then Thread.yield()
|
||||
done
|
||||
|
||||
let _ = yield := (Array.length Sys.argv > 1)
|
||||
let t1 = Thread.create print_message 'a'
|
||||
let t2 = Thread.create print_message 'b'
|
||||
let _ = Thread.join t1
|
||||
let _ = Thread.join t2
|
||||
|
||||
;;
|
|
@ -1,13 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Xavier Clerc, SED, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2010 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
sed -e 1q test3.result | grep -q '^[ab]*'
|
|
@ -1,16 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Xavier Clerc, SED, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2010 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
$RUNTIME ./program >test3.result &
|
||||
pid=$!
|
||||
sleep 5
|
||||
kill -9 $pid
|
|
@ -1,13 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Xavier Clerc, SED, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2010 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
LC_ALL=C $SORT -u test4.result | $DIFF test4.reference -
|
|
@ -1,3 +0,0 @@
|
|||
abc
|
||||
def
|
||||
ghi
|
|
@ -1,33 +0,0 @@
|
|||
(***********************************************************************)
|
||||
(* *)
|
||||
(* OCaml *)
|
||||
(* *)
|
||||
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
||||
(* *)
|
||||
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
||||
(* en Automatique. All rights reserved. This file is distributed *)
|
||||
(* under the terms of the Q Public License version 1.0. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
let output_lock = Mutex.create()
|
||||
|
||||
let rec fib n = if n <= 2 then 1 else fib(n-1) + fib(n-2)
|
||||
|
||||
let fibtask n =
|
||||
while true do
|
||||
let res = fib n in
|
||||
Mutex.lock output_lock;
|
||||
print_int res; print_newline();
|
||||
Mutex.unlock output_lock
|
||||
done
|
||||
|
||||
let _ =
|
||||
Thread.create fibtask 28;
|
||||
Thread.delay 1.0;
|
||||
while true do
|
||||
let l = read_line () in
|
||||
Mutex.lock output_lock;
|
||||
print_string ">> "; print_string l; print_newline();
|
||||
Mutex.unlock output_lock
|
||||
done
|
|
@ -1,4 +0,0 @@
|
|||
317811
|
||||
>> abc
|
||||
>> def
|
||||
>> ghi
|
|
@ -1,13 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Xavier Clerc, SED, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2010 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
$RUNTIME ./program <test4.data >test4.result 2>/dev/null || true
|
|
@ -1,13 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Xavier Clerc, SED, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2010 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
LC_ALL=C $SORT -u test5.result | $DIFF test5.reference -
|
|
@ -1,4 +0,0 @@
|
|||
A: hello
|
||||
A: world
|
||||
B: hello
|
||||
B: world
|
|
@ -1,16 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Xavier Clerc, SED, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2010 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
$RUNTIME ./program >test5.result &
|
||||
pid=$!
|
||||
sleep 3
|
||||
kill -9 $pid
|
|
@ -1,13 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Xavier Clerc, SED, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2010 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
LC_ALL=C $SORT -u test6.result | $DIFF test6.reference -
|
|
@ -1,27 +0,0 @@
|
|||
(***********************************************************************)
|
||||
(* *)
|
||||
(* OCaml *)
|
||||
(* *)
|
||||
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
||||
(* *)
|
||||
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
||||
(* en Automatique. All rights reserved. This file is distributed *)
|
||||
(* under the terms of the Q Public License version 1.0. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
open Event
|
||||
|
||||
let ch = (new_channel() : string channel)
|
||||
|
||||
let rec f tag msg =
|
||||
select [
|
||||
send ch msg;
|
||||
wrap (receive ch) (fun x -> print_string(tag ^ ": " ^ x); print_newline())
|
||||
];
|
||||
f tag msg
|
||||
|
||||
let _ =
|
||||
Thread.create (f "A") "hello";
|
||||
f "B" "world";
|
||||
exit 0
|
|
@ -1,13 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Damien Doligez, projet Gallium, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2013 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
$CANKILL
|
|
@ -1,2 +0,0 @@
|
|||
A: world
|
||||
B: hello
|
|
@ -1,16 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Xavier Clerc, SED, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2010 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
$RUNTIME ./program >test6.result &
|
||||
pid=$!
|
||||
sleep 1
|
||||
kill -9 $pid
|
|
@ -1,14 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Xavier Clerc, SED, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2010 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
test `grep -E '^-?[0123456789]+$' test7.result | wc -l` \
|
||||
= `cat test7.result | wc -l`
|
|
@ -1,38 +0,0 @@
|
|||
(***********************************************************************)
|
||||
(* *)
|
||||
(* OCaml *)
|
||||
(* *)
|
||||
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
||||
(* *)
|
||||
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
||||
(* en Automatique. All rights reserved. This file is distributed *)
|
||||
(* under the terms of the Q Public License version 1.0. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
open Event
|
||||
|
||||
let add_ch = new_channel()
|
||||
let sub_ch = new_channel()
|
||||
let read_ch = new_channel()
|
||||
|
||||
let rec accu n =
|
||||
select [
|
||||
wrap (receive add_ch) (fun x -> accu (n+x));
|
||||
wrap (receive sub_ch) (fun x -> accu (n-x));
|
||||
wrap (send read_ch n) (fun () -> accu n)
|
||||
]
|
||||
|
||||
let rec sender chan value =
|
||||
sync(send chan value); sender chan value
|
||||
|
||||
let read () =
|
||||
print_int(sync(receive read_ch)); print_newline()
|
||||
|
||||
let main () =
|
||||
Thread.create accu 0;
|
||||
Thread.create (sender add_ch) 1;
|
||||
Thread.create (sender sub_ch) 1;
|
||||
while true do read() done
|
||||
|
||||
let _ = Printexc.catch main ()
|
|
@ -1,13 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Damien Doligez, projet Gallium, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2013 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
$CANKILL
|
|
@ -1,16 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Xavier Clerc, SED, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2010 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
$RUNTIME ./program >test7.result &
|
||||
pid=$!
|
||||
sleep 1
|
||||
kill -9 $pid
|
|
@ -1,13 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Damien Doligez, projet Gallium, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2013 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
$CANKILL
|
|
@ -1,13 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Damien Doligez, projet Gallium, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2013 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
LC_ALL=C $SORT test9.result | $DIFF test9.reference -
|
|
@ -1,13 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Damien Doligez, projet Gallium, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2013 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
$CANKILL
|
|
@ -1,13 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Xavier Clerc, SED, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2010 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
LC_ALL=C $SORT testA.result | $DIFF testA.reference -
|
|
@ -1,13 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Xavier Clerc, SED, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2010 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
LC_ALL=C $SORT testexit.result | $DIFF testexit.reference -
|
|
@ -1,33 +0,0 @@
|
|||
(***********************************************************************)
|
||||
(* *)
|
||||
(* OCaml *)
|
||||
(* *)
|
||||
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
||||
(* *)
|
||||
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
||||
(* en Automatique. All rights reserved. This file is distributed *)
|
||||
(* under the terms of the Q Public License version 1.0. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
(* Test Thread.exit *)
|
||||
|
||||
let somethread (name, limit, last) =
|
||||
let counter = ref 0 in
|
||||
while true do
|
||||
incr counter;
|
||||
if !counter >= limit then begin
|
||||
print_string (name ^ " exiting\n");
|
||||
flush stdout;
|
||||
if last then exit 0 else Thread.exit()
|
||||
end;
|
||||
print_string (name ^ ": " ^ string_of_int !counter ^ "\n");
|
||||
flush stdout;
|
||||
Thread.delay 0.5
|
||||
done
|
||||
|
||||
let _ =
|
||||
let _ = Thread.create somethread ("A", 5, false) in
|
||||
let _ = Thread.create somethread ("B", 8, false) in
|
||||
let _ = Thread.create somethread ("C", 11, true) in
|
||||
somethread ("Main", 3, false)
|
|
@ -1,27 +0,0 @@
|
|||
A exiting
|
||||
A: 1
|
||||
A: 2
|
||||
A: 3
|
||||
A: 4
|
||||
B exiting
|
||||
B: 1
|
||||
B: 2
|
||||
B: 3
|
||||
B: 4
|
||||
B: 5
|
||||
B: 6
|
||||
B: 7
|
||||
C exiting
|
||||
C: 1
|
||||
C: 10
|
||||
C: 2
|
||||
C: 3
|
||||
C: 4
|
||||
C: 5
|
||||
C: 6
|
||||
C: 7
|
||||
C: 8
|
||||
C: 9
|
||||
Main exiting
|
||||
Main: 1
|
||||
Main: 2
|
|
@ -1,54 +0,0 @@
|
|||
(***********************************************************************)
|
||||
(* *)
|
||||
(* OCaml *)
|
||||
(* *)
|
||||
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
||||
(* *)
|
||||
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
||||
(* en Automatique. All rights reserved. This file is distributed *)
|
||||
(* under the terms of the Q Public License version 1.0. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
let sieve primes=
|
||||
Event.sync (Event.send primes 0);
|
||||
Event.sync (Event.send primes 1);
|
||||
Event.sync (Event.send primes 2);
|
||||
let integers = Event.new_channel () in
|
||||
let rec enumerate n=
|
||||
Event.sync (Event.send integers n);
|
||||
enumerate (n + 2)
|
||||
and filter inpout =
|
||||
let n = Event.sync (Event.receive inpout)
|
||||
(* On prepare le terrain pour l'appel recursif *)
|
||||
and output = Event.new_channel () in
|
||||
(* Celui qui etait en tete du crible est premier *)
|
||||
Event.sync (Event.send primes n);
|
||||
Thread.create filter output;
|
||||
(* On elimine de la sortie ceux qui sont des multiples de n *)
|
||||
while true do
|
||||
let m = Event.sync (Event.receive inpout) in
|
||||
(* print_int n; print_string ": "; print_int m; print_newline(); *)
|
||||
if (m mod n) = 0
|
||||
then ()
|
||||
else ((Event.sync (Event.send output m));())
|
||||
done in
|
||||
Thread.create filter integers;
|
||||
Thread.create enumerate 3
|
||||
|
||||
let premiers = Event.new_channel ()
|
||||
|
||||
let main _ =
|
||||
Thread.create sieve premiers;
|
||||
while true do
|
||||
for i = 1 to 100 do
|
||||
let n = Event.sync (Event.receive premiers) in
|
||||
print_int n; print_newline()
|
||||
done;
|
||||
exit 0
|
||||
done
|
||||
|
||||
|
||||
let _ =
|
||||
try main ()
|
||||
with _ -> exit 0;;
|
|
@ -1,100 +0,0 @@
|
|||
0
|
||||
1
|
||||
2
|
||||
3
|
||||
5
|
||||
7
|
||||
11
|
||||
13
|
||||
17
|
||||
19
|
||||
23
|
||||
29
|
||||
31
|
||||
37
|
||||
41
|
||||
43
|
||||
47
|
||||
53
|
||||
59
|
||||
61
|
||||
67
|
||||
71
|
||||
73
|
||||
79
|
||||
83
|
||||
89
|
||||
97
|
||||
101
|
||||
103
|
||||
107
|
||||
109
|
||||
113
|
||||
127
|
||||
131
|
||||
137
|
||||
139
|
||||
149
|
||||
151
|
||||
157
|
||||
163
|
||||
167
|
||||
173
|
||||
179
|
||||
181
|
||||
191
|
||||
193
|
||||
197
|
||||
199
|
||||
211
|
||||
223
|
||||
227
|
||||
229
|
||||
233
|
||||
239
|
||||
241
|
||||
251
|
||||
257
|
||||
263
|
||||
269
|
||||
271
|
||||
277
|
||||
281
|
||||
283
|
||||
293
|
||||
307
|
||||
311
|
||||
313
|
||||
317
|
||||
331
|
||||
337
|
||||
347
|
||||
349
|
||||
353
|
||||
359
|
||||
367
|
||||
373
|
||||
379
|
||||
383
|
||||
389
|
||||
397
|
||||
401
|
||||
409
|
||||
419
|
||||
421
|
||||
431
|
||||
433
|
||||
439
|
||||
443
|
||||
449
|
||||
457
|
||||
461
|
||||
463
|
||||
467
|
||||
479
|
||||
487
|
||||
491
|
||||
499
|
||||
503
|
||||
509
|
||||
521
|
|
@ -1,13 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Xavier Clerc, SED, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2010 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
sed -e 1q testsignal.result | grep -q '^[ab]*Got ctrl-C, exiting...$'
|
|
@ -1,13 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Damien Doligez, projet Gallium, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2013 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
$CANKILL
|
|
@ -1,13 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Damien Doligez, projet Gallium, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2013 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
$CANKILL
|
|
@ -1,48 +0,0 @@
|
|||
(***********************************************************************)
|
||||
(* *)
|
||||
(* OCaml *)
|
||||
(* *)
|
||||
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
||||
(* *)
|
||||
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
||||
(* en Automatique. All rights reserved. This file is distributed *)
|
||||
(* under the terms of the Q Public License version 1.0. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
open Unix
|
||||
|
||||
let engine verbose number address =
|
||||
print_int number; print_string "> connecting"; print_newline();
|
||||
let (ic, oc) = open_connection (ADDR_INET(address, 80)) in
|
||||
print_int number; print_string "> connected"; print_newline();
|
||||
output_string oc "GET / HTTP1.0\r\n\r\n"; flush oc;
|
||||
try
|
||||
while true do
|
||||
let s = input_line ic in
|
||||
if verbose then begin
|
||||
print_int number; print_string ">"; print_string s; print_newline()
|
||||
end
|
||||
done;
|
||||
with End_of_file ->
|
||||
close_out oc;
|
||||
print_int number; print_string "> data retrieved"; print_newline()
|
||||
|
||||
let main() =
|
||||
let verbose, argv =
|
||||
match Sys.argv with
|
||||
| [| _ |] -> false, [| Sys.argv.(0); "caml.inria.fr" |]
|
||||
| _ -> true, Sys.argv in
|
||||
let addresses = Array.make (Array.length argv - 1) inet_addr_any in
|
||||
for i = 1 to Array.length argv - 1 do
|
||||
addresses.(i - 1) <- (gethostbyname argv.(i)).h_addr_list.(0)
|
||||
done;
|
||||
let processes = Array.make (Array.length addresses) (Thread.self()) in
|
||||
for i = 0 to Array.length addresses - 1 do
|
||||
processes.(i) <- Thread.create (engine verbose i) addresses.(i)
|
||||
done;
|
||||
for i = 0 to Array.length processes - 1 do
|
||||
Thread.join processes.(i)
|
||||
done
|
||||
|
||||
let _ = Printexc.catch main (); exit 0
|
|
@ -1,3 +0,0 @@
|
|||
0> connecting
|
||||
0> connected
|
||||
0> data retrieved
|
|
@ -10,4 +10,4 @@
|
|||
# #
|
||||
#########################################################################
|
||||
|
||||
sed -e 1q testsignal2.result | grep -q '^[ab]*'
|
||||
LC_ALL=C $SORT tls.result | $DIFF tls.reference -
|
|
@ -1,48 +0,0 @@
|
|||
(***********************************************************************)
|
||||
(* *)
|
||||
(* OCaml *)
|
||||
(* *)
|
||||
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
||||
(* *)
|
||||
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
||||
(* en Automatique. All rights reserved. This file is distributed *)
|
||||
(* under the terms of the Q Public License version 1.0. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
(* Performance test for mutexes and conditions *)
|
||||
|
||||
let mut = Mutex.create()
|
||||
|
||||
let niter = ref 0
|
||||
|
||||
let token = ref 0
|
||||
|
||||
let process (n, conds, nprocs) =
|
||||
while true do
|
||||
Mutex.lock mut;
|
||||
while !token <> n do
|
||||
(* Printf.printf "Thread %d waiting (token = %d)\n" n !token; *)
|
||||
Condition.wait conds.(n) mut
|
||||
done;
|
||||
(* Printf.printf "Thread %d got token %d\n" n !token; *)
|
||||
incr token;
|
||||
if !token >= nprocs then token := 0;
|
||||
if n = 0 then begin
|
||||
decr niter;
|
||||
if !niter <= 0 then exit 0
|
||||
end;
|
||||
Condition.signal conds.(!token);
|
||||
Mutex.unlock mut
|
||||
done
|
||||
|
||||
let main() =
|
||||
let nprocs = try int_of_string Sys.argv.(1) with _ -> 100 in
|
||||
let iter = try int_of_string Sys.argv.(2) with _ -> 1000 in
|
||||
let conds = Array.make nprocs (Condition.create()) in
|
||||
for i = 1 to nprocs - 1 do conds.(i) <- Condition.create() done;
|
||||
niter := iter;
|
||||
for i = 0 to nprocs - 1 do Thread.create process (i, conds, nprocs) done;
|
||||
Thread.delay 3600.
|
||||
|
||||
let _ = main()
|
|
@ -1,51 +0,0 @@
|
|||
(***********************************************************************)
|
||||
(* *)
|
||||
(* OCaml *)
|
||||
(* *)
|
||||
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
||||
(* *)
|
||||
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
||||
(* en Automatique. All rights reserved. This file is distributed *)
|
||||
(* under the terms of the Q Public License version 1.0. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
(* Performance test for I/O scheduling *)
|
||||
|
||||
let mut = Mutex.create()
|
||||
|
||||
let niter = ref 0
|
||||
|
||||
let token = ref 0
|
||||
|
||||
let process (n, ins, outs, nprocs) =
|
||||
let buf = String.make 1 '.' in
|
||||
while buf <> "-" do
|
||||
Unix.read ins.(n) buf 0 1;
|
||||
(* Printf.printf "Thread %d got the token\n" n; *)
|
||||
if n = 0 then begin
|
||||
decr niter;
|
||||
if !niter <= 0 then buf.[0] <- '-';
|
||||
end;
|
||||
let next = if n + 1 >= nprocs then 0 else n + 1 in
|
||||
(* Printf.printf "Thread %d sending token to thread %d\n" n next; *)
|
||||
Unix.write outs.(next) buf 0 1
|
||||
done
|
||||
|
||||
let main() =
|
||||
let nprocs = try int_of_string Sys.argv.(1) with _ -> 100 in
|
||||
let iter = try int_of_string Sys.argv.(2) with _ -> 1000 in
|
||||
let ins = Array.make nprocs Unix.stdin in
|
||||
let outs = Array.make nprocs Unix.stdout in
|
||||
let threads = Array.make nprocs (Thread.self ()) in
|
||||
for n = 0 to nprocs - 1 do
|
||||
let (i, o) = Unix.pipe() in ins.(n) <- i; outs.(n) <- o
|
||||
done;
|
||||
niter := iter;
|
||||
for i = 0 to nprocs - 1 do
|
||||
threads.(i) <- Thread.create process (i, ins, outs, nprocs)
|
||||
done;
|
||||
Unix.write outs.(0) "X" 0 1;
|
||||
for i = 0 to nprocs - 1 do Thread.join threads.(i) done
|
||||
|
||||
let _ = main()
|
|
@ -1,3 +0,0 @@
|
|||
abc
|
||||
def
|
||||
ghi
|
|
@ -10,9 +10,9 @@
|
|||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
(* Torture test - lots of GC *)
|
||||
(* Torture test - I/O interspersed with lots of GC *)
|
||||
|
||||
let finished = ref false;;
|
||||
let finished = ref false
|
||||
|
||||
let gc_thread () =
|
||||
while not !finished do
|
||||
|
@ -21,35 +21,28 @@ let gc_thread () =
|
|||
Thread.yield()
|
||||
done
|
||||
|
||||
let stdin_thread () =
|
||||
while not !finished do
|
||||
print_string ">"; flush stdout;
|
||||
let s = read_line() in
|
||||
print_string " >>> "; print_string s; print_newline()
|
||||
done
|
||||
|
||||
let writer_thread (oc, size) =
|
||||
while not !finished do
|
||||
(* print_string "writer "; print_int size; print_newline(); *)
|
||||
let buff = String.make size 'a' in
|
||||
Unix.write oc buff 0 size
|
||||
ignore(Unix.write oc buff 0 size)
|
||||
done;
|
||||
let buff = String.make size 'b' in
|
||||
Unix.write oc buff 0 size
|
||||
ignore (Unix.write oc buff 0 size)
|
||||
|
||||
let reader_thread (ic, size) =
|
||||
while true do
|
||||
(* print_string "reader "; print_int size; print_newline(); *)
|
||||
let buff = String.create size in
|
||||
let buff = String.make size ' ' in
|
||||
let n = Unix.read ic buff 0 size in
|
||||
(* print_string "reader "; print_int n; print_newline(); *)
|
||||
for i = 0 to n-1 do
|
||||
if buff.[i] = 'b' then raise Exit
|
||||
else if buff.[i] <> 'a' then prerr_endline "error in reader_thread"
|
||||
if buff.[i] = 'b' then Thread.exit()
|
||||
else if buff.[i] <> 'a' then print_string "error in reader_thread\n"
|
||||
done
|
||||
done
|
||||
|
||||
let main() =
|
||||
let _ =
|
||||
let t1 = Thread.create gc_thread () in
|
||||
let (out1, in1) = Unix.pipe() in
|
||||
let t2 = Thread.create writer_thread (in1, 4096) in
|
||||
|
@ -57,10 +50,8 @@ let main() =
|
|||
let (out2, in2) = Unix.pipe() in
|
||||
let t4 = Thread.create writer_thread (in2, 16) in
|
||||
let t5 = Thread.create reader_thread (out2, 16) in
|
||||
try
|
||||
stdin_thread()
|
||||
with _ ->
|
||||
finished := true;
|
||||
List.iter Thread.join [t1; t2; t3; t4; t5]
|
||||
Thread.delay 3.0;
|
||||
finished := true;
|
||||
List.iter Thread.join [t1; t2; t3; t4; t5];
|
||||
print_string "passed\n"
|
||||
|
||||
let _ = main()
|
||||
|
|
|
@ -1,4 +1 @@
|
|||
> >>> abc
|
||||
> >>> def
|
||||
> >>> ghi
|
||||
>
|
||||
passed
|
||||
|
|
|
@ -1,13 +0,0 @@
|
|||
#########################################################################
|
||||
# #
|
||||
# OCaml #
|
||||
# #
|
||||
# Xavier Clerc, SED, INRIA Rocquencourt #
|
||||
# #
|
||||
# Copyright 2010 Institut National de Recherche en Informatique et #
|
||||
# en Automatique. All rights reserved. This file is distributed #
|
||||
# under the terms of the Q Public License version 1.0. #
|
||||
# #
|
||||
#########################################################################
|
||||
|
||||
$RUNTIME ./program <torture.data >torture.result 2>/dev/null || true
|
|
@ -76,4 +76,4 @@ let greater pair =
|
|||
match group_order pair with Greater -> true | _ -> false
|
||||
|
||||
let _ =
|
||||
for i = 1 to 20 do kb_complete greater [] geom_rules done
|
||||
kb_complete greater [] geom_rules
|
||||
|
|
File diff suppressed because it is too large
Load Diff
|
@ -312,6 +312,7 @@ let _ =
|
|||
Printf.printf "%d %.2f %.2f\n%!" p position.(0) position.(1)
|
||||
done;
|
||||
(* Benchmark *)
|
||||
(**
|
||||
for i = 0 to test_loops - 1 do
|
||||
jd.(0) <- j2000;
|
||||
jd.(1) <- 0.0;
|
||||
|
@ -323,3 +324,4 @@ let _ =
|
|||
done
|
||||
done
|
||||
done
|
||||
**)
|
||||
|
|
|
@ -183,4 +183,4 @@ let test np =
|
|||
print_newline()
|
||||
|
||||
let _ =
|
||||
let np = ref 16 in for i = 1 to 16 do test !np; np := !np*2 done
|
||||
let np = ref 16 in for i = 1 to 15 do test !np; np := !np*2 done
|
||||
|
|
|
@ -13,4 +13,3 @@
|
|||
65536... ok
|
||||
131072... ok
|
||||
262144... ok
|
||||
524288... ok
|
||||
|
|
|
@ -84,7 +84,7 @@ let test_sort sort_fun size =
|
|||
|
||||
|
||||
let main () =
|
||||
test_sort qsort 500000;
|
||||
test_sort qsort2 500000
|
||||
test_sort qsort 50000;
|
||||
test_sort qsort2 50000
|
||||
|
||||
let _ = main(); exit 0
|
||||
|
|
|
@ -213,9 +213,9 @@ let test_hwb bdd vars =
|
|||
|
||||
let main () =
|
||||
let n =
|
||||
if Array.length Sys.argv >= 2 then int_of_string Sys.argv.(1) else 22 in
|
||||
if Array.length Sys.argv >= 2 then int_of_string Sys.argv.(1) else 20 in
|
||||
let ntests =
|
||||
if Array.length Sys.argv >= 3 then int_of_string Sys.argv.(2) else 100 in
|
||||
if Array.length Sys.argv >= 3 then int_of_string Sys.argv.(2) else 10 in
|
||||
let bdd = hwb n in
|
||||
let succeeded = ref true in
|
||||
for i = 1 to ntests do
|
||||
|
|
|
@ -880,7 +880,7 @@ let term = cterm_to_term(
|
|||
|
||||
let _ =
|
||||
let ok = ref true in
|
||||
for i = 1 to 50 do
|
||||
for i = 1 to 10 do
|
||||
if not (tautp (apply_subst subst term)) then ok := false
|
||||
done;
|
||||
if !ok then
|
||||
|
@ -888,22 +888,3 @@ let _ =
|
|||
else
|
||||
print_string "Cannot prove!\n";
|
||||
exit 0
|
||||
|
||||
(*********
|
||||
with
|
||||
failure s ->
|
||||
print_string "Exception failure("; print_string s; print_string ")\n"
|
||||
| Unify ->
|
||||
print_string "Exception Unify\n"
|
||||
| match_failure(file,start,stop) ->
|
||||
print_string "Exception match_failure(";
|
||||
print_string file;
|
||||
print_string ",";
|
||||
print_int start;
|
||||
print_string ",";
|
||||
print_int stop;
|
||||
print_string ")\n"
|
||||
| _ ->
|
||||
print_string "Exception ?\n"
|
||||
|
||||
**********)
|
||||
|
|
|
@ -17,5 +17,5 @@ let _ =
|
|||
let n =
|
||||
if Array.length Sys.argv >= 2
|
||||
then int_of_string Sys.argv.(1)
|
||||
else 40 in
|
||||
else 30 in
|
||||
print_int(fib n); print_newline(); exit 0
|
||||
|
|
|
@ -1 +1 @@
|
|||
165580141
|
||||
1346269
|
||||
|
|
|
@ -3230,7 +3230,6 @@ let
|
|||
run () = most_distant_atom (pseudoknot ())
|
||||
|
||||
let main () =
|
||||
for i = 1 to 50 do ignore(run()) done;
|
||||
Printf.printf "%.4f" (run ()); print_newline()
|
||||
|
||||
let _ = main ()
|
||||
|
|
|
@ -193,9 +193,8 @@ let chklex b rstate n a = chkgen (mkrec1 b) cmplex rstate n a;;
|
|||
|
||||
let lens = [
|
||||
0; 1; 2; 3; 4; 5; 6; 7; 8; 9; 10; 11; 12; 13; 28;
|
||||
100; 127; 128; 129; 191; 192; 193; 506;
|
||||
1000; 1023; 1024; 1025; 1535; 1536; 1537; 2323;
|
||||
4000; 4094; 4096; 4098; 5123;
|
||||
100; 127; 128; 129; 193; 506;
|
||||
1000; 1025; 1535; 2323;
|
||||
];;
|
||||
|
||||
type ('a, 'b, 'c, 'd) aux = {
|
||||
|
|
|
@ -2,197 +2,197 @@ Command line arguments are:
|
|||
Testing List.sort...
|
||||
List.sort with constant ints
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.sort with sorted ints
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.sort with reverse-sorted ints
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.sort with random ints (many dups)
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.sort with random ints (few dups)
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.sort with records (str)
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.sort with records (int[1])
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.sort with records (int[10])
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.sort with records (int[100])
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.sort with records (int[1000])
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Testing List.stable_sort...
|
||||
List.stable_sort with constant ints
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.stable_sort with sorted ints
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.stable_sort with reverse-sorted ints
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.stable_sort with random ints (many dups)
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.stable_sort with random ints (few dups)
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.stable_sort with records (str)
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.stable_sort with records (int[1])
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.stable_sort with records (int[10])
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.stable_sort with records (int[100])
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.stable_sort with records (int[1000])
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.stable_sort with records (int[1]) [stable]
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.stable_sort with records (int[10]) [stable]
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.stable_sort with records (int[100]) [stable]
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
List.stable_sort with records (int[1000]) [stable]
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Testing Array.sort...
|
||||
Array.sort with constant ints
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.sort with sorted ints
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.sort with reverse-sorted ints
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.sort with random ints (many dups)
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.sort with random ints (few dups)
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.sort with records (str)
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.sort with records (int[1])
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.sort with records (int[10])
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.sort with records (int[100])
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.sort with records (int[1000])
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Testing Array.stable_sort...
|
||||
Array.stable_sort with constant ints
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.stable_sort with sorted ints
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.stable_sort with reverse-sorted ints
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.stable_sort with random ints (many dups)
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.stable_sort with random ints (few dups)
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.stable_sort with records (str)
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.stable_sort with records (int[1])
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.stable_sort with records (int[10])
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.stable_sort with records (int[100])
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.stable_sort with records (int[1000])
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.stable_sort with records (int[1]) [stable]
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.stable_sort with records (int[10]) [stable]
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.stable_sort with records (int[100]) [stable]
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Array.stable_sort with records (int[1000]) [stable]
|
||||
0. 1. 2. 3. 4. 5. 6. 7. 8. 9. 10. 11.
|
||||
12. 13. 28. 100. 127. 128. 129. 191. 192. 193. 506. 1000.
|
||||
1023. 1024. 1025. 1535. 1536. 1537. 2323. 4000. 4094. 4096. 4098. 5123.
|
||||
12. 13. 28. 100. 127. 128. 129. 193. 506. 1000. 1025. 1535.
|
||||
2323.
|
||||
Number of tests failed: 0
|
||||
|
|
Some files were not shown because too many files have changed in this diff Show More
Loading…
Reference in New Issue