Is it possible to list the names and types of fields in a record data type that derives Generic?

前端 未结 1 2047
野趣味
野趣味 2021-02-07 20:51

I know that for data types that derive Data.Data, constrFields gives the list of field names. Looking at the GHC.Generics documentation, I think the same should be possible for

1条回答
  •  深忆病人
    2021-02-07 21:19

    List all record fields

    This one is very much possible, and it's indeed done by recursing on the structure of Rep, using a class. The solution below works for single-constructor types and returns empty string names for fields without selectors:

    {-# LANGUAGE DeriveGeneric #-}
    {-# LANGUAGE PolyKinds #-}
    {-# LANGUAGE TypeOperators #-}
    {-# LANGUAGE FlexibleInstances #-}
    {-# LANGUAGE ScopedTypeVariables #-}
    
    import Data.ByteString (ByteString)
    import Data.Data
    import Data.Int
    import Data.Proxy
    import GHC.Generics
    import qualified Data.ByteString as B
    
    data Record = Record { recordId :: Int32, recordName :: ByteString }
      deriving (Generic)
    
    class Selectors rep where
      selectors :: Proxy rep -> [(String, TypeRep)]
    
    instance Selectors f => Selectors (M1 D x f) where
      selectors _ = selectors (Proxy :: Proxy f)
    
    instance Selectors f => Selectors (M1 C x f) where
      selectors _ = selectors (Proxy :: Proxy f)
    
    instance (Selector s, Typeable t) => Selectors (M1 S s (K1 R t)) where
      selectors _ =
        [ ( selName (undefined :: M1 S s (K1 R t) ()) , typeOf (undefined :: t) ) ]
    
    instance (Selectors a, Selectors b) => Selectors (a :*: b) where
      selectors _ = selectors (Proxy :: Proxy a) ++ selectors (Proxy :: Proxy b)
    
    instance Selectors U1 where
      selectors _ = []
    

    Now we can have:

    selectors (Proxy :: Proxy (Rep Record))
    -- [("recordId",Int32),("recordName",ByteString)]
    

    The least obvious part here is selName and Selector: this class can be found in GHC.Generics, and it allows us to extract the selector names from the generated selector types. In the case of Record, the representation is

    :kind! Rep Record
    Rep Record :: * -> *
    = D1
        Main.D1Record
        (C1
           Main.C1_0Record
           (S1 Main.S1_0_0Record (Rec0 Int32)
            :*: S1 Main.S1_0_1Record (Rec0 ByteString)))
    

    and the selector types are Main.S1_0_0Record and Main.S1_0_1Record. We can only access these types by extracting them from the Rep type using classes or type families, because GHC doesn't export them. Anyway, selName gets us the selector name from any M1 node with an s selector tag (it has a more general type t s f a -> String but that doesn't concern us here).

    It's also possible to handle multiple constructors, and have selectors return [[(String, TypeRep)]]. In that case we would probably have two classes, one similar to the one above, used for extracting selectors from a given constructor, and another class for gathering the lists for constructors.

    Inspect a record selector

    It's easy to get the record type from a function:

    class Magic f where
      magic :: f -> TypeRep
    
    instance Typeable a => Magic (a -> b) where
      magic _ = typeOf (undefined :: a)
    

    Or statically:

    type family Arg f where
       Arg (a -> b) = a
    

    However, without TH we can't know whether a function is a legitimate selector or just a function with the right type; they're indistinguishable in Haskell. There is no way to inspect the name "recordId" in magic recordId.


    2019 update: selector extraction with GHC 8.6.5 and typed TypeReps. We modernize the solution a bit by getting rid of proxies in favor of type applications.

    {-# language
      AllowAmbiguousTypes,
      DeriveGeneric,
      FlexibleContexts,
      FlexibleInstances,
      RankNTypes,
      TypeApplications,
      TypeInType
      #-}
    
    import Type.Reflection
    import GHC.Generics
    
    class Selectors rep where
      selectors :: [(String, SomeTypeRep)]
    
    instance Selectors f => Selectors (M1 D x f) where
      selectors = selectors @f
    
    instance Selectors f => Selectors (M1 C x f) where
      selectors = selectors @f
    
    instance (Selector s, Typeable t) => Selectors (M1 S s (K1 R t)) where
      selectors =
        [(selName (undefined :: M1 S s (K1 R t) ()) , SomeTypeRep (typeRep @t))]
    
    instance (Selectors a, Selectors b) => Selectors (a :*: b) where
      selectors = selectors @a ++ selectors @b
    
    instance Selectors U1 where
      selectors = []
    

    Now the usage becomes selectors @(Rep MyType).

    0 讨论(0)
提交回复
热议问题