summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorDamien Doligez <damien.doligez-inria.fr>2000-01-07 16:05:19 +0000
committerDamien Doligez <damien.doligez-inria.fr>2000-01-07 16:05:19 +0000
commit00089ba61a960ea4f85ff6945558b3c512b1dbaa (patch)
treef73401da1dedcc8e61a129ac186a4d5e003b3d9e
parent96ddeabcb78cbce02561d9ae66891d7e56a8fc68 (diff)
detabisation
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@2741 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--byterun/io.c17
-rw-r--r--byterun/main.c2
-rw-r--r--otherlibs/graph/color.c18
-rw-r--r--otherlibs/graph/graphics.mli2
-rw-r--r--otherlibs/graph/make_img.c3
-rw-r--r--otherlibs/labltk/browser/README20
-rw-r--r--otherlibs/labltk/example/README15
-rw-r--r--otherlibs/str/str.mli13
-rw-r--r--otherlibs/threads/threadUnix.mli9
-rw-r--r--otherlibs/unix/unix.mli28
10 files changed, 61 insertions, 66 deletions
diff --git a/byterun/io.c b/byterun/io.c
index 24949c578..1f0e04be2 100644
--- a/byterun/io.c
+++ b/byterun/io.c
@@ -52,7 +52,7 @@ void (*channel_mutex_unlock_exn) (void) = NULL;
No locking is performed. */
/* Functions shared between input and output */
-
+
struct channel * open_descriptor(int fd)
{
struct channel * channel;
@@ -71,7 +71,7 @@ void close_channel(struct channel *channel)
close(channel->fd);
if (channel_mutex_free != NULL) (*channel_mutex_free)(channel);
stat_free(channel);
-}
+}
long channel_size(struct channel *channel)
{
@@ -356,7 +356,7 @@ long input_scan_line(struct channel *channel)
n = do_read(channel->fd, channel->max, channel->end - channel->max);
if (n == 0) {
/* End-of-file encountered. Return the number of characters in the
- buffer, with negative sign since we haven't encountered
+ buffer, with negative sign since we haven't encountered
a newline. */
return -(channel->max - channel->curr);
}
@@ -479,11 +479,11 @@ value caml_output(value vchannel, value buff, value start, value length) /* ML *
long len = Long_val(length);
Lock(channel);
- while (len > 0) {
- int written = putblock(channel, &Byte(buff, pos), len);
- pos += written;
- len -= written;
- }
+ while (len > 0) {
+ int written = putblock(channel, &Byte(buff, pos), len);
+ pos += written;
+ len -= written;
+ }
Unlock(channel);
CAMLreturn (Val_unit);
}
@@ -563,4 +563,3 @@ value caml_input_scan_line(value vchannel) /* ML */
Unlock(channel);
return Val_long(res);
}
-
diff --git a/byterun/main.c b/byterun/main.c
index ecbf0445e..ecdd70f48 100644
--- a/byterun/main.c
+++ b/byterun/main.c
@@ -12,7 +12,7 @@
/* $Id$ */
-/* Main entry point (can be overriden by a user-provided main()
+/* Main entry point (can be overridden by a user-provided main()
function that calls caml_main() later). */
#include "misc.h"
diff --git a/otherlibs/graph/color.c b/otherlibs/graph/color.c
index 2bde01cce..65a5a3ad6 100644
--- a/otherlibs/graph/color.c
+++ b/otherlibs/graph/color.c
@@ -61,8 +61,8 @@ unsigned long gr_pixel_rgb(int rgb)
if (direct_rgb){
switch ( bits_per_pixel ){
case 16:
- tmp = ((r >> 3) << 11) + ((g >> 2) << 5) + ((b >> 3) << 0);
- return (unsigned long) tmp;
+ tmp = ((r >> 3) << 11) + ((g >> 2) << 5) + ((b >> 3) << 0);
+ return (unsigned long) tmp;
case 32:
return (r << 16) + (g << 8) + (b << 0);
}
@@ -75,13 +75,13 @@ unsigned long gr_pixel_rgb(int rgb)
if (color_cache[i].rgb == rgb) return color_cache[i].pixel;
i = (i + 1) & (Color_cache_size - 1);
if (i == h) {
- /* Cache is full. Instead of inserting at slot h, which causes
- thrashing if many colors hash to the same value,
- insert at h + n where n is pseudo-random and
- smaller than Color_cache_slack */
- int slack = num_overflows++ & (Color_cache_slack - 1);
- i = (i + slack) & (Color_cache_size - 1);
- break;
+ /* Cache is full. Instead of inserting at slot h, which causes
+ thrashing if many colors hash to the same value,
+ insert at h + n where n is pseudo-random and
+ smaller than Color_cache_slack */
+ int slack = num_overflows++ & (Color_cache_slack - 1);
+ i = (i + slack) & (Color_cache_size - 1);
+ break;
}
}
color.red = r * 0x101;
diff --git a/otherlibs/graph/graphics.mli b/otherlibs/graph/graphics.mli
index 047bf0cc0..f6a97993f 100644
--- a/otherlibs/graph/graphics.mli
+++ b/otherlibs/graph/graphics.mli
@@ -87,7 +87,7 @@ external lineto : x:int -> y:int -> unit = "gr_lineto"
(* Draw a line with endpoints the current point and the given point,
and move the current point to the given point. *)
external draw_arc :
- x:int -> y:int -> rx:int -> ry:int -> start:int -> stop:int -> unit
+ x:int -> y:int -> rx:int -> ry:int -> start:int -> stop:int -> unit
= "gr_draw_arc" "gr_draw_arc_nat"
(* [draw_arc x y rx ry a1 a2] draws an elliptical arc with center
[x,y], horizontal radius [rx], vertical radius [ry], from angle
diff --git a/otherlibs/graph/make_img.c b/otherlibs/graph/make_img.c
index 33cb61e72..ae655685b 100644
--- a/otherlibs/graph/make_img.c
+++ b/otherlibs/graph/make_img.c
@@ -50,7 +50,7 @@ value gr_make_image(value m)
bits_per_pixel = idata->bits_per_pixel;
#ifdef DIRECT_RGB_DEBUG
fprintf(stderr, "Byte_order: %d = %s\n", byte_order,
- byte_order ? "LSBFirst" : "MSBFirst");
+ byte_order ? "LSBFirst" : "MSBFirst");
fprintf(stderr, "Bitmp_unit: %d\n", bitmap_unit);
fprintf(stderr, "Bits per pixel: %d\n", idata->bits_per_pixel);
#endif
@@ -107,4 +107,3 @@ value gr_make_image(value m)
XFlush(grdisplay);
return im;
}
-
diff --git a/otherlibs/labltk/browser/README b/otherlibs/labltk/browser/README
index 70cd79c80..21fdbd0c2 100644
--- a/otherlibs/labltk/browser/README
+++ b/otherlibs/labltk/browser/README
@@ -1,5 +1,5 @@
- Installing and Using OCamlBrowser
+ Installing and Using OCamlBrowser
INSTALLATION
@@ -38,10 +38,10 @@ a) Viewer
File - Shell opens an OCaml shell.
Modules - Path editor changes the load path.
- Pressing [Add to path] or Insert key adds selected directories
- to the load path.
- Pressing [Remove from path] or Delete key removes selected
- paths from the load path.
+ Pressing [Add to path] or Insert key adds selected directories
+ to the load path.
+ Pressing [Remove from path] or Delete key removes selected
+ paths from the load path.
Modules - Reset cache rescans the load path and resets the module
cache. Do it if you recompile some interface, or change the load
path in a conflictual way.
@@ -68,7 +68,7 @@ b) Module walking
sub-module) or display the signature for this identifier below.
Signatures are clickable. Double clicking with the left mouse
- button on an identifier in a signature brings you to its signature,
+ button on an identifier in a signature brings you to its signature,
inside its module box.
A single click on the right button pops up a menu displaying the
type declaration for the selected identifier. Its title, when
@@ -82,7 +82,7 @@ b) Module walking
the currently displayed signature, if it is available.
C-s opens a text search dialog for the displayed signature.
-
+
c) File editor
You can edit files with it, but there is no auto-save nor undo at
the moment. Otherwise you can use it as a browser, making
@@ -134,10 +134,10 @@ BUGS
* When you quit the editor and some file was modified, a dialogue is
displayed asking wether you want to really quit or not. But 1) if
you quit directly from the viewer, there is no dialogue at all, and
- 2) if you close from the window manager, the dialogue is displayed,
+ 2) if you close from the window manager, the dialogue is displayed,
but you cannot cancel the destruction... Beware.
-* When you run it through xon, the shell hangs at the first error. But
+* When you run it through xon, the shell hangs at the first error. But
its ok if you start ocamlbrowser from a remote shell...
TODO
@@ -152,4 +152,4 @@ TODO
experimented users.
-Bug reports and comments to <garrigue@kurims.kyoto-u.ac.jp> \ No newline at end of file
+Bug reports and comments to <garrigue@kurims.kyoto-u.ac.jp>
diff --git a/otherlibs/labltk/example/README b/otherlibs/labltk/example/README
index 71bbaca79..b3f473bac 100644
--- a/otherlibs/labltk/example/README
+++ b/otherlibs/labltk/example/README
@@ -3,16 +3,15 @@ $Id$
Some examples for LablTk. They must be compiled with the -modern
option, except for hello.ml and calc.ml.
-hello.ml A very simple example of CamlTk
-hello.tcl The same programme in Tcl/Tk
+hello.ml A very simple example of CamlTk
+hello.tcl The same programme in Tcl/Tk
-demo.ml A demonstration using many widget classes
+demo.ml A demonstration using many widget classes
-eyes.ml A "bind" test
+eyes.ml A "bind" test
-calc.ml A little calculator
+calc.ml A little calculator
-clock.ml An analog clock
-
-tetris.ml You NEED a game also. Edit it to set a background
+clock.ml An analog clock
+tetris.ml You NEED a game also. Edit it to set a background
diff --git a/otherlibs/str/str.mli b/otherlibs/str/str.mli
index cd9aab1d5..5a1139fe4 100644
--- a/otherlibs/str/str.mli
+++ b/otherlibs/str/str.mli
@@ -57,23 +57,23 @@ val regexp_string_case_fold: string -> regexp
(*** String matching and searching *)
external string_match: pat:regexp -> string -> pos:int -> bool
- = "str_string_match"
+ = "str_string_match"
(* [string_match r s start] tests whether the characters in [s]
starting at position [start] match the regular expression [r].
The first character of a string has position [0], as usual. *)
external search_forward: pat:regexp -> string -> pos:int -> int
- = "str_search_forward"
+ = "str_search_forward"
(* [search_forward r s start] searchs the string [s] for a substring
matching the regular expression [r]. The search starts at position
[start] and proceeds towards the end of the string.
Return the position of the first character of the matched
substring, or raise [Not_found] if no substring matches. *)
external search_backward: pat:regexp -> string -> pos:int -> int
- = "str_search_backward"
+ = "str_search_backward"
(* Same as [search_forward], but the search proceeds towards the
beginning of the string. *)
external string_partial_match: pat:regexp -> string -> pos:int -> bool
- = "str_string_partial_match"
+ = "str_string_partial_match"
(* Similar to [string_match], but succeeds whenever the argument
string is a prefix of a string that matches. This includes
the case of a true complete match. *)
@@ -169,15 +169,14 @@ val bounded_full_split: sep:regexp -> string -> int -> split_result list
val string_before: string -> pos:int -> string
(* [string_before s n] returns the substring of all characters of [s]
- that precede position [n] (excluding the character at
+ that precede position [n] (excluding the character at
position [n]). *)
val string_after: string -> pos:int -> string
(* [string_after s n] returns the substring of all characters of [s]
- that follow position [n] (including the character at
+ that follow position [n] (including the character at
position [n]). *)
val first_chars: string -> pos:int -> string
(* [first_chars s n] returns the first [n] characters of [s].
This is the same function as [string_before]. *)
val last_chars: string -> pos:int -> string
(* [last_chars s n] returns the last [n] characters of [s]. *)
-
diff --git a/otherlibs/threads/threadUnix.mli b/otherlibs/threads/threadUnix.mli
index ddaa37f3d..ec42c828c 100644
--- a/otherlibs/threads/threadUnix.mli
+++ b/otherlibs/threads/threadUnix.mli
@@ -42,7 +42,7 @@ val timed_read :
val timed_write :
Unix.file_descr ->
buffer:string -> pos:int -> len:int -> timeout:float -> int
- (* Behave as [read] and [write], except that
+ (* Behave as [read] and [write], except that
[Unix_error(ETIMEDOUT,_,_)] is raised if no data is
available for reading or ready for writing after [d] seconds.
The delay [d] is given in the fifth argument, in seconds. *)
@@ -67,13 +67,13 @@ val sleep : int -> unit
(*** Sockets *)
val socket : domain:Unix.socket_domain ->
- type:Unix.socket_type -> proto:int -> Unix.file_descr
+ type:Unix.socket_type -> proto:int -> Unix.file_descr
val socketpair : domain:Unix.socket_domain -> type:Unix.socket_type ->
- proto:int -> Unix.file_descr * Unix.file_descr
+ proto:int -> Unix.file_descr * Unix.file_descr
val accept : Unix.file_descr -> Unix.file_descr * Unix.sockaddr
val connect : Unix.file_descr -> Unix.sockaddr -> unit
val recv : Unix.file_descr -> buffer:string ->
- pos:int -> len:int -> flags:Unix.msg_flag list -> int
+ pos:int -> len:int -> flags:Unix.msg_flag list -> int
val recvfrom : Unix.file_descr -> buffer:string -> pos:int -> len:int ->
flags:Unix.msg_flag list -> int * Unix.sockaddr
val send : Unix.file_descr -> buffer:string -> pos:int -> len:int ->
@@ -84,4 +84,3 @@ val open_connection : Unix.sockaddr -> in_channel * out_channel
val establish_server :
fun:(in:in_channel -> out:out_channel -> 'a) ->
addr:Unix.sockaddr -> unit
-
diff --git a/otherlibs/unix/unix.mli b/otherlibs/unix/unix.mli
index 92484025c..ebe6eb701 100644
--- a/otherlibs/unix/unix.mli
+++ b/otherlibs/unix/unix.mli
@@ -230,7 +230,7 @@ val write : file_descr -> buf:string -> pos:int -> len:int -> int
(*** Interfacing with the standard input/output library. *)
-val in_channel_of_descr : file_descr -> in_channel
+val in_channel_of_descr : file_descr -> in_channel
(* Create an input channel reading from the given descriptor.
The channel is initially in binary mode; use
[set_binary_mode_in ic false] if text mode is desired. *)
@@ -324,13 +324,13 @@ type access_permission =
(* Flags for the [access] call. *)
val chmod : name:string -> perm:file_perm -> unit
- (* Change the permissions of the named file. *)
+ (* Change the permissions of the named file. *)
val fchmod : file_descr -> perm:file_perm -> unit
- (* Change the permissions of an opened file. *)
+ (* Change the permissions of an opened file. *)
val chown : name:string -> uid:int -> gid:int -> unit
- (* Change the owner uid and owner gid of the named file. *)
+ (* Change the owner uid and owner gid of the named file. *)
val fchown : file_descr -> uid:int -> gid:int -> unit
- (* Change the owner uid and owner gid of an opened file. *)
+ (* Change the owner uid and owner gid of an opened file. *)
val umask : int -> int
(* Set the process creation mask, and return the previous mask. *)
val access : name:string -> perm:access_permission list -> unit
@@ -384,7 +384,7 @@ val opendir : string -> dir_handle
(* Open a descriptor on a directory *)
val readdir : dir_handle -> string
(* Return the next entry in a directory.
- Raise [End_of_file] when the end of the directory has been
+ Raise [End_of_file] when the end of the directory has been
reached. *)
val rewinddir : dir_handle -> unit
(* Reposition the descriptor to the beginning of the directory *)
@@ -397,7 +397,7 @@ val closedir : dir_handle -> unit
val pipe : unit -> file_descr * file_descr
(* Create a pipe. The first component of the result is opened
for reading, that's the exit to the pipe. The second component is
- opened for writing, that's the entrance to the pipe. *)
+ opened for writing, that's the entrance to the pipe. *)
val mkfifo : string -> perm:file_perm -> unit
(* Create a named pipe with the given permissions. *)
@@ -410,7 +410,7 @@ val create_process :
stdin:file_descr -> stdout:file_descr -> stderr:file_descr -> int
(* [create_process prog args new_stdin new_stdout new_stderr]
forks a new process that executes the program
- in file [prog], with arguments [args]. The pid of the new
+ in file [prog], with arguments [args]. The pid of the new
process is returned immediately; the new process executes
concurrently with the current process.
The standard input and outputs of the new process are connected
@@ -425,7 +425,7 @@ val create_process :
outputs. *)
val create_process_env :
- name:string -> args:string array -> env:string array ->
+ name:string -> args:string array -> env:string array ->
stdin:file_descr -> stdout:file_descr -> stderr:file_descr -> int
(* [create_process_env prog args env new_stdin new_stdout new_stderr]
works as [create_process], except that the extra argument
@@ -759,16 +759,16 @@ type msg_flag =
val recv :
file_descr -> buf:string -> pos:int -> len:int
- -> mode:msg_flag list -> int
+ -> mode:msg_flag list -> int
val recvfrom :
file_descr -> buf:string -> pos:int -> len:int
- -> mode:msg_flag list -> int * sockaddr
+ -> mode:msg_flag list -> int * sockaddr
(* Receive data from an unconnected socket. *)
val send : file_descr -> buf:string -> pos:int -> len:int
- -> mode:msg_flag list -> int
+ -> mode:msg_flag list -> int
val sendto :
file_descr -> buf:string -> pos:int -> len:int
- -> mode:msg_flag list -> addr:sockaddr -> int
+ -> mode:msg_flag list -> addr:sockaddr -> int
(* Send data over an unconnected socket. *)
type socket_option =
@@ -797,7 +797,7 @@ val shutdown_connection : in_channel -> unit
that is, transmit an end-of-file condition to the server reading
on the other side of the connection. *)
val establish_server : fun:(in:in_channel -> out:out_channel -> unit) ->
- addr:sockaddr -> unit
+ addr:sockaddr -> unit
(* Establish a server on the given address.
The function given as first argument is called for each connection
with two buffered channels connected to the client. A new process