ast.ml 23 KB

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