我正在建模一个系统,该系统具有创建资源的操作以及使用该资源的其他操作.但是,给定的资源只能被使用一次 - 有没有一种方法可以保证在编译时?
具体来说,让我们说第一次操作烤蛋糕,还有另外两种操作,一种用于"选择吃"蛋糕,一种用于"选择吃蛋糕",我只能做一种或另一种.
-- This is my current "weakly typed" interface: bake :: IO Cake eat :: Cake -> IO () keep :: Cake -> IO () -- This is OK do brownie <- bake muffin <- bake eat brownie keep muffin -- Eating and having the same cake is not OK: do brownie <- bake eat brownie keep brownie -- oops! already eaten!
通过在我们使用之后在蛋糕上设置标记,很容易强制执行限制,即不在运行时保留已经吃过的蛋糕(反之亦然).但有没有办法在编译时强制执行此操作?
顺便说一句,这个问题是为了概念证明,所以我可以使用任何可以给我静电安全的黑魔法.
在Haskell中,这个的基本版本可以用由蛋糕存储索引的GADT表示(由Nat
-s 列表表示):
{-# LANGUAGE TypeFamilies, GADTs, TypeOperators, PartialTypeSignatures, DataKinds, PolyKinds #-} import GHC.TypeLits import Data.Proxy import GHC.Exts -- Allocate a new cake type family New cs where New '[] = 0 New (c ': cs) = c + 1 -- Constraint satisfiable if "c" is in "cs" type family Elem c cs :: Constraint where Elem c (c ': cs) = () Elem c (c' ': cs) = Elem c cs type family Remove c cs where Remove c '[] = '[] Remove c (c ': cs) = cs Remove c (c' ': cs) = c' ': Remove c cs data Bake :: [Nat] -> [Nat] -> * -> * where Pure :: a -> Bake cs cs a Bake :: (Proxy (New cs) -> Bake (New cs ': cs) cs' a) -> Bake cs cs' a Eat :: Elem c cs => Proxy c -> Bake (Remove c cs) cs' a -> Bake cs cs' a Keep :: Elem c cs => Proxy c -> Bake cs cs' a -> Bake cs cs' a ok :: Bake '[] _ _ ok = Bake $ \cake1 -> Bake $ \cake2 -> Eat cake1 $ Keep cake2 $ Eat cake2 $ Pure () not_ok :: Bake '[] _ _ not_ok = Bake $ \cake1 -> Bake $ \cake2 -> Eat cake1 $ Keep cake1 $ -- we already ate that Eat cake2 $ Pure ()
遗憾的是,我们无法从Bake
操作中删除类型注释并保留要推断的类型:
foo = Bake $ \cake1 -> Bake $ \cake2 -> Eat cake1 $ Pure () -- Error: Could not deduce (Elem (New cs0) (New cs0 + 1 : New cs0 : cs0))
显然,(Elem (New cs0) (New cs0 + 1 : New cs0 : cs0))
对所有人来说都是可以满足的cs0
,但GHC无法看到这一点,因为它不能决定是否New cs0
不等New cs0 + 1
,因为GHC不能假设任何关于灵活cs0
变量的东西.
如果我们添加NoMonomorphismRestriction
,foo
将进行类型检查,但这会使得所有Elem
约束都被推到顶部甚至是错误的程序.这仍然会阻止对不正确的术语做任何有用的事情,但这是一个相当丑陋的解决方案.
更一般地说,我们可以表达Bake
一个索引的自由monad,它可以得到我们的do
注释RebindableSyntax
,并且允许对它的定义BakeF
比我们之前看到的更清晰.它也可以像普通的Free
monad 一样减少样板,尽管我发现在实际代码中人们不太可能在两个不同的场合找到索引的免费monad.
{-# LANGUAGE TypeFamilies, GADTs, TypeOperators, PartialTypeSignatures, StandaloneDeriving, DataKinds, PolyKinds, NoImplicitPrelude, RebindableSyntax, DeriveFunctor #-} import Prelude hiding (Monad(..)) import GHC.TypeLits import Data.Proxy import GHC.Exts class IxFunctor f where imap :: (a -> b) -> f i j a -> f i j b class IxFunctor m => IxMonad m where return :: a -> m i i a (>>=) :: m i j a -> (a -> m j k b) -> m i k b fail :: String -> m i j a infixl 1 >> infixl 1 >>= (>>) :: IxMonad m => m i j a -> m j k b -> m i k b ma >> mb = ma >>= const mb data IxFree f i j a where Pure :: a -> IxFree f i i a Free :: f i j (IxFree f j k a) -> IxFree f i k a liftf :: IxFunctor f => f i j a -> IxFree f i j a liftf = Free . imap Pure instance IxFunctor f => IxFunctor (IxFree f) where imap f (Pure a) = Pure (f a) imap f (Free fa) = Free (imap (imap f) fa) instance IxFunctor f => IxMonad (IxFree f) where return = Pure Pure a >>= f = f a Free fa >>= f = Free (imap (>>= f) fa) fail = error -- Old stuff for Bake type family New cs where New '[] = 0 New (c ': cs) = c + 1 type family Elem c cs :: Constraint where Elem c (c ': cs) = () Elem c (c' ': cs) = Elem c cs type family Remove c cs where Remove c '[] = '[] Remove c (c ': cs) = cs Remove c (c' ': cs) = c' ': Remove c cs -- Now the return type indices of BakeF directly express the change -- from the old store to the new store. data BakeF cs cs' k where BakeF :: (Proxy (New cs) -> k) -> BakeF cs (New cs ': cs) k EatF :: Elem c cs => Proxy c -> k -> BakeF cs (Remove c cs) k KeepF :: Elem c cs => Proxy c -> k -> BakeF cs cs k deriving instance Functor (BakeF cs cs') instance IxFunctor BakeF where imap = fmap type Bake = IxFree BakeF bake = liftf (BakeF id) eat c = liftf (EatF c ()) keep c = liftf (KeepF c ()) ok :: Bake '[] _ _ ok = do cake1 <- bake cake2 <- bake eat cake1 keep cake2 eat cake2 -- not_ok :: Bake '[] _ _ -- not_ok = do -- cake1 <- bake -- cake2 <- bake -- eat cake1 -- keep cake1 -- already ate it -- eat cake2
Polakow在他的Haskell Symposium论文中展示了在Haskell(pdf)中嵌入完整的线性lambda演算如何做到这一点.
主要思想是使用输入和输出上下文为每个构造函数编制索引,以跟踪各个子项中消耗的资源.