<div dir="auto"><div>Another option, I believe, would be to include singletons (or constraints providing them) to the Add constructor.<br><div class="gmail_extra"><br><div class="gmail_quote">On Dec 8, 2016 3:13 AM, "Oleg Grenrus" <<a href="mailto:oleg.grenrus@iki.fi">oleg.grenrus@iki.fi</a>> wrote:<br type="attribution"><blockquote class="quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div style="word-wrap:break-word">The david’s approach is ingenious, but a more direct way, is to construct<div>the type equality proof yourself.</div><div><br></div><div>It’s more like what it would look like in say Agda:</div><div><br></div><div><div>{-# LANGUAGE DataKinds #-}</div><div>{-# LANGUAGE GADTs #-}</div><div>{-# LANGUAGE RankNTypes #-}</div><div>{-# LANGUAGE ScopedTypeVariables #-}</div><div>{-# LANGUAGE TypeFamilies #-}</div><div>{-# LANGUAGE TypeOperators #-}</div><div>{-# OPTIONS_GHC -Wall -Wno-redundant-constraints #-}</div><div>import Data.Type.Bool</div><div>import Data.Type.Equality</div><div><br></div><div>-- <a href="http://hackage.haskell.org/package/singleton-bool-0.1.2.0/docs/Data-Singletons-Bool.html" target="_blank">http://hackage.haskell.org/<wbr>package/singleton-bool-0.1.2.<wbr>0/docs/Data-Singletons-Bool.<wbr>html</a></div><div>import Data.Singletons.Bool</div><div><br></div><div>import Unsafe.Coerce (unsafeCoerce)</div><div><br></div><div>-- Safe version</div><div>proof</div><div>    :: forall a b. (SBoolI a, SBoolI b, (a || b) ~ 'False)</div><div>    => (a :~: 'False, b :~: 'False)</div><div>proof = case (sbool :: SBool a, sbool :: SBool b) of</div><div>    (SFalse, SFalse) -> (Refl, Refl)</div><div><br></div><div>-- with unsafeCoerce we don't need the contexts. they can be satisfied for all a, b :: Bool</div><div>-- and we don't want runtime SBool dictionaries hanging around (would need to change Expr definition)</div><div>proof'</div><div>    :: forall a b. ((a || b) ~ 'False)</div><div>    => (a :~: 'False, b :~: 'False)</div><div>proof' = (unsafeCoerce trivialRefl, unsafeCoerce trivialRefl)</div><div><br></div><div>data Expr t where</div><div>    Add :: Expr t -> Expr t' -> Expr (t || t')</div><div class="quoted-text"><div>    Lit :: Int -> Expr 'False</div><div>    Var :: Expr 'True</div><div><br></div></div><div class="quoted-text"><div>eval' :: Expr 'False -> Int</div><div>eval' (Lit i) = i</div></div><div>eval' (Add a b) = add a b</div><div>  where</div><div>    add :: forall t t'. ((t || t') ~ 'False) => Expr t -> Expr t' ->  Int</div><div>    add x y = case proof' :: (t :~: 'False, t' :~: 'False) of</div><div>        (Refl, Refl) -> eval' x + eval' y</div></div><div><br></div><div><br><div><div><blockquote type="cite"><div class="elided-text"><div>On 07 Dec 2016, at 09:43, Guillaume Bouchard <<a href="mailto:guillaum.bouchard+haskell@gmail.com" target="_blank">guillaum.bouchard+haskell@<wbr>gmail.com</a>> wrote:</div><br class="m_-6077618269027232225Apple-interchange-newline"></div><div><div class="elided-text"><div dir="ltr">Hi.<div><br></div><div>I have the following GADT :</div><div><br></div><div>-----------------------------</div><div><div>type family Or a b where</div><div>  Or 'False 'False = 'False</div><div>  Or _ _ = 'True</div><div><br></div><div>data Expr t where</div><div>  Add :: Expr t -> Expr t' -> Expr (Or t t')</div><div>  Lit :: Int -> Expr 'False</div><div>  Var :: Expr 'True</div></div><div>----------------------</div><div><br></div><div>The idea is that if the `Expr` contains a sub `Var`, its type is `Expr 'True`, else it is `Expr 'False`.</div><div><br></div><div>I now want to evaluate my expression, something like that :</div><div><br></div><div>--------------</div><div><div>eval :: Expr t -> Int</div><div>eval (Lit i) = i</div><div>eval (Add a b) = eval a + eval b</div><div>eval Var = error "Cannot evaluate expression with variable"</div></div><div>----------------</div><div><br></div><div>Using the GADT I previously defined, I'm tempted to remove the impossible "Var" case with :</div><div><br></div><div>---------------</div><div><div>eval' :: Expr 'False -> Int</div><div>eval' (Lit i) = i</div><div>eval' (Add a b) = eval' a + eval' b</div></div><div>----------------</div><div><br></div><div>However this does not typecheck because GHC cannot deduce that `a` and `b` are `~ Expr 'False`. Because the type family `Or` is not injective.</div><div><br></div><div>The wiki <a href="https://ghc.haskell.org/trac/ghc/wiki/InjectiveTypeFamilies" target="_blank">https://ghc.haskell.org/<wbr>trac/ghc/wiki/<wbr>InjectiveTypeFamilies</a> <wbr>classifies injectives types families in three categories, but I don't think my `Or` appears in any of them.</div><div><br></div><div>Actually `Or` is injective only if `Or t t' ~ 'False` and in this case, we can deduce that `t ~ 'False` and `t' ~ 'False`. I qualify it as a "partialy injective type family".</div><div><br></div><div>The type checker does not know that, hence my code does not compile.</div><div><br></div><div>Is there a solution, other than writing a custom type checker plugin? Is there a way to provide the inverse type family function, something such as:</div><div><br></div><div>type family InverseOr a where</div><div>     InverseOr 'False = ('False, 'False)</div><div><br></div><div>Thank you.</div><div><br></div><div>-- </div><div>G.</div></div></div><div class="quoted-text">
______________________________<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" 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.</div></div></blockquote></div><br></div></div></div><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></div></div>