[Haskell-cafe] How to match on such type

Ivan Lazar Miljenovic ivan.miljenovic at gmail.com
Tue Dec 5 11:16:51 UTC 2017


On 5 December 2017 at 21:47, Baa <aquagnu at gmail.com> wrote:
> Hello, All!
>
> I have type:
>
>   infixr 9 |||
>   data a ||| b = A a|B b deriving (Eq, Data, Show)
>
> and usually I wraps into it values which are instances of my class
> IsTag:
>
>   class IsTag a where
>     anyTag :: a
>
> So, I need to check if some value wrapping by `a|||b` is equal to
> `anyTag`, i.e.:
>
>   A (B (A x)) == (anyTag::TypeOf_x)
>   ==> True

Do you:

a) know whether it should be wrapped as A or B?

b) how many layers down it is?

One solution is to use something like (untested):

-- | Is type @a@ equivalent to @anyTag :: x@ ?
class EquivToTag a x where
  tagEquiv :: a -> Proxy x -> Bool

instance {-# OVERLAPPABLE #-} EquivToTag x x where
  tagEquiv _ _ = True

instance {-# OVERLAPPABLE #-} (EquivToTag a x) => EquivToTag (a ||| b) x where
  tagEquiv _ _ = True

instance {-# OVERLAPPABLE #-} (EquivToTag b x) => EquivToTag (a ||| b) x where
  tagEquiv _ _ = True

... Except there's no way of having False here, and the two |||
instances can't really both be there (which to pick?).

I'm not sure what the intent of this is, but would it make more sense
to use a type family which resolves to a Constraint?

>
> This function must be generic, ie, it can not know anything about
> concreate TypeOf_x, only: `a|||b` and `IsTag`. How to do it???
>
> I added `Data` to `a|||b` and even to values which I "wrap" with
> `a|||b` (I assumed to use `gmap*` and Co), but this does not help me.
> Is it even possible??
>
> ==
> Best regadrs, Paul
>
> _______________________________________________
> 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
http://IvanMiljenovic.wordpress.com


More information about the Haskell-Cafe mailing list