2012-06-11 16 views
6

Vì vậy, để giúp tôi hiểu một số tính năng và khái niệm Haskell/GHC nâng cao hơn, tôi quyết định thực hiện GADT dữ liệu được nhập động và mở rộng nó để bao gồm các loại tham số. (Tôi xin lỗi vì chiều dài của ví dụ này.)Tôi không thể nhận được đồ chơi dựa trên GADT Kiểu động để làm việc với các loại tham số

{-# LANGUAGE GADTs #-} 

module Dyn (Dynamic(..), 
      toDynamic, 
      fromDynamic 
      ) where 

import Control.Applicative 

---------------------------------------------------------------- 
---------------------------------------------------------------- 
-- 
-- Equality proofs 
-- 

-- | The type of equality proofs. 
data Equal a b where 
    Reflexivity :: Equal a a 
    -- | Inductive case for parametric types 
    Induction :: Equal a b -> Equal (f a) (f b) 

instance Show (Equal a b) where 
    show Reflexivity = "Reflexivity" 
    show (Induction proof) = "Induction (" ++ show proof ++ ")" 

---------------------------------------------------------------- 
---------------------------------------------------------------- 
-- 
-- Type representations 
-- 

-- | Type representations. If @x :: TypeRep [email protected], then @[email protected] is a singleton 
-- value that stands in for type @[email protected] 
data TypeRep a where 
    Integer :: TypeRep Integer 
    Char :: TypeRep Char 
    Maybe :: TypeRep a -> TypeRep (Maybe a) 
    List :: TypeRep a -> TypeRep [a] 

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


-- | Match two types and return @[email protected] an equality proof if they are 
-- equal, @[email protected] if they are not. 
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 _ _ = Nothing 


instance Show (TypeRep a) where 
    show Integer = "Integer" 
    show Char = "Char" 
    show (List a) = "[" ++ show a ++ "]" 
    show (Maybe a) = "Maybe (" ++ show a ++ ")" 


---------------------------------------------------------------- 
---------------------------------------------------------------- 
-- 
-- Dynamic data 
-- 

data Dynamic where 
    Dyn :: TypeRep a -> a -> Dynamic 

instance Show Dynamic where 
    show (Dyn typ val) = "Dyn " ++ show typ 

-- | Inject a value of a @[email protected] type into @[email protected] 
toDynamic :: Representable a => a -> Dynamic 
toDynamic = Dyn typeRep 

-- | Cast a @[email protected] into a @[email protected] type. 
fromDynamic :: Representable a => Dynamic -> Maybe a 
fromDynamic = fromDynamic' typeRep 

fromDynamic' :: TypeRep a -> Dynamic -> Maybe a 
fromDynamic' target (Dyn source value) = 
    case matchTypes source target of 
     Just Reflexivity -> Just value 
     Nothing -> Nothing 
     -- The following pattern causes compilation to fail. 
     Just (Induction _) -> Just value 

Compilation điều này, tuy nhiên, thất bại trên dòng cuối cùng (số dòng của tôi không phù hợp lên đến ví dụ):

../src/Dyn.hs:105:34: 
    Could not deduce (a2 ~ b) 
    from the context (a1 ~ f a2, a ~ f b) 
     bound by a pattern with constructor 
       Induction :: forall a b (f :: * -> *). 
           Equal a b -> Equal (f a) (f b), 
       in a case alternative 
     at ../src/Dyn.hs:105:13-23 
     `a2' is a rigid type variable bound by 
      a pattern with constructor 
      Induction :: forall a b (f :: * -> *). 
          Equal a b -> Equal (f a) (f b), 
      in a case alternative 
      at ../src/Dyn.hs:105:13 
     `b' is a rigid type variable bound by 
      a pattern with constructor 
      Induction :: forall a b (f :: * -> *). 
         Equal a b -> Equal (f a) (f b), 
      in a case alternative 
      at ../src/Dyn.hs:105:13 
    Expected type: a1 
     Actual type: a 
    In the first argument of `Just', namely `value' 
    In the expression: Just value 
    In a case alternative: Just (Induction _) -> Just value 

Cách tôi đọc này, trình biên dịch không thể tìm ra rằng trong Inductive :: Equal a b -> Equal (f a) (f b), ab phải bằng nhau cho các giá trị không phải dưới cùng. Vì vậy, tôi đã cố gắng Inductive :: Equal a a -> Equal (f a) (f a), nhưng điều đó không quá, trong định nghĩa của matchTypes :: TypeRep a -> TypeRep b -> Maybe (Equal a b):

../src/Dyn.hs:66:60: 
    Could not deduce (a2 ~ a1) 
    from the context (a ~ [a1]) 
     bound by a pattern with constructor 
       List :: forall a. TypeRep a -> TypeRep [a], 
       in an equation for `matchTypes' 
     at ../src/Dyn.hs:66:13-18 
    or from (b ~ [a2]) 
     bound by a pattern with constructor 
       List :: forall a. TypeRep a -> TypeRep [a], 
       in an equation for `matchTypes' 
     at ../src/Dyn.hs:66:22-27 
     `a2' is a rigid type variable bound by 
      a pattern with constructor 
      List :: forall a. TypeRep a -> TypeRep [a], 
      in an equation for `matchTypes' 
      at ../src/Dyn.hs:66:22 
     `a1' is a rigid type variable bound by 
      a pattern with constructor 
      List :: forall a. TypeRep a -> TypeRep [a], 
      in an equation for `matchTypes' 
      at ../src/Dyn.hs:66:13 
    Expected type: TypeRep a1 
     Actual type: TypeRep a 
    In the second argument of `matchTypes', namely `b' 
    In the second argument of `(<$>)', namely `(matchTypes a b)' 

Thay đổi kiểu của matchTypes :: TypeRep a -> TypeRep b -> Maybe (Equal a b) để sản xuất matchTypes :: TypeRep a -> TypeRep b -> Maybe (Equal a a) không hoạt động (chỉ cần đọc nó như là một đề xuất). Không matchTypes :: TypeRep a -> TypeRep a -> Maybe (Equal a a) (một đề xuất tầm thường khác, và điều này như tôi hiểu nó sẽ yêu cầu người dùng của fromDynamic' to know the a in the TypeRep a contained in the Động`).

Vì vậy, tôi bị bối rối. Bất kỳ con trỏ về cách di chuyển về phía trước ở đây?

+2

Bạn không thể thả hàm tạo 'Induction' và lấy cùng nguyên tắc' cảm ứng :: Eq a b -> Eq (f a) (f b); cảm ứng Reflexivity = Reflexivity'? – pigworker

Trả lời

8

Vấn đề là mẫu ký tự đại diện của mẫu của bạn sẽ mất thông tin bình đẳng. Nếu bạn mã hóa cảm ứng theo cách này, bạn không thể viết một bộ sưu tập mẫu (hữu hạn) bao gồm tất cả các trường hợp. Giải pháp là di chuyển cảm ứng ra khỏi kiểu dữ liệu của bạn thành một giá trị xác định. Những thay đổi có liên quan như thế này:

data Equal a b where 
    Reflexivity :: Equal a a 

induction :: Equal a b -> Equal (f a) (f b) 
induction Reflexivity = Reflexivity 

matchTypes (List a) (List b) = induction <$> matchTypes a b 
matchTypes (Maybe a) (Maybe b) = induction <$> matchTypes a b 

fromDynamic' :: TypeRep a -> Dynamic -> Maybe a 
fromDynamic' target (Dyn source value) = 
    case matchTypes source target of 
     Just Reflexivity -> Just value 
     Nothing -> Nothing 

Bằng cách này, các mẫu trong fromDynamic' đầy đủ mọi khía, nhưng không có bất kỳ ký tự đại diện thông tin thua lỗ.

+0

Vâng, tôi đã nghi ngờ về các ký tự đại diện. Tại một thời điểm tôi đã cố gắng giải quyết vấn đề bằng cách viết một hàm 'normalizeEqual :: Equal ab -> Equal aa' để biến tất cả các trường hợp' Induction' thành 'Reflexivity', nhưng điều đó cũng không thành công vì lý do tôi không thể nhớ lại. .. –

+2

Bạn thực sự có thể chuẩn hóa dữ liệu từ loại dữ liệu này 'dữ liệu EqI :: * -> * -> * trong đó ReflI :: EqI aa; RespI :: EqI ab -> EqI (fa) (fb) 'vào dữ liệu trong kiểu dữ liệu này' dữ liệu EqR :: * -> * -> * trong đó Refl :: EqR aa' như sau: 'fact :: EqI ab -> EqR ab; thực tế ReflI = Refl; thực tế (RespI p) = trường hợp thực tế p của Refl -> Refl' – pigworker

+0

@sacundim Tôi đoán bạn có thể có thể làm cho 'normalizeEqual :: Equal a b -> Equal a b' làm việc, nhưng loại bạn đề nghị có vẻ lạ với tôi. Bạn luôn có thể xây dựng một giá trị kiểu 'Equal a a' - cung cấp một bằng chứng rằng' a' bằng với cái gì đó khác có vẻ không cần thiết. –

Các vấn đề liên quan