tree.ml 5.2 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168
  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 = { pos : 'a; name : string; index : 'a expression option }
  13. [@@deriving eq, show]
  14. and 'a expression =
  15. | Integer of 'a * string
  16. | Literal of 'a * 'a expression literal list
  17. | Ident of 'a variable
  18. | BinaryOp of 'a * T.boperator * 'a expression * 'a expression
  19. | Op of 'a * T.uoperator * 'a expression
  20. | Function of 'a * T.function_ * 'a expression list
  21. [@@deriving eq, show]
  22. and 'a condition = 'a * 'a expression * 'a statement list
  23. and 'a statement =
  24. | If of {
  25. loc : 'a;
  26. then_ : 'a condition;
  27. elifs : 'a condition list;
  28. else_ : 'a statement list;
  29. }
  30. | Act of { loc : 'a; label : 'a expression; statements : 'a statement list }
  31. | Declaration of ('a * 'a variable * T.assignation_operator * 'a expression)
  32. | Expression of 'a expression
  33. | Comment of 'a
  34. | Call of 'a * T.keywords * 'a expression list
  35. | Location of 'a * string
  36. [@@deriving eq, show]
  37. end
  38. (** Default implementation for the expression *)
  39. module Expression : sig
  40. include S.Expression with type t' = S.pos Ast.expression
  41. val eq : (S.pos -> S.pos -> bool) -> t' -> t' -> bool
  42. val hash : (S.pos -> int) -> t' -> int
  43. val exists : f:(t' -> bool) -> t' -> bool
  44. end = struct
  45. type t = S.pos Ast.expression
  46. type t' = t
  47. let eq : (S.pos -> S.pos -> bool) -> t -> t -> bool = Ast.equal_expression
  48. (* Add a way to filter an expression *)
  49. let rec exists : f:(t -> bool) -> t -> bool =
  50. fun ~f -> function
  51. | BinaryOp (_, _, o1, o2) as op -> f op || exists ~f o1 || exists ~f o2
  52. | Op (_, _, expr) as op -> f op || exists ~f expr
  53. | Function (_, _, exprs) as fn -> f fn || List.exists exprs ~f:(exists ~f)
  54. | Literal (_, litts) as litt ->
  55. f litt
  56. || List.exists litts ~f:(function
  57. | T.Text _ -> false
  58. | T.Expression ex -> exists ~f ex)
  59. | Ident { index; _ } as ident -> (
  60. f ident
  61. || match index with None -> false | Some expr -> exists ~f expr)
  62. | Integer _ as int -> f int
  63. let rec hash : (S.pos -> int) -> t -> int =
  64. fun f -> function
  65. | Integer (pos, v) -> Hashtbl.hash (f pos, v)
  66. | Literal (pos, l) ->
  67. let litt = List.map ~f:(T.map_litteral ~f:(hash f)) l in
  68. Hashtbl.hash (f pos, litt)
  69. | Ident { pos; name; index } ->
  70. Hashtbl.hash (f pos, name, Option.map (hash f) index)
  71. | BinaryOp (pos, op, o1, o2) ->
  72. Hashtbl.hash (f pos, op, hash f o1, hash f o2)
  73. | Op (pos, op, o1) -> Hashtbl.hash (f pos, op, hash f o1)
  74. | Function (pos, name, args) ->
  75. Hashtbl.hash (f pos, name, List.map ~f:(hash f) args)
  76. let v : t -> t' = fun t -> t
  77. let integer : S.pos -> string -> t = fun pos i -> Ast.Integer (pos, i)
  78. let literal : S.pos -> t T.literal list -> t =
  79. fun pos l -> Ast.Literal (pos, l)
  80. let function_ : S.pos -> T.function_ -> t list -> t =
  81. fun pos name args -> Ast.Function (pos, name, args)
  82. let uoperator : S.pos -> T.uoperator -> t -> t =
  83. fun pos op expression -> Ast.Op (pos, op, expression)
  84. let boperator : S.pos -> T.boperator -> t -> t -> t =
  85. fun pos op op1 op2 ->
  86. let op1 = op1 and op2 = op2 in
  87. Ast.BinaryOp (pos, op, op1, op2)
  88. let ident : (S.pos, t) S.variable -> t =
  89. fun { pos; name; index } ->
  90. let index = Option.map (fun i -> i) index in
  91. Ast.Ident { pos; name; index }
  92. end
  93. module Instruction :
  94. S.Instruction
  95. with type t' = S.pos Ast.statement
  96. and type expression = Expression.t' = struct
  97. type t = S.pos Ast.statement
  98. type t' = t
  99. type expression = Expression.t'
  100. let v : t -> t' = fun t -> t
  101. let call : S.pos -> T.keywords -> Expression.t' list -> t =
  102. fun pos name args -> Ast.Call (pos, name, args)
  103. let location : S.pos -> string -> t =
  104. fun loc label -> Ast.Location (loc, label)
  105. let comment : S.pos -> t = fun pos -> Ast.Comment pos
  106. let expression : Expression.t' -> t = fun expr -> Ast.Expression expr
  107. let if_ :
  108. S.pos ->
  109. (Expression.t', t) S.clause ->
  110. elifs:(Expression.t', t) S.clause list ->
  111. else_:(S.pos * t list) option ->
  112. t =
  113. fun pos predicate ~elifs ~else_ ->
  114. let clause (pos, expr, repr) = (pos, expr, repr) in
  115. let elifs = List.map ~f:clause elifs
  116. and else_ =
  117. match else_ with None -> [] | Some (_, instructions) -> instructions
  118. in
  119. Ast.If { loc = pos; then_ = clause predicate; elifs; else_ }
  120. let act : S.pos -> label:Expression.t' -> t list -> t =
  121. fun pos ~label statements -> Ast.Act { loc = pos; label; statements }
  122. let assign :
  123. S.pos ->
  124. (S.pos, Expression.t') S.variable ->
  125. T.assignation_operator ->
  126. Expression.t' ->
  127. t =
  128. fun pos_loc { pos; name; index } op expr ->
  129. (*let index = Option.map (fun i -> fst @@ Expression.observe (i [])) index*)
  130. Ast.Declaration (pos_loc, { pos; name; index }, op, expr)
  131. end
  132. module Location = struct
  133. type t = S.pos * S.pos Ast.statement list
  134. let v _ = []
  135. let location : unit -> S.pos -> Instruction.t' list -> t =
  136. fun () pos block -> (pos, block)
  137. end