<div dir="ltr"><div><div><div>That's great, it works, thanks.<br></div>Now I am blocked on this one:<br><br><span style="font-family:monospace,monospace">data Foo a where<br>  A :: Foo a<br>  B :: Foo [a]<br><br>deriving instance Typeable Foo<br>deriving instance (Data a) => Data (Foo a)</span><br><br>Could not deduce (a ~ [a0])<br>    from the context (Typeable (Foo a), Data a)<br><br><br></div>It would compile only if I comment the B constructor.<br></div>How can I make a Data instance of Foo??<br><div><div><br></div></div></div><div class="gmail_extra"><br><div class="gmail_quote">On Thu, Jul 21, 2016 at 11:26 AM, Jonas Scholl <span dir="ltr"><<a href="mailto:anselm.scholl@tu-harburg.de" target="_blank">anselm.scholl@tu-harburg.de</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">With "just Typeable" I mean using only the Typeable class. As already<br>
mentioned by Michael, it is also possible to achieve the  same effect<br>
with the Data class:<br>
<br>
data SomeData = forall e. (Data e, Eq e) => SomeData e<br>
<br>
isNothing'' :: SomeData -> Bool<br>
isNothing'' (SomeData a) = toConstr a == toConstr (Nothing :: Maybe ())<br>
<br>
Depending on your use-case, this may be simpler and it avoids using<br>
unsafeCoerce, which may make one feel a little bit uneasy. On the other<br>
hand, it adds an additional constraint. Additionally, a programmer can<br>
write his own Data instance while Typeable instances are always<br>
generated by the compiler (in newer versions of GHC).<br>
<span class=""><br>
On 07/21/2016 10:48 AM, Corentin Dupont wrote:<br>
> That's great, exactly what I need.<br>
> What do you mean by "just Typeable"?<br>
> Do you have another idea in mind?<br>
><br>
> On Thu, Jul 21, 2016 at 10:23 AM, Jonas Scholl<br>
</span><div><div class="h5">> <<a href="mailto:anselm.scholl@tu-harburg.de">anselm.scholl@tu-harburg.de</a> <mailto:<a href="mailto:anselm.scholl@tu-harburg.de">anselm.scholl@tu-harburg.de</a>>> wrote:<br>
><br>
>     If you want to use just Typeable, you can implement your own cast:<br>
>     Extract the TypeRep of the thing in SomeData, get the TyCon, which is<br>
>     the top-level constructor, i.e. Maybe without arguments, and compare it<br>
>     with the TyCon from Maybe. If they match, you coerce the value to Maybe<br>
>     () and use isNothing. While this is not completely safe, we do not<br>
>     evaluate the thing we just coerced to (), and thus are safe, as Maybe<br>
>     should have identical representation regardless of the type parameter.<br>
><br>
>     isNothing' :: SomeData -> Bool<br>
>     isNothing' (SomeData a) = tyCon == maybeTyCon<br>
>         && isNothing (unsafeCoerce a :: Maybe ())<br>
>         where<br>
>             tyCon = typeRepTyCon (typeRep (mkProxy a))<br>
>             maybeTyCon = typeRepTyCon $ typeRep (Proxy :: Proxy (Maybe ()))<br>
>             mkProxy :: a -> Proxy a<br>
>             mkProxy = const Proxy<br>
><br>
><br>
>     On 07/21/2016 09:51 AM, Corentin Dupont wrote:<br>
>     > Hi Ivan,<br>
>     > I could use isNothing, but the data is forall'ed...<br>
>     > I tried but it doesn't work:<br>
>     ><br>
>     > data SomeData = forall e. (Typeable e, Eq e) => SomeData e<br>
>     ><br>
>     > isNothing' :: SomeData -> Bool<br>
>     > isNothing' (SomeData a) = case (cast a) of<br>
>     >    (a :: Maybe a) -> isNothing a<br>
>     ><br>
>     > Could not deduce (Typeable a) arising from a use of ‘cast’<br>
>     ><br>
>     > On Wed, Jul 20, 2016 at 11:21 PM, Ivan Lazar Miljenovic<br>
>     > <<a href="mailto:ivan.miljenovic@gmail.com">ivan.miljenovic@gmail.com</a> <mailto:<a href="mailto:ivan.miljenovic@gmail.com">ivan.miljenovic@gmail.com</a>><br>
</div></div>>     <mailto:<a href="mailto:ivan.miljenovic@gmail.com">ivan.miljenovic@gmail.com</a><br>
<span class="">>     <mailto:<a href="mailto:ivan.miljenovic@gmail.com">ivan.miljenovic@gmail.com</a>>>> wrote:<br>
>     ><br>
>     >     On 21 July 2016 at 02:30, Corentin Dupont <<a href="mailto:corentin.dupont@gmail.com">corentin.dupont@gmail.com</a> <mailto:<a href="mailto:corentin.dupont@gmail.com">corentin.dupont@gmail.com</a>><br>
</span><span class="">>     >     <mailto:<a href="mailto:corentin.dupont@gmail.com">corentin.dupont@gmail.com</a> <mailto:<a href="mailto:corentin.dupont@gmail.com">corentin.dupont@gmail.com</a>>>> wrote:<br>
>     >     > I see....<br>
>     >     > The think is, I am interested to know if "e" is "Nothing", whatever the type<br>
>     >     > of Nothing is!<br>
>     ><br>
>     >     Data.Maybe.isNothing ?<br>
>     ><br>
>     >     ><br>
>     >     ><br>
>     >     ><br>
>     >     > On Wed, Jul 20, 2016 at 5:44 PM, Patrick Chilton<br>
>     >     <<a href="mailto:chpatrick@gmail.com">chpatrick@gmail.com</a> <mailto:<a href="mailto:chpatrick@gmail.com">chpatrick@gmail.com</a>><br>
</span>>     <mailto:<a href="mailto:chpatrick@gmail.com">chpatrick@gmail.com</a> <mailto:<a href="mailto:chpatrick@gmail.com">chpatrick@gmail.com</a>>>><br>
<span class="">>     >     > wrote:<br>
>     >     >><br>
>     >     >> It's because you're doing === Nothing and the type of the Nothing is<br>
>     >     >> ambiguous (Maybe a1).<br>
>     >     >><br>
>     >     >> On Wed, Jul 20, 2016 at 5:18 PM, Corentin Dupont<br>
>     >     >> <<a href="mailto:corentin.dupont@gmail.com">corentin.dupont@gmail.com</a><br>
</span>>     <mailto:<a href="mailto:corentin.dupont@gmail.com">corentin.dupont@gmail.com</a>> <mailto:<a href="mailto:corentin.dupont@gmail.com">corentin.dupont@gmail.com</a><br>
<div><div class="h5">>     <mailto:<a href="mailto:corentin.dupont@gmail.com">corentin.dupont@gmail.com</a>>>> wrote:<br>
>     >     >>><br>
>     >     >>> Hi all,<br>
>     >     >>> I'm surprised this doesn't work:<br>
>     >     >>><br>
>     >     >>> data SomeData = forall e. (Typeable e, Eq e) => SomeData e<br>
>     >     >>><br>
>     >     >>> (===) :: (Typeable a, Typeable b, Eq a, Eq b) =>  a ->  b<br>
>     ->  Bool<br>
>     >     >>> (===) x y = cast x == Just y<br>
>     >     >>><br>
>     >     >>> test :: SomeData' ->  Bool<br>
>     >     >>> test (SomeData' e) | e === Nothing = True<br>
>     >     >>> test _ = False<br>
>     >     >>><br>
>     >     >>> It says<br>
>     >     >>>  Could not deduce (Eq a1) arising from a use of ‘===’<br>
>     >     >>><br>
>     >     >>> How can I achieve something of the same effect?<br>
>     >     >>><br>
>     >     >>> Thanks<br>
>     >     >>> Corentin<br>
>     >     >>><br>
>     >     >>> _______________________________________________<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-bin/mailman/listinfo/haskell-cafe</a><br>
>     >     >>> Only members subscribed via the mailman list are allowed<br>
>     to post.<br>
>     >     >><br>
>     >     >><br>
>     >     ><br>
>     >     ><br>
>     >     > _______________________________________________<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-bin/mailman/listinfo/haskell-cafe</a><br>
>     >     > Only members subscribed via the mailman list are allowed to<br>
>     post.<br>
>     ><br>
>     ><br>
>     ><br>
>     >     --<br>
>     >     Ivan Lazar Miljenovic<br>
>     >     <a href="mailto:Ivan.Miljenovic@gmail.com">Ivan.Miljenovic@gmail.com</a> <mailto:<a href="mailto:Ivan.Miljenovic@gmail.com">Ivan.Miljenovic@gmail.com</a>><br>
</div></div>>     <mailto:<a href="mailto:Ivan.Miljenovic@gmail.com">Ivan.Miljenovic@gmail.com</a> <mailto:<a href="mailto:Ivan.Miljenovic@gmail.com">Ivan.Miljenovic@gmail.com</a>>><br>
<div class="HOEnZb"><div class="h5">>     >     <a href="http://IvanMiljenovic.wordpress.com" rel="noreferrer" target="_blank">http://IvanMiljenovic.wordpress.com</a><br>
>     ><br>
>     ><br>
>     ><br>
>     ><br>
>     > _______________________________________________<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-bin/mailman/listinfo/haskell-cafe</a><br>
>     > Only members subscribed via the mailman list are allowed to post.<br>
>     ><br>
><br>
><br>
><br>
>     _______________________________________________<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-bin/mailman/listinfo/haskell-cafe</a><br>
>     Only members subscribed via the mailman list are allowed to post.<br>
><br>
><br>
<br>
<br>
</div></div><br>_______________________________________________<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-bin/mailman/listinfo/haskell-cafe</a><br>
Only members subscribed via the mailman list are allowed to post.<br></blockquote></div><br></div>