diff --git a/src/Data/SumBag.hs b/src/Data/SumBag.hs
index 12267b5aa001cc786ff8e8244407359a79b87b09..4a366122f9fec3e5eb4ff8dd42f275b40eda2188 100644
--- a/src/Data/SumBag.hs
+++ b/src/Data/SumBag.hs
@@ -13,6 +13,7 @@ module Data.SumBag
   ) where
 
 import Prelude hiding (sum, min, elem)
+import Data.Foldable hiding (sum,elem)
 import qualified Data.List.NonEmpty as NE
 
 type SumBag a = Tree a
@@ -20,10 +21,26 @@ type SumBag a = Tree a
 data Tree a = Leaf | Node (MetaData a) (Element a) (Tree a) (Tree a)
   deriving (Show)
 
+type role Tree nominal
+
 instance (Ord a, Eq a) => Eq (Tree a) where
   x == y = toAscList x == toAscList y
 
-type role Tree nominal
+-- TODO There are a few functions from foldable that can be implemented way more
+-- efficiently.
+--
+-- Notably 'minimum' and 'maximum', but also explicit recursion instead of
+-- conversions to lists in a lot of cases.
+instance Foldable Tree where
+  foldMap f = foldMap f . toAscList
+  {-# INLINE foldMap #-}
+
+  fold = sum
+  {-# INLINE fold #-}
+
+  toList = toAscList
+  {-# INLINE toList #-}
+  
 
 data MetaData a = MetaData
   { nodeSize :: Int
@@ -81,7 +98,7 @@ delete a (Node _ e left right)
           let (min, rest) = delmin right
           in balance1 min left rest
 
-toAscList :: Ord a => SumBag a -> [a]
+toAscList :: SumBag a -> [a]
 toAscList bag = helper bag []
   where helper Leaf accu = accu
         helper (Node _ e left right) accu =