File: asmlink.mli

package info (click to toggle)
ocaml 1.05-2
  • links: PTS
  • area: non-free
  • in suites: hamm, slink
  • size: 7,472 kB
  • ctags: 12,935
  • sloc: ml: 37,142; ansic: 24,745; asm: 11,632; lisp: 1,957; sh: 1,801; makefile: 1,512; perl: 29; sed: 28
file content (29 lines) | stat: -rw-r--r-- 1,236 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
(***********************************************************************)
(*                                                                     *)
(*                           Objective Caml                            *)
(*                                                                     *)
(*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
(*                                                                     *)
(*  Copyright 1996 Institut National de Recherche en Informatique et   *)
(*  Automatique.  Distributed only by permission.                      *)
(*                                                                     *)
(***********************************************************************)

(* $Id: asmlink.mli,v 1.4 1996/04/30 14:42:11 xleroy Exp $ *)

(* Link a set of .cmx/.o files and produce an executable *)

val link: string list -> unit

type error =
    File_not_found of string
  | Not_an_object_file of string
  | Missing_implementations of string list
  | Inconsistent_interface of string * string * string
  | Inconsistent_implementation of string * string * string
  | Assembler_error of string
  | Linking_error

exception Error of error

val report_error: error -> unit