Re: Optics?

2021-10-03 Thread Alan & Kim Zimmerman
With a pointer from Vlad and some study of the lens tutorial, I made a
proof of concept at [1].
I am deliberately not using the existing lens library as I envisage this
code ending up in GHC.

Alan

[1]
https://github.com/alanz/ghc-exactprint/blob/f218e211c47943c216a2e25d7855f98a0355f6b8/src/Language/Haskell/GHC/ExactPrint/ExactPrint.hs#L689-L723



On Sun, 3 Oct 2021 at 18:52, Vladislav Zavialov 
wrote:

> Hi Alan,
>
> Your pair of functions can be packaged up as a single function, so that
>
> getEpa :: a -> EpaLocation
> setEpa :: a -> EpaLocation -> a
>
> becomes
>
> lensEpa :: forall f. Functor f => (EpaLocation -> f EpaLocation)
> -> (a -> f a)
>
> And the get/set parts can be recovered by instantiating `f` to either
> Identity or Const.
>
> The nice thing about lenses is that they compose, so that if you need
> nested access, you could define several lenses, compose them together, and
> then reach deep into a data structure. Then lenses might offer some
> simplification. Otherwise, an ordinary getter/setter pair is just as good.
>
> - Vlad
>
> > On 3 Oct 2021, at 20:40, Alan & Kim Zimmerman 
> wrote:
> >
> > Hi all
> >
> > I am working on a variant of the exact printer which updates the
> annotation locations from the `EpaSpan` version to the `EpaDelta` version,
> as the printing happens
> >
> > data EpaLocation = EpaSpan RealSrcSpan
> >  | EpaDelta DeltaPos
> >
> > The function doing the work is this
> >
> > markAnnKw :: (Monad m, Monoid w)
> >   => EpAnn a -> (a -> EpaLocation) -> (a -> EpaLocation -> a) ->
> AnnKeywordId -> EP w m (EpAnn a)
> >
> > which gets an annotation, a function to pull a specific location out,
> and one to update it.
> >
> > I do not know much about lenses, but have a feeling that I could
> simplify things by using one.
> >
> > Can anyone give me any pointers?
> >
> > Alan
> >
> > ___
> > ghc-devs mailing list
> > ghc-devs@haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Optics?

2021-10-03 Thread Vladislav Zavialov
Hi Alan,

Your pair of functions can be packaged up as a single function, so that

getEpa :: a -> EpaLocation
setEpa :: a -> EpaLocation -> a

becomes

lensEpa :: forall f. Functor f => (EpaLocation -> f EpaLocation) -> (a 
-> f a)  

And the get/set parts can be recovered by instantiating `f` to either Identity 
or Const.

The nice thing about lenses is that they compose, so that if you need nested 
access, you could define several lenses, compose them together, and then reach 
deep into a data structure. Then lenses might offer some simplification. 
Otherwise, an ordinary getter/setter pair is just as good.

- Vlad

> On 3 Oct 2021, at 20:40, Alan & Kim Zimmerman  wrote:
> 
> Hi all
> 
> I am working on a variant of the exact printer which updates the annotation 
> locations from the `EpaSpan` version to the `EpaDelta` version, as the 
> printing happens
> 
> data EpaLocation = EpaSpan RealSrcSpan
>  | EpaDelta DeltaPos
> 
> The function doing the work is this
> 
> markAnnKw :: (Monad m, Monoid w)
>   => EpAnn a -> (a -> EpaLocation) -> (a -> EpaLocation -> a) -> AnnKeywordId 
> -> EP w m (EpAnn a)
> 
> which gets an annotation, a function to pull a specific location out, and one 
> to update it.
> 
> I do not know much about lenses, but have a feeling that I could simplify 
> things by using one.
> 
> Can anyone give me any pointers?
> 
> Alan
> 
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Optics?

2021-10-03 Thread Alan & Kim Zimmerman
Hi all

I am working on a variant of the exact printer which updates the annotation
locations from the `EpaSpan` version to the `EpaDelta` version, as the
printing happens

data EpaLocation = EpaSpan RealSrcSpan
 | EpaDelta DeltaPos

The function doing the work is this

markAnnKw :: (Monad m, Monoid w)
  => EpAnn a -> (a -> EpaLocation) -> (a -> EpaLocation -> a) ->
AnnKeywordId -> EP w m (EpAnn a)

which gets an annotation, a function to pull a specific location out, and
one to update it.

I do not know much about lenses, but have a feeling that I could simplify
things by using one.

Can anyone give me any pointers?

Alan
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


GHC indecisive whether matching on GADT constructors in arrow notation is allowed

2021-10-03 Thread Alexis King
Hi,

I’ve been working on bringing my reimplementation of arrow notation back up
to date, and I’ve run into some confusion about the extent to which arrow
notation is “supposed” to support matching on GADT constructors. Note
[Arrows and patterns] in GHC.Tc.Gen.Pat suggests they aren’t supposed to be
supported at all, which is what I would essentially expect. But issues
#17423  and #18950
 provide examples of
using GADT constructors in arrow notation, and there seems to be some
expectation that in fact they *ought* to be supported, and some
recently-added test cases verify that’s the case.

But this is quite odd, because it means the arrows test suite now includes
test cases that verify both that this is supported *and* that it isn’t… and
all of them pass! Here’s my understanding of the status quo:

   -

   Matching on constructors that bind bona fide existential variables is
   not allowed, and this is verified by the arrowfail004 test case, which
   involves the following program:

   data T = forall a. T a

   panic :: (Arrow arrow) => arrow T T
   panic = proc (T x) -> do returnA -< T x

   This program is rejected with the following error message:

   arrowfail004.hs:12:15:
   Proc patterns cannot use existential or GADT data constructors
   In the pattern: T x

   -

   Despite the previous point, matching on constructors that bind evidence
   is allowed. This is enshrined in test cases T15175, T17423, and T18950,
   which match on constructors like these:

   data DecoType a where
 DecoBool :: Maybe (String, String) -> Maybe (Int, Int) -> DecoType Bool
   data Point a where
 Point :: RealFloat a => a -> Point a


This seems rather contradictory to me. I don’t think there’s much of a
meaningful distinction between these types of matches, as they create
precisely the same set of challenges from the Core point of view… right?
And even if I’m wrong, the error message in arrowfail004 seems rather
misleading, since I would definitely call DecoBool and Point above “GADT
data constructors”.

So what’s the intended story here? Is matching on GADT constructors in
arrow notation supposed to be allowed or not? (I suspect this is really
just yet another case of “nobody really knows what’s ‘supposed’ to happen
with arrow notation,” but I figured I might as well ask out of hopefulness
that someone has some idea.)

Thanks,
Alexis
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs