remove labels from List.assoc/remove_assoc

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@3767 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Jacques Garrigue 2001-09-17 13:08:34 +00:00
parent e22a330b29
commit 7ae26d5b11
8 changed files with 21 additions and 21 deletions

View File

@ -113,7 +113,7 @@ let select_shell txt =
begin fun () ->
try
let name = Listbox.get box ~index:`Active in
txt.shell <- Some (name, List.assoc name ~map:shells);
txt.shell <- Some (name, List.assoc name shells);
destroy tl
with Not_found -> txt.shell <- None; destroy tl
end

View File

@ -52,7 +52,7 @@ let gettklabel fc =
else s
in begin
if List.mem s forbidden then
try List.assoc s ~map:nicknames
try List.assoc s nicknames
with Not_found -> small fc.var_name
else s
end
@ -97,7 +97,7 @@ let ppMLtype ?(any=false) ?(return=false) ?(def=false) ?(counter=ref 0) =
begin
try
let typdef = Hashtbl.find types_table sup in
let fcl = List.assoc sub ~map:typdef.subtypes in
let fcl = List.assoc sub typdef.subtypes in
let tklabels = List.map ~f:gettklabel fcl in
let l = List.map fcl ~f:
begin fun fc ->
@ -499,7 +499,7 @@ let code_of_template ~context_widget ?func:(funtemplate=false) template =
StringArg s -> "TkToken \"" ^ s ^ "\""
| TypeArg (_, List (Subtype (sup, sub) as ty)) ->
let typdef = Hashtbl.find types_table sup in
let classdef = List.assoc sub ~map:typdef.subtypes in
let classdef = List.assoc sub typdef.subtypes in
let lbl = gettklabel (List.hd classdef) in
catch_opts := (sub ^ "_" ^ sup, lbl);
newvar := newvar2;

View File

@ -27,7 +27,7 @@ let write_create_p ~w wname =
begin
try
let option = Hashtbl.find types_table "options" in
let classdefs = List.assoc wname ~map:option.subtypes in
let classdefs = List.assoc wname option.subtypes in
let tklabels = List.map ~f:gettklabel classdefs in
let l = List.map classdefs ~f:
begin fun fc ->

View File

@ -181,7 +181,7 @@ let declared_type_parser_arity s =
(Hashtbl.find types_table s).parser_arity
with
Not_found ->
try List.assoc s ~map:!types_external
try List.assoc s !types_external
with
Not_found ->
prerr_string "Type "; prerr_string s;
@ -388,10 +388,10 @@ let enter_widget name components =
| External, _ -> ()
end;
let commands =
try List.assoc Command ~map:sorted_components
try List.assoc Command sorted_components
with Not_found -> []
and externals =
try List.assoc External ~map:sorted_components
try List.assoc External sorted_components
with Not_found -> []
in
Hashtbl'.add module_table ~key:name
@ -415,10 +415,10 @@ let enter_module name components =
| External, _ -> ()
end;
let commands =
try List.assoc Command ~map:sorted_components
try List.assoc Command sorted_components
with Not_found -> []
and externals =
try List.assoc External ~map:sorted_components
try List.assoc External sorted_components
with Not_found -> []
in
Hashtbl'.add module_table ~key:name

View File

@ -11,7 +11,7 @@ LABLTKDIR=$(LIBDIR)/labltk
## Tools from the Objective Caml distribution
CAMLRUN=$(TOPDIR)/boot/ocamlrun
LABLC=$(CAMLRUN) $(TOPDIR)/ocamlc -I $(TOPDIR)/stdlib
LABLC=$(CAMLRUN) $(TOPDIR)/ocamlc -w l -I $(TOPDIR)/stdlib
LABLCOMP=$(LABLC) -c
LABLYACC=$(TOPDIR)/boot/ocamlyacc -v
LABLLEX=$(CAMLRUN) $(TOPDIR)/boot/ocamllex
@ -20,6 +20,6 @@ LABLDEP=$(CAMLRUN) $(TOPDIR)/tools/ocamldep
COMPFLAGS=
LINKFLAGS=
CAMLOPT=$(CAMLRUN) $(TOPDIR)/ocamlopt -I $(TOPDIR)/stdlib -labels
CAMLOPT=$(CAMLRUN) $(TOPDIR)/ocamlopt -w l -I $(TOPDIR)/stdlib -labels
CAMLOPTLIBR=$(CAMLOPT) -a
MKLIB=$(TOPDIR)/tools/ocamlmklib

View File

@ -126,7 +126,7 @@ and widget_toplevel_table = [ "toplevel" ]
let new_suffix clas n =
try
(List.assoc clas ~map:naming_scheme) ^ (string_of_int n)
(List.assoc clas naming_scheme) ^ (string_of_int n)
with
Not_found -> "w" ^ (string_of_int n)

View File

@ -148,14 +148,14 @@ val partition : f:('a -> bool) -> 'a list -> 'a list * 'a list
(** Association lists *)
val assoc : 'a -> map:('a * 'b) list -> 'b
val assoc : 'a -> ('a * 'b) list -> 'b
(* [assoc a l] returns the value associated with key [a] in the list of
pairs [l]. That is,
[assoc a [ ...; (a,b); ...] = b]
if [(a,b)] is the leftmost binding of [a] in list [l].
Raise [Not_found] if there is no value associated with [a] in the
list [l]. *)
val assq : 'a -> map:('a * 'b) list -> 'b
val assq : 'a -> ('a * 'b) list -> 'b
(* Same as [assoc], but uses physical equality instead of structural
equality to compare keys. *)
@ -166,12 +166,12 @@ val mem_assq : 'a -> map:('a * 'b) list -> bool
(* Same as [mem_assoc], but uses physical equality instead of
structural equality to compare keys. *)
val remove_assoc : 'a -> map:('a * 'b) list -> ('a * 'b) list
val remove_assoc : 'a -> ('a * 'b) list -> ('a * 'b) list
(* [remove_assoc a l] returns the list of
pairs [l] without the first pair with key [a], if any.
Not tail-recursive. *)
val remove_assq : 'a -> map:('a * 'b) list -> ('a * 'b) list
val remove_assq : 'a -> ('a * 'b) list -> ('a * 'b) list
(* Same as [remove_assq], but uses physical equality instead
of structural equality to compare keys. Not tail-recursive. *)

View File

@ -78,12 +78,12 @@ module List : sig
val filter : f:('a -> bool) -> 'a list -> 'a list
val find_all : f:('a -> bool) -> 'a list -> 'a list
val partition : f:('a -> bool) -> 'a list -> 'a list * 'a list
val assoc : 'a -> map:('a * 'b) list -> 'b
val assq : 'a -> map:('a * 'b) list -> 'b
val assoc : 'a -> ('a * 'b) list -> 'b
val assq : 'a -> ('a * 'b) list -> 'b
val mem_assoc : 'a -> map:('a * 'b) list -> bool
val mem_assq : 'a -> map:('a * 'b) list -> bool
val remove_assoc : 'a -> map:('a * 'b) list -> ('a * 'b) list
val remove_assq : 'a -> map:('a * 'b) list -> ('a * 'b) list
val remove_assoc : 'a -> ('a * 'b) list -> ('a * 'b) list
val remove_assq : 'a -> ('a * 'b) list -> ('a * 'b) list
val split : ('a * 'b) list -> 'a list * 'b list
val combine : 'a list -> 'b list -> ('a * 'b) list
val sort : cmp:('a -> 'a -> int) -> 'a list -> 'a list