我怎样才能以编程方式从另一个产生这种数据类型? [英] How can I programatically produce this datatype from the other?

查看:96
本文介绍了我怎样才能以编程方式从另一个产生这种数据类型?的处理方法,对大家解决问题具有一定的参考价值,需要的朋友们下面随着小编来一起学习吧!

问题描述

我想使用 DSum 。要使用 DSum ,您需要有一个带有一个类型参数的'tag'类型,例如

I'd like to use DSum for something. To work with DSum, you need to have a 'tag' type which takes one type argument, e.g.

data Tag a where
  AFirst :: Tag Int
  ASecond :: Tag String

然而,我想在图书馆内部使用它。我想让我向用户公开的接口采用任何旧的数据类型,例如。/ b>

However, I'd like to use this internally in a library. I want the interface that I expose to users to take any old datatype, e.g.

data SomeUserType1 = Foo Int | Bar String

显然,从这个结果到 / code>上面给出的类型。那么,是否有可能通过某种泛型编程技术在代码中实现这一点?

it's clearly quite mechanical to go from this to the Tag a type given above. So, is it possible to do this in code, with some sort of generic programming techniques?

下面是另一个要清楚我想要生成的映射类型的示例。

Here's another example to be clear about the type of mapping I want to produce.

data SomeUserType2 = Foo Int | Bar Char | Baz Bool String

应该成为

should become

data Tag2 a where
  AFirst :: Tag2 Int
  ASecond :: Tag2 Char
  AThird :: Tag2 (Bool, String)

这是模板Haskell的工作吗?还有别的吗?我甚至都不知道这里有什么选项。

Is this a job for Template Haskell? Something else? I don't even really know what the options are here.

推荐答案

{-# LANGUAGE TemplateHaskell #-}

module Tag where

import Language.Haskell.TH

makeTag :: Name -> DecsQ
makeTag name = do
    -- Reify the data declaration to get the constructors.
    -- Note we are forcing there to be no type variables...
    (TyConI (DataD _ _ [] _ cons _)) <- reify name

    pure [ DataD [] tagTyName [PlainTV (mkName "a")] Nothing (fmap tagCon cons) [] ]
  where
  -- Generate the name for the new tag GADT type constructor.
  tagTyName :: Name
  tagTyName = mkName ("Tag" ++ nameBase name)

  -- Given a constructor, construct the corresponding constructor for the GADT.
  tagCon :: Con -> Con
  tagCon (NormalC conName args) =
    let tys = fmap snd args
        tagType = foldl AppT (TupleT (length tys)) tys
    in GadtC [mkName ("Tag" ++ nameBase conName)] []
             (AppT (ConT tagTyName) tagType)

然后您可以在另一个文件中测试它:

Then you can test it out in another file:

{-# LANGUAGE TemplateHaskell, GADTs #-}

import Tag

data SomeUserType1 = Foo Int | Bar String
data SomeUserType2 = Fooo Int | Baar Char | Baaz Bool String

makeTag ''SomeUserType1
makeTag ''SomeUserType2

如果您检查GHCi中的第二个文件(或者通过将 -ddump-splices 传递给 ghci ghc ),您会看到会生成以下内容:

If you inspect the second file in GHCi (or look at the generated code by passing -ddump-splices to either ghci or ghc) you'll see that the following is generated:

data TagSomeUserType1 a where
  TagFoo :: TagSomeUserType1 Int
  TagBar :: TagSomeUserType1 String

data TagSomeUserType3 a where
  TagFooo :: TagSomeUserType2 Int
  TagBaar :: TagSomeUserType2 Char
  TagBaaz :: TagSomeUserType2 (Bool, String)

我必须使用 mkName 不是 newName 因为如果您预计会使用这些生成的GADT,你需要他们有可预测的名字,你可以写。从示例中应该清楚,我的约定是在类型和数据构造函数中加入 Tag

I have to use mkName and not newName because, if you are ever expected to use these generated GADTs, you'll need them to have predictable names you can write. As should be clear from the examples, my convention is to prepend Tag to both the type and data constructors.

这篇关于我怎样才能以编程方式从另一个产生这种数据类型?的文章就介绍到这了,希望我们推荐的答案对大家有所帮助,也希望大家多多支持IT屋!

查看全文
相关文章
登录 关闭
扫码关注1秒登录
发送“验证码”获取 | 15天全站免登陆