ast.ml 23 KB

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