diff options
Diffstat (limited to 'otherlibs/labltk/support')
-rw-r--r-- | otherlibs/labltk/support/camltkwrap.mli | 54 | ||||
-rw-r--r-- | otherlibs/labltk/support/cltkEval.c | 8 | ||||
-rw-r--r-- | otherlibs/labltk/support/cltkImg.c | 20 | ||||
-rw-r--r-- | otherlibs/labltk/support/cltkMain.c | 38 | ||||
-rw-r--r-- | otherlibs/labltk/support/cltkMisc.c | 2 | ||||
-rw-r--r-- | otherlibs/labltk/support/cltkVar.c | 8 | ||||
-rw-r--r-- | otherlibs/labltk/support/cltkWait.c | 4 | ||||
-rw-r--r-- | otherlibs/labltk/support/protocol.ml | 8 | ||||
-rw-r--r-- | otherlibs/labltk/support/rawwidget.ml | 4 | ||||
-rw-r--r-- | otherlibs/labltk/support/textvariable.ml | 6 |
10 files changed, 76 insertions, 76 deletions
diff --git a/otherlibs/labltk/support/camltkwrap.mli b/otherlibs/labltk/support/camltkwrap.mli index 914ad0223..9c9321c21 100644 --- a/otherlibs/labltk/support/camltkwrap.mli +++ b/otherlibs/labltk/support/camltkwrap.mli @@ -50,7 +50,7 @@ module Widget : sig (* [dummy] is a widget used as context when we don't have any. It is *not* a real widget. *) - + val new_atom : parent: widget -> ?name: string -> string -> widget (* incompatible with the classic camltk *) @@ -80,10 +80,10 @@ module Widget : sig val chk_sub : string -> 'a list -> 'a -> unit val check_class : widget -> string list -> unit - (* Widget subtyping *) + (* Widget subtyping *) exception IllegalWidgetType of string - (* Raised when widget command applied illegally*) + (* Raised when widget command applied illegally*) (* this function is not used, but introduced for the compatibility with labltk. useless for camltk users *) @@ -95,10 +95,10 @@ module Protocol : sig (* Lower level interface *) exception TkError of string - (* Raised by the communication functions *) + (* Raised by the communication functions *) val debug : bool ref - (* When set to true, displays approximation of intermediate Tcl code *) + (* When set to true, displays approximation of intermediate Tcl code *) type tkArgs = TkToken of string @@ -108,7 +108,7 @@ module Protocol : sig (* Misc *) external splitlist : string -> string list - = "camltk_splitlist" + = "camltk_splitlist" val add_destroy_hook : (widget -> unit) -> unit @@ -133,19 +133,19 @@ module Protocol : sig val openTk : ?display:string -> ?clas:string -> unit -> widget (* [openTk ~display:display ~clas:clas ()] is equivalent to - [opentk ["-display"; display; "-name"; clas]] *) + [opentk ["-display"; display; "-name"; clas]] *) (* Legacy opentk functions *) val openTkClass: string -> widget (* [openTkClass class] is equivalent to [opentk ["-name"; class]] *) val openTkDisplayClass: string -> string -> widget (* [openTkDisplayClass disp class] is equivalent to - [opentk ["-display"; disp; "-name"; class]] *) + [opentk ["-display"; disp; "-name"; class]] *) val closeTk : unit -> unit val finalizeTk : unit -> unit (* Finalize tcl/tk before exiting. This function will be automatically - called when you call [Pervasives.exit ()] *) + called when you call [Pervasives.exit ()] *) val mainLoop : unit -> unit @@ -164,23 +164,23 @@ module Protocol : sig type cbid = Protocol.cbid type callback_buffer = string list - (* Buffer for reading callback arguments *) + (* Buffer for reading callback arguments *) val callback_naming_table : (cbid, callback_buffer -> unit) Hashtbl.t (* CAMLTK val callback_memo_table : (widget, cbid) Hashtbl.t *) val callback_memo_table : (widget, cbid) Hashtbl.t - (* Exported for debug purposes only. Don't use them unless you - know what you are doing *) + (* Exported for debug purposes only. Don't use them unless you + know what you are doing *) val new_function_id : unit -> cbid val string_of_cbid : cbid -> string val register_callback : widget -> callback:(callback_buffer -> unit) -> string - (* Callback support *) + (* Callback support *) val clear_callback : cbid -> unit - (* Remove a given callback from the table *) + (* Remove a given callback from the table *) val remove_callbacks : widget -> unit - (* Clean up callbacks associated to widget. Must be used only when - the Destroy event is bind by the user and masks the default - Destroy event binding *) + (* Clean up callbacks associated to widget. Must be used only when + the Destroy event is bind by the user and masks the default + Destroy event binding *) val cTKtoCAMLwidget : string -> widget val cCAMLtoTKwidget : string list -> widget -> tkArgs @@ -196,27 +196,27 @@ module Textvariable : sig open Protocol type textVariable = Textvariable.textVariable - (* TextVariable is an abstract type *) + (* TextVariable is an abstract type *) val create : ?on: widget -> unit -> textVariable - (* Allocation of a textVariable with lifetime associated to widget - if a widget is specified *) + (* Allocation of a textVariable with lifetime associated to widget + if a widget is specified *) val create_temporary : widget -> textVariable (* for backward compatibility - [create_temporary w] is equivalent to [create ~on:w ()] *) + [create_temporary w] is equivalent to [create ~on:w ()] *) val set : textVariable -> string -> unit - (* Setting the val of a textVariable *) + (* Setting the val of a textVariable *) val get : textVariable -> string - (* Reading the val of a textVariable *) + (* Reading the val of a textVariable *) val name : textVariable -> string - (* Its tcl name *) + (* Its tcl name *) val cCAMLtoTKtextVariable : textVariable -> tkArgs - (* Internal conversion function *) + (* Internal conversion function *) val handle : textVariable -> (unit -> unit) -> unit - (* Callbacks on variable modifications *) + (* Callbacks on variable modifications *) val coerce : string -> textVariable @@ -231,7 +231,7 @@ module Fileevent : sig val remove_fileinput: file_descr -> unit val add_fileoutput : file_descr -> (unit -> unit) -> unit val remove_fileoutput: file_descr -> unit - (* see [tk] module *) + (* see [tk] module *) end module Timer : sig diff --git a/otherlibs/labltk/support/cltkEval.c b/otherlibs/labltk/support/cltkEval.c index 236dc299a..ae86452f2 100644 --- a/otherlibs/labltk/support/cltkEval.c +++ b/otherlibs/labltk/support/cltkEval.c @@ -203,8 +203,8 @@ CAMLprim value camltk_tcl_direct_eval(value v) Tcl_DStringInit(&buf); Tcl_DStringAppend(&buf, argv[0], -1); for (i=1; i<size; i++) { - Tcl_DStringAppend(&buf, " ", -1); - Tcl_DStringAppend(&buf, argv[i], -1); + Tcl_DStringAppend(&buf, " ", -1); + Tcl_DStringAppend(&buf, argv[i], -1); } result = Tcl_Eval(cltclinterp, Tcl_DStringValue(&buf)); Tcl_DStringFree(&buf); @@ -217,13 +217,13 @@ CAMLprim value camltk_tcl_direct_eval(value v) } else { /* implement the autoload stuff */ if (Tcl_GetCommandInfo(cltclinterp,"unknown",&info)) { /* unknown found */ for (i = size; i >= 0; i--) - argv[i+1] = argv[i]; + argv[i+1] = argv[i]; argv[0] = "unknown"; result = (*info.proc)(info.clientData,cltclinterp,size+1,argv); } else { /* ah, it isn't there at all */ result = TCL_ERROR; Tcl_AppendResult(cltclinterp, "Unknown command \"", - argv[0], "\"", NULL); + argv[0], "\"", NULL); } } diff --git a/otherlibs/labltk/support/cltkImg.c b/otherlibs/labltk/support/cltkImg.c index f30166ef5..7eaca3689 100644 --- a/otherlibs/labltk/support/cltkImg.c +++ b/otherlibs/labltk/support/cltkImg.c @@ -59,16 +59,16 @@ CAMLprim value camltk_getimgdata (value imgname) /* ML */ CAMLreturn(res); } else { int y; /* varies from 0 to height - 1 */ - int yoffs = 0; /* byte offset of line in src */ - int yidx = 0; /* byte offset of line in dst */ + int yoffs = 0; /* byte offset of line in src */ + int yidx = 0; /* byte offset of line in dst */ for (y=0; y<pib.height; y++,yoffs+=pib.pitch,yidx+=pib.width * 3) { - int x; /* varies from 0 to width - 1 */ - int xoffs = yoffs; /* byte offset of pxl in src */ - int xidx = yidx; /* byte offset of pxl in dst */ + int x; /* varies from 0 to width - 1 */ + int xoffs = yoffs; /* byte offset of pxl in src */ + int xidx = yidx; /* byte offset of pxl in dst */ for (x=0; x<pib.width; x++,xoffs+=pib.pixelSize,xidx+=3) { - Byte(res, xidx) = pib.pixelPtr[xoffs+pib.offset[0]]; - Byte(res, xidx + 1) = pib.pixelPtr[xoffs+pib.offset[1]]; - Byte(res, xidx + 2) = pib.pixelPtr[xoffs+pib.offset[2]]; + Byte(res, xidx) = pib.pixelPtr[xoffs+pib.offset[0]]; + Byte(res, xidx + 1) = pib.pixelPtr[xoffs+pib.offset[1]]; + Byte(res, xidx + 2) = pib.pixelPtr[xoffs+pib.offset[2]]; }; } CAMLreturn(res); @@ -77,7 +77,7 @@ CAMLprim value camltk_getimgdata (value imgname) /* ML */ CAMLprim void camltk_setimgdata_native (value imgname, value pixmap, value x, value y, - value w, value h) /* ML */ + value w, value h) /* ML */ { Tk_PhotoHandle ph; Tk_PhotoImageBlock pib; @@ -107,5 +107,5 @@ CAMLprim void camltk_setimgdata_bytecode(argv,argn) int argn; { camltk_setimgdata_native(argv[0], argv[1], argv[2], argv[3], - argv[4], argv[5]); + argv[4], argv[5]); } diff --git a/otherlibs/labltk/support/cltkMain.c b/otherlibs/labltk/support/cltkMain.c index 6047f8551..6a3a35641 100644 --- a/otherlibs/labltk/support/cltkMain.c +++ b/otherlibs/labltk/support/cltkMain.c @@ -103,32 +103,32 @@ CAMLprim value camltk_opentk(value argv) tmp = Field(argv, 1); /* starts from argv[1] */ while ( tmp != Val_int(0) ) { - argc++; - tmp = Field(tmp, 1); + argc++; + tmp = Field(tmp, 1); } if( argc != 0 ){ - int i; - char *args; - char **tkargv; - char argcstr[256]; /* string of argc */ - - tkargv = (char**)stat_alloc(sizeof( char* ) * argc ); - tmp = Field(argv, 1); /* starts from argv[1] */ - i = 0; - - while ( tmp != Val_int(0) ) { - tkargv[i] = String_val(Field(tmp, 0)); - tmp = Field(tmp, 1); - i++; - } - - sprintf( argcstr, "%d", argc ); + int i; + char *args; + char **tkargv; + char argcstr[256]; /* string of argc */ + + tkargv = (char**)stat_alloc(sizeof( char* ) * argc ); + tmp = Field(argv, 1); /* starts from argv[1] */ + i = 0; + + while ( tmp != Val_int(0) ) { + tkargv[i] = String_val(Field(tmp, 0)); + tmp = Field(tmp, 1); + i++; + } + + sprintf( argcstr, "%d", argc ); Tcl_SetVar(cltclinterp, "argc", argcstr, TCL_GLOBAL_ONLY); args = Tcl_Merge(argc, tkargv); /* args must be freed by Tcl_Free */ Tcl_SetVar(cltclinterp, "argv", args, TCL_GLOBAL_ONLY); Tcl_Free(args); - stat_free( tkargv ); + stat_free( tkargv ); } } if (Tk_Init(cltclinterp) != TCL_OK) diff --git a/otherlibs/labltk/support/cltkMisc.c b/otherlibs/labltk/support/cltkMisc.c index a6e823d1d..e9824b6e9 100644 --- a/otherlibs/labltk/support/cltkMisc.c +++ b/otherlibs/labltk/support/cltkMisc.c @@ -39,7 +39,7 @@ CAMLprim value camltk_splitlist (value v) switch(result) { case TCL_OK: { value res = copy_string_list(argc,argv); - Tcl_Free((char *)argv); /* only one large block was allocated */ + Tcl_Free((char *)argv); /* only one large block was allocated */ /* argv points into utf: utf must be freed after argv are freed */ stat_free( utf ); return res; diff --git a/otherlibs/labltk/support/cltkVar.c b/otherlibs/labltk/support/cltkVar.c index 971336850..83fedbafd 100644 --- a/otherlibs/labltk/support/cltkVar.c +++ b/otherlibs/labltk/support/cltkVar.c @@ -76,10 +76,10 @@ typedef char *(Tcl_VarTraceProc) _ANSI_ARGS_((ClientData clientData, */ static char * tracevar(clientdata, interp, name1, name2, flags) ClientData clientdata; - Tcl_Interp *interp; /* Interpreter containing variable. */ - char *name1; /* Name of variable. */ - char *name2; /* Second part of variable name. */ - int flags; /* Information about what happened. */ + Tcl_Interp *interp; /* Interpreter containing variable. */ + char *name1; /* Name of variable. */ + char *name2; /* Second part of variable name. */ + int flags; /* Information about what happened. */ { Tcl_UntraceVar2(interp, name1, name2, TCL_GLOBAL_ONLY|TCL_TRACE_WRITES|TCL_TRACE_UNSETS, diff --git a/otherlibs/labltk/support/cltkWait.c b/otherlibs/labltk/support/cltkWait.c index f562ff6e6..7c3cef53f 100644 --- a/otherlibs/labltk/support/cltkWait.c +++ b/otherlibs/labltk/support/cltkWait.c @@ -45,8 +45,8 @@ struct WinCBData { }; static void WaitVisibilityProc(clientData, eventPtr) - ClientData clientData; - XEvent *eventPtr; /* Information about event (not used). */ + ClientData clientData; + XEvent *eventPtr; /* Information about event (not used). */ { struct WinCBData *vis = clientData; value cbid = Val_int(vis->cbid); diff --git a/otherlibs/labltk/support/protocol.ml b/otherlibs/labltk/support/protocol.ml index 586c937b4..6e3208cfe 100644 --- a/otherlibs/labltk/support/protocol.ml +++ b/otherlibs/labltk/support/protocol.ml @@ -179,11 +179,11 @@ let protected_dispatch id args = with | e -> try - Printf.eprintf "Uncaught exception: %s\n" (Printexc.to_string e); - flush stderr; - (* raise x *) + Printf.eprintf "Uncaught exception: %s\n" (Printexc.to_string e); + flush stderr; + (* raise x *) with - Out_of_memory -> raise Out_of_memory + Out_of_memory -> raise Out_of_memory | Sys.Break -> raise Sys.Break let _ = Callback.register "camlcb" protected_dispatch diff --git a/otherlibs/labltk/support/rawwidget.ml b/otherlibs/labltk/support/rawwidget.ml index 4ddf1a301..8eba3b8b1 100644 --- a/otherlibs/labltk/support/rawwidget.ml +++ b/otherlibs/labltk/support/rawwidget.ml @@ -148,8 +148,8 @@ let new_atom ~parent ?name:nom clas = else parentpath ^ "." ^ name in let w = Typed(path,clas) in - Hashtbl.add table path w; - w + Hashtbl.add table path w; + w (* Just create a path. Only to check existence of widgets *) (* Use with care *) diff --git a/otherlibs/labltk/support/textvariable.ml b/otherlibs/labltk/support/textvariable.ml index af272e682..4581976b5 100644 --- a/otherlibs/labltk/support/textvariable.ml +++ b/otherlibs/labltk/support/textvariable.ml @@ -96,9 +96,9 @@ let add w v = try Hashtbl.find memo w with Not_found -> - let r = ref StringSet.empty in - Hashtbl.add memo w r; - r in + let r = ref StringSet.empty in + Hashtbl.add memo w r; + r in r := StringSet.add v !r (* to be used with care ! *) |