Need help understanding and fixing generic lens and overloaded labels

I started using lens after watching this great talk: https://youtu.be/LBiFYbQMAXc

I’ve since then successfully made lens with very few lines of code for custom types. But I know very little about generic and overloaded labels. I encountered a problem when trying to make lens for these types (only showed the relevant ones):

data Chat = Chat
  { users :: Map Int User
  , msgs :: [ MsgFromServer ]
  , joinCount :: Int
  , config :: Config
  } deriving ( Generic )


data Config = Config         
  { maxJoinCount :: Maybe Int
  , expiry :: Expiry         
  , persist :: Bool          
  , sendHistory :: Bool      
  } deriving ( Generic )     
instance FromJSON Config     
                             
                             
data Expiry                  
  = Empty                    
  | MaxJoined                
  | Never                    
  deriving ( Generic )       
instance FromJSON Expiry     


isMaxJoined :: Chat -> Bool
isMaxJoined chat =
  case chat ^. #config . #maxJoinCount of
    Just posInt ->
      if chat ^. #joinCount == posInt then True
      else False

    _ -> False

I got 4 errors:
• No instance for (GHC.OverloadedLabels.IsLabel
“config” (b0 -> Chat -> Data.Functor.Const.Const (Maybe a0) Chat))
arising from the overloaded label ‘#config
(maybe you haven’t applied a function to enough arguments?)
• In the first argument of ‘(.)’, namely ‘#config
In the second argument of ‘(^.)’, namely ‘#config . #maxJoinCount
In the expression: chat ^. #config . #maxJoinCount
|
77 | case chat ^. #config . #maxJoinCount of

^^^^^^^
• No instance for (GHC.OverloadedLabels.IsLabel                                   
                     "maxJoinCount"                                               
                     ((Maybe a0 -> Data.Functor.Const.Const (Maybe a0) (Maybe a0))
                      -> b0))                                                     
    arising from the overloaded label ‘#maxJoinCount’                             
    (maybe you haven't applied a function to enough arguments?)                   
• In the second argument of ‘(.)’, namely ‘#maxJoinCount’                         
  In the second argument of ‘(^.)’, namely ‘#config . #maxJoinCount’              
  In the expression: chat ^. #config . #maxJoinCount                              

|
77 | case chat ^. #config . #maxJoinCount of

^^^^^^^^^^^^^
• Ambiguous type variable ‘a0’ arising from a use of ‘==’            
  prevents the constraint ‘(Eq a0)’ from being solved.               
  Relevant bindings include posInt :: a0 (bound at src/Chat.hs:78:10)
  prevents the constraint ‘(Eq a0)’ from being solved.                    
  Relevant bindings include posInt :: a0 (bound at src/Chat.hs:78:10)     
  Probable fix: use a type annotation to specify what ‘a0’ should be.     
  These potential instances exist:                                        
    instance (Eq k, Eq a) => Eq (Map k a)                                 
      -- Defined in ‘Data.Map.Internal’                                   
    instance Eq Ordering -- Defined in ‘ghc-prim-0.6.1:GHC.Classes’       
    instance Eq ChatId -- Defined at src/Chat.hs:32:14                    
    ...plus 24 others                                                     
    ...plus 216 instances involving out-of-scope types                    
    (use -fprint-potential-instances to see them all)                     
• In the expression: chat ^. #joinCount == posInt                         
  In the expression:                                                      
    if chat ^. #joinCount == posInt then True else False                  
  In a case alternative:                                                  
      Just posInt -> if chat ^. #joinCount == posInt then True else False 

|
79 | if chat ^. #joinCount == posInt then True

^^^^^^^^^^^^^^^^^^^^^^^^^^^^
• No instance for (GHC.OverloadedLabels.IsLabel                           
                     "joinCount" (Control.Lens.Getter.Getting a0 Chat a0))
    arising from the overloaded label ‘#joinCount’                        
    (maybe you haven't applied a function to enough arguments?)           
• In the second argument of ‘(^.)’, namely ‘#joinCount’                   
  In the first argument of ‘(==)’, namely ‘chat ^. #joinCount’            
  In the expression: chat ^. #joinCount == posInt                         

|
79 | if chat ^. #joinCount == posInt then True
| ^^^^^^^^^^

So everything worked before I added this new Config type. And I’m most surprised that #joinCount is somehow not working here.

I found out that if I move isMaxJoined out of the src/Chat.hs module where those types and lenses are defined, into src/Lib.hs which actually uses it, the code will compile. But if I create a separate src/ChatUtils.hs and move isMaxJoined there, it somehow throws the same errors.

The resource online explaining generic and overloaded labels are too dense for me to comprehend. Can I get some directions?

1 Like

Are you importing Data.Generics.Labels on all the modules which use the labels? Data.Generics.Labels provides the IsLabel instance that “translates” between labels and lenses. Your code won’t “see” the instance otherwise.

2 Likes

Is it maybe just that the maxJoinCount label is not defined, i see that Config does not have such a field? I think all the overloading and inference can move the errors further away from the real source, so the first, third and fourth error might just be consequences of the second error. If you write an explicit type signature for posInt then some errors should get more obvious.

No. I visited that link, but couldn’t comprehend the docs there at all.
I guess I need to understand what is OverloadedLabels first? I doubt there’s any easy resources for this. I can’t understand the docs from GHC. I saw that:

if GHC sees an occurrence of the overloaded label syntax #foo, it is replaced with
fromLabel @“foo” :: alpha
plus a wanted constraint IsLabel “foo” alpha

But then what is @"foo"? When I look up @ in Haskell, I only see that it’s used for capturing a value like list@(x:xs). Here it’s followed by a string literal.

Update:
Importing Data.Generics.Labels unqualified made it compile! It’s kind of a surprise. Somehow importing a library made the code compile. I hope to know how.

@ is also used for TypeApplications and the string is a type level string literal.

You can also use the optics package. It has much better error messages:

{-# LANGUAGE OverloadedLabels, DeriveGeneric #-}

module Test where

import Optics
import GHC.Generics

data Chat = Chat
  { users :: [(Int, String)]
  , msgs :: [ String ]
  , joinCount :: Int
  , config :: Config
  } deriving ( Generic )


data Config = Config
  { persist :: Bool
  , sendHistory :: Bool
  } deriving ( Generic )


isMaxJoined :: Chat -> Bool
isMaxJoined chat =
  case chat ^. #config % #maxJoinCount of
    Just posInt -> chat ^. #joinCount == posInt
    _ -> False

Gives the error:

Test.hs:24:26: error:
    • Data constructor ‘Config’ doesn't have a field named ‘maxJoinCount’
    • In the second argument of ‘(%)’, namely ‘#maxJoinCount’
      In the second argument of ‘(^.)’, namely ‘#config % #maxJoinCount’
      In the expression: chat ^. #config % #maxJoinCount
   |
24 |   case chat ^. #config % #maxJoinCount of
   |                          ^^^^^^^^^^^^^

Sorry, I omitted those fields when trying to make it simpler. It was just that after I removed them in code, it didn’t compile either. So it left me wondering how some simple Bool types won’t work either. I updated the post to leave them in.

Ah, I see now, then @danidiaz is probably right. You probably forgot to import Data.Generic.Labels. I’m getting those same errors when I don’t import that.

When you import a library you automatically import its type class instances. And the OverloadedLabels mechanism uses type classes to resolve the labels. That is why you have to import it, but you don’t have to import any specific function or type from that module.

The official documentation of OverloadedLabels is here. That has all the details.

Ah okay. I’m guessing that library has made IsLabel instances for types like String, Bool, Maybe?
But then why is it that things have worked before the import, to a point?

It uses yet another feature called Generic programming to automatically derive IsLabel instances for any type that is an instance of the Generic type class (which basically exposes the structure of the type).

I think this is really hard to answer without concrete examples of your previous code.

It uses yet another feature called Generic programming

Ah, that’s another piece of puzzle I need to crack.

I think this is really hard to answer without concrete examples of your previous code.

Very odd. I grep’ed through my code for Data.Generics.Labels, and surprisingly found them imported. But I have absolutely no memories of importing them. I don’t even recognize this library.

And removing the import causes the same kinds of errors. So I think that’s the answer here.

@ is also used for TypeApplications and the string is a type level string literal.

I’m trying to go through the docs here. It’s one of those feelings when I’m half-understanding something. I guess I can try to brute-force it by keep looking up unknown concepts recursively, until there’s none left. Although I wish there exists some guides that are higher level then compiler docs.

You can also use the optics 1 package. It has much better error messages

I’m currently using generic-lens. optics sounds cool. Does it have any downsides I should worry about? Or should people generally just choose optics over generic-lens and lens?

I completely agree with that. This would probably warrant a blog post or something, but I cannot find anything unfortunately.

Generic programming, for example, is a bit more mature and you can find many blog posts about that, but in this use case you really only need to have very high level knowledge about it. Knowing that it exists and what kinds of things it can do is all you need, while most blog post I think go into detail about how you can use it to implement things yourself.

Also note that OverloadedLabels is quite new, so that also influences the quantity and quality of documentation.

I would say that optics has better error messages, better documentation, it has less dependencies (faster to compile) and it is a bit simpler. And lens is more mature and has more features.

1 Like

One way of explaining OverloadedLabels could be through an analogy with Monoid, in particular with mempty.

Each type that has an instance of Monoid has its own mempty value that can be conjured out of thin air, just by supplying the type. For example mempty :: [Int] = [] or mempty :: Data.Monoid.Sum Int = Sum 0.

The OverloadedLabels mechanism also produces values out of thin air for a type. In fact—unlike mempty—it can give you several values for the same type, because the IsLabel typeclass is also parameterized by second type of kind Symbol. Types kind Symbol are type-level strings, suitable for identifying fields at compile time.

#somename :: X is syntax sugar for “give me the value of type X that corresponds to the label somename”. For this to compile, the corresponding IsLabel "somename" X instance must exist.

Data.Generics.Labels declares an IsLabel instance for functions. What kind of functions it conjures? Lenses! When the module is imported, if GHC enconters a term #somename and from its context deduces it has type somerecord -> sometype, it puts there a lens going from somerecord to its field named somename of type sometype.

But, how does the IsLabel instance for functions know how to produce the correct lens? Well, the IsLabel instance as a precondition. It only exists for records that can be “analyzed” at compile-time using the technique employed by generic-lens.

How the optics package recommended by @jaror makes of IsLabel is, in some ways, better than how generic-lens uses it. The IsLabel instance defined in Data.Generics.Labels is an orphan, which is sometimes frowned upon (it would be too long to explain here why orphan instances are bad though). Meanwhile, the IsLabel instance in optics is not an orphan.

1 Like

I see. My next stop of studying is generic programming, I guess. Maybe some language-agnostic exposure to it will make me more comfortable in Haskell later.

That’s the direction I needed, thanks a ton for laying these out for me!

After reading your explanation several times I’m able to grasp a vague picture. I like the analogy of conjuring values out of thin air!

I looked up on Hoogle and found this:

class IsLabel (x :: Symbol) a where
  fromLabel :: a

So IsLabel class has a single function fromLabel. In generic lens library, it is implemented so that record field name as Symbol, parameterized by a where a is function, is an instance of IsLabel, or “is a label”. fromLabel will then produce a value of type a, which is of the same function type. This function takes a record, and the value at the field of matching name and type.

That makes it pretty clear why missing the import of Data.Generic.Labels will make it fail. Is this understanding correct?

Just beware that what, for example, Java calls generics is not the same thing as what Haskell calls generics. Java generics is more like data type polymorphism, like having a list with elements of an arbitrary type. While I would describe Haskell generics more like introspection or reflection of the structure or representation of user-defined data types.

Is this understanding correct?

Yes, that’s basically it. Instances are only visible if you import the module in which they are defined.

Usually, instances are defined either at the point you declare the type (like the omnipresent deriving Show for your own types) or at the point you define the class (like declaring some class Bazable and writing instances for common types Int, Bool…)

The IsLabel instance from Data.Generics.Labels is an orphan, meaning that it’s neither defined in the same module as the type (->) to which it applies, nor in the module that declares the IsLabel typeclass. This has some unpleasant consequences, like having to remember to import the module just for the typeclass.

The IsLabel instance in optics is not an orphan, because it applies not to functions but to a special abstract type Optic and is definied in the same module as the datatype itself.

Fair warning. I thought the two are related.
And yeah, reflection definitely came to my mind when I see “Symbol”.

So that’s what an orphan instance is. Thanks a ton for showing me!
I can imagine how the author of generic-lens can’t write code at the OverloadedLabels extension, nor at wherever (->) is defined (prelude?). I saw a workaround for orphan is to make a newtype. Though it’s beyond my imagination now whether it was favorable for generic-lens.