Personnally, I like #sumOf:, like for example (1 to: 10) sumOf: #squared.
Same with maxOf: minOf: productOf: ...


2013/4/22 Frank Shearar <frank.shea...@gmail.com>

> On 22 April 2013 12:32, Sven Van Caekenberghe <s...@stfx.eu> wrote:
> > Hi,
> >
> > I agree with Frank on the processing block: it has nothing to do with
> summing.
> >
> > Mathematically, defining adding (sum) leads to a neutral element (zero).
> But you only need it if the collection is empty.
> >
> > The trick of the #zero selector is elegant, but not needed with the
> #anyOne trick.
>
> That's a good point. I thought of #zero because my own hacking on
> SqueakCheck led naturally to thinking of protocols: using a class-side
> #zero means that I could work with "all objects that understand + and
> have a zero".
>
> #collectAndSum: might be a good name for the method, actually.
>
> frank
>
> > Currently, #sum does not work with empty collections in Pharo, which
> surprised me.
> >
> > I would add a
> >
> > Collection>>#sumFrom: value
> >         ^ self inject: value into: [ :sum :each | sum + each ]
> >
> > And change
> >
> > Collection>>#sum
> >         | sample sum |
> >         self isEmpty ifTrue: [ ^ self sumFrom: 0 ].
> >         sample := self anyOne.
> >         sum := self inject: sample into: [ :sum :each | sum + each ].
> >         ^ sum - sample
> >
> > A variant with an additional collect style processing block could be
> added along these lines, #sum: and #sum:from:
> >
> > Sven
> >
> > On 22 Apr 2013, at 12:29, Frank Shearar <frank.shea...@gmail.com> wrote:
> >
> >> "Sum" is usually well-defined, so I don't understand what the block's
> >> for. With the block it's more like "take this collection, map the
> >> values with some function, and sum the result".
> >>
> >> If so, it sounds like you're looking for a sugared form of
> >> (myCollection collect: aBlock) inject: self first class zero into: #+.
> >> ?
> >>
> >> (There's already Float class >> #zero and (in Squeak at least) Integer
> >> class >> #zero, and so on. Just add MyUnit class >> #zero and you're
> >> done.)
> >>
> >> frank
> >>
> >> On 22 April 2013 10:37, Tudor Girba <tu...@tudorgirba.com> wrote:
> >>> Hi,
> >>>
> >>> I am CC-ing the pharo mailing list because it can be of interest.
> >>>
> >>> I agree with Guillaume that there is a legitimate need for a generic
> >>> solution. However, at the same time we lose the convenience of simply
> adding
> >>> numbers, which is likely to be the most encountered use case.
> >>>
> >>> I see a couple of possibilities:
> >>> - add Collection>>sum: aBlock from: aZeroValue that takes aZeroValue
> as the
> >>> default.
> >>> - add Collection>>sumNumbers: aBlock that takes 0 as default rather
> than
> >>> anyOne.
> >>>
> >>> What do you think?
> >>>
> >>> Cheers,
> >>> Doru
> >>>
> >>>
> >>>
> >>> On Mon, Apr 22, 2013 at 10:14 AM, Guillaume Larcheveque
> >>> <guillaume.larcheve...@gmail.com> wrote:
> >>>>
> >>>> For example, in Artefact we use Units and I have tried to use sum but
> it
> >>>> doesn't works because Units doesn't allow to do 0 + 4 cm which is
> >>>> inconsistent.
> >>>>
> >>>>
> >>>> 2013/4/22 Alexandre Bergel <alexandre.ber...@me.com>
> >>>>>
> >>>>> Thanks for letting us know. I cannot see a case where having 0 as the
> >>>>> initial value does not work as expected.
> >>>>>
> >>>>> Cheers,
> >>>>> Alexandre
> >>>>>
> >>>>>
> >>>>> Le 21 avr. 2013 à 17:35, Tudor Girba <tu...@tudorgirba.com> a écrit
> :
> >>>>>
> >>>>>> Hi,
> >>>>>>
> >>>>>> Pharo 2.0 comes with Collection>>sum:
> >>>>>>
> >>>>>> Collection>>sum: aBlock
> >>>>>>   "This is implemented using a variant of the normal inject:into:
> >>>>>> pattern.
> >>>>>>   The reason for this is that it is not known whether we're in the
> >>>>>> normal
> >>>>>>   number line, i.e. whether 0 is a good initial value for the sum.
> >>>>>>   Consider a collection of measurement objects, 0 would be the
> >>>>>> unitless
> >>>>>>   value and would not be appropriate to add with the unit-ed
> objects."
> >>>>>>   | sum sample |
> >>>>>>   sample := aBlock value: self anyOne.
> >>>>>>   sum := self inject: sample into: [ :previousValue :each |
> >>>>>> previousValue + (aBlock value: each) ].
> >>>>>>   ^ sum - sample
> >>>>>>
> >>>>>> To some extent, this is more generic than the one we had in Moose
> that
> >>>>>> considered only numbers:
> >>>>>> Collection>>sum: aSymbolOrBlock
> >>>>>>   ^ self
> >>>>>>       inject: 0
> >>>>>>       into: [:sum :each | sum + (aSymbolOrBlock value: each)]
> >>>>>>
> >>>>>>
> >>>>>> However, with the Pharo 2.0 implementation the collection must not
> be
> >>>>>> empty, while the other implementation we get 0. If the collection
> is empty,
> >>>>>> you get an exception due to anyOne.
> >>>>>>
> >>>>>> This induced several errors in metric computations (like number of
> >>>>>> methods of a package when the package had no classes). These are
> now fixed,
> >>>>>> but I thought I would let you know just in case you want to rely on
> this
> >>>>>> method.
> >>>>>>
> >>>>>> I actually still believe we would benefit from a robust but more
> >>>>>> limited sum:. Perhaps we could have sumNumbers:.
> >>>>>>
> >>>>>> Cheers,
> >>>>>> Doru
> >>>>>>
> >>>>>>
> >>>>>> --
> >>>>>> www.tudorgirba.com
> >>>>>>
> >>>>>> "If you can't say why something is relevant,
> >>>>>> it probably isn't."
> >>>>>>
> >>>>>>
> >>>>>> _______________________________________________
> >>>>>> Moose-dev mailing list
> >>>>>> moose-...@iam.unibe.ch
> >>>>>> https://www.iam.unibe.ch/mailman/listinfo/moose-dev
> >>>>>
> >>>>> _______________________________________________
> >>>>> Moose-dev mailing list
> >>>>> moose-...@iam.unibe.ch
> >>>>> https://www.iam.unibe.ch/mailman/listinfo/moose-dev
> >>>>
> >>>>
> >>>> --
> >>>> Guillaume Larcheveque
> >>>>
> >>>> _______________________________________________
> >>>> Moose-dev mailing list
> >>>> moose-...@iam.unibe.ch
> >>>> https://www.iam.unibe.ch/mailman/listinfo/moose-dev
> >>>
> >>> --
> >>> www.tudorgirba.com
> >>>
> >>> "Every thing has its own flow"
> >
> >
> > --
> > Sven Van Caekenberghe
> > Proudly supporting Pharo
> > http://pharo.org
> > http://association.pharo.org
> > http://consortium.pharo.org
> >
> >
> >
> >
> >
>
>

Reply via email to