summaryrefslogtreecommitdiffstats
path: root/bytecomp/printlambda.ml
diff options
context:
space:
mode:
authorLuc Maranget <luc.maranget@inria.fr>2014-03-21 17:02:44 +0000
committerLuc Maranget <luc.maranget@inria.fr>2014-03-21 17:02:44 +0000
commitc2a88c27fd3867e022c8ae4363bb24bca864619b (patch)
treeecf353c6af43216c7277824f9d8d8eb70a983015 /bytecomp/printlambda.ml
parent3d1c1adaf392f1c740c8c2015b9d1032ef3226c5 (diff)
#PR6269 Optimized string matching
Noticed that I had to bootstrap to test on ARM, so I commit a new bootstrap compiler. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14479 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'bytecomp/printlambda.ml')
-rw-r--r--bytecomp/printlambda.ml13
1 files changed, 12 insertions, 1 deletions
diff --git a/bytecomp/printlambda.ml b/bytecomp/printlambda.ml
index beb268480..e02196f9b 100644
--- a/bytecomp/printlambda.ml
+++ b/bytecomp/printlambda.ml
@@ -299,11 +299,22 @@ let rec lam ppf = function
if !spc then fprintf ppf "@ " else spc := true;
fprintf ppf "@[<hv 1>default:@ %a@]" lam l
end in
-
fprintf ppf
"@[<1>(%s %a@ @[<v 0>%a@])@]"
(match sw.sw_failaction with None -> "switch*" | _ -> "switch")
lam larg switch sw
+ | Lstringswitch(arg, cases, default) ->
+ let switch ppf cases =
+ let spc = ref false in
+ List.iter
+ (fun (s, l) ->
+ if !spc then fprintf ppf "@ " else spc := true;
+ fprintf ppf "@[<hv 1>case \"%s\":@ %a@]" (String.escaped s) lam l)
+ cases;
+ if !spc then fprintf ppf "@ " else spc := true;
+ fprintf ppf "@[<hv 1>default:@ %a@]" lam default in
+ fprintf ppf
+ "@[<1>(stringswitch %a@ @[<v 0>%a@])@]" lam arg switch cases
| Lstaticraise (i, ls) ->
let lams ppf largs =
List.iter (fun l -> fprintf ppf "@ %a" lam l) largs in