Puzzling instance method definitions in Data.Sequence.Internal

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/Sequen... #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/Sequen... -- | \( 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/Sequen... 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.

On Tue, 2 Mar 2021, Viktor Dukhovni wrote:
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/Sequen...
It is enough if the method name is imported with qualification. Surprising and maybe inconsistent but that's the state of affairs. GHC even forbids qualification on the left-hand side of a method definition. This at least is consistent with all function definitions.

On Mar 2, 2021, at 6:08 AM, Henning Thielemann
wrote: On Tue, 2 Mar 2021, Viktor Dukhovni wrote:
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/Sequen...
It is enough if the method name is imported with qualification. Surprising and maybe inconsistent but that's the state of affairs. GHC even forbids qualification on the left-hand side of a method definition. This at least is consistent with all function definitions.
Thanks, that explains it. By far from obvious, but handy to know. Indeed the module also has (one more line than I took into account): https://github.com/haskell/containers/blob/master/containers/src/Data/Sequen... import qualified Data.Foldable as F Much appreciated. -- Viktor.
participants (2)
-
Henning Thielemann
-
Viktor Dukhovni