Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Representable Functor isomorphic to (Bool -> a)

I thought I'd try the intriguing Representable-functors package to define a Monad and Comonad instance for the functor given by data Pair a = Pair a a which is representable by Bool; as mentioned in the answer to my earlier question on the vector monad.

The first thing I noticed was that to make my type an instance of Representable, I should not only define tabulate and index, but also ensure my type is an instance of the Indexable, Distributive, Keyed, Apply, Applicative, and Functor type classes. Well, ok, index completes the definition of Indexable, and the <.> function of Apply can use <*> from Applicative; and it shouldn't be a surprise that a Functor instance is required. Nevertheless, I am doubtful of my instances for Keyed and Distributive.

data Pair a = Pair a a
  deriving (Show,Eq)

instance Functor Pair where
  fmap f (Pair x y) = Pair (f x) (f y)

type instance Key Pair = Bool

instance Keyed Pair where
  mapWithKey f (Pair x y) = Pair (f False x) (f False y)

instance Indexable Pair where
  index (Pair x _) False = x
  index (Pair _ y) True  = y

instance Applicative Pair where
  pure a = Pair a a
  Pair f g <*> Pair x y = Pair (f x) (g y)

instance Apply Pair where
  (<.>) = (<*>)

instance Distributive Pair where
  collect f x = Pair (getL . f <$> x) (getR . f <$> x)
    where getL (Pair x _) = x
          getR (Pair _ y) = y

instance Representable Pair where
  tabulate f = Pair (f False) (f True)

My mapWithKey definition borrows from that of the [] instance for Keyed: though I don't understand why 0 was used there for every iteration. I have similarly used False for each term of Pair.

As I concluded by defining the Monad and Comonad instances, I discovered that Bool requires a Semigroup definition for Extend, and a Monoid definition for Comonad. I follow the Semigroup instance for the Either, which is isomorphic to (||), and choose False for mempty:

instance Monad Pair where
  return = pureRep
  (>>=)  = bindRep

instance Monoid Bool where
  mempty = False
  mappend = (||)

instance Semigroup Bool where
  (<>) = mappend

instance Extend Pair where
  extend = extendRep -- needs Bool Semigroup

instance Comonad Pair where
  extract = extractRep -- needs Bool Monoid

So then, have I met the requirements of the Representable class correctly, and idiomatically?

like image 727
user2023370 Avatar asked May 30 '11 15:05

user2023370


1 Answers

Yes you have. Though your instance for Keyed is off.

instance Keyed Pair where
    mapWithKey f (Pair x y) = Pair (f False x) (f True y)

or even easier

instance Keyed Pair where
    mapWithKey = mapWithKeyRep

and similarly

instance Distributive Pair where
    distribute = distributeRep

Given index and tabulate you can use the various fooRep methods in the Representable module to provide definitions for all of the other superclasses.

The Extend and Comonad definitions, are not actually part of the requirements to be Representable. They are included though, because being representable means you are isomorphic to a function, which enables you to recycle the definition for the "exponential" Comonad (aka cowriter, or Traced comonad) to become a Comonad as well, given some monoid on your representation. This isn't required though, mainly because I can't constrain it to hold given the types involved.

You may want to drop the Semigroup and Monoid for Bool though and just hand implement extend and extract. It is easy enough.

instance Extend Pair where
    extend f p@(Pair a b) = Pair (f p) (f (Pair b a))

instance Comonad Pair where
    extract (Pair a b) = a

Also, this type is provided by the representable-tries package, which includes a number of other instances.

And,

import Control.Applicative
bool = [True, False]
f tt _tf _ft _ff True  True  = tt
f _tt tf _ft _ff True  False = tf
f _tt _tf ft _ff False True  = ft
f _tt _tf _ft ff False False = ff
associative f = and (assoc <$> bool <*> bool <*> bool) where 
    assoc a b c = f (f a b) c == f a (f b c)
semigroups = filter associative 
    [ f tt tf ft ff | tt <- bool, tf <- bool, ft <- bool, ff <- bool ]
unital (u, f) = all unit bool where 
    unit a = f u a == a && f a u == a
monoids = filter unital 
    [ (u, f) | u <- bool, f <- semigroups ]

shows that as you surmised there are the 4 possible monoids you surmised and if you only want an extend instance, there are 8 semigroups available.

like image 104
Edward Kmett Avatar answered Nov 10 '22 16:11

Edward Kmett