2
0
Эх сурвалжийг харах

move some string stuff to StringHelper

Simon Krajewski 6 жил өмнө
parent
commit
b1eaa8d8e4

+ 1 - 1
src/compiler/main.ml

@@ -746,7 +746,7 @@ try
 	let args_callback cl =
 		begin try
 			let path,name = Path.parse_path cl in
-			if Path.starts_uppercase name then
+			if StringHelper.starts_uppercase name then
 				classes := (path,name) :: !classes
 			else begin
 				force_typing := true;

+ 1 - 1
src/context/sourcemaps.ml

@@ -131,7 +131,7 @@ class sourcemap_writer (generated_file:string) =
 			"],\n");
 		if Common.defined com Define.SourceMapContent then begin
 			output_string channel ("\"sourcesContent\":[" ^
-				(String.concat "," (List.map (fun s -> try "\"" ^ Ast.s_escape (Std.input_file ~bin:true s) ^ "\"" with _ -> "null") sources)) ^
+				(String.concat "," (List.map (fun s -> try "\"" ^ StringHelper.s_escape (Std.input_file ~bin:true s) ^ "\"" with _ -> "null") sources)) ^
 				"],\n");
 		end;
 		output_string channel "\"names\":[],\n";

+ 2 - 16
src/core/ast.ml

@@ -354,24 +354,10 @@ let parse_path s =
 	| [] -> [],"" (* This is how old extlib behaved. *)
 	| x :: l -> List.rev l, x
 
-let s_escape ?(hex=true) s =
-	let b = Buffer.create (String.length s) in
-	for i = 0 to (String.length s) - 1 do
-		match s.[i] with
-		| '\n' -> Buffer.add_string b "\\n"
-		| '\t' -> Buffer.add_string b "\\t"
-		| '\r' -> Buffer.add_string b "\\r"
-		| '"' -> Buffer.add_string b "\\\""
-		| '\\' -> Buffer.add_string b "\\\\"
-		| c when int_of_char c < 32 && hex -> Buffer.add_string b (Printf.sprintf "\\x%.2X" (int_of_char c))
-		| c -> Buffer.add_char b c
-	done;
-	Buffer.contents b
-
 let s_constant = function
 	| Int s -> s
 	| Float s -> s
-	| String s -> "\"" ^ s_escape s ^ "\""
+	| String s -> "\"" ^ StringHelper.s_escape s ^ "\""
 	| Ident s -> s
 	| Regexp (r,o) -> "~/" ^ r ^ "/"
 
@@ -713,7 +699,7 @@ let iter_expr loop (e,p) =
 	| EVars vl -> List.iter (fun (_,_,_,eo) -> opt eo) vl
 
 let s_object_key_name name =  function
-	| DoubleQuotes -> "\"" ^ s_escape name ^ "\""
+	| DoubleQuotes -> "\"" ^ StringHelper.s_escape name ^ "\""
 	| NoQuotes -> name
 
 let s_display_kind = function

+ 2 - 9
src/core/path.ml

@@ -1,3 +1,5 @@
+open StringHelper
+
 let get_path_parts f =
 	(*
 		this function is quite weird: it tries to determine whether the given
@@ -46,15 +48,6 @@ let parse_path f =
 	in
 	loop cl
 
-let starts_uppercase x =
-	x.[0] = '_' || (x.[0] >= 'A' && x.[0] <= 'Z')
-
-let check_uppercase x =
-	if String.length x = 0 then
-		failwith "empty part"
-	else if not (starts_uppercase x) then
-		failwith "Class name must start with uppercase character"
-
 let parse_type_path s =
 	let pack,name = parse_path s in
 	check_uppercase name;

+ 24 - 1
src/core/stringHelper.ml

@@ -16,4 +16,27 @@ let capitalize s =
 		let code = Char.code (Bytes.get bytes 0) in
 		if 97 <= code && code <= 122 then
 			Bytes.set bytes 0 (Char.chr (code - 32));
-		Bytes.to_string bytes
+		Bytes.to_string bytes
+
+let starts_uppercase x =
+	x.[0] = '_' || (x.[0] >= 'A' && x.[0] <= 'Z')
+
+let check_uppercase x =
+	if String.length x = 0 then
+		failwith "empty part"
+	else if not (starts_uppercase x) then
+		failwith "Class name must start with uppercase character"
+
+let s_escape ?(hex=true) s =
+	let b = Buffer.create (String.length s) in
+	for i = 0 to (String.length s) - 1 do
+		match s.[i] with
+		| '\n' -> Buffer.add_string b "\\n"
+		| '\t' -> Buffer.add_string b "\\t"
+		| '\r' -> Buffer.add_string b "\\r"
+		| '"' -> Buffer.add_string b "\\\""
+		| '\\' -> Buffer.add_string b "\\\\"
+		| c when int_of_char c < 32 && hex -> Buffer.add_string b (Printf.sprintf "\\x%.2X" (int_of_char c))
+		| c -> Buffer.add_char b c
+	done;
+	Buffer.contents b

+ 1 - 1
src/core/type.ml

@@ -1112,7 +1112,7 @@ let s_expr_kind e =
 let s_const = function
 	| TInt i -> Int32.to_string i
 	| TFloat s -> s
-	| TString s -> Printf.sprintf "\"%s\"" (Ast.s_escape s)
+	| TString s -> Printf.sprintf "\"%s\"" (StringHelper.s_escape s)
 	| TBool b -> if b then "true" else "false"
 	| TNull -> "null"
 	| TThis -> "this"

+ 4 - 4
src/generators/genas3.ml

@@ -146,7 +146,7 @@ let valid_as3_ident s =
 
 let anon_field s =
 	let s = s_ident s in
-	if not (valid_as3_ident s) then "\"" ^ (Ast.s_escape s) ^ "\"" else s
+	if not (valid_as3_ident s) then "\"" ^ (StringHelper.s_escape s) ^ "\"" else s
 
 let rec create_dir acc = function
 	| [] -> ()
@@ -352,7 +352,7 @@ let generate_resources infos =
 			k := !k + 1;
 			print ctx "\t\t[Embed(source = \"__res/%s\", mimeType = \"application/octet-stream\")]\n" (Bytes.unsafe_to_string (Base64.str_encode name));
 			print ctx "\t\tpublic static var %s:Class;\n" varname;
-			inits := ("list[\"" ^ Ast.s_escape name ^ "\"] = " ^ varname ^ ";") :: !inits;
+			inits := ("list[\"" ^ StringHelper.s_escape name ^ "\"] = " ^ varname ^ ";") :: !inits;
 		) infos.com.resources;
 		spr ctx "\t\tstatic public function __init__():void {\n";
 		spr ctx "\t\t\tlist = new Dictionary();\n";
@@ -368,7 +368,7 @@ let generate_resources infos =
 let gen_constant ctx p = function
 	| TInt i -> print ctx "%ld" i
 	| TFloat s -> spr ctx s
-	| TString s -> print ctx "\"%s\"" (Ast.s_escape s)
+	| TString s -> print ctx "\"%s\"" (StringHelper.s_escape s)
 	| TBool b -> spr ctx (if b then "true" else "false")
 	| TNull -> spr ctx "null"
 	| TThis -> spr ctx (this ctx)
@@ -1209,7 +1209,7 @@ let generate_enum ctx e =
 		print ctx "public static var __meta__ : * = ";
 		gen_expr ctx e;
 		newline ctx);
-	print ctx "public static var __constructs__ : Array = [%s];" (String.concat "," (List.map (fun s -> "\"" ^ Ast.s_escape s ^ "\"") e.e_names));
+	print ctx "public static var __constructs__ : Array = [%s];" (String.concat "," (List.map (fun s -> "\"" ^ StringHelper.s_escape s ^ "\"") e.e_names));
 	cl();
 	newline ctx;
 	print ctx "}";

+ 5 - 5
src/generators/gencpp.ml

@@ -1060,7 +1060,7 @@ let escape_command s =
 
 let gen_str macro gen s =
    let rec split s plus =
-      let escaped = Ast.s_escape ~hex:false s in
+      let escaped = StringHelper.s_escape ~hex:false s in
       let hexed = (special_to_hex escaped) in
       if (String.length hexed <= 16000 ) then
          plus ^ " HX_CSTRING(\"" ^ hexed ^ "\")"
@@ -1070,7 +1070,7 @@ let gen_str macro gen s =
          (split (String.sub s 0 half) plus ) ^ (split (String.sub s half (len-half)) "+" )
       end
    in
-   let escaped = Ast.s_escape ~hex:false s in
+   let escaped = StringHelper.s_escape ~hex:false s in
    let hexed = (special_to_hex escaped) in
    if (String.length hexed <= 16000 ) then
       macro ^ "(\"" ^ hexed ^ "\"," ^ (gen s) ^ ")"
@@ -1103,7 +1103,7 @@ let strq ctx s =
 
 
 let const_char_star s =
-   let escaped = Ast.s_escape ~hex:false s in
+   let escaped = StringHelper.s_escape ~hex:false s in
    "\"" ^ special_to_hex escaped ^ "\"";
 ;;
 
@@ -1297,7 +1297,7 @@ let strip_file ctx file = (match Common.defined ctx Common.Define.AbsolutePath w
 let hx_stack_push ctx output clazz func_name pos gc_stack =
    if ctx.ctx_debug_level > 0 then begin
       let stripped_file = strip_file ctx.ctx_common pos.pfile in
-      let esc_file = (Ast.s_escape stripped_file) in
+      let esc_file = (StringHelper.s_escape stripped_file) in
       ctx.ctx_file_info := PMap.add stripped_file pos.pfile !(ctx.ctx_file_info);
       let full_name = clazz ^ "." ^ func_name ^ (
         if (clazz="*") then
@@ -5935,7 +5935,7 @@ let generate_class_files baseCtx super_deps constructor_deps class_def inScripta
                   output_cpp ("\tcase " ^ (string_of_int l) ^ ":\n");
                   len_case := l;
                end;
-               output_cpp ("\t\tif (HX_FIELD_EQ(inName,\"" ^  (Ast.s_escape field)  ^ "\") ) { " ^ result ^ " }\n");
+               output_cpp ("\t\tif (HX_FIELD_EQ(inName,\"" ^  (StringHelper.s_escape field)  ^ "\") ) { " ^ result ^ " }\n");
             ) sfields;
             output_cpp "\t}\n";
          end;

+ 1 - 1
src/generators/gencs.ml

@@ -1097,7 +1097,7 @@ let generate con =
 				let cur_line = Lexer.get_error_line p in
 				let file = Path.get_full_path p.pfile in
 				if cur_line <> ((!last_line)+1) then
-					let line = Ast.s_escape file in
+					let line = StringHelper.s_escape file in
 					if String.length line <= 256 then
 						begin print w "#line %d \"%s\"" cur_line line; newline w end
 					else (* Compiler Error CS1560 https://msdn.microsoft.com/en-us/library/z3t5e5sw(v=vs.90).aspx *)

+ 1 - 1
src/generators/genjava.ml

@@ -1396,7 +1396,7 @@ let generate con =
 		else fun w p ->
 			let cur_line = Lexer.get_error_line p in
 			let file = Path.get_full_path p.pfile in
-			print w "//line %d \"%s\"" cur_line (Ast.s_escape file); newline w
+			print w "//line %d \"%s\"" cur_line (StringHelper.s_escape file); newline w
 	in
 
 	let extract_statements expr =

+ 3 - 3
src/generators/genjs.ml

@@ -267,7 +267,7 @@ let write_mappings ctx smap =
 		"],\n");
 	if Common.defined ctx.com Define.SourceMapContent then begin
 		output_string channel ("\"sourcesContent\":[" ^
-			(String.concat "," (List.map (fun s -> try "\"" ^ Ast.s_escape (Std.input_file ~bin:true s) ^ "\"" with _ -> "null") sources)) ^
+			(String.concat "," (List.map (fun s -> try "\"" ^ StringHelper.s_escape (Std.input_file ~bin:true s) ^ "\"" with _ -> "null") sources)) ^
 			"],\n");
 	end;
 	output_string channel "\"names\":[],\n";
@@ -346,7 +346,7 @@ let is_dynamic_iterator ctx e =
 let gen_constant ctx p = function
 	| TInt i -> print ctx "%ld" i
 	| TFloat s -> spr ctx s
-	| TString s -> print ctx "\"%s\"" (Ast.s_escape s)
+	| TString s -> print ctx "\"%s\"" (StringHelper.s_escape s)
 	| TBool b -> spr ctx (if b then "true" else "false")
 	| TNull -> spr ctx "null"
 	| TThis -> spr ctx (this ctx)
@@ -668,7 +668,7 @@ and gen_expr ctx e =
 	| TObjectDecl fields ->
 		spr ctx "{ ";
 		concat ctx ", " (fun ((f,_,qs),e) -> (match qs with
-			| DoubleQuotes -> print ctx "\"%s\" : " (Ast.s_escape f);
+			| DoubleQuotes -> print ctx "\"%s\" : " (StringHelper.s_escape f);
 			| NoQuotes -> print ctx "%s : " (anon_field f));
 			gen_value ctx e
 		) fields;

+ 1 - 1
src/generators/genlua.ml

@@ -84,7 +84,7 @@ let dot_path = Globals.s_type_path
 let s_path ctx = flat_path
 
 (* Lua requires decimal encoding for characters, rather than the hex *)
-(* provided by Ast.s_escape *)
+(* provided by StringHelper.s_escape *)
 let s_escape_lua ?(dec=true) s =
     let b = Buffer.create (String.length s) in
     for i = 0 to (String.length s) - 1 do

+ 3 - 3
src/generators/genpy.ml

@@ -1089,7 +1089,7 @@ module Printer = struct
 		| OpInterval | OpArrow | OpIn | OpAssignOp _ -> assert false
 
 	let print_string s =
-		Printf.sprintf "\"%s\"" (Ast.s_escape s)
+		Printf.sprintf "\"%s\"" (StringHelper.s_escape s)
 
 	let print_constant = function
 		| TThis -> "self"
@@ -1738,7 +1738,7 @@ module Printer = struct
 			print_exprs pctx sep el
 
 	and print_exprs_named pctx sep fl =
-		let args = String.concat sep (List.map (fun ((s,_,_),e) -> Printf.sprintf "'%s': %s" (Ast.s_escape (handle_keywords s)) (print_expr pctx e)) fl) in
+		let args = String.concat sep (List.map (fun ((s,_,_),e) -> Printf.sprintf "'%s': %s" (StringHelper.s_escape (handle_keywords s)) (print_expr pctx e)) fl) in
 		Printf.sprintf "{%s}" args
 	and print_params_named pctx sep fl =
 		let args = String.concat sep (List.map (fun ((s,_,_),e) -> Printf.sprintf "%s= %s" (handle_keywords s) (print_expr pctx e)) fl) in
@@ -2337,7 +2337,7 @@ module Generator = struct
 					","
 				in
 				let k_enc = Codegen.escape_res_name k false in
-				print ctx "%s\"%s\": open('%%s.%%s'%%(_file,'%s'),'rb').read()" prefix (Ast.s_escape k) k_enc;
+				print ctx "%s\"%s\": open('%%s.%%s'%%(_file,'%s'),'rb').read()" prefix (StringHelper.s_escape k) k_enc;
 
 				let f = open_out_bin (ctx.com.file ^ "." ^ k_enc) in
 				output_string f v;

+ 1 - 1
src/generators/hl2c.ml

@@ -263,7 +263,7 @@ let string_data_limit = 64
 let string ctx sid =
 	let s = ctx.hlcode.strings.(sid) in
 	if String.length s < string_data_limit then
-		sprintf "USTR(\"%s\")" (Ast.s_escape ~hex:false s)
+		sprintf "USTR(\"%s\")" (StringHelper.s_escape ~hex:false s)
 	else
 		sprintf "string$%d" sid
 

+ 1 - 1
src/macro/eval/evalDebugSocket.ml

@@ -18,7 +18,7 @@ let var_to_json name value access =
 	let jv t v structured =
 		JObject ["name",JString name;"type",JString t;"value",JString v;"structured",JBool structured;"access",JString access]
 	in
-	let string_repr s = "\"" ^ (Ast.s_escape s.sstring) ^ "\"" in
+	let string_repr s = "\"" ^ (StringHelper.s_escape s.sstring) ^ "\"" in
 	let rec level2_value_repr = function
 		| VNull -> "null"
 		| VTrue -> "true"

+ 1 - 1
src/macro/macroApi.ml

@@ -1617,7 +1617,7 @@ let macro_api ccom get_api =
 						vnull
 					);
 					"quoteString", vfun1 (fun v ->
-						encode_string ("\"" ^ Ast.s_escape (decode_string v) ^ "\"")
+						encode_string ("\"" ^ StringHelper.s_escape (decode_string v) ^ "\"")
 					);
 					"buildMetaData", vfun1 (fun t ->
 						match Texpr.build_metadata com.basic (decode_type_decl t) with

+ 1 - 0
src/optimization/analyzer.ml

@@ -17,6 +17,7 @@
 	Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301, USA.
  *)
 
+open StringHelper
 open Ast
 open Type
 open Common