Filter being too aggressive - clojure

I have tried to make it unnecessary to fully understand the code, so read the whole question first, then dig into the code if necessary.
I'm trying to make a macro for pattern matching.
It works by taking a list in which the first element is type of matching to be performed
Example: the first element in the list is "cons"; the macro would call a cons matching function.
A matching function takes an object and a function, calls the function with the matched value. With the cons matcher, it would call the function with the head and tail of the list.
I used a "num" matcher for testing. It's basically an identity matcher, so it could be nested inside itself arbitrarily, as I did below.
;a macro to make debugging easier
(defmacro log [item] `(do (print ~(join [(str item) ": "])) (println ~item)))
(defn make-pattern-matcher-iter [result bindings-queue]
(println "starting next iteration")
(log bindings-queue)
(if (first bindings-queue) (println "bindings-queue does contain an element") nil)
(if (first bindings-queue)
(let [[next-symbol pattern] (first bindings-queue)
pattern-name (first pattern)
pattern-items (next pattern)
pattern-matching-function (prepend-symbol "match-" pattern-name)
gensyms-attached-to-subpatterns (map (fn [pattern]
(if (symbol? pattern)
pattern
`(~(gensym "matchbinding") ~pattern)))
pattern-items)
all-bound-symbols (map (fn [sym]
(if (symbol? sym) sym (first sym)))
gensyms-attached-to-subpatterns)
gensyms-subpattern-pairs (filter list? gensyms-attached-to-subpatterns)
rest-of-bindings-queue (next bindings-queue)
updated-bindings-queue (concat rest-of-bindings-queue
gensyms-subpattern-pairs)
subpatterns (map second gensyms-subpattern-pairs)]
(log next-symbol)
(log all-bound-symbols)
(log updated-bindings-queue)
(log gensyms-attached-to-subpatterns)
(log gensyms-subpattern-pairs)
(log subpatterns)
`(~pattern-matching-function
~next-symbol
(fn [~#all-bound-symbols] ~(make-pattern-matcher-iter result updated-bindings-queue))))
result))
(defn make-pattern-matcher [object pattern result] (make-pattern-matcher-iter result [[object pattern]]))
(defn match-num [x f]
(if (number? x) (f x) nil))
(def this-m (make-pattern-matcher-iter '(+ x y) [['object '(pair x y)]]))
(def this-n (make-pattern-matcher '15 '(num (num z)) 'z))
(= this-n this-m)
(defmacro bind-match [object pattern result] (make-pattern-matcher object pattern result))
(bind-match 15 (num (num z)) z)
The problem is that the macro isn't properly binding "z"
the log gives on the second iteration:
gensyms-attached-to-subpatterns: ((matchbinding8210 (num z)))
gensyms-subpattern-pairs: ()
there are other log messages, but these seem to be the problem.
Take a look at how gensyms-subpattern-pairs is calculated. In the let block it says:
gensyms-subpattern-pairs (filter list? gensyms-attached-to-subpatterns)
this should take out everything but lists, which is all there is, so it shouldn't take out anything.
The filter seems to be too aggressive. Why?

As you noted, the elements of gensyms-attached-to-subpatterns are not IPersistentLists, but rather Conses. Sanity check:
(contains? (supers clojure.lang.Cons) clojure.lang.IPersistentList)
;=> false
So it looks like you'll need to use some other check than list?.

Related

Writing a lazy-as-possible unfoldr-like function to generate arbitrary factorizations

problem formulation
Informally speaking, I want to write a function which, taking as input a function that generates binary factorizations and an element (usually neutral), creates an arbitrary length factorization generator. To be more specific, let us first define the function nfoldr in Clojure.
(defn nfoldr [f e]
(fn rec [n]
(fn [s]
(if (zero? n)
(if (empty? s) e)
(if (seq s)
(if-some [x ((rec (dec n)) (rest s))]
(f (list (first s) x))))))))
Here nil is used with the meaning "undefined output, input not in function's domain". Additionally, let us view the inverse relation of a function f as a set-valued function defining inv(f)(y) = {x | f(x) = y}.
I want to define a function nunfoldr such that inv(nfoldr(f , e)(n)) = nunfoldr(inv(f) , e)(n) when for every element y inv(f)(y) is finite, for each binary function f, element e and natural number n.
Moreover, I want the factorizations to be generated as lazily as possible, in a 2-dimensional sense of laziness. My goal is that, when getting some part of a factorization for the first time, there does not happen (much) computation needed for next parts or next factorizations. Similarly, when getting one factorization for the first time, there does not happen computation needed for next ones, whereas all the previous ones get in effect fully realized.
In an alternative formulation we can use the following longer version of nfoldr, which is equivalent to the shorter one when e is a neutral element.
(defn nfoldr [f e]
(fn [n]
(fn [s]
(if (zero? n)
(if (empty? s) e)
((fn rec [n]
(fn [s]
(if (= 1 n)
(if (and (seq s) (empty? (rest s))) (first s))
(if (seq s)
(if-some [x ((rec (dec n)) (rest s))]
(f (list (first s) x)))))))
n)))))
a special case
This problem is a generalization of the problem of generating partitions described in that question. Let us see how the old problem can be reduced to the current one. We have for every natural number n:
npt(n) = inv(nconcat(n)) = inv(nfoldr(concat2 , ())(n)) = nunfoldr(inv(concat2) , ())(n) = nunfoldr(pt2 , ())(n)
where:
npt(n) generates n-ary partitions
nconcat(n) computes n-ary concatenation
concat2 computes binary concatenation
pt2 generates binary partitions
So the following definitions give a solution to that problem.
(defn generate [step start]
(fn [x] (take-while some? (iterate step (start x)))))
(defn pt2-step [[x y]]
(if (seq y) (list (concat x (list (first y))) (rest y))))
(def pt2-start (partial list ()))
(def pt2 (generate pt2-step pt2-start))
(def npt (nunfoldr pt2 ()))
I will summarize my story of solving this problem, using the old one to create example runs, and conclude with some observations and proposals for extension.
solution 0
At first, I refined/generalized the approach I took for solving the old problem. Here I write my own versions of concat and map mainly for a better presentation and, in the case of concat, for some added laziness. Of course we can use Clojure's versions or mapcat instead.
(defn fproduct [f]
(fn [s]
(lazy-seq
(if (and (seq f) (seq s))
(cons
((first f) (first s))
((fproduct (rest f)) (rest s)))))))
(defn concat' [s]
(lazy-seq
(if (seq s)
(if-let [x (seq (first s))]
(cons (first x) (concat' (cons (rest x) (rest s))))
(concat' (rest s))))))
(defn map' [f]
(fn rec [s]
(lazy-seq
(if (seq s)
(cons (f (first s)) (rec (rest s)))))))
(defn nunfoldr [f e]
(fn rec [n]
(fn [x]
(if (zero? n)
(if (= e x) (list ()) ())
((comp
concat'
(map' (comp
(partial apply map)
(fproduct (list
(partial partial cons)
(rec (dec n))))))
f)
x)))))
In an attempt to get inner laziness we could replace (partial partial cons) with something like (comp (partial partial concat) list). Although this way we get inner LazySeqs, we do not gain any effective laziness because, before consing, most of the computation required for fully realizing the rest part takes place, something that seems unavoidable within this general approach. Based on the longer version of nfoldr, we can also define the following faster version.
(defn nunfoldr [f e]
(fn [n]
(fn [x]
(if (zero? n)
(if (= e x) (list ()) ())
(((fn rec [n]
(fn [x] (println \< x \>)
(if (= 1 n)
(list (list x))
((comp
concat'
(map' (comp
(partial apply map)
(fproduct (list
(partial partial cons)
(rec (dec n))))))
f)
x))))
n)
x)))))
Here I added a println call inside the main recursive function to get some visualization of eagerness. So let us demonstrate the outer laziness and inner eagerness.
user=> (first ((npt 5) (range 3)))
< (0 1 2) >
< (0 1 2) >
< (0 1 2) >
< (0 1 2) >
< (0 1 2) >
(() () () () (0 1 2))
user=> (ffirst ((npt 5) (range 3)))
< (0 1 2) >
< (0 1 2) >
< (0 1 2) >
< (0 1 2) >
< (0 1 2) >
()
solution 1
Then I thought of a more promising approach, using the function:
(defn transpose [s]
(lazy-seq
(if (every? seq s)
(cons
(map first s)
(transpose (map rest s))))))
To get the new solution we replace the previous argument in the map' call with:
(comp
(partial map (partial apply cons))
transpose
(fproduct (list
repeat
(rec (dec n)))))
Trying to get inner laziness we could replace (partial apply cons) with #(cons (first %) (lazy-seq (second %))) but this is not enough. The problem lies in the (every? seq s) test inside transpose, where checking a lazy sequence of factorizations for emptiness (as a stopping condition) results in realizing it.
solution 2
A first way to tackle the previous problem that came to my mind was to use some additional knowledge about the number of n-ary factorizations of an element. This way we can repeat a certain number of times and use only this sequence for the stopping condition of transpose. So we will replace the test inside transpose with (seq (first s)), add an input count to nunfoldr and replace the argument in the map' call with:
(comp
(partial map #(cons (first %) (lazy-seq (second %))))
transpose
(fproduct (list
(partial apply repeat)
(rec (dec n))))
(fn [[x y]] (list (list ((count (dec n)) y) x) y)))
Let us turn to the problem of partitions and define:
(defn npt-count [n]
(comp
(partial apply *)
#(map % (range 1 n))
(partial comp inc)
(partial partial /)
count))
(def npt (nunfoldr pt2 () npt-count))
Now we can demonstrate outer and inner laziness.
user=> (first ((npt 5) (range 3)))
< (0 1 2) >
(< (0 1 2) >
() < (0 1 2) >
() < (0 1 2) >
() < (0 1 2) >
() (0 1 2))
user=> (ffirst ((npt 5) (range 3)))
< (0 1 2) >
()
However, the dependence on additional knowledge and the extra computational cost make this solution unacceptable.
solution 3
Finally, I thought that in some crucial places I should use a kind of lazy sequences "with a non-lazy end", in order to be able to check for emptiness without realizing. An empty such sequence is just a non-lazy empty list and overall they behave somewhat like the lazy-conss of the early days of Clojure. Using the definitions given below we can reach an acceptable solution, which works under the assumption that always at least one of the concat'ed sequences (when there is one) is non-empty, something that holds in particular when every element has at least one binary factorization and we are using the longer version of nunfoldr.
(def lazy? (partial instance? clojure.lang.IPending))
(defn empty-eager? [x] (and (not (lazy? x)) (empty? x)))
(defn transpose [s]
(lazy-seq
(if-not (some empty-eager? s)
(cons
(map first s)
(transpose (map rest s))))))
(defn concat' [s]
(if-not (empty-eager? s)
(lazy-seq
(if-let [x (seq (first s))]
(cons (first x) (concat' (cons (rest x) (rest s))))
(concat' (rest s))))
()))
(defn map' [f]
(fn rec [s]
(if-not (empty-eager? s)
(lazy-seq (cons (f (first s)) (rec (rest s))))
())))
Note that in this approach the input function f should produce lazy sequences of the new kind and the resulting n-ary factorizer will also produce such sequences. To take care of the new input requirement, for the problem of partitions we define:
(defn pt2 [s]
(lazy-seq
(let [start (list () s)]
(cons
start
((fn rec [[x y]]
(if (seq y)
(lazy-seq
(let [step (list (concat x (list (first y))) (rest y))]
(cons step (rec step))))
()))
start)))))
Once again, let us demonstrate outer and inner laziness.
user=> (first ((npt 5) (range 3)))
< (0 1 2) >
< (0 1 2) >
(< (0 1 2) >
() < (0 1 2) >
() < (0 1 2) >
() () (0 1 2))
user=> (ffirst ((npt 5) (range 3)))
< (0 1 2) >
< (0 1 2) >
()
To make the input and output use standard lazy sequences (sacrificing a bit of laziness), we can add:
(defn lazy-end->eager-end [s]
(if (seq s)
(lazy-seq (cons (first s) (lazy-end->eager-end (rest s))))
()))
(defn eager-end->lazy-end [s]
(lazy-seq
(if-not (empty-eager? s)
(cons (first s) (eager-end->lazy-end (rest s))))))
(def nunfoldr
(comp
(partial comp (partial comp eager-end->lazy-end))
(partial apply nunfoldr)
(fproduct (list
(partial comp lazy-end->eager-end)
identity))
list))
observations and extensions
While creating solution 3, I observed that the old mechanism for lazy sequences in Clojure might not be necessarily inferior to the current one. With the transition, we gained the ability to create lazy sequences without any substantial computation taking place but lost the ability to check for emptiness without doing the computation needed to get one more element. Because both of these abilities can be important in some cases, it would be nice if a new mechanism was introduced, which would combine the advantages of the previous ones. Such a mechanism could use again an outer LazySeq thunk, which when forced would return an empty list or a Cons or another LazySeq or a new LazyCons thunk. This new thunk when forced would return a Cons or perhaps another LazyCons. Now empty? would force only LazySeq thunks while first and rest would also force LazyCons. In this setting map could look like this:
(defn map [f s]
(lazy-seq
(if (empty? s) ()
(lazy-cons
(cons (f (first s)) (map f (rest s)))))))
I have also noticed that the approach taken from solution 1 onwards lends itself to further generalization. If inside the argument in the map' call in the longer nunfoldr we replace cons with concat, transpose with some implementation of Cartesian product and repeat with another recursive call, we can then create versions that "split at different places". For example, using the following as the argument we can define a nunfoldm function that "splits in the middle" and corresponds to an easy-to-imagine nfoldm. Note that all "splitting strategies" are equivalent when f is associative.
(comp
(partial map (partial apply concat))
cproduct
(fproduct (let [n-half (quot n 2)]
(list (rec n-half) (rec (- n n-half))))))
Another natural modification would allow for infinite factorizations. To achieve this, if f generated infinite factorizations, nunfoldr(f , e)(n) should generate the factorizations in an order of type ω, so that each one of them could be produced in finite time.
Other possible extensions include dropping the n parameter, creating relational folds (in correspondence with the relational unfolds we consider here) and generically handling algebraic data structures other than sequences as input/output. This book, which I have just discovered, seems to contain valuable relevant information, given in a categorical/relational language.
Finally, to be able to do this kind of programming more conveniently, we could transfer it into a point-free, algebraic setting. This would require constructing considerable "extra machinery", in fact almost making a new language. This paper demonstrates such a language.

clojure.lang.LazySeq cannot be cast to java.lang.CharSequence

I am writing a function that, for any given string, replaces any digits within that String with the same number of '.' characters.
Examples:
AT2X -> AT..X
QW3G45 -> QW...G.........
T3Z1 -> T...Z.
I've written the following Clojure function but I am getting an error I don't quite understand:
java.lang.ClassCastException: clojure.lang.LazySeq (in module: Unnamed Module) cannot be case to java.lang.Charsequence
I'm interpreting from the error that I need to force an evaluation of a lazy sequence back into a String (or CharSequence) but I can't figure out where to do so or if this is correct.
(defn dotify
;;Replaces digits with the same number of '.'s for use in traditional board formats
[FEN]
(let [values (doall (filter isDigit (seq FEN)))]
(fn [values]
(let [value (first values)]
(str/replace FEN value (fn dots [number]
(fn [s times]
(if (> times 0)
(recur (str s ".") (dec times)))) "" (Character/digit number 10)) value))
(recur (rest values))) values))
There is a standard clojure.string/replace function that may handle that case. Its last argument might be not just a string or a pattern but also a function that turns a found fragment into what you want.
Let's prepare such a function first:
(defn replacer [sum-str]
(let [num (read-string num-str)]
(apply str (repeat num \.))))
You may try it in this way:
user> (replacer "2")
..
user> (replacer "9")
.........
user> (replacer "22")
......................
user>
Now pass it into replace as follows:
user> (clojure.string/replace "a2b3c11" #"\d+" replacer)
a..b...c...........
Here's a way to do this using reduce:
(defn dotify [s]
(->> s
(reduce (fn [acc elem]
(if (Character/isDigit elem)
(let [dots (Integer/parseInt (str elem))]
(apply conj acc (repeat dots \.)))
(conj acc elem)))
[])
(apply str)))
(dotify "zx4g1z2h")
=> "zx....g.z..h"
And another version using mapcat:
(defn dotify-mapcat [s]
(apply str
(mapcat (fn [c]
(if (Character/isDigit c)
(repeat (Integer/parseInt (str c)) \.)
[c]))
s)))
There are some issues in your example:
Many of the internal forms are themselves functions, but it looks like you just want their bodies or implementations instead of wrapping them in functions.
It's hard to tell by the indentation/whitespace, but the entire function is just recur-ing, the fn above it is not being used or returned.
One of the arguments to str/replace is a function that returns a function.
It helps to break the problem down into smaller pieces. For one, you know you'll need to examine each character in a string and decide whether to just return it or expand it into a sequence of dots. So you can start with a function:
(defn expand-char [^Character c]
(if (Character/isDigit c)
(repeat (Integer/parseInt (str c)) \.)
[c]))
Then use that function that operates on one character at a time in a higher-order function that operates on the entire string:
(apply str (mapcat expand-char s))
=> "zx....g.z..h"
Note this is also ~5x faster than the examples above because of the ^Character type-hint in expand-char function.
You can do this with str/replace too:
(defn expand-char [s]
(if (Character/isDigit ^Character (first s))
(apply str (repeat (Integer/parseInt s) \.))
s))
(str/replace "zx4g1z2h" #"." expand-char)
=> "zx....g.z..h"

Clojure: Find even numbers in a vector

I am coming from a Java background trying to learn Clojure. As the best way of learning is by actually writing some code, I took a very simple example of finding even numbers in a vector. Below is the piece of code I wrote:
`
(defn even-vector-2 [input]
(def output [])
(loop [x input]
(if (not= (count x) 0)
(do
(if (= (mod (first x) 2) 0)
(do
(def output (conj output (first x)))))
(recur (rest x)))))
output)
`
This code works, but it is lame that I had to use a global symbol to make it work. The reason I had to use the global symbol is because I wanted to change the state of the symbol every time I find an even number in the vector. let doesn't allow me to change the value of the symbol. Is there a way this can be achieved without using global symbols / atoms.
The idiomatic solution is straightfoward:
(filter even? [1 2 3])
; -> (2)
For your educational purposes an implementation with loop/recur
(defn filter-even [v]
(loop [r []
[x & xs :as v] v]
(if (seq v) ;; if current v is not empty
(if (even? x)
(recur (conj r x) xs) ;; bind r to r with x, bind v to rest
(recur r xs)) ;; leave r as is
r))) ;; terminate by not calling recur, return r
The main problem with your code is you're polluting the namespace by using def. You should never really use def inside a function. If you absolutely need mutability, use an atom or similar object.
Now, for your question. If you want to do this the "hard way", just make output a part of the loop:
(defn even-vector-3 [input]
(loop [[n & rest-input] input ; Deconstruct the head from the tail
output []] ; Output is just looped with the input
(if n ; n will be nil if the list is empty
(recur rest-input
(if (= (mod n 2) 0)
(conj output n)
output)) ; Adding nothing since the number is odd
output)))
Rarely is explicit looping necessary though. This is a typical case for a fold: you want to accumulate a list that's a variable-length version of another list. This is a quick version:
(defn even-vector-4 [input]
(reduce ; Reducing the input into another list
(fn [acc n]
(if (= (rem n 2) 0)
(conj acc n)
acc))
[] ; This is the initial accumulator.
input))
Really though, you're just filtering a list. Just use the core's filter:
(filter #(= (rem % 2) 0) [1 2 3 4])
Note, filter is lazy.
Try
#(filterv even? %)
if you want to return a vector or
#(filter even? %)
if you want a lazy sequence.
If you want to combine this with more transformations, you might want to go for a transducer:
(filter even?)
If you wanted to write it using loop/recur, I'd do it like this:
(defn keep-even
"Accepts a vector of numbers, returning a vector of the even ones."
[input]
(loop [result []
unused input]
(if (empty? unused)
result
(let [curr-value (first unused)
next-result (if (is-even? curr-value)
(conj result curr-value)
result)
next-unused (rest unused) ]
(recur next-result next-unused)))))
This gets the same result as the built-in filter function.
Take a look at filter, even? and vec
check out http://cljs.info/cheatsheet/
(defn even-vector-2 [input](vec(filter even? input)))
If you want a lazy solution, filter is your friend.
Here is a non-lazy simple solution (loop/recur can be avoided if you apply always the same function without precise work) :
(defn keep-even-numbers
[coll]
(reduce
(fn [agg nb]
(if (zero? (rem nb 2)) (conj agg nb) agg))
[] coll))
If you like mutability for "fun", here is a solution with temporary mutable collection :
(defn mkeep-even-numbers
[coll]
(persistent!
(reduce
(fn [agg nb]
(if (zero? (rem nb 2)) (conj! agg nb) agg))
(transient []) coll)))
...which is slightly faster !
mod would be better than rem if you extend the odd/even definition to negative integers
You can also replace [] by the collection you want, here a vector !
In Clojure, you generally don't need to write a low-level loop with loop/recur. Here is a quick demo.
(ns tst.clj.core
(:require
[tupelo.core :as t] ))
(t/refer-tupelo)
(defn is-even?
"Returns true if x is even, otherwise false."
[x]
(zero? (mod x 2)))
; quick sanity checks
(spyx (is-even? 2))
(spyx (is-even? 3))
(defn keep-even
"Accepts a vector of numbers, returning a vector of the even ones."
[input]
(into [] ; forces result into vector, eagerly
(filter is-even? input)))
; demonstrate on [0 1 2...9]
(spyx (keep-even (range 10)))
with result:
(is-even? 2) => true
(is-even? 3) => false
(keep-even (range 10)) => [0 2 4 6 8]
Your project.clj needs the following for spyx to work:
:dependencies [
[tupelo "0.9.11"]

working with variadic arguments

I am playing around and trying to create my own reductions implementation, so far I have this which works with this test data:
((fn [func & args]
(reduce (fn [acc item]
(conj acc (func (last acc) item))
)[(first args)] (first (rest args)))) * 2 [3 4 5]
What I don't like is how I am separating the args.
(first args) is what I would expect, i.e. 2 but (rest args) is ([3 4 5]) and so I am getting the remainder like this (first (rest args)) which I do not like.
Am I missing some trick that makes it easier to work with variadic arguments?
Variadic arguments are just about getting an unspecified number of arguments in a list, so all list/destructuring operations can be applied here.
For example:
(let [[fst & rst] a-list]
; fst is the first element
; rst is the rest
)
This is more readable than:
(let [fst (first a-list)
rst (rest a-list)]
; ...
)
You can go further to get the first and second elements of a list (assuming it has >1 elements) in one line:
(let [fst snd & rst]
; ...
)
I originally misread your question and thought you were trying to reimplement the reduce function. Here is a sample implementation I wrote for this answer which does’t use first or rest:
(defn myreduce
;; here we accept the form with no initial value
;; like in (myreduce * [2 3 4 5]), which is equivalent
;; to (myreduce * 2 [3 4 5]). Notice how we use destructuring
;; to get the first/rest of the list passed as a second
;; argument
([op [fst & rst]] (myreduce op fst rst))
;; we take an operator (function), accumulator and list of elements
([op acc els]
;; no elements? give the accumulator back
(if (empty? els)
acc
;; all the function's logic is in here
;; we're destructuring els to get its first (el) and rest (els)
(let [[el & els] els]
;; then apply again the function on the same operator,
;; using (op acc el) as the new accumulator, and the
;; rest of the previous elements list as the new
;; elements list
(recur op (op acc el) els)))))
I hope it helps you see how to work with list destructuring, which is probably what you want in your function. Here is a relevant blog post on this subject.
Tidying up your function.
As #bfontaine commented, you can use (second args) instead of (first (rest args)):
(defn reductions [func & args]
(reduce
(fn [acc item] (conj acc (func (last acc) item)))
[(first args)]
(second args)))
This uses
func
(first args)
(second args)
... but ignores the rest of args.
So we can use destructuring to name the first and second elements of args - init and coll seem suitable - giving
(defn reductions [func & [init coll & _]]
(reduce
(fn [acc item] (conj acc (func (last acc) item)))
[init]
coll))
... where _ is the conventional name for the ignored argument, in this case a sequence.
We can get rid of it, simplifying to
(defn reductions [func & [init coll]] ... )
... and then to
(defn reductions [func init coll] ... )
... - a straightforward function of three arguments.
Dealing with the underlying problems.
Your function has two problems:
slowness
lack of laziness.
Slowness
The flashing red light in this function is the use of last in
(fn [acc item] (conj acc (func (last acc) item)))
This scans the whole of acc every time it is called, even if acc is a vector. So this reductions takes time proportional to the square of the length of coll: hopelessly slow for long sequences.
A simple fix is to replace (last acc) by (acc (dec (count acc))), which takes effectively constant time.
Lack of laziness
We still can't lazily use what the function produces. For example, it would be nice to encapsulate the sequence of factorials like this:
(def factorials (reductions * 1N (next (range)))))
With your reductions, this definition never returns.
You have to entirely recast your function to make it lazy. Let's modify the standard -lazy -reductions to employ destructuring:
(defn reductions [f init coll]
(cons
init
(lazy-seq
(when-let [[x & xs] (seq coll)]
(reductions f (f init x) xs)))))
Now we can define
(def factorials (reductions * 1N (next (range))))
Then, for example,
(take 10 factorials)
;(1N 1N 2N 6N 24N 120N 720N 5040N 40320N 362880N)
Another approach is to derive the sequence from itself, like a railway locomotive laying the track it travels on:
(defn reductions [f init coll]
(let [answer (lazy-seq (reductions f init coll))]
(cons init (map f answer coll))))
But this contains a hidden recursion (hidden from me, at least):
(nth (reductions * 1N (next (range))) 10000)
;StackOverflowError ...

Howto find a listitem which contains a specific substring

I have a list of strings, fx '("abc" "def" "gih") and i would like to be able to search the list for any items containing fx "ef" and get the item or index returned.
How is this done?
Combining filter and re-find can do this nicely.
user> (def fx '("abc" "def" "gih"))
#'user/fx
user> (filter (partial re-find #"ef") fx)
("def")
user> (filter (partial re-find #"a") fx)
("abc")
In this case I like to combine them with partial though defining an anonymous function works fine in that case as well. It is also useful to use re-pattern if you don't know the search string in advance:
user> (filter (partial re-find (re-pattern "a")) fx)
("abc")
If you want to retrieve all the indexes of the matching positions along with the element you can try this:
(filter #(re-find #"ef" (second %)) (map-indexed vector '("abc" "def" "gih")))
=>([1 "def"])
map-indexed vector generates an index/value lazy sequence
user> (map-indexed vector '("abc" "def" "gih"))
([0 "abc"] [1 "def"] [2 "gih"])
Which you can then filter using a regular expression against the second element of each list member.
#(re-find #"ef" (second %))
Just indices:
Lazily:
(keep-indexed #(if (re-find #"ef" %2)
%1) '("abc" "def" "gih"))
=> (1)
Using loop/recur
(loop [[str & strs] '("abc" "def" "gih")
idx 0
acc []]
(if str
(recur strs
(inc idx)
(cond-> acc
(re-find #"ef" str) (conj idx)))
acc))
For just the element, refer to Arthur Ulfeldts answer.
Here is a traditional recursive definition that returns the index. It's easy to modify to return the corresponding string as well.
(defn strs-index [re lis]
(let [f (fn [ls n]
(cond
(empty? ls) nil
(re-find re (first ls)) n
:else (recur (rest ls) (inc n))))]
(f lis 0)))
user=> (strs-index #"de" ["abc" "def" "gih"])
1
user=> (strs-index #"ih" ["abc" "def" "gih"])
2
user=> (strs-index #"xy" ["abc" "def" "gih"])
nil
(Explanation: The helper function f is defined as a binding in let, and then is called at the end. If the sequence of strings passed to it is not empty, it searches for the regular expression in the first element of the sequence and returns the index if it finds the string. This uses the fact that re-find's result counts as true unless it fails, in which case it returns nil. If the previous steps don't succeed, the function starts over with the rest of the sequence and an incremented index. If it gets to the end of the sequence, it returns nil.)