Gi-gtk's use of OverloadedLabels and OverloadRecordDot together

I was looking at the current example ‘hello world’ program for gi-gtk, compiling with GHC 9.6.6, and was confused by the last line of (extract):

{-# LANGUAGE ImplicitParams      #-}
{-# LANGUAGE OverloadedLabels    #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE OverloadedStrings   #-}

...

main :: IO ()
main = do
  app <- new Gtk.Application
    [ #applicationId := "haskell-gi.example"
    , On #activate (activate ?self)
    ]

  void $ app.run Nothing

I realised that, with language extension OverloadedRecordDot, app.run could mean the same as run app (where run is an in-scope field label). However, I could not see where the run field label was coming from.

I subsequently realised that app.run here actually meant the same as #run app, with #run possible because of the language extension OverloadedLabels.

My question is: is that (#field value can be written value.field) documented anywhere? I can’t see it mentioned in the following parts of the GHC 9.6.6 User Guide:

EDIT: As explained by @taylorfausak below, my question was based on a false premise.

They don’t mean the same thing:

$ ghci -XOverloadedLabels -XOverloadedRecordDot
GHCi, version 9.10.1: https://www.haskell.org/ghc/  :? for help
ghci> data Name = MkName { first, last :: String } deriving Show

ghci> let me = MkName "Taylor" "Fausak"

ghci> me.first
"Taylor"

ghci> (.first) me
"Taylor"

ghci> #first me
<interactive>:5:1: error: [GHC-39999]
    • No instance for ‘GHC.Internal.OverloadedLabels.IsLabel
                         "first" (Name -> ())’
        arising from a use of ‘it’
        (maybe you haven't applied a function to enough arguments?)
    • In the first argument of ‘print’, namely ‘it’
      In a stmt of an interactive GHCi command: print it

ghci> :t (.first)
(.first) :: GHC.Internal.Records.HasField "first" r a => r -> a

ghci> :t #first
#first :: GHC.Internal.OverloadedLabels.IsLabel "first" a => a
2 Likes

Does that mean that something clever has been done, somewhere, by the package authors to allow #run app to be written app.run in this case? EDIT: I think the answer is: Yes.

With the benefit of your pointer (many thanks), I can see that module GI.Gtk.Objects.Application of gi-gtk-4.0.9 has (the clever):

#if MIN_VERSION_base(4,13,0)
instance ( info ~ ResolveApplicationMethod t Application
         , O.OverloadedMethod info Application p
         , R.HasField t Application p
         ) => R.HasField t Application p where
  getField = O.overloadedMethod @info
#endif
1 Like

I have a follow on question: in the code immediately above defining an instance of a type class, there is a constraint (R.HasField t Application p) in the instance context which is identical to the instance being defined (R.HasField t Application p).

If anybody can help me understand what is going on in that code, I would be grateful.

Yes, I remember when that ruse was discovered. It turned out to be a long-standing ‘bug’ (or not, depending on your point of view) which SPJ found too scary to even try to fix. Note that identical context code is rejected by Hugs. Now, where on earth is that documented …? It’s on one of the long-standing tickets to do with ‘relaxed’ constraints/FunDeps/wiggly arrows. I’ll hunt around for it if I get time.

Addit: see here various comments with “circular trick”, and note it’s on a proposal DYSFUNCTIONAL pragma. You do need UndecidableInstances to get the code accepted.

How does the circular trick get through instance validation? GHC caches the constraints it already has. When it raises a Wanted, it first checks to see if it’s in the cache, to avoid a repeated search. The identical context is necessarily already in the cache. Is it type-safe? Usually yes, but see that ticket for where it’s dodgy. Here ‘dodgy’ means merely that the code won’t compile, not that it’ll cause a segfault.

2 Likes

Many thanks, that led me to here and a reference to ‘including the instance head as a constraint’ doing the trick - now I just need to understand what is ‘the trick’ that it is doing!

Ah, well done. It’s SPJ’s “Your way of getting around the fundept is terrifying.” that I was trying to find.

The whole swirl of FunDeps, overlaps, UndecidableInstances is … errm under-specified. I think best not to ask too hard how the sausage is made. And beware that since it’s ‘un(der)documented’, it’s liable to change at a future release without much warning.

The ‘trick’ is that you can get any instance decl accepted providing it has a constraint that is circular. Whether or not at a call site for the method that instance ever gets selected is then down to the murky overlapping instance mechanisms.

For HasField the situation is reasonably clear: there should be a ‘base’ instance for each combo of field label and record/structure. Or in the example above, one umbrella instance for the whole record Application. I’d be worried if there’s other instances HasField "foo" Application p ....

1 Like

It’s SPJ’s “Your way of getting around the fundept is terrifying.” that I was trying to find.

That one went immediately to my bookmarks:

Then here’s another for your collection. (Somewhat off-topic here, but very relevant for a couple of parallel threads …)

You can’t work this trick with Type Families. (In effect, the ‘trick’ is: the result depends somewhat on the arguments but chiefly on the result getting handed in at the usage site.) So

  • In retrospect it was a wise choice to use FunDeps with HasField rather than TFs.
  • FunDeps will continue to be needed for as long as HasField is the mechanism of choice.
  • Dependent Haskell will presumably also be unable to work this trick.

But Hugs has Trex (anonymous records, similar to purescript) in which the field label is part of the type/structure of the record. So you write instances to structurally decompose a record by label name/type. Your instances have a FunDep yielding the field’s type, same as HasField. The field type is straightforwardly read out of the record structure.

Looking at that ticket #18759 again, this might be a slightly less terrifying way to write that HasField instance; and less liable to get banjaxed by some future fix. (But really it’s relying on the same trick.)

instance ( info ~ ResolveApplicationMethod t Application
         , O.OverloadedMethod info Application p
         , pp ~ p                  -- R.HasField t Application p
         ) => R.HasField t Application pp where
  getField = O.overloadedMethod @info
1 Like

Thanks for all the responses. I write ‘notes to myself’ about some of my Haskell experiments, in the form of a blog. This one is at https://pilgrem.com/2024/10/31/haskell-and-gui-revisited/. I mention it in case another newbie like me can make use of my trial and error.