summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--testsuite/external/.ignore2
-rw-r--r--testsuite/external/Makefile250
-rw-r--r--testsuite/external/coq-8.4pl1.patch11
-rw-r--r--testsuite/external/obrowser-1.1.1.patch224
-rw-r--r--testsuite/external/ocamlnet-3.5.1.patch11
5 files changed, 388 insertions, 110 deletions
diff --git a/testsuite/external/.ignore b/testsuite/external/.ignore
index a65ca6ca8..a4359ade2 100644
--- a/testsuite/external/.ignore
+++ b/testsuite/external/.ignore
@@ -23,6 +23,8 @@ camlimages
camlimages-4.0.1
camlpdf
camlpdf-0.5
+camlp4
+camlp4-trunk
camlp5
camlp5-6.10
camlzip
diff --git a/testsuite/external/Makefile b/testsuite/external/Makefile
index 5fcd005ba..a6ca0949d 100644
--- a/testsuite/external/Makefile
+++ b/testsuite/external/Makefile
@@ -40,14 +40,14 @@ default:
all-cygwin: findlib ounit res pcre react ocamltext ocamlssl camlzip cryptokit \
sqlite ocgi xmllight configfile xmlm omake \
camomile zen vsyml extlib fileutils ocamlify ocamlmod \
- calendar dbm ocamlscript camlp5 geneweb coq
+ calendar dbm ocamlscript
all-macos: findlib lablgtk ocamlgraph ounit res pcre core react ocamltext \
- ocamlssl lwt camlzip cryptokit sqlite menhir obrowser hevea \
+ ocamlssl lwt camlzip cryptokit sqlite menhir hevea \
unison ocgi xmllight configfile xmlm lablgtkextras sks omake \
altergo boomerang camomile zen vsyml ocamlnet extlib fileutils \
odn ocamlify expect ocamlmod oasis calendar camlimages advi \
- dbm ocsigen ocamlscript camlp5 geneweb coq framac
+ dbm ocsigen ocamlscript framac
platform:
case `uname -s` in \
@@ -56,11 +56,35 @@ platform:
*) ${MAKE} all;; \
esac
+# https://github.com/ocaml/camlp4/
+CAMLP4=camlp4-trunk
+${CAMLP4}.zip:
+ ${WGET} https://github.com/ocaml/camlp4/archive/trunk.zip
+ mv trunk.zip ${CAMLP4}.zip
+camlp4: ${CAMLP4}.zip
+ printf "%s " "$@" >/dev/tty
+ test -d ${PREFIX}
+ rm -rf ${CAMLP4}
+ unzip -q ${CAMLP4}.zip
+ ./Patcher.sh ${CAMLP4}
+ ( cd ${CAMLP4} && \
+ export PATH=${PREFIX}/bin:$$PATH && \
+ sh ./configure --prefix ${PREFIX} && \
+ ${MAKE} all && \
+ ocamlfind remove camlp4 && \
+ ${MAKE} install )
+ echo ${VERSION} >$@
+clean::
+ rm -rf ${CAMLP4} camlp4
+distclean::
+ rm -f ${CAMLP4}.tar.gz
+all: camlp4
+
# http://projects.camlcity.org/projects/findlib.html
FINDLIB=findlib-1.3.3
${FINDLIB}.tar.gz:
${WGET} http://download.camlcity.org/download/$@
-findlib: ${FINDLIB}.tar.gz
+findlib: ${FINDLIB}.tar.gz camlp4
printf "%s " "$@" >/dev/tty
test -d ${PREFIX}
rm -rf ${FINDLIB}
@@ -715,27 +739,28 @@ distclean::
rm -f ${MENHIR}.tar.gz
all: menhir
-# http://ocsigen.org/obrowser/install
-OBROWSER=obrowser-1.1.1
-${OBROWSER}.tar.gz:
- ${WGET} http://ocsigen.org/download/$@
-obrowser: ${OBROWSER}.tar.gz lwt menhir
- printf "%s " "$@" >/dev/tty
- test -d ${PREFIX}
- rm -rf ${OBROWSER}
- tar zxf ${OBROWSER}.tar.gz
- ./Patcher.sh ${OBROWSER}
- ( cd ${OBROWSER} && \
- export PATH=${PREFIX}/bin:$$PATH && \
- ${MAKE} && \
- ocamlfind remove obrowser && \
- ${MAKE} install )
- echo ${VERSION} >$@
-clean::
- rm -rf ${OBROWSER} obrowser
-distclean::
- rm -f ${OBROWSER}.tar.gz
-all: obrowser
+# disabled: cannot find module Js
+# # http://ocsigen.org/obrowser/install
+# OBROWSER=obrowser-1.1.1
+# ${OBROWSER}.tar.gz:
+# ${WGET} http://ocsigen.org/download/$@
+# obrowser: ${OBROWSER}.tar.gz lwt menhir ocsigen
+# printf "%s " "$@" >/dev/tty
+# test -d ${PREFIX}
+# rm -rf ${OBROWSER}
+# tar zxf ${OBROWSER}.tar.gz
+# ./Patcher.sh ${OBROWSER}
+# ( cd ${OBROWSER} && \
+# export PATH=${PREFIX}/bin:$$PATH && \
+# ${MAKE} && \
+# ocamlfind remove obrowser && \
+# ${MAKE} install )
+# echo ${VERSION} >$@
+# clean::
+# rm -rf ${OBROWSER} obrowser
+# distclean::
+# rm -f ${OBROWSER}.tar.gz
+# all: obrowser
# http://hevea.inria.fr/old/
HEVEA=hevea-2.09
@@ -1389,7 +1414,7 @@ all: dbm
OCSIGEN=ocsigen-bundle-2.2.2
${OCSIGEN}.tar.gz:
${WGET} http://ocsigen.org/download/$@
-ocsigen: ${OCSIGEN}.tar.gz findlib lwt obrowser pcre ocamlnet ocamlssl \
+ocsigen: ${OCSIGEN}.tar.gz findlib lwt pcre ocamlnet ocamlssl \
sqlite camlzip cryptokit calendar dbm
printf "%s " "$@" >/dev/tty
test -d ${PREFIX}
@@ -1501,70 +1526,74 @@ distclean::
rm -f ${CAMLPDF}.tar.gz
all: camlpdf
-# http://pauillac.inria.fr/~ddr/camlp5/
-CAMLP5=camlp5-6.10
-${CAMLP5}.tgz:
- ${WGET} http://pauillac.inria.fr/~ddr/camlp5/distrib/src/$@
-camlp5: ${CAMLP5}.tgz
- printf "%s " "$@" >/dev/tty
- test -d ${PREFIX}
- rm -rf ${CAMLP5}
- tar zxf ${CAMLP5}.tgz
- ./Patcher.sh ${CAMLP5}
- ( cd ${CAMLP5} && \
- export PATH=${PREFIX}/bin:$$PATH && \
- ./configure --transitional && \
- ${MAKE} world.opt && \
- ${MAKE} install )
- echo ${VERSION} >$@
-clean::
- rm -rf ${CAMLP5} camlp5
-distclean::
- rm -f ${CAMLP5}.tgz
-all: camlp5
-
-# http://opensource.geneanet.org/projects/geneweb
-GENEWEB=gw-6.05-src
-${GENEWEB}.tgz:
- ${WGET} http://opensource.geneanet.org/attachments/download/190/$@
-geneweb: ${GENEWEB}.tgz camlp5
- printf "%s " "$@" >/dev/tty
- test -d ${PREFIX}
- rm -rf ${GENEWEB}
- tar zxf ${GENEWEB}.tgz
- ./Patcher.sh ${GENEWEB}
- ( cd ${GENEWEB} && \
- export PATH=${PREFIX}/bin:$$PATH && \
- sh ./configure && \
- ${MAKE} )
- echo ${VERSION} >$@
-clean::
- rm -rf ${GENEWEB} geneweb
-distclean::
- rm -f ${GENEWEB}.tgz
-all: geneweb
-
+# disabled: need to be updated for new AST stuff
+# # http://pauillac.inria.fr/~ddr/camlp5/
+# CAMLP5=camlp5-6.10
+# ${CAMLP5}.tgz:
+# ${WGET} http://pauillac.inria.fr/~ddr/camlp5/distrib/src/$@
+# camlp5: ${CAMLP5}.tgz
+# printf "%s " "$@" >/dev/tty
+# test -d ${PREFIX}
+# rm -rf ${CAMLP5}
+# tar zxf ${CAMLP5}.tgz
+# ./Patcher.sh ${CAMLP5}
+# ( cd ${CAMLP5} && \
+# export PATH=${PREFIX}/bin:$$PATH && \
+# ./configure --transitional && \
+# ${MAKE} world.opt && \
+# ${MAKE} install )
+# echo ${VERSION} >$@
+# clean::
+# rm -rf ${CAMLP5} camlp5
+# distclean::
+# rm -f ${CAMLP5}.tgz
+# all: camlp5
+
+# disabled: depends on camlp5
+# # http://opensource.geneanet.org/projects/geneweb
+# GENEWEB=gw-6.05-src
+# ${GENEWEB}.tgz:
+# ${WGET} http://opensource.geneanet.org/attachments/download/190/$@
+# geneweb: ${GENEWEB}.tgz camlp5
+# printf "%s " "$@" >/dev/tty
+# test -d ${PREFIX}
+# rm -rf ${GENEWEB}
+# tar zxf ${GENEWEB}.tgz
+# ./Patcher.sh ${GENEWEB}
+# ( cd ${GENEWEB} && \
+# export PATH=${PREFIX}/bin:$$PATH && \
+# sh ./configure && \
+# ${MAKE} )
+# echo ${VERSION} >$@
+# clean::
+# rm -rf ${GENEWEB} geneweb
+# distclean::
+# rm -f ${GENEWEB}.tgz
+# all: geneweb
+
+# disabled: Cannot find file q_coqast.cmo
+# maybe because of the camlp5 -> camlp4 switch
# http://coq.inria.fr/download
-COQ=coq-8.4pl1
-${COQ}.tar.gz:
- ${WGET} http://coq.inria.fr/distrib/V8.4pl1/files/$@
-coq: ${COQ}.tar.gz camlp5
- printf "%s " "$@" >/dev/tty
- test -d ${PREFIX}
- rm -rf ${COQ}
- tar zxf ${COQ}.tar.gz
- ./Patcher.sh ${COQ}
- ( cd ${COQ} && \
- export PATH=${PREFIX}/bin:$$PATH && \
- ./configure -prefix ${PREFIX} -with-doc no && \
- ${MAKE} world && \
- ${MAKE} install )
- echo ${VERSION} >$@
-clean::
- rm -rf ${COQ} coq
-distclean::
- rm -f ${COQ}.tar.gz
-all: coq
+# COQ=coq-8.4pl1
+# ${COQ}.tar.gz:
+# ${WGET} http://coq.inria.fr/distrib/V8.4pl1/files/$@
+# coq: ${COQ}.tar.gz
+# printf "%s " "$@" >/dev/tty
+# test -d ${PREFIX}
+# rm -rf ${COQ}
+# tar zxf ${COQ}.tar.gz
+# ./Patcher.sh ${COQ}
+# ( cd ${COQ} && \
+# export PATH=${PREFIX}/bin:$$PATH && \
+# ./configure -prefix ${PREFIX} -with-doc no && \
+# ${MAKE} world && \
+# ${MAKE} install )
+# echo ${VERSION} >$@
+# clean::
+# rm -rf ${COQ} coq
+# distclean::
+# rm -f ${COQ}.tar.gz
+# all: coq
# http://code.google.com/p/bitstring/
@@ -1592,33 +1621,34 @@ distclean::
rm -f ${BITSTRING}.tar.gz
all: bitstring
+# disabled: depends on coq
# http://compcert.inria.fr
-COMPCERT=compcert-1.13
-${COMPCERT}.tgz:
- ${WGET} http://compcert.inria.fr/release/$@
-compcert: ${COMPCERT}.tgz coq bitstring
- printf "%s " "$@" >/dev/tty
- test -d ${PREFIX}
- rm -rf ${COMPCERT}
- tar zxf ${COMPCERT}.tgz
- ./Patcher.sh ${COMPCERT}
- ( cd ${COMPCERT} && \
- export PATH=${PREFIX}/bin:$$PATH && \
- sh ./configure -prefix ${PREFIX} ppc-linux && \
- ${MAKE} all && \
- ${MAKE} install )
- echo ${VERSION} >$@
-clean::
- rm -rf ${COMPCERT} compcert
-distclean::
- rm -f ${COMPCERT}.tgz
-all: compcert
+# COMPCERT=compcert-1.13
+# ${COMPCERT}.tgz:
+# ${WGET} http://compcert.inria.fr/release/$@
+# compcert: ${COMPCERT}.tgz coq bitstring
+# printf "%s " "$@" >/dev/tty
+# test -d ${PREFIX}
+# rm -rf ${COMPCERT}
+# tar zxf ${COMPCERT}.tgz
+# ./Patcher.sh ${COMPCERT}
+# ( cd ${COMPCERT} && \
+# export PATH=${PREFIX}/bin:$$PATH && \
+# sh ./configure -prefix ${PREFIX} ppc-linux && \
+# ${MAKE} all && \
+# ${MAKE} install )
+# echo ${VERSION} >$@
+# clean::
+# rm -rf ${COMPCERT} compcert
+# distclean::
+# rm -f ${COMPCERT}.tgz
+# all: compcert
# http://frama-c.com/
FRAMAC=frama-c-Oxygen-20120901
${FRAMAC}.tar.gz:
${WGET} http://frama-c.com/download/$@
-framac: ${FRAMAC}.tar.gz lablgtk ocamlgraph altergo coq
+framac: ${FRAMAC}.tar.gz lablgtk ocamlgraph altergo # coq removed (disabled)
printf "%s " "$@" >/dev/tty
test -d ${PREFIX}
rm -rf ${FRAMAC}
diff --git a/testsuite/external/coq-8.4pl1.patch b/testsuite/external/coq-8.4pl1.patch
new file mode 100644
index 000000000..058038282
--- /dev/null
+++ b/testsuite/external/coq-8.4pl1.patch
@@ -0,0 +1,11 @@
+--- coq-8.4pl1/kernel/univ.ml.orig 2013-11-27 15:53:01.000000000 +0100
++++ coq-8.4pl1/kernel/univ.ml 2013-11-27 15:53:20.000000000 +0100
+@@ -226,7 +226,7 @@
+
+
+ (* between : UniverseLevel.t -> canonical_arc -> canonical_arc list *)
+-(* between u v = {w|u<=w<=v, w canonical} *)
++(* between u v = {w |u<=w<=v, w canonical} *)
+ (* between is the most costly operation *)
+
+ let between g arcu arcv =
diff --git a/testsuite/external/obrowser-1.1.1.patch b/testsuite/external/obrowser-1.1.1.patch
index e135f1d3f..f67a3b7a8 100644
--- a/testsuite/external/obrowser-1.1.1.patch
+++ b/testsuite/external/obrowser-1.1.1.patch
@@ -1159,3 +1159,227 @@
+
+ @since 4.01.0
+*)
+--- obrowser-1.1.1/rt/caml/pervasives.mli 2013-11-27 09:51:32.000000000 +0100
++++ /usr/local/ocaml/trunk/lib/ocaml/pervasives.mli 2013-11-26 19:03:11.000000000 +0100
+@@ -28,6 +28,11 @@
+ external raise : exn -> 'a = "%raise"
+ (** Raise the given exception value *)
+
++external raise_notrace : exn -> 'a = "%raise_notrace"
++(** A faster version [raise] which does not record the backtrace.
++ @since 4.02.0
++*)
++
+ val invalid_arg : string -> 'a
+ (** Raise exception [Invalid_argument] with the given string. *)
+
+--- obrowser-1.1.1/rt/caml/pervasives.ml 2013-11-27 14:25:40.000000000 +0100
++++ /usr/local/ocaml/trunk/lib/ocaml/pervasives.ml 2013-11-26 19:03:11.000000000 +0100
+@@ -15,7 +15,17 @@
+
+ (* Exceptions *)
+
++external register_named_value : string -> 'a -> unit
++ = "caml_register_named_value"
++
++let () =
++ (* for asmrun/fail.c *)
++ register_named_value "Pervasives.array_bound_error"
++ (Invalid_argument "index out of bounds")
++
++
+ external raise : exn -> 'a = "%raise"
++external raise_notrace : exn -> 'a = "%raise_notrace"
+
+ let failwith s = raise(Failure s)
+ let invalid_arg s = raise(Invalid_argument s)
+@@ -454,7 +464,4 @@
+ do_at_exit ();
+ sys_exit retcode
+
+-external register_named_value : string -> 'a -> unit
+- = "caml_register_named_value"
+-
+ let _ = register_named_value "Pervasives.do_at_exit" do_at_exit
+--- obrowser-1.1.1/rt/caml/printexc.mli 2013-11-27 14:26:19.000000000 +0100
++++ /usr/local/ocaml/trunk/lib/ocaml/printexc.mli 2013-11-26 19:03:11.000000000 +0100
+@@ -112,3 +112,23 @@
+
+ @since 4.01.0
+ *)
++
++
++(** {6 Exception slots} *)
++
++val exn_slot_id: exn -> int
++(** [Printexc.exn_slot_id] returns an integer which uniquely identifies
++ the constructor used to create the exception value [exn]
++ (in the current runtime).
++
++ @since 4.02.0
++*)
++
++val exn_slot_name: exn -> string
++(** [Printexc.exn_slot_id exn] returns the internal name of the constructor
++ used to create the exception value [exn].
++
++ @since 4.02.0
++*)
++
++
+--- obrowser-1.1.1/rt/caml/printexc.ml 2013-11-27 14:27:37.000000000 +0100
++++ /usr/local/ocaml/trunk/lib/ocaml/printexc.ml 2013-11-26 19:03:11.000000000 +0100
+@@ -58,9 +58,12 @@
+ sprintf locfmt file line char (char+6) "Undefined recursive module"
+ | _ ->
+ let x = Obj.repr x in
+- let constructor =
+- (Obj.magic (Obj.field (Obj.field x 0) 0) : string) in
+- constructor ^ (fields x) in
++ if Obj.tag x <> 0 then
++ (Obj.magic (Obj.field x 0) : string)
++ else
++ let constructor =
++ (Obj.magic (Obj.field (Obj.field x 0) 0) : string) in
++ constructor ^ (fields x) in
+ conv !printers
+
+ let print fct arg =
+@@ -168,3 +171,16 @@
+
+
+ external get_callstack: int -> raw_backtrace = "caml_get_current_callstack"
++
++
++let exn_slot x =
++ let x = Obj.repr x in
++ if Obj.tag x = 0 then Obj.field x 0 else x
++
++let exn_slot_id x =
++ let slot = exn_slot x in
++ (Obj.obj (Obj.field slot 1) : int)
++
++let exn_slot_name x =
++ let slot = exn_slot x in
++ (Obj.obj (Obj.field slot 0) : string)
+--- obrowser-1.1.1/rt/caml/list.mli 2013-11-27 14:28:14.000000000 +0100
++++ /usr/local/ocaml/trunk/lib/ocaml/list.mli 2013-11-26 19:03:11.000000000 +0100
+@@ -280,6 +278,9 @@
+ (** Same as {!List.sort} or {!List.stable_sort}, whichever is faster
+ on typical input. *)
+
++val sort_uniq : ('a -> 'a -> int) -> 'a list -> 'a list
++(** Same as {!List.sort}, but also remove duplicates. *)
++
+ val merge : ('a -> 'a -> int) -> 'a list -> 'a list -> 'a list
+ (** Merge two lists:
+ Assuming that [l1] and [l2] are sorted according to the
+--- obrowser-1.1.1/rt/caml/list.ml 2013-11-27 14:29:31.000000000 +0100
++++ /usr/local/ocaml/trunk/lib/ocaml/list.ml 2013-11-26 19:03:11.000000000 +0100
+@@ -326,3 +324,106 @@
+ array_to_list_in_place a
+ ;;
+ *)
++
++
++(** sorting + removing duplicates *)
++
++let sort_uniq cmp l =
++ let rec rev_merge l1 l2 accu =
++ match l1, l2 with
++ | [], l2 -> rev_append l2 accu
++ | l1, [] -> rev_append l1 accu
++ | h1::t1, h2::t2 ->
++ let c = cmp h1 h2 in
++ if c = 0 then rev_merge t1 t2 (h1::accu)
++ else if c < 0
++ then rev_merge t1 l2 (h1::accu)
++ else rev_merge l1 t2 (h2::accu)
++ in
++ let rec rev_merge_rev l1 l2 accu =
++ match l1, l2 with
++ | [], l2 -> rev_append l2 accu
++ | l1, [] -> rev_append l1 accu
++ | h1::t1, h2::t2 ->
++ let c = cmp h1 h2 in
++ if c = 0 then rev_merge_rev t1 t2 (h1::accu)
++ else if c > 0
++ then rev_merge_rev t1 l2 (h1::accu)
++ else rev_merge_rev l1 t2 (h2::accu)
++ in
++ let rec sort n l =
++ match n, l with
++ | 2, x1 :: x2 :: _ ->
++ let c = cmp x1 x2 in
++ if c = 0 then [x1]
++ else if c < 0 then [x1; x2] else [x2; x1]
++ | 3, x1 :: x2 :: x3 :: _ ->
++ let c = cmp x1 x2 in
++ if c = 0 then begin
++ let c = cmp x2 x3 in
++ if c = 0 then [x2]
++ else if c < 0 then [x2; x3] else [x3; x2]
++ end else if c < 0 then begin
++ let c = cmp x2 x3 in
++ if c = 0 then [x1; x2]
++ else if c < 0 then [x1; x2; x3]
++ else let c = cmp x1 x3 in
++ if c = 0 then [x1; x2]
++ else if c < 0 then [x1; x3; x2]
++ else [x3; x1; x2]
++ end else begin
++ let c = cmp x1 x3 in
++ if c = 0 then [x2; x1]
++ else if c < 0 then [x2; x1; x3]
++ else let c = cmp x2 x3 in
++ if c = 0 then [x2; x1]
++ else if c < 0 then [x2; x3; x1]
++ else [x3; x2; x1]
++ end
++ | n, l ->
++ let n1 = n asr 1 in
++ let n2 = n - n1 in
++ let l2 = chop n1 l in
++ let s1 = rev_sort n1 l in
++ let s2 = rev_sort n2 l2 in
++ rev_merge_rev s1 s2 []
++ and rev_sort n l =
++ match n, l with
++ | 2, x1 :: x2 :: _ ->
++ let c = cmp x1 x2 in
++ if c = 0 then [x1]
++ else if c > 0 then [x1; x2] else [x2; x1]
++ | 3, x1 :: x2 :: x3 :: _ ->
++ let c = cmp x1 x2 in
++ if c = 0 then begin
++ let c = cmp x2 x3 in
++ if c = 0 then [x2]
++ else if c > 0 then [x2; x3] else [x3; x2]
++ end else if c > 0 then begin
++ let c = cmp x2 x3 in
++ if c = 0 then [x1; x2]
++ else if c > 0 then [x1; x2; x3]
++ else let c = cmp x1 x3 in
++ if c = 0 then [x1; x2]
++ else if c > 0 then [x1; x3; x2]
++ else [x3; x1; x2]
++ end else begin
++ let c = cmp x1 x3 in
++ if c = 0 then [x2; x1]
++ else if c > 0 then [x2; x1; x3]
++ else let c = cmp x2 x3 in
++ if c = 0 then [x2; x1]
++ else if c > 0 then [x2; x3; x1]
++ else [x3; x2; x1]
++ end
++ | n, l ->
++ let n1 = n asr 1 in
++ let n2 = n - n1 in
++ let l2 = chop n1 l in
++ let s1 = sort n1 l in
++ let s2 = sort n2 l2 in
++ rev_merge s1 s2 []
++ in
++ let len = length l in
++ if len < 2 then l else sort len l
++;;
diff --git a/testsuite/external/ocamlnet-3.5.1.patch b/testsuite/external/ocamlnet-3.5.1.patch
index db8718541..46884d211 100644
--- a/testsuite/external/ocamlnet-3.5.1.patch
+++ b/testsuite/external/ocamlnet-3.5.1.patch
@@ -39,3 +39,14 @@
with _ -> raise Protocol_error;
+*)
end
+--- ocamlnet-3.5.1/src/netstring/netencoding.mli.orig 2013-11-27 14:41:37.000000000 +0100
++++ ocamlnet-3.5.1/src/netstring/netencoding.mli 2013-11-27 14:41:52.000000000 +0100
+@@ -120,7 +120,7 @@
+ * to ensure that all output lines have a length <= 76 bytes.
+ *
+ * Note unsafe characters:
+- * As recommended by RFC 2045, the characters [!#$\@[]^`{|}~]
++ * As recommended by RFC 2045, the characters [!#$\@[]^`{}|~]
+ * and the double quotes
+ * are additionally represented as hex tokens.
+ * Furthermore, the letter 'F' is considered as unsafe if it