Idiomatic way to get every digit of a number - clojure

What's the idiomatic way to get each digit of a number and put them into a sequence?
Currently I'm doing
(map #(Integer/parseInt %) (map str ((comp seq str) 123456)))
, which is somewhat ugly...
Any ideas?

(for [n (str 123456)]
(- (byte n) 48))

(map #(Character/getNumericValue %) (str 123456))

I think it's nice to write this with lazy sequences, even if you can't actually use the laziness because you're building it from the "wrong" end:
(defn digits [x]
(rseq (mapv #(rem % 10)
(->> x
(iterate #(quot % 10))
(take-while pos?)))))
If you want, you can write a digits* that doesn't use mapv or rseq, and lazily returns the digits in backwards order.

How about:
(defn digits
[x]
(if (< x 10)
[x]
(conj (digits (quot x 10))
(rem x 10))))
user=>(digits 123456)
[1 2 3 4 5 6]

Related

Clojure function to Replace Count

I need help with an assignment that uses Clojure. It is very small but the language is a bit confusing to understand. I need to create a function that behaves like count without actually using the count funtion. I know a loop can be involved with it somehow but I am at a lost because nothing I have tried even gets my code to work. I expect it to output the number of elements in list. For example:
(defn functionname []
...
...)
(println(functionname '(1 4 8)))
Output:3
Here is what I have so far:
(defn functionname [n]
(def n 0)
(def x 0)
(while (< x n)
do
()
)
)
(println(functionname '(1 4 8)))
It's not much but I think it goes something like this.
This implementation takes the first element of the list and runs a sum until it can't anymore and then returns the sum.
(defn recount [list-to-count]
(loop [xs list-to-count sum 0]
(if (first xs)
(recur (rest xs) (inc sum))
sum
)))
user=> (recount '(3 4 5 9))
4
A couple more example implementations:
(defn not-count [coll]
(reduce + (map (constantly 1) coll)))
or:
(defn not-count [coll]
(reduce (fn [a _] (inc a)) 0 coll))
or:
(defn not-count [coll]
(apply + (map (fn [_] 1) coll)))
result:
(not-count '(5 7 8 1))
=> 4
I personally like the first one with reduce and constantly.

How to split a number in Clojure?

I am looking for a nice method to split a number with n digits in Clojure I have these two methods:
(->> (str 942)
seq
(map str)
(map read-string)) => (9 4 2)
and...
(defn digits [n]
(cons
(str (mod n 10)) (lazy-seq (positive-numbers (quot n 10)))))
(map read-string (reverse (take 5 (digits 10012)))) => (1 0 0 1 2)
Is there a more concise method for doing this type of operation?
A concise version of your first method is
(defn digits [n]
(->> n str (map (comp read-string str))))
... and of your second is
(defn digits [n]
(if (pos? n)
(conj (digits (quot n 10)) (mod n 10) )
[]))
An idiomatic alternative
(defn digits [n]
(->> n
(iterate #(quot % 10))
(take-while pos?)
(mapv #(mod % 10))
rseq))
For example,
(map digits [0 942 -3])
;(nil (9 4 2) nil)
The computation is essentially eager, since the last digit in is the
first out. So we might as well use mapv and rseq (instead of map and reverse) to do it faster.
The function is transducer-ready.
It works properly only on positive numbers.
You could simply do
(map #(Character/digit % 10) (str 942))
EDIT: Adding a function definition
(defn digits [number] (map #(Character/digit % 10) (str number)))
Usage:
(digits 1234)
Note: This is concise, but does use java String and Character classes. An efficient implementation can be written using integer modulo arithmetic, but won't be concise. One such solution similar to Charles' answer would be:
(defn numTodigits
[num]
(loop [n num res []]
(if (zero? n)
res
(recur (quot n 10) (cons (mod n 10) res)))))
Source
I'm not sure about concise, but this one avoids unnecessary inefficiency such as converting to strings and back to integers.
(defn digits [n]
(loop [result (list), n n]
(if (pos? n)
(recur (conj result (rem n 10))
(quot n 10))
result)))
A recursive implementation (could be more efficient and less concise, but it shouldn't matter for reasonable numbers).
(defn digits [n]
(when (pos? n)
(concat (digits (quot n 10))
[(mod n 10)])))
a looping method:
(defn split-numbers [number]
(loop [itr 0 res [] n number]
(if (= n 0)
res
(recur (inc itr) (concat (vector (mod n 10)) res) (int (/ n 10)))
)
)
)
Easiest i could find:
(->> (str n)
seq
(map (comp read-string str)))

Generating binary numbers of n digits in clojure

I'd like to generate binary numbers of n digits from 0 to 2^n-1. For example of 3 digits, "000", "001", "010", ..., "111" (0 to 7 in decimal). The way I used is to use java.lang.Integer.toBinaryString() method and add zeros if necessary like the following:
(defn pad-zero [s n]
(str (reduce str (repeat (- n (count s)) "0")) s))
(defn binary-permutation [n]
(map (fn [s] (pad-zero s n))
(map #(Integer/toBinaryString %) (range 0 (Math/pow 2 n)))))
With this code, I can generate what I want like this. For 3 digits:
(binary-permutation 3)
=> ("000" "001" "010" "011" "100" "101" "110" "111")
But this codes look a little verbose.
Aren't there any ways better or more clojure way to do this?
You can simplify the formatting using cl-format from clojure.pprint:
(defn binary-permutation [n]
(map (partial cl-format nil "~v,'0B" n) (range 0 (Math/pow 2 n))))
You may also be interested to know that (Math/pow 2 n) is equivalent to (bit-shift-left 1 n).
Another way to express this would be in term of selections from clojure.math.combinatorics:
(defn binary-permutation [n]
(map (partial apply str) (selections [0 1] n)))
(defn binary-permutation [n]
(for [x (range (Math/pow 2 n))]
(apply str (reverse (take n (map #(bit-and 1 %) (iterate #(bit-shift-right % 1) x)))))))
(defn pad-zero [s n]
(apply str (take-last n (concat (repeat n \0) s))))

Clojure: number of consecutive repetition items

I need a function to calculate the number of consecutive equal entries in a sequence. For example, (consecutive "abcdefg") should return 0, while (consecutive "aabcdddefg") should return 3.
Is the way i wrote it idiomatic or could it be improved?
(defn consecutive [p]
(second (reduce
#(vector %2
(if (= (first %1) %2)
(inc (second %1))
(second %1)))
[nil 0]
p)))
I think that (consecutive "abcdefg") should return 1, not 0.
Here's a simple implementation that achieves this:
(defn consecutive [s]
(apply max (map count (partition-by identity s))))
user> (defn consecutive [s] (->> s (partition-by identity) (reduce #(+ % (dec (count %2))) 0)))
#'user/consecutive
user> (consecutive "abcdefg")
0
user> (consecutive "aabcdddefg")
3
I prefer the (partition-by identity) idiom when some consecutive sequences are required.
try this.
(defn consecutive [string]
(let [n (apply max (map count (partition-by identity string)))]
(if (= n 1) 0 n)))
it's common pattern

clojure - ordered pairwise combination of 2 lists

Being quite new to clojure I am still struggling with its functions. If I have 2 lists, say "1234" and "abcd" I need to make all possible ordered lists of length 4. Output I want to have is for length 4 is:
("1234" "123d" "12c4" "12cd" "1b34" "1b3d" "1bc4" "1bcd"
"a234" "a23d" "a2c4" "a2cd" "ab34" "ab3d" "abc4" "abcd")
which 2^n in number depending on the inputs.
I have written a the following function to generate by random walk a single string/list.
The argument [par] would be something like ["1234" "abcd"]
(defn make-string [par] (let [c1 (first par) c2 (second par)] ;version 3 0.63 msec
(apply str (for [loc (partition 2 (interleave c1 c2))
:let [ch (if (< (rand) 0.5) (first loc) (second loc))]]
ch))))
The output will be 1 of the 16 ordered lists above. Each of the two input lists will always have equal length, say 2,3,4,5, up to say 2^38 or within available ram. In the above function I have tried to modify it to generate all ordered lists but failed. Hopefully someone can help me. Thanks.
Mikera is right that you need to use recursion, but you can do this while being both more concise and more general - why work with two strings, when you can work with N sequences?
(defn choices [colls]
(if (every? seq colls)
(for [item (map first colls)
sub-choice (choices (map rest colls))]
(cons item sub-choice))
'(())))
(defn choose-strings [& strings]
(for [chars (choices strings)]
(apply str chars)))
user> (choose-strings "123" "abc")
("123" "12c" "1b3" "1bc" "a23" "a2c" "ab3" "abc")
This recursive nested-for is a very useful pattern for creating a sequence of paths through a "tree" of choices. Whether there's an actual tree, or the same choice repeated over and over, or (as here) a set of N choices that don't depend on the previous choices, this is a handy tool to have available.
You can also take advantage of the cartesian-product from the clojure.math.combinatorics package, although this requires some pre- and post-transformation of your data:
(ns your-namespace (:require clojure.math.combinatorics))
(defn str-combinations [s1 s2]
(->>
(map vector s1 s2) ; regroup into pairs of characters, indexwise
(apply clojure.math.combinatorics/cartesian-product) ; generate combinations
(map (partial apply str)))) ; glue seqs-of-chars back into strings
> (str-combinations "abc" "123")
("abc" "ab3" "a2c" "a23" "1bc" "1b3" "12c" "123")
>
The trick is to make the function recursive, calling itself on the remainder of the list at each step.
You can do something like:
(defn make-all-strings [string1 string2]
(if (empty? string1)
[""]
(let [char1 (first string1)
char2 (first string2)
following-strings (make-all-strings (next string1) (next string2))]
(concat
(map #(str char1 %) following-strings)
(map #(str char2 %) following-strings)))))
(make-all-strings "abc" "123")
=> ("abc" "ab3" "a2c" "a23" "1bc" "1b3" "12c" "123")
(defn combine-strings [a b]
(if (seq a)
(for [xs (combine-strings (rest a) (rest b))
x [(first a) (first b)]]
(str x xs))
[""]))
Now that I wrote it I realize it's a less generic version of amalloiy's one.
You could also use the binary digits of numbers between 0 and 16 to form your combinations:
if a bit is zero select from the first string otherwise the second.
E.g. 6 = 2r0110 => "1bc4", 13 = 2r1101 => "ab3d", etc.
(map (fn [n] (apply str (map #(%1 %2)
(map vector "1234" "abcd")
(map #(if (bit-test n %) 1 0) [3 2 1 0])))); binary digits
(range 0 16))
=> ("1234" "123d" "12c4" "12cd" "1b34" "1b3d" "1bc4" "1bcd" "a234" "a23d" "a2c4" "a2cd" "ab34" "ab3d" "abc4" "abcd")
The same approach can apply to generating combinations from more than 2 strings.
Say you have 3 strings ("1234" "abcd" "ABCD"), there will be 81 combinations (3^4). Using base-3 ternary digits:
(defn ternary-digits [n] (reverse (map #(mod % 3) (take 4 (iterate #(quot % 3) n))))
(map (fn [n] (apply str (map #(%1 %2)
(map vector "1234" "abcd" "ABCD")
(ternary-digits n)
(range 0 81))
(def c1 "1234")
(def c2 "abcd")
(defn make-string [c1 c2]
(map #(apply str %)
(apply map vector
(map (fn [col rep]
(take (math/expt 2 (count c1))
(cycle (apply concat
(map #(repeat rep %) col)))))
(map vector c1 c2)
(iterate #(* 2 %) 1)))))
(make-string c1 c2)
=> ("1234" "a234" "1b34" "ab34" "12c4" "a2c4" "1bc4" "abc4" "123d" "a23d" "1b3d" "ab3d" "12cd" "a2cd" "1bcd" "abcd")