转换参数化类型(带推断参数)

发布于 2024-11-04 21:10:00 字数 3277 浏览 0 评论 0原文

我有一个数据类型,它带有“隐藏”(推断)类型和具体值。现在我尝试实现一个可以改变这两者的函数,但无法使其通过 GHC。

我的示例代码是这样的:

data T tag val = T val

data A = A
data B = B

mkIntVal :: T a b -> T Int b
mkIntVal (T x) = T x

mkCharVal :: T a b -> T Char b
mkCharVal (T x) = T x

convert :: T Int a -> T Char b
convert (T A) = mkCharVal $ T B
convert (T B) = mkCharVal $ T A

它产生的错误是这样的:

test.hs:13:12:
    Couldn't match type `A' with `B'
    In the pattern: A
    In the pattern: T A
    In an equation for `convert': convert (T A) = mkCharVal $ T B

test.hs:13:17:
    Couldn't match type `B' with `A'
    Expected type: T Char b
      Actual type: T Char B
    In the expression: mkCharVal $ T B
    In an equation for `convert': convert (T A) = mkCharVal $ T B

必须做什么才能使其工作?我必须更改数据结构吗?


编辑

我正在尝试扩展 Don Stewart 的解决方案以处理多态数据类型。我一直在研究实例定义,但最有希望的外观是这样的:

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}

data C a = C a deriving Show

class Convertable inVal outVal outTag | outVal -> outTag where
    convert :: T Int inVal -> T outTag outVal

instance Convertable A B Char where
    convert (T A) = mkCharVal $ T B

instance Convertable B A Char where
    convert (T B) = mkCharVal $ T A

instance Convertable a b Char => Convertable (C a) (C (T Char b)) Char where
    convert (T (C val)) = mkCharVal $ T (C (convert val)) -- line 29

但这给了我另一个错误消息:

test.hs:29:57:
    Could not deduce (a ~ T Int inVal0)
    from the context (Convertable a b Char)
      bound by the instance declaration at test.hs:28:10-70
      `a' is a rigid type variable bound by
          the instance declaration at test.hs:28:22
    In the first argument of `convert', namely `val'
    In the first argument of `C', namely `(convert val)'
    In the first argument of `T', namely `(C (convert val))'

正如唐所说,这应该是可能的,我对如何实现它感兴趣。


解决方案

经过多次“尝试”,我终于想出了一些可行的方法。这对你来说看起来不错吗?

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE OverlappingInstances #-}


data T tag val = T val deriving Show

data A = A deriving Show
data B = B deriving Show
data C a = C a deriving Show


class Convertable inTag inVal outTag outVal | inTag -> outTag, inVal -> outVal
where
    convert :: T inTag inVal -> T outTag outVal

instance Convertable Int A Char B where
    convert (T A) = T B

instance Convertable Int B Char A where
    convert (T B) = T A

instance (Convertable Int (T Int a) Char (T Char b), Convertable Int a Char b)
    => Convertable Int (C (T Int a)) Char (C (T Char b)) where
    convert (T (C x)) = T (C (convert x))

instance Convertable Int (C (T Int A)) Char (C (T Char B)) where
    convert (T (C x)) = T (C (convert x))

instance Convertable Int (C (T Int B)) Char (C (T Char A)) where
    convert (T (C x)) = T (C (convert x))

用法:

*Main> convert $ mkIntVal $ T $ C $ mkIntVal $ T A
T (C (T B))
*Main> :t it
it :: T Char (C (T Char B))

I have a data type which carries a 'hidden' (inferred) type and a concrete value. Now I try to implement a function which changes both of these but am unable to make it pass GHC.

My sample code is this:

data T tag val = T val

data A = A
data B = B

mkIntVal :: T a b -> T Int b
mkIntVal (T x) = T x

mkCharVal :: T a b -> T Char b
mkCharVal (T x) = T x

convert :: T Int a -> T Char b
convert (T A) = mkCharVal $ T B
convert (T B) = mkCharVal $ T A

The error it produces is this:

test.hs:13:12:
    Couldn't match type `A' with `B'
    In the pattern: A
    In the pattern: T A
    In an equation for `convert': convert (T A) = mkCharVal $ T B

test.hs:13:17:
    Couldn't match type `B' with `A'
    Expected type: T Char b
      Actual type: T Char B
    In the expression: mkCharVal $ T B
    In an equation for `convert': convert (T A) = mkCharVal $ T B

What has to be done to make this work? Do I have to change the data structure?


EDIT

I am trying to extend Don Stewart's solution to work with polymorphic data types. I have been playing around with the instance definition but the most promising looking a came up with is this:

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}

data C a = C a deriving Show

class Convertable inVal outVal outTag | outVal -> outTag where
    convert :: T Int inVal -> T outTag outVal

instance Convertable A B Char where
    convert (T A) = mkCharVal $ T B

instance Convertable B A Char where
    convert (T B) = mkCharVal $ T A

instance Convertable a b Char => Convertable (C a) (C (T Char b)) Char where
    convert (T (C val)) = mkCharVal $ T (C (convert val)) -- line 29

But That gives me just another error message:

test.hs:29:57:
    Could not deduce (a ~ T Int inVal0)
    from the context (Convertable a b Char)
      bound by the instance declaration at test.hs:28:10-70
      `a' is a rigid type variable bound by
          the instance declaration at test.hs:28:22
    In the first argument of `convert', namely `val'
    In the first argument of `C', namely `(convert val)'
    In the first argument of `T', namely `(C (convert val))'

As Don says it should be possible I'm interested in how that would be implemented.


Solution

After a lot more 'playing' I finally came up with something that works. Does this look good to you?

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE OverlappingInstances #-}


data T tag val = T val deriving Show

data A = A deriving Show
data B = B deriving Show
data C a = C a deriving Show


class Convertable inTag inVal outTag outVal | inTag -> outTag, inVal -> outVal
where
    convert :: T inTag inVal -> T outTag outVal

instance Convertable Int A Char B where
    convert (T A) = T B

instance Convertable Int B Char A where
    convert (T B) = T A

instance (Convertable Int (T Int a) Char (T Char b), Convertable Int a Char b)
    => Convertable Int (C (T Int a)) Char (C (T Char b)) where
    convert (T (C x)) = T (C (convert x))

instance Convertable Int (C (T Int A)) Char (C (T Char B)) where
    convert (T (C x)) = T (C (convert x))

instance Convertable Int (C (T Int B)) Char (C (T Char A)) where
    convert (T (C x)) = T (C (convert x))

Usage:

*Main> convert $ mkIntVal $ T $ C $ mkIntVal $ T A
T (C (T B))
*Main> :t it
it :: T Char (C (T Char B))

如果你对这篇内容有疑问,欢迎到本站社区发帖提问 参与讨论,获取更多帮助,或者扫码二维码加入 Web 技术交流群。

扫码二维码加入Web技术交流群

发布评论

需要 登录 才能够评论, 你可以免费 注册 一个本站的账号。

评论(1

难如初 2024-11-11 21:10:00

convert 函数的每种情况都有不同的、冲突的类型:

convertA :: T t A -> T Char B
convertA (T A) = mkCharVal $ T B

convertB :: T t B -> T Char A
convertB (T B) = mkCharVal $ T A

则可以通过类型类统一这些类型

{-# LANGUAGE MultiParamTypeClasses  #-}
{-# LANGUAGE FunctionalDependencies #-}


class C a b c | b -> c where
    convert :: T t a -> T c b

instance C A B Char where
    convert (T A) = mkCharVal (T B)

instance C B A Char where
    convert (T B) = mkCharVal (T A)

如果您确实希望单个函数在不同类型下以不同方向进行转换, 。请注意,它如何获取任何带有标签的 T,丢弃它,并用由值类型确定的新标签替换标签和值。

Each case of your convert function has a different, conflicting type:

convertA :: T t A -> T Char B
convertA (T A) = mkCharVal $ T B

convertB :: T t B -> T Char A
convertB (T B) = mkCharVal $ T A

You can unify these via a typeclass,

{-# LANGUAGE MultiParamTypeClasses  #-}
{-# LANGUAGE FunctionalDependencies #-}


class C a b c | b -> c where
    convert :: T t a -> T c b

instance C A B Char where
    convert (T A) = mkCharVal (T B)

instance C B A Char where
    convert (T B) = mkCharVal (T A)

if you truly wish a single function that at different types, converts in different directions. Note how this takes any T with a tag, discards it, and replaces the tag and value with a new tag determined by the value type.

~没有更多了~
我们使用 Cookies 和其他技术来定制您的体验包括您的登录状态等。通过阅读我们的 隐私政策 了解更多相关信息。 单击 接受 或继续使用网站,即表示您同意使用 Cookies 和您的相关数据。
原文