How do you avoid the -Wunused-top-binds with makeLenses

Ok, this is a usability question. Say that I have this code:

module Record (Record, changeRecord) where 

data Record = {
   _foo :: String,
   _bar :: Int
}

makeLenses ''Record

changeRecord :: Record -> Record 
changeRecord = undefined

I like to have the -Werror in my compiler, but then this code flags the -Werror=unused-top-binds for lenses foo and bar and to me this is perfectly fine same way I haven’t used _foo and _bar in my module.

So solutions that I’ve thinked of are:

  1. Use makeLensesFor but then I’m doing extra boilerplate just to satisfy the compiler.
  2. Split this module in 2 files, Types.hs with Record and Lenses declaration fully open and exported and then Record.hs importing Types.hs and reexporting the Record type but not the Record constructor. This solution to me “pollutes” the file/module structure of the project with extra nexting (ie Record/Types.hs)

So I wonder if someone has a solution that:

  1. Still keeps the unused-top-binds warning for the functions I define but not for the lenses
  2. Hides the internal implementation of the type and doesn’t exports constructors.
1 Like

Solution 2 sounds fine.

Or you can just export everything from module Record where if you’ll be using all the fields anyway, and then add the exports when you’re done.

Solution 2 unfortunately could have a performance cost, as GHC is more willing to perform certain optimizations when it knows that some function is used only internally in some module and not outside of it. So by having some ‘Types’ module that exports some function ‘myInternalFunction’ this may prevent such optimizations to ‘myInternalFunction’. I don’t know how realistic this concern is for things as definitions of lenses (which I guess you want inlined anyway), but still.

I somehow sometimes end up simply implementing lenses for the fields I use manually. (Or by dumping the TH and simply making that code explicit). Not really ideal either :(.

Another (IMO best in terms of usability) solution is to:

  1. Enable DuplicateRecordFields and NoFieldSelectors, drop silly underscores.
  2. Enable OverloadedRecordDot for field access.
  3. Enable OverloadedLabels and use generic optics from the optics library for field modification. You can also use generic-lens if you really want to stick with lens, but these are less efficient in terms of compile time (and sometimes runtime) performance.

Example:

{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedRecordDot #-}
module Record where

import GHC.Generics
import Optics.Core

data Record1 = Record1
  { foo :: String
  , bar :: Int
  } deriving Generic

data Record2 = Record2
  { foo :: Int
  , bar :: String
  } deriving Generic

fieldAccessExample1 :: Record1 -> String
fieldAccessExample1 r = r.foo

fieldModificationExample1 :: Record1 -> Record1
fieldModificationExample1 r = r & #foo .~ "hmm"
                                & #bar .~ 777

fieldAccessExample2 :: Record2 -> Int
fieldAccessExample2 r = r.foo

fieldModificationExample2 :: Record2 -> Record2
fieldModificationExample2 r = r & #foo .~ 123
                                & #bar .~ "hey"
9 Likes

I think your solution is what I was looking for, thanks!!

I didn’t know about the optics library, is there a comparison between the 2 libraries in terms of performance (both runtime and compile times) and feature coverage? I keep referring to Optics by example when using them and it would be too bad if the APIs diverge too much.

There’s an extensive test suite that ensures that things optimize well and benchmark suite that includes comparison with lens to ensure competitiveness.

The vast majority of api is the same. Most differences are listed here. In particular there’s a link to this blog post.

2 Likes

Note that there’s been a lot of discussion around whether TH-generated code should produce warnings, and there are even inconsistencies currently. See e.g. #18260: Warnings in TH expressions (pre-splice) should be suppressible · Issues · Glasgow Haskell Compiler / GHC · GitLab.