[Haskell-cafe] How to match on such type

Baa aquagnu at gmail.com
Tue Dec 5 12:15:57 UTC 2017


Hello, Ivan!

Little context, no I don't know. I have:

  instance (Read a, Read b) => Read (a ||| b) where
    readPrec = parens $ (A <$> readPrec) <|> (B <$> readPrec)

with it I read in generic way combination of types, like:

  read "something" :: T1|||T2|||T3|||T4

I have already matching function, so I can check if some tag exists in
this tags combination. Nested layers number can be any - it's passed by
client of the library like `T1|||T2` or `T1|||T2|||T3|||T4`...

This task emerged from the fact that I can have lift of lists of tags
(already implemented) and want to match list on this list-of-lists:

  "tag1, tag2"  MATCH [ "tag1, tag3"
                      , "tag2, tag3"
                      , "tag1, tag2"
                      , "tag1, tag*" ]

/in pseudo-code/

So, I have 2 matches: ["tag1, tag2", "tag1, tag*"]. To distinguish them
I added match-weight, so more specialized will be "tag1, tag2" with
weight > than "tag1, tag*". But to be done, I need to know that "tag*"
is `anyTag`. Actually "tag1, tag*" as Haskell type is `Tags [a|||b]`,
where `Tags` is newtype-wrapper, `a|||b` is my generic type. Client
will pass this `a|||b` as some `T1|||T2|||T3...|||Tn`. So, somewhere in
this `a|||b` will be value which can be equal to `anyTag` and be
represented as "tag*". Sure, I don't know what type is it exactly (I
have not T1/T2/Tn in the library). I'm not sure is it possible even. I
added `Data` instances anywhere and now I'm trying to done it with
`gmapQ` but I have not experience with `Data` and `Typeable`.


===
Best regards, Paul

> 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.  
> 
> 
> 



More information about the Haskell-Cafe mailing list