Liking cljdoc? Tell your friends :D

plumbing.core

Utility belt for Clojure in the wild

Utility belt for Clojure in the wild
raw docstring

<-clj/smacro

(<- & body)

Converts a ->> to a ->

(->> (range 10) (map inc) (<- (doto prn)) (reduce +))

Jason W01fe is happy to give a talk anywhere any time on the calculus of arrow macros

Converts a ->> to a ->

(->> (range 10) (map inc) (<- (doto prn)) (reduce +))

Jason W01fe is happy to give a talk anywhere any time on
the calculus of arrow macros
sourceraw docstring

?>clj/smacro

(?> arg do-it? & rest)

Conditional single-arrow operation (-> m (?> add-kv? (assoc :k :v)))

Conditional single-arrow operation (-> m (?> add-kv? (assoc :k :v)))
sourceraw docstring

?>>clj/smacro

(?>> do-it? & args)

Conditional double-arrow operation (->> nums (?>> inc-all? (map inc)))

Conditional double-arrow operation (->> nums (?>> inc-all? (map inc)))
sourceraw docstring

aconcatclj/s

(aconcat s)

Like (apply concat s) but lazier (and shorter)

Like (apply concat s) but lazier (and shorter) 
sourceraw docstring

as->>clj/smacro

(as->> name & forms-and-expr)

Like as->, but can be used in double arrow.

Like as->, but can be used in double arrow.
sourceraw docstring

assoc-whenclj/s

(assoc-when m & kvs)

Like assoc but only assocs when value is truthy

Like assoc but only assocs when value is truthy
sourceraw docstring

conj-whenclj/s

(conj-when coll x)
(conj-when coll x & xs)

Like conj but ignores non-truthy values

Like conj but ignores non-truthy values
sourceraw docstring

cons-whenclj/s

(cons-when x s)

Like cons but does nothing if x is non-truthy.

Like cons but does nothing if x is non-truthy.
sourceraw docstring

count-whenclj/s

(count-when pred xs)

Returns # of elements of xs where pred holds

Returns # of elements of xs where pred holds
sourceraw docstring

defnkclj/smacro

(defnk & defnk-args)

Analogy: fn:fnk :: defn::defnk

Analogy: fn:fnk :: defn::defnk
sourceraw docstring

dissoc-inclj/s

(dissoc-in m [k & ks])

Dissociate this keyseq from m, removing any empty maps created as a result (including at the top-level).

Dissociate this keyseq from m, removing any empty maps created as a result
(including at the top-level).
sourceraw docstring

distinct-byclj/s

(distinct-by f xs)

Returns elements of xs which return unique values according to f. If multiple elements of xs return the same value under f, the first is returned

Returns elements of xs which return unique
values according to f. If multiple elements of xs return the same
value under f, the first is returned
sourceraw docstring

distinct-fastclj

(distinct-fast xs)

Like clojure.core/distinct, but faster. Uses Java's equal/hash, so may produce incorrect results if given values that are = but not .equal

Like clojure.core/distinct, but faster.
Uses Java's equal/hash, so may produce incorrect results if
given values that are = but not .equal
sourceraw docstring

distinct-idclj

(distinct-id xs)

Like distinct but uses reference rather than value identity, very clojurey

Like distinct but uses reference rather than value identity, very clojurey
sourceraw docstring

fn->clj/smacro

(fn-> & body)

Equivalent to `(fn [x] (-> x ~@body))

Equivalent to `(fn [x] (-> x ~@body))
sourceraw docstring

fn->>clj/smacro

(fn->> & body)

Equivalent to `(fn [x] (->> x ~@body))

Equivalent to `(fn [x] (->> x ~@body))
sourceraw docstring

fnkclj/smacro

(fnk & args)

Keyword fn, using letk. Generates a prismatic/schema schematized fn that accepts a single explicit map i.e., (f {:foo :bar}).

Explicit top-level map structure will be recorded in output spec, or to capture implicit structure use an explicit prismatic/schema hint on the function name.

Individual inputs can also be schematized by putting :- schemas after the binding symbol. Schemas can also be used on & more symbols to describe additional map inputs, or on entire [] bindings to override the automatically generated schema for the contents (caveat emptor).

By default, input schemas allow for arbitrary additional mappings ({s/Keyword s/Any}) unless explicit binding or & more schemas are provided.

Keyword fn, using letk.  Generates a prismatic/schema schematized fn that
accepts a single explicit map i.e., (f {:foo :bar}).

Explicit top-level map structure will be recorded in output spec, or
to capture implicit structure use an explicit prismatic/schema hint on the
function name.

Individual inputs can also be schematized by putting :- schemas after the
binding symbol.  Schemas can also be used on & more symbols to describe
additional map inputs, or on entire [] bindings to override the automatically
generated schema for the contents (caveat emptor).

By default, input schemas allow for arbitrary additional mappings
({s/Keyword s/Any}) unless explicit binding or & more schemas are provided.
sourceraw docstring

for-mapclj/smacro

(for-map seq-exprs key-expr val-expr)
(for-map m-sym seq-exprs key-expr val-expr)

Like 'for' for building maps. Same bindings except the body should have a key-expression and value-expression. If a key is repeated, the last value (according to "for" semantics) will be retained.

(= (for-map [i (range 2) j (range 2)] [i j] (even? (+ i j))) {[0 0] true, [0 1] false, [1 0] false, [1 1] true})

An optional symbol can be passed as a first argument, which will be bound to the transient map containing the entries produced so far.

Like 'for' for building maps. Same bindings except the body should have a
key-expression and value-expression. If a key is repeated, the last
value (according to "for" semantics) will be retained.

(= (for-map [i (range 2) j (range 2)] [i j] (even? (+ i j)))
   {[0 0] true, [0 1] false, [1 0] false, [1 1] true})

An optional symbol can be passed as a first argument, which will be
bound to the transient map containing the entries produced so far.
sourceraw docstring

frequencies-fastclj

(frequencies-fast xs)

Like clojure.core/frequencies, but faster. Uses Java's equal/hash, so may produce incorrect results if given values that are = but not .equal

Like clojure.core/frequencies, but faster.
Uses Java's equal/hash, so may produce incorrect results if
given values that are = but not .equal
sourceraw docstring

get-and-set!clj/s

(get-and-set! a new-val)

Like reset! but returns old-val

Like reset! but returns old-val
sourceraw docstring

grouped-mapclj/s

(grouped-map key-fn map-fn coll)

Like group-by, but accepts a map-fn that is applied to values before collected.

Like group-by, but accepts a map-fn that is applied to values before
collected.
sourceraw docstring

if-letkclj/smacro

(if-letk bindings then)
(if-letk bindings then else)

bindings => binding-form test

If test is true, evaluates then with binding-form bound to the value of test, if not, yields else

bindings => binding-form test

If test is true, evaluates then with binding-form bound to the value of
test, if not, yields else
sourceraw docstring

indexedclj/s

(indexed s)

Returns [idx x] for x in seqable s

Returns [idx x] for x in seqable s
sourceraw docstring

interleave-allclj/s

(interleave-all & colls)

Analogy: partition:partition-all :: interleave:interleave-all

Analogy: partition:partition-all :: interleave:interleave-all
sourceraw docstring

keywordize-mapclj/sdeprecated

(keywordize-map x)

DEPRECATED. prefer clojure.walk/keywordize-keys.

Recursively convert maps in m (including itself) to have keyword keys instead of string

DEPRECATED.  prefer clojure.walk/keywordize-keys.

Recursively convert maps in m (including itself)
to have keyword keys instead of string
sourceraw docstring

lazy-getclj/smacro

(lazy-get m k d)

Like get but lazy about default

Like get but lazy about default
sourceraw docstring

letkclj/smacro

(letk bindings & body)

Keyword let. Accepts an interleaved sequence of binding forms and map forms like: (letk [[a {b 2} [:f g h] c d {e 4} :as m & more] a-map ...] & body) a, c, d, and f are required keywords, and letk will barf if not in a-map. b and e are optional, and will be bound to default values if not present. g and h are required keys in the map found under :f. m will be bound to the entire map (a-map). more will be bound to all the unbound keys (ie (dissoc a-map :a :b :c :d :e)). :as and & are both optional, but must be at the end in the specified order if present. The same symbol cannot be bound multiple times within the same destructing level.

Optional values can reference symbols bound earlier within the same binding, i.e., (= [2 2] (let [a 1] (letk [[a {b a}] {:a 2}] [a b]))) but (= [2 1] (let [a 1] (letk [[{b a} a] {:a 2}] [a b])))

If present, :as and :& symbols are bound before other symbols within the binding.

Namespaced keys are supported by specifying fully-qualified key in binding form. The bound symbol uses the name portion of the namespaced key, i.e, (= 1 (letk [[a/b] {:a/b 1}] b)).

Map destructuring bindings can be mixed with ordinary symbol bindings.

Keyword let.  Accepts an interleaved sequence of binding forms and map forms like:
(letk [[a {b 2} [:f g h] c d {e 4} :as m & more] a-map ...] & body)
a, c, d, and f are required keywords, and letk will barf if not in a-map.
b and e are optional, and will be bound to default values if not present.
g and h are required keys in the map found under :f.
m will be bound to the entire map (a-map).
more will be bound to all the unbound keys (ie (dissoc a-map :a :b :c :d :e)).
:as and & are both optional, but must be at the end in the specified order if present.
The same symbol cannot be bound multiple times within the same destructing level.

Optional values can reference symbols bound earlier within the same binding, i.e.,
(= [2 2] (let [a 1] (letk [[a {b a}] {:a 2}] [a b]))) but
(= [2 1] (let [a 1] (letk [[{b a} a] {:a 2}] [a b])))

If present, :as and :& symbols are bound before other symbols within the binding.

Namespaced keys are supported by specifying fully-qualified key in binding form. The bound
symbol uses the _name_ portion of the namespaced key, i.e,
(= 1 (letk [[a/b] {:a/b 1}] b)).

Map destructuring bindings can be mixed with ordinary symbol bindings.
sourceraw docstring

map-from-keysclj/s

(map-from-keys f ks)

Build map k -> (f k) for keys in ks

Build map k -> (f k) for keys in ks
sourceraw docstring

map-from-valsclj/s

(map-from-vals f vs)

Build map (f v) -> v for vals in vs

Build map (f v) -> v for vals in vs
sourceraw docstring

map-keysclj/s

(map-keys f m)

Build map (f k) -> v for [k v] in map m

Build map (f k) -> v for [k v] in map m
sourceraw docstring

map-valsclj/s

(map-vals f m)

Build map k -> (f v) for [k v] in map, preserving the initial type

Build map k -> (f v) for [k v] in map, preserving the initial type
sourceraw docstring

mapplyclj/s

(mapply f m)
(mapply f arg & args)

Like apply, but applies a map to a function with positional map arguments. Can take optional initial args just like apply.

Like apply, but applies a map to a function with positional map
arguments. Can take optional initial args just like apply.
sourceraw docstring

memoized-fnclj/smacro

(memoized-fn name args & body)

Like fn, but memoized (including recursive calls).

The clojure.core memoize correctly caches recursive calls when you do a top-level def of your memoized function, but if you want an anonymous fibonacci function, you must use memoized-fn rather than memoize to cache the recursive calls.

Like fn, but memoized (including recursive calls).

The clojure.core memoize correctly caches recursive calls when you do a top-level def
of your memoized function, but if you want an anonymous fibonacci function, you must use
memoized-fn rather than memoize to cache the recursive calls.
sourceraw docstring

millisclj/s

(millis)
source

positionsclj/s

(positions f s)

Returns indices idx of sequence s where (f (nth s idx))

Returns indices idx of sequence s where (f (nth s idx))
sourceraw docstring

rsort-byclj/s

Like sort-by, but prefers higher values rather than lower ones.

Like sort-by, but prefers higher values rather than lower ones.
sourceraw docstring

safe-getclj/s

(safe-get m k)

Like get but throw an exception if not found

Like get but throw an exception if not found
sourceraw docstring

safe-get-inclj/s

(safe-get-in m ks)

Like get-in but throws exception if not found

Like get-in but throws exception if not found
sourceraw docstring

singletonclj/s

(singleton xs)

returns (first xs) when xs has only 1 element

returns (first xs) when xs has only 1 element
sourceraw docstring

sumclj/s

(sum xs)
(sum f xs)

Return sum of (f x) for each x in xs

Return sum of (f x) for each x in xs
sourceraw docstring

swap-pair!clj/s

(swap-pair! a f)
(swap-pair! a f & args)

Like swap! but returns a pair [old-val new-val]

Like swap! but returns a pair [old-val new-val]
sourceraw docstring

unchunkclj/s

(unchunk s)

Takes a seqable and returns a lazy sequence that is maximally lazy and doesn't realize elements due to either chunking or apply.

Useful when you don't want chunking, for instance, (first awesome-website? (map slurp +a-bunch-of-urls+)) may slurp up to 31 unneed webpages, wherease (first awesome-website? (map slurp (unchunk +a-bunch-of-urls+))) is guaranteed to stop slurping after the first awesome website.

Taken from http://stackoverflow.com/questions/3407876/how-do-i-avoid-clojures-chunking-behavior-for-lazy-seqs-that-i-want-to-short-ci

Takes a seqable and returns a lazy sequence that
 is maximally lazy and doesn't realize elements due to either
 chunking or apply.

 Useful when you don't want chunking, for instance,
 (first awesome-website? (map slurp +a-bunch-of-urls+))
 may slurp up to 31 unneed webpages, wherease
 (first awesome-website? (map slurp (unchunk +a-bunch-of-urls+)))
 is guaranteed to stop slurping after the first awesome website.

Taken from http://stackoverflow.com/questions/3407876/how-do-i-avoid-clojures-chunking-behavior-for-lazy-seqs-that-i-want-to-short-ci
sourceraw docstring

update-in-whenclj/s

(update-in-when m key-seq f & args)

Like update-in but returns m unchanged if key-seq is not present.

Like update-in but returns m unchanged if key-seq is not present.
sourceraw docstring

when-letkclj/smacro

(when-letk bindings & body)

bindings => binding-form test

When test is true, evaluates body with binding-form bound to the value of test

bindings => binding-form test

When test is true, evaluates body with binding-form bound to the value of test
sourceraw docstring

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

× close