2012-06-11 4 views
6

더 진보 된 Haskell/GHC 기능 및 개념을 이해할 수 있도록 GADT 기반 구현을 수행하기로 결정했습니다. 동적으로 형식이 지정된 데이터를 확장하고 매개 변수 유형을 포함하도록 확장합니다. (내 줄 번호가 예까지 일치하지 않는)이의GADT 기반 장난감을 사용할 수 없습니다. 파라 메트릭 유형으로 작동하는 동적 유형

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

컴파일 (. 나는이 예제의 길이에 대해 사과) 그러나, 마지막 줄에 실패

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

내가 읽는 방식으로, 컴파일러는 Inductive :: Equal a b -> Equal (f a) (f b)에서 ab이 비 - 하단 값에 대해 같아야한다는 것을 알 수 없습니다. 그래서 Inductive :: Equal a a -> Equal (f a) (f 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)' 

가 (단지 명제로 읽기) 작동하지 않습니다 matchTypes :: TypeRep a -> TypeRep b -> Maybe (Equal a a)을 생산하는 matchTypes :: TypeRep a -> TypeRep b -> Maybe (Equal a b)의 유형을 변경. matchTypes :: TypeRep a -> TypeRep a -> Maybe (Equal a a)도 없다. (또 다른 간단한 명제가 아니고, 나는 사용자가 fromDynamic' to know thein the TypeRep contained in the Dynamic을 요구할 것이라고 이해한다.).

그래서 나는 혼란 스럽습니다. 여기로 나아갈 수있는 방법에 대한 조언이 있습니까?

+2

'유도'생성자를 삭제할 수 없으며 동일한 원리를 유도 할 수 없습니까? 유도 : : 등식 : 등식 (f a) (f b); 유도 성 반사율 = 반사율'? – pigworker

답변

8

패턴의 와일드 카드 패턴이 평등 정보를 잃어 버리는 것이 문제입니다. 이러한 방식으로 유도를 인코딩하면 모든 경우를 다루는 (유한) 패턴 모음을 작성할 수 없습니다. 해결 방법은 데이터 유형에서 정의 된 값으로 유도를 이동하는 것입니다. fromDynamic'에서

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 

이 방법 패턴이 철저하지만, 어떤 정보 손실 와일드 카드가없는 : 관련 변화는 다음과 같습니다.

+0

네, 와일드 카드를 의심했습니다. 어떤 시점에서 모든 유도 사례를'반사성 '으로 바꾸는'normalizeEqual :: Equal ab-> Equal aa' 함수를 작성하여이 문제를 해결하려했지만 기억하지 못하는 이유로 실패했습니다. .. –

+2

이 형식의 데이터를 실제로 정규화 할 수 있습니다.'data EqI :: * * *> * 여기서 ReflI :: EqI aa; 이 타입의 데이터에 대한 EqR :: * -> * * 여기서 Refl :: EqR aa'는'fact :: EqI ab -> EqR ab; 사실 ReflI = Refl; 사실 (RespI p) = Refl의 케이스 팩트 -> Refl' – pigworker

+0

@sacundim 나는 당신이 아마 normalizeEqual :: Equal a b -> Equal a b' 작업을 할 수있을 것이라고 생각하지만, 제안한 타입이 이상하게 보입니다. 'Equal a a' 타입의 값을 만들 수 있습니다 -'a'가 다른 것과 동일하다는 증거를 제공하면 불필요 해 보입니다. –

관련 문제