ast.ml 16 KB

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