[Haskell-cafe] type error when specializing lens zooms in ghc >= 9.0

Brandon Allbery allbery.b at gmail.com
Fri May 12 21:13:22 UTC 2023


My first suspicion would be simplified subsumption. Try eta-expanding them.

On Fri, May 12, 2023 at 5:10 PM Olaf Klinke <olf at aatal-apotheke.de> wrote:
>
> Dear Cafe,
>
> I'm an infrequent lens user so please forgive me if the below problem
> has a trivial solution.
>
> For a long time the documentation of Control.Lens.Zoom has been
> claiming that 'zoom' and 'magnify' can be specialized to the following
> types.
>
> {-# LANGUAGE RankNTypes #-}
> -- Type error with GHC 9.0.2 or 9.2.7, okay with GHC 8.8.4
> import Control.Lens.Zoom (zoom,magnify)
> import Control.Lens.Type (Lens')
> import Control.Monad.RWS (RWS)
> zoomRWS ::    Monoid w => Lens' s s' -> RWS r w s' a -> RWS r w s a
> zoomRWS = zoom
> magnifyRWS :: Monoid w => Lens' r r' -> RWS r' w s a -> RWS r w s a
> magnifyRWS = magnify
>
> Indeed GHC 8.8.4 compiles this happily (on lens-4.18.1), but 9.0.2 (on
> lens-5.0.1) throws nearly undecipherable errors, claiming that Lens'
> can not be matched with some more specialized type involving Magnified
> and LensLike.
> The source of Control.Lens.Zoom does not differ substantially between
> 4.18.1 and 5.0.1 so my guess is it is a type checker issue. Can anyone
> explain? On which bug tracker should I raise this issue, if it is
> indeed a valid one?
> (I pulled the above versions from stackage lts-16.31, -19.5 and -20.20,
> respectively and compiled with stack.)
>
> Thanks
> Olaf
>
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.



-- 
brandon s allbery kf8nh
allbery.b at gmail.com


More information about the Haskell-Cafe mailing list