我注意到Writer m
和Either e
monad之间存在双重关系。如果m是幺半群,那么
unit :: () -> m
join :: (m,m) -> m
可用于形成monad:
return is composition: a -> ((),a) -> (m,a)
join is composition: (m,(m,a)) -> ((m,m),a) -> (m,a)
()的双重是Void(空类型),产品的双重是副产品。每种类型的e都可以被赋予“comonoid”结构:
unit :: Void -> e
join :: Either e e -> e
以明显的方式。现在,
return is composition: a -> Either Void a -> Either e a
join is composition: Either e (Either e a) -> Either (Either e e) a -> Either e a
这是Either e
monad。箭头遵循完全相同的模式。
问题:是否可以编写一个能够同时执行Either e
和Writer m
的通用代码,具体取决于给定的幺半群?
答案 0 :(得分:5)
我不会说这些monad是绝对双重的,而是它们都是由以下结构产生的:给定monoidal category(C,⊗,1)和C中的代数A,考虑monad将X发送到A⊗X。在第一种情况下,C是Hask,⊗是×,代数是幺半群,在第二种情况下C是Hask,⊗是E(Either),而代数只是一种类型(每种类型都是一种独特的代数 - 这就是你所谓的“共生”,尽管这通常意味着别的东西,见下文)。按照惯例,我在一个假想的世界工作,其中⊥不存在,因此×实际上是一种产品,依此类推。对于幺半群类别,可能使用合适的类型类来捕获这种常见的泛化(我太累了,无法理解目前在这方面正在尝试做什么类别 - 并且因此同时将Writer和Either定义为monad( modulo newtypes,可能)。
至于Writer m-well的分类对偶,它取决于你想要考虑的是什么,但最可能的候选者似乎是(,)m上的comonad结构,没有任何m条件:
instance Comonad ((,) m) where
coreturn (m, a) = a
cojoin (m, a) = (m, (m, a))
(注意这里是我们使用的地方,m是一个comonoid,即我们有地图m→(),m→m×m)。
答案 1 :(得分:3)
以下是代码:
{-# LANGUAGE FlexibleInstances, EmptyDataDecls, MultiParamTypeClasses,
FunctionalDependencies, GeneralizedNewtypeDeriving, UndecidableInstances #-}
import Control.Arrow (first, second, left, right)
import Data.Monoid
data Void
data Iso a b = Iso { from :: a -> b, to :: b -> a}
-- monoidal category (Hask, m, unit)
class MonoidalCategory m unit | m -> unit where
iso1 :: Iso (m (m x y) z) (m x (m y z))
iso2 :: Iso x (m x unit)
iso3 :: Iso x (m unit x)
map1 :: (a -> b) -> (m a c -> m b c)
map2 :: (a -> b) -> (m c a -> m c b)
instance MonoidalCategory (,) () where
iso1 = Iso (\((x,y),z) -> (x,(y,z))) (\(x,(y,z)) -> ((x,y),z))
iso2 = Iso (\x -> (x,())) (\(x,()) -> x)
iso3 = Iso (\x -> ((),x)) (\((),x) -> x)
map1 = first
map2 = second
instance MonoidalCategory Either Void where
iso1 = Iso f g
where f (Left (Left x)) = Left x
f (Left (Right x)) = Right (Left x)
f (Right x) = Right (Right x)
g (Left x) = Left (Left x)
g (Right (Left x)) = Left (Right x)
g (Right (Right x)) = Right x
iso2 = Iso Left (\(Left x) -> x)
iso3 = Iso Right (\(Right x) -> x)
map1 = left
map2 = right
-- monoid in monoidal category (Hask, c, u)
class MonoidM m c u | m -> c u where
mult :: c m m -> m
unit :: u -> m
-- object of monoidal category (Hask, Either, Void)
newtype Eith a = Eith { getEith :: a } deriving (Show)
-- object of monoidal category (Hask, (,), ())
newtype Monoid m => Mult m = Mult { getMult :: m } deriving (Monoid, Show)
instance MonoidM (Eith a) Either Void where
mult (Left x) = x
mult (Right x) = x
unit _ = undefined
instance Monoid m => MonoidM (Mult m) (,) () where
mult = uncurry mappend
unit = const mempty
instance (MonoidalCategory c u, MonoidM m c u) => Monad (c m) where
return = map1 unit . from iso3
x >>= f = (map1 mult . to iso1) (map2 f x)
用法:
a = (Mult "hello", 5) >>= (\x -> (Mult " world", x+1))
-- (Mult {getMult = "hello world"}, 6)
inv 0 = Left (Eith "error")
inv x = Right (1/x)
b = Right 5 >>= inv -- Right 0.2
c = Right 0 >>= inv -- Left (Eith {getEith="error"})
d = Left (Eith "a") >>= inv -- Left (Eith {getEith="a"})
答案 2 :(得分:1)
严格地说,()
和Void
不是双重的 - ⊥的存在意味着所有类型都有人居住,因此⊥是Void
的唯一居民,使其成为您期望的终端对象。 ()
有两个值,所以不相关。如果你手动⊥离开,那么()
就是终点,Void
就像希望的那样是最初的。
我认为你的例子也不是一个类似的结构 - 一个comonoid的签名应该是这样的,我想:
class Comonoid a
coempty :: a -> ()
coappend :: a -> (a, a)
如果你考虑一下等效的共生法则必须是什么,我认为最终会毫无用处。
我想知道,如果应用于代数数据类型,你所获得的是与自然界的标准和/产品幺半群更密切相关吗? Void
和Either
为0 / +,而()
和(,)
为1 / *。但我不确定如何证明其余部分的合理性。