SAFE: a Foldable proposal

Bryan Richter b at chreekat.net
Fri Feb 26 05:53:34 UTC 2016


On Thu, Feb 25, 2016 at 09:29:48PM -0700, Kris Nuttycombe wrote:
> On Thu, Feb 25, 2016 at 4:47 AM, Thomas Tuegel wrote:
> 
> >
> > Foldable implies a notion of structural direction through the
> > associativity of its members. Set is different from the
> > well-behaved Foldables because its notion of direction or order is
> > not structural, i.e. not preserved by operations on Set.
> >
> >
> This is the first argument that I've seen in this whole messy thread
> that actually rings true for me - the fact that foldability is
> intricately tied to the ordering of elements is a very important one
> given that all that Monoid gives us is associativity and therefore
> any operation that we apply across a data structure that is *not*
> strictly ordered can have unpredictable results. Thank you very much
> for pointing this out.
> 
> Converting from a Map or a Set to an ordered data structure before
> folding is obviously the principled thing to do - with Map in
> particular, the fact that the ordering of the keys is completely
> unrelated to the ordering of the values means that any
> non-commutative operation being applied across those values with
> foldMap is essentially a roll of the dice. This is troubling and
> something that should be corrected.

Without judgment, it appears that the answer for why things are not
principled in this way is because 'it doesn't work for [our favorite
datatypes]'.

https://www.reddit.com/r/haskell/comments/47i5cp/safe_a_foldable_proposal/d0der46

Q. Shouldn't Foldable require a mappend that commutes?
A. It can't, because that wouldn't work for Map k, Set, ...

Q. Shouldn't there at least be an Ord somewhere?
A. It can't, because "the Foldable/Monoid machinery for Maybe don't
   involve Ord in any way".

So rather than being told "it should" or "it should not", I was told
"it cannot".

However, it appears that Map and Set *are* already 'converted' to an
ordered structure. This puts us in the position of having instances
for structures that logically shouldn't have them, but which work fine
anyway. Their underlying, ordered implementation is apparently
(ab)used to implement non-evil Foldable instances. Check out the
QuickCheck below.

This leads me to believe that Foldable works for unordered containers
because people need it to work for unordered containers, and damn the
principles, and (psst unordered containers aren't actually unordered
anyway).

Again, I state all this without judgment, and I don't think I've said
anything new to the people who made these decisions (assuming I
haven't gotten details wrong).

---------

    -- A quick test I wrote

    import Test.QuickCheck
    import Data.Foldable
    import qualified Data.HashSet as HS
    import qualified Data.Set as S

    prop_orderedHS xs = do
        xs' <- shuffle xs
        return $ fold (HS.fromList xs) == fold (HS.fromList xs')
      where
        types = (xs :: [String])

    prop_orderedS xs = do
        xs' <- shuffle xs
        return $ fold (S.fromList xs) == fold (S.fromList xs')
      where
        types = (xs :: [String])


------------

    -- The basis for HashSet's and HashMap's implementation of `fold`,
    -- which uses the underlying arrays, which in turn are
    -- `GHC.Exts.Array#`s. 

    -- Data/HashMap/Base.hs:907
    foldrWithKey :: (k -> v -> a -> a) -> a -> HashMap k v -> a
    foldrWithKey f = go
      where
        go z Empty                 = z
        go z (Leaf _ (L k v))      = f k v z
        go z (BitmapIndexed _ ary) = A.foldr (flip go) z ary
        go z (Full ary)            = A.foldr (flip go) z ary
        go z (Collision _ ary)     = A.foldr (\ (L k v) z' -> f k v z') z ary

-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 801 bytes
Desc: Digital signature
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20160225/ee2a50a8/attachment.sig>


More information about the Libraries mailing list