[Haskell-cafe] Puzzling instance method definitions in Data.Sequence.Internal
Viktor Dukhovni
ietf-dane at dukhovni.org
Tue Mar 2 07:44:01 UTC 2021
In `containers`, Data.Sequence.Internal defines a Foldable instance for `Seq`
with method definitions for `length` and `null` that I'm struggling to understand:
https://github.com/haskell/containers/blob/master/containers/src/Data/Sequence/Internal.hs#L410-L415
#if MIN_VERSION_base(4,8,0)
length = length
{-# INLINE length #-}
null = null
{-# INLINE null #-}
#endif
further down the file there are also explicit top-level definitions for these
functions:
https://github.com/haskell/containers/blob/master/containers/src/Data/Sequence/Internal.hs#L2161-L2168
-- | \( O(1) \). Is this the empty sequence?
null :: Seq a -> Bool
null (Seq EmptyT) = True
null _ = False
-- | \( O(1) \). The number of elements in the sequence.
length :: Seq a -> Int
length (Seq xs) = size xs
So the intent seems clear, but I don't understand how the instance method
definitions are valid. The imports of Both Prelude and Data.Foldable don't
include `length` or `null`:
https://github.com/haskell/containers/blob/master/containers/src/Data/Sequence/Internal.hs#L194-L213
So the RHS definitions should plausibly resolve to the top-level
functions, but when I try to define a similar type class instance
GHC tells me:
‘method’ is not a (visible) method of class ‘Class’
and in any case I'd expect `length = length` to yield an infinite
loop, regardless of any other bindings in the outer scope. How
is Data.Sequence.Internal getting away with this???
--
Viktor.
More information about the Haskell-Cafe
mailing list