Functions and utilities for faster processing.

(ns metabase.util.performance
  (:refer-clojure :exclude [reduce mapv run! some concat])
  (:import (clojure.lang LazilyPersistentVector RT)
           java.util.Iterator))
(set! *warn-on-reflection* true)

Like clojure.core/reduce, but uses iterators under the hood to walk the collections and can iterate several collections at once. The function f accepts the number of arguments that is the number of iterated collections + 1 (accumulator).

(defn reduce
  ([f init coll1]
   (if (nil? coll1)
     init
     (let [it1 (.iterator ^Iterable coll1)]
       (loop [res init]
         (if (.hasNext it1)
           (let [res (f res (.next it1))]
             (if (reduced? res)
               @res
               (recur res)))
           res)))))
  ([f init coll1 coll2]
   (if (or (nil? coll1) (nil? coll2))
     init
     (let [it1 (.iterator ^Iterable coll1)
           it2 (.iterator ^Iterable coll2)]
       (loop [res init]
         (if (and (.hasNext it1) (.hasNext it2))
           (let [res (f res (.next it1) (.next it2))]
             (if (reduced? res)
               @res
               (recur res)))
           res)))))
  ([f init coll1 coll2 coll3]
   (if (or (nil? coll1) (nil? coll2) (nil? coll3))
     init
     (let [it1 (.iterator ^Iterable coll1)
           it2 (.iterator ^Iterable coll2)
           it3 (.iterator ^Iterable coll3)]
       (loop [res init]
         (if (and (.hasNext it1) (.hasNext it2) (.hasNext it3))
           (let [res (f res (.next it1) (.next it2) (.next it3))]
             (if (reduced? res)
               @res
               (recur res)))
           res)))))
  ([f init coll1 coll2 coll3 coll4]
   (if (or (nil? coll1) (nil? coll2) (nil? coll3) (nil? coll4))
     init
     (let [it1 (.iterator ^Iterable coll1)
           it2 (.iterator ^Iterable coll2)
           it3 (.iterator ^Iterable coll3)
           it4 (.iterator ^Iterable coll4)]
       (loop [res init]
         (if (and (.hasNext it1) (.hasNext it2) (.hasNext it3) (.hasNext it4))
           (let [res (f res (.next it1) (.next it2) (.next it3) (.next it4))]
             (if (reduced? res)
               @res
               (recur res)))
           res))))))

Special case for mapv. If the iterated collection has size <=32, it is more efficient to use object array as accumulator instead of transients, and then build a vector from it.

(definterface ISmallTransient
  (conj [x])
  (persistent []))
(deftype SmallTransientImpl [^objects arr, ^:unsynchronized-mutable ^long cnt]
  ISmallTransient
  (conj [this x]
    (RT/aset arr (unchecked-int cnt) x)
    (set! cnt (unchecked-inc cnt))
    this)
  (persistent [_]
    (LazilyPersistentVector/createOwning arr)))
(defn- small-transient [n]
  (SmallTransientImpl. (object-array n) 0))
(defn- small-conj!
  {:inline (fn [st x] `(.conj ~(with-meta st {:tag `ISmallTransient}) ~x))}
  [^ISmallTransient st x]
  (.conj st x))
(defn- small-persistent! [^ISmallTransient st]
  (.persistent st))
(defn- smallest-count
  (^long [c1 c2] (min (count c1) (count c2)))
  (^long [c1 c2 c3] (min (count c1) (count c2) (count c3)))
  (^long [c1 c2 c3 c4] (min (count c1) (count c2) (count c3) (count c4))))

Like clojure.core/mapv, but iterates multiple collections more efficiently and uses Java iterators under the hood.

(defn mapv
  ([f coll1]
   (let [n (count coll1)]
     (cond (= n 0) []
           (<= n 32) (small-persistent! (reduce #(small-conj! %1 (f %2)) (small-transient n) coll1))
           :else (persistent! (reduce #(conj! %1 (f %2)) (transient []) coll1)))))
  ([f coll1 coll2]
   (let [n (smallest-count coll1 coll2)]
     (cond (= n 0) []
           (<= n 32) (small-persistent! (reduce #(small-conj! %1 (f %2 %3)) (small-transient n) coll1 coll2))
           :else (persistent! (reduce #(conj! %1 (f %2 %3)) (transient []) coll1 coll2)))))
  ([f coll1 coll2 coll3]
   (let [n (smallest-count coll1 coll2 coll3)]
     (cond (= n 0) []
           (<= n 32) (small-persistent! (reduce #(small-conj! %1 (f %2 %3 %4)) (small-transient n) coll1 coll2 coll3))
           :else (persistent! (reduce #(conj! %1 (f %2 %3 %4)) (transient []) coll1 coll2 coll3)))))
  ([f coll1 coll2 coll3 coll4]
   (let [n (smallest-count coll1 coll2 coll3 coll4)]
     (cond (= n 0) []
           (<= n 32) (small-persistent! (reduce #(small-conj! %1 (f %2 %3 %4 %5)) (small-transient n) coll1 coll2 coll3 coll4))
           :else (persistent! (reduce #(conj! %1 (f %2 %3 %4 %5)) (transient []) coll1 coll2 coll3 coll4))))))

Like clojure.core/run!, but iterates collections more efficiently and uses Java iterators under the hood.

(defn run!
  ([f coll1]
   (reduce (fn [_ x] (f x)) nil coll1)))

Like clojure.core/juxt, but accepts a list of functions instead of varargs. Uses more efficient mapping.

(defn juxt*
  [fns]
  (let [fns (vec fns)]
    (fn
      ([] (mapv #(%) fns))
      ([x] (mapv #(% x) fns))
      ([x y] (mapv #(% x y) fns))
      ([x y z] (mapv #(% x y z) fns))
      ([x y z & args] (mapv #(apply % x y z args) fns)))))

Like clojure.core/some but uses our custom reduce which in turn uses iterators.

(defn some
  [f coll]
  (unreduced (reduce #(when-let [match (f %2)] (reduced match)) nil coll)))

Like clojure.core/concat but accumulates the result into a vector.

(defn concat
  ([a b]
   (into (vec a) b))
  ([a b c]
   (as-> (transient (vec a)) res
     (reduce conj! res b)
     (reduce conj! res c)
     (persistent! res)))
  ([a b c d]
   (as-> (transient (vec a)) res
     (reduce conj! res b)
     (reduce conj! res c)
     (reduce conj! res d)
     (persistent! res)))
  ([a b c d e]
   (as-> (transient (vec a)) res
     (reduce conj! res b)
     (reduce conj! res c)
     (reduce conj! res d)
     (reduce conj! res e)
     (persistent! res)))
  ([a b c d e f]
   (as-> (transient (vec a)) res
     (reduce conj! res b)
     (reduce conj! res c)
     (reduce conj! res d)
     (reduce conj! res e)
     (reduce conj! res f)
     (persistent! res)))
  ([a b c d e f & more]
   (as-> (transient (vec a)) res
     (reduce conj! res b)
     (reduce conj! res c)
     (reduce conj! res d)
     (reduce conj! res e)
     (reduce conj! res f)
     (reduce (fn [res l] (reduce conj! res l)) res more)
     (persistent! res))))

Like (apply mapv vector coll-of-colls), but more efficient.

(defn transpose
  [coll-of-colls]
  (let [its (mapv #(.iterator ^Iterable %) coll-of-colls)]
    (mapv (fn [_] (mapv #(.next ^Iterator %) its))
          (first coll-of-colls))))

clojure.walk reimplementation. Partially adapted from https://github.com/tonsky/clojure-plus.

(defn- editable? [coll]
  (instance? clojure.lang.IEditableCollection coll))
(defn- transient? [coll]
  (instance? clojure.lang.ITransientCollection coll))
(defn- assoc+ [coll key value]
  (cond
    (transient? coll) (assoc! coll key value)
    (editable? coll)  (assoc! (transient coll) key value)
    :else             (assoc  coll key value)))
(defn- dissoc+ [coll key]
  (cond
    (transient? coll) (dissoc! coll key)
    (editable? coll)  (dissoc! (transient coll) key)
    :else             (dissoc  coll key)))
(defn- maybe-persistent! [coll]
  (cond-> coll
    (transient? coll) persistent!))

Like clojure.walk/walk, but optimized for efficiency and has the following behavior differences: - Doesn't walk over map entries. When descending into a map, walks keys and values separately. - Uses transients and reduce where possible and tries to return the same input form if no changes were made.

(defn walk
  [inner outer form]
  (cond
    (map? form)
    (let [new-keys (volatile! (transient #{}))]
      (-> (reduce-kv (fn [m k v]
                       (let [k' (inner k)
                             v' (inner v)]
                         (if (identical? k' k)
                           (if (identical? v' v)
                             m
                             (assoc+ m k' v'))
                           (do (vswap! new-keys conj! k')
                               (if (contains? @new-keys k)
                                 (assoc+ m k' v')
                                 (-> m (dissoc+ k) (assoc+ k' v')))))))
                     form form)
          maybe-persistent!
          (with-meta (meta form))
          outer))
    (vector? form)
    (-> (reduce-kv (fn [v idx el]
                     (let [el' (inner el)]
                       (if (identical? el' el)
                         v
                         (assoc+ v idx el'))))
                   form form)
        maybe-persistent!
        (with-meta (meta form))
        outer)
    ;; Don't care much about optimizing seq and generic coll cases. When efficiency is required, use vectors.
    (seq? form) (outer (with-meta (seq (mapv inner form)) (meta form))) ;;
    (coll? form) (outer (with-meta (into (empty form) (map inner) form) (meta form)))
    :else (outer form)))

Like clojure.walk/prewalk, but uses a more efficient metabase.util.performance/walk underneath.

(defn prewalk
  [f form]
  (walk (fn prewalker [form] (walk prewalker identity (f form))) identity (f form)))

Like clojure.walk/postwalk, but uses a more efficient metabase.util.performance/walk underneath.

(defn postwalk
  [f form]
  (walk (fn postwalker [form] (walk postwalker f form)) f form))

Like clojure.walk/keywordize-keys, but uses a more efficient metabase.util.performance/walk underneath and preserves original metadata on the transformed maps.

(defn keywordize-keys
  [m]
  (postwalk
   (fn [form]
     (if (map? form)
       (-> (reduce-kv (fn [m k v]
                        (if (string? k)
                          (-> m (dissoc+ k) (assoc+ (keyword k) v))
                          m))
                      form form)
           maybe-persistent!
           (with-meta (meta form)))
       form))
   m))