diff options
Diffstat (limited to 'otherlibs/labltk/support')
-rw-r--r-- | otherlibs/labltk/support/camltk.h | 4 | ||||
-rw-r--r-- | otherlibs/labltk/support/cltkCaml.c | 10 | ||||
-rw-r--r-- | otherlibs/labltk/support/cltkDMain.c | 2 | ||||
-rw-r--r-- | otherlibs/labltk/support/cltkEval.c | 8 | ||||
-rw-r--r-- | otherlibs/labltk/support/cltkMain.c | 2 | ||||
-rw-r--r-- | otherlibs/labltk/support/cltkMisc.c | 2 | ||||
-rw-r--r-- | otherlibs/labltk/support/cltkVar.c | 4 |
7 files changed, 16 insertions, 16 deletions
diff --git a/otherlibs/labltk/support/camltk.h b/otherlibs/labltk/support/camltk.h index 54671a075..29452aacc 100644 --- a/otherlibs/labltk/support/camltk.h +++ b/otherlibs/labltk/support/camltk.h @@ -33,7 +33,7 @@ #endif /* cltkMisc.c */ -/* copy a Caml string to the C heap. Must be deallocated with stat_free */ +/* copy an OCaml string to the C heap. Must be deallocated with stat_free */ extern char *string_to_c(value s); /* cltkUtf.c */ @@ -45,7 +45,7 @@ CAMLTKextern Tcl_Interp *cltclinterp; /* The Tcl interpretor */ extern value copy_string_list(int argc, char **argv); /* cltkCaml.c */ -/* pointers to Caml values */ +/* pointers to OCaml values */ extern value *tkerror_exn; extern value *handler_code; extern int CamlCBCmd(ClientData clientdata, Tcl_Interp *interp, diff --git a/otherlibs/labltk/support/cltkCaml.c b/otherlibs/labltk/support/cltkCaml.c index f0372f14b..9a3d38a55 100644 --- a/otherlibs/labltk/support/cltkCaml.c +++ b/otherlibs/labltk/support/cltkCaml.c @@ -27,7 +27,7 @@ value * tkerror_exn = NULL; value * handler_code = NULL; -/* The Tcl command for evaluating callback in Caml */ +/* The Tcl command for evaluating callback in OCaml */ int CamlCBCmd(ClientData clientdata, Tcl_Interp *interp, int argc, CONST84 char **argv) { @@ -41,7 +41,7 @@ int CamlCBCmd(ClientData clientdata, Tcl_Interp *interp, return TCL_ERROR; callback2(*handler_code,Val_int(id), copy_string_list(argc - 2,(char **)&argv[2])); - /* Never fails (Caml would have raised an exception) */ + /* Never fails (OCaml would have raised an exception) */ /* but result may have been set by callback */ return TCL_OK; } @@ -69,14 +69,14 @@ CAMLprim void tk_error(char *errmsg) } -/* The initialisation of the C global variables pointing to Caml values - must be made accessible from Caml, so that we are sure that it *always* +/* The initialisation of the C global variables pointing to OCaml values + must be made accessible from OCaml, so that we are sure that it *always* takes place during loading of the protocol module */ CAMLprim value camltk_init(value v) { - /* Initialize the Caml pointers */ + /* Initialize the OCaml pointers */ if (tkerror_exn == NULL) tkerror_exn = caml_named_value("tkerror"); if (handler_code == NULL) diff --git a/otherlibs/labltk/support/cltkDMain.c b/otherlibs/labltk/support/cltkDMain.c index 7edb92a98..04af209de 100644 --- a/otherlibs/labltk/support/cltkDMain.c +++ b/otherlibs/labltk/support/cltkDMain.c @@ -35,7 +35,7 @@ /* - * Dealing with signals: when a signal handler is defined in Caml, + * Dealing with signals: when a signal handler is defined in OCaml, * the actual execution of the signal handler upon reception of the * signal is delayed until we are sure we are out of the GC. * If a signal occurs during the MainLoop, we would have to wait diff --git a/otherlibs/labltk/support/cltkEval.c b/otherlibs/labltk/support/cltkEval.c index 9ec3f1476..69ba6d8a1 100644 --- a/otherlibs/labltk/support/cltkEval.c +++ b/otherlibs/labltk/support/cltkEval.c @@ -32,7 +32,7 @@ /* The Tcl interpretor */ Tcl_Interp *cltclinterp = NULL; -/* Copy a list of strings from the C heap to Caml */ +/* Copy a list of strings from the C heap to OCaml */ value copy_string_list(int argc, char **argv) { CAMLparam0(); @@ -53,7 +53,7 @@ value copy_string_list(int argc, char **argv) } /* - * Calling Tcl from Caml + * Calling Tcl from OCaml * this version works on an arbitrary Tcl command, * and does parsing and substitution */ @@ -65,7 +65,7 @@ CAMLprim value camltk_tcl_eval(value str) CheckInit(); /* Tcl_Eval may write to its argument, so we take a copy - * If the evaluation raises a Caml exception, we have a space + * If the evaluation raises an OCaml exception, we have a space * leak */ Tcl_ResetResult(cltclinterp); @@ -84,7 +84,7 @@ CAMLprim value camltk_tcl_eval(value str) } /* - * Calling Tcl from Caml + * Calling Tcl from OCaml * direct call, argument is TkArgs vect type TkArgs = TkToken of string diff --git a/otherlibs/labltk/support/cltkMain.c b/otherlibs/labltk/support/cltkMain.c index be9c907c4..8751334c5 100644 --- a/otherlibs/labltk/support/cltkMain.c +++ b/otherlibs/labltk/support/cltkMain.c @@ -35,7 +35,7 @@ #endif /* - * Dealing with signals: when a signal handler is defined in Caml, + * Dealing with signals: when a signal handler is defined in OCaml, * the actual execution of the signal handler upon reception of the * signal is delayed until we are sure we are out of the GC. * If a signal occurs during the MainLoop, we would have to wait diff --git a/otherlibs/labltk/support/cltkMisc.c b/otherlibs/labltk/support/cltkMisc.c index 0e14cde81..a89ea341f 100644 --- a/otherlibs/labltk/support/cltkMisc.c +++ b/otherlibs/labltk/support/cltkMisc.c @@ -51,7 +51,7 @@ CAMLprim value camltk_splitlist (value v) } } -/* Copy a Caml string to the C heap. Should deallocate with stat_free */ +/* Copy an OCaml string to the C heap. Should deallocate with stat_free */ char *string_to_c(value s) { int l = string_length(s); diff --git a/otherlibs/labltk/support/cltkVar.c b/otherlibs/labltk/support/cltkVar.c index a508d2288..dcda8a77c 100644 --- a/otherlibs/labltk/support/cltkVar.c +++ b/otherlibs/labltk/support/cltkVar.c @@ -39,7 +39,7 @@ CAMLprim value camltk_getvar(value var) if (s == NULL) tk_error(Tcl_GetStringResult(cltclinterp)); - else + else return(tcl_string_to_caml(s)); } @@ -51,7 +51,7 @@ CAMLprim value camltk_setvar(value var, value contents) CheckInit(); /* SetVar makes a copy of the contents. */ - /* In case we have write traces in Caml, it's better to make sure that + /* In case we have write traces in OCaml, it's better to make sure that var doesn't move... */ stable_var = string_to_c(var); utf_contents = caml_string_to_tcl(contents); |