summaryrefslogtreecommitdiffstats
path: root/otherlibs/labltk/compiler/lexer.mll
diff options
context:
space:
mode:
Diffstat (limited to 'otherlibs/labltk/compiler/lexer.mll')
-rw-r--r--otherlibs/labltk/compiler/lexer.mll22
1 files changed, 11 insertions, 11 deletions
diff --git a/otherlibs/labltk/compiler/lexer.mll b/otherlibs/labltk/compiler/lexer.mll
index a2251b902..337c5cdc2 100644
--- a/otherlibs/labltk/compiler/lexer.mll
+++ b/otherlibs/labltk/compiler/lexer.mll
@@ -25,10 +25,10 @@ let current_line = ref 1
(* The table of keywords *)
-let keyword_table = (Hashtbl.create size:149 : (string, token) Hashtbl.t)
+let keyword_table = (Hashtbl.create 149 : (string, token) Hashtbl.t)
let _ = List.iter
- fun:(fun (str,tok) -> Hashtbl.add keyword_table key:str data:tok)
+ f:(fun (str,tok) -> Hashtbl.add keyword_table key:str data:tok)
[
"int", TYINT;
"float", TYFLOAT;
@@ -52,7 +52,7 @@ let _ = List.iter
(* To buffer string literals *)
-let initial_string_buffer = String.create len:256
+let initial_string_buffer = String.create 256
let string_buff = ref initial_string_buffer
let string_index = ref 0
@@ -63,7 +63,7 @@ let reset_string_buffer () =
let store_string_char c =
if !string_index >= String.length (!string_buff) then begin
- let new_buff = String.create len:(String.length (!string_buff) * 2) in
+ let new_buff = String.create (String.length (!string_buff) * 2) in
String.blit src:(!string_buff) src_pos:0 dst:new_buff dst_pos:0
len:(String.length (!string_buff));
string_buff := new_buff
@@ -85,9 +85,9 @@ let char_for_backslash = function
| c -> c
let char_for_decimal_code lexbuf i =
- Char.chr(100 * (Char.code(Lexing.lexeme_char lexbuf pos:i) - 48) +
- 10 * (Char.code(Lexing.lexeme_char lexbuf pos:(i+1)) - 48) +
- (Char.code(Lexing.lexeme_char lexbuf pos:(i+2)) - 48))
+ Char.chr(100 * (Char.code(Lexing.lexeme_char lexbuf i) - 48) +
+ 10 * (Char.code(Lexing.lexeme_char lexbuf (i+1)) - 48) +
+ (Char.code(Lexing.lexeme_char lexbuf (i+2)) - 48))
let saved_string_start = ref 0
@@ -101,7 +101,7 @@ rule main = parse
( '_' ? ['A'-'Z' 'a'-'z' '\192'-'\214' '\216'-'\246' '\248'-'\255' (*'*) '0'-'9' ] ) *
{ let s = Lexing.lexeme lexbuf in
try
- Hashtbl.find keyword_table key:s
+ Hashtbl.find keyword_table s
with Not_found ->
IDENT s }
@@ -134,7 +134,7 @@ and string = parse
| '\\' [' ' '\010' '\013' '\009' '\026' '\012'] +
{ string lexbuf }
| '\\' ['\\' '"' 'n' 't' 'b' 'r']
- { store_string_char(char_for_backslash(Lexing.lexeme_char lexbuf pos:1));
+ { store_string_char(char_for_backslash(Lexing.lexeme_char lexbuf 1));
string lexbuf }
| '\\' ['0'-'9'] ['0'-'9'] ['0'-'9']
{ store_string_char(char_for_decimal_code lexbuf 1);
@@ -143,10 +143,10 @@ and string = parse
{ raise (Lexical_error("string not terminated")) }
| '\010'
{ incr current_line;
- store_string_char(Lexing.lexeme_char lexbuf pos:0);
+ store_string_char(Lexing.lexeme_char lexbuf 0);
string lexbuf }
| _
- { store_string_char(Lexing.lexeme_char lexbuf pos:0);
+ { store_string_char(Lexing.lexeme_char lexbuf 0);
string lexbuf }
and comment = parse