すべてのレコード フィールドを一覧表示する
これは非常に可能でありRep
、クラスを使用して の構造を再帰することによって実際に行われます。以下のソリューションは、単一コンストラクター型に対して機能し、セレクターのないフィールドに対して空の文字列名を返します。
{-# 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 _ = []
これで、次のことができます。
selectors (Proxy :: Proxy (Rep Record))
-- [("recordId",Int32),("recordName",ByteString)]
ここで最も目立たない部分はselName
andSelector
です。このクラスは にありGHC.Generics
、生成されたセレクター タイプからセレクター名を抽出できます。の場合Record
、表現は
: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)))
セレクターの型はMain.S1_0_0Record
とMain.S1_0_1Record
です。Rep
GHC はそれらをエクスポートしないため、クラスまたは型ファミリを使用して型からそれらを抽出することによってのみ、これらの型にアクセスできます。とにかく、セレクタータグを持つ任意のノードselName
からセレクター名を取得します(より一般的なタイプですが、ここでは関係ありません)。M1
s
t s f a -> String
複数のコンストラクターを処理し、selectors
returnを持つことも可能[[(String, TypeRep)]]
です。その場合、おそらく 2 つのクラスがあります。1 つは上のクラスに似ており、特定のコンストラクターからセレクターを抽出するために使用され、もう 1 つのクラスはコンストラクターのリストを収集するために使用されます。
レコード セレクターを調べる
関数からレコード タイプを取得するのは簡単です。
class Magic f where
magic :: f -> TypeRep
instance Typeable a => Magic (a -> b) where
magic _ = typeOf (undefined :: a)
または静的に:
type family Arg f where
Arg (a -> b) = a
ただし、TH がなければ、関数が正当なセレクターなのか、それとも正しい型の関数なのかを知ることはできません。Haskell では区別できません。で名前「recordId」を検査する方法はありませんmagic recordId
。
2019 更新: GHC 8.6.5 と型付きTypeRep
s を使用したセレクター抽出。タイプアプリケーションを優先してプロキシを取り除くことで、ソリューションを少し近代化します。
{-# 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 = []
これで使用法は になりselectors @(Rep MyType)
ます。