Liking cljdoc? Tell your friends :D

dom-top.core

Unorthodox control flow.

Unorthodox control flow.
raw docstring

assert+cljmacro

(assert+ x)
(assert+ x message)
(assert+ x ex-type message)

Like Clojure assert, but throws customizable exceptions (by default, IllegalArgumentException), and returns the value it checks, instead of nil.

Clojure assertions are a little weird. Syntactically, they're a great candidate for runtime validation of state--making sure you got an int instead of a map, or that an object you looked up was present. However, they don't return the thing you pass them, which makes it a bit akward to use them in nested expressions. You typically have to do a let binding and then assert. So... let's return truthy values! Now you can

(assert+ (fetch-person-from-db :liu)
         "Couldn't fetch Liu!")

Moreover, Clojure assertions sensibly throw AssertionError. However, AssertionError is an error that "should never occur" and "a reasonable application should not try to catch." There are LOTS of cases where you DO expect assertions to fail sometimes and intend to catch them: for instance, validating user input, or bounds checks. So we're going to throw customizable exceptions.

Oh, and you can throw maps too. Those become ex-infos.

(assert+ (thing? that)
         {:type   :wasn't-a-thing
          :I'm    [:so :sorry]})
Like Clojure assert, but throws customizable exceptions (by default,
IllegalArgumentException), and returns the value it checks, instead of nil.

Clojure assertions are a little weird. Syntactically, they're a great
candidate for runtime validation of state--making sure you got an int instead
of a map, or that an object you looked up was present. However, they don't
*return* the thing you pass them, which makes it a bit akward to use them in
nested expressions. You typically have to do a let binding and then assert.
So... let's return truthy values! Now you can

    (assert+ (fetch-person-from-db :liu)
             "Couldn't fetch Liu!")

Moreover, Clojure assertions sensibly throw AssertionError. However,
AssertionError is an error that "should never occur" and "a reasonable
application should not try to catch." There are LOTS of cases where you DO
expect assertions to fail sometimes and intend to catch them: for instance,
validating user input, or bounds checks. So we're going to throw
customizable exceptions.

Oh, and you can throw maps too. Those become ex-infos.

    (assert+ (thing? that)
             {:type   :wasn't-a-thing
              :I'm    [:so :sorry]})
sourceraw docstring

bounded-futurecljmacro

(bounded-future & body)

Like future, but runs on the bounded agent executor. Useful for CPU-bound futures.

Like future, but runs on the bounded agent executor. Useful for CPU-bound
futures.
sourceraw docstring

bounded-future-callclj

(bounded-future-call f)

Like clojure.core/future-call, but runs on the bounded agent executor instead of the unbounded one. Useful for CPU-bound futures.

Like clojure.core/future-call, but runs on the bounded agent executor
instead of the unbounded one. Useful for CPU-bound futures.
sourceraw docstring

bounded-pmapclj

(bounded-pmap f coll)

Like pmap, but spawns tasks immediately, and uses the global bounded agent threadpool. Ideal for computationally bound tasks, especially when you might want to, say, pmap inside each of several parallel tasks without spawning eight gazillion threads.

Like pmap, but spawns tasks immediately, and uses the global bounded agent
threadpool. Ideal for computationally bound tasks, especially when you might
want to, say, pmap *inside* each of several parallel tasks without spawning
eight gazillion threads.
sourceraw docstring

disorderlycljmacro

(disorderly a)
(disorderly a b)
(disorderly a b & more)

This is a chaotic do expression. Like do, takes any number of forms. Where do evaluates forms in order, disorderly evaluates them in a random order. Where do returns the result of evaluating the final form, disorderly returns a sequence of the results of each form, in lexical (as opposed to execution) order, making it suitable for binding results.

This is particularly helpful when you want side effects, but you're not exactly sure how. Consider, for instance, testing that several mutations of an object all commute.

(disorderly (do (prn 1) :a)
            (do (prn 2) :b))

... prints either 1 then 2, or 2 then 1, but always returns (:a :b). Note that disorderly is not concurrent: branches evaluate in some order; it's just not a deterministic one.

This is a chaotic do expression. Like `do`, takes any number of forms. Where
`do` evaluates forms in order, `disorderly` evaluates them in a random order.
Where `do` returns the result of evaluating the final form, `disorderly`
returns a sequence of the results of each form, in lexical (as opposed to
execution) order, making it suitable for binding results.

This is particularly helpful when you want side effects, but you're not
exactly sure how. Consider, for instance, testing that several mutations of
an object all commute.

    (disorderly (do (prn 1) :a)
                (do (prn 2) :b))

... prints either 1 then 2, or 2 then 1, but always returns (:a :b). Note
that `disorderly` is *not* concurrent: branches evaluate in some order; it's
just not a deterministic one.
sourceraw docstring

fcatchclj

(fcatch f)

Takes a function and returns a version of it which returns, rather than throws, exceptions.

; returns RuntimeException
((fcatch #(throw (RuntimeException. "hi"))))
Takes a function and returns a version of it which returns, rather than
throws, exceptions.

    ; returns RuntimeException
    ((fcatch #(throw (RuntimeException. "hi"))))
sourceraw docstring

letrcljmacro

(letr bindings & body)

Let bindings, plus early return.

You want to do some complicated, multi-stage operation assigning lots of variables--but at different points in the let binding, you need to perform some conditional check to make sure you can proceed to the next step. Ordinarily, you'd intersperse let and if statements, like so:

(let [res (network-call)]
  (if-not (:ok? res)
    :failed-network-call

    (let [people (:people (:body res))]
      (if (zero? (count people))
        :no-people

        (let [res2 (network-call-2 people)]
          ...

This is a linear chain of operations, but we're forced to nest deeply because we have no early-return construct. In ruby, we might write

res = network_call
return :failed_network_call if not x.ok?

people = res[:body][:people]
return :no-people if people.empty?

res2 = network_call_2 people
...

which reads the same, but requires no nesting thanks to Ruby's early return. Clojure's single-return is usually a boon to understandability, but deep linear branching usually means something like

  • Deep nesting (readability issues)
  • Function chaining (lots of arguments for bound variables)
  • Throw/catch (awkward exception wrappers)
  • Monadic interpreter (slow, indirect)

This macro lets you write:

(letr [res    (network-call)
       _      (when-not (:ok? res) (return :failed-network-call))
       people (:people (:body res))
       _      (when (zero? (count people)) (return :no-people))
       res2   (network-call-2 people)]
  ...)

letr works like let, but if (return x) is ever returned from a binding, letr returns x, and does not evaluate subsequent expressions.

If something other than (return x) is returned from evaluating a binding, letr binds the corresponding variable as normal. Here, we use _ to indicate that we're not using the results of (when ...), but this is not mandatory. You cannot use a destructuring bind for a return expression.

letr is not a true early return--(return x) must be a terminal expression for it to work--like (recur). For example,

(letr [x (do (return 2) 1)]
  x)

returns 1, not 2, because (return 2) was not the terminal expression. Someone clever should fix this.

(return ...) only works within letr's bindings, not its body.

Let bindings, plus early return.

You want to do some complicated, multi-stage operation assigning lots of
variables--but at different points in the let binding, you need to perform
some conditional check to make sure you can proceed to the next step.
Ordinarily, you'd intersperse let and if statements, like so:

    (let [res (network-call)]
      (if-not (:ok? res)
        :failed-network-call

        (let [people (:people (:body res))]
          (if (zero? (count people))
            :no-people

            (let [res2 (network-call-2 people)]
              ...

This is a linear chain of operations, but we're forced to nest deeply because
we have no early-return construct. In ruby, we might write

    res = network_call
    return :failed_network_call if not x.ok?

    people = res[:body][:people]
    return :no-people if people.empty?

    res2 = network_call_2 people
    ...

which reads the same, but requires no nesting thanks to Ruby's early return.
Clojure's single-return is *usually* a boon to understandability, but deep
linear branching usually means something like

- Deep nesting         (readability issues)
- Function chaining    (lots of arguments for bound variables)
- Throw/catch          (awkward exception wrappers)
- Monadic interpreter  (slow, indirect)

This macro lets you write:

    (letr [res    (network-call)
           _      (when-not (:ok? res) (return :failed-network-call))
           people (:people (:body res))
           _      (when (zero? (count people)) (return :no-people))
           res2   (network-call-2 people)]
      ...)

letr works like let, but if (return x) is ever returned from a binding, letr
returns x, and does not evaluate subsequent expressions.

If something other than (return x) is returned from evaluating a binding,
letr binds the corresponding variable as normal. Here, we use _ to indicate
that we're not using the results of (when ...), but this is not mandatory.
You cannot use a destructuring bind for a return expression.

letr is not a *true* early return--(return x) must be a *terminal* expression
for it to work--like (recur). For example,

    (letr [x (do (return 2) 1)]
      x)

returns 1, not 2, because (return 2) was not the terminal expression. Someone
clever should fix this.

(return ...) only works within letr's bindings, not its body.
sourceraw docstring

letr-let-ifclj

(letr-let-if groups body)

Takes a sequence of binding groups and a body expression, and emits a let for the first group, an if statement checking for a return, and recurses; ending with body.

Takes a sequence of binding groups and a body expression, and emits a let
for the first group, an if statement checking for a return, and recurses;
ending with body.
sourceraw docstring

letr-partition-bindingsclj

(letr-partition-bindings bindings)

Takes a vector of bindings [sym expr, sym' expr, ...]. Returns binding-groups: a sequence of vectors of bindgs, where the final binding in each group has an early return. The final group (possibly empty!) contains no early return.

Takes a vector of bindings [sym expr, sym' expr, ...]. Returns
binding-groups: a sequence of vectors of bindgs, where the final binding in
each group has an early return. The final group (possibly empty!) contains no
early return.
sourceraw docstring

letr-rewrite-returnclj

(letr-rewrite-return expr)

Rewrites (return x) to (Return. x) in expr. Returns a pair of [changed? expr], where changed is whether the expression contained a return.

Rewrites (return x) to (Return. x) in expr. Returns a pair of [changed?
expr], where changed is whether the expression contained a return.
sourceraw docstring

load-class!clj

(load-class! class-name class-bytes)

Takes a class name as a string (e.g. foo.bar.Baz) and bytes for its class file. Loads the class dynamically, and also emits those bytes to compile-path, for AOT. Returns class.

Takes a class name as a string (e.g. foo.bar.Baz) and bytes for its class
file. Loads the class dynamically, and also emits those bytes to
*compile-path*, for AOT. Returns class.
sourceraw docstring

looprcljmacro

(loopr accumulator-bindings element-bindings body & [final :as final-forms])

Like loop, but for reducing over (possibly nested) collections. Compared to loop, makes iteration implicit. Compared to reduce, eliminates the need for nested reductions, fn wrappers, and destructuring multiple accumulators. Compared to for, loopr is eager, and lets you carry accumulators.

Takes an initial binding vector for accumulator variables, (like loop); then a binding vector of loop variables to collections (like for); then a body form, then an optional final form. Iterates over each element of the collections, like for would, and evaluates body with that combination of elements bound.

Like loop, the body should generally contain one or more (recur ...) forms with new values for each accumulator. Any non-recur form in tail position causes loopr to return that value immediately.

When the loop completes normally, loopr returns:

  • The value of the final expression, which has access to the accumulators, or
  • If no final is given...
    • With zero accumulators, returns nil
    • With one accumulator, returns that accumulator
    • With multiple accumulators, returns a vector of each.

For example,

(loopr [sum 0] [x [1 2 3]] (recur (+ sum x)))

returns 6: the sum of 1, 2 and 3.

This would typically be written as (reduce + [1 2 3]), and for single accumulators or single loops using reduce or loop is often more concise. Loopred's power comes from its ability to carry multiple accumulators and to traverse multiple dimensions. For instance, to get the mean of all elements in a matrix:

(loopr [count 0 sum 0] [row [[1 2 3] [4 5 6] [7 8 9]] x row] (recur (inc count) (+ sum x)) (/ sum count)) ; returns 45/9 = 5

Here, we have a body which recurs, and a final expression (/ sum count), which is evaluated with the final value of the accumulators. Compare this to the equivalent nested reduce:

(let [[sum count] (reduce (fn [[count sum] row] (reduce (fn [[count sum] x] [(inc count) (+ sum x)]) [count sum] row)) [0 0] [[1 2 3] [4 5 6] [7 8 9]])] (/ sum count))

This requires an enclosing let binding to transform the loop results, two calls to reduce, each with their own function, creating and destructuring vectors at each level, and keeping track of accumulator initial values far from their point of use. The structure of accumulators is encoded in five places instead of two, which makes it harder to change accumulators later. It also requires deeper indentation. Here's the same loop expressed as a flat loop over seqs:

(loop [count 0 sum 0 rows [[1 2 3] [4 5 6] [7 8 9]] row (first rows)] (if-not (seq rows) (/ sum count) ; Done with iteration (if-not (seq row) ; Done with row; move on to next row (recur count sum (next rows) (first (next rows))) (let [[x & row'] row] (recur (inc count) (+ sum x) rows row')))))

This version is less indented but also considerably longer, and the interweaving of traversal machinery and accumulation logic makes it difficult to understand. It is also significantly slower than the nested reduce, on account of seq allocation--vectors can more efficiently reduce over their internal structure.

Depending on how many accumulators are at play, and which data structures are being traversed, it may be faster to use loop with an iterator, loop with aget, or reduce with a function. loopr compiles to (possibly nested) reduce when given a single accumulator, and to (possibly nested) loop with mutable iterators when given multiple accumulators. You can also control the iteration tactic for each collection explicitly:

(loopr [count 0 sum 0] [row [[1 2 3] [4 5 6] [7 8 9]] :via :reduce x row :via :iterator] (recur (inc count) (+ sum x)) (/ sum count))

This compiles into a reduce over rows, and a loop over each row using an iterators. For array iteration, use :via :array:

(loopr [sum 0] [x (long-array (range 10000)) :via :array] (recur (+ sum x))) ; => 49995000

Note that alength/aget are very sensitive to type hints; use lein check to ensure that you're not using reflection, and add type hints as necessary. On my older xeon, this is roughly an order of magnitude faster than (reduce + longs). For nested array reduction, make sure to hint inner collections, like so:

(loopr [sum 0] [row matrix :via :array x ^"[Ljava.lang.Long;" row :via :array] (recur (+ sum x)))))

Like loop, loopr supports early return. Any non (recur ...) form in tail position in the body is returned immediately, without visiting any other elements in the collection(s). To search for the first odd number in collection, returning that number and its index:

(loopr [i 0] [x [0 3 4 5]] (if (odd? x) {:i i, :x x} (recur (inc i)))) ; => {:i 1, :x 3}

When no accumulators are provided, loopr still iterates, returning any early-returned value, or the final expression when iteration completes, or nil otherwise. Here we find an key in a map by value. Note that we can also destructure in iterator bindings.

(loopr [] [[k v] {:x 1, :y 2}] (if (= v 2) k (recur)) :not-found) ; => :y

Like `loop`, but for reducing over (possibly nested) collections. Compared to
`loop`, makes iteration implicit. Compared to reduce, eliminates the need for
nested reductions, fn wrappers, and destructuring multiple accumulators.
Compared to `for`, loopr is eager, and lets you carry accumulators.

Takes an initial binding vector for accumulator variables, (like `loop`);
then a binding vector of loop variables to collections (like `for`); then a
body form, then an optional final form. Iterates over each element of the
collections, like `for` would, and evaluates body with that combination of
elements bound.

Like `loop`, the body should generally contain one or more (recur ...) forms
with new values for each accumulator. Any non-recur form in tail position
causes loopr to return that value immediately.

When the loop completes normally, loopr returns:

- The value of the final expression, which has access to the accumulators, or
- If no `final` is given...
  - With zero accumulators, returns `nil`
  - With one accumulator, returns that accumulator
  - With multiple accumulators, returns a vector of each.

For example,

  (loopr [sum 0]
         [x [1 2 3]]
    (recur (+ sum x)))

returns 6: the sum of 1, 2 and 3.

This would typically be written as `(reduce + [1 2 3])`, and for single
accumulators or single loops using `reduce` or `loop` is often more concise.
Loopred's power comes from its ability to carry multiple accumulators and to
traverse multiple dimensions. For instance, to get the mean of all elements
in a matrix:

  (loopr [count 0
          sum   0]
         [row [[1 2 3] [4 5 6] [7 8 9]]
          x   row]
    (recur (inc count) (+ sum x))
    (/ sum count))
  ; returns 45/9 = 5

Here, we have a body which recurs, and a final expression `(/ sum count)`,
which is evaluated with the final value of the accumulators. Compare this to
the equivalent nested reduce:

  (let [[sum count] (reduce (fn [[count sum] row]
                              (reduce (fn [[count sum] x]
                                        [(inc count) (+ sum x)])
                                      [count sum]
                                      row))
                            [0 0]
                            [[1 2 3] [4 5 6] [7 8 9]])]
    (/ sum count))

This requires an enclosing `let` binding to transform the loop results, two
calls to reduce, each with their own function, creating and destructuring
vectors at each level, and keeping track of accumulator initial values far
from their point of use. The structure of accumulators is encoded in five
places instead of two, which makes it harder to change accumulators later.
It also requires deeper indentation. Here's the same loop expressed as a
flat `loop` over seqs:

  (loop [count 0
         sum   0
         rows  [[1 2 3] [4 5 6] [7 8 9]]
         row   (first rows)]
    (if-not (seq rows)
      (/ sum count)       ; Done with iteration
      (if-not (seq row)   ; Done with row; move on to next row
        (recur count sum (next rows) (first (next rows)))
        (let [[x & row'] row]
          (recur (inc count) (+ sum x) rows row')))))

This version is less indented but also considerably longer, and the
interweaving of traversal machinery and accumulation logic makes it
difficult to understand. It is also significantly slower than the nested
`reduce`, on account of seq allocation--vectors can more efficiently reduce
over their internal structure.

Depending on how many accumulators are at play, and which data structures are
being traversed, it may be faster to use `loop` with an iterator, `loop` with
`aget`, or `reduce` with a function. loopr compiles to (possibly nested)
`reduce` when given a single accumulator, and to (possibly nested) `loop`
with mutable iterators when given multiple accumulators. You can also control
the iteration tactic for each collection explicitly:

  (loopr [count 0
          sum   0]
         [row [[1 2 3] [4 5 6] [7 8 9]] :via :reduce
          x   row                       :via :iterator]
    (recur (inc count) (+ sum x))
    (/ sum count))

This compiles into a `reduce` over rows, and a `loop` over each row using an
iterators. For array iteration, use `:via :array`:

  (loopr [sum 0]
         [x (long-array (range 10000)) :via :array]
         (recur (+ sum x)))
  ; => 49995000

Note that alength/aget are *very* sensitive to type hints; use `lein check`
to ensure that you're not using reflection, and add type hints as necessary.
On my older xeon, this is roughly an order of magnitude faster than (reduce +
longs). For nested array reduction, make sure to hint inner collections, like
so:

  (loopr [sum 0]
         [row                        matrix :via :array
          x   ^"[Ljava.lang.Long;" row    :via :array]
         (recur (+ sum x)))))

Like `loop`, `loopr` supports early return. Any non `(recur ...)` form in
tail position in the body is returned immediately, without visiting any other
elements in the collection(s). To search for the first odd number in
collection, returning that number and its index:

  (loopr [i 0]
         [x [0 3 4 5]]
         (if (odd? x)
           {:i i, :x x}
           (recur (inc i))))
  ; => {:i 1, :x 3}

When no accumulators are provided, loopr still iterates, returning any
early-returned value, or the final expression when iteration completes, or
`nil` otherwise. Here we find an key in a map by value. Note that we can also
destructure in iterator bindings.

  (loopr []
         [[k v] {:x 1, :y 2}]
         (if (= v 2)
           k
           (recur))
         :not-found)
  ; => :y
sourceraw docstring

loopr-arrayclj

(loopr-array accumulator-bindings
             [{:keys [lhs rhs] :as eb} & more-element-bindings]
             body
             {:keys [acc-count] :as opts})

A single loopr layer specialized for traversal over arrays. Builds a form which returns a single accumulator, or a vector of accumulators, or a Return, after traversing each x in xs using aget.

A single loopr layer specialized for traversal over arrays. Builds a form
which returns a single accumulator, or a vector of accumulators, or a Return,
after traversing each x in xs using `aget`.
sourceraw docstring

loopr-helperclj

(loopr-helper accumulator-bindings element-bindings body opts)

Helper for building each stage of a nested loopr. Takes an accumulator binding vector, a vector of element bindings maps {:lhs, :rhs, :name}, a body expression, and an option map with

:acc-count - The number of accumulators

Helper for building each stage of a nested loopr. Takes an accumulator
binding vector, a vector of element bindings maps {:lhs, :rhs, :name}, a
body expression, and an option map with

:acc-count - The number of accumulators
sourceraw docstring

loopr-iteratorclj

(loopr-iterator accumulator-bindings
                [{:keys [lhs rhs] :as eb} & more-element-bindings]
                body
                {:keys [acc-count] :as opts})

A single loopr layer specialized for traversal using a mutable iterator. Builds a form which returns a single accumulator, or a vector of accumulators, or a Return, after traversing each x in xs (and more element bindings within).

A single loopr layer specialized for traversal using a mutable iterator.
Builds a form which returns a single accumulator, or a vector of
accumulators, or a Return, after traversing each x in xs (and more element
bindings within).
sourceraw docstring

loopr-reduceclj

(loopr-reduce accumulator-bindings
              [{:keys [lhs rhs] :as eb} & more-element-bindings]
              body
              {:keys [acc-count] :as opts})

A single loopr layer specialized for traversal using reduce. Builds a form which returns a single accumulator, or a vector of accumulators, or a Return, after traversing each x in xs (and more element bindings within). Reduce is often faster over Clojure data structures than an iterator.

A single loopr layer specialized for traversal using `reduce`. Builds a form
which returns a single accumulator, or a vector of accumulators, or a Return,
after traversing each x in xs (and more element bindings within). Reduce is
often faster over Clojure data structures than an iterator.
sourceraw docstring

mutable-acc-cache*clj

A mutable cache of mutable accumulator types we've generated. Stores a map of type hints (e.g. ['long 'Object]) to classes (e.g. MutableAcc-long-Object).

A mutable cache of mutable accumulator types we've generated. Stores
a map of type hints (e.g. ['long 'Object]) to classes (e.g.
MutableAcc-long-Object).
sourceraw docstring

mutable-acc-class-loaderclj

The classloader we use to load mutable acc-types. We store this to prevent it from being GCed and rendering types unusable.

The classloader we use to load mutable acc-types. We store this to
prevent it from being GCed and rendering types unusable.
sourceraw docstring

mutable-acc-typeclj

(mutable-acc-type types)

Takes a list of types as symbols and returns the class of a mutable accumulator which can store those types. May compile new classes on the fly, or re-use a cached class.

This method largely courtesy of Justin Conklin! hat tip

Takes a list of types as symbols and returns the class of a mutable
accumulator which can store those types. May compile new classes on the fly,
or re-use a cached class.

This method largely courtesy of Justin Conklin! *hat tip*
sourceraw docstring

real-pmapclj

(real-pmap f coll)

Like pmap, but spawns tasks immediately, and launches real Threads instead of using a bounded threadpool. Useful when your tasks might block on each other, and you don't want to deadlock by exhausting the default clojure worker threadpool halfway through the collection. For instance,

(let [n 1000
      b (CyclicBarrier. n)]
  (pmap (fn [i] [i (.await b)]) (range n)))

... deadlocks, but replacing pmap with real-pmap works fine.

If any thread throws an exception, all mapping threads are interrupted, and the original exception is rethrown. This prevents deadlock issues where mapping threads synchronize on some resource (like a cyclicbarrier or countdownlatch), but one crashes, causing other threads to block indefinitely on the barrier. Note that we do not include a ConcurrentExecutionException wrapper.

All pmap threads should terminate before real-pmap returns or throws. This prevents race conditions where mapping threads continue doing work concurrently with, say, clean-up code intended to run after the call to (pmap).

If the thread calling (pmap) itself is interrupted, all bets are off.

Like pmap, but spawns tasks immediately, and launches real Threads instead
of using a bounded threadpool. Useful when your tasks might block on each
other, and you don't want to deadlock by exhausting the default clojure
worker threadpool halfway through the collection. For instance,

    (let [n 1000
          b (CyclicBarrier. n)]
      (pmap (fn [i] [i (.await b)]) (range n)))

... deadlocks, but replacing `pmap` with `real-pmap` works fine.

If any thread throws an exception, all mapping threads are interrupted, and
the original exception is rethrown. This prevents deadlock issues where
mapping threads synchronize on some resource (like a cyclicbarrier or
countdownlatch), but one crashes, causing other threads to block indefinitely
on the barrier. Note that we do not include a ConcurrentExecutionException
wrapper.

All pmap threads should terminate before real-pmap returns or throws. This
prevents race conditions where mapping threads continue doing work
concurrently with, say, clean-up code intended to run after the call to
(pmap).

If the thread calling (pmap) itself is interrupted, all bets are off.
sourceraw docstring

real-pmap-helperclj

(real-pmap-helper f coll)

Helper for real-pmap. Maps f over coll, collecting results and exceptions. Returns a tuple of [results, exceptions], where results is a sequence of results from calling f on each element (nil if f throws); and exceptions is a sequence of exceptions thrown by f, in roughly time order.

Helper for real-pmap. Maps f over coll, collecting results and exceptions.
Returns a tuple of [results, exceptions], where results is a sequence of
results from calling `f` on each element (`nil` if f throws); and exceptions
is a sequence of exceptions thrown by f, in roughly time order.
sourceraw docstring

reducercljmacro

(reducer accumulator-bindings element-bindings body & [final :as final-forms])

Syntactic sugar for writing reducing/transducing functions with multiple accumulators. Much like loopr, this takes a binding vector of loop variables and their initial values, a single binding vector for an element of the collection, a body which calls (recur) with new values of the accumulators (or doesn't recur, for early return), and a final expression, which is evaluated with the accumulators and returned at the end of the reduction. Returns a function with 0, 1, and 2-arity forms suitable for use with transduce.

(transduce identity (reducer [sum 0, count 0] [x] (recur (+ sum x) (inc count)) (/ sum count)) [1 2 2]) ; => 5/3

This is logically equivalent to:

(transduce identity (fn ([] [0 0]) ([[sum count]] (/ sum count)) ([[sum count] x] [(+ sum x) (inc count)])) [1 2 2])

For zero and one-accumulator forms, these are equivalent. However, reducer is faster for reducers with more than one accumulator. Its identity arity creates unsynchronized mutable accumulators (including primitive types, if you hint your accumulator variables), and the reduction arity mutates that state in-place to skip the need for vector creation & destructuring on each reduction step. This makes it about twice as fast as a plain old reducer fn.

These functions also work out-of-the-box with Tesser, clojure.core.reducers, and other Clojure fold libraries.

If you want to use a final expression with a reduced form and multiple accumulators, add an :as foo to your accumulator binding vector. This symbol will be available in the final expression, bound to a vector of accumulators if the reduction completes normally, or bound to whatever was returned early. Using :as foo signals that you intend to use early return and may not have accumulators any more--hence the accumulator bindings will not be available in the final expression.

(transduce identity (reducer [sum 0, count 0 :as acc] [x] (if (= count 2) [:early sum] (recur (+ sum x) (inc count))) [:final acc]) [4 1 9 9 9]) ; => [:early 5]

Syntactic sugar for writing reducing/transducing functions with multiple
accumulators. Much like `loopr`, this takes a binding vector of loop
variables and their initial values, a single binding vector for an element of
the collection, a body which calls (recur) with new values of the
accumulators (or doesn't recur, for early return), and a final expression,
which is evaluated with the accumulators and returned at the end of the
reduction. Returns a function with 0, 1, and 2-arity forms suitable for use
with `transduce`.

  (transduce identity
             (reducer [sum 0, count 0]
                      [x]
                      (recur (+ sum x) (inc count))
                      (/ sum count))
             [1 2 2])
  ; => 5/3

This is logically equivalent to:

  (transduce identity
             (fn ([] [0 0])
                 ([[sum count]] (/ sum count))
                 ([[sum count] x]
                  [(+ sum x) (inc count)]))
             [1 2 2])

For zero and one-accumulator forms, these are equivalent. However, `reducer`
is faster for reducers with more than one accumulator. Its identity arity
creates unsynchronized mutable accumulators (including primitive types, if
you hint your accumulator variables), and the reduction arity mutates that
state in-place to skip the need for vector creation & destructuring on each
reduction step. This makes it about twice as fast as a plain old reducer fn.

These functions also work out-of-the-box with Tesser, clojure.core.reducers,
and other Clojure fold libraries.

If you want to use a final expression with a `reduced` form *and* multiple
accumulators, add an `:as foo` to your accumulator binding vector. This
symbol will be available in the final expression, bound to a vector of
accumulators if the reduction completes normally, or bound to whatever was
returned early. Using `:as foo` signals that you intend to use early return
and may not *have* accumulators any more--hence the accumulator bindings will
not be available in the final expression.

  (transduce identity
             (reducer [sum 0, count 0 :as acc]
                      [x]
                      (if (= count 2)
                        [:early sum]
                        (recur (+ sum x) (inc count)))
                      [:final acc])
             [4 1 9 9 9])
  ; => [:early 5]
sourceraw docstring

rewrite-tailsclj

(rewrite-tails f form)

Takes a Clojure form and invokes f on each of its tail forms--the final expression in a do or let, both branches of an if, values of a case, etc.

Takes a Clojure form and invokes f on each of its tail forms--the final
expression in a do or let, both branches of an if, values of a case, etc.
sourceraw docstring

rewrite-tails*clj

(rewrite-tails* f form)

Helper for rewrite-tails which doesn't macroexpand.

Helper for rewrite-tails which doesn't macroexpand.
sourceraw docstring

type->descclj

(type->desc t)

Takes a type (e.g. 'int, 'objects, 'longs, 'Foo) and converts it to a JVM type descriptor like "I".

Takes a type (e.g. 'int, 'objects, 'longs, 'Foo) and converts it to a JVM
type descriptor like "I".
sourceraw docstring

with-retrycljmacro

(with-retry initial-bindings & body)

It's really fucking inconvenient not being able to recur from within (catch) expressions. This macro wraps its body in a (loop [bindings] (try ...)). Provides a (retry & new bindings) form which is usable within (catch) blocks: when this form is returned by the body, the body will be retried with the new bindings. For instance,

(with-retry [attempts 5]
  (network-request...)
  (catch RequestFailed e
    (if (< 1 attempts)
      (retry (dec attempts))
      (throw e))))
It's really fucking inconvenient not being able to recur from within (catch)
expressions. This macro wraps its body in a (loop [bindings] (try ...)).
Provides a (retry & new bindings) form which is usable within (catch) blocks:
when this form is returned by the body, the body will be retried with the new
bindings. For instance,

    (with-retry [attempts 5]
      (network-request...)
      (catch RequestFailed e
        (if (< 1 attempts)
          (retry (dec attempts))
          (throw e))))
sourceraw docstring

cljdoc is a website building & hosting documentation for Clojure/Script libraries

× close