Dan*_*ton 9 polymorphism haskell concatenative-language higher-order-functions impredicativetypes
我最近受到了Haskell博客活动1的启发,试图在Haskell中编写类似Forth的DSL.我采取的方法既简单又令人困惑:
{-# LANGUAGE TypeOperators, RankNTypes, ImpredicativeTypes #-}
-- a :~> b represents a "stack transformation"
-- from stack type "a" to stack type "b"
-- a :> b represents a "stack" where the top element is of type "b"
-- and the "rest" of the stack has type "a"
type s :~> s' = forall r. s -> (s' -> r) -> r
data a :> b = a :> b deriving Show
infixl 4 :>
Run Code Online (Sandbox Code Playgroud)
对于做简单的事情,这非常有效:
start :: (() -> r) -> r
start f = f ()
end :: (() :> a) -> a
end (() :> a) = a
stack x f = f x
runF s = s end
_1 = liftS0 1
neg = liftS1 negate
add = liftS2 (+)
-- aka "push"
liftS0 :: a -> (s :~> (s :> a))
liftS0 a s = stack $ s :> a
liftS1 :: (a -> b) -> ((s :> a) :~> (s :> b))
liftS1 f (s :> a) = stack $ s :> f a
liftS2 :: (a -> b -> c) -> ((s :> a :> b) :~> (s :> c))
liftS2 f (s :> a :> b) = stack $ s :> f a b
Run Code Online (Sandbox Code Playgroud)
简单的函数可以简单地转换为相应的堆栈转换.到目前为止,一些游戏产生了令人愉快
ghci> runF $ start _1 _1 neg add
0
Run Code Online (Sandbox Code Playgroud)
当我尝试使用高阶函数扩展它时遇到了麻烦.
-- this requires ImpredicativeTypes...not really sure what that means
-- also this implementation seems way too simple to be correct
-- though it does typecheck. I arrived at this after pouring over types
-- and finally eta-reducing the (s' -> r) function argument out of the equation
-- call (a :> f) h = f a h
call :: (s :> (s :~> s')) :~> s'
call (a :> f) = f a
Run Code Online (Sandbox Code Playgroud)
call应该通过将转换(保持在堆栈的尖端)"应用"到它的"休息" (s :> (s :~> s'))来将形式的堆栈转换为形式s.我想它应该像这样工作:
ghci> runF $ start _1 (liftS0 neg) call
-1
Run Code Online (Sandbox Code Playgroud)
但实际上,它给了我一个巨大的类型不匹配错误.我究竟做错了什么?"堆栈转换"表示可以充分处理高阶函数,还是需要调整它?
1 N.B. 不像这些家伙那样做,而不是start push 1 push 2 add end,我希望它是runF $ start (push 1) (push 2) add,这个想法可能是以后我可以使用一些类型类魔术来push隐含某些文字.
您的:~>类型不是您真正想要的(因此是ImpredicativeTypes)。如果您只是从中删除类型注释,call那么您的最后一个示例将按预期工作。让它工作的另一种方法是使用不那么花哨但更合适的类型和额外的参数:
type Tran s s' r = s -> (s' -> r) -> r
call :: Tran (s :> (Tran s s' r)) s' r
call (a :> f) = f a
Run Code Online (Sandbox Code Playgroud)
但是,如果您追求的是一个很好的 DSL 语法并且您可以容忍,OverlappingInstances那么您甚至可以几乎摆脱 liftSx 函数:
{-# LANGUAGE TypeOperators, MultiParamTypeClasses, TypeFamilies,
FlexibleInstances, FlexibleContexts,
UndecidableInstances, IncoherentInstances #-}
data a :> b = a :> b deriving Show
infixl 4 :>
class Stackable s o r where
eval :: s -> o -> r
data End = End
instance (r1 ~ s) => Stackable s End r1 where
eval s End = s
instance (Stackable (s :> a) o r0, r ~ (o -> r0)) => Stackable s a r where
eval s a = eval (s :> a)
instance (a ~ b, Stackable s c r0, r ~ r0) => Stackable (s :> a) (b -> c) r where
eval (s :> a) f = eval s (f a)
-- Wrap in Box a function which should be just placed on stack without immediate application
data Box a = Box a
instance (Stackable (s :> a) o r0, r ~ (o -> r0)) => Stackable s (Box a) r where
eval s (Box a) = eval (s :> a)
runS :: (Stackable () a r) => a -> r
runS a = eval () a
-- tests
t1 = runS 1 negate End
t2 = runS 2 1 negate (+) End
t3 = runS 1 (Box negate) ($) End
t4 = runS [1..5] 0 (Box (+)) foldr End
t5 = runS not True (flip ($)) End
t6 = runS 1 (+) 2 (flip ($)) End
Run Code Online (Sandbox Code Playgroud)