Return an else value when using recur - clojure

I am new to Clojure, and doing my best to forget all my previous experience with more procedural languages (java, ruby, swift) and embrace Clojure for what it is. I am actually really enjoying the way it makes me think differently -- however, I have come up against a pattern that I just can't seem to figure out. The easiest way to illustrate, is with some code:
(defn char-to-int [c] (Integer/valueOf (str c)))
(defn digits-dont-decrease? [str]
(let [digits (map char-to-int (seq str)) i 0]
(when (< i 5)
(if (> (nth digits i) (nth digits (+ i 1)))
false
(recur (inc i))))))
(def result (digits-dont-decrease? "112233"))
(if (= true result)
(println "fit rules")
(println "doesn't fit rules"))
The input is a 6 digit number as a string, and I am simply attempting to make sure that each digit from left to right is >= the previous digit. I want to return false if it doesn't, and true if it does. The false situation works great -- however, given that recur needs to be the last thing in the function (as far as I can tell), how do I return true. As it is, when the condition is satisfied, I get an illegal argument exception:
Execution error (IllegalArgumentException) at clojure.exercise.two/digits-dont-decrease? (four:20).
Don't know how to create ISeq from: java.lang.Long
How should I be thinking about this? I assume my past training is getting in my mental way.

This is not answering your question, but also shows an alternative. While the (apply < ...) approach over the whole string is very elegant for small strings (it is eager), you can use every? for an short-circuiting approach. E.g.:
user=> (defn nr-seq [s] (map #(Integer/parseInt (str %)) s))
#'user/nr-seq
user=> (every? (partial apply <=) (partition 2 1 (nr-seq "123")))
true

You need nothing but
(apply <= "112233")
Reason: string is a sequence of character and comparison operator works on character.
(->> "0123456789" (mapcat #(repeat 1000 %)) (apply str) (def loooong))
(count loooong)
10000
(time (apply <= loooong))
"Elapsed time: 21.006625 msecs"
true
(->> "9123456789" (mapcat #(repeat 1000 %)) (apply str) (def bad-loooong))
(count bad-loooong)
10000
(time (apply <= bad-loooong))
"Elapsed time: 2.581750 msecs"
false
(above runs on my iPhone)

In this case, you don't really need loop/recur. Just use the built-in nature of <= like so:
(ns tst.demo.core
(:use demo.core tupelo.core tupelo.test))
(def true-samples
["123"
"112233"
"13"])
(def false-samples
["10"
"12324"])
(defn char->int
[char-or-str]
(let [str-val (str char-or-str)] ; coerce any chars to len-1 strings
(assert (= 1 (count str-val)))
(Integer/parseInt str-val)))
(dotest
(is= 5 (char->int "5"))
(is= 5 (char->int \5))
(is= [1 2 3] (mapv char->int "123"))
; this shows what we are going for
(is (<= 1 1 2 2 3 3))
(isnt (<= 1 1 2 1 3 3))
and now test the char sequences:
;-----------------------------------------------------------------------------
; using built-in `<=` function
(doseq [true-samp true-samples]
(let [digit-vals (mapv char->int true-samp)]
(is (apply <= digit-vals))))
(doseq [false-samp false-samples]
(let [digit-vals (mapv char->int false-samp)]
(isnt (apply <= digit-vals))))
if you want to write your own, you can like so:
(defn increasing-equal-seq?
"Returns true iff sequence is non-decreasing"
[coll]
(when (< (count coll) 2)
(throw (ex-info "coll must have at least 2 vals" {:coll coll})))
(loop [prev (first coll)
remaining (rest coll)]
(if (empty? remaining)
true
(let [curr (first remaining)
prev-next curr
remaining-next (rest remaining)]
(if (<= prev curr)
(recur prev-next remaining-next)
false)))))
;-----------------------------------------------------------------------------
; using home-grown loop/recur
(doseq [true-samp true-samples]
(let [digit-vals (mapv char->int true-samp)]
(is (increasing-equal-seq? digit-vals))))
(doseq [false-samp false-samples]
(let [digit-vals (mapv char->int false-samp)]
(isnt (increasing-equal-seq? digit-vals))))
)
with result
-------------------------------
Clojure 1.10.1 Java 13
-------------------------------
Testing tst.demo.core
Ran 2 tests containing 15 assertions.
0 failures, 0 errors.
Passed all tests
Finished at 23:36:17.096 (run time: 0.028s)

You an use loop with recur.
Assuming you require following input v/s output -
"543221" => false
"54321" => false
"12345" => true
"123345" => true
Following function can help
;; Assuming char-to-int is defined by you before as per the question
(defn digits-dont-decrease?
[strng]
(let [digits (map char-to-int (seq strng))]
(loop [;;the bindings in loop act as initial state
decreases true
i (- (count digits) 2)]
(let [decreases (and decreases (>= (nth digits (+ i 1)) (nth digits i)))]
(if (or (< i 1) (not decreases))
decreases
(recur decreases (dec i)))))))
This should work for numeric string of any length.
Hope this helps. Please let me know if you were looking for something else :).

(defn non-decreasing? [str]
(every?
identity
(map
(fn [a b]
(<= (int a) (int b)))
(seq str)
(rest str))))
(defn non-decreasing-loop? [str]
(loop [a (seq str) b (rest str)]
(if-not (seq b)
true
(if (<= (int (first a)) (int (first b)))
(recur (rest a) (rest b))
false))))
(non-decreasing? "112334589")
(non-decreasing? "112324589")
(non-decreasing-loop? "112334589")
(non-decreasing-loop? "112324589")

Related

a version of `sequence` that doesn't do chunking

I'd like to have a version of sequence that doesn't do the chunking of 32 elements. Currently, this code will output
(def peek #(doto % (print " ")))
(def pause #(do (Thread/sleep 10)
%))
(take 2 (->> (range 100)
(sequence (comp (map peek)
(map pause)
(map inc)))))
;; prints 0 1 2 3 4 <..etc..> 32
;; => (0, 1)
I'd like a version of it so that it only iterates through the elements that it needs
(take 2 (->> (range 100)
(iter-sequence (comp (map peek)
(map pause)
(map inc)))))
;; prints 0 1
;; => (0, 1)
Is there a way to do this?
I had to change a couple of things to get it working. The first is to cut and paste sequence code and replace clojure.lang.RT/chunkIteratorSeq with an alternative version of clojure.lang.IteratorSeq that has exposed public constructor methods.
The reason being is that the clojure.lang.IteratorSeq/create has a check to iter.next() on L27 which will block if the source is blocking.
(defn seqiter
{:added "1.0"
:static true}
([coll] coll)
([xform coll]
(IteratorSeq.
(TransformerIterator/create xform (clojure.lang.RT/iter coll))))
([xform coll & colls]
(IteratorSeq.
(TransformerIterator/createMulti
xform
(map #(clojure.lang.RT/iter %) (cons coll colls))))))

Clojure - Using recursion to find the number of elements in a list

I have written a function that uses recursion to find the number of elements in a list and it works successfully however, I don't particularly like the way I've written it. Now I've written it one way I can't seem to think of a different way of doing it.
My code is below:
(def length
(fn [n]
(loop [i n total 0]
(cond (= 0 i) total
:t (recur (rest i)(inc total))))))
To me it seems like it is over complicated, can anyone think of another way this can be written for comparison?
Any help greatly appreciated.
Here is a naive recursive version:
(defn my-count [coll]
(if (empty? coll)
0
(inc (my-count (rest coll)))))
Bear in mind there's not going to be any tail call optimization going on here so for long lists the stack will overflow.
Here is a version using reduce:
(defn my-count [coll]
(reduce (fn [acc x] (inc acc)) 0 coll))
Here is code showing some different solutions. Normally, you should use the built-in function count.
(def data [:one :two :three])
(defn count-loop [data]
(loop [cnt 0
remaining data]
(if (empty? remaining)
cnt
(recur (inc cnt) (rest remaining)))))
(defn count-recursive [remaining]
(if (empty? remaining)
0
(inc (count-recursive (rest remaining)))))
(defn count-imperative [data]
(let [cnt (atom 0)]
(doseq [elem data]
(swap! cnt inc))
#cnt))
(deftest t-count
(is (= 3 (count data)))
(is (= 3 (count-loop data)))
(is (= 3 (count-recursive data)))
(is (= 3 (count-imperative data))))
Here's one that is tail-call optimized, and doesn't rely on loop. Basically the same as Alan Thompson's first one, but inner functions are the best things. (And feel more idiomatic to me.) :-)
(defn my-count [sq]
(letfn [(inner-count [c s]
(if (empty? s)
c
(recur (inc c) (rest s))))]
(inner-count 0 sq)))
Just for completeness, here is another twist
(defn my-count
([data]
(my-count data 0))
([data counter]
(if (empty? data)
counter
(recur (rest data) (inc counter)))))

clojure performance on badly performing code

I have completed this problem on hackerrank and my solution passes most test cases but it is not fast enough for 4 out of the 11 test cases.
My solution looks like this:
(ns scratch.core
(require [clojure.string :as str :only (split-lines join split)]))
(defn ascii [char]
(int (.charAt (str char) 0)))
(defn process [text]
(let [parts (split-at (int (Math/floor (/ (count text) 2))) text)
left (first parts)
right (if (> (count (last parts)) (count (first parts)))
(rest (last parts))
(last parts))]
(reduce (fn [acc i]
(let [a (ascii (nth left i))
b (ascii (nth (reverse right) i))]
(if (> a b)
(+ acc (- a b))
(+ acc (- b a))))
) 0 (range (count left)))))
(defn print-result [[x & xs]]
(prn x)
(if (seq xs)
(recur xs)))
(let [input (slurp "/Users/paulcowan/Downloads/input10.txt")
inputs (str/split-lines input)
length (read-string (first inputs))
texts (rest inputs)]
(time (print-result (map process texts))))
Can anyone give me any advice about what I should look at to make this faster?
Would using recursion instead of reduce be faster or maybe this line is expensive:
right (if (> (count (last parts)) (count (first parts)))
(rest (last parts))
(last parts))
Because I am getting a count twice.
You are redundantly calling reverse on every iteration of the reduce:
user=> (let [c [1 2 3]
noisey-reverse #(doto (reverse %) println)]
(reduce (fn [acc e] (conj acc (noisey-reverse c) e))
[]
[:a :b :c]))
(3 2 1)
(3 2 1)
(3 2 1)
[(3 2 1) :a (3 2 1) :b (3 2 1) :c]
The reversed value could be calculated inside the containing let, and would then only need to be calculated once.
Also, due to the way your parts is defined, you are doing linear time lookups with each call to nth. It would be better to put parts in a vector and do indexed lookup. In fact you wouldn't need a reversed parts, and could do arithmetic based on the count of the vector to find the item to look up.

Function for replacing subsequences

Is there a function that could replace subsequences? For example:
user> (good-fnc [1 2 3 4 5] [1 2] [3 4 5])
;; => [3 4 5 3 4 5]
I know that there is clojure.string/replace for strings:
user> (clojure.string/replace "fat cat caught a rat" "a" "AA")
;; => "fAAt cAAt cAAught AA rAAt"
Is there something similar for vectors and lists?
Does this work for you?
(defn good-fnc [s sub r]
(loop [acc []
s s]
(cond
(empty? s) (seq acc)
(= (take (count sub) s) sub) (recur (apply conj acc r)
(drop (count sub) s))
:else (recur (conj acc (first s)) (rest s)))))
Here is a version that plays nicely with lazy seq inputs. Note that it can take an infinite lazy sequence (range) without looping infinitely as a loop based version would.
(defn sq-replace
[match replacement sq]
(let [matching (count match)]
((fn replace-in-sequence [[elt & elts :as sq]]
(lazy-seq
(cond (empty? sq)
()
(= match (take matching sq))
(concat replacement (replace-in-sequence (drop matching sq)))
:default
(cons elt (replace-in-sequence elts)))))
sq)))
#'user/sq-replace
user> (take 10 (sq-replace [3 4 5] ["hello, world"] (range)))
(0 1 2 "hello, world" 6 7 8 9 10 11)
I took the liberty of making the sequence argument the final argument, since this is the convention in Clojure for functions that walk a sequence.
My previous (now deleted) answer was incorrect because this was not as trivial as I first thought, here is my second attempt:
(defn seq-replace
[coll sub rep]
(letfn [(seq-replace' [coll]
(when-let [s (seq coll)]
(let [start (take (count sub) s)
end (drop (count sub) s)]
(if (= start sub)
(lazy-cat rep (seq-replace' end))
(cons (first s) (lazy-seq (seq-replace' (rest s))))))))]
(seq-replace' coll)))

What's wrong with this clojure prime seq?

I can't figure out why this definition of a lazy primes sequence would cause non-termination. The stack-trace I get isn't very helpful (my one complaint about clojure is obtuse stack-traces).
(declare naturals is-prime? primes)
(defn naturals
([] (naturals 1))
([n] (lazy-seq (cons n (naturals (inc n))))))
(defn is-prime? [n]
(not-any? #(zero? (rem n %))
(take-while #(> n (* % %)) (primes))))
(defn primes
([] (lazy-seq (cons 2 (primes 3))))
([n] (let [m (first (filter is-prime? (naturals n)))]
(lazy-seq (cons m (primes (+ 2 m)))))))
(take 10 (primes)) ; this results in a stack overflow error
Let's start executing primes, and we'll magically realise one seq just to be clear. I'll ignore naturals because it's correctly lazy:
> (magically-realise-seq (primes))
=> (magically-realise-seq (lazy-seq (cons 2 (primes 3))))
=> (cons 2 (primes 3))
=> (cons 2 (let [m (first (filter is-prime? (naturals 3)))]
(lazy-seq (cons m (primes (+ 2 3))))))
=> (cons 2 (let [m (first (filter
(fn [n]
(not-any? #(zero? (rem n %))
(take-while #(> n (* % %)) (primes)))))
(naturals 3)))]
(lazy-seq (cons m (primes (+ 2 3))))))
I've substituted is-prime? in as a fn at the end there—you can see that primes will get called again, and realised at least once as take-while pulls out elements. This will then cause the loop.
The issue is that to know to calculate the "primes" function you are using the "is-prime?" function, and then to calculate the "is-prime?" function you are using "(primes)", hence the stack over flow.
So to calculate the "(primes 3)", you are need calculate the "(first (filter is-prime? (naturals 3)))", which is going to call "(is-prime? 1)", which is calling "(primes)", which in turns calls "(primes 3)". In other words you are doing:
user=> (declare a b)
#'user/b
user=> (defn a [] (b))
#'user/a
user=> (defn b [] (a))
#'user/b
user=> (a)
StackOverflowError user/b (NO_SOURCE_FILE:1)
To see how to generate prime numbers: Fast Prime Number Generation in Clojure
I think the problem is, that you're trying to use (primes) before it's already constructed.
Changing is-prime? like that fixes the problem:
(defn is-prime? [n]
(not-any? #(zero? (rem n %))
(take-while #(>= n (* % %)) (next (naturals)))))
(Note, that I've changed > with >=, otherwise it gives that 4 is prime. It still says that 1 is prime, which isn't true and may cause problems if you use is-prime? elsewhere.