Clojure: how to move vector elements in a map elegantly - clojure

In clojure, I am trying to accomplish the following logic:
Input:
{:a [11 22 33] :b [10 20 30]}, 2
Output:
{:a [11] :b [10 20 30 22 33]}
i.e. Move the last 2 elements from :a to :b
Is there a clojurish way for this operation?

Since you're effectively modifying both mappings in the map, it's probably easiest to explicitly deconstruct the map and just return the new map via a literal, using subvec and into for the vector manipulation:
(defn move [m n]
(let [{:keys [a b]} m
i (- (count a) n)
left (subvec a 0 i)
right (subvec a i)]
{:a left :b (into b right)}))
(move {:a [11 22 33] :b [10 20 30]} 2)
;;=> {:a [11], :b [10 20 30 22 33]}
As a bonus, this particular implementation is both very idiomatic and very fast.
Alternatively, using the split-at' function from here, you could write it like this:
(defn split-at' [n v]
[(subvec v 0 n) (subvec v n)])
(defn move [m n]
(let [{:keys [a b]} m
[left right] (split-at' (- (count a) n) a)]
{:a left :b (into b right)}))

First, using the sub-vec in the other answers will throw an IndexOutOfBoundsException when the number of elements to be moved is greater than the size of the collection.
Secondly, the destructuring, the way most have done here, couples the function to one specific data structure. This being, a map with keys :a and :b and values for these keys that are vectors. Now if you change one of the keys in the input, then you need to also change it in move function.
My solution follows:
(defn move [colla collb n]
(let [newb (into (into [] collb) (take-last n colla))
newa (into [] (drop-last n colla))]
[newa newb]))
This should work for any collection and will return vector of 2 vectors. My solution is far more reusable. Try:
(move (range 100000) (range 200000) 10000)
Edit:
Now you can use first and second to access the vector you need in the return.

I would do it just a little differently than Josh:
(defn tx-vals [ {:keys [a b]} num-to-move ]
{:a (drop-last num-to-move a)
:b (concat b (take-last num-to-move a)) } )
(tx-vals {:a [11 22 33], :b [10 20 30]} 2)
=> {:a (11), :b (10 20 30 22 33)}
Update
Sometimes it may be more convenient to use the clojure.core/split-at function as follows:
(defn tx-vals-2 [ {:keys [a b]} num-to-move ]
(let [ num-to-keep (- (count a) num-to-move)
[a-head, a-tail] (split-at num-to-keep a) ]
{ :a a-head
:b (concat b a-tail) } ))
If vectors are preferred on output (my favorite!), just do:
(defn tx-vals-3 [ {:keys [a b]} num-to-move ]
(let [ num-to-keep (- (count a) num-to-move)
[a-head, a-tail] (split-at num-to-keep a) ]
{:a (vec a-head)
:b (vec (concat b a-tail))} ))
to get the results:
(tx-vals-2 data 2) => {:a (11), :b (10 20 30 22 33)}
(tx-vals-3 data 2) => {:a [11], :b [10 20 30 22 33]}

(defn f [{:keys [a b]} n]
(let [last-n (take-last n a)]
{:a (into [] (take (- (count a) n) a))
:b (into b last-n)}))
(f {:a [11 22 33] :b [10 20 30]} 2)
=> {:a [11], :b [10 20 30 22 33]}

In case if the order of those items does not matter, here is my attempt:
(def m {:a [11 22 33] :b [10 20 30]})
(defn so-42476918 [{:keys [a b]} n]
(zipmap [:a :b] (map vec (split-at (- (count a) n) (concat a b)))))
(so-42476918 m 2)
gives:
{:a [11], :b [22 33 10 20 30]}

i would go with an approach, which differs a bit from the previous answers (well, technically it is the same, but it differs on the application-scale level).
First of all, transferring data between two collections is quite a frequent task, so it at least deserves some special utility function for that in your library:
(defn transfer [from to n & {:keys [get-from put-to]
:or {:get-from :start :put-to :end}}]
(let [f (if (= get-from :end)
(partial split-at (- (count from) n))
(comp reverse (partial split-at n)))
[from swap] (f from)]
[from (if (= put-to :start)
(concat swap to)
(concat to swap))]))
ok, it looks verbose, but it lets you transfer data from start/end of one collection to start/end of the other:
user> (transfer [1 2 3] [4 5 6] 2)
[(3) (4 5 6 1 2)]
user> (transfer [1 2 3] [4 5 6] 2 :get-from :end)
[(1) (4 5 6 2 3)]
user> (transfer [1 2 3] [4 5 6] 2 :put-to :start)
[(3) (1 2 4 5 6)]
user> (transfer [1 2 3] [4 5 6] 2 :get-from :end :put-to :start)
[(1) (2 3 4 5 6)]
So what's left, is to make your domain specific function on top of it:
(defn move [data n]
(let [[from to] (transfer (:a data) (:b data) n
:get-from :end
:put-to :end)]
(assoc data
:a (vec from)
:b (vec to))))
user> (move {:a [1 2 3 4 5] :b [10 20 30 40] :c [:x :y]} 3)
{:a [1 2], :b [10 20 30 40 3 4 5], :c [:x :y]}

Related

Clojure nested for loop with index

I've been trying to idiomatically loop through a nested vector like below:
[[:a 1 :b 1 :c 1] [:a 1 :b 1 :c 3] [:a 1 :b 1 :c 1]]
I also need to return the coordinates once I've found a value.
eg The call (find-key-value 3) should return [1 2]
This is what I have so far but its not giving me the output that I need it would return ([] [] [] [] [] [1 2] [] [] []) where as i only need [1 2]
(defn find-key-value
[array value]
(for [x (range 0 (count array))]
(loop [y 0
ret []]
(cond
(= y (count (nth array x))) [x y]
:else (if (= value (get-in array [x y]))
(recur (+ 1 y) (conj ret [x y]))
(recur (+ 1 y) ret))))))
Anyone have any ideas on how I can fix my code to get to my desired solution or have a better approach in mind!
A list comprehension can be used to find coordinates of all values satisfying a predicate:
(defn find-locs [pred coll]
(for [[i vals] (map-indexed vector coll)
[j val] (map-indexed vector vals)
:when (pred val)]
[i j]))
(find-locs #(= 3 %) [[:a 1 :b 1 :c 1] [:a 1 :b 1 :c 3] [:a 1 :b 1 :c 1]])
=> ([1 5])
(find-locs zero? [[0 1 1] [1 1 1] [1 0 1]])
=> ([0 0] [2 1])
The posed question seems to imply that the keywords in the inputs should be ignored, in which case the answer becomes:
(defn find-locs-ignore-keyword [pred coll]
(for [[i vals] (map-indexed vector coll)
[j val] (map-indexed vector (remove keyword? vals))
:when (pred val)]
[i j]))
(find-locs-ignore-keyword #(= 3 %) [[:a 1 :b 1 :c 1] [:a 1 :b 1 :c 3] [:a 1 :b 1 :c 1]])
=> ([1 2])
there is a function in clojure core, which exactly suites the task: keep-indexed. Which is exactly indexed map + filter:
(defn find-val-idx [v data]
(ffirst (keep-indexed
(fn [i row]
(seq (keep-indexed
(fn [j [_ x]] (when (= v x) [i j]))
(partition 2 row))))
data)))
user> (find-val-idx 3 [[:a 1 :b 1 :c 1] [:a 1 :b 1 :c 3] [:a 1 :b 1 :c 1]])
;;=> [1 2]
user> (find-val-idx 10 [[:a 1 :b 1 :c 1] [:a 1 :b 1 :c 3] [:a 1 :b 1 :c 1]])
;;=> nil
user> (find-val-idx 1 [[:a 1 :b 1 :c 1] [:a 1 :b 1 :c 3] [:a 1 :b 1 :c 1]])
;;=> [0 0]
There is a map-indexed that is sometimes helpful. See the Clojure Cheatsheet and other docs listed here.
==> Could you please edit the question to clarify the search conditions?
Here is an outline of what you could do to search for the desired answer:
(ns tst.demo.core
(:use demo.core tupelo.core tupelo.test))
(defn coords
[data pred]
(let [result (atom [])]
(doseq [row (range (count data))
col (range (count (first data)))]
(let [elem (get-in data [row col])
keeper? (pred elem)]
(when keeper?
(swap! result conj [row col]))))
(deref result)))
(dotest
(let [data [[11 12 13]
[21 22 23]
[31 32 33]]
ends-in-2? (fn [x] (zero? (mod x 2)))]
(is= (coords data ends-in-2?)
[[0 1]
[1 1]
[2 1]])))
It is based on the same template project as the docs. There are many variations (for example, you could use reduce instead of an atom).
Please review the docs listed above.
(defn vec-to-map [v] (into {} (into [] (map vec (partition 2 v)))))
(defn vec-vals [v] (vals (vec-to-map v)))
(defn map-vec-index [v el] (.indexOf (vec-vals v) el))
(defn find-val-coord
([arr val] (find-val-coord arr val 0))
([arr val counter]
(let [row (first arr)
idx (map-vec-index row val)]
(cond (< 0 idx) [counter idx]
:else (recur (rest arr) val (inc counter))))))
(find-val-coord arr 3) ;; => [1 2]
We can also write functions to pick value or corresponding key
from array when coordinate is given:
(defn vec-keys [v] (keys (vec-to-map v)))
(defn get-val-coord [arr coord]
(nth (vec-vals (nth arr (first coord))) (second coord)))
(defn get-key-coord [arr coord]
(nth (vec-keys (nth arr (first coord))) (second coord)))
(get-val-coord arr [1 2]) ;; => 3
(get-key-coord arr [1 2]) ;; => :c
I might be over-engineering this answer slightly, but here is a non-recursive and non-lazy approach based on a single loop that will work for arbitrary and mixed levels of nesting and won't suffer from stack overflow due to recursion:
(defn find-key-value [array value]
(loop [remain [[[] array]]]
(if (empty? remain)
nil
(let [[[path x] & remain] remain]
(cond (= x value) path
(sequential? x)
(recur (into remain
(comp (remove keyword?)
(map-indexed (fn [i x] [(conj path i) x])))
x))
:default (recur remain))))))
(find-key-value [[:a 1 :b 1 :c 1] [:a 1 :b 1 :c 3] [:a 1 :b 1 :c 1]] 3)
;; => [1 2]
(find-key-value [[:a 1 [[[[[:c]]]] [[[9 [[[3]] :k]] 119]]]] [:a [[[1]]] :b 1]] 3)
;; => [0 1 1 0 0 1 0 0 0]
(find-key-value (last (take 20000 (iterate vector 3))) 3)
;; => [0 0 0 0 0 0 0 0 0 0 0 0 0 ...]
A simpler solution, assuming 2D array where the inner vectors are
key value vectors, uses flattening of the 2D array and .indexOf.
(defn find-coord [arr val]
(let [m (count (first arr))
idx (.indexOf (flatten arr) val)]
[(quot idx m) (quot (dec (mod idx m)) 2)]))
(find-coord arr 3) ;;=> [1 2]

Juxtaposed transducers

Let's imagine we want to compute two different functions on some given input. How can we do that with transducers?
For example, let's say we have these two transducers:
(def xf-dupl (map #(* 2 %)))
(def xf-inc (map inc))
Now, I would like some function f that takes a collection of transducers and returns a new transducer that combines them, as follows:
(into [] (f [xf-dupl xf-inc]) (range 5))
; => [[0 2 4 6 8] [1 2 3 4 5]]
There should probably be a very simple solution to this, but I cannot find it.
Note: I have tried with cgrand/xforms library's transjuxt, but there I get the following
(into [] (x/transjuxt {:a xf-dupl :b xf-inc}) (range 5))
; => [{:a 0 :b 1}]
Thanks for your help!
Using cgrand/xforms you can define f as
(defn f
[xfs]
(comp
(x/multiplex (zipmap (range) xfs))
(x/by-key (x/into []))
(map second)))
Calling f as you outlined in your question yields
user> (into [] (f [xf-dupl xf-inc]) (range 5))
[[0 2 4 6 8] [1 2 3 4 5]]

Clojure - Function that returns all the indices of a vector of vectors

If I have a vector [[[1 2 3] [4 5 6] [7 8 9]] [[10 11] [12 13]] [[14] [15]]]
How can I return the positions of each element in the vector?
For example 1 has index [0 0 0], 2 has index [0 0 1], etc
I want something like
(some-fn [[[1 2 3] [4 5 6] [7 8 9]] [[10 11] [12 13]] [[14] [15]]] 1)
=> [0 0 0]
I know that if I have a vector [1 2 3 4], I can do (.indexOf [1 2 3 4] 1) => 0 but how can I extend this to vectors within vectors.
Thanks
and one more solution with zippers:
(require '[clojure.zip :as z])
(defn find-in-vec [x data]
(loop [curr (z/vector-zip data)]
(cond (z/end? curr) nil
(= x (z/node curr)) (let [path (rseq (conj (z/path curr) x))]
(reverse (map #(.indexOf %2 %1) path (rest path))))
:else (recur (z/next curr)))))
user> (find-in-vec 11 data)
(1 0 1)
user> (find-in-vec 12 data)
(1 1 0)
user> (find-in-vec 18 data)
nil
user> (find-in-vec 8 data)
(0 2 1)
the idea is to make a depth-first search for an item, and then reconstruct a path to it, indexing it.
Maybe something like this.
Unlike Asthor's answer it works for any nesting depth (until it runs out of stack). Their answer will give the indices of all items that match, while mine will return the first one. Which one you want depends on the specific use-case.
(defn indexed [coll]
(map-indexed vector coll))
(defn nested-index-of [coll target]
(letfn [(step [indices coll]
(reduce (fn [_ [i x]]
(if (sequential? x)
(when-let [result (step (conj indices i) x)]
(reduced result))
(when (= x target)
(reduced (conj indices i)))))
nil, (indexed coll)))]
(step [] coll)))
(def x [[[1 2 3] [4 5 6] [7 8 9]] [[10 11] [12 13]] [[14] [15]]])
(nested-index-of x 2) ;=> [0 0 1]
(nested-index-of x 15) ;=> [2 1 0]
Edit: Target never changes, so the inner step fn doesn't need it as an argument.
Edit 2: Cause I'm procrastinating here, and recursion is a nice puzzle, maybe you wanted the indices of all matches.
You can tweak my first function slightly to carry around an accumulator.
(defn nested-indices-of [coll target]
(letfn [(step [indices acc coll]
(reduce (fn [acc [i x]]
(if (sequential? x)
(step (conj indices i) acc x)
(if (= x target)
(conj acc (conj indices i))
acc)))
acc, (indexed coll)))]
(step [] [] coll)))
(def y [[[1 2 3] [4 5 6] [7 8 9]] [[10 11] [12 13]] [[14] [15 [16 17 4]]]])
(nested-indices-of y 4) ;=> [[0 1 0] [2 1 1 2]]
Vectors within vectors are no different to ints within vectors:
(.indexOf [[[1 2 3] [4 5 6] [7 8 9]] [[10 11] [12 13]] [[14] [15]]] [[14] [15]])
;;=> 2
The above might be a bit difficult to read, but [[14] [15]] is the third element.
Something like
(defn indexer [vec number]
(for [[x set1] (map-indexed vector vec)
[y set2] (map-indexed vector set1)
[z val] (map-indexed vector set2)
:when (= number val)]
[x y z]))
Written directly into here so not tested. Giving more context on what this would be used for might make it easier to give a good answer as this feels like something you shouldn't end up doing in Clojure.
You can also try and flatten the vectors in some way
An other solution to find the path of every occurrences of a given number.
Usually with functional programming you can go for broader, general, elegant, bite size solution. You will always be able to optimize using language constructs or techniques as you need (tail recursion, use of accumulator, use of lazy-seq, etc)
(defn indexes-of-value [v coll]
(into []
(comp (map-indexed #(if (== v %2) %1))
(remove nil?))
coll))
(defn coord' [v path coll]
(cond
;; node is a leaf: empty or coll of numbers
(or (empty? coll)
(number? (first coll)))
(when-let [indexes (seq (indexes-of-value v coll))]
(map #(conj path %) indexes))
;; node is branch: a coll of colls
(coll? (first coll))
(seq (sequence (comp (map-indexed vector)
(mapcat #(coord' v (conj path (first %)) (second %))))
coll))))
(defn coords [v coll] (coord' v [] coll))
Execution examples:
(def coll [[2 1] [] [7 8 9] [[] [1 2 2 3 2]]])
(coords 2 coll)
=> ([0 0] [3 1 1] [3 1 2] [3 1 4])
As a bonus you can write a function to test if paths are all valid:
(defn valid-coords? [v coll coords]
(->> coords
(map #(get-in coll %))
(remove #(== v %))
empty?))
and try the solution with input generated with clojure.spec:
(s/def ::leaf-vec (s/coll-of nat-int? :kind vector?))
(s/def ::branch-vec (s/or :branch (s/coll-of ::branch-vec :kind vector?
:min-count 1)
:leaf ::leaf-vec))
(let [v 1
coll (first (gen/sample (s/gen ::branch-vec) 1))
res (coords v coll)]
(println "generated coll: " coll)
(if-not (valid-coords? v coll res)
(println "Error:" res)
:ok))
Here is a function that can recursively search for a target value, keeping track of the indexes as it goes:
(ns tst.clj.core
(:use clj.core tupelo.test)
(:require [tupelo.core :as t] ))
(t/refer-tupelo)
(defn index-impl
[idxs data tgt]
(apply glue
(for [[idx val] (zip (range (count data)) data)]
(let [idxs-curr (append idxs idx)]
(if (sequential? val)
(index-impl idxs-curr val tgt)
(if (= val tgt)
[{:idxs idxs-curr :val val}]
[nil]))))))
(defn index [data tgt]
(keep-if not-nil? (index-impl [] data tgt)))
(dotest
(let [data-1 [1 2 3]
data-2 [[1 2 3]
[10 11]
[]]
data-3 [[[1 2 3]
[4 5 6]
[7 8 9]]
[[10 11]
[12 13]]
[[20]
[21]]
[[30]]
[[]]]
]
(spyx (index data-1 2))
(spyx (index data-2 10))
(spyx (index data-3 13))
(spyx (index data-3 21))
(spyx (index data-3 99))
))
with results:
(index data-1 2) => [{:idxs [1], :val 2}]
(index data-2 10) => [{:idxs [1 0], :val 10}]
(index data-3 13) => [{:idxs [1 1 1], :val 13}]
(index data-3 21) => [{:idxs [2 1 0], :val 21}]
(index data-3 99) => []
If we add repeated values we get the following:
data-4 [[[1 2 3]
[4 5 6]
[7 8 9]]
[[10 11]
[12 2]]
[[20]
[21]]
[[30]]
[[2]]]
(index data-4 2) => [{:idxs [0 0 1], :val 2}
{:idxs [1 1 1], :val 2}
{:idxs [4 0 0], :val 2}]

Clojure; select all nth element from list of lists with unequal size, for n = 1, 2,

I'd like to have a function, such that,
(f '([1 4 7] [2 5 9] [3 6]))
would give
([1 2 3] [4 5 6] [7 9])
I tried
(apply map vector '([1 4 7] [2 5 9] [3 6]))
would only produce:
([1 2 3] [4 5 6])
I find it hard to describe my requirements that it's difficult for me to search for a ready solution.
Please help me either to improve my description, or pointer to a solution.
Thanks in advance!
I'd solve a more general problem which means you might reuse that function in the future. I'd change map so that it keeps going past the smallest map.
(defn map-all
"Like map but if given multiple collections will call the function f
with as many arguments as there are elements still left."
([f] (map f))
([f coll] (map f coll))
([f c1 & colls]
(let [step (fn step [cs]
(lazy-seq
(let [ss (keep seq cs)]
(when (seq ss)
(cons (map first ss)
(step (map rest ss)))))))]
(map #(apply f %) (step (conj colls c1))))))
(apply map-all vector '([1 4 7] [2 5 9] [3 6]))
(apply map-all vector '([1 false 7] [nil 5 9] [3 6] [8]))
Note, that as opposed to many other solutions, this one works fine even if any of the sequences contain nil or false.
or this way with loop/recur:
user> (defn transpose-all-2 [colls]
(loop [colls colls res []]
(if-let [colls (seq (filter seq colls))]
(recur (doall (map next colls))
(conj res (mapv first colls)))
res)))
#'user/transpose-all-2
user> (transpose-all-2 x)
[[1 2 3] [4 5 6] [7 9]]
user> (transpose-all-2 '((0 1 2 3) (4 5 6 7) (8 9)))
[[0 4 8] [1 5 9] [2 6] [3 7]]
If you know the maximum length of the vectors ahead of time, you could define
(defn tx [colls]
(lazy-seq
(cons (filterv identity (map first colls))
(tx (map rest colls)))))
then
(take 3 (tx '([1 4 7] [2 5 9] [3 6])))
A simple solution is
(defn transpose-all
[colls]
(lazy-seq
(let [ss (keep seq colls)]
(when (seq ss)
(cons (map first ss) (transpose-all (map rest ss)))))))
For example,
(transpose-all '([1 4 7] [2 5 9] [3 6] [11 12 13 14]))
;((1 2 3 11) (4 5 6 12) (7 9 13) (14))
Here is my own attempt:
(defn f [l]
(let [max-count (apply max (map count l))
l-patched (map (fn [e] (if (< (count e) max-count)
(concat e (take (- max-count (count e)) (repeat nil)))
e)) l)]
(map (fn [x] (filter identity x)) (apply map vector l-patched))
))
Another simple solution:
(->> jagged-list
(map #(concat % (repeat nil)))
(apply map vector)
(take-while (partial some identity)))
A jagged-list like this
'([1 4 7 ]
[2 5 9 ]
[3 6 ]
[11 12 13 14])
will produce:
'([1 2 3 11]
[4 5 6 12]
[7 9 nil 13]
[nil nil nil 14])
Here is another go that doesn't require you to know the vector length in advance:
(defn padzip [& [colls]]
(loop [acc [] colls colls]
(if (every? empty? colls) acc
(recur (conj acc (filterv some?
(map first colls))) (map rest colls)))))

How to remove multiple items from a list?

I have a list [2 3 5] which I want to use to remove items from another list like [1 2 3 4 5], so that I get [1 4].
thanks
Try this:
(let [a [1 2 3 4 5]
b [2 3 5]]
(remove (set b) a))
which returns (1 4).
The remove function, by the way, takes a predicate and a collection, and returns a sequence of the elements that don't satisfy the predicate (a set, in this example).
user=> (use 'clojure.set)
nil
user=> (difference (set [1 2 3 4 5]) (set [2 3 5]))
#{1 4}
Reference:
http://clojure.org/data_structures#toc22
http://clojure.org/api#difference
You can do this yourself with something like:
(def a [2 3 5])
(def b [1 2 3 4 5])
(defn seq-contains?
[coll target] (some #(= target %) coll))
(filter #(not (seq-contains? a %)) b)
; (3 4 5)
A version based on the reducers library could be:
(require '[clojure.core.reducers :as r])
(defn seq-contains?
[coll target]
(some #(= target %) coll))
(defn my-remove
"remove values from seq b that are present in seq a"
[a b]
(into [] (r/filter #(not (seq-contains? b %)) a)))
(my-remove [1 2 3 4 5] [2 3 5] )
; [1 4]
EDIT Added seq-contains? code
Here is my take without using sets;
(defn my-diff-func [X Y]
(reduce #(remove (fn [x] (= x %2)) %1) X Y ))