我是否可以在此显示实例中消除对不可判定实例的使用以获得免费 monad



我一直在尝试围绕免费的monads进行思考;作为学习辅助工具,我设法为以下Free类型编写了一个Show实例:

{-# LANGUAGE FlexibleContexts, UndecidableInstances #-}
-- Free monad datatype
data Free f a = Return a | Roll (f (Free f a))
instance Functor f => Monad (Free f) where
    return = Return
    Return a >>= f = f a
    Roll ffa >>= f = Roll $ fmap (>>= f) ffa
-- Show instance for Free; requires FlexibleContexts and
-- UndecidableInstances
instance (Show (f (Free f a)), Show a) => Show (Free f a) where
    show (Return x) = "Return (" ++ show x ++ ")"
    show (Roll ffx) = "Roll (" ++ show ffx ++ ")"

-- Identity functor with Show instance
newtype Identity a = Id a deriving (Eq, Ord)
instance Show a => Show (Identity a) where
    show (Id x) = "Id (" ++ show x ++ ")"
instance Functor (Identity) where
    fmap f (Id x)= Id (f x)

-- Example computation in the Free monad
example1 :: Free Identity String
example1 = do x <- return "Hello"
              y <- return "World"
              return (x ++ " " ++ y)

使用UndecidableInstances让我有些困扰;有没有办法没有它? 谷歌得到的只是爱德华·凯米特(Edward Kmett)的这篇博文,令人欣慰的是,它与我的Show类定义基本相同。

您实际上可以在此处消除对Show的 UndecidableInstance 要求,尽管您不能对 ReadEq 执行相同的操作。

诀窍是用您可以更直接显示但不会告诉其他人的内容替换函子的内容。因此,我们将导出限制为:

{-# LANGUAGE FlexibleContexts #-}
module Free (Free(..)) where

并为我们只能show的东西敲出一种数据类型.

newtype Showable = Showable (Int -> ShowS)
showable :: Show a => a -> Showable
showable a = Showable $ d -> showsPrec d a
instance Show Showable where
    showsPrec d (Showable f) = f d

现在,如果我们从不告诉任何人关于ShowableShow (f Showable)的唯一实例将是多a态的实例,最多约束到一个 Show 实例。只要最终用户没有主动尝试使用其他扩展来破坏您的代码,这就是合理的推理。通过添加功能依赖和/或重叠/不可判定的实例,可能会有一些麻烦,但只有颠覆意图的东西,没有可能导致你崩溃的东西。

有了这个,我们可以构建一个可判定的Show实例。

data Free f a = Pure a | Free (f (Free f a))
instance (Functor f, Show (f Showable), Show a) => Show (Free f a) where
  showsPrec d (Pure a)  = showParen (d > 10) $ showString "Pure " . showsPrec 10 a
  showsPrec d (Free as) = showParen (d > 10) $ showString "Free " . showsPrec 10 (fmap showable as)

这里给出的实现并没有消除对FlexibleContexts的需求,但你也可以通过编写几个额外的类层来消除它——如果你真的觉得需要 Haskell 98 兼容性。

我在几个包(包括我的ad包)中使用了这个技巧,以减少对不可判定实例的需求。

最新更新