Module Jingoo.Jg_runtime

val jg_nth : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_nth n seq returns the n-th value of sequence seq

val jg_escape_html : Jg_types.tvalue -> Jg_types.tvalue

jg_escape_html x escape x string representation using Jg_utils.escape_html

val jg_test_defined : Jg_types.context -> string -> Jg_types.tvalue
val jg_test_undefined : Jg_types.context -> string -> Jg_types.tvalue
val jg_test_none : Jg_types.context -> string -> Jg_types.tvalue

Alias for jg_test_undefined

val jg_test_obj_defined : Jg_types.context -> string -> string -> Jg_types.tvalue
val jg_test_obj_undefined : Jg_types.context -> string -> string -> Jg_types.tvalue
val jg_test_escaped : Jg_types.context -> Jg_types.tvalue

FIXME: this should check the value and not the context

val jg_negative : Jg_types.tvalue -> Jg_types.tvalue
val jg_is_true : Jg_types.tvalue -> bool
val jg_not : Jg_types.tvalue -> Jg_types.tvalue
val jg_plus : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_plus a b The multi-purpose + operator. Can add two numbers, concat two strings or a string and a number, append two sequences (list or array).

val jg_minus : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue
val jg_times : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue
val jg_power : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue
val jg_div : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue
val jg_mod : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue
val jg_and : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_or e1 e2 The boolean and.

val jg_or : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_or e1 e2 The boolean or.

val jg_compare : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_compare x y returns 0 if x is equal to y, a negative integer if x is less than y, and a positive integer if x is greater than y.

val jg_eq_eq : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue
val jg_not_eq : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue
val jg_lt : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue
val jg_gt : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue
val jg_lteq : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue
val jg_gteq : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue
val jg_inop : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_inop x seq Test if seq contains element x.

val jg_upper : Jg_types.tvalue -> Jg_types.tvalue

jg_upper s Apply upper case to s.

val jg_lower : Jg_types.tvalue -> Jg_types.tvalue

jg_upper s Apply lower case to s.

val jg_capitalize : Jg_types.tvalue -> Jg_types.tvalue

jg_capitalize txt Apply uppercase to the first letter of txt and lowercase to the rest

val jg_title : Jg_types.tvalue -> Jg_types.tvalue

jg_title txt Apply titlecase (lower case except for first letter of all words which is upper cased) to txt.

val jg_int : Jg_types.tvalue -> Jg_types.tvalue

jg_int x turns x into an integer. Support int, float and string types.

val jg_float : Jg_types.tvalue -> Jg_types.tvalue

jg_float x turns x into a float. Support int, float and string types.

val jg_join : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_join sep seq concatenates the string representation of values in seq, inserting the separator sep between each.

val jg_split : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_split pat text returns the list of all (possibly empty) substrings of text that are delimited by pat regex.

val jg_substring : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_substring start len s returns a string of length len, containing the substring of s that starts at position start and has length len

val jg_truncate : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_truncate len str is a shorthand for jg_substring 0 len str

val jg_strlen : Jg_types.tvalue -> Jg_types.tvalue

jg_strlen s returns the length (number of characters) of s

val jg_length : Jg_types.tvalue -> Jg_types.tvalue

jg_length seq returns the number of of elements in sequence seq. If seq is a string jg_strlen seq is returned.

val jg_md5 : Jg_types.tvalue -> Jg_types.tvalue
val jg_abs : Jg_types.tvalue -> Jg_types.tvalue

jg_abs x Return the absolute value of x.

val jg_attr : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_attr p o Return the p property of object o. Support dotted notation.

val jg_center : ?⁠defaults:'a -> 'b -> 'b

TODO

val jg_default : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_default default value Return value if different from Tnull, and default otherwise.

val jg_dictsort : ?⁠defaults:'a -> Jg_types.tvalue -> Jg_types.tvalue

TODO: keyword arguments

val jg_reverse : Jg_types.tvalue -> Jg_types.tvalue
val jg_last : Jg_types.tvalue -> Jg_types.tvalue

jg_last seq. Return the last element of sequence seq.

val jg_random : Jg_types.tvalue -> Jg_types.tvalue
val jg_replace : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue
val jg_add : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_add a b is a + b. It only support int and float. If both a and b are int, the result is an int, it is a float otherwise.

val jg_sum : Jg_types.tvalue -> Jg_types.tvalue

jg_sum seq is the sum of elements in seq produced using jg_add.

val jg_trim : Jg_types.tvalue -> Jg_types.tvalue

jg_trim s returns s with leading and trailing whitespace.

val jg_list : Jg_types.tvalue -> Jg_types.tvalue

jg_list x convert x to a list. Support list, tuple, string and array.

val jg_batch : ?⁠defaults:(string * Jg_types.tvalue) list -> ?⁠kwargs:(string * Jg_types.tvalue) list -> Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_batch count value split value into chunks containing count values.

If fill_with=v keyword argument is given, the last chunk will be filled with v instead of null if needed.

val jg_slice : ?⁠kwargs:(string * Jg_types.tvalue) list -> Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_slice nb value split value into nb chunks.

If fill_with=v keyword argument is given, v will be used when buckets will need to be filled so that they all contain the same number of elements.

See also jg_batch.

val jg_sublist : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_sublist i len list returns the sub-list of list, starting at the i-th element, and containing len elements, or all elements after the i-th if len is null.

val jg_wordcount : Jg_types.tvalue -> Jg_types.tvalue

jg_wordcount str count (non-empty) words in str using spacing as delimiter between words.

val jg_round : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_round meth x rounds x using meth rounding method. Supported methods are "ceil" and "floor".

val jg_fmt_float : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue
val jg_range : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_range start stop returns a sequence of values going from start to (or downto) stop. Support integers and string with one ascii character.

val jg_urlize_regexp : Re.re lazy_t
val jg_urlize : Jg_types.tvalue -> Jg_types.tvalue
val jg_striptags_regexp : Re.re lazy_t
val jg_striptags : Jg_types.tvalue -> Jg_types.tvalue
val jg_sort : ?⁠kwargs:(string * Jg_types.tvalue) list -> Jg_types.tvalue -> Jg_types.tvalue

jg_sort ?kwargs seq sort the seq. Support the following keyword arguments:

  • "reverse": sorted in descending order.
  • "attribute": use attribute of elements to sort the sequence. Support dotted notation.
  • "compare": provide a comparison function to be use instead of the built-in one.
val jg_xmlattr : Jg_types.tvalue -> Jg_types.tvalue

jg_xmlattr o Format a string containing keys/values representation of object o so it can be used as xml attributes. i.e. 'key1="value1" key2="value2"

val jg_wordwrap : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue
module JgHashtbl : sig ... end
val fun_or_attribute : kwargs:Jg_types.kwargs -> arg:Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue
val jg_groupby_aux : (Jg_types.tvalue -> JgHashtbl.key) -> int -> ((Jg_types.tvalue -> unit) -> 'a -> unit) -> 'a -> Jg_types.tvalue
val jg_groupby : ?⁠kwargs:Jg_types.kwargs -> Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_groupby ?kwargs fn seq For each element x of seq, fn x returns a key used to group elements with the same key together.

Resulting list is a list of objects with two fields: gouper, the key, and list, the list containing values from seq whose key is grouper.

"attribute"=path keyword argument will apply attr(path) function.

val jg_map : ?⁠kwargs:Jg_types.kwargs -> Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_map ?kwargs fn seq build the sequence seq' such as seq'[n] = fn (seq[n]) .

"attribute"=path keyword argument will apply attr(path) function.

val jg_max_min_aux : bool -> Jg_types.tvalue -> ((Jg_types.tvalue -> unit) -> 'a -> unit) -> 'a -> (string * Jg_types.tvalue) list -> Jg_types.tvalue
val jg_max : ?⁠kwargs:(string * Jg_types.tvalue) list -> Jg_types.tvalue -> Jg_types.tvalue

jg_max ?kwargs sequence return the maximal value of sequence. kwargs may be used to specify an attribute ("attribute", str) to use when comparing values (dotted notation is supported).

val jg_min : ?⁠kwargs:(string * Jg_types.tvalue) list -> Jg_types.tvalue -> Jg_types.tvalue

jg_min ?kwargs sequence return the minimal value of sequence. kwargs may be used to specify an attribute ("attribute", str) to use when comparing values (dotted notation is supported).

val jg_select_aux : string -> (bool -> bool) -> Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue
val jg_reject : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_reject fn seq returns the elements of seq that don't satify fn.

val jg_select : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_select fn seq returns the elements of seq that satify fn.

val jg_fold : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_fold fn acc [b1, ..., bn] is fn (... (fn (fn acc b1) b2) ...) bn.

val jg_forall : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

for_all fn seq checks if all elements of the sequence seq satisfy the predicate fn.

val jg_test_divisibleby : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_test_divisibleby divisor dividend tests if dividend is divisible by divisor.

val jg_test_even : Jg_types.tvalue -> Jg_types.tvalue

jg_test_even x tests if x is even (only works with int).

val jg_test_odd : Jg_types.tvalue -> Jg_types.tvalue

jg_test_odd x tests if x is odd (only works with int).

val jg_test_iterable_aux : Jg_types.tvalue -> bool
val jg_test_iterable : Jg_types.tvalue -> Jg_types.tvalue

jg_test_upper x tests if x is iterable.

val jg_test_lower : Jg_types.tvalue -> Jg_types.tvalue

jg_test_upper x tests if x is an lowercased string.

val jg_test_upper : Jg_types.tvalue -> Jg_types.tvalue

jg_test_upper x tests if x is an uppercased string.

val jg_test_number : Jg_types.tvalue -> Jg_types.tvalue

jg_test_number x tests if x is a number (i.e. an int or a float).

val jg_test_sameas : Jg_types.tvalue -> Jg_types.tvalue -> Jg_types.tvalue

jg_test_sameas x y tests if y and x are physically equals.

val jg_test_sequence : Jg_types.tvalue -> Jg_types.tvalue

jg_test_sequence x tests if x is sequence (i.e. a list or an array).

val jg_test_string : Jg_types.tvalue -> Jg_types.tvalue

jg_test_string x tests if x is of type string.

val std_filters : (string * Jg_types.tvalue) list
val jg_load_extensions : string list -> unit
val jg_init_context : ?⁠models:(string * Jg_types.tvalue) list -> (Jg_types.tvalue -> unit) -> Jg_types.environment -> Jg_types.context

jg_init_context ?models output env Define a context to use with evaluation functions from Jg_interp. See Jg_types.context.