<div dir="ltr">Hi Anthony<div><br></div><div>Perhaps I've misunderstood, but there's a few issues with the approaches you suggest:</div><div><br></div><div>Firstly, you refer to <a href="https://wiki.haskell.org/GHC/AdvancedOverlap">https://wiki.haskell.org/GHC/AdvancedOverlap</a>. Unfortunately (unless I've missed something) these involve listing all the instances of parent classes. I'm trying to avoid that. Indeed if I have to explicitly list all the instances I might as well write them the normal way so I'm not sure what the point of any trickery is.</div><div><br></div><div>I also tried the associated types approach you suggested towards the end of your email previously. This works perfectly fine if you can edit the base class, but I can't edit say, "Applicative" or "Num". I did something like the following, but I ran into a problem:</div><div><br></div><div><div><font face="monospace, monospace">{-# LANGUAGE TypeFamilies #-}</font></div><div><font face="monospace, monospace">{-# LANGUAGE UndecidableInstances #-}</font></div><div><font face="monospace, monospace">{-# LANGUAGE FlexibleInstances #-}</font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace">data Satisfied</font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace">class Num t => MyNum t where</font></div><div><font face="monospace, monospace">  type IsNum t</font></div><div><font face="monospace, monospace">instance Num t => MyNum t where</font></div><div><font face="monospace, monospace">  type IsNum t = Satisfied</font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace">data D = D</font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace">f :: IsNum t ~ Satisfied => t -> ()</font></div><div><font face="monospace, monospace">f _ = ()</font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace">main = print $ f D</font></div></div><div><br></div><div>Ideally this should not compile, but unfortunately it happily compiles, showing that GHC generates an "IsNum" type family instance for "D", despite the fact that "Num D" is not satisfied. </div><div><br></div><div>Any suggestions going forward from here?</div><div><br></div></div><div class="gmail_extra"><br><div class="gmail_quote">On Mon, May 7, 2018 at 9:11 PM, Anthony Clayden <span dir="ltr"><<a href="mailto:anthony_clayden@clear.net.nz" target="_blank">anthony_clayden@clear.net.nz</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><span class=""><div dir="auto">> <span style="white-space:pre-wrap;background-color:rgb(255,255,255)">It's occurred to me that one could write a class C t which is satisfied</span></div></span><pre style="white-space:pre-wrap;background-color:rgb(255,255,255)"><span class=""><div dir="auto">> whenever (A t) or (B t) is satisfied like so:</div><div dir="auto"><br></div></span><div dir="auto">Hi Clinton, this sounds like you might want "Choosing a type-class instance based on the context" <div><a href="https://wiki.haskell.org/GHC/AdvancedOverlap" target="_blank">https://wiki.haskell.org/GHC/<wbr>AdvancedOverlap</a></div></div><span class=""><div dir="auto"><br></div><div dir="auto">
> ---
>
> data Satisfied
>
> type family IsSatisfiable :: Constraint -> Type</div><div dir="auto"><br></div></span><div dir="auto">That type family is doing the same job as auxiliary class `ShowPred` on that wiki page.</div><div dir="auto"><br></div><div dir="auto">Rather than all the machinery you give for the disjunction, you could use another type family:</div><div dir="auto"><br></div><div dir="auto">type family EitherSatisfied :: Type -> Type -> Type</div><div dir="auto">instance EitherSatisfied Satisfied tb = Satisfied</div><div dir="auto">instance EitherSatisfied ta Satisfied = Satisfied</div><div dir="auto"><br></div><div dir="auto">Those two instances do overlap (as you expected); and they exhibit confluence, aka coincident overlap (they produce the same result); so that's fine.</div><div dir="auto"><br></div><div dir="auto">But you haven't given any instances for `IsSatisfiable`. How do you expect to get from the Constraint to the `Satisfied` type?</div><div dir="auto"><br></div><div dir="auto">You say</div><span class=""><div dir="auto"><br></div><div dir="auto">> <span style="font-family:-apple-system,HelveticaNeue">IsSatisfiable c = Satisfied -- (if c is satisfiable)</span><br><br></div></span><div dir="auto">What are you going to put for `c`? If you follow that wiki page, you'll need to in effect repeat every instance decl for classes `A, B`:</div><div dir="auto"><br></div><div dir="auto">instance A Int where ...</div><div dir="auto"><br></div><div dir="auto">type instance IsSatisfiable (A Int) = Satisfied</div><div dir="auto"><br></div><div dir="auto">(The wiki page was written before there were type families, so type class `ShowPred` has a Functional Dependency giving a type-level Boolean result.)</div><div dir="auto">
</div><div dir="auto">Your `C t` class becomes</div><div dir="auto">
class EitherSatisfied ( IsSatisfiable (A t)) ( IsSatisfiable (B t)) ~ Satisfied => C t where ...</div><div dir="auto"><br></div><div dir="auto">----</div><div dir="auto"><br></div><div dir="auto">Nowadays there's a better way: make Associated Types for the two classes, give them a default instance:</div><div dir="auto"><br></div><div dir="auto">class A t where</div><div dir="auto">  type APred t</div><div dir="auto">  type instance APred t = Satisfied</div><div dir="auto">  ...</div><div dir="auto"><br></div><div dir="auto">class B t where</div><div dir="auto">  type BPred t</div><pre style="white-space:pre-wrap"><div dir="auto">  type instance BPred t = Satisfied</div><div dir="auto">  ...</div></pre><div dir="auto"><br></div><div dir="auto">Now every instance defined for `A, B` in effect automatically gives you `APred, BPred` instances. <span style="font-family:-apple-system,HelveticaNeue">Then</span></div><div dir="auto"><br></div><div dir="auto">class EitherSatisifed (APred t) (BPred t) ~ Satisfied => C t where ...</div><div dir="auto"><br></div><div dir="auto"><br></div><div dir="auto">AntC</div><div dir="auto"><br></div></pre>
<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.<br></blockquote></div><br></div>