[Haskell-cafe] Lattice and calculation of Least Upper Bounds

Olaf Klinke olf at aatal-apotheke.de
Tue Jun 19 22:16:17 UTC 2018


Well, free lattice ~= continuation monad is not entirely true, since 

Cont a x = (x -> a) -> a

and 

FreeLattice x = forall a. Lattice a => (x -> a) -> a

So in the latter the a is qualified and a rank-2 type. But the types are similar in structure. Thinking of it some more, the unit should be identical but the monad bind could be different. I'm just throwing in the first thing that type-checks; I haven't proven the monad laws for this. But at this abstraction level, the chances are good that the first thing that type-checks is the one you want. Consider the following. (I shortened the type names a bit.)

{-# LANGUAGE Rank2Types #-}
class Lat a where
   v :: a -> a -> a
   -- add more operations if you wish

newtype F x = F {free :: forall a. Lat a => (x -> a) -> a}
instance Lat (F x) where
   v x y = F (\f -> v (free x f) (free y f))

returnLat :: x -> F x
returnLat x = F (\f -> f x)
-- ^ same as for continuation monad

bindF :: F x -> (x -> F y) -> F y
bindF phi k = free phi k
-- ^ uses the fact that F y is a Lat instance.

Maybe also a blog post by Dan Doel [1] is relevant, where the free monoid is considered. 
-- Olaf

[1] http://comonad.com/reader/2015/free-monoids-in-haskell/


> 
> Am 19.06.2018 um 22:13 schrieb Siddharth Bhat <siddu.druid at gmail.com>:
> 
> I'd love a reference for the last sentence - free lattice ~= continuation monad?
> 
> Thanks,
> Siddharth



More information about the Haskell-Cafe mailing list