Sunday, August 16, 2015

[clomduww] Foldable with metadata

The Foldable instances of Array and Map in Haskell do not provide access to the index or key respectively. It is possible to provide such access, but doing so requires defining Foldable differently, making it a multiparameter type class and explicitly specifying an intermediate type that packages up the element and metadata, e.g., index or key.

GHC 7.10.1, array-0.5.1.0, base-4.8.0.0, containers-0.5.6.2

{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, ScopedTypeVariables #-}
module FoldableWithKey where {
import Data.Array.IArray;
import qualified Data.Map as Map;

-- similar to Foldable, except the intermediate type can be different from the element type.
class FoldableWithKey collection intermediate where {
foldWithKey :: (intermediate -> b -> b) -> b -> collection -> b;
};

-- unclear why OVERLAPPABLE is needed here, as Map is clearly not an IArray
instance {-# OVERLAPPABLE #-} (IArray a e, Ix i) => FoldableWithKey (a i e) (i,e) where {
foldWithKey f z = foldr f z . assocs ;
};

instance FoldableWithKey (Map.Map k a) (k,a) where {
foldWithKey f = Map.foldWithKey $ \xk xa xb -> f (xk,xa) xb;
};

-- Overlapping Instance
-- Allows foldWithKey to be a drop-in replacement for foldr.
instance {-# OVERLAPPABLE #-} (Foldable t) => FoldableWithKey (t a) a where {
foldWithKey = foldr;
};

test1 :: [Int] -> Int;
test1 = foldWithKey (+) 0;

test2 :: Map.Map String Int -> Int;
test2 = foldWithKey (+) 0;

test3 :: Map.Map String Int -> (String,Int);
test3 = foldWithKey (\(s,i) (sold,iold) -> (s ++ sold, i + iold)) ("",0);

test4 :: Map.Map String Int -> Int;
-- explicit type signature weirdly needed on s
test4 = foldWithKey (\(s :: String, i) iold -> length s + i + iold) 0;

test5 :: Array Int Double -> Double;
-- explicit type signature weirdly needed on i
test5 = foldWithKey (\(i :: Int , d) dold -> d + dold + fromIntegral i) 0;
}

5 comments :

Unknown said...
This comment has been removed by the author.
Unknown said...

"-- unclear why OVERLAPPABLE is needed here, as Map is clearly not an IArray"

It's because there really isn't anything to prevent someone from providing an IArray instance for Map, and if such an instance were defined then the IArray and Map instances of FoldableWithKey with (k, a) as the intermediate would overlap.

"-- explicit type signature weirdly needed on s"

This is similar. The class isn't closed; more instances could be added, including e.g. an instance for the same Map with an intermediate like ([Int], Int).

This could be avoided by declaring the intermediate as a dependent type, but then you would have to give up the genetic Foldable instance:

class FoldableWithKey collection intermediate | collection -> intermediate where ...

Unknown said...
This comment has been removed by the author.
Unknown said...
This comment has been removed by the author.
Ken said...

Thanks for your edifying comment!