Arnaud Spiwack
The reader functor \((E\rightarrow)\) is a monad iff \(E\) is a comonoid
When \(\otimes\) is a Cartesian product, then there exists a unique comonoid on each object.
Category of sets and relations
Comonoid species #1
Interference
a %1-> b
Since GHC 9.0
{-# LANGUAGE LinearTypes #-}
Completely normal Haskell + an extra type
(+ stuff for polymorphism)
(but we won't talk about it today)
f :: A %1-> B
f u
u
If is consumed exactly once
then is consumed exactly once
What does “consume exactly once” mean?
evaluate x
apply x and consume the result exactly once
decompose x and consume both components exactly once
Base type
Function
Pair
id x = x
✓
linear
dup x = (x,x)
✗
not linear
swap (x,y) = (y,x)
✓
linear
forget x = ()
✗
not linear
f (Left x) = x
f (Right y) = y
✓
linear
✓
linear
✗
not linear
h x b = case b of
True -> x
False -> x
g z = case z of
Left x -> x
Right y -> y
k x b = case b of
True -> x
False -> ()
✓
linear
f x = dup x
✓
linear
✗
not linear
h u = u 0
g x = id (id x)
k u = u (u 0)
✓
linear
✗
not linear
Linear types have (non-trivial) comonoids
class Consumable a where
consume :: a %1 -> ()
class Consumable a => Dupable a where
dup2 :: a %1 -> (a, a)
(in truth: more methods)
Comonoid species #2
Hidden shared state
class Lattice a where
top :: a
sup :: a -> a -> a
data L
instance Lattice L
data LV ≈ IORef L
δ r ≈ (r, r)
ε r ≈ ()
shout :: LV %1 -> L -> ()
shout r l ≈ modifyIORef r (sup l)
Can't read back 🙁 . Blocking operations impossible(?) in pure code
fix :: (LV %1 -> a) -> (L, a)
f :: LV %1 -> a
Computes a monotonic function in a lattice (+ some value)
Iterates f until a fixpoint
(conditions may apply)
data UF ≈ <some mutable union-find data structure>
δ r ≈ (r, r)
ε r ≈ ()
union :: UF %1 -> A -> A -> ()
find :: UF %1 -> Ur A
We may still take a fixed point, but union-find is not necessarily finite-height, so it can diverge.
It'll works if A is a finite type.
class Monoid a
=> Commutative a where
-- a <> b = b <> a
data M
instance Commutative M
data W ≈ IORef M
δ r ≈ (r, r)
ε r ≈ ()
shout :: W %1 -> M -> ()
shout r a ≈ modifyIORef r (<> a)
No fixed-point, no reads. Resembles map-reduce.
We might as well remember all the intermediate values
a₀
a₀ <> a₁
a₀ <> a₁ <> a₂
a₀ <> a₁ <> a₂ <> a₃
read :: W %1 -> Ur M
Needs more. What exactly?
It seems to work in a monad 🤢
A structure which can accumulate Ms, can accumulate Xs directly. Optimisation!
instance MSet (Endo s) s where
s • (Endo f) = f s
So we could encode the (non-linear) state monad as a comonoid, if we can solve the pesky read issue.
newtype Act w = Act (forall r. w r -> r)
instance Comonad w => Semigroup (Act w) where
(Act a) <> (Act b) = Act $ b . extend a
instance Comonad w => Monoid (Act w) where
mempty = Act extract
instance MSet (Act w) w where
s • (Act a) = extend a s
Question: is
WAct w %1 -> a
w a
?