jsffi.nim 18 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511
  1. #
  2. #
  3. # Nim's Runtime Library
  4. # (c) Copyright 2017 Nim Authors
  5. #
  6. # See the file "copying.txt", included in this
  7. # distribution, for details about the copyright.
  8. #
  9. ## This Module implements types and macros to facilitate the wrapping of, and
  10. ## interaction with JavaScript libraries. Using the provided types ``JsObject``
  11. ## and ``JsAssoc`` together with the provided macros allows for smoother
  12. ## interfacing with JavaScript, allowing for example quick and easy imports of
  13. ## JavaScript variables:
  14. ##
  15. ## .. code-block:: nim
  16. ##
  17. ## # Here, we are using jQuery for just a few calls and do not want to wrap the
  18. ## # whole library:
  19. ##
  20. ## # import the document object and the console
  21. ## var document {. importc, nodecl .}: JsObject
  22. ## var console {. importc, nodecl .}: JsObject
  23. ## # import the "$" function
  24. ## proc jq(selector: JsObject): JsObject {. importcpp: "$(#)" .}
  25. ##
  26. ## # Use jQuery to make the following code run, after the document is ready.
  27. ## # This uses an experimental ``.()`` operator for ``JsObject``, to emit
  28. ## # JavaScript calls, when no corresponding proc exists for ``JsObject``.
  29. ## proc main =
  30. ## jq(document).ready(proc() =
  31. ## console.log("Hello JavaScript!")
  32. ## )
  33. ##
  34. when not defined(js) and not defined(nimdoc) and not defined(nimsuggest):
  35. {.fatal: "Module jsFFI is designed to be used with the JavaScript backend.".}
  36. import macros, tables
  37. const
  38. setImpl = "#[#] = #"
  39. getImpl = "#[#]"
  40. var
  41. mangledNames {. compileTime .} = initTable[string, string]()
  42. nameCounter {. compileTime .} = 0
  43. proc validJsName(name: string): bool =
  44. result = true
  45. const reservedWords = ["break", "case", "catch", "class", "const", "continue",
  46. "debugger", "default", "delete", "do", "else", "export", "extends",
  47. "finally", "for", "function", "if", "import", "in", "instanceof", "new",
  48. "return", "super", "switch", "this", "throw", "try", "typeof", "var",
  49. "void", "while", "with", "yield", "enum", "implements", "interface",
  50. "let", "package", "private", "protected", "public", "static", "await",
  51. "abstract", "boolean", "byte", "char", "double", "final", "float", "goto",
  52. "int", "long", "native", "short", "synchronized", "throws", "transient",
  53. "volatile", "null", "true", "false"]
  54. case name
  55. of reservedWords: return false
  56. else: discard
  57. if name[0] notin {'A'..'Z','a'..'z','_','$'}: return false
  58. for chr in name:
  59. if chr notin {'A'..'Z','a'..'z','_','$','0'..'9'}:
  60. return false
  61. template mangleJsName(name: cstring): cstring =
  62. inc nameCounter
  63. "mangledName" & $nameCounter
  64. # only values that can be mapped 1 to 1 with cstring should be keys: they have an injective function with cstring
  65. proc toJsKey*[T: SomeInteger](text: cstring, t: type T): T {.importcpp: "parseInt(#)".}
  66. proc toJsKey*[T: enum](text: cstring, t: type T): T =
  67. T(text.toJsKey(int))
  68. proc toJsKey*(text: cstring, t: type cstring): cstring =
  69. text
  70. proc toJsKey*[T: SomeFloat](text: cstring, t: type T): T {.importcpp: "parseFloat(#)".}
  71. type
  72. JsKey* = concept a, type T
  73. cstring.toJsKey(T) is type(a)
  74. JsObject* = ref object of JsRoot
  75. ## Dynamically typed wrapper around a JavaScript object.
  76. JsAssoc*[K: JsKey, V] = ref object of JsRoot
  77. ## Statically typed wrapper around a JavaScript object.
  78. js* = JsObject
  79. var
  80. jsArguments* {.importc: "arguments", nodecl}: JsObject
  81. ## JavaScript's arguments pseudo-variable
  82. jsNull* {.importc: "null", nodecl.}: JsObject
  83. ## JavaScript's null literal
  84. jsUndefined* {.importc: "undefined", nodecl.}: JsObject
  85. ## JavaScript's undefined literal
  86. jsDirname* {.importc: "__dirname", nodecl.}: cstring
  87. ## JavaScript's __dirname pseudo-variable
  88. jsFilename* {.importc: "__filename", nodecl.}: cstring
  89. ## JavaScript's __filename pseudo-variable
  90. # Exceptions
  91. type
  92. JsError* {.importc: "Error".} = object of JsRoot
  93. message*: cstring
  94. JsEvalError* {.importc: "EvalError".} = object of JsError
  95. JsRangeError* {.importc: "RangeError".} = object of JsError
  96. JsReferenceError* {.importc: "ReferenceError".} = object of JsError
  97. JsSyntaxError* {.importc: "SyntaxError".} = object of JsError
  98. JsTypeError* {.importc: "TypeError".} = object of JsError
  99. JsURIError* {.importc: "URIError".} = object of JsError
  100. # New
  101. proc newJsObject*: JsObject {. importcpp: "{@}" .}
  102. ## Creates a new empty JsObject
  103. proc newJsAssoc*[K: JsKey, V]: JsAssoc[K, V] {. importcpp: "{@}" .}
  104. ## Creates a new empty JsAssoc with key type `K` and value type `V`.
  105. # Checks
  106. proc hasOwnProperty*(x: JsObject, prop: cstring): bool
  107. {. importcpp: "#.hasOwnProperty(#)" .}
  108. ## Checks, whether `x` has a property of name `prop`.
  109. proc jsTypeOf*(x: JsObject): cstring {. importcpp: "typeof(#)" .}
  110. ## Returns the name of the JsObject's JavaScript type as a cstring.
  111. proc jsNew*(x: auto): JsObject {.importcpp: "(new #)".}
  112. ## Turns a regular function call into an invocation of the
  113. ## JavaScript's `new` operator
  114. proc jsDelete*(x: auto): JsObject {.importcpp: "(delete #)".}
  115. ## JavaScript's `delete` operator
  116. proc require*(module: cstring): JsObject {.importc.}
  117. ## JavaScript's `require` function
  118. # Conversion to and from JsObject
  119. proc to*(x: JsObject, T: typedesc): T {. importcpp: "(#)" .}
  120. ## Converts a JsObject `x` to type `T`.
  121. proc toJs*[T](val: T): JsObject {. importcpp: "(#)" .}
  122. ## Converts a value of any type to type JsObject
  123. template toJs*(s: string): JsObject = cstring(s).toJs
  124. macro jsFromAst*(n: untyped): untyped =
  125. result = n
  126. if n.kind == nnkStmtList:
  127. result = newProc(procType = nnkDo, body = result)
  128. return quote: toJs(`result`)
  129. proc `&`*(a, b: cstring): cstring {.importcpp: "(# + #)".}
  130. ## Concatenation operator for JavaScript strings
  131. proc `+` *(x, y: JsObject): JsObject {. importcpp: "(# + #)" .}
  132. proc `-` *(x, y: JsObject): JsObject {. importcpp: "(# - #)" .}
  133. proc `*` *(x, y: JsObject): JsObject {. importcpp: "(# * #)" .}
  134. proc `/` *(x, y: JsObject): JsObject {. importcpp: "(# / #)" .}
  135. proc `%` *(x, y: JsObject): JsObject {. importcpp: "(# % #)" .}
  136. proc `+=` *(x, y: JsObject): JsObject {. importcpp: "(# += #)", discardable .}
  137. proc `-=` *(x, y: JsObject): JsObject {. importcpp: "(# -= #)", discardable .}
  138. proc `*=` *(x, y: JsObject): JsObject {. importcpp: "(# *= #)", discardable .}
  139. proc `/=` *(x, y: JsObject): JsObject {. importcpp: "(# /= #)", discardable .}
  140. proc `%=` *(x, y: JsObject): JsObject {. importcpp: "(# %= #)", discardable .}
  141. proc `++` *(x: JsObject): JsObject {. importcpp: "(++#)" .}
  142. proc `--` *(x: JsObject): JsObject {. importcpp: "(--#)" .}
  143. proc `>` *(x, y: JsObject): JsObject {. importcpp: "(# > #)" .}
  144. proc `<` *(x, y: JsObject): JsObject {. importcpp: "(# < #)" .}
  145. proc `>=` *(x, y: JsObject): JsObject {. importcpp: "(# >= #)" .}
  146. proc `<=` *(x, y: JsObject): JsObject {. importcpp: "(# <= #)" .}
  147. proc `and`*(x, y: JsObject): JsObject {. importcpp: "(# && #)" .}
  148. proc `or` *(x, y: JsObject): JsObject {. importcpp: "(# || #)" .}
  149. proc `not`*(x: JsObject): JsObject {. importcpp: "(!#)" .}
  150. proc `in` *(x, y: JsObject): JsObject {. importcpp: "(# in #)" .}
  151. proc `[]`*(obj: JsObject, field: cstring): JsObject {. importcpp: getImpl .}
  152. ## Return the value of a property of name `field` from a JsObject `obj`.
  153. proc `[]`*(obj: JsObject, field: int): JsObject {. importcpp: getImpl .}
  154. ## Return the value of a property of name `field` from a JsObject `obj`.
  155. proc `[]=`*[T](obj: JsObject, field: cstring, val: T) {. importcpp: setImpl .}
  156. ## Set the value of a property of name `field` in a JsObject `obj` to `v`.
  157. proc `[]=`*[T](obj: JsObject, field: int, val: T) {. importcpp: setImpl .}
  158. ## Set the value of a property of name `field` in a JsObject `obj` to `v`.
  159. proc `[]`*[K: JsKey, V](obj: JsAssoc[K, V], field: K): V
  160. {. importcpp: getImpl .}
  161. ## Return the value of a property of name `field` from a JsAssoc `obj`.
  162. proc `[]=`*[K: JsKey, V](obj: JsAssoc[K, V], field: K, val: V)
  163. {. importcpp: setImpl .}
  164. ## Set the value of a property of name `field` in a JsAssoc `obj` to `v`.
  165. proc `[]`*[V](obj: JsAssoc[cstring, V], field: string): V =
  166. obj[cstring(field)]
  167. proc `[]=`*[V](obj: JsAssoc[cstring, V], field: string, val: V) =
  168. obj[cstring(field)] = val
  169. proc `==`*(x, y: JsRoot): bool {. importcpp: "(# === #)" .}
  170. ## Compare two JsObjects or JsAssocs. Be careful though, as this is comparison
  171. ## like in JavaScript, so if your JsObjects are in fact JavaScript Objects,
  172. ## and not strings or numbers, this is a *comparison of references*.
  173. {. experimental .}
  174. macro `.`*(obj: JsObject, field: untyped): JsObject =
  175. ## Experimental dot accessor (get) for type JsObject.
  176. ## Returns the value of a property of name `field` from a JsObject `x`.
  177. ##
  178. ## Example:
  179. ##
  180. ## .. code-block:: nim
  181. ##
  182. ## let obj = newJsObject()
  183. ## obj.a = 20
  184. ## console.log(obj.a) # puts 20 onto the console.
  185. if validJsName($field):
  186. let importString = "#." & $field
  187. result = quote do:
  188. proc helper(o: JsObject): JsObject
  189. {. importcpp: `importString`, gensym .}
  190. helper(`obj`)
  191. else:
  192. if not mangledNames.hasKey($field):
  193. mangledNames[$field] = $mangleJsName($field)
  194. let importString = "#." & mangledNames[$field]
  195. result = quote do:
  196. proc helper(o: JsObject): JsObject
  197. {. importcpp: `importString`, gensym .}
  198. helper(`obj`)
  199. macro `.=`*(obj: JsObject, field, value: untyped): untyped =
  200. ## Experimental dot accessor (set) for type JsObject.
  201. ## Sets the value of a property of name `field` in a JsObject `x` to `value`.
  202. if validJsName($field):
  203. let importString = "#." & $field & " = #"
  204. result = quote do:
  205. proc helper(o: JsObject, v: auto)
  206. {. importcpp: `importString`, gensym .}
  207. helper(`obj`, `value`)
  208. else:
  209. if not mangledNames.hasKey($field):
  210. mangledNames[$field] = $mangleJsName($field)
  211. let importString = "#." & mangledNames[$field] & " = #"
  212. result = quote do:
  213. proc helper(o: JsObject, v: auto)
  214. {. importcpp: `importString`, gensym .}
  215. helper(`obj`, `value`)
  216. macro `.()`*(obj: JsObject,
  217. field: untyped,
  218. args: varargs[JsObject, jsFromAst]): JsObject =
  219. ## Experimental "method call" operator for type JsObject.
  220. ## Takes the name of a method of the JavaScript object (`field`) and calls
  221. ## it with `args` as arguments, returning a JsObject (which may be discarded,
  222. ## and may be `undefined`, if the method does not return anything,
  223. ## so be careful when using this.)
  224. ##
  225. ## Example:
  226. ##
  227. ## .. code-block:: nim
  228. ##
  229. ## # Let's get back to the console example:
  230. ## var console {. importc, nodecl .}: JsObject
  231. ## let res = console.log("I return undefined!")
  232. ## console.log(res) # This prints undefined, as console.log always returns
  233. ## # undefined. Thus one has to be careful, when using
  234. ## # JsObject calls.
  235. var importString: string
  236. if validJsName($field):
  237. importString = "#." & $field & "(@)"
  238. else:
  239. if not mangledNames.hasKey($field):
  240. mangledNames[$field] = $mangleJsName($field)
  241. importString = "#." & mangledNames[$field] & "(@)"
  242. result = quote:
  243. proc helper(o: JsObject): JsObject
  244. {. importcpp: `importString`, gensym, discardable .}
  245. helper(`obj`)
  246. for idx in 0 ..< args.len:
  247. let paramName = newIdentNode(!("param" & $idx))
  248. result[0][3].add newIdentDefs(paramName, newIdentNode(!"JsObject"))
  249. result[1].add args[idx].copyNimTree
  250. macro `.`*[K: cstring, V](obj: JsAssoc[K, V],
  251. field: untyped): V =
  252. ## Experimental dot accessor (get) for type JsAssoc.
  253. ## Returns the value of a property of name `field` from a JsObject `x`.
  254. var importString: string
  255. if validJsName($field):
  256. importString = "#." & $field
  257. else:
  258. if not mangledNames.hasKey($field):
  259. mangledNames[$field] = $mangleJsName($field)
  260. importString = "#." & mangledNames[$field]
  261. result = quote do:
  262. proc helper(o: type(`obj`)): `obj`.V
  263. {. importcpp: `importString`, gensym .}
  264. helper(`obj`)
  265. macro `.=`*[K: cstring, V](obj: JsAssoc[K, V],
  266. field: untyped,
  267. value: V): untyped =
  268. ## Experimental dot accessor (set) for type JsAssoc.
  269. ## Sets the value of a property of name `field` in a JsObject `x` to `value`.
  270. var importString: string
  271. if validJsName($field):
  272. importString = "#." & $field & " = #"
  273. else:
  274. if not mangledNames.hasKey($field):
  275. mangledNames[$field] = $mangleJsName($field)
  276. importString = "#." & mangledNames[$field] & " = #"
  277. result = quote do:
  278. proc helper(o: type(`obj`), v: `obj`.V)
  279. {. importcpp: `importString`, gensym .}
  280. helper(`obj`, `value`)
  281. macro `.()`*[K: cstring, V: proc](obj: JsAssoc[K, V],
  282. field: untyped,
  283. args: varargs[untyped]): auto =
  284. ## Experimental "method call" operator for type JsAssoc.
  285. ## Takes the name of a method of the JavaScript object (`field`) and calls
  286. ## it with `args` as arguments. Here, everything is typechecked, so you do not
  287. ## have to worry about `undefined` return values.
  288. let dotOp = bindSym"."
  289. result = quote do:
  290. (`dotOp`(`obj`, `field`))()
  291. for elem in args:
  292. result.add elem
  293. # Iterators:
  294. iterator pairs*(obj: JsObject): (cstring, JsObject) =
  295. ## Yields tuples of type ``(cstring, JsObject)``, with the first entry
  296. ## being the `name` of a fields in the JsObject and the second being its
  297. ## value wrapped into a JsObject.
  298. var k: cstring
  299. var v: JsObject
  300. {.emit: "for (var `k` in `obj`) {".}
  301. {.emit: " if (!`obj`.hasOwnProperty(`k`)) continue;".}
  302. {.emit: " `v`=`obj`[`k`];".}
  303. yield (k, v)
  304. {.emit: "}".}
  305. iterator items*(obj: JsObject): JsObject =
  306. ## Yields the `values` of each field in a JsObject, wrapped into a JsObject.
  307. var v: JsObject
  308. {.emit: "for (var k in `obj`) {".}
  309. {.emit: " if (!`obj`.hasOwnProperty(k)) continue;".}
  310. {.emit: " `v`=`obj`[k];".}
  311. yield v
  312. {.emit: "}".}
  313. iterator keys*(obj: JsObject): cstring =
  314. ## Yields the `names` of each field in a JsObject.
  315. var k: cstring
  316. {.emit: "for (var `k` in `obj`) {".}
  317. {.emit: " if (!`obj`.hasOwnProperty(`k`)) continue;".}
  318. yield k
  319. {.emit: "}".}
  320. iterator pairs*[K: JsKey, V](assoc: JsAssoc[K, V]): (K,V) =
  321. ## Yields tuples of type ``(K, V)``, with the first entry
  322. ## being a `key` in the JsAssoc and the second being its corresponding value.
  323. var k: cstring
  324. var v: V
  325. {.emit: "for (var `k` in `assoc`) {".}
  326. {.emit: " if (!`assoc`.hasOwnProperty(`k`)) continue;".}
  327. {.emit: " `v`=`assoc`[`k`];".}
  328. yield (k.toJsKey(K), v)
  329. {.emit: "}".}
  330. iterator items*[K, V](assoc: JSAssoc[K, V]): V =
  331. ## Yields the `values` in a JsAssoc.
  332. var v: V
  333. {.emit: "for (var k in `assoc`) {".}
  334. {.emit: " if (!`assoc`.hasOwnProperty(k)) continue;".}
  335. {.emit: " `v`=`assoc`[k];".}
  336. yield v
  337. {.emit: "}".}
  338. iterator keys*[K: JsKey, V](assoc: JSAssoc[K, V]): K =
  339. ## Yields the `keys` in a JsAssoc.
  340. var k: cstring
  341. {.emit: "for (var `k` in `assoc`) {".}
  342. {.emit: " if (!`assoc`.hasOwnProperty(`k`)) continue;".}
  343. yield k.toJsKey(K)
  344. {.emit: "}".}
  345. # Literal generation
  346. macro `{}`*(typ: typedesc, xs: varargs[untyped]): auto =
  347. ## Takes a ``typedesc`` as its first argument, and a series of expressions of
  348. ## type ``key: value``, and returns a value of the specified type with each
  349. ## field ``key`` set to ``value``, as specified in the arguments of ``{}``.
  350. ##
  351. ## Example:
  352. ##
  353. ## .. code-block:: nim
  354. ##
  355. ## # Let's say we have a type with a ton of fields, where some fields do not
  356. ## # need to be set, and we do not want those fields to be set to ``nil``:
  357. ## type
  358. ## ExtremelyHugeType = ref object
  359. ## a, b, c, d, e, f, g: int
  360. ## h, i, j, k, l: cstring
  361. ## # And even more fields ...
  362. ##
  363. ## let obj = ExtremelyHugeType{ a: 1, k: "foo".cstring, d: 42 }
  364. ##
  365. ## # This generates roughly the same JavaScript as:
  366. ## {. emit: "var obj = {a: 1, k: "foo", d: 42};" .}
  367. ##
  368. let a = !"a"
  369. var body = quote do:
  370. var `a` {.noinit.}: `typ`
  371. {.emit: "`a` = {};".}
  372. for x in xs.children:
  373. if x.kind == nnkExprColonExpr:
  374. let
  375. k = x[0]
  376. kString = quote do:
  377. when compiles($`k`): $`k` else: "invalid"
  378. v = x[1]
  379. body.add quote do:
  380. when compiles(`a`.`k`):
  381. `a`.`k` = `v`
  382. elif compiles(`a`[`k`]):
  383. `a`[`k`] = `v`
  384. else:
  385. `a`[`kString`] = `v`
  386. else:
  387. error("Expression `" & $x.toStrLit & "` not allowed in `{}` macro")
  388. body.add quote do:
  389. return `a`
  390. result = quote do:
  391. proc inner(): `typ` {.gensym.} =
  392. `body`
  393. inner()
  394. # Macro to build a lambda using JavaScript's `this`
  395. # from a proc, `this` being the first argument.
  396. macro bindMethod*(procedure: typed): auto =
  397. ## Takes the name of a procedure and wraps it into a lambda missing the first
  398. ## argument, which passes the JavaScript builtin ``this`` as the first
  399. ## argument to the procedure. Returns the resulting lambda.
  400. ##
  401. ## Example:
  402. ##
  403. ## We want to generate roughly this JavaScript:
  404. ##
  405. ## .. code-block:: js
  406. ## var obj = {a: 10};
  407. ## obj.someMethod = function() {
  408. ## return this.a + 42;
  409. ## };
  410. ##
  411. ## We can achieve this using the ``bindMethod`` macro:
  412. ##
  413. ## .. code-block:: nim
  414. ## let obj = JsObject{ a: 10 }
  415. ## proc someMethodImpl(that: JsObject): int =
  416. ## that.a.to(int) + 42
  417. ## obj.someMethod = bindMethod someMethodImpl
  418. ##
  419. ## # Alternatively:
  420. ## obj.someMethod = bindMethod
  421. ## proc(that: JsObject): int = that.a.to(int) + 42
  422. if not (procedure.kind == nnkSym or procedure.kind == nnkLambda):
  423. error("Argument has to be a proc or a symbol corresponding to a proc.")
  424. var
  425. rawProc = if procedure.kind == nnkSym:
  426. getImpl(procedure.symbol)
  427. else:
  428. procedure
  429. args = rawProc[3]
  430. thisType = args[1][1]
  431. params = newNimNode(nnkFormalParams).add(args[0])
  432. body = newNimNode(nnkLambda)
  433. this = newIdentNode("this")
  434. # construct the `this` parameter:
  435. thisQuote = quote do:
  436. var `this` {. nodecl, importc .} : `thisType`
  437. call = newNimNode(nnkCall).add(rawProc[0], thisQuote[0][0][0])
  438. # construct the procedure call inside the method
  439. if args.len > 2:
  440. for idx in 2..args.len-1:
  441. params.add(args[idx])
  442. call.add(args[idx][0])
  443. body.add(newNimNode(nnkEmpty),
  444. rawProc[1],
  445. rawProc[2],
  446. params,
  447. rawProc[4],
  448. rawProc[5],
  449. newTree(nnkStmtList, thisQuote, call)
  450. )
  451. result = body