Tezos via JSOO - 02, Account balance

This mini tutorial series shows how to access Tezos network from web browsers using JSOO, js_of_ocaml library. This is the second tutorial. The first one is available at:

Balance of an account

To get the balance of given account, we can use RPC endpoint

GET /chains/main/blocks/<block_id>/context/contracts/<contract_id>/balance

which is described here. Let’s get the balance of the account tz3RDC3Jdn4j15J7bBHZd29EUee9gVB1CxD9 via this RPC. Its URL is https://mainnet.smartpy.io/chains/main/blocks/head/context/contracts/tz3RDC3Jdn4j15J7bBHZd29EUee9gVB1CxD9/balance:

$ curl https://mainnet.smartpy.io/chains/main/blocks/head/context/contracts/tz3RDC3Jdn4j15J7bBHZd29EUee9gVB1CxD9/balance:
"423271651423"

It returns double-quoted string of an integer, the balance of the account in mutez, micro tez. Therefore the above tells us the account has 423,271,651,423 mutez, that is 423,271.651,423 tez.

Let’s call this API from JSOO and show the balance in a web browser.

Calling the RPC endpoint

As we have seen in the previous tutorial, we use XmlHttpRequest.perform against the endpoint. Don’t forget that the node must be CORS enabled:

let+ http_frame = XmlHttpRequest.perform (balance_url adrs) in
match http_frame.code with
| 200 ->
    report "response: %S" http_frame.content;
    ...

Parsing JSON in JSOO

The response string from the Tezos node is actually a JSON. We have to parse it.

JS has a built-in JSON parser and stringify object JSON and we can use it in JSOO:

open Js
val _JSON : < parse : 'a. js_string t -> 'a meth;
              stringify : 'a. 'a -> js_string t meth > t

We use _JSON##parse to parse the response JSON string to JS object of type Js.js_string Js.t:

let s : Js.js_string Js.t = Js._JSON##parse (Js.string http_frame.content) in

Beware! It is not string but Js.js_string Js.t.

Crossing typed and untyped worlds

If you feel uneasy about the polymorphic types of the _JSON methods, your instinct is correct. This is not OCaml but JS, and there is no type safety. The type constraint to Js.js_string Js.t in JSOO does not check the type of the returned JS object: even if the response is not a string but something else like an integer 1234, the above declaration of s succeeds. A run time JS type error will be reported only when s is used as a string, which can be much later in general.

In this tutorial, we convert the result string to an integer immediately. If the RPC returns something unexpected, we can find it easily.

Use of Zarith and zarith_stubs_js

The maximum possible mutez in Tezos is 9223372036854775807, which is too large for Javascript 54 bit signed integer and also for OCaml 63 bit signed integer. Therefore mutez is represented as a string in JSON for safety. (JSON format itself does not specify the maximum possible number, though.)

To handle such a huge integer in OCaml, we use Z.t of Zarith arbitrary precision integer library. Zarith does not work in JSOO as is, since it uses C code for the primitives of Z.t. Fortunately, we have zarith_stubs_js, JS implementation for the primitives. We need zarith and zarith_stubs_js at the libraries stanza of dune file:

; dune 
(executables
  (names test)
  (modes js)
  (libraries
    js_of_ocaml
    js_of_ocaml-lwt
    zarith           ; new addition
    zarith_stubs_js  ; new addition
  )
  (preprocess (pps js_of_ocaml-ppx)))

Don’t forget to install zarith and zarith_stubs_js if not yet:

$ opam install zarith zarith_stubs_js

Once they are installed, the conversion from the string to Z.t is easy:

let balance = Z.of_string (Js.to_string s) in

It is in mutez. Let’s change it to tez and print the result to the screen:

let tz, mtz = Z.div_rem balance (Z.of_int 1_000_000) in
report "%s : %s.%06d TEZ" adrs (Z.to_string tz) (Z.to_int mtz)

Full OCaml code

We introduce report function with printf interface to show the results on the web page.

open Js_of_ocaml
open Js_of_ocaml_lwt
open Lwt.Syntax

(* The node.  Must be CORS enabled. *)
let node = "https://mainnet.smartpy.io"

(* Tezos RPC path to get the balance of an address *)
let balance_url adrs =
  Option.get
  @@ Url.url_of_string
  @@ node ^ "/chains/main/blocks/head/context/contracts/" ^ adrs ^ "/balance"

let adrs = "tz3RDC3Jdn4j15J7bBHZd29EUee9gVB1CxD9"

module Html = Dom_html

let start () =
  let elem = Html.getElementById "result" in

  (* printf style reporting function to textarea *)
  let report fmt =
    Format.kasprintf
      (fun s ->
         elem##.innerText := elem##.innerText##concat (Js.string (s ^ "\n")))
      fmt
  in

  let url = balance_url adrs in
  report "URL: %s" (Url.string_of_url url);
  (* The node must be CORS enabled. *)
  let+ http_frame = XmlHttpRequest.perform (balance_url adrs) in
  match http_frame.code with
  | 200 ->
      report "response: %S" http_frame.content;
      (* It is a JSON string.  Parse it using Js._JSON##parse *)
      let s : Js.js_string Js.t =
        Js._JSON##parse (Js.string http_frame.content)
      in
      (* balance in Tezos is an arbitrary-precision integer, in mutez
         (micro tez).

         To use module Z of Zarith library, we use zarith_stubs_js package
         to provide JS code for Z.t.  See dune file.
      *)
      let balance = Z.of_string (Js.to_string s) in
      (* let's print the balance in tz *)
      let tz, mtz = Z.div_rem balance (Z.of_int 1_000_000) in
      report "%s : %s.%06d TEZ" adrs (Z.to_string tz) (Z.to_int mtz)
  | _ ->
      report "HTTP code %d" http_frame.code

let _ =
  Html.window##.onload := Html.handler (fun _ -> ignore @@ start (); Js._false)

The entire code set (this code + dune + index.html) is available here. How to compile the tutorial examples are explained in the Appendix of the first tutorial.

Conclusion

This is the end of the 2nd tutorial of Tezos via JSOO. Key takeaways today are:

  • Use Js._JSON to parse the JSON response from the Tezos node.
  • JS is untyped, so is Js._JSON!
  • Zarith is required to handle Tezos integers and balances. In JSOO, zarith_stubs_js must be linked together.

In the next tutorial, we try to handle more complex JSON response from the node.