add a few missing copyright headers

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13485 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Damien Doligez 2013-04-04 15:27:13 +00:00
parent e2eacb06cd
commit a3f9e65668
39 changed files with 468 additions and 0 deletions

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* 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. *)
(* *)
(***********************************************************************)
(* Exotic OCaml syntax constructs found in the manual that are not *)
(* used in the source of the OCaml distribution (even in the tests). *)

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 f x = print_string "This is Main.f\n"; x
let () = Registry.register f

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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. *)
(* *)
(***********************************************************************)
external stub1: unit -> string = "stub1"
let f x = print_string "This is Plug1.f\n"; x + 1

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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. *)
(* *)
(***********************************************************************)
external stub2: unit -> unit = "stub2"
let f x = print_string "This is Plug2.f\n"; x + 2

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Xavier Leroy, projet Gallium, INRIA Rocquencourt *)
(* *)
(* Copyright 2012 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 functions = ref ([]: (int -> int) list)
let register f =

View File

@ -1,3 +1,15 @@
/***********************************************************************/
/* */
/* OCaml */
/* */
/* Alain Frisch, LexiFi */
/* */
/* Copyright 2007 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. */
/* */
/***********************************************************************/
#include "caml/mlvalues.h"
#include "caml/memory.h"
#include "caml/alloc.h"

View File

@ -1,3 +1,15 @@
/***********************************************************************/
/* */
/* OCaml */
/* */
/* Alain Frisch, LexiFi */
/* */
/* Copyright 2007 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. */
/* */
/***********************************************************************/
#include "caml/mlvalues.h"
#include "caml/memory.h"
#include "caml/alloc.h"

View File

@ -1,3 +1,15 @@
/***********************************************************************/
/* */
/* OCaml */
/* */
/* Alain Frisch, LexiFi */
/* */
/* Copyright 2007 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. */
/* */
/***********************************************************************/
#include <caml/memory.h>
#include <caml/alloc.h>
#include <caml/mlvalues.h>

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 load s =
Printf.printf "Loading %s\n%!" s;
try

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 f x = x.{2}
let () =

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 x = ref 0
let u = Random.int 1000

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 mods = ref []
let reg_mod name =

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 () =
print_endline "B is running";
incr A.x;

View File

@ -1,2 +1,14 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 () = try raise (Invalid_argument "X") with Invalid_argument s ->
raise (Invalid_argument (s ^ s))

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 () =
print_endline "C is running";
incr A.x;

View File

@ -1,3 +1,15 @@
/***********************************************************************/
/* */
/* OCaml */
/* */
/* Alain Frisch, LexiFi */
/* */
/* Copyright 2007 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. */
/* */
/***********************************************************************/
#include "caml/mlvalues.h"
#include "caml/memory.h"
#include "caml/alloc.h"

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 () =
Api.add_cb (fun () -> print_endline "Callback from main")

View File

@ -1,2 +1,14 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 () =
print_endline Mypack.Packed1.mykey

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 () =
Api.reg_mod "Packed1"

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 () =
Api.reg_mod "Packed1_client";
print_endline Packed1.mykey

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 rec f x = ignore ([x]); f x
let rec fact n = if n = 0 then 1 else n * fact (n - 1)

View File

@ -1 +1,13 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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. *)
(* *)
(***********************************************************************)
val facts: int list

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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. *)
(* *)
(***********************************************************************)
(*external ex: int -> int = "caml_ex"*)
let () =

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 () =
Printf.printf "time = %f\n" (Unix.time ());
Api.reg_mod "Plugin"

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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. *)
(* *)
(***********************************************************************)
external fact: int -> string = "factorial"
let () =

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 f x x x x x x x x x x x x x = ()
let g x = f x x x x x x x x

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 x = ref 0
let () =

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 facts = [ (Random.int 4) ]
let () = print_endline "COUCOU"; print_char '\n'

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 () =
Api.reg_mod "Plugin_thread";
let _t =

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 f i =
Printf.printf "Sub/api: f called with %i\n" i;
i + 1

View File

@ -1 +1,13 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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. *)
(* *)
(***********************************************************************)
val f : int -> int

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 rec fact n = if n = 0 then 1 else n * fact (n - 1)
let facts = [ fact 1; fact 2; fact 3; fact 4; fact 5 ]

View File

@ -1,2 +1,14 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Alain Frisch, LexiFi *)
(* *)
(* Copyright 2007 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 () =
ignore (Api.f 10)

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Damien Doligez, projet Gallium, INRIA Rocquencourt *)
(* *)
(* Copyright 2011 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. *)
(* *)
(***********************************************************************)
type t;;
type xdr_value;;

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Damien Doligez, projet Gallium, INRIA Rocquencourt *)
(* *)
(* Copyright 2011 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 marshal_int f =
match [] with
| _ :: `INT n :: _ -> f n

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Damien Doligez, projet Gallium, INRIA Rocquencourt *)
(* *)
(* Copyright 2012 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;;
(* PR#5233: Create a dangling pointer and use it to access random parts

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Damien Doligez, projet Gallium, INRIA Rocquencourt *)
(* *)
(* Copyright 2012 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. *)
(* *)
(***********************************************************************)
Random.init 3;;
for i = 0 to 100_000 do
ignore (String.create (Random.int 1_000_000))

View File

@ -1,3 +1,15 @@
(***********************************************************************)
(* *)
(* OCaml *)
(* *)
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* *)
(* Copyright 2001 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 rec f x =
if not (x = 0 || x = 10000 || x = 20000)
then 1 + f (x + 1)

View File

@ -1 +1,13 @@
(***********************************************************************)
(* *)
(* 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 channel = open_out "titi:/toto"