Skip to content

Commit fd3b940

Browse files
committed
Fix integer literal handling to 64bit large integers.
Signed-off-by: Cong Wang <cwang@multikernel.io>
1 parent 65c013b commit fd3b940

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

50 files changed

+884
-647
lines changed

src/ast.ml

Lines changed: 78 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -55,14 +55,8 @@ type map_flag =
5555
| Wronly (* BPF_F_WRONLY *)
5656
| Clone (* BPF_F_CLONE *)
5757

58-
(** Type definitions for structs, enums, and type aliases *)
59-
type type_def =
60-
| StructDef of string * (string * bpf_type) list
61-
| EnumDef of string * (string * int option) list
62-
| TypeAlias of string * bpf_type
63-
6458
(** BPF type system with extended type definitions *)
65-
and bpf_type =
59+
type bpf_type =
6660
(* Primitive types *)
6761
| U8 | U16 | U32 | U64 | I8 | I16 | I32 | I64 | Bool | Char | Void
6862
| Str of int (* Fixed-size string str<N> *)
@@ -113,9 +107,82 @@ type map_declaration = {
113107
map_pos: position;
114108
}
115109

110+
(** Integer value with proper signed/unsigned distinction *)
111+
type integer_value =
112+
| Signed64 of Int64.t
113+
| Unsigned64 of Int64.t (* Stored in Int64.t but interpreted as unsigned *)
114+
115+
(** Helper module for working with integer values elegantly *)
116+
module IntegerValue = struct
117+
let of_string s =
118+
try
119+
(* Try signed parsing first *)
120+
Signed64 (Int64.of_string s)
121+
with Failure _ ->
122+
(* Handle unsigned 64-bit integers that exceed signed range *)
123+
try
124+
(* Parse as unsigned using custom logic for large values *)
125+
let parse_uint64 str =
126+
let len = String.length str in
127+
let rec aux i acc =
128+
if i >= len then acc
129+
else
130+
let digit = Char.code str.[i] - Char.code '0' in
131+
if digit < 0 || digit > 9 then
132+
failwith "Invalid digit"
133+
else
134+
let new_acc = Int64.add (Int64.mul acc 10L) (Int64.of_int digit) in
135+
aux (i + 1) new_acc
136+
in
137+
aux 0 0L
138+
in
139+
let uint64_val = parse_uint64 s in
140+
Unsigned64 uint64_val
141+
with _ ->
142+
failwith ("Invalid integer literal: " ^ s)
143+
144+
let to_string = function
145+
| Signed64 i -> Int64.to_string i
146+
| Unsigned64 i ->
147+
(* Handle unsigned 64-bit values correctly *)
148+
if Int64.compare i 0L >= 0 then
149+
Int64.to_string i
150+
else
151+
(* For negative Int64.t values representing large unsigned numbers *)
152+
(* Use Printf to format as unsigned *)
153+
Printf.sprintf "%Lu" i
154+
155+
let to_c_literal = function
156+
| Signed64 i -> Int64.to_string i ^ "LL"
157+
| Unsigned64 i ->
158+
(* Use unsigned formatting for C literals *)
159+
if Int64.compare i 0L >= 0 then
160+
Int64.to_string i ^ "ULL"
161+
else
162+
Printf.sprintf "%LuULL" i
163+
164+
let is_negative = function
165+
| Signed64 i -> Int64.compare i 0L < 0
166+
| Unsigned64 _ -> false (* Unsigned values are never conceptually negative *)
167+
168+
let to_int64 = function
169+
| Signed64 i -> i
170+
| Unsigned64 i -> i
171+
172+
let compare_with_zero = function
173+
| Signed64 i -> Int64.compare i 0L
174+
| Unsigned64 i -> if Int64.compare i 0L < 0 then 1 else Int64.compare i 0L (* Handle unsigned wrap-around *)
175+
end
176+
177+
(** Type definitions for structs, enums, and type aliases *)
178+
type type_def =
179+
| StructDef of string * (string * bpf_type) list
180+
| EnumDef of string * (string * integer_value option) list
181+
| TypeAlias of string * bpf_type
182+
116183
(** Literal values *)
117184
type literal =
118-
| IntLit of int * string option (* value * original_representation *)
185+
| IntLit of integer_value * string option (* value * original_representation *)
119186
| StringLit of string
120187
| CharLit of char
121188
| BoolLit of bool
@@ -649,10 +716,10 @@ let rec string_of_bpf_type = function
649716
| Null -> "null"
650717

651718
let rec string_of_literal = function
652-
| IntLit (i, original_opt) ->
719+
| IntLit (int_val, original_opt) ->
653720
(match original_opt with
654721
| Some orig -> orig (* Use original format if available *)
655-
| None -> string_of_int i)
722+
| None -> IntegerValue.to_string int_val)
656723
| StringLit s -> Printf.sprintf "\"%s\"" s
657724
| CharLit c -> Printf.sprintf "'%c'" c
658725
| BoolLit b -> string_of_bool b
@@ -848,7 +915,7 @@ let string_of_declaration = function
848915
(String.concat ",\n " (List.map (fun (name, opt) ->
849916
match opt with
850917
| None -> name
851-
| Some v -> Printf.sprintf "%s = %d" name v) values))
918+
| Some v -> Printf.sprintf "%s = %s" name (IntegerValue.to_string v)) values))
852919
| TypeAlias (name, typ) ->
853920
Printf.sprintf "type %s = %s;" name (string_of_bpf_type typ)
854921
in

src/ebpf_c_codegen.ml

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -654,7 +654,7 @@ let collect_enum_definitions ?symbol_table ir_multi_prog =
654654
match symbol.Symbol_table.kind with
655655
| Symbol_table.TypeDef (Ast.EnumDef (enum_name, enum_values)) ->
656656
let processed_values = List.map (fun (const_name, opt_value) ->
657-
(const_name, Option.value ~default:0 opt_value)
657+
(const_name, Option.value ~default:(Ast.Signed64 0L) opt_value)
658658
) enum_values in
659659
Hashtbl.replace enum_map enum_name processed_values
660660
| _ -> ()
@@ -669,7 +669,7 @@ let generate_enum_definition ctx enum_name enum_values =
669669
increase_indent ctx;
670670
let value_count = List.length enum_values in
671671
List.iteri (fun i (const_name, value) ->
672-
let line = sprintf "%s = %d%s" const_name value (if i = value_count - 1 then "" else ",") in
672+
let line = sprintf "%s = %s%s" const_name (Ast.IntegerValue.to_string value) (if i = value_count - 1 then "" else ",") in
673673
emit_line ctx line
674674
) enum_values;
675675
decrease_indent ctx;
@@ -1491,7 +1491,7 @@ let generate_global_variables ctx global_variables =
14911491
(match original_opt with
14921492
| Some orig when String.contains orig 'x' || String.contains orig 'X' -> orig
14931493
| Some orig when String.contains orig 'b' || String.contains orig 'B' -> orig
1494-
| _ -> string_of_int i)
1494+
| _ -> Ast.IntegerValue.to_string i)
14951495
| IRLiteral (Ast.BoolLit b) -> if b then "1" else "0"
14961496
| IRLiteral (Ast.StringLit s) -> sprintf "\"%s\"" s
14971497
| IRLiteral (Ast.CharLit c) -> sprintf "'%c'" c
@@ -1565,7 +1565,7 @@ let rec generate_c_value ?(auto_deref_map_access=false) ctx ir_val =
15651565
(match original_opt with
15661566
| Some orig when String.contains orig 'x' || String.contains orig 'X' -> orig
15671567
| Some orig when String.contains orig 'b' || String.contains orig 'B' -> orig
1568-
| _ -> string_of_int i)
1568+
| _ -> Ast.IntegerValue.to_string i)
15691569
| IRLiteral (BoolLit b) -> if b then "1" else "0"
15701570
| IRLiteral (CharLit c) -> sprintf "'%c'" c
15711571
| IRLiteral (NullLit) -> "NULL"
@@ -1593,7 +1593,7 @@ let rec generate_c_value ?(auto_deref_map_access=false) ctx ir_val =
15931593
| ZeroArray -> "{0}" (* Empty array initialization *)
15941594
| FillArray fill_lit ->
15951595
let fill_str = match fill_lit with
1596-
| Ast.IntLit (i, _) -> string_of_int i
1596+
| Ast.IntLit (i, _) -> Ast.IntegerValue.to_string i
15971597
| Ast.BoolLit b -> if b then "1" else "0"
15981598
| Ast.CharLit c -> sprintf "'%c'" c
15991599
| Ast.StringLit s -> sprintf "\"%s\"" s
@@ -1605,7 +1605,7 @@ let rec generate_c_value ?(auto_deref_map_access=false) ctx ir_val =
16051605
| ExplicitArray elements ->
16061606
let element_strings = List.map (fun elem ->
16071607
match elem with
1608-
| Ast.IntLit (i, _) -> string_of_int i
1608+
| Ast.IntLit (i, _) -> Ast.IntegerValue.to_string i
16091609
| Ast.BoolLit b -> if b then "1" else "0"
16101610
| Ast.CharLit c -> sprintf "'%c'" c
16111611
| Ast.StringLit s -> sprintf "\"%s\"" s
@@ -2305,7 +2305,7 @@ let generate_ringbuf_operation ctx ringbuf_val op =
23052305
(** Helper function to convert AST expressions to C code for bpf_loop callbacks *)
23062306
let rec generate_ast_expr_to_c (expr : Ast.expr) counter_var =
23072307
match expr.Ast.expr_desc with
2308-
| Ast.Literal (Ast.IntLit (i, _)) -> string_of_int i
2308+
| Ast.Literal (Ast.IntLit (i, _)) -> Ast.IntegerValue.to_string i
23092309
| Ast.Literal (Ast.BoolLit b) -> if b then "true" else "false"
23102310
| Ast.Identifier name when name = "i" -> counter_var (* Map loop variable to counter *)
23112311
| Ast.Identifier name -> name
@@ -2880,13 +2880,13 @@ let rec generate_c_instruction ctx ir_instr =
28802880
let ret_str = match ret_val.value_desc with
28812881
(* Use context-specific action constant mapping *)
28822882
| IRLiteral (IntLit (i, _)) when ret_val.val_type = IRAction Xdp_actionType ->
2883-
(match Kernelscript_context.Context_codegen.map_context_action_constant "xdp" i with
2883+
(match Kernelscript_context.Context_codegen.map_context_action_constant "xdp" (Int64.to_int (Ast.IntegerValue.to_int64 i)) with
28842884
| Some action -> action
2885-
| None -> string_of_int i)
2885+
| None -> Ast.IntegerValue.to_string i)
28862886
| IRLiteral (IntLit (i, _)) when ret_val.val_type = IRAction TcActionType ->
2887-
(match Kernelscript_context.Context_codegen.map_context_action_constant "tc" i with
2887+
(match Kernelscript_context.Context_codegen.map_context_action_constant "tc" (Int64.to_int (Ast.IntegerValue.to_int64 i)) with
28882888
| Some action -> action
2889-
| None -> string_of_int i)
2889+
| None -> Ast.IntegerValue.to_string i)
28902890
| IRMapAccess (_, _, _) ->
28912891
(* For map access in return position, auto-dereference to return the value *)
28922892
generate_c_value ~auto_deref_map_access:true ctx ret_val

src/evaluator.ml

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ type runtime_value =
3232
| ArrayValue of runtime_value array
3333
| PointerValue of int (* Address representation *)
3434
| StructValue of (string * runtime_value) list
35-
| EnumValue of string * int
35+
| EnumValue of string * Int64.t
3636
| MapHandle of string (* Map identifier *)
3737
| ContextValue of string * (string * runtime_value) list
3838
| NullValue (* Simple null value representation *)
@@ -318,7 +318,7 @@ let rec string_of_runtime_value = function
318318
| StructValue fields ->
319319
"{" ^ String.concat "; " (List.map (fun (name, value) ->
320320
name ^ " = " ^ string_of_runtime_value value) fields) ^ "}"
321-
| EnumValue (name, value) -> Printf.sprintf "%s(%d)" name value
321+
| EnumValue (name, value) -> Printf.sprintf "%s(%Ld)" name value
322322
| MapHandle name -> Printf.sprintf "map<%s>" name
323323
| ContextValue (ctx_type, fields) ->
324324
Printf.sprintf "%s_context{%s}" ctx_type
@@ -330,7 +330,7 @@ let rec string_of_runtime_value = function
330330

331331
(** Convert literal to runtime value *)
332332
let runtime_value_of_literal = function
333-
| IntLit (i, _) -> IntValue i
333+
| IntLit (i, _) -> IntValue (Int64.to_int (Ast.IntegerValue.to_int64 i))
334334
| StringLit s -> StringValue s
335335
| CharLit c -> CharValue c
336336
| BoolLit b -> BoolValue b
@@ -354,7 +354,7 @@ let is_truthy_value rv =
354354
| StringValue s -> String.length s > 0 (* empty string is falsy, non-empty is truthy *)
355355
| CharValue c -> c <> '\000' (* null character is falsy, others truthy *)
356356
| PointerValue addr -> addr <> 0 (* null pointer is falsy, non-null is truthy *)
357-
| EnumValue (_, value) -> value <> 0 (* enum based on numeric value *)
357+
| EnumValue (_, value) -> Int64.compare value 0L <> 0 (* enum based on numeric value *)
358358
| MapHandle _ -> true (* maps are always truthy *)
359359
| ContextValue (_, _) -> true (* context values are always truthy *)
360360
| NullValue -> false (* null is always falsy *)
@@ -643,7 +643,7 @@ and eval_expression ctx expr =
643643
(* Look up enum constants from loaded builtin AST files *)
644644
(match Symbol_table.lookup_symbol symbol_table name with
645645
| Some { kind = Symbol_table.EnumConstant (enum_name, Some value); _ } ->
646-
EnumValue (enum_name, value)
646+
EnumValue (enum_name, Ast.IntegerValue.to_int64 value)
647647
| _ ->
648648
(* Not an enum constant, try variables *)
649649
(try
@@ -731,8 +731,8 @@ and eval_expression ctx expr =
731731
(match Symbol_table.lookup_symbol symbol_table name with
732732
| Some { kind = Symbol_table.EnumConstant (_, Some value); _ } ->
733733
(match matched_value with
734-
| EnumValue (_, matched_val) -> matched_val = value
735-
| IntValue matched_val -> matched_val = value
734+
| EnumValue (_, matched_val) -> matched_val = Ast.IntegerValue.to_int64 value
735+
| IntValue matched_val -> Int64.of_int matched_val = Ast.IntegerValue.to_int64 value
736736
| _ -> false)
737737
| _ -> false)
738738
| None -> false)

src/ir.ml

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -135,7 +135,7 @@ and ir_type =
135135
| IRPointer of ir_type * bounds_info
136136
| IRArray of ir_type * int * bounds_info
137137
| IRStruct of string * (string * ir_type) list
138-
| IREnum of string * (string * int) list
138+
| IREnum of string * (string * Ast.integer_value) list
139139
| IRResult of ir_type * ir_type
140140
| IRContext of context_type
141141
| IRAction of action_type
@@ -224,7 +224,7 @@ and ir_value_desc =
224224
| IRRegister of int
225225
| IRContextField of context_type * string
226226
| IRMapRef of string
227-
| IREnumConstant of string * string * int (* enum_name, constant_name, value *)
227+
| IREnumConstant of string * string * Ast.integer_value (* enum_name, constant_name, value *)
228228
| IRFunctionRef of string (* Function reference by name *)
229229
| IRMapAccess of string * ir_value * (ir_value_desc * ir_type) (* map_name, key, (underlying_value_desc, underlying_type) *)
230230

@@ -753,7 +753,7 @@ let rec ast_type_to_ir_type_with_context symbol_table ast_type =
753753
IRStruct (name, ir_fields)
754754
| Symbol_table.TypeDef (Ast.EnumDef (_, values)) ->
755755
let ir_values = List.map (fun (enum_name, opt_value) ->
756-
(enum_name, Option.value ~default:0 opt_value)
756+
(enum_name, Option.value ~default:(Ast.Signed64 0L) opt_value)
757757
) values in
758758
IREnum (name, ir_values)
759759
| _ -> ast_type_to_ir_type ast_type)
@@ -776,7 +776,7 @@ let rec ast_type_to_ir_type_with_context symbol_table ast_type =
776776
IRStruct (name, ir_fields)
777777
| Symbol_table.TypeDef (Ast.EnumDef (_, values)) ->
778778
let ir_values = List.map (fun (enum_name, opt_value) ->
779-
(enum_name, Option.value ~default:0 opt_value)
779+
(enum_name, Option.value ~default:(Ast.Signed64 0L) opt_value)
780780
) values in
781781
IREnum (name, ir_values)
782782
| _ -> ast_type_to_ir_type ast_type)
@@ -798,7 +798,7 @@ let rec ast_type_to_ir_type_with_context symbol_table ast_type =
798798
(match symbol.kind with
799799
| Symbol_table.TypeDef (Ast.EnumDef (_, values)) ->
800800
let ir_values = List.map (fun (enum_name, opt_value) ->
801-
(enum_name, Option.value ~default:0 opt_value)
801+
(enum_name, Option.value ~default:(Ast.Signed64 0L) opt_value)
802802
) values in
803803
IREnum (name, ir_values)
804804
| _ -> ast_type_to_ir_type ast_type)

src/ir_analysis.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -205,9 +205,9 @@ module AssignmentOptimization = struct
205205
| IRMapStore (map_val, _key_val, _value_val, _) ->
206206
let assignment = Map_assignment.{
207207
map_name = (match map_val.value_desc with IRMapRef name -> name | _ -> "unknown");
208-
key_expr = { Ast.expr_desc = Ast.Literal (IntLit (0, None)); expr_type = None; expr_pos = instr.instr_pos;
208+
key_expr = { Ast.expr_desc = Ast.Literal (IntLit (Ast.Signed64 0L, None)); expr_type = None; expr_pos = instr.instr_pos;
209209
type_checked = false; program_context = None; map_scope = None }; (* Simplified for IR analysis *)
210-
value_expr = { Ast.expr_desc = Ast.Literal (IntLit (0, None)); expr_type = None; expr_pos = instr.instr_pos;
210+
value_expr = { Ast.expr_desc = Ast.Literal (IntLit (Ast.Signed64 0L, None)); expr_type = None; expr_pos = instr.instr_pos;
211211
type_checked = false; program_context = None; map_scope = None }; (* Simplified for IR analysis *)
212212
assignment_type = DirectAssignment;
213213
assignment_pos = instr.instr_pos;

0 commit comments

Comments
 (0)