为了在简单的产品上一般地推导出FromRow
-kind- class的实例,我想静态地分析一个类型,而不实际提供任何具体的术语。
的例子:
class FromRow a where
rowrep :: Proxy a -> [Maybe NativeType]
fromRow :: Statement -> IO a
data User = User
{ name :: String
, uid :: Int
, active :: Bool
} deriving (Show, Generic)
"trick"在获取任何数据之前,我需要rowrep -可能会覆盖某些甚至所有列的默认值。在我想用rowrep的时候,我还没有项,所以是Proxy
。编写FromRow
的实例可能会变得非常繁琐和容易出错,所以我认为我应该为Generic
类型添加default
实现。然而,它似乎得到了通用的表示,我需要提供一个给定类型(from :: a -> Rep a
)的术语,类型本身的知识是不够的。
实际上,我们可以看到这不仅仅是API的一个噱头,泛型表示确实保存值:
> from (User "foo" 1 True)
M1 {unM1 = M1 {unM1 = M1 {unM1 = K1 {unK1 = "foo"}} :*: (M1 {unM1 = K1 {unK1 = 1}} :*: M1 {unM1 = K1 {unK1 = True}})}}
有没有一种方法可以使用Generic
来分析事物的结构和类型,即我们不关心实际值的地方?如果做不到这一点,TH会覆盖这个用例吗?
您不需要提供术语。您不需要Rep a
的值,您只需要将其检查为类型,这可以在不使用from
的情况下完成。
对于这个问题,你也不需要Proxy
,那总是一个丑陋的hack来弥补Haskell在TypeApplications
出现之前的缺陷。
{-# LANGUAGE TypeFamilies, TypeApplications, AllowAmbiguousTypes
, ScopedTypeVariables, UnicodeSyntax, DefaultSignatures #-}
import Data.Kind (Type)
data NativeType = Intish | Floatish
class FromRow a where
rowrep :: [Maybe NativeType]
instance FromRow Int where
rowrep = [Just Intish]
现在,为了编写泛型实例,我们首先需要一个助手类来完成Rep
的类型级检查:
class GFromRow (g :: k -> Type) where
gRowrep :: [Maybe NativeType]
instance ∀ i c f . GFromRow f => GFromRow (M1 i c f) where
gRowRep = gRowRep @f
instance ∀ i c . FromRow c => GFromRow (K1 i c) where
gRowRep = rowRep @c
... -- instances for U1 and f:*:g
那么默认实现将是
class FromRow a where
rowrep :: [Maybe NativeType]
default rowrep :: GFromRow (Rep a) => [Maybe NativeType]
rowrep = gRowrep @(Rep a)