首页 > 解决方案 > 组合类型类的函数时如何添加中间值的类型注解?

问题描述

背景:我正在开发一个声明式编译器。在本课程中,我将编写一个类来构造一个中间数据结构。构建数据结构后,可以从数据结构中重新呈现输出。为了简化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)?)

...

标签: haskell

解决方案


明显的问题是,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]

推荐阅读