プログラムが推論したい唯一の閉じた型のセットがある場合は、回避することを検討Data.Typeable
し、以下に示すように GADT を使用して独自の型表現を展開することができます。これと標準の違いTypeable
は次のとおりです。
TypeRep
からの にData.Typeable
は、それらが表す型を表す型変数がありませんが、以下の代替TypeRep a
でa
は、 はあなたTypeRep
が表す型です (例: typeOf "foo" :: TypeRep [Char]
)。
- ただし、以下に示す GADT アプローチは、コンパイル時に固定された一連の型に対してのみ機能します。自作の
TypeRep
定義では、表現可能なすべての型と型コンストラクターをリストする必要があるためです。
なぜ私はこの複雑な道を進むことを提案しているのですか? この手法を使用して、 の定義で一連のパターン ガードを削除できるためですfield
。
data Schema a = ...
| Field (TypeRep a) -- my TypeRep from below, not the standard one!
| ...
field :: TypeRep a -> Schema a
field t = Field typeRep
ここでの欠点は、 GADTに型パラメーターがあることです。コンストラクターTypeRep
のケースを処理するには、他のアプローチが必要になります。これは. たぶん、次のようなことを試すことができます:Object :: [Schema] -> Schema
[Schema]
[Schema a]
{-# LANGUAGE GADTs #-}
data Schema a where
Field :: TypeRep a -> Schema a
Array :: Schema a -> Schema (Array a)
Object2 :: Schema a -> Schema b -> Schema (a, b)
Object3 :: Schema a -> Schema b -> Schema c -> Schema (a, b, c)
...
しかし、以下のコードを調べれば、あなたがしていることに組み込むことができるいくつかのアイデアを見つけることができると思います — あなたの型は、私の型がアトミック型に加えて型コンストラクターを表すことができることを除いて、以下のTypeEnum
私の型に似ています.TypeRep
コードは次のとおりです (選択したタイプに合わせて簡単に変更できるはずです)。
{-# LANGUAGE GADTs #-}
import Control.Applicative
----------------------------------------------------------------
----------------------------------------------------------------
--
-- | Type representations. If @x :: TypeRep a@, then @x@ is a singleton
-- value that stands in for type @a@.
data TypeRep a where
Integer :: TypeRep Integer
Char :: TypeRep Char
Maybe :: TypeRep a -> TypeRep (Maybe a)
List :: TypeRep a -> TypeRep [a]
Pair :: TypeRep a -> TypeRep b -> TypeRep (a, b)
-- | Typeclass for types that have a TypeRep
class Representable a where
typeRep :: TypeRep a
instance Representable Integer where typeRep = Integer
instance Representable Char where typeRep = Char
instance Representable a => Representable (Maybe a) where
typeRep = Maybe typeRep
instance Representable a => Representable [a] where
typeRep = List typeRep
instance (Representable a, Representable b) => Representable (a,b) where
typeRep = Pair typeRep typeRep
typeOf :: Representable a => a -> TypeRep a
typeOf = const typeRep
----------------------------------------------------------------
----------------------------------------------------------------
--
-- | Type equality proofs.
data Equal a b where
Reflexivity :: Equal a a
-- | Induction rules for type equality proofs for parametric types
induction :: Equal a b -> Equal (f a) (f b)
induction Reflexivity = Reflexivity
induction2 :: Equal a a' -> Equal b b' -> Equal (f a b) (f a' b')
induction2 Reflexivity Reflexivity = Reflexivity
-- | Given two TypeReps, prove or disprove their equality.
matchTypes :: TypeRep a -> TypeRep b -> Maybe (Equal a b)
matchTypes Integer Integer = Just Reflexivity
matchTypes Char Char = Just Reflexivity
matchTypes (List a) (List b) = induction <$> (matchTypes a b)
matchTypes (Maybe a) (Maybe b) = induction <$> (matchTypes a b)
matchTypes (Pair a b) (Pair a' b') =
induction2 <$> matchTypes a a' <*> matchTypes b b'
matchTypes _ _ = Nothing
----------------------------------------------------------------
----------------------------------------------------------------
--
-- Example use: type-safe coercions and casts
--
-- | Given a proof that a and b are the same type, you can
-- actually have an a -> b function.
coerce :: Equal a b -> a -> b
coerce Reflexivity x = x
cast :: TypeRep a -> TypeRep b -> a -> Maybe b
cast a b x = coerce <$> (matchTypes a b) <*> pure x
----------------------------------------------------------------
----------------------------------------------------------------
--
-- Example use: dynamic data
--
data Dynamic where
Dyn :: TypeRep a -> a -> Dynamic
-- | Inject a value of a @Representable@ type into @Dynamic@.
toDynamic :: Representable a => a -> Dynamic
toDynamic = Dyn typeRep
-- | Cast a @Dynamic@ into a @Representable@ type.
fromDynamic :: Representable a => Dynamic -> Maybe a
fromDynamic = fromDynamic' typeRep
fromDynamic' :: TypeRep a -> Dynamic -> Maybe a
fromDynamic' :: TypeRep a -> Dynamic -> Maybe a
fromDynamic' target (Dyn source value) = cast source target value
編集:私は仕方がなかったが、上記でもう少し遊んだ:
{-# LANGUAGE StandaloneDeriving #-}
import Data.List (intercalate)
--
-- And now, I believe this is very close to what you want...
--
data Schema where
Field :: TypeRep a -> Schema
Object :: [Schema] -> Schema
Array :: Schema -> Schema
deriving instance Show (TypeRep a)
deriving instance Show (Schema)
example :: Schema
example = Object [Field (List Char), Field Integer]
describeSchema :: Schema -> String
describeSchema (Field t) = "Field of type " ++ show t
describeSchema (Array s) = "Array of type " ++ show s
describeSchema (Object schemata) =
"an Object with these schemas: "
++ intercalate ", " (map describeSchema schemata)
これにより、 がdescribeSchema example
生成され"an Object with these schemas: Field of type List Char, Field of type Integer"
ます。