在组合类型类的函数时,如何添加中间值的类型注释



背景:我正在开发一个声明性编译器。在本课程中,我将编写一个类来构造一个中间数据结构。在构建数据结构之后,可以从数据结构中重新呈现输出。为了简化stackoverflow,我创建了以下代码:

module Main where
import qualified Data.Word as W
import qualified Octetable as Oct
main :: IO ()
main = 
do
print (buildNRender "123")
data MyData = MyData Integer
data Construction model = Contains model | Error String
deriving Show
class Builder g where
build :: String -> (Construction g)
render :: (Construction g) -> [W.Word8]
buildNRender :: String -> [W.Word8]
buildNRender = render . build
instance Builder MyData where
build s = Contains (MyData (read s :: Integer))
render (Contains (MyData n)) = Oct.toOctets n
render (Error _) = []

显而易见的问题是,"buildNRender"不能是Builder的一部分,因为根本没有使用类型参数g。

现在,对我来说,很明显,类型类不能像这样工作,因为两个或多个函数组合中的中间值有一个类型参数。

下面的代码使中间类型显式,并且可以工作,但没有buildNRender。

...
main :: IO ()
main = 
do
print (render ((build "123") :: (Construction MyData))
...

然而,是否有一种优雅的方法可以定义类的DEFAULT方法(如"buildNRender"(,并在调用方的上下文中指定中间类型,如以下代码中所示?

...
main :: IO ()
main = 
do
print ((buildNRender "123") :: ?(Construction MyData)?)
...

显而易见的问题是,buildNRender不能是Builder的一部分,因为根本没有使用类型参数g

好吧,曾经是一个问题(具体地说,g将是不明确的(,但现在已经不是了,因为GHC现在有允许使用这些参数的扩展。

{-# LANGUAGE AllowAmbiguousTypes, TypeApplications, ScopedTypeVariables, UnicodeSyntax #-}

module Main where
import qualified Data.Word as W
import qualified Octetable as Oct
main :: IO ()
main = 
do
print (buildNRender @MyData "123")
data MyData = MyData Integer
data Construction model = Contains model | Error String
deriving Show
class Builder g where
build :: String ->(Construction g)
render :: (Construction g) ->[W.Word8]
buildNRender :: ∀ g . Builder g =>String ->[W.Word8]
-- ∀ (forall) g . introduces the type variable g into scope
-- needs extension AllowAmbiguousTypes
buildNRender = render . build @g -- @g is a Type Application
instance Builder MyData where
build s = Contains (MyData (read s :: Integer))
render (Contains (MyData n)) = Oct.toOctets n
render (Error _) = []

或者,没有UnicodeSyntax:

{-# LANGUAGE AllowAmbiguousTypes, TypeApplications, ScopedTypeVariables #-}
...
buildNRender :: forall g . Builder g => String -> [W.Word8]

AllowAmbiguousTypesTypeApplications无疑是目前的好方法。但是,如果您喜欢避免它们,可以使用两种经典技术之一:代理传递或newtype标记。

代理传递

使用ScopedTypeVariables:最简单

class Builder g where
build :: String -> Construction g
render :: Construction g -> [W.Word8]
buildNRender :: proxy g -> String -> [W.Word8]
buildNRender _ = render . (build :: String -> Construction g)

类头中的g类型变量将覆盖buildNRender默认定义的主体,并可在中使用以解决歧义。例如,

buildNRender (Proxy :: Proxy MyData) "123"

传递给buildNRender的代理参数可以是最后一个类型参数代表所需类型的任何类型。规范选择定义在Data.Proxy:中

data Proxy a = Proxy

如果你也想避免ScopedTypeVariables,那么你需要一些辅助函数。例如,您可以编写

blub :: proxy g -> (String -> Construction g) -> String -> Construction g
blub _ = id

然后

buildNRender p = render . blub p build

如果你需要很多这样的东西,你可以定义更通用的版本。例如,blub的类型可以用前缀表示法重写:

blub :: proxy g -> (->) String (Construction g) -> (->) String (Construction g)
blub _ = id

这导致了一个泛化,

blub :: proxy g -> f (c g) -> f (c g)
blub _ = id

其可以以完全相同的方式使用。

新型标记

为了避免以处理过程中的大量麻烦为代价的代理传递的任何可能的运行时影响,您可以导入Data.Tagged,它定义了

newtype Tagged s b = Tagged {unTagged :: b}
-- It has a Functor instance

现在您可以(使用ScopedTypeVariables(编写

buildNRender :: Tagged g (String -> [W.Word8])
buildNRender = Tagged (render . (build :: String -> Construction g))

如果没有ScopedTypeVariables,事情会再次变得更加棘手。一种选择是

blurble :: f (c g) -> Tagged g (f (c g))
blurble = Tagged
buildNRender :: Tagged g (String -> [W.Word8])
buildNRender = (render .) <$> blurble build

呼叫可能是:

unTagged (buildNRender :: Tg.Tagged MyData (String -> [W.Word8])) "123"

最新更新