ast.ml 16 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722
  1. (*
  2. * Copyright (C)2005-2013 Haxe Foundation
  3. *
  4. * Permission is hereby granted, free of charge, to any person obtaining a
  5. * copy of this software and associated documentation files (the "Software"),
  6. * to deal in the Software without restriction, including without limitation
  7. * the rights to use, copy, modify, merge, publish, distribute, sublicense,
  8. * and/or sell copies of the Software, and to permit persons to whom the
  9. * Software is furnished to do so, subject to the following conditions:
  10. *
  11. * The above copyright notice and this permission notice shall be included in
  12. * all copies or substantial portions of the Software.
  13. *
  14. * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
  15. * IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
  16. * FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
  17. * AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
  18. * LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
  19. * FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER
  20. * DEALINGS IN THE SOFTWARE.
  21. *)
  22. type pos = {
  23. pfile : string;
  24. pmin : int;
  25. pmax : int;
  26. }
  27. module Meta = struct
  28. type strict_meta =
  29. | Abstract
  30. | Access
  31. | Accessor
  32. | Allow
  33. | Annotation
  34. | ArrayAccess
  35. | Ast
  36. | AutoBuild
  37. | Bind
  38. | Bitmap
  39. | Build
  40. | BuildXml
  41. | Class
  42. | ClassCode
  43. | Commutative
  44. | CompilerGenerated
  45. | CoreApi
  46. | CoreType
  47. | CppFileCode
  48. | CppNamespaceCode
  49. | CsNative
  50. | Dce
  51. | Debug
  52. | Decl
  53. | DefParam
  54. | Delegate
  55. | Depend
  56. | Deprecated
  57. | DynamicObject
  58. | Enum
  59. | EnumConstructorParam
  60. | Event
  61. | Exhaustive
  62. | Expose
  63. | Extern
  64. | FakeEnum
  65. | File
  66. | Final
  67. | FlatEnum
  68. | Font
  69. | Forward
  70. | From
  71. | FunctionCode
  72. | FunctionTailCode
  73. | Generic
  74. | GenericBuild
  75. | Getter
  76. | Hack
  77. | HaxeGeneric
  78. | HeaderClassCode
  79. | HeaderCode
  80. | HeaderNamespaceCode
  81. | HxGen
  82. | IfFeature
  83. | Impl
  84. | Include
  85. | InitPackage
  86. | Internal
  87. | IsVar
  88. | JavaNative
  89. | Keep
  90. | KeepInit
  91. | KeepSub
  92. | Meta
  93. | Macro
  94. | MaybeUsed
  95. | MergeBlock
  96. | MultiType
  97. | Native
  98. | NativeGen
  99. | NativeGeneric
  100. | NoCompletion
  101. | NoDebug
  102. | NoDoc
  103. | NoImportGlobal
  104. | NoPackageRestrict
  105. | NoStack
  106. | NotNull
  107. | NoUsing
  108. | Ns
  109. | Op
  110. | Optional
  111. | Overload
  112. | PrivateAccess
  113. | Property
  114. | Protected
  115. | Public
  116. | PublicFields
  117. | ReadOnly
  118. | RealPath
  119. | Remove
  120. | Require
  121. | RequiresAssign
  122. | ReplaceReflection
  123. | Rtti
  124. | Runtime
  125. | RuntimeValue
  126. | Setter
  127. | SkipCtor
  128. | SkipReflection
  129. | Sound
  130. | Struct
  131. | SuppressWarnings
  132. | This
  133. | Throws
  134. | To
  135. | ToString
  136. | Transient
  137. | ValueUsed
  138. | Volatile
  139. | Unbound
  140. | UnifyMinDynamic
  141. | Unreflective
  142. | Unsafe
  143. | Usage
  144. | Used
  145. | Last
  146. (* do not put any custom metadata after Last *)
  147. | Dollar of string
  148. | Custom of string
  149. let has m ml = List.exists (fun (m2,_,_) -> m = m2) ml
  150. let get m ml = List.find (fun (m2,_,_) -> m = m2) ml
  151. let to_string_ref = ref (fun _ -> assert false)
  152. let to_string (m : strict_meta) : string = !to_string_ref m
  153. end
  154. type keyword =
  155. | Function
  156. | Class
  157. | Var
  158. | If
  159. | Else
  160. | While
  161. | Do
  162. | For
  163. | Break
  164. | Continue
  165. | Return
  166. | Extends
  167. | Implements
  168. | Import
  169. | Switch
  170. | Case
  171. | Default
  172. | Static
  173. | Public
  174. | Private
  175. | Try
  176. | Catch
  177. | New
  178. | This
  179. | Throw
  180. | Extern
  181. | Enum
  182. | In
  183. | Interface
  184. | Untyped
  185. | Cast
  186. | Override
  187. | Typedef
  188. | Dynamic
  189. | Package
  190. | Inline
  191. | Using
  192. | Null
  193. | True
  194. | False
  195. | Abstract
  196. | Macro
  197. type binop =
  198. | OpAdd
  199. | OpMult
  200. | OpDiv
  201. | OpSub
  202. | OpAssign
  203. | OpEq
  204. | OpNotEq
  205. | OpGt
  206. | OpGte
  207. | OpLt
  208. | OpLte
  209. | OpAnd
  210. | OpOr
  211. | OpXor
  212. | OpBoolAnd
  213. | OpBoolOr
  214. | OpShl
  215. | OpShr
  216. | OpUShr
  217. | OpMod
  218. | OpAssignOp of binop
  219. | OpInterval
  220. | OpArrow
  221. type unop =
  222. | Increment
  223. | Decrement
  224. | Not
  225. | Neg
  226. | NegBits
  227. type constant =
  228. | Int of string
  229. | Float of string
  230. | String of string
  231. | Ident of string
  232. | Regexp of string * string
  233. type token =
  234. | Eof
  235. | Const of constant
  236. | Kwd of keyword
  237. | Comment of string
  238. | CommentLine of string
  239. | Binop of binop
  240. | Unop of unop
  241. | Semicolon
  242. | Comma
  243. | BrOpen
  244. | BrClose
  245. | BkOpen
  246. | BkClose
  247. | POpen
  248. | PClose
  249. | Dot
  250. | DblDot
  251. | Arrow
  252. | IntInterval of string
  253. | Sharp of string
  254. | Question
  255. | At
  256. | Dollar of string
  257. type unop_flag =
  258. | Prefix
  259. | Postfix
  260. type while_flag =
  261. | NormalWhile
  262. | DoWhile
  263. type type_path = {
  264. tpackage : string list;
  265. tname : string;
  266. tparams : type_param_or_const list;
  267. tsub : string option;
  268. }
  269. and type_param_or_const =
  270. | TPType of complex_type
  271. | TPExpr of expr
  272. and complex_type =
  273. | CTPath of type_path
  274. | CTFunction of complex_type list * complex_type
  275. | CTAnonymous of class_field list
  276. | CTParent of complex_type
  277. | CTExtend of type_path list * class_field list
  278. | CTOptional of complex_type
  279. and func = {
  280. f_params : type_param list;
  281. f_args : (string * bool * complex_type option * expr option) list;
  282. f_type : complex_type option;
  283. f_expr : expr option;
  284. }
  285. and expr_def =
  286. | EConst of constant
  287. | EArray of expr * expr
  288. | EBinop of binop * expr * expr
  289. | EField of expr * string
  290. | EParenthesis of expr
  291. | EObjectDecl of (string * expr) list
  292. | EArrayDecl of expr list
  293. | ECall of expr * expr list
  294. | ENew of type_path * expr list
  295. | EUnop of unop * unop_flag * expr
  296. | EVars of (string * complex_type option * expr option) list
  297. | EFunction of string option * func
  298. | EBlock of expr list
  299. | EFor of expr * expr
  300. | EIn of expr * expr
  301. | EIf of expr * expr * expr option
  302. | EWhile of expr * expr * while_flag
  303. | ESwitch of expr * (expr list * expr option * expr option) list * expr option option
  304. | ETry of expr * (string * complex_type * expr) list
  305. | EReturn of expr option
  306. | EBreak
  307. | EContinue
  308. | EUntyped of expr
  309. | EThrow of expr
  310. | ECast of expr * complex_type option
  311. | EDisplay of expr * bool
  312. | EDisplayNew of type_path
  313. | ETernary of expr * expr * expr
  314. | ECheckType of expr * complex_type
  315. | EMeta of metadata_entry * expr
  316. and expr = expr_def * pos
  317. and type_param = {
  318. tp_name : string;
  319. tp_params : type_param list;
  320. tp_constraints : complex_type list;
  321. }
  322. and documentation = string option
  323. and metadata_entry = (Meta.strict_meta * expr list * pos)
  324. and metadata = metadata_entry list
  325. and access =
  326. | APublic
  327. | APrivate
  328. | AStatic
  329. | AOverride
  330. | ADynamic
  331. | AInline
  332. | AMacro
  333. and class_field_kind =
  334. | FVar of complex_type option * expr option
  335. | FFun of func
  336. | FProp of string * string * complex_type option * expr option
  337. and class_field = {
  338. cff_name : string;
  339. cff_doc : documentation;
  340. cff_pos : pos;
  341. mutable cff_meta : metadata;
  342. mutable cff_access : access list;
  343. mutable cff_kind : class_field_kind;
  344. }
  345. type enum_flag =
  346. | EPrivate
  347. | EExtern
  348. type class_flag =
  349. | HInterface
  350. | HExtern
  351. | HPrivate
  352. | HExtends of type_path
  353. | HImplements of type_path
  354. type abstract_flag =
  355. | APrivAbstract
  356. | AFromType of complex_type
  357. | AToType of complex_type
  358. | AIsType of complex_type
  359. type enum_constructor = {
  360. ec_name : string;
  361. ec_doc : documentation;
  362. ec_meta : metadata;
  363. ec_args : (string * bool * complex_type) list;
  364. ec_pos : pos;
  365. ec_params : type_param list;
  366. ec_type : complex_type option;
  367. }
  368. type ('a,'b) definition = {
  369. d_name : string;
  370. d_doc : documentation;
  371. d_params : type_param list;
  372. d_meta : metadata;
  373. d_flags : 'a list;
  374. d_data : 'b;
  375. }
  376. type import_mode =
  377. | INormal
  378. | IAsName of string
  379. | IAll
  380. type type_def =
  381. | EClass of (class_flag, class_field list) definition
  382. | EEnum of (enum_flag, enum_constructor list) definition
  383. | ETypedef of (enum_flag, complex_type) definition
  384. | EAbstract of (abstract_flag, class_field list) definition
  385. | EImport of (string * pos) list * import_mode
  386. | EUsing of type_path
  387. type type_decl = type_def * pos
  388. type package = string list * type_decl list
  389. let is_lower_ident i =
  390. let rec loop p =
  391. match String.unsafe_get i p with
  392. | 'a'..'z' -> true
  393. | '_' -> if p + 1 < String.length i then loop (p + 1) else true
  394. | _ -> false
  395. in
  396. loop 0
  397. let pos = snd
  398. let rec is_postfix (e,_) op = match op with
  399. | Increment | Decrement -> (match e with EConst _ | EField _ | EArray _ -> true | EMeta(_,e1) -> is_postfix e1 op | _ -> false)
  400. | Not | Neg | NegBits -> false
  401. let is_prefix = function
  402. | Increment | Decrement -> true
  403. | Not | Neg | NegBits -> true
  404. let base_class_name = snd
  405. let null_pos = { pfile = "?"; pmin = -1; pmax = -1 }
  406. let punion p p2 =
  407. {
  408. pfile = p.pfile;
  409. pmin = min p.pmin p2.pmin;
  410. pmax = max p.pmax p2.pmax;
  411. }
  412. let rec punion_el el = match el with
  413. | [] ->
  414. null_pos
  415. | (_,p) :: [] ->
  416. p
  417. | (_,p) :: el ->
  418. punion p (punion_el el)
  419. let s_type_path (p,s) = match p with [] -> s | _ -> String.concat "." p ^ "." ^ s
  420. let parse_path s =
  421. match List.rev (ExtString.String.nsplit s ".") with
  422. | [] -> failwith "Invalid empty path"
  423. | x :: l -> List.rev l, x
  424. let s_escape ?(hex=true) s =
  425. let b = Buffer.create (String.length s) in
  426. for i = 0 to (String.length s) - 1 do
  427. match s.[i] with
  428. | '\n' -> Buffer.add_string b "\\n"
  429. | '\t' -> Buffer.add_string b "\\t"
  430. | '\r' -> Buffer.add_string b "\\r"
  431. | '"' -> Buffer.add_string b "\\\""
  432. | '\\' -> Buffer.add_string b "\\\\"
  433. | c when int_of_char c < 32 && hex -> Buffer.add_string b (Printf.sprintf "\\x%.2X" (int_of_char c))
  434. | c -> Buffer.add_char b c
  435. done;
  436. Buffer.contents b
  437. let s_constant = function
  438. | Int s -> s
  439. | Float s -> s
  440. | String s -> "\"" ^ s_escape s ^ "\""
  441. | Ident s -> s
  442. | Regexp (r,o) -> "~/" ^ r ^ "/"
  443. let s_access = function
  444. | APublic -> "public"
  445. | APrivate -> "private"
  446. | AStatic -> "static"
  447. | AOverride -> "override"
  448. | ADynamic -> "dynamic"
  449. | AInline -> "inline"
  450. | AMacro -> "macro"
  451. let s_keyword = function
  452. | Function -> "function"
  453. | Class -> "class"
  454. | Static -> "static"
  455. | Var -> "var"
  456. | If -> "if"
  457. | Else -> "else"
  458. | While -> "while"
  459. | Do -> "do"
  460. | For -> "for"
  461. | Break -> "break"
  462. | Return -> "return"
  463. | Continue -> "continue"
  464. | Extends -> "extends"
  465. | Implements -> "implements"
  466. | Import -> "import"
  467. | Switch -> "switch"
  468. | Case -> "case"
  469. | Default -> "default"
  470. | Private -> "private"
  471. | Public -> "public"
  472. | Try -> "try"
  473. | Catch -> "catch"
  474. | New -> "new"
  475. | This -> "this"
  476. | Throw -> "throw"
  477. | Extern -> "extern"
  478. | Enum -> "enum"
  479. | In -> "in"
  480. | Interface -> "interface"
  481. | Untyped -> "untyped"
  482. | Cast -> "cast"
  483. | Override -> "override"
  484. | Typedef -> "typedef"
  485. | Dynamic -> "dynamic"
  486. | Package -> "package"
  487. | Inline -> "inline"
  488. | Using -> "using"
  489. | Null -> "null"
  490. | True -> "true"
  491. | False -> "false"
  492. | Abstract -> "abstract"
  493. | Macro -> "macro"
  494. let rec s_binop = function
  495. | OpAdd -> "+"
  496. | OpMult -> "*"
  497. | OpDiv -> "/"
  498. | OpSub -> "-"
  499. | OpAssign -> "="
  500. | OpEq -> "=="
  501. | OpNotEq -> "!="
  502. | OpGte -> ">="
  503. | OpLte -> "<="
  504. | OpGt -> ">"
  505. | OpLt -> "<"
  506. | OpAnd -> "&"
  507. | OpOr -> "|"
  508. | OpXor -> "^"
  509. | OpBoolAnd -> "&&"
  510. | OpBoolOr -> "||"
  511. | OpShr -> ">>"
  512. | OpUShr -> ">>>"
  513. | OpShl -> "<<"
  514. | OpMod -> "%"
  515. | OpAssignOp op -> s_binop op ^ "="
  516. | OpInterval -> "..."
  517. | OpArrow -> "=>"
  518. let s_unop = function
  519. | Increment -> "++"
  520. | Decrement -> "--"
  521. | Not -> "!"
  522. | Neg -> "-"
  523. | NegBits -> "~"
  524. let s_token = function
  525. | Eof -> "<end of file>"
  526. | Const c -> s_constant c
  527. | Kwd k -> s_keyword k
  528. | Comment s -> "/*"^s^"*/"
  529. | CommentLine s -> "//"^s
  530. | Binop o -> s_binop o
  531. | Unop o -> s_unop o
  532. | Semicolon -> ";"
  533. | Comma -> ","
  534. | BkOpen -> "["
  535. | BkClose -> "]"
  536. | BrOpen -> "{"
  537. | BrClose -> "}"
  538. | POpen -> "("
  539. | PClose -> ")"
  540. | Dot -> "."
  541. | DblDot -> ":"
  542. | Arrow -> "->"
  543. | IntInterval s -> s ^ "..."
  544. | Sharp s -> "#" ^ s
  545. | Question -> "?"
  546. | At -> "@"
  547. | Dollar v -> "$" ^ v
  548. let unescape s =
  549. let b = Buffer.create 0 in
  550. let rec loop esc i =
  551. if i = String.length s then
  552. ()
  553. else
  554. let c = s.[i] in
  555. if esc then begin
  556. let inext = ref (i + 1) in
  557. (match c with
  558. | 'n' -> Buffer.add_char b '\n'
  559. | 'r' -> Buffer.add_char b '\r'
  560. | 't' -> Buffer.add_char b '\t'
  561. | '"' | '\'' | '\\' -> Buffer.add_char b c
  562. | '0'..'3' ->
  563. let c = (try char_of_int (int_of_string ("0o" ^ String.sub s i 3)) with _ -> raise Exit) in
  564. Buffer.add_char b c;
  565. inext := !inext + 2;
  566. | 'x' ->
  567. let c = (try char_of_int (int_of_string ("0x" ^ String.sub s (i+1) 2)) with _ -> raise Exit) in
  568. Buffer.add_char b c;
  569. inext := !inext + 2;
  570. | 'u' ->
  571. let (u, a) =
  572. (try
  573. (int_of_string ("0x" ^ String.sub s (i+1) 4), 4)
  574. with
  575. _ -> try
  576. assert (s.[i+1] = '{');
  577. let l = String.index_from s (i+3) '}' - (i+2) in
  578. let u = int_of_string ("0x" ^ String.sub s (i+2) l) in
  579. assert (u <= 0x10FFFF);
  580. (u, l+2)
  581. with _ -> raise Exit) in
  582. let ub = UTF8.Buf.create 0 in
  583. UTF8.Buf.add_char ub (UChar.uchar_of_int u);
  584. Buffer.add_string b (UTF8.Buf.contents ub);
  585. inext := !inext + a;
  586. | _ ->
  587. raise Exit);
  588. loop false !inext;
  589. end else
  590. match c with
  591. | '\\' -> loop true (i + 1)
  592. | c ->
  593. Buffer.add_char b c;
  594. loop false (i + 1)
  595. in
  596. loop false 0;
  597. Buffer.contents b
  598. let map_expr loop (e,p) =
  599. let opt f o =
  600. match o with None -> None | Some v -> Some (f v)
  601. in
  602. let rec tparam = function
  603. | TPType t -> TPType (ctype t)
  604. | TPExpr e -> TPExpr (loop e)
  605. and cfield f =
  606. { f with cff_kind = (match f.cff_kind with
  607. | FVar (t,e) -> FVar (opt ctype t, opt loop e)
  608. | FFun f -> FFun (func f)
  609. | FProp (get,set,t,e) -> FProp (get,set,opt ctype t,opt loop e))
  610. }
  611. and ctype = function
  612. | CTPath t -> CTPath (tpath t)
  613. | CTFunction (cl,c) -> CTFunction (List.map ctype cl, ctype c)
  614. | CTAnonymous fl -> CTAnonymous (List.map cfield fl)
  615. | CTParent t -> CTParent (ctype t)
  616. | CTExtend (tl,fl) -> CTExtend (List.map tpath tl, List.map cfield fl)
  617. | CTOptional t -> CTOptional (ctype t)
  618. and tparamdecl t =
  619. { tp_name = t.tp_name; tp_constraints = List.map ctype t.tp_constraints; tp_params = List.map tparamdecl t.tp_params }
  620. and func f =
  621. {
  622. f_params = List.map tparamdecl f.f_params;
  623. f_args = List.map (fun (n,o,t,e) -> n,o,opt ctype t,opt loop e) f.f_args;
  624. f_type = opt ctype f.f_type;
  625. f_expr = opt loop f.f_expr;
  626. }
  627. and tpath t = { t with tparams = List.map tparam t.tparams }
  628. in
  629. let e = (match e with
  630. | EConst _ -> e
  631. | EArray (e1,e2) -> EArray (loop e1, loop e2)
  632. | EBinop (op,e1,e2) -> EBinop (op,loop e1, loop e2)
  633. | EField (e,f) -> EField (loop e, f)
  634. | EParenthesis e -> EParenthesis (loop e)
  635. | EObjectDecl fl -> EObjectDecl (List.map (fun (f,e) -> f,loop e) fl)
  636. | EArrayDecl el -> EArrayDecl (List.map loop el)
  637. | ECall (e,el) -> ECall (loop e, List.map loop el)
  638. | ENew (t,el) -> ENew (tpath t,List.map loop el)
  639. | EUnop (op,f,e) -> EUnop (op,f,loop e)
  640. | EVars vl -> EVars (List.map (fun (n,t,eo) -> n,opt ctype t,opt loop eo) vl)
  641. | EFunction (n,f) -> EFunction (n,func f)
  642. | EBlock el -> EBlock (List.map loop el)
  643. | EFor (e1,e2) -> EFor (loop e1, loop e2)
  644. | EIn (e1,e2) -> EIn (loop e1, loop e2)
  645. | EIf (e,e1,e2) -> EIf (loop e, loop e1, opt loop e2)
  646. | EWhile (econd,e,f) -> EWhile (loop econd, loop e, f)
  647. | ESwitch (e,cases,def) -> ESwitch (loop e, List.map (fun (el,eg,e) -> List.map loop el, opt loop eg, opt loop e) cases, opt (opt loop) def)
  648. | ETry (e, catches) -> ETry (loop e, List.map (fun (n,t,e) -> n,ctype t,loop e) catches)
  649. | EReturn e -> EReturn (opt loop e)
  650. | EBreak -> EBreak
  651. | EContinue -> EContinue
  652. | EUntyped e -> EUntyped (loop e)
  653. | EThrow e -> EThrow (loop e)
  654. | ECast (e,t) -> ECast (loop e,opt ctype t)
  655. | EDisplay (e,f) -> EDisplay (loop e,f)
  656. | EDisplayNew t -> EDisplayNew (tpath t)
  657. | ETernary (e1,e2,e3) -> ETernary (loop e1,loop e2,loop e3)
  658. | ECheckType (e,t) -> ECheckType (loop e, ctype t)
  659. | EMeta (m,e) -> EMeta(m, loop e)
  660. ) in
  661. (e,p)
  662. let rec s_expr (e,_) =
  663. match e with
  664. | EConst c -> s_constant c
  665. | EParenthesis e -> "(" ^ (s_expr e) ^ ")"
  666. | EArrayDecl el -> "[" ^ (String.concat "," (List.map s_expr el)) ^ "]"
  667. | EObjectDecl fl -> "{" ^ (String.concat "," (List.map (fun (n,e) -> n ^ ":" ^ (s_expr e)) fl)) ^ "}"
  668. | EBinop (op,e1,e2) -> s_expr e1 ^ s_binop op ^ s_expr e2
  669. | _ -> "'???'"