[Haskell-cafe] Proposal for GHC: global HasFoo classes

KAction at gnu.org KAction at gnu.org
Tue Feb 13 04:39:07 UTC 2018


Hello!

I have idea for GHC to make working with lenses even more convenient.

# Rationale

Let us recall, that "type Lens' a b = (a -> f a) -> (b -> f b)" is about
accessing some value of type `a' somewhere deep in value of type `b'.

Let us consider that we have following datatypes:

  -- module 1
  {-# LANGUAGE DisambiguateRecordFields  #-}
  data Foo = Foo { _a :: Int, _b :: Double }
  data Bar = Bar { _a :: Double, _c :: Char }

Since we want to be able to use 'a' as both lens into 'Foo' and into
'Bar', we would use 'makeFields' function from 'lens' package, and get
something like this generated (implementation is omited):

  -- module 1
  class HasA w p | w -> p where a :: Lens' w p
  class HasB w p | w -> p where b :: Lens' w p
  class HasC w p | w -> p where c :: Lens' w p
  instance HasA Foo Int
  instance HasA Bar Double
  instance HasB Foo Double
  instance HasC Bar Char

It is all great and convenient, but what if we have another module with

  -- module 2
  data Quiz = Quiz { _a ::  Bool }

In same spirit, 'makeFields' will create

  -- module 2
  class HasA w p | w -> p where a :: Lens' w p
  instance HasA Quiz Bool

Now, you import unqualified both modules, and you have two versions of
'a' function, one per module. From GHC's point of view, class HasA in
module 1 and module 2 are different, while we, humans, understand, that
they are not.

To mitigate this problem, common convention is to collect all types,
used in package, and their lenses in signle module. But there is no
solution {as far as I know} for lenses from different packages.

# Proposal

Let us introduce a new extension -XGlobalLensClasses (better name is
welcome). When this extension is activated in module, you can write
instances like

  instance HasFoo Foo Int where foo = -- apporiate lens

with following implicit class definition:

  class HasFoo w p | w -> p where foo :: Lens' w p

After that, module can export 'foo'. All implicit HasFoo classes, whose
instances are defined in different modules are considered the same. It
eliminates problem, described in rationale if both modules in
consideration used proposed extension.

It should be noted, that this extension would not disrupt any existing
code, although in distant future we could have it by default.

# Alternative idea

The proposal of making global only one particular class namespace
'Has<Foo>' with very specific signature is not generic enough.  Maybe we
can add option to mark class definition as global instead, merging all
global classes with same signature together?

Sounds more complicated, but this solution will not upset those people
who disagree with Lens-based HasFoo classes.

Opinions?


More information about the Haskell-Cafe mailing list