@@ -908,10 +908,12 @@ instance Alternative Seq where
908908 (<|>) = (><)
909909
910910instance Eq a => Eq (Seq a ) where
911- xs == ys = length xs == length ys && toList xs == toList ys
911+ xs == ys = liftEq (==) xs ys
912+ {-# INLINABLE (==) #-}
912913
913914instance Ord a => Ord (Seq a ) where
914- compare xs ys = compare (toList xs) (toList ys)
915+ compare xs ys = liftCompare compare xs ys
916+ {-# INLINABLE compare #-}
915917
916918#ifdef TESTING
917919instance Show a => Show (Seq a ) where
@@ -929,11 +931,49 @@ instance Show1 Seq where
929931
930932-- | @since 0.5.9
931933instance Eq1 Seq where
932- liftEq eq xs ys = length xs == length ys && liftEq eq (toList xs) (toList ys)
934+ liftEq eq xs ys =
935+ sameSize xs ys && sameSizeLiftEqLists eq (toList xs) (toList ys)
936+ {-# INLINE liftEq #-}
933937
934938-- | @since 0.5.9
935939instance Ord1 Seq where
936- liftCompare cmp xs ys = liftCompare cmp (toList xs) (toList ys)
940+ liftCompare f xs ys = liftCmpLists f (toList xs) (toList ys)
941+ {-# INLINE liftCompare #-}
942+
943+ -- Note [Eq and Ord]
944+ -- ~~~~~~~~~~~~~~~~~
945+ -- Eq and Ord for Seq are implemented by converting to lists, which turns out
946+ -- to be quite efficient.
947+ -- However, we define our own functions to work with lists because the relevant
948+ -- list functions in base have performance issues (liftEq and liftCompare are
949+ -- recursive and cannot inline, (==) and compare are not INLINABLE and cannot
950+ -- specialize).
951+
952+ -- Same as `length xs == length ys` but uses the structure invariants to skip
953+ -- unnecessary cases.
954+ sameSize :: Seq a -> Seq b -> Bool
955+ sameSize (Seq t1) (Seq t2) = case (t1, t2) of
956+ (EmptyT , EmptyT ) -> True
957+ (Single _, Single _) -> True
958+ (Deep v1 _ _ _, Deep v2 _ _ _) -> v1 == v2
959+ _ -> False
960+
961+ -- Assumes the lists are of equal size to skip some cases.
962+ sameSizeLiftEqLists :: (a -> b -> Bool ) -> [a ] -> [b ] -> Bool
963+ sameSizeLiftEqLists eq = go
964+ where
965+ go (x: xs) (y: ys) = eq x y && go xs ys
966+ go _ _ = True
967+ {-# INLINE sameSizeLiftEqLists #-}
968+
969+ liftCmpLists :: (a -> b -> Ordering ) -> [a ] -> [b ] -> Ordering
970+ liftCmpLists cmp = go
971+ where
972+ go [] [] = EQ
973+ go [] (_: _) = LT
974+ go (_: _) [] = GT
975+ go (x: xs) (y: ys) = cmp x y <> go xs ys
976+ {-# INLINE liftCmpLists #-}
937977
938978instance Read a => Read (Seq a ) where
939979#ifdef __GLASGOW_HASKELL__
0 commit comments