all messages for Emacs-related lists mirrored at yhetil.org
 help / color / mirror / code / Atom feed
* bug#58278: Add new function seq-keep
@ 2022-10-03 21:30 Jonas Bernoulli
  2022-10-03 23:47 ` Lars Ingebrigtsen
  0 siblings, 1 reply; 16+ messages in thread
From: Jonas Bernoulli @ 2022-10-03 21:30 UTC (permalink / raw)
  To: 58278

While I still appreciate the `dash' package, I try to avoid it in
a package when all or most of its used `dash' functions and macros,
can be replaced with equivalent functions/macros from `seq', `cl-lib'
or other parts of Emacs.

Unfortunately I cannot find a replacement for `-keep', which I have been
using a lot.  I propose that we add something like:

  (cl-defgeneric seq-keep (pred sequence)
    "Return a list of all non-nil results of (PRED element) for elements in SEQUENCE."
    (delq nil (seq-map (lambda (elt) (funcall pred elt))
                       sequence)))

Cheers,
Jonas





^ permalink raw reply	[flat|nested] 16+ messages in thread

* bug#58278: Add new function seq-keep
  2022-10-03 21:30 bug#58278: Add new function seq-keep Jonas Bernoulli
@ 2022-10-03 23:47 ` Lars Ingebrigtsen
  2022-10-04 10:05   ` Robert Pluim
  2022-10-04 12:50   ` Jonas Bernoulli
  0 siblings, 2 replies; 16+ messages in thread
From: Lars Ingebrigtsen @ 2022-10-03 23:47 UTC (permalink / raw)
  To: Jonas Bernoulli; +Cc: 58278

Jonas Bernoulli <jonas@bernoul.li> writes:

> Unfortunately I cannot find a replacement for `-keep', which I have been
> using a lot.  I propose that we add something like:
>
>   (cl-defgeneric seq-keep (pred sequence)
>     "Return a list of all non-nil results of (PRED element) for elements in SEQUENCE."
>     (delq nil (seq-map (lambda (elt) (funcall pred elt))
>                        sequence)))

Hm...  well, here PRED isn't a predicate, really, but a transforming
function?  But you wish to filter out the nil results of that
transforming function.

That sounds useful -- there's more than a 100 matches for "delq
nil.*map" in-tree only -- but it's slightly confusing that the function
isn't altogether a predicate, but only kinda.  Would a function
signature like

(cl-defgeneric seq-keep (function sequence &optional pred)
  ...)

make more sense for this combination of map/filter?  (The default
predicate would, of course, be "not null".)





^ permalink raw reply	[flat|nested] 16+ messages in thread

* bug#58278: Add new function seq-keep
  2022-10-03 23:47 ` Lars Ingebrigtsen
@ 2022-10-04 10:05   ` Robert Pluim
  2022-10-04 10:13     ` Lars Ingebrigtsen
  2022-10-04 12:50   ` Jonas Bernoulli
  1 sibling, 1 reply; 16+ messages in thread
From: Robert Pluim @ 2022-10-04 10:05 UTC (permalink / raw)
  To: Lars Ingebrigtsen; +Cc: 58278, Jonas Bernoulli

>>>>> On Tue, 04 Oct 2022 01:47:59 +0200, Lars Ingebrigtsen <larsi@gnus.org> said:

    Lars> Jonas Bernoulli <jonas@bernoul.li> writes:
    >> Unfortunately I cannot find a replacement for `-keep', which I have been
    >> using a lot.  I propose that we add something like:
    >> 
    >> (cl-defgeneric seq-keep (pred sequence)
    >> "Return a list of all non-nil results of (PRED element) for elements in SEQUENCE."
    >> (delq nil (seq-map (lambda (elt) (funcall pred elt))
    >> sequence)))

    Lars> Hm...  well, here PRED isn't a predicate, really, but a transforming
    Lars> function?  But you wish to filter out the nil results of that
    Lars> transforming function.

    Lars> That sounds useful -- there's more than a 100 matches for "delq
    Lars> nil.*map" in-tree only -- but it's slightly confusing that the function
    Lars> isn't altogether a predicate, but only kinda.  Would a function
    Lars> signature like

    Lars> (cl-defgeneric seq-keep (function sequence &optional pred)
    Lars>   ...)

    Lars> make more sense for this combination of map/filter?  (The default
    Lars> predicate would, of course, be "not null".)

How is this different from 'cl-mapcan'? (apart from the syntactic sugar)

Robert
-- 





^ permalink raw reply	[flat|nested] 16+ messages in thread

* bug#58278: Add new function seq-keep
  2022-10-04 10:05   ` Robert Pluim
@ 2022-10-04 10:13     ` Lars Ingebrigtsen
  2022-10-04 10:27       ` Robert Pluim
  0 siblings, 1 reply; 16+ messages in thread
From: Lars Ingebrigtsen @ 2022-10-04 10:13 UTC (permalink / raw)
  To: Robert Pluim; +Cc: 58278, Jonas Bernoulli

Robert Pluim <rpluim@gmail.com> writes:

> How is this different from 'cl-mapcan'? (apart from the syntactic sugar)

I don't see how seq-keep would resemble cl-mapcan much?





^ permalink raw reply	[flat|nested] 16+ messages in thread

* bug#58278: Add new function seq-keep
  2022-10-04 10:13     ` Lars Ingebrigtsen
@ 2022-10-04 10:27       ` Robert Pluim
  2022-10-04 10:42         ` Lars Ingebrigtsen
  0 siblings, 1 reply; 16+ messages in thread
From: Robert Pluim @ 2022-10-04 10:27 UTC (permalink / raw)
  To: Lars Ingebrigtsen; +Cc: 58278, Jonas Bernoulli

>>>>> On Tue, 04 Oct 2022 12:13:55 +0200, Lars Ingebrigtsen <larsi@gnus.org> said:

    Lars> Robert Pluim <rpluim@gmail.com> writes:
    >> How is this different from 'cl-mapcan'? (apart from the syntactic sugar)

    Lars> I don't see how seq-keep would resemble cl-mapcan much?

Well, cl-mapcan applies a function to the elements of a sequence and
discards 'nil' results. Looks pretty similar to me.

Robert
-- 





^ permalink raw reply	[flat|nested] 16+ messages in thread

* bug#58278: Add new function seq-keep
  2022-10-04 10:27       ` Robert Pluim
@ 2022-10-04 10:42         ` Lars Ingebrigtsen
  2022-10-04 10:50           ` Robert Pluim
  0 siblings, 1 reply; 16+ messages in thread
From: Lars Ingebrigtsen @ 2022-10-04 10:42 UTC (permalink / raw)
  To: Robert Pluim; +Cc: 58278, Jonas Bernoulli

Robert Pluim <rpluim@gmail.com> writes:

> Well, cl-mapcan applies a function to the elements of a sequence and
> discards 'nil' results. Looks pretty similar to me.

No, it concatenates the results, so the values returned by the function
has to be lists.

But, yes, if you return lists, then nil return values will "disappear".





^ permalink raw reply	[flat|nested] 16+ messages in thread

* bug#58278: Add new function seq-keep
  2022-10-04 10:42         ` Lars Ingebrigtsen
@ 2022-10-04 10:50           ` Robert Pluim
  2022-10-04 11:10             ` Lars Ingebrigtsen
  0 siblings, 1 reply; 16+ messages in thread
From: Robert Pluim @ 2022-10-04 10:50 UTC (permalink / raw)
  To: Lars Ingebrigtsen; +Cc: 58278, Jonas Bernoulli

>>>>> On Tue, 04 Oct 2022 12:42:50 +0200, Lars Ingebrigtsen <larsi@gnus.org> said:

    Lars> Robert Pluim <rpluim@gmail.com> writes:
    >> Well, cl-mapcan applies a function to the elements of a sequence and
    >> discards 'nil' results. Looks pretty similar to me.

    Lars> No, it concatenates the results, so the values returned by the function
    Lars> has to be lists.

Thatʼs why I said "apart from the syntactic sugar" 😀

Robert
-- 





^ permalink raw reply	[flat|nested] 16+ messages in thread

* bug#58278: Add new function seq-keep
  2022-10-04 10:50           ` Robert Pluim
@ 2022-10-04 11:10             ` Lars Ingebrigtsen
  2022-10-04 11:21               ` Robert Pluim
  0 siblings, 1 reply; 16+ messages in thread
From: Lars Ingebrigtsen @ 2022-10-04 11:10 UTC (permalink / raw)
  To: Robert Pluim; +Cc: 58278, Jonas Bernoulli

Robert Pluim <rpluim@gmail.com> writes:

> Thatʼs why I said "apart from the syntactic sugar" 😀

Having to rewrite

(seq-keep #'cl-digit-char-p '(?6 ?a))
=> (6)

to

(cl-mapcan (lambda (c)
	     (let ((res (cl-digit-char-p c)))
	       (and res (list res))))
	   '(?6 ?a))
=> (6)

is more than "syntactic sugar" in my book.  Nobody would want to write
code like the latter.





^ permalink raw reply	[flat|nested] 16+ messages in thread

* bug#58278: Add new function seq-keep
  2022-10-04 11:10             ` Lars Ingebrigtsen
@ 2022-10-04 11:21               ` Robert Pluim
  2022-10-04 11:23                 ` Lars Ingebrigtsen
  0 siblings, 1 reply; 16+ messages in thread
From: Robert Pluim @ 2022-10-04 11:21 UTC (permalink / raw)
  To: Lars Ingebrigtsen; +Cc: 58278, Jonas Bernoulli

>>>>> On Tue, 04 Oct 2022 13:10:38 +0200, Lars Ingebrigtsen <larsi@gnus.org> said:

    Lars> Robert Pluim <rpluim@gmail.com> writes:
    >> Thatʼs why I said "apart from the syntactic sugar" 😀

    Lars> Having to rewrite

    Lars> (seq-keep #'cl-digit-char-p '(?6 ?a))
    Lars> => (6)

    Lars> to

    Lars> (cl-mapcan (lambda (c)
    Lars> 	     (let ((res (cl-digit-char-p c)))
    Lars> 	       (and res (list res))))
    Lars> 	   '(?6 ?a))
    Lars> => (6)

    Lars> is more than "syntactic sugar" in my book.  Nobody would want to write
    Lars> code like the latter.

I never meant that. I meant defining `seq-keep' in terms of `'cl-mapcan',
with the appropriate converting elements to lists done for you (or
even using `mapcan' if youʼre willing to give up the &rest behaviour
of `cl-mapcan')

Robert
-- 





^ permalink raw reply	[flat|nested] 16+ messages in thread

* bug#58278: Add new function seq-keep
  2022-10-04 11:21               ` Robert Pluim
@ 2022-10-04 11:23                 ` Lars Ingebrigtsen
  2022-10-04 11:37                   ` Robert Pluim
  0 siblings, 1 reply; 16+ messages in thread
From: Lars Ingebrigtsen @ 2022-10-04 11:23 UTC (permalink / raw)
  To: Robert Pluim; +Cc: 58278, Jonas Bernoulli

Robert Pluim <rpluim@gmail.com> writes:

> I never meant that. I meant defining `seq-keep' in terms of `'cl-mapcan',
> with the appropriate converting elements to lists done for you (or
> even using `mapcan' if youʼre willing to give up the &rest behaviour
> of `cl-mapcan')

Oh, OK.  I don't think that would be particularly efficient, though.





^ permalink raw reply	[flat|nested] 16+ messages in thread

* bug#58278: Add new function seq-keep
  2022-10-04 11:23                 ` Lars Ingebrigtsen
@ 2022-10-04 11:37                   ` Robert Pluim
  0 siblings, 0 replies; 16+ messages in thread
From: Robert Pluim @ 2022-10-04 11:37 UTC (permalink / raw)
  To: Lars Ingebrigtsen; +Cc: 58278, Jonas Bernoulli

>>>>> On Tue, 04 Oct 2022 13:23:02 +0200, Lars Ingebrigtsen <larsi@gnus.org> said:

    Lars> Robert Pluim <rpluim@gmail.com> writes:
    >> I never meant that. I meant defining `seq-keep' in terms of `'cl-mapcan',
    >> with the appropriate converting elements to lists done for you (or
    >> even using `mapcan' if youʼre willing to give up the &rest behaviour
    >> of `cl-mapcan')

    Lars> Oh, OK.  I don't think that would be particularly efficient, though.

Iʼve measured it: itʼs not (even when using mapcan) :-)

Robert
-- 





^ permalink raw reply	[flat|nested] 16+ messages in thread

* bug#58278: Add new function seq-keep
  2022-10-03 23:47 ` Lars Ingebrigtsen
  2022-10-04 10:05   ` Robert Pluim
@ 2022-10-04 12:50   ` Jonas Bernoulli
  2022-10-04 13:47     ` Lars Ingebrigtsen
  1 sibling, 1 reply; 16+ messages in thread
From: Jonas Bernoulli @ 2022-10-04 12:50 UTC (permalink / raw)
  To: Lars Ingebrigtsen; +Cc: 58278

Lars Ingebrigtsen <larsi@gnus.org> writes:

> Would a function signature like
>
> (cl-defgeneric seq-keep (function sequence &optional pred)
>   ...)
>
> make more sense for this combination of map/filter?  (The default
> predicate would, of course, be "not null".)

Yes, that would be an improvement.  Some (but certainly not all)
uses of dash's `-keep' look something like

  (-keep (lambda (elt)
           (and (symbolp elt)
                (symbol-name elt)))
         sequence)

and

  (seq-keep #'symbol-name sequence #'symbolp)

would be much nicer in those situations.

In at least some of those cases `mapcan' would work just as well
as `-keep', so after adding &optional PRED, `seq-keep' could also
be used in many places one would have reached for `mapcan' before,
making it even more useful.

I am unsure how I feel about it myself, but we should also consider

  (function pred sequence)

PRED wouldn't be optional then, but we should of course allow it to
be nil.  (Forcing the use of #'identity would not make sense, since
we want FUNCTION to serve both as a predicate and a transforming
function in that case.)

Concerning the argument order, in my opinion

  (seq-keep (lambda (elt)
              ...)
            (lambda (elt)
              ...)
            sequence)

looks better than

  (seq-keep (lambda (elt)
              ...)
            sequence
            (lambda (elt)
              ...))

because the variable named "sequence" looks out of place in the second
instance.  But of course all of FUNCTION, PRED and SEQUENCE can be just
a symbol or a more complex expression.  For instance if only PRED is
complex, then

  (seq-keep #'symbol-name sequence
            (lambda (elt)
               ...))

looks better than

  (seq-keep #'symbol-name
            (lambda (elt)
               ...)
            sequence)

So there is no order that is always best, from an aesthetic point
of view.  In my own use at least, most of the time either all three
arguments would be moderately complex expressions or only the two
functions arguments would complex and the sequence argument would be
just a variable. For that reason I would favor the two functions to
be placed next to each other, I think.

The (function pred sequence) argument list has the advantage that it
is in (reverse) "chronological" order.  First we have a sequence, then
we filter the elements, and finally we transform the elements that we
kept, at least conceptually.

Using actual chronological order (sequence pred function) is out of
question as that would conflict with all(?) other mapping functions;
as is (sequence [pred] function), I presume.

Just some food for thought; as of yet, I am unsure what order I
prefer myself -- though I lean towards (function pred sequence).
But if that is deemed unusual and thus undesirable, (function
sequence &optional pred) also works for me.





^ permalink raw reply	[flat|nested] 16+ messages in thread

* bug#58278: Add new function seq-keep
  2022-10-04 12:50   ` Jonas Bernoulli
@ 2022-10-04 13:47     ` Lars Ingebrigtsen
  2022-10-04 13:56       ` Lars Ingebrigtsen
  0 siblings, 1 reply; 16+ messages in thread
From: Lars Ingebrigtsen @ 2022-10-04 13:47 UTC (permalink / raw)
  To: Jonas Bernoulli; +Cc: 58278

Jonas Bernoulli <jonas@bernoul.li> writes:

> Yes, that would be an improvement.  Some (but certainly not all)
> uses of dash's `-keep' look something like
>
>   (-keep (lambda (elt)
>            (and (symbolp elt)
>                 (symbol-name elt)))
>          sequence)
>
> and
>
>   (seq-keep #'symbol-name sequence #'symbolp)
>
> would be much nicer in those situations.

Hm...  That's not exactly what I was thinking here.  I was thinking

(cl-defgeneric seq-keep (func sequence &optional pred)
  (if pred
      (seq-filter pred (seq-mapcar func sequence))
    (delq nil (seq-mapcar func sequence))))

which is the traditional "keep" semantics, but allows extending the
concept of "keep" to more than "is non-nil".

But that may well be an overcomplication -- in the unusual cases where
it's not nil that people want to keep, they can just type

  (seq-filter pred (seq-mapcar func sequence))

themselves, which has very clear semantics.

So I think, on second consideration, I'd rather just go with

(cl-defgeneric seq-keep (func sequence)
  (delq nil (seq-mapcar func sequence)))

like you originally suggested (but with just an argument name change).





^ permalink raw reply	[flat|nested] 16+ messages in thread

* bug#58278: Add new function seq-keep
  2022-10-04 13:47     ` Lars Ingebrigtsen
@ 2022-10-04 13:56       ` Lars Ingebrigtsen
  2022-10-04 13:59         ` Lars Ingebrigtsen
  0 siblings, 1 reply; 16+ messages in thread
From: Lars Ingebrigtsen @ 2022-10-04 13:56 UTC (permalink / raw)
  To: Jonas Bernoulli; +Cc: 58278

Just for kicks, here's some random "del.*map" instances from the
Emacs sources:

(delq nil (mapcar (lambda (n) (and (>= n 0) n)) articles))

This should be (seq-filter #'cl-plusp articles).

(delq nil (mapcar #'gnus-server-to-method gnus-agent-covered-methods))

This would be nice as seq-keep.

      (delq nil (mapcar
                 (lambda (c)
                   (when (string-prefix-p base c)
                     (substring c base-size)))
                 hist)))))

Ditto.

   (delq nil (mapcar (lambda (action)
                       (cond
                        ((eq action 'create) 'created)
                        ((eq action 'modify) 'changed)
                        ((eq action 'attrib) 'attribute-changed)
                        ((memq action '(delete delete-self move-self)) 'deleted)
                        ((eq action 'moved-from) 'renamed-from)
                        ((eq action 'moved-to) 'renamed-to)
                        ((eq action 'ignored) 'stopped)))
                     actions))

Ditto.

     (delq nil (mapcar
		(lambda (x) (if (string-match "\\`\\." x) x))
		ido-temp-list)))

This should be seq-filter.

			(cookies (delq nil (mapcar
					    (lambda (e)
					      (org-list-get-checkbox e s))
					    items))))

seq-keep.

    (let* ((have (delq nil (mapcar
			    (lambda (x) (get-text-property 1 'time-of-day x))
			    list)))

seq-keep.

          (string-join
           (delq nil (mapcar
                      (lambda (item)
                        (when (cdr item)
                          (format "%s='%s'" (car item) (cdr item))))
                      `(("type" . ,type) ("sender" . ,sender)
                        ("destination" . ,destination) ("path" . ,path)
                        ("interface" . ,interface) ("member" . ,member))))
           ",")

seq-keep.

       (reverse (delete "" (mapcar (lambda (r)
				     (replace-regexp-in-string "nil" "" r))
				   result0)))))))

This suggest that the signature should be

(func sequence &optional delete-element)

which defaults to nil, but could be "" here, and use seq-keep.

  (delq 'type (mapcar #'car (haiku-selection-data clipboard nil))))

Ditto.







^ permalink raw reply	[flat|nested] 16+ messages in thread

* bug#58278: Add new function seq-keep
  2022-10-04 13:56       ` Lars Ingebrigtsen
@ 2022-10-04 13:59         ` Lars Ingebrigtsen
  2022-10-04 19:46           ` Lars Ingebrigtsen
  0 siblings, 1 reply; 16+ messages in thread
From: Lars Ingebrigtsen @ 2022-10-04 13:59 UTC (permalink / raw)
  To: Jonas Bernoulli; +Cc: 58278

Lars Ingebrigtsen <larsi@gnus.org> writes:

> This suggest that the signature should be
>
> (func sequence &optional delete-element)
>
> which defaults to nil, but could be "" here, and use seq-keep.

But that gets us into problems w.r.t. the comparison function -- we can
use delq here for "", but not for "foo", which seems inconsistent.

So...  we're back to the (func sequence) as the signature.





^ permalink raw reply	[flat|nested] 16+ messages in thread

* bug#58278: Add new function seq-keep
  2022-10-04 13:59         ` Lars Ingebrigtsen
@ 2022-10-04 19:46           ` Lars Ingebrigtsen
  0 siblings, 0 replies; 16+ messages in thread
From: Lars Ingebrigtsen @ 2022-10-04 19:46 UTC (permalink / raw)
  To: Jonas Bernoulli; +Cc: 58278

Lars Ingebrigtsen <larsi@gnus.org> writes:

> So...  we're back to the (func sequence) as the signature.

So I've now added this to Emacs 29.





^ permalink raw reply	[flat|nested] 16+ messages in thread

end of thread, other threads:[~2022-10-04 19:46 UTC | newest]

Thread overview: 16+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2022-10-03 21:30 bug#58278: Add new function seq-keep Jonas Bernoulli
2022-10-03 23:47 ` Lars Ingebrigtsen
2022-10-04 10:05   ` Robert Pluim
2022-10-04 10:13     ` Lars Ingebrigtsen
2022-10-04 10:27       ` Robert Pluim
2022-10-04 10:42         ` Lars Ingebrigtsen
2022-10-04 10:50           ` Robert Pluim
2022-10-04 11:10             ` Lars Ingebrigtsen
2022-10-04 11:21               ` Robert Pluim
2022-10-04 11:23                 ` Lars Ingebrigtsen
2022-10-04 11:37                   ` Robert Pluim
2022-10-04 12:50   ` Jonas Bernoulli
2022-10-04 13:47     ` Lars Ingebrigtsen
2022-10-04 13:56       ` Lars Ingebrigtsen
2022-10-04 13:59         ` Lars Ingebrigtsen
2022-10-04 19:46           ` Lars Ingebrigtsen

Code repositories for project(s) associated with this external index

	https://git.savannah.gnu.org/cgit/emacs.git
	https://git.savannah.gnu.org/cgit/emacs/org-mode.git

This is an external index of several public inboxes,
see mirroring instructions on how to clone and mirror
all data and code used by this external index.