作为练习,我试图在 Haskell 中重新创建 Lisp 的 apply。我不打算将它用于任何实际目的,我只是认为这是一个很好的机会来熟悉 Haskell 的类型系统和一般的类型系统。 (所以我也不是在寻找其他人的实现。)

我的想法如下:我可以使用 GADT 来“标记”一个列表,其中包含它可以应用的函数类型。因此,我以类似的方式重新定义 NilCons,我们将使用 Nat 定义对类型中的列表长度进行编码,但不是使用 Peano 数字,而是使用标记函数类型中的编码方式(即长度对应于数字)函数的参数)。

这是我到目前为止的代码:

{-# LANGUAGE GADTs #-}

-- n represents structure of the function I apply to
-- o represents output type of the function
-- a represents argument type of the function (all arguments same type)
data FList n o a where
  -- with Nil the function is the output
  Nil :: FList o o a
  -- with Cons the corresponding function takes one more argument
  Cons :: a -> FList f o a -> FList (a -> f) o a

args0 = Nil :: FList Int Int Int -- will not apply an argument
args1 = Cons 1 args0 -- :: FList (Int -> Int) Int Int
args2 = Cons 2 args1 -- :: FList (Int -> Int -> Int) Int Int
args3 = Cons 3 args2 -- :: FList (Int -> Int -> Int -> Int) Int Int

listApply :: (n -> o) -> FList (n -> o) o a -> o
-- I match on (Cons p Nil) because I always want fun to be a function (n -> o)
listApply fun (Cons p Nil) = fun p
listApply fun (Cons p l) = listApply (fun p) l

main = print $ listApply (+) args2

在最后一行中,我的想法是 (+) 将是 Int -> Int -> Int 类型,其中 Int -> Int 对应于 n 中的 (n -> o),而 o 对应于最后一个 Int(输出)[1]。据我所知,这种类型似乎适用于我的 argsN 定义的类型。

但是,我收到两个错误,其中我将说明似乎与我相关的组件:
test.hs:19:43:
    Could not deduce (f ~ (n0 -> f))
    from the context ((n -> o) ~ (a -> f))
      bound by a pattern with constructor
                 Cons :: forall o a f. a -> FList f o a -> FList (a -> f) o a,
               in an equation for ‘listApply’


test.hs:21:34:
    Couldn't match type ‘Int’ with ‘Int -> Int’
    Expected type: FList (Int -> Int -> Int) (Int -> Int) Int
      Actual type: FList (Int -> Int -> Int) Int Int
    In the second argument of ‘listApply’, namely ‘args2’

我不确定如何解释第一个错误。第二个错误让我感到困惑,因为它与我之前用 [1] 标记的解释不符。

对出了什么问题的任何见解?

P.S:如果这会使这项工作有效,我非常愿意了解新的扩展。

最佳答案

你几乎猜对了。递归应该遵循GADT的结构:

{-# LANGUAGE GADTs #-}
-- n represents structure of the function I apply to
-- o represents output type of the function
-- a represents argument type of the function (all arguments same type)
data FList n o a where
  -- with Nil the function is the output
  Nil :: FList o o a
  -- with Cons the corresponding function takes one more argument
  Cons :: a -> FList f o a -> FList (a -> f) o a

args0 = Nil :: FList Int Int Int -- will not apply an argument
args1 = Cons 1 args0 -- :: FList (Int -> Int) Int Int
args2 = Cons 2 args1 -- :: FList (Int -> Int -> Int) Int Int
args3 = Cons 3 args2 -- :: FList (Int -> Int -> Int -> Int) Int Int

-- n, not (n -> o)
listApply :: n -> FList n o a -> o
listApply fun Nil = fun
listApply fun (Cons p l) = listApply (fun p) l

main = print $ listApply (+) args2

three :: Int
three = listApply (+) (Cons 2 (Cons 1  Nil))

oof :: String
oof = listApply reverse (Cons "foo" Nil)

true :: Bool
true = listApply True Nil -- True

-- The return type can be different than the arguments:

showplus :: Int -> Int -> String
showplus x y = show (x + y)

zero :: String
zero = listApply showplus (Cons 2 (Cons 1 Nil))

必须说,这看起来很优雅!

甚至 OP 也不要求其他人实现。您可以以不同的方式处理问题,从而产生外观不同但简洁的API:
{-# LANGUAGE KindSignatures #-}
{-# LANGuAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE AllowAmbiguousTypes #-}

import Data.Proxy

data N = O | S N

p0 :: Proxy O
p1 :: Proxy (S O)
p2 :: Proxy (S (S O))
p0 = Proxy
p1 = Proxy
p2 = Proxy

type family ArityNFun (n :: N) (a :: *) (b :: *) where
  ArityNFun O a b = b
  ArityNFun (S n) a b = a -> ArityNFun n a b

listApply :: Proxy n -> ArityNFun n a b -> ArityNFun n a b
listApply _ = id

three :: Int
three = listApply p2 (+) 2 1

oof :: String
oof = listApply p1 reverse "foo"

true :: Bool
true = listApply p0 True

showplus :: Int -> Int -> String
showplus x y = show (x + y)

zero :: String
zero = listApply p2 showplus 0 0

这里我们可以使用 Nat 中的 GHC.TypeLits ,但是我们需要 UndecidableInstances 。在这个例子中,添加的糖不值得麻烦。

如果你想制作多态版本,那也是可能的,但是 index 不是 (n :: Nat) (a :: *) 而是 (as :: [*]) 。对于两种编码,制作 plusN 也可能是一个很好的练习。

关于haskell - 使用 GADT 在 Haskell 中重新创建 Lisp 的 `apply`,我们在Stack Overflow上找到一个类似的问题:https://stackoverflow.com/questions/32628236/

10-11 22:34
查看更多