diff options
Diffstat (limited to 'test')
-rw-r--r-- | test/KB/equations.ml | 4 | ||||
-rw-r--r-- | test/KB/equations.mli | 4 | ||||
-rw-r--r-- | test/KB/kb.ml | 4 | ||||
-rw-r--r-- | test/KB/kb.mli | 4 | ||||
-rw-r--r-- | test/KB/kbmain.ml | 4 | ||||
-rw-r--r-- | test/KB/orderings.ml | 4 | ||||
-rw-r--r-- | test/KB/orderings.mli | 4 | ||||
-rw-r--r-- | test/KB/terms.ml | 4 | ||||
-rw-r--r-- | test/KB/terms.mli | 4 | ||||
-rw-r--r-- | test/Lex/gram_aux.ml | 10 | ||||
-rw-r--r-- | test/Lex/grammar.mly | 4 | ||||
-rw-r--r-- | test/Lex/lexgen.ml | 14 | ||||
-rw-r--r-- | test/Lex/main.ml | 4 | ||||
-rw-r--r-- | test/Lex/output.ml | 4 | ||||
-rw-r--r-- | test/Lex/scan_aux.ml | 4 | ||||
-rw-r--r-- | test/Lex/scanner.mll | 4 | ||||
-rw-r--r-- | test/Lex/syntax.ml | 4 | ||||
-rw-r--r-- | test/Lex/testmain.ml | 4 | ||||
-rw-r--r-- | test/Lex/testscanner.mll | 4 | ||||
-rw-r--r-- | test/Makefile | 20 | ||||
-rw-r--r-- | test/Makefile.nt | 16 | ||||
-rw-r--r-- | test/Moretest/Makefile | 8 | ||||
-rw-r--r-- | test/Moretest/sets.ml | 4 | ||||
-rw-r--r-- | test/boyer.ml | 4 | ||||
-rw-r--r-- | test/fft.ml | 8 | ||||
-rw-r--r-- | test/fib.ml | 4 | ||||
-rw-r--r-- | test/nucleic.ml | 10 | ||||
-rw-r--r-- | test/quicksort.ml | 8 | ||||
-rw-r--r-- | test/sieve.ml | 4 | ||||
-rw-r--r-- | test/soli.ml | 6 | ||||
-rw-r--r-- | test/takc.ml | 4 | ||||
-rw-r--r-- | test/taku.ml | 4 |
32 files changed, 96 insertions, 96 deletions
diff --git a/test/KB/equations.ml b/test/KB/equations.ml index 92770283e..ed13f4eb4 100644 --- a/test/KB/equations.ml +++ b/test/KB/equations.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/KB/equations.mli b/test/KB/equations.mli index caa88ec96..619fd5710 100644 --- a/test/KB/equations.mli +++ b/test/KB/equations.mli @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/KB/kb.ml b/test/KB/kb.ml index b4d2b6d32..52c9e8d1e 100644 --- a/test/KB/kb.ml +++ b/test/KB/kb.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/KB/kb.mli b/test/KB/kb.mli index d715f2daf..c80771ab6 100644 --- a/test/KB/kb.mli +++ b/test/KB/kb.mli @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/KB/kbmain.ml b/test/KB/kbmain.ml index 61047351a..84d555dfd 100644 --- a/test/KB/kbmain.ml +++ b/test/KB/kbmain.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/KB/orderings.ml b/test/KB/orderings.ml index 2f30c8cb0..762d5849b 100644 --- a/test/KB/orderings.ml +++ b/test/KB/orderings.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/KB/orderings.mli b/test/KB/orderings.mli index 91777aeb0..678ffd5ba 100644 --- a/test/KB/orderings.mli +++ b/test/KB/orderings.mli @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/KB/terms.ml b/test/KB/terms.ml index d4790f6ed..493bfb262 100644 --- a/test/KB/terms.ml +++ b/test/KB/terms.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/KB/terms.mli b/test/KB/terms.mli index 7d1197074..302c3801a 100644 --- a/test/KB/terms.mli +++ b/test/KB/terms.mli @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/Lex/gram_aux.ml b/test/Lex/gram_aux.ml index 0d6d724c7..17eb892c0 100644 --- a/test/Lex/gram_aux.ml +++ b/test/Lex/gram_aux.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) @@ -29,11 +29,11 @@ let regexp_for_string s = let char_class c1 c2 = - let class = ref [] in + let cl = ref [] in for i = Char.code c2 downto Char.code c1 do - class := Char.chr i :: !class + cl := Char.chr i :: !cl done; - !class + !cl let all_chars = char_class '\001' '\255' diff --git a/test/Lex/grammar.mly b/test/Lex/grammar.mly index f5e8ba398..e0d989062 100644 --- a/test/Lex/grammar.mly +++ b/test/Lex/grammar.mly @@ -1,10 +1,10 @@ /***********************************************************************/ /* */ -/* Caml Special Light */ +/* Objective Caml */ /* */ /* Xavier Leroy, projet Cristal, INRIA Rocquencourt */ /* */ -/* Copyright 1995 Institut National de Recherche en Informatique et */ +/* Copyright 1996 Institut National de Recherche en Informatique et */ /* Automatique. Distributed only by permission. */ /* */ /***********************************************************************/ diff --git a/test/Lex/lexgen.ml b/test/Lex/lexgen.ml index 6dd225000..cf0d85d07 100644 --- a/test/Lex/lexgen.ml +++ b/test/Lex/lexgen.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) @@ -165,7 +165,7 @@ let rec lastpos = function let followpos size name_regexp_list = - let v = Array.new size [] in + let v = Array.create size [] in let fill_pos first = function OnChars pos -> v.(pos) <- merge_trans first v.(pos); () | ToAction _ -> () in @@ -195,7 +195,7 @@ let split_trans_set = (no_action, []) -let memory = (Hashtbl.new 131 : (transition list, int) Hashtbl.t) +let memory = (Hashtbl.create 131 : (transition list, int) Hashtbl.t) let todo = ref ([] : (transition list * int) list) let next = ref 0 @@ -222,8 +222,8 @@ let goto_state = function let transition_from chars follow pos_set = - let tr = Array.new 256 [] - and shift = Array.new 256 Backtrack in + let tr = Array.create 256 [] + and shift = Array.create 256 Backtrack in List.iter (fun pos -> List.iter @@ -259,7 +259,7 @@ let make_dfa lexdef = let states = map_on_states (translate_state chars follow) in let v = - Array.new (number_of_states()) (Perform 0) in + Array.create (number_of_states()) (Perform 0) in List.iter (fun (auto, i) -> v.(i) <- auto) states; (initial_states, v, actions) diff --git a/test/Lex/main.ml b/test/Lex/main.ml index bdf1176bc..1e8a7e81e 100644 --- a/test/Lex/main.ml +++ b/test/Lex/main.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/Lex/output.ml b/test/Lex/output.ml index 0b5350e75..2a94efe0b 100644 --- a/test/Lex/output.ml +++ b/test/Lex/output.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/Lex/scan_aux.ml b/test/Lex/scan_aux.ml index 7bf98bcf0..1c2db88db 100644 --- a/test/Lex/scan_aux.ml +++ b/test/Lex/scan_aux.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/Lex/scanner.mll b/test/Lex/scanner.mll index bc3cc29f6..08a687325 100644 --- a/test/Lex/scanner.mll +++ b/test/Lex/scanner.mll @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/Lex/syntax.ml b/test/Lex/syntax.ml index 6685f8e7e..40ced286c 100644 --- a/test/Lex/syntax.ml +++ b/test/Lex/syntax.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/Lex/testmain.ml b/test/Lex/testmain.ml index 1862c592e..969890f3b 100644 --- a/test/Lex/testmain.ml +++ b/test/Lex/testmain.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/Lex/testscanner.mll b/test/Lex/testscanner.mll index f01ff5cca..3a88596ee 100644 --- a/test/Lex/testscanner.mll +++ b/test/Lex/testscanner.mll @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/Makefile b/test/Makefile index fd1542e67..8b3b2eb6a 100644 --- a/test/Makefile +++ b/test/Makefile @@ -1,12 +1,12 @@ include ../config/Makefile -CAMLC=../boot/cslrun ../cslc -I ../stdlib -I KB -I Lex -CAMLOPT=../boot/cslrun ../cslopt -I ../stdlib -I KB -I Lex +CAMLC=../boot/ocamlrun ../ocamlc -I ../stdlib -I KB -I Lex +CAMLOPT=../boot/ocamlrun ../ocamlopt -I ../stdlib -I KB -I Lex OPTFLAGS=-S -CAMLYACC=../yacc/cslyacc -CAMLLEX=../boot/cslrun ../lex/csllex -CAMLDEP=../boot/cslrun ../tools/csldep -CAMLRUN=../byterun/cslrun +CAMLYACC=../yacc/ocamlyacc +CAMLLEX=../boot/ocamlrun ../lex/ocamllex +CAMLDEP=../boot/ocamlrun ../tools/ocamldep +CAMLRUN=../byterun/ocamlrun CODERUNPARAMS=CAMLRUNPARAM='o=100' BYTE_EXE=fib.byt takc.byt taku.byt sieve.byt quicksort.byt quicksort.fast.byt \ @@ -57,14 +57,14 @@ clean:: rm -f Lex/*.cm[iox] Lex/*.[os] rm -f Lex/*~ -Lex/grammar.ml Lex/grammar.mli: Lex/grammar.mly ../yacc/cslyacc +Lex/grammar.ml Lex/grammar.mli: Lex/grammar.mly ../yacc/ocamlyacc $(CAMLYACC) $(YACCFLAGS) Lex/grammar.mly clean:: rm -f Lex/grammar.ml Lex/grammar.mli beforedepend:: Lex/grammar.ml Lex/grammar.mli -Lex/scanner.ml: Lex/scanner.mll ../lex/csllex +Lex/scanner.ml: Lex/scanner.mll ../lex/ocamllex $(CAMLLEX) Lex/scanner.mll clean:: @@ -101,9 +101,9 @@ beforedepend:: Lex/scanner.ml .ml.cmx: $(CAMLOPT) $(OPTFLAGS) -c $< -$(BYTE_EXE) $(BYTE_KB) $(BYTE_GENLEX): ../cslc +$(BYTE_EXE) $(BYTE_KB) $(BYTE_GENLEX): ../ocamlc $(BYTE_EXE): ../stdlib/stdlib.cma -$(CODE_EXE) $(CODE_KB) $(CODE_GENLEX): ../cslopt +$(CODE_EXE) $(CODE_KB) $(CODE_GENLEX): ../ocamlopt $(CODE_EXE): ../stdlib/stdlib.cmxa ../stdlib/libasmrun.a clean:: diff --git a/test/Makefile.nt b/test/Makefile.nt index 3b2d8474c..88ae492f1 100644 --- a/test/Makefile.nt +++ b/test/Makefile.nt @@ -1,12 +1,12 @@ !include ..\config\Makefile.nt -CAMLC=..\boot\cslrun ..\cslc -I ..\stdlib -I KB -I Lex -CAMLOPT=..\boot\cslrun ..\cslopt -I ..\stdlib -I KB -I Lex +CAMLC=..\boot\ocamlrun ..\ocamlc -I ..\stdlib -I KB -I Lex +CAMLOPT=..\boot\ocamlrun ..\ocamlopt -I ..\stdlib -I KB -I Lex OPTFLAGS=-S -CAMLYACC=..\yacc\cslyacc -CAMLLEX=..\boot\cslrun ..\lex\csllex -CAMLDEP=..\boot\cslrun ..\tools\csldep -CAMLRUN=..\byterun\cslrun +CAMLYACC=..\yacc\ocamlyacc +CAMLLEX=..\boot\ocamlrun ..\lex\ocamllex +CAMLDEP=..\boot\ocamlrun ..\tools\ocamldep +CAMLRUN=..\byterun\ocamlrun CODERUNPARAMS=CAMLRUNPARAM='o=100' BYTE_EXE=fib.byt takc.byt taku.byt sieve.byt quicksort.byt quicksort.fast.byt \ @@ -121,9 +121,9 @@ fft.fast.exe: fft.ml .ml.cmx: $(CAMLOPT) $(OPTFLAGS) -c $< -$(BYTE_EXE) $(BYTE_KB) $(BYTE_GENLEX): ..\cslc +$(BYTE_EXE) $(BYTE_KB) $(BYTE_GENLEX): ..\ocamlc $(BYTE_EXE): ..\stdlib\stdlib.cma -$(CODE_EXE) $(CODE_KB) $(CODE_GENLEX): ..\cslopt +$(CODE_EXE) $(CODE_KB) $(CODE_GENLEX): ..\ocamlopt $(CODE_EXE): ..\stdlib\stdlib.cmxa ..\stdlib\libasmrun.lib clean:: diff --git a/test/Moretest/Makefile b/test/Moretest/Makefile index e8b083b43..e79523031 100644 --- a/test/Moretest/Makefile +++ b/test/Moretest/Makefile @@ -1,10 +1,10 @@ include ../../config/Makefile -CAMLC=../../boot/cslrun ../../cslc -I ../../stdlib -CAMLOPT=../../boot/cslrun ../../cslopt -I ../../stdlib +CAMLC=../../boot/ocamlrun ../../ocamlc -I ../../stdlib +CAMLOPT=../../boot/ocamlrun ../../ocamlopt -I ../../stdlib OPTFLAGS=-S -CAMLDEP=../../boot/cslrun ../../tools/csldep -CAMLRUN=../../byterun/cslrun +CAMLDEP=../../boot/ocamlrun ../../tools/ocamldep +CAMLRUN=../../byterun/ocamlrun CODERUNPARAMS=CAMLRUNPARAM='o=100' callback.byt: callback.cmo callbackprim.o diff --git a/test/Moretest/sets.ml b/test/Moretest/sets.ml index 4a363d62d..7d295823b 100644 --- a/test/Moretest/sets.ml +++ b/test/Moretest/sets.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/boyer.ml b/test/boyer.ml index 054699271..5eaceff9a 100644 --- a/test/boyer.ml +++ b/test/boyer.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/fft.ml b/test/fft.ml index 7a7517c4c..9dabe517d 100644 --- a/test/fft.ml +++ b/test/fft.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) @@ -136,8 +136,8 @@ let test np = print_int np; print_string "... "; flush stdout; let enp = float np in let npm = np / 2 - 1 in - let pxr = Array.new (np+2) 0.0 - and pxi = Array.new (np+2) 0.0 in + let pxr = Array.create (np+2) 0.0 + and pxi = Array.create (np+2) 0.0 in let t = pi /. enp in pxr.(1) <- (enp -. 1.0) *. 0.5; pxi.(1) <- 0.0; diff --git a/test/fib.ml b/test/fib.ml index bb8833729..ef7aa3bfc 100644 --- a/test/fib.ml +++ b/test/fib.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/nucleic.ml b/test/nucleic.ml index 931ac178f..146809e87 100644 --- a/test/nucleic.ml +++ b/test/nucleic.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) @@ -2875,15 +2875,15 @@ let rec get_var id (v::lst) = (* Sequential backtracking algorithm *) -let rec search (partial_inst : variable list) l constraint = +let rec search (partial_inst : variable list) l constr = match l with [] -> [partial_inst] | (h::t) -> let rec try_assignments = function [] -> [] | v::vs -> - if constraint v partial_inst then - (search (v::partial_inst) t constraint) @ (try_assignments vs) + if constr v partial_inst then + (search (v::partial_inst) t constr) @ (try_assignments vs) else try_assignments vs in diff --git a/test/quicksort.ml b/test/quicksort.ml index 7a484b259..0f42248d9 100644 --- a/test/quicksort.ml +++ b/test/quicksort.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) @@ -64,8 +64,8 @@ let random() = exception Failed let test_sort sort_fun size = - let a = Array.new size 0 in - let check = Array.new 4096 0 in + let a = Array.create size 0 in + let check = Array.create 4096 0 in for i = 0 to size-1 do let n = random() in a.(i) <- n; check.(n) <- check.(n)+1 done; diff --git a/test/sieve.ml b/test/sieve.ml index 4a11e9020..22dc759bb 100644 --- a/test/sieve.ml +++ b/test/sieve.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/soli.ml b/test/soli.ml index e143d4761..80c2b8673 100644 --- a/test/soli.ml +++ b/test/soli.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) @@ -49,7 +49,7 @@ let dir = [| {dx = 0; dy = 1}; {dx = 1; dy = 0}; type move = { x1: int; y1: int; x2: int; y2: int } -let moves = Array.new 31 {x1=0;y1=0;x2=0;y2=0} +let moves = Array.create 31 {x1=0;y1=0;x2=0;y2=0} let counter = ref 0 diff --git a/test/takc.ml b/test/takc.ml index 627f26423..c561b8156 100644 --- a/test/takc.ml +++ b/test/takc.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/test/taku.ml b/test/taku.ml index e14225300..95dab2ea7 100644 --- a/test/taku.ml +++ b/test/taku.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) |