ast.ml 14 KB

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