[Haskell-cafe] pattern match on forall'ed data
Patrick Chilton
chpatrick at gmail.com
Thu Jul 21 09:50:33 UTC 2016
You also might want to consider whether this existential approach is
correct to begin with. Could you just use a Maybe SomeData instead? Do you
need the existential at all?
https://lukepalmer.wordpress.com/2010/01/24/haskell-antipattern-existential-typeclass/
On Thu, Jul 21, 2016 at 10:48 AM, Corentin Dupont <corentin.dupont at gmail.com
> wrote:
> That's great, exactly what I need.
> What do you mean by "just Typeable"?
> Do you have another idea in mind?
>
> On Thu, Jul 21, 2016 at 10:23 AM, Jonas Scholl <
> anselm.scholl at tu-harburg.de> wrote:
>
>> If you want to use just Typeable, you can implement your own cast:
>> Extract the TypeRep of the thing in SomeData, get the TyCon, which is
>> the top-level constructor, i.e. Maybe without arguments, and compare it
>> with the TyCon from Maybe. If they match, you coerce the value to Maybe
>> () and use isNothing. While this is not completely safe, we do not
>> evaluate the thing we just coerced to (), and thus are safe, as Maybe
>> should have identical representation regardless of the type parameter.
>>
>> isNothing' :: SomeData -> Bool
>> isNothing' (SomeData a) = tyCon == maybeTyCon
>> && isNothing (unsafeCoerce a :: Maybe ())
>> where
>> tyCon = typeRepTyCon (typeRep (mkProxy a))
>> maybeTyCon = typeRepTyCon $ typeRep (Proxy :: Proxy (Maybe ()))
>> mkProxy :: a -> Proxy a
>> mkProxy = const Proxy
>>
>>
>> On 07/21/2016 09:51 AM, Corentin Dupont wrote:
>> > Hi Ivan,
>> > I could use isNothing, but the data is forall'ed...
>> > I tried but it doesn't work:
>> >
>> > data SomeData = forall e. (Typeable e, Eq e) => SomeData e
>> >
>> > isNothing' :: SomeData -> Bool
>> > isNothing' (SomeData a) = case (cast a) of
>> > (a :: Maybe a) -> isNothing a
>> >
>> > Could not deduce (Typeable a) arising from a use of ‘cast’
>> >
>> > On Wed, Jul 20, 2016 at 11:21 PM, Ivan Lazar Miljenovic
>> > <ivan.miljenovic at gmail.com <mailto:ivan.miljenovic at gmail.com>> wrote:
>> >
>> > On 21 July 2016 at 02:30, Corentin Dupont <
>> corentin.dupont at gmail.com
>> > <mailto:corentin.dupont at gmail.com>> wrote:
>> > > I see....
>> > > The think is, I am interested to know if "e" is "Nothing",
>> whatever the type
>> > > of Nothing is!
>> >
>> > Data.Maybe.isNothing ?
>> >
>> > >
>> > >
>> > >
>> > > On Wed, Jul 20, 2016 at 5:44 PM, Patrick Chilton
>> > <chpatrick at gmail.com <mailto:chpatrick at gmail.com>>
>> > > wrote:
>> > >>
>> > >> It's because you're doing === Nothing and the type of the
>> Nothing is
>> > >> ambiguous (Maybe a1).
>> > >>
>> > >> On Wed, Jul 20, 2016 at 5:18 PM, Corentin Dupont
>> > >> <corentin.dupont at gmail.com <mailto:corentin.dupont at gmail.com>>
>> wrote:
>> > >>>
>> > >>> Hi all,
>> > >>> I'm surprised this doesn't work:
>> > >>>
>> > >>> data SomeData = forall e. (Typeable e, Eq e) => SomeData e
>> > >>>
>> > >>> (===) :: (Typeable a, Typeable b, Eq a, Eq b) => a -> b ->
>> Bool
>> > >>> (===) x y = cast x == Just y
>> > >>>
>> > >>> test :: SomeData' -> Bool
>> > >>> test (SomeData' e) | e === Nothing = True
>> > >>> test _ = False
>> > >>>
>> > >>> It says
>> > >>> Could not deduce (Eq a1) arising from a use of ‘===’
>> > >>>
>> > >>> How can I achieve something of the same effect?
>> > >>>
>> > >>> Thanks
>> > >>> Corentin
>> > >>>
>> > >>> _______________________________________________
>> > >>> Haskell-Cafe mailing list
>> > >>> To (un)subscribe, modify options or view archives go to:
>> > >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>> > >>> Only members subscribed via the mailman list are allowed to
>> post.
>> > >>
>> > >>
>> > >
>> > >
>> > > _______________________________________________
>> > > Haskell-Cafe mailing list
>> > > To (un)subscribe, modify options or view archives go to:
>> > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>> > > Only members subscribed via the mailman list are allowed to post.
>> >
>> >
>> >
>> > --
>> > Ivan Lazar Miljenovic
>> > Ivan.Miljenovic at gmail.com <mailto:Ivan.Miljenovic at gmail.com>
>> > http://IvanMiljenovic.wordpress.com
>> >
>> >
>> >
>> >
>> > _______________________________________________
>> > Haskell-Cafe mailing list
>> > To (un)subscribe, modify options or view archives go to:
>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>> > Only members subscribed via the mailman list are allowed to post.
>> >
>>
>>
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> To (un)subscribe, modify options or view archives go to:
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>> Only members subscribed via the mailman list are allowed to post.
>>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20160721/971df840/attachment-0001.html>
More information about the Haskell-Cafe
mailing list