How to get constructor name with Generic

I’m using Generic to write a simple parser. The task is pretty much equivalent to write a Read instance for a simple sum type. The problem is, you need to have the constructor name (to check the input string against). You can do so by using conName but it requires an object of the type you are trying to construct (so you don’t have it ).
For a Show instance, there is no problem (I can call conName on the argument) but for Readlike how do you do ?

The best I come with is

class GHeader f where
  gParse :: Text -> [Text] -> Either Text (f a)

instance forall a c. (Constructor c, GHeader a) => GHeader (C1 c a) where
  gParse header tags = if unpack header == dropEnd 1 cname
                  then M1 <$> (gParse header tags)
                  else Left $ pack $ cname ++ " invalid header"
                  where cname = conName @c (error "dummy to get type constructor")

The problem is in relies on TypeApplication, ScopedTypeVariables and creating a “dummy” object (with `error “dummy to get type constructor”). Surely there must be something simpler.

Well, at the very least

data Dummy t c f = Dummy

... conName @c Dummy ...

probably works, doesn’t it?

1 Like

Nope

/home/max/devel/mae/Fames/app/Planner/Internal.hs:207:44: error:
    • Couldn't match kind ‘*’ with ‘Meta’
      When matching types
        t0 :: Meta -> (* -> *) -> * -> *
        Dummy :: * -> * -> * -> *
      Expected: t0 c f0 a4
        Actual: Dummy t1 c0 a4
    • In the second argument of ‘conName’, namely ‘Dummy’
      In the expression: conName @c Dummy
      In an equation for ‘cname’: cname = conName @c Dummy
    |
207 |                   where cname = conName @c Dummy -- (error "dummy to get type constructor")
    |                                            ^^^^^

It still doe rely on two extensions (one of them I am pretty sure wasn’t there at the time Generics has been introduced).

OK, fine, then

data Dummy (t :: Meta) (c :: * -> *) f = Dummy

It still doe rely on two extensions

Yes, the extensions make this better, not worse :slight_smile:

Indeed, it works, however it need a third extension (DataKinds).
I am surprised that there is no straight forward way to do so. Is there not anything possible without extension ? (out of curiosity).

Tom’s solution is probably better because it doesn’t require undefined, but cname = conName (undefined :: C1 c a x) should also work.

1 Like

Yet another option would be to define the instance for MetaCons instead of c. Something like

instance (..., KnownSymbol n) => GHeader (C1 (MetaCons n f r) a) where
   ...
   cname = symbolVal (Proxy :: Proxy n)

I can’t use undefined for coding standard reason (thus the `error “dummy” instead).

What I mean is, what I am trying to do seems a really basic use of Generic yet Generics doesn’t provide any simple way to do it. Maybe I should stick with TH :slight_smile:

I think GHC.Generics is suffering from its API being pre-TypeApplications. I suggest a new function

data Dummy (t :: Meta) (c :: * -> *) f = Dummy

conName' :: forall c. Constructor c => String
conName' = conName @c Dummy

which seems much easier to understand and use!

1 Like

The reason the Constructor class has the interface it does is exactly because the intro of generics predates many other type-level programming extensions. If it would be reintroduced now, I guess the MetaCons option I described above or a function just expecting a type-level argument would probably be the standard interface. The classic interface assumes a normal use case being one where you’re either destructing or constructing a value of the “generic” type. Your use case deviates from that in that you don’t have that, because you’re constructing an Either and want it in the Right case. Hence you’ll have to either accept partiality (i.e., undefined/error) or some form of type info passing.

2 Likes

Yes, I think this would be a good addition.

3 Likes

I guess I could use the return value itself as conName with something like

gParse header tags = 
   let result = gParse header tags
   in if hearder == conName result
       then M1 result
       else ...

I am only using Either because I am parsing a sum type and I need to both options for :+: as in

instance (GHeader a , GHeader b) => GHeader (a :+: b) where -- Sum
  gParse header tags = fmap L1 (gParse header tags) <> fmap R1 (gParse header tags)

So what would be the normal way of rewriting Read for type like Bool (without using Either )?