This is very true.
In fact, after some tweaking, I found that the best solution is using foldl', lazy type and force some strictness in "insert" using "seq". See below:
import Data.Foldable (foldl', foldr')
data Color = Red | Black deriving (Show)
data Tree a = Empty | Node Color (Tree a) a (Tree a)
deriving (Show)
insert :: Ord a => a -> Tree a -> Tree a
insert x t = makeBlack (ins t)
where
ins Empty = Node Red Empty x Empty
-- ins (Node color a y b) | x < y = ins a `seq` balance color (ins a) y b
-- | x == y = Node color a y b
-- | x > y = ins b `seq` balance color a y (ins b)
ins (Node color a y b) | x < y = balance color (ins a) y b
| x == y = Node color a y b
| x > y = balance color a y (ins b)
makeBlack :: Tree a -> Tree a
makeBlack (Node _ a y b) = Node Black a y b
makeBlack Empty = Empty
balance :: Color -> Tree a -> a -> Tree a -> Tree a
balance Black (Node Red (Node Red a x b) y c) z d = Node Red (Node Black a x b) y (Node Black c z d)
balance Black (Node Red a x (Node Red b y c)) z d = Node Red (Node Black a x b) y (Node Black c z d)
balance Black a x (Node Red (Node Red b y c) z d) = Node Red (Node Black a x b) y (Node Black c z d)
balance Black a x (Node Red b y (Node Red c z d)) = Node Red (Node Black a x b) y (Node Black c z d)
balance color a x b = Node color a x b
maxTree :: Ord a => Tree a -> a
maxTree (Node _ Empty n Empty) = n
maxTree (Node _ _ _ t) = maxTree t
toInsert :: [Int]
-- toInsert = [1..1000000]
toInsert = map (`mod` 100) [1..10000000]
main :: IO ()
main = putStrLn $ show $ maxTree $ foldl' (flip insert) Empty toInsert
Note that if the improvement is around 10% for "toInsert" being a monotonic sequence of integers, the improvement is much bigger (>2x for me) for a more "random" "toInsert" sequence.
L.