ast.ml 23 KB

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