tree.ml 6.0 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201
  1. open StdLabels
  2. let identifier = "tree"
  3. let description = "Build the AST"
  4. let is_global = false
  5. let active = ref true
  6. type context = unit
  7. let initialize = Fun.id
  8. let finalize () = []
  9. module Ast = struct
  10. type 'a literal = 'a T.literal = Text of string | Expression of 'a
  11. [@@deriving eq, show]
  12. type 'a variable = {
  13. pos : 'a;
  14. name : string;
  15. index : 'a expression option;
  16. local : bool;
  17. }
  18. [@@deriving eq, show]
  19. and 'a expression =
  20. | Integer of 'a * string
  21. | Literal of 'a * 'a expression literal list
  22. | Ident of 'a variable
  23. | BinaryOp of 'a * T.boperator * 'a expression * 'a expression
  24. | Op of 'a * T.uoperator * 'a expression
  25. | Function of 'a * T.function_ * 'a expression list
  26. [@@deriving eq, show]
  27. and 'a condition = 'a * 'a expression * 'a statement list
  28. and 'a statement =
  29. | If of {
  30. loc : 'a;
  31. then_ : 'a condition;
  32. elifs : 'a condition list;
  33. else_ : 'a statement list;
  34. }
  35. | Act of { loc : 'a; label : 'a expression; statements : 'a statement list }
  36. | Declaration of ('a * 'a variable * T.assignation_operator * 'a expression)
  37. | Expression of 'a expression
  38. | Comment of 'a
  39. | Call of 'a * T.keywords * 'a expression list
  40. | Location of 'a * string
  41. | For of {
  42. loc : 'a;
  43. variable : 'a variable;
  44. start : 'a expression;
  45. to_ : 'a expression;
  46. step : 'a expression option;
  47. statements : 'a statement list;
  48. }
  49. [@@deriving eq, show]
  50. end
  51. (** Default implementation for the expression *)
  52. module Expression : sig
  53. include S.Expression with type t' = S.pos Ast.expression
  54. val eq : (S.pos -> S.pos -> bool) -> t' -> t' -> bool
  55. val hash : (S.pos -> int) -> t' -> int
  56. val exists : f:(t' -> bool) -> t' -> bool
  57. end = struct
  58. type t = S.pos Ast.expression
  59. type t' = t
  60. let eq : (S.pos -> S.pos -> bool) -> t -> t -> bool = Ast.equal_expression
  61. (* Add a way to filter an expression *)
  62. let rec exists : f:(t -> bool) -> t -> bool =
  63. fun ~f -> function
  64. | BinaryOp (_, _, o1, o2) as op -> f op || exists ~f o1 || exists ~f o2
  65. | Op (_, _, expr) as op -> f op || exists ~f expr
  66. | Function (_, _, exprs) as fn -> f fn || List.exists exprs ~f:(exists ~f)
  67. | Literal (_, litts) as litt ->
  68. f litt
  69. || List.exists litts ~f:(function
  70. | T.Text _ -> false
  71. | T.Expression ex -> exists ~f ex)
  72. | Ident { index; _ } as ident -> (
  73. f ident
  74. || match index with None -> false | Some expr -> exists ~f expr)
  75. | Integer _ as int -> f int
  76. let rec hash : (S.pos -> int) -> t -> int =
  77. fun f -> function
  78. | Integer (pos, v) -> Hashtbl.hash (f pos, v)
  79. | Literal (pos, l) ->
  80. let litt = List.map ~f:(T.map_litteral ~f:(hash f)) l in
  81. Hashtbl.hash (f pos, litt)
  82. | Ident { pos; name; index; _ } ->
  83. Hashtbl.hash (f pos, name, Option.map (hash f) index)
  84. | BinaryOp (pos, op, o1, o2) ->
  85. Hashtbl.hash (f pos, op, hash f o1, hash f o2)
  86. | Op (pos, op, o1) -> Hashtbl.hash (f pos, op, hash f o1)
  87. | Function (pos, name, args) ->
  88. Hashtbl.hash (f pos, name, List.map ~f:(hash f) args)
  89. let v : t -> t' = fun t -> t
  90. let integer : S.pos -> string -> t = fun pos i -> Ast.Integer (pos, i)
  91. let literal : S.pos -> t T.literal list -> t =
  92. fun pos l -> Ast.Literal (pos, l)
  93. let function_ : S.pos -> T.function_ -> t list -> t =
  94. fun pos name args -> Ast.Function (pos, name, args)
  95. let uoperator : S.pos -> T.uoperator -> t -> t =
  96. fun pos op expression -> Ast.Op (pos, op, expression)
  97. let boperator : S.pos -> T.boperator -> t -> t -> t =
  98. fun pos op op1 op2 ->
  99. let op1 = op1 and op2 = op2 in
  100. Ast.BinaryOp (pos, op, op1, op2)
  101. let ident : (S.pos, t) S.variable -> t =
  102. fun { pos; name; index; local } ->
  103. let index = Option.map (fun i -> i) index in
  104. Ast.Ident { pos; name; index; local }
  105. end
  106. module Instruction :
  107. S.Instruction
  108. with type t' = S.pos Ast.statement
  109. and type expression = Expression.t' = struct
  110. type t = S.pos Ast.statement
  111. type t' = t
  112. type expression = Expression.t'
  113. let v : t -> t' = fun t -> t
  114. let call : S.pos -> T.keywords -> Expression.t' list -> t =
  115. fun pos name args -> Ast.Call (pos, name, args)
  116. let location : S.pos -> string -> t =
  117. fun loc label -> Ast.Location (loc, label)
  118. let comment : S.pos -> t = fun pos -> Ast.Comment pos
  119. let expression : Expression.t' -> t = fun expr -> Ast.Expression expr
  120. let if_ :
  121. S.pos ->
  122. (Expression.t', t) S.clause ->
  123. elifs:(Expression.t', t) S.clause list ->
  124. else_:(S.pos * t list) option ->
  125. t =
  126. fun pos predicate ~elifs ~else_ ->
  127. let clause (pos, expr, repr) = (pos, expr, repr) in
  128. let elifs = List.map ~f:clause elifs
  129. and else_ =
  130. match else_ with None -> [] | Some (_, instructions) -> instructions
  131. in
  132. Ast.If { loc = pos; then_ = clause predicate; elifs; else_ }
  133. let act : S.pos -> label:Expression.t' -> t list -> t =
  134. fun pos ~label statements -> Ast.Act { loc = pos; label; statements }
  135. let assign :
  136. S.pos ->
  137. (S.pos, Expression.t') S.variable ->
  138. T.assignation_operator ->
  139. Expression.t' ->
  140. t =
  141. fun pos_loc { pos; name; index; local } op expr ->
  142. (*let index = Option.map (fun i -> fst @@ Expression.observe (i [])) index*)
  143. Ast.Declaration (pos_loc, { pos; name; index; local }, op, expr)
  144. let for_ :
  145. S.pos ->
  146. (S.pos, Expression.t') S.variable ->
  147. start:Expression.t' ->
  148. to_:Expression.t' ->
  149. step:Expression.t' option ->
  150. t list ->
  151. t =
  152. fun loc variable ~start ~to_ ~step statements ->
  153. let variable =
  154. Ast.
  155. {
  156. pos = variable.S.pos;
  157. name = variable.S.name;
  158. index = variable.S.index;
  159. local = variable.S.local;
  160. }
  161. in
  162. Ast.For { loc; variable; start; to_; step; statements }
  163. end
  164. module Location = struct
  165. type t = S.pos * S.pos Ast.statement list
  166. let v _ = []
  167. let location : unit -> S.pos -> Instruction.t' list -> t =
  168. fun () pos block -> (pos, block)
  169. end