Powerset-over-Reader monad 是否存在?
Does a Powerset-over-Reader monad exist?
环境共享和不确定性的规范 'Monad instance' 如下(使用伪 Haskell,因为 Haskell 的 Data.Set
当然不是,一元):
eta :: a -> r -> {a} -- '{a}' means the type of a set of a's
eta x = \r -> {x}
bind :: (r -> {a}) -> (a -> r -> {b}) -> r -> {b}
m `bind` f = \r -> {v | x ∈ m r, v ∈ f x r}
通常,当尝试将一个 'container' monad(如 Powerset(List、Writer 等))与第二个 monad m
(此处大致为 Reader)组合时,一个 'wraps' m
围绕容器 monad,如上所述。
那么,我想知道以下潜在的 Powerset-over-Reader 规范:
eta' :: a -> {r -> a}
eta' x = {\r -> x}
bind' :: {r -> a} -> (a -> {r -> b}) -> {r -> b}
m `bind'` f = {rb | x <- m, ∀r: ∃rb' ∈ f (x r): rb r == rb' r}
这看起来并不明显疯狂(我确实意识到 GHCi 无法检查 rb r == rb' r
许多 rb
和 rb'
),但是 bind'
很复杂足以让(对我来说)检查单子定律是否成立变得困难。
那么,我的问题是 eta'
和 bind'
是否真的是一元的——如果不是,违反了哪条法律,可能会出现什么样的意外行为这对应于?
第二个问题,假设 eta'
和 bind'
不是单子的,是如何确定 是否 具有这些类型的函数是?
有趣的问题。这是我的看法——让我们看看我有没有犯错!
首先,我会把你的签名拼写成(稍微不那么伪)Haskell:
return :: a -> PSet (r -> a)
(>>=) :: PSet (r -> a) -> (a -> PSet (r -> b)) -> PSet (r -> b))
在继续之前,值得一提的是两个实际的并发症。首先,正如您已经观察到的那样,由于 Eq
and/or Ord
约束,它是 non-trivial 来提供集合 Functor
或 Monad
实例;无论如何,there are ways around it. Secondly, and more worryingly, with the type you propose for (>>=)
it is necessary to extract a
s from PSet (r -> a)
without having any obvious supply of r
s -- or, in other words, your (>>=)
demands a traversal of the function functor (->) r
. That, of course, is not possible in the general case, and tends to be impractical even when possible -- at least as far as Haskell is concerned. In any case, for our speculative purposes it is fine to suppose we can traverse (->) r
by applying the function to all possible r
values. I will indicate this through a hand-wavy universe :: PSet r
set, named in tribute to this package。我还将使用 universe :: PSet (r -> b)
,并假设即使不需要 Eq
约束,我们也可以判断两个 r -> b
函数是否同意某个 r
。 (pseudo-Haskell 确实越来越假了!)
初步评论,这是我的 pseudo-Haskell 版本的你的方法:
return :: a -> PSet (r -> a)
return x = singleton (const x)
(>>=) :: PSet (r -> a) -> (a -> PSet (r -> b)) -> PSet (r -> b))
m >>= f = unionMap (\x ->
intersectionMap (\r ->
filter (\rb ->
any (\rb' -> rb' r == rb r) (f (x r)))
(universe :: PSet (r -> b)))
(universe :: PSet r)) m
where
unionMap f = unions . map f
intersectionMap f = intersections . map f
接下来,单子定律:
m >>= return = m
return y >>= f = f y
m >>= f >>= g = m >>= \y -> f y >>= g
(顺便说一句,在做这类事情时,最好记住我们正在使用的 class 的其他演示文稿——在这种情况下,我们有 join
和 (>=>)
作为 (>>=)
的替代品——因为切换演示文稿可能会使您选择的实例更愉快。在这里我将坚持 (>>=)
演示文稿 Monad
。)
第一定律...
m >>= return = m
m >>= return -- LHS
unionMap (\x ->
intersectionMap (\r ->
filter (\rb ->
any (\rb' -> rb' r == rb r) (singleton (const (x r))))
(universe :: PSet (r -> b)))
(universe :: PSet r)) m
unionMap (\x ->
intersectionMap (\r ->
filter (\rb ->
const (x r) r == rb r)
(universe :: PSet (r -> b)))
(universe :: PSet r)) m
unionMap (\x ->
intersectionMap (\r ->
filter (\rb ->
x r == rb r)
(universe :: PSet (r -> b)))
(universe :: PSet r)) m
-- In other words, rb has to agree with x for all r.
unionMap (\x -> singleton x) m
m -- RHS
一个下来,两个去。
return y >>= f = f y
return y -- LHS
unionMap (\x ->
intersectionMap (\r ->
filter (\rb ->
any (\rb' -> rb' r == rb r) (f (x r)))
(universe :: PSet (r -> b)))
(universe :: PSet r)) (singleton (const y))
(\x ->
intersectionMap (\r ->
filter (\rb ->
any (\rb' -> rb' r == rb r) (f (x r)))
(universe :: PSet (r -> b)))
(universe :: PSet r)) (const y)
intersectionMap (\r ->
filter (\rb ->
any (\rb' -> rb' r == rb r) (f (const y r)))
(universe :: PSet (r -> b)))
(universe :: PSet r)
intersectionMap (\r ->
filter (\rb ->
any (\rb' -> rb' r == rb r) (f y)))
(universe :: PSet (r -> b)))
(universe :: PSet r)
-- This set includes all functions that agree with at least one function
-- from (f y) at each r.
因此,return y >>= f
可能比 f y
大得多。我们违反了第二定律;因此,我们没有 monad —— 至少这里提出的实例没有。
附录:这里是您的函数的一个实际的、可运行的实现,它至少可以用于小类型。它利用了前面提到的 universe 包。
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
module FunSet where
import Data.Universe
import Data.Map (Map)
import qualified Data.Map as M
import Data.Set (Set)
import qualified Data.Set as S
import Data.Int
import Data.Bool
-- FunSet and its would-be monad instance
newtype FunSet r a = FunSet { runFunSet :: Set (Fun r a) }
deriving (Eq, Ord, Show)
fsreturn :: (Finite a, Finite r, Ord r) => a -> FunSet r a
fsreturn x = FunSet (S.singleton (toFun (const x)))
-- Perhaps we should think of a better name for this...
fsbind :: forall r a b.
(Ord r, Finite r, Ord a, Ord b, Finite b, Eq b)
=> FunSet r a -> (a -> FunSet r b) -> FunSet r b
fsbind (FunSet s) f = FunSet $
unionMap (\x ->
intersectionMap (\r ->
S.filter (\rb ->
any (\rb' -> funApply rb' r == funApply rb r)
((runFunSet . f) (funApply x r)))
(universeF' :: Set (Fun r b)))
(universeF' :: Set r)) s
toFunSet :: (Finite r, Finite a, Ord r, Ord a) => [r -> a] -> FunSet r a
toFunSet = FunSet . S.fromList . fmap toFun
-- Materialised functions
newtype Fun r a = Fun { unFun :: Map r a }
deriving (Eq, Ord, Show, Functor)
instance (Finite r, Ord r, Universe a) => Universe (Fun r a) where
universe = fmap (Fun . (\f ->
foldr (\x m ->
M.insert x (f x) m) M.empty universe))
universe
instance (Finite r, Ord r, Finite a) => Finite (Fun r a) where
universeF = universe
funApply :: Ord r => Fun r a -> r -> a
funApply f r = maybe
(error "funApply: Partial functions are not fun")
id (M.lookup r (unFun f))
toFun :: (Finite r, Finite a, Ord r) => (r -> a) -> Fun r a
toFun f = Fun (M.fromList (fmap ((,) <$> id <*> f) universeF))
-- Set utilities
unionMap :: (Ord a, Ord b) => (a -> Set b) -> (Set a -> Set b)
unionMap f = S.foldl S.union S.empty . S.map f
-- Note that this is partial. Since for our immediate purposes the only
-- consequence is that r in FunSet r a cannot be Void, I didn't bother
-- with making it cleaner.
intersectionMap :: (Ord a, Ord b) => (a -> Set b) -> (Set a -> Set b)
intersectionMap f s = case ss of
[] -> error "intersectionMap: Intersection of empty set of sets"
_ -> foldl1 S.intersection ss
where
ss = S.toList (S.map f s)
universeF' :: (Finite a, Ord a) => Set a
universeF' = S.fromList universeF
-- Demo
main :: IO ()
main = do
let andor = toFunSet [uncurry (&&), uncurry (||)]
print andor -- Two truth tables
print $ funApply (toFun (2+)) (3 :: Int8) -- 5
print $ (S.map (flip funApply (7 :: Int8)) . runFunSet)
(fsreturn (Just True)) -- fromList [Just True]
-- First monad law demo
print $ fsbind andor fsreturn == andor -- True
-- Second monad law demo
let twoToFour = [ bool (Left False) (Left True)
, bool (Left False) (Right False)]
decider b = toFunSet
(fmap (. bool (uncurry (&&)) (uncurry (||)) b) twoToFour)
print $ fsbind (fsreturn True) decider == decider True -- False (!)
用 Kleisli 表示法验证定律要容易一些。
kleisli' :: (a -> {r -> b}) -> (b -> {r -> c}) -> (a -> {r -> c})
g `kleisli'` f = \z -> {rb | x <- g z, ∀r: ∃rb' ∈ f (x r): rb r == rb' r}
我们来验证一下return `kleisli'` f = f
。
(\a -> {\r->a}) `kleisli'` f =
\z -> {rb | x <- {\r->z}, ∀r: ∃rb' ∈ f (x r): rb r == rb' r} =
\z -> {rb | ∀r: ∃rb' ∈ f z: rb r == rb' r}
假设我们所有的类型 a
、b
、c
和 r
都是 Integer
和 f x = {const x, const -x}
。 (return `kleisli'` f) 5
中有哪些功能?这个集合应该是f 5
,即{const 5, const -5}
。
是吗?当然 const 5
和 const -5
都在,但不仅如此。比如\r->if even r then 5 else -5
也在.
环境共享和不确定性的规范 'Monad instance' 如下(使用伪 Haskell,因为 Haskell 的 Data.Set
当然不是,一元):
eta :: a -> r -> {a} -- '{a}' means the type of a set of a's
eta x = \r -> {x}
bind :: (r -> {a}) -> (a -> r -> {b}) -> r -> {b}
m `bind` f = \r -> {v | x ∈ m r, v ∈ f x r}
通常,当尝试将一个 'container' monad(如 Powerset(List、Writer 等))与第二个 monad m
(此处大致为 Reader)组合时,一个 'wraps' m
围绕容器 monad,如上所述。
那么,我想知道以下潜在的 Powerset-over-Reader 规范:
eta' :: a -> {r -> a}
eta' x = {\r -> x}
bind' :: {r -> a} -> (a -> {r -> b}) -> {r -> b}
m `bind'` f = {rb | x <- m, ∀r: ∃rb' ∈ f (x r): rb r == rb' r}
这看起来并不明显疯狂(我确实意识到 GHCi 无法检查 rb r == rb' r
许多 rb
和 rb'
),但是 bind'
很复杂足以让(对我来说)检查单子定律是否成立变得困难。
那么,我的问题是 eta'
和 bind'
是否真的是一元的——如果不是,违反了哪条法律,可能会出现什么样的意外行为这对应于?
第二个问题,假设 eta'
和 bind'
不是单子的,是如何确定 是否 具有这些类型的函数是?
有趣的问题。这是我的看法——让我们看看我有没有犯错!
首先,我会把你的签名拼写成(稍微不那么伪)Haskell:
return :: a -> PSet (r -> a)
(>>=) :: PSet (r -> a) -> (a -> PSet (r -> b)) -> PSet (r -> b))
在继续之前,值得一提的是两个实际的并发症。首先,正如您已经观察到的那样,由于 Eq
and/or Ord
约束,它是 non-trivial 来提供集合 Functor
或 Monad
实例;无论如何,there are ways around it. Secondly, and more worryingly, with the type you propose for (>>=)
it is necessary to extract a
s from PSet (r -> a)
without having any obvious supply of r
s -- or, in other words, your (>>=)
demands a traversal of the function functor (->) r
. That, of course, is not possible in the general case, and tends to be impractical even when possible -- at least as far as Haskell is concerned. In any case, for our speculative purposes it is fine to suppose we can traverse (->) r
by applying the function to all possible r
values. I will indicate this through a hand-wavy universe :: PSet r
set, named in tribute to this package。我还将使用 universe :: PSet (r -> b)
,并假设即使不需要 Eq
约束,我们也可以判断两个 r -> b
函数是否同意某个 r
。 (pseudo-Haskell 确实越来越假了!)
初步评论,这是我的 pseudo-Haskell 版本的你的方法:
return :: a -> PSet (r -> a)
return x = singleton (const x)
(>>=) :: PSet (r -> a) -> (a -> PSet (r -> b)) -> PSet (r -> b))
m >>= f = unionMap (\x ->
intersectionMap (\r ->
filter (\rb ->
any (\rb' -> rb' r == rb r) (f (x r)))
(universe :: PSet (r -> b)))
(universe :: PSet r)) m
where
unionMap f = unions . map f
intersectionMap f = intersections . map f
接下来,单子定律:
m >>= return = m
return y >>= f = f y
m >>= f >>= g = m >>= \y -> f y >>= g
(顺便说一句,在做这类事情时,最好记住我们正在使用的 class 的其他演示文稿——在这种情况下,我们有 join
和 (>=>)
作为 (>>=)
的替代品——因为切换演示文稿可能会使您选择的实例更愉快。在这里我将坚持 (>>=)
演示文稿 Monad
。)
第一定律...
m >>= return = m
m >>= return -- LHS
unionMap (\x ->
intersectionMap (\r ->
filter (\rb ->
any (\rb' -> rb' r == rb r) (singleton (const (x r))))
(universe :: PSet (r -> b)))
(universe :: PSet r)) m
unionMap (\x ->
intersectionMap (\r ->
filter (\rb ->
const (x r) r == rb r)
(universe :: PSet (r -> b)))
(universe :: PSet r)) m
unionMap (\x ->
intersectionMap (\r ->
filter (\rb ->
x r == rb r)
(universe :: PSet (r -> b)))
(universe :: PSet r)) m
-- In other words, rb has to agree with x for all r.
unionMap (\x -> singleton x) m
m -- RHS
一个下来,两个去。
return y >>= f = f y
return y -- LHS
unionMap (\x ->
intersectionMap (\r ->
filter (\rb ->
any (\rb' -> rb' r == rb r) (f (x r)))
(universe :: PSet (r -> b)))
(universe :: PSet r)) (singleton (const y))
(\x ->
intersectionMap (\r ->
filter (\rb ->
any (\rb' -> rb' r == rb r) (f (x r)))
(universe :: PSet (r -> b)))
(universe :: PSet r)) (const y)
intersectionMap (\r ->
filter (\rb ->
any (\rb' -> rb' r == rb r) (f (const y r)))
(universe :: PSet (r -> b)))
(universe :: PSet r)
intersectionMap (\r ->
filter (\rb ->
any (\rb' -> rb' r == rb r) (f y)))
(universe :: PSet (r -> b)))
(universe :: PSet r)
-- This set includes all functions that agree with at least one function
-- from (f y) at each r.
因此,return y >>= f
可能比 f y
大得多。我们违反了第二定律;因此,我们没有 monad —— 至少这里提出的实例没有。
附录:这里是您的函数的一个实际的、可运行的实现,它至少可以用于小类型。它利用了前面提到的 universe 包。
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
module FunSet where
import Data.Universe
import Data.Map (Map)
import qualified Data.Map as M
import Data.Set (Set)
import qualified Data.Set as S
import Data.Int
import Data.Bool
-- FunSet and its would-be monad instance
newtype FunSet r a = FunSet { runFunSet :: Set (Fun r a) }
deriving (Eq, Ord, Show)
fsreturn :: (Finite a, Finite r, Ord r) => a -> FunSet r a
fsreturn x = FunSet (S.singleton (toFun (const x)))
-- Perhaps we should think of a better name for this...
fsbind :: forall r a b.
(Ord r, Finite r, Ord a, Ord b, Finite b, Eq b)
=> FunSet r a -> (a -> FunSet r b) -> FunSet r b
fsbind (FunSet s) f = FunSet $
unionMap (\x ->
intersectionMap (\r ->
S.filter (\rb ->
any (\rb' -> funApply rb' r == funApply rb r)
((runFunSet . f) (funApply x r)))
(universeF' :: Set (Fun r b)))
(universeF' :: Set r)) s
toFunSet :: (Finite r, Finite a, Ord r, Ord a) => [r -> a] -> FunSet r a
toFunSet = FunSet . S.fromList . fmap toFun
-- Materialised functions
newtype Fun r a = Fun { unFun :: Map r a }
deriving (Eq, Ord, Show, Functor)
instance (Finite r, Ord r, Universe a) => Universe (Fun r a) where
universe = fmap (Fun . (\f ->
foldr (\x m ->
M.insert x (f x) m) M.empty universe))
universe
instance (Finite r, Ord r, Finite a) => Finite (Fun r a) where
universeF = universe
funApply :: Ord r => Fun r a -> r -> a
funApply f r = maybe
(error "funApply: Partial functions are not fun")
id (M.lookup r (unFun f))
toFun :: (Finite r, Finite a, Ord r) => (r -> a) -> Fun r a
toFun f = Fun (M.fromList (fmap ((,) <$> id <*> f) universeF))
-- Set utilities
unionMap :: (Ord a, Ord b) => (a -> Set b) -> (Set a -> Set b)
unionMap f = S.foldl S.union S.empty . S.map f
-- Note that this is partial. Since for our immediate purposes the only
-- consequence is that r in FunSet r a cannot be Void, I didn't bother
-- with making it cleaner.
intersectionMap :: (Ord a, Ord b) => (a -> Set b) -> (Set a -> Set b)
intersectionMap f s = case ss of
[] -> error "intersectionMap: Intersection of empty set of sets"
_ -> foldl1 S.intersection ss
where
ss = S.toList (S.map f s)
universeF' :: (Finite a, Ord a) => Set a
universeF' = S.fromList universeF
-- Demo
main :: IO ()
main = do
let andor = toFunSet [uncurry (&&), uncurry (||)]
print andor -- Two truth tables
print $ funApply (toFun (2+)) (3 :: Int8) -- 5
print $ (S.map (flip funApply (7 :: Int8)) . runFunSet)
(fsreturn (Just True)) -- fromList [Just True]
-- First monad law demo
print $ fsbind andor fsreturn == andor -- True
-- Second monad law demo
let twoToFour = [ bool (Left False) (Left True)
, bool (Left False) (Right False)]
decider b = toFunSet
(fmap (. bool (uncurry (&&)) (uncurry (||)) b) twoToFour)
print $ fsbind (fsreturn True) decider == decider True -- False (!)
用 Kleisli 表示法验证定律要容易一些。
kleisli' :: (a -> {r -> b}) -> (b -> {r -> c}) -> (a -> {r -> c})
g `kleisli'` f = \z -> {rb | x <- g z, ∀r: ∃rb' ∈ f (x r): rb r == rb' r}
我们来验证一下return `kleisli'` f = f
。
(\a -> {\r->a}) `kleisli'` f =
\z -> {rb | x <- {\r->z}, ∀r: ∃rb' ∈ f (x r): rb r == rb' r} =
\z -> {rb | ∀r: ∃rb' ∈ f z: rb r == rb' r}
假设我们所有的类型 a
、b
、c
和 r
都是 Integer
和 f x = {const x, const -x}
。 (return `kleisli'` f) 5
中有哪些功能?这个集合应该是f 5
,即{const 5, const -5}
。
是吗?当然 const 5
和 const -5
都在,但不仅如此。比如\r->if even r then 5 else -5
也在.