<div dir="ltr">I'm against this proposal but only because there is already a better attempt to solve this in a more general way. Here's a list of terms and hyperlinks that you will find interesting:<div><br></div><div>- OverloadedLabels</div><div>- IsLabel</div><div>- HasField</div><div>- <a href="https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/OverloadedLabels">https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/OverloadedLabels</a></div><div>- <a href="https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/MagicClasses">https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/MagicClasses</a></div><div>- <a href="https://github.com/ghc-proposals/ghc-proposals/pull/6">https://github.com/ghc-proposals/ghc-proposals/pull/6</a></div><div><br></div><div>The last link is represents the most up-to-date thinking on the subject. I would recommend reading the proposal and, if you see anything lacking, leaving a comment there.</div></div><div class="gmail_extra"><br><div class="gmail_quote">On Mon, Feb 12, 2018 at 11:39 PM,  <span dir="ltr"><<a href="mailto:KAction@gnu.org" target="_blank">KAction@gnu.org</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><br>
Hello!<br>
<br>
I have idea for GHC to make working with lenses even more convenient.<br>
<br>
# Rationale<br>
<br>
Let us recall, that "type Lens' a b = (a -> f a) -> (b -> f b)" is about<br>
accessing some value of type `a' somewhere deep in value of type `b'.<br>
<br>
Let us consider that we have following datatypes:<br>
<br>
  -- module 1<br>
  {-# LANGUAGE DisambiguateRecordFields  #-}<br>
  data Foo = Foo { _a :: Int, _b :: Double }<br>
  data Bar = Bar { _a :: Double, _c :: Char }<br>
<br>
Since we want to be able to use 'a' as both lens into 'Foo' and into<br>
'Bar', we would use 'makeFields' function from 'lens' package, and get<br>
something like this generated (implementation is omited):<br>
<br>
  -- module 1<br>
  class HasA w p | w -> p where a :: Lens' w p<br>
  class HasB w p | w -> p where b :: Lens' w p<br>
  class HasC w p | w -> p where c :: Lens' w p<br>
  instance HasA Foo Int<br>
  instance HasA Bar Double<br>
  instance HasB Foo Double<br>
  instance HasC Bar Char<br>
<br>
It is all great and convenient, but what if we have another module with<br>
<br>
  -- module 2<br>
  data Quiz = Quiz { _a ::  Bool }<br>
<br>
In same spirit, 'makeFields' will create<br>
<br>
  -- module 2<br>
  class HasA w p | w -> p where a :: Lens' w p<br>
  instance HasA Quiz Bool<br>
<br>
Now, you import unqualified both modules, and you have two versions of<br>
'a' function, one per module. From GHC's point of view, class HasA in<br>
module 1 and module 2 are different, while we, humans, understand, that<br>
they are not.<br>
<br>
To mitigate this problem, common convention is to collect all types,<br>
used in package, and their lenses in signle module. But there is no<br>
solution {as far as I know} for lenses from different packages.<br>
<br>
# Proposal<br>
<br>
Let us introduce a new extension -XGlobalLensClasses (better name is<br>
welcome). When this extension is activated in module, you can write<br>
instances like<br>
<br>
  instance HasFoo Foo Int where foo = -- apporiate lens<br>
<br>
with following implicit class definition:<br>
<br>
  class HasFoo w p | w -> p where foo :: Lens' w p<br>
<br>
After that, module can export 'foo'. All implicit HasFoo classes, whose<br>
instances are defined in different modules are considered the same. It<br>
eliminates problem, described in rationale if both modules in<br>
consideration used proposed extension.<br>
<br>
It should be noted, that this extension would not disrupt any existing<br>
code, although in distant future we could have it by default.<br>
<br>
# Alternative idea<br>
<br>
The proposal of making global only one particular class namespace<br>
'Has<Foo>' with very specific signature is not generic enough.  Maybe we<br>
can add option to mark class definition as global instead, merging all<br>
global classes with same signature together?<br>
<br>
Sounds more complicated, but this solution will not upset those people<br>
who disagree with Lens-based HasFoo classes.<br>
<br>
Opinions?<br>
______________________________<wbr>_________________<br>
Haskell-Cafe mailing list<br>
To (un)subscribe, modify options or view archives go to:<br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-<wbr>bin/mailman/listinfo/haskell-<wbr>cafe</a><br>
Only members subscribed via the mailman list are allowed to post.</blockquote></div><br><br clear="all"><div><br></div>-- <br><div class="gmail_signature" data-smartmail="gmail_signature">-Andrew Thaddeus Martin</div>
</div>