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

Viktor Dukhovni ietf-dane at dukhovni.org
Sat Oct 2 19:01:37 UTC 2021


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 at .
--   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]


More information about the Haskell-Cafe mailing list