检查字段类型是类型级计算结果的记录

huangapple go评论53阅读模式
英文:

Inspecting records whose fields' types are the result of type-level computations

问题

在[servant](https://hackage.haskell.org/package/servant-server)库的背景下提出了这个问题,但在[其他上下文](https://gitlab.haskell.org/ghc/ghc/-/wikis/implementing-trees-that-grow/trees-that-grow-guidance)中也出现了这个问题。

[Servant][1]允许您使用记录定义[命名路由][2],就像这样:

```haskell
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE TypeOperators #-}
import GHC.Generics
import Servant

type API = NamedRoutes Counter

data Counter mode = Counter
  { counterPost :: mode :- Capture "stuff" Int :> PostNoContent,
    counterGet :: mode :- Get '[JSON] Int
  }
  deriving stock (Generic)

类型Server API将执行一些类型级计算,该计算评估为类型

ghci> :kind! Server API
Server API :: *
= Counter (AsServerT Handler)

我希望有一种方法可以“窥视”记录类型并检查每个字段的最终类型,这里将是评估 AsServerT Handler :- Capture "stuff" Int :> PostNoContentAsServerT Handler :- Get '[JSON] Int 的结果。

但是分别指定这两个表达式很不方便。我想将类型 Server API 传递给...某物,并得到所有字段评估后的类型。是否存在这样的功能?


<details>
<summary>英文:</summary>

This came up in the context of the [servant](https://hackage.haskell.org/package/servant-server) library, but the issue reappears in [other contexts](https://gitlab.haskell.org/ghc/ghc/-/wikis/implementing-trees-that-grow/trees-that-grow-guidance).

[Servant][1] allows you to define [named routes][2] using a record, like this:

```haskell
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE TypeOperators #-}
import GHC.Generics
import Servant

type API = NamedRoutes Counter

data Counter mode = Counter
  { counterPost :: mode :- Capture &quot;stuff&quot; Int :&gt; PostNoContent,
    counterGet :: mode :- Get &#39;[JSON] Int
  }
  deriving stock (Generic)

The type Server API will perform some type-level computation, which evaluates to the type

ghci&gt; :kind! Server API
Server API :: *
= Counter (AsServerT Handler)

I would like a way to "peek into" the record type and inspect the final types of each field, which here would be the result of evaluating AsServerT Handler :- Capture &quot;stuff&quot; Int :&gt; PostNoContent and AsServerT Handler :- Get &#39;[JSON] Int.

But specifying those two expressions separatedly is inconvenient. I would like to pass the type Server API to... something, and get the evaluated type of all fields in return. Does such functionality exist?

答案1

得分: 4

It seems that one way of getting the fields' types is through the generic representation:

ghci> :kind! Rep (Server API)
Rep (Server API) :: * -> *
= M1
    D
    ('MetaData "Counter" "Main" "main" 'False)
    (M1
       C
       ('MetaCons "Counter" 'PrefixI 'True)
       (M1
          S
          ('MetaSel
             ('Just "counterPost")
             'NoSourceUnpackedness
             'NoSourceStrictness
             'DecidedLazy)
          (K1 R (Int -> Handler NoContent))
        :*: M1
              S
              ('MetaSel
                 ('Just "counterGet")
                 'NoSourceUnpackedness
                 'NoSourceStrictness
                 'DecidedLazy)
              (K1 R (Handler Int))))

For less verbosity, a Generics-based helper could produce a more manageable output. Using my by-other-names package, we can define:

recordFields ::
  forall r.
  (Generic r, GHasFieldNames (Rep r), GRecord Typeable (Rep r)) =>
  [(String, TypeRep)]
recordFields =
  Data.Foldable.toList $
    gRecordEnum @Typeable @(Rep r) gGetFieldNames typeRep

Which, put to use:

检查字段类型是类型级计算结果的记录

英文:

It seems that one way of getting the fields' types is through the generic representation:

ghci&gt; :kind! Rep (Server API)
Rep (Server API) :: * -&gt; *
= M1
    D
    (&#39;MetaData &quot;Counter&quot; &quot;Main&quot; &quot;main&quot; &#39;False)
    (M1
       C
       (&#39;MetaCons &quot;Counter&quot; &#39;PrefixI &#39;True)
       (M1
          S
          (&#39;MetaSel
             (&#39;Just &quot;counterPost&quot;)
             &#39;NoSourceUnpackedness
             &#39;NoSourceStrictness
             &#39;DecidedLazy)
          (K1 R (Int -&gt; Handler NoContent))
        :*: M1
              S
              (&#39;MetaSel
                 (&#39;Just &quot;counterGet&quot;)
                 &#39;NoSourceUnpackedness
                 &#39;NoSourceStrictness
                 &#39;DecidedLazy)
              (K1 R (Handler Int))))

Kind of verbose, but it works and plays well with the "Eval" code lens in VSCode:

检查字段类型是类型级计算结果的记录

For less verbosity, a Generics-based helper could produce a more manageable output. Using my by-other-names package, we can define:

recordFields ::
  forall r.
  (Generic r, GHasFieldNames (Rep r), GRecord Typeable (Rep r)) =&gt;
  [(String, TypeRep)]
recordFields =
  Data.Foldable.toList $
    gRecordEnum @Typeable @(Rep r) gGetFieldNames typeRep

Which, put to use:

检查字段类型是类型级计算结果的记录

huangapple
  • 本文由 发表于 2023年4月11日 01:56:18
  • 转载请务必保留本文链接:https://go.coder-hub.com/75979484.html
匿名

发表评论

匿名网友

:?: :razz: :sad: :evil: :!: :smile: :oops: :grin: :eek: :shock: :???: :cool: :lol: :mad: :twisted: :roll: :wink: :idea: :arrow: :neutral: :cry: :mrgreen:

确定