Re: [Haskell-cafe] Improving the docs (specifically Data.Foldable)

Am 17.09.21 um 07:15 schrieb Michael Turner:>> >>* "The contribution of each element to the final result is combined with an *>>* accumulator via an /operator/ function. The operator may be explicitly *>>* provided by the caller as in `foldr` or may be implicit as in `length`. In *>>* the case of `foldMap`, the caller provides a function mapping each element *>>* into a suitable 'Monoid', which makes it possible to merge
At *Fri Oct 1 01:42:39 UTC 2021* Ben Franksen wrote the per-element *>>* contributions via that monoid's `mappend` function." *> >>* This is a little better, but I'd write it this way, I think. *>> >>* "Folds take operators as arguments. In some cases, it's implicit, as *>>* in the function "length". These operators are applied to elements when *>>* lazy evaluation requires it, with a fold 'accumulator' as one of the *>>* operands. 'foldMap' uses a function (implicit? explicit?) that maps *>>* elements into . . . ." *
The problem you two are both facing is this: you want to describe, abstractly, generally, the common principle behind an ad-hoc lumped-together set of functions. This is very likely to result in contortions and provides you with no insight.
I think neither "ad-hoc" nor "lumped-together" is accurate. For both `Functor t` and `Foldable t` the metaphor is `t` as container. * For `Functor` we wish to preserve the shape/spine and mangle each element irrespective of other content. * For `Foldable` we wish to throw away the shape/spine and return some characteristic of the contents-as-a-whole. (The fold is possibly returning another container/contents, but it won't necessarily be the same `t`; even if it is, the result won't be the same shape/spine.) There are some frequent use-cases for "characteristic of the contents-as-a-whole": count, sum, min/max, is-element. So it makes sense to provide (possibly optimised) methods. Yes the insight is that there's a common principle. But the optimising devil is in the detail. The devilish detail is that although we're going to throw away the shape/spine, knowing its organising principle will help navigating it effectively. Otherwise we could stick with List as container -- but as Ref [1] points out, that's hardly ever wise. For somebody coming to the docos to generate their own `instance Foldable`, thinking in terms of `toList` might help in getting the right result; it won't explain why they'd want to use something other than a List.

On Sat, Oct 02, 2021 at 07:22:29PM +1300, Anthony Clayden wrote:
The problem you two are both facing is this: you want to describe, abstractly, generally, the common principle behind an ad-hoc lumped-together set of functions. This is very likely to result in contortions and provides you with no insight.
I think neither "ad-hoc" nor "lumped-together" is accurate.
For both `Functor t` and `Foldable t` the metaphor is `t` as container.
* For `Functor` we wish to preserve the shape/spine and mangle each element irrespective of other content.
* For `Foldable` we wish to throw away the shape/spine and return some characteristic of the contents-as-a-whole.
(The fold is possibly returning another container/contents, but it won't necessarily be the same `t`; even if it is, the result won't be the same shape/spine.)
This a nice concise summary. Do you think it would be helpful to say something based on this in the Foldable overview documentation. We could even attempt to say something along these lines in Traversable, where we keep the shape spine like in Functor, but get to thread Applicative "effects" as we go, and so can end up with zero or more than one copy of the structure when all's said and done. The "effects" can involve state, and so how a element is mapped could depend on prior elements. Traversable structures `t a` can be recovered from their shape/spine `t ()` and element list `[a]`. -- Viktor. {-# LANGUAGE ScopedTypeVariables #-} import Control.Monad.State.Strict import Control.Monad.Trans.Class import Data.Functor.Identity (Identity(..)) import Data.Coerce import qualified Data.List as L -- | Combine a spine @t ()@ and its element list to yield @t a@. -- Returns `Nothing` when the element count does not match the spine recomp :: forall t a. Traversable t => (t (), [a]) -> Maybe (t a) recomp (ta, s) = runStateT (traverse f ta) s >>= (<$) <$> fst <*> guard . null . snd where f :: () -> StateT [a] Maybe a f _ = get >>= lift . L.uncons >>= (<$) <$> fst <*> put . snd -- | Transform @t a@ to its spine @t ()@ and its element list @[a]@ decomp :: forall a t. Traversable t => t a -> (t (), [a]) decomp = go where go :: t a -> (t (), [a]) go t = reverse <$> coerce (traverse @t @(State [a]) @a @()) f t z where f :: a -> State [a] () f = modify . (:) z = [] :: [a]
participants (2)
-
Anthony Clayden
-
Viktor Dukhovni