<div>On Thu, Apr 9, 2009 at 5:14 AM, Simon Peyton-Jones <span dir="ltr">&lt;<a href="mailto:simonpj@microsoft.com">simonpj@microsoft.com</a>&gt;</span> wrote:<br></div><div><blockquote class="gmail_quote" style="margin-top: 0px; margin-right: 0px; margin-bottom: 0px; margin-left: 0.8ex; border-left-width: 1px; border-left-color: rgb(204, 204, 204); border-left-style: solid; padding-left: 1ex; ">
<div class="im">| &gt; 3) Is it possible to implement the following function?<br>| &gt;<br>| &gt;&gt; mkMonoidInst :: a -&gt; (a -&gt; a -&gt; a) -&gt; MonoidInst a<br>| &gt;&gt; mkMonoidInst mempty mappend = ...<br><br></div>
No it&#39;s not possible.  And now you know why!<br><font color="#888888"><br>Simon<br></font><div><div></div></div></blockquote></div><div><br></div><div><div>Simon, </div><div><br></div></div>While we can&#39;t give him exactly what he asked for, we can approximate the construction using Oleg and CC Shan&#39;s Implicit Configurations and fulfill the spirit of the request.<div>
<br></div><div><div>&gt; {-# LANGUAGE ScopedTypeVariables, TypeOperators, MultiParamTypeClasses, FlexibleContexts, UndecidableInstances, Rank2Types, GeneralizedNewtypeDeriving #-}</div><div><br></div><div><div>Please, pardon the gratuitous use of extensions.</div>
<div><br></div></div><div>&gt; import Data.Bits</div><div>&gt; import Data.Monoid</div><div>&gt; import Data.Reflection -- from package &#39;reflection&#39;</div><div><br></div><div>First define the concept of a dictionary for a monoid.</div>
<div><br></div><div>&gt;  type M a = (a, a -&gt; a -&gt; a)</div><div><br></div><div>Then provide a type level brand that indicates which dictionary you are going to use.</div><div><br></div><div>&gt; data (a `WithMonoid` s) = Mon { getWithMonoid :: a } deriving (Eq,Ord,Show)<br>
</div><div><br></div><div>Use reflection to access the dictionary</div><div><br></div><div>&gt; instance (s `Reflects` M a) =&gt; Monoid (a `WithMonoid` s) where</div><div>&gt;     mempty = Mon (fst (reflect (undefined :: s)))</div>
<div>&gt;     Mon a `mappend` Mon b = Mon ((snd (reflect (undefined :: s))) a b)</div><div><br></div><div>Reify a monoid dictionary for use within a universally quantified world, ala ST.</div><div><br></div><div>&gt; reifyMonoid :: a -&gt; (a -&gt; a -&gt; a) -&gt; (forall s. (s `Reflects` M a) =&gt; s -&gt; w) -&gt; w</div>
<div>&gt; reifyMonoid = curry reify</div><div><br></div><div>Change the type of the above to avoid the spurious argument, and to automatically unwrap the result.</div><div><br></div><div>&gt; withMonoid :: a -&gt; (a -&gt; a -&gt; a) -&gt; (forall s. (s `Reflects` M a) =&gt; w `WithMonoid` s) -&gt; w</div>
<div>&gt; withMonoid = withMonoid&#39; undefined where</div><div>&gt;    withMonoid&#39; :: w -&gt; a -&gt; (a -&gt; a -&gt; a) -&gt; (forall s. (s `Reflects` M a) =&gt; w `WithMonoid` s) -&gt; w</div><div>&gt;    withMonoid&#39; (_::w) (i::a) f k = reifyMonoid i f (\(_::t) -&gt; getWithMonoid (k :: w `WithMonoid` t))</div>
<div><br></div><div>And now we have some likely candidates to test:</div><div><br></div><div>&gt; test :: Int</div><div>&gt; test = withMonoid 0 (+) (mconcat [Mon 2,mempty,Mon 0])</div><div><br></div><div>&gt; test2 :: Int</div>
<div>&gt; test2 = withMonoid 1 (*) (mconcat [Mon 3,mempty,Mon 2])</div><div><br></div><div>&gt; test3 :: Integer</div><div>&gt; test3 = withMonoid 0 xor (mconcat [Mon 4,mempty,Mon 4])</div><div><br></div></div><div><div>*Main&gt; test</div>
<div>Loading package reflection-0.1.1 ... linking ... done.</div><div>2</div><div><div>*Main&gt; test2</div><div>6</div><div>*Main&gt; test3</div><div>0</div><div><br></div><div>There you have it, everything works out.</div>
</div><div><br></div><div>Amusingly, I have a similar set of constructions for reifying other kinds of constructs in my &#39;monoids&#39; library on Hackage, but I don&#39;t currently provide a reified Monoid type, mainly because the signature isn&#39;t enough to enforce its associativity.</div>
<div><br></div><div>However, I do allow you to reify an arbitrary function into a &#39;Reducer&#39; using this trick to enable you to uniformly inject values into a particular monoid.</div><div><br></div><div>-Edward Kmett</div>
<div><br></div><div class="gmail_quote"><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex;"><div><div class="h5">
<br>
| -----Original Message-----<br>
| From: <a href="mailto:haskell-cafe-bounces@haskell.org">haskell-cafe-bounces@haskell.org</a> [mailto:<a href="mailto:haskell-cafe-bounces@haskell.org">haskell-cafe-bounces@haskell.org</a>] On<br>
| Behalf Of Lennart Augustsson<br>
| Sent: 09 April 2009 09:54<br>
| To: Martijn van Steenbergen<br>
| Cc: Haskell Cafe<br>
| Subject: Re: [Haskell-cafe] Ambiguous reified dictionaries<br>
|<br>
| That program is incorrect, it contains two instances for Monoid Int,<br>
| and the compiler should flag it as illegal.<br>
|<br>
|    -- Lennart<br>
|<br>
| On Thu, Apr 9, 2009 at 10:35 AM, Martijn van Steenbergen<br>
| &lt;<a href="mailto:martijn@van.steenbergen.nl">martijn@van.steenbergen.nl</a>&gt; wrote:<br>
| &gt; Good morning,<br>
| &gt;<br>
| &gt; The [1]GHC user&#39;s guide, section 8.4.5 says:<br>
| &gt;<br>
| &gt; &quot;The new feature is that pattern-matching on MkSet (as in the definition of<br>
| &gt; insert) makes available an (Eq a) context. In implementation terms, the<br>
| &gt; MkSet constructor has a hidden field that stores the (Eq a) dictionary that<br>
| &gt; is passed to MkSet; so when pattern-matching that dictionary becomes<br>
| &gt; available for the right-hand side of the match.&quot;<br>
| &gt;<br>
| &gt; But what happens if there are several dictionaries available?<br>
| &gt;<br>
| &gt; Consider these three modules:<br>
| &gt;<br>
| &gt; ReifyMonoid.hs:<br>
| &gt;<br>
| &gt;&gt; {-# LANGUAGE GADTs #-}<br>
| &gt;&gt;<br>
| &gt;&gt; module ReifyMonoid where<br>
| &gt;&gt;<br>
| &gt;&gt; import Data.Monoid<br>
| &gt;&gt;<br>
| &gt;&gt; data MonoidInst a where<br>
| &gt;&gt;  MkMonoidInst :: Monoid a =&gt; MonoidInst a<br>
| &gt;<br>
| &gt; ReifySum.hs:<br>
| &gt;<br>
| &gt;&gt; module ReifySum where<br>
| &gt;&gt;<br>
| &gt;&gt; import ReifyMonoid<br>
| &gt;&gt; import Data.Monoid<br>
| &gt;&gt;<br>
| &gt;&gt; instance Monoid Int where<br>
| &gt;&gt;  mempty = 0<br>
| &gt;&gt;  mappend = (+)<br>
| &gt;&gt;<br>
| &gt;&gt; intSum :: MonoidInst Int<br>
| &gt;&gt; intSum = MkMonoidInst<br>
| &gt;<br>
| &gt; ReifyProd.hs:<br>
| &gt;<br>
| &gt;&gt; module ReifyProd where<br>
| &gt;&gt;<br>
| &gt;&gt; import ReifyMonoid<br>
| &gt;&gt; import Data.Monoid<br>
| &gt;&gt;<br>
| &gt;&gt; instance Monoid Int where<br>
| &gt;&gt;  mempty = 1<br>
| &gt;&gt;  mappend = (*)<br>
| &gt;&gt;<br>
| &gt;&gt; intProd :: MonoidInst Int<br>
| &gt;&gt; intProd = MkMonoidInst<br>
| &gt;<br>
| &gt; Now a function<br>
| &gt;<br>
| &gt;&gt; emp :: MonoidInst a -&gt; a<br>
| &gt;&gt; emp MkMonoidInst = mempty<br>
| &gt;<br>
| &gt; works as you&#39;d expect:<br>
| &gt;<br>
| &gt; *ReifySum ReifyProd&gt; emp intSum<br>
| &gt; 0<br>
| &gt; *ReifySum ReifyProd&gt; emp intProd<br>
| &gt; 1<br>
| &gt;<br>
| &gt; But what about this function?<br>
| &gt;<br>
| &gt;&gt; empAmb :: MonoidInst a -&gt; MonoidInst a -&gt; a<br>
| &gt;&gt; empAmb MkMonoidInst MkMonoidInst = mempty<br>
| &gt;<br>
| &gt; Now there are two dictionaries available. GHC consistently picks the one<br>
| &gt; from the second argument:<br>
| &gt;<br>
| &gt; *ReifySum ReifyProd&gt; empAmb intProd intSum<br>
| &gt; 1<br>
| &gt; *ReifySum ReifyProd&gt; empAmb intSum intProd<br>
| &gt; 0<br>
| &gt;<br>
| &gt; My questions are:<br>
| &gt;<br>
| &gt; 1) Shouldn&#39;t GHC reject this as being ambiguous?<br>
| &gt; 2) Should class constraints only be available on existentially qualified<br>
| &gt; type variables to prevent this from happening at all?<br>
| &gt; 3) Is it possible to implement the following function?<br>
| &gt;<br>
| &gt;&gt; mkMonoidInst :: a -&gt; (a -&gt; a -&gt; a) -&gt; MonoidInst a<br>
| &gt;&gt; mkMonoidInst mempty mappend = ...<br>
| &gt;<br>
| &gt; Thank you,<br>
| &gt;<br>
| &gt; Martijn.<br>
| &gt;<br>
| &gt;<br>
| &gt;<br>
| &gt; [1]<br>
| &gt; <a href="http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-" target="_blank">http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-</a><br>
| extensions.html#gadt-style<br>
| &gt; _______________________________________________<br>
| &gt; Haskell-Cafe mailing list<br>
| &gt; <a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
| &gt; <a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
| &gt;<br>
| _______________________________________________<br>
| Haskell-Cafe mailing list<br>
| <a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
| <a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
<br>
_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
</div></div></blockquote></div><br></div>