<div dir="auto"><div>I need to look through a bit more of this, but explicit type application certainly can be avoided using Tagged. Once we get the necessary magic, libraries will be able to come up with whatever interfaces they like. My main concern about the generality of</div><div dir="auto"><br></div><div dir="auto"><span style="font-family:sans-serif">reify# :: forall r. (RC a => r) -> a -> r</span></div><div dir="auto"><font face="sans-serif"><br></font></div><div dir="auto"><font face="sans-serif">(as with the primop type Edward came up with) is that it lacks the `forall s` safety mechanism of the reflection library. Along with its key role in ensuring class coherence[*], that mechanism also makes it clear what specialization is and is not allowed to do with reified values. Again, I'm not sure it can mess up the simpler/more general form you and Edward propose, but it makes me nervous.</font></div><div dir="auto"><font face="sans-serif"><br></font></div><div dir="auto"><font face="sans-serif">[*] Coherence: as long as an instance of Reifies S A exists for some concrete S::K, users can't incoherently write a polymorphic Reifies instance for s::K.<br></font><div class="gmail_extra" dir="auto"><br><div class="gmail_quote">On Jan 13, 2017 7:33 PM, "Simon Peyton Jones" <<a href="mailto:simonpj@microsoft.com">simonpj@microsoft.com</a>> wrote:<br type="attribution"><blockquote class="quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">





<div lang="EN-GB" link="#0563C1" vlink="#954F72">
<div class="m_-4256948752900361843WordSection1">
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">David, Edward<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">Here’s my take on this thread about reflection.   I’ll ignore Tagged and the ‘s’ parameter, and the proxy arguments, since they are incidental.<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">I can finally see a reasonable path; I think there’s a potential GHC proposal here.<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">Simon<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"><u></u> <u></u></span></p>
<p class="MsoNormal"><b><span style="font-family:"Calibri",sans-serif">First thing</span></b><span style="font-family:"Calibri",sans-serif">: PLEASE let's give a Core rendering of whatever is proposed. If it's expressible in Core that's reassuring.  If it requires
 an extension to Core, that's a whole different thing.<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"><u></u> <u></u></span></p>
<p class="MsoNormal"><b><span style="font-family:"Calibri",sans-serif">Second</span></b><span style="font-family:"Calibri",sans-serif">.  For any
<i>particular</i> class, I think it's easy to express reify in Core.  Example (in Core):<u></u><u></u></span></p>
<p class="m_-4256948752900361843Code">reifyTypeable :: (Typeable a => b) -> TypeRep a -> b<u></u><u></u></p>
<p class="m_-4256948752900361843Code">reifyTypable k = k |> co<u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">where co is a coercion that witnesses<u></u><u></u></span></p>
<p class="m_-4256948752900361843Code">  co :: (forall a b. Typeable a => b) ~ forall a b. (TypeRep a -> b)<u></u><u></u></p>
<p class="MsoNormal"><b><span style="font-family:"Calibri",sans-serif"><u></u> <u></u></span></b></p>
<p class="MsoNormal"><b><span style="font-family:"Calibri",sans-serif">Third.  </span>
</b><span style="font-family:"Calibri",sans-serif">This does not depend, and should not depend, on the fact that single-method classes are represented with a newtype.  E.g. if we changed Typeable to be represented with a data type thus (in Core)<u></u><u></u></span></p>
<p class="m_-4256948752900361843Code">data Typeable a = MkTypeable (TypeRep a)<u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">using data rather than newtype, then we could still write reifyTypable.<u></u><u></u></span></p>
<p class="m_-4256948752900361843Code">reifyTypeable :: (Typeable a => b) -> TypeRep a -> b<u></u><u></u></p>
<p class="m_-4256948752900361843Code">reifyTypable = /\ab. \(f :: Typeable a => b). \(r :: TypeRep a).<u></u><u></u></p>
<p class="m_-4256948752900361843Code">               f (MkTypeable r)<u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">The efficiency of newtype is nice, but it’s not essential.<u></u><u></u></span></p>
<p class="MsoNormal"><b><span style="font-family:"Calibri",sans-serif"><u></u> <u></u></span></b></p>
<p class="MsoNormal"><b><span style="font-family:"Calibri",sans-serif">Fourth</span></b><span style="font-family:"Calibri",sans-serif">.   As you point out, reify# is far too polymorphic.
<b>Clearly you need reify# to be a class method!</b>  Something like this<u></u><u></u></span></p>
<p class="m_-4256948752900361843Code">class Reifiable a where<u></u><u></u></p>
<p class="m_-4256948752900361843Code">  type RC a :: Constraint  -- Short for Reified Constraint<u></u><u></u></p>
<p class="m_-4256948752900361843Code">  reify# :: forall r. (RC a => r) -> a -> r<u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">Now (in Core at least) we can make instances<u></u><u></u></span></p>
<p class="m_-4256948752900361843Code">instance Reifiable (TypeRep a) where<u></u><u></u></p>
<p class="m_-4256948752900361843Code">  type RC (TypeRep a) = Typeable a<u></u><u></u></p>
<p class="m_-4256948752900361843Code">  reify# k = k |> co  -- For a suitable co<u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">Now, we can’t write those instances in Haskell, but we could make the ‘deriving’ mechanism deal with it, thus:<u></u><u></u></span></p>
<p class="m_-4256948752900361843Code">deriving instance Reifiable (Typeable a)<u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">You can supply a ‘where’ part if you like, but if you don’t GHC will fill in the implementation for you.  It’ll check that Typeable is a single-method class; produce a suitable implementation
 (in Core, as above) for reify#, and a suitable instance for RC. Pretty simple.   Now the solver can use those instances.<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">There are lots of details<u></u><u></u></span></p>
<p class="m_-4256948752900361843MsoListParagraph"><u></u><span style="font-family:Symbol"><span>·<span style="font:7.0pt "Times New Roman"">       
</span></span></span><u></u><span style="font-family:"Calibri",sans-serif">I’ve used a single parameter class and a type function, because the call site of reify# will provide no information about the ‘c’ in (c => r) argument.<u></u><u></u></span></p>
<p class="m_-4256948752900361843MsoListParagraph"><u></u><span style="font-family:Symbol"><span>·<span style="font:7.0pt "Times New Roman"">       
</span></span></span><u></u><span style="font-family:"Calibri",sans-serif">What if some other class has the same method type?  E.g. if someone wrote 
<u></u><u></u></span></p>
<p class="m_-4256948752900361843Code">class MyTR a where op :: TypeRep a<u></u><u></u></p>
<p class="m_-4256948752900361843MsoListParagraph"><span style="font-family:"Calibri",sans-serif">would that mess up the use of reify# for Typeable?   Well it would if they also did<u></u><u></u></span></p>
<p class="m_-4256948752900361843Code">deriving instance Reifiable (MyTR a)<u></u><u></u></p>
<p class="m_-4256948752900361843MsoListParagraph"><span style="font-family:"Calibri",sans-serif">And there really is an ambiguity: what should (reify# k (tr :: TypeRep Int)) do?  Apply k to a TypeRep or to a MyTR?  So a complaint here would be entirely legitimate.<u></u><u></u></span></p>
<p class="m_-4256948752900361843MsoListParagraph"><u></u><span style="font-family:Symbol"><span>·<span style="font:7.0pt "Times New Roman"">       
</span></span></span><u></u><span style="font-family:"Calibri",sans-serif">I suppose that another formulation might be to abstract over the constraint, rather than the method type, and use explicit type application at calls of reify#.  So<u></u><u></u></span></p>
<p class="m_-4256948752900361843Code">class Reifiable c where<u></u><u></u></p>
<p class="m_-4256948752900361843Code">  type RL c :: *<u></u><u></u></p>
<p class="m_-4256948752900361843Code">  reify# :: (c => r) -> RL c -> r<u></u><u></u></p>
<p class="m_-4256948752900361843MsoListParagraph"><span style="font-family:"Calibri",sans-serif">Now all calls of reify# would have to look like
<u></u><u></u></span></p>
<p class="m_-4256948752900361843Code">reify# @(Typeable Int) k tr<u></u><u></u></p>
<p class="m_-4256948752900361843MsoListParagraph"><span style="font-family:"Calibri",sans-serif">Maybe that’s acceptable.  But it doesn’t seem as nice to me.<u></u><u></u></span></p>
<p class="m_-4256948752900361843MsoListParagraph"><u></u><span style="font-family:Symbol"><span>·<span style="font:7.0pt "Times New Roman"">       
</span></span></span><u></u><span style="font-family:"Calibri",sans-serif">One could use functional dependencies and a 2-parameter type class, but I don’t think it would change anything much.  If type functions work, they are more robust than fundeps.<u></u><u></u></span></p>
<p class="m_-4256948752900361843MsoListParagraph"><u></u><span style="font-family:Symbol"><span>·<span style="font:7.0pt "Times New Roman"">       
</span></span></span><u></u><span style="font-family:"Calibri",sans-serif">One could abstract over the type constructor rather than the type.  I see no advantage and some disadvantages<u></u><u></u></span></p>
<p class="m_-4256948752900361843Code">class Reifiable t where<u></u><u></u></p>
<p class="m_-4256948752900361843Code">  type RC t :: * -> Constraint  -- Short for Reified Constraint<u></u><u></u></p>
<p class="m_-4256948752900361843Code">  reify# :: forall r. (RC t a => r) -> t a -> r<u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"><u></u> <u></u></span></p>
<p class="m_-4256948752900361843MsoPlainText">|  <span lang="EN-US">-----Original Message-----</span><u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <span lang="EN-US">From: ghc-devs [<a href="mailto:ghc-devs-bounces@haskell.org" target="_blank">mailto:ghc-devs-bounces@<wbr>haskell.org</a>] On Behalf Of David</span><u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <span lang="EN-US">Feuer</span><u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <span lang="EN-US">Sent: 11 December 2016 05:01</span><u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <span lang="EN-US">To: ghc-devs <<a href="mailto:ghc-devs@haskell.org" target="_blank">ghc-devs@haskell.org</a>>; Edward Kmett <<a href="mailto:ekmett@gmail.com" target="_blank">ekmett@gmail.com</a>></span><u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <span lang="EN-US">Subject: Magical function to support reflection</span><u></u><u></u></p><div class="elided-text">
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  The following proposal (with fancier formatting and some improved<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  wording) can be viewed at<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <a href="https://ghc.haskell.org/trac/ghc/wiki/MagicalReflectionSupport" target="_blank">
<span style="color:windowtext;text-decoration:none">https://ghc.haskell.org/trac/<wbr>ghc/wiki/<wbr>MagicalReflectionSupport</span></a><u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  Using the Data.Reflection has some runtime costs. Notably, there can be no<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  inlining or unboxing of reified values. I think it would be nice to add a<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  GHC special to support it. I'll get right to the point of what I want, and<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  then give a bit of background about why.<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  === What I want<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  I propose the following absurdly over-general lie:<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  reify# :: (forall s . c s a => t s r) -> a -> r<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  `c` is assumed to be a single-method class with no superclasses whose<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  dictionary representation is exactly the same as the representation of `a`,<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  and `t s r` is assumed to be a newtype wrapper around `r`. In desugaring,<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  reify# f would be compiled to f@S, where S is a fresh type. I believe it's<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  necessary to use a fresh type to prevent specialization from mixing up<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  different reified values.<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  === Background<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  Let me set up a few pieces. These pieces are slightly modified from what the<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  package actually does to make things cleaner under the hood, but the<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  differences are fairly shallow.<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  newtype Tagged s a = Tagged { unTagged :: a }<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  unproxy :: (Proxy s -> a) -> Tagged s a<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  unproxy f = Tagged (f Proxy)<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  class Reifies s a | s -> a where<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|    reflect' :: Tagged s a<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  -- For convenience<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  reflect :: forall s a proxy . Reifies s a => proxy s -> a reflect _ =<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  unTagged (reflect' :: Tagged s a)<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  -- The key function--see below regarding implementation reify' :: (forall s<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  . Reifies s a => Tagged s r) -> a -> r<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  -- For convenience<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  reify :: a -> (forall s . Reifies s a => Proxy s -> r) -> r reify a f =<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  reify' (unproxy f) a<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  The key idea of reify' is that something of type<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  forall s . Reifies s a => Tagged s r<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  is represented in memory exactly the same as a function of type<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  a -> r<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  So we can currently use unsafeCoerce to interpret one as the other.<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  Following the general approach of the library, we can do this as such:<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  newtype Magic a r = Magic (forall s . Reifies s a => Tagged s r) reify' ::<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  (forall s . Reifies s a => Tagged s r) -> a -> r reify' f = unsafeCoerce<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  (Magic f)<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  This certainly works. The trouble is that any knowledge about what is<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  reflected is totally lost. For instance, if I write<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  reify 12 $ \p -> reflect p + 3<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  then GHC will not see, at compile time, that the result is 15. If I write<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  reify (+1) $ \p -> reflect p x<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  then GHC will never inline the application of (+1). Etc.<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  I'd like to replace reify' with reify# to avoid this problem.<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  Thanks,<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  David Feuer<u></u><u></u></p>
</div><p class="m_-4256948752900361843MsoPlainText">|  ______________________________<wbr>_________________<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  ghc-devs mailing list<u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <a href="mailto:ghc-devs@haskell.org" target="_blank"><span style="color:windowtext;text-decoration:none">ghc-devs@haskell.org</span></a><u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText">|  <a href="https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-devs&data=02%7C01%7Csimonpj%40microsoft.com%7C488bf00986e34ac0833208d42182c47a%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636170292905032831&sdata=quvCny8vD%2Fw%2BjIIypEtungW3OWbVmCQxFAK4%2FXrX%2Bb8%3D&reserved=0" target="_blank">
<span style="color:windowtext;text-decoration:none">https://na01.safelinks.<wbr>protection.outlook.com/?url=<wbr>http%3A%2F%2Fmail.haskell</span></a><u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText"><a href="https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-devs&data=02%7C01%7Csimonpj%40microsoft.com%7C488bf00986e34ac0833208d42182c47a%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636170292905032831&sdata=quvCny8vD%2Fw%2BjIIypEtungW3OWbVmCQxFAK4%2FXrX%2Bb8%3D&reserved=0" target="_blank"><span style="color:windowtext;text-decoration:none">| 
 .org%2Fcgi-bin%2Fmailman%<wbr>2Flistinfo%2Fghc-</span></a><u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText"><a href="https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-devs&data=02%7C01%7Csimonpj%40microsoft.com%7C488bf00986e34ac0833208d42182c47a%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636170292905032831&sdata=quvCny8vD%2Fw%2BjIIypEtungW3OWbVmCQxFAK4%2FXrX%2Bb8%3D&reserved=0" target="_blank"><span style="color:windowtext;text-decoration:none">| 
 devs&data=02%7C01%7Csimonpj%<wbr>40microsoft.com%<wbr>7C488bf00986e34ac0833208d42182<wbr>c4</span></a><u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText"><a href="https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-devs&data=02%7C01%7Csimonpj%40microsoft.com%7C488bf00986e34ac0833208d42182c47a%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636170292905032831&sdata=quvCny8vD%2Fw%2BjIIypEtungW3OWbVmCQxFAK4%2FXrX%2Bb8%3D&reserved=0" target="_blank"><span style="color:windowtext;text-decoration:none">| 
 7a%<wbr>7C72f988bf86f141af91ab2d7cd011<wbr>db47%7C1%7C0%<wbr>7C636170292905032831&sdata=quv</span></a><u></u><u></u></p>
<p class="m_-4256948752900361843MsoPlainText"><a href="https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-devs&data=02%7C01%7Csimonpj%40microsoft.com%7C488bf00986e34ac0833208d42182c47a%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636170292905032831&sdata=quvCny8vD%2Fw%2BjIIypEtungW3OWbVmCQxFAK4%2FXrX%2Bb8%3D&reserved=0" target="_blank"><span style="color:windowtext;text-decoration:none">| 
 Cny8vD%2Fw%<wbr>2BjIIypEtungW3OWbVmCQxFAK4%<wbr>2FXrX%2Bb8%3D&reserved=0</span></a><u></u><u></u></p>
</div>
</div>

</blockquote></div><br></div></div></div>