Week 2 Exercises
These exercises still involve lots of examples and counterexamples, although there are some jigsaw puzzle elements too.
Exercise 1
Some of the following types admit functors, contravariant functors, bifunctors or profunctors, while others do not admit any.
- Instances for
Bool
. - Instances for
Maybe a
. - Instances for
Either a b
. - Instances for
(,) a b
. - Instances for
Endo a
. - Instances for
(->) a b
andOp a b
. - Instances for
()
. - Instances for
[] a
. - Instances for
NonEmpty a
. - Instances for
Void
. - Instances for
IO a
. - Instances for
Map k a
.
Figure out which ones admit which, implement the corresponding type class instances and prove that your instances are coherent. Your code must compile, but your proofs may be as informal as you wish.
Since some of these instances already exist in Prelude
, you may need to use the following wrappers or introduce new ones to avoid duplicate instance declaration errors. However, be mindful not to accidentally use the existing instances from Prelude
!
You may need to install the contravariant
, bifunctors
and profunctors
packages if you want to import the type classes.
While it is fine to define the instances for IO
using do
notation, the morally correct way requires primitive operations from the GHC.IO
module, which in turn requires the MagicHash
and UnboxedTuples
extensions. If you implement the instances in this way, they should look a lot like State
in exercise 3.
module Week2.Exercise1 where
import Data.Bifunctor
import Data.Functor.Contravariant
import Data.List.NonEmpty (NonEmpty (..))
import qualified Data.List.NonEmpty as NonEmpty
import Data.Map (Map (..))
import qualified Data.Map as Map
import Data.Profunctor
import Data.Void
newtype Endo a = Endo {appEndo :: a -> a}
newtype Op' a b = Op' {getOp' :: Op a b}
Exercise 2
Some of the following types admit functors, while others do not.
- Instances for
Sum m n a
, given instances form
andn
. - Instances for
Product m n a
, given instances form
andn
. - Instances for
Identity a
. - Instances for
Compose m n a
, given instances form
andn
. - Instances for
Const a b
. - Instances for
Proxy a
. - Instances for
State a b
. - Instances for
Cont a b
. - Instances for
Star m a b
, given instances form
. - Instances for
Costar m a b
. - Instances for
Yoneda m a
, given instances form
. - Instances for
Coyoneda m a
.
Figure out which ones do, implement the corresponding type class instances and prove that your instances are coherent. Your code must compile, but your proofs may be as informal as you wish.
Most of the same considerations apply as in exercise 1.
The language extensions are required to be able to use universal quantifiers more freely with Yoneda
and Coyoneda
.
{-# LANGUAGE ExistentialQuantification, RankNTypes #-}
module Week2.Exercise2 where
data Sum m n a = InL (m a) | InR (n a)
deriving Show
data Product m n a = Pair {fstPair :: m a, sndPair :: n a}
deriving Show
newtype Identity a = Identity {runIdentity :: a}
deriving Show
newtype Compose m n a = Compose {getCompose :: m (n a)}
deriving Show
newtype Const a b = Const {getConst :: a}
deriving Show
data Proxy a = Proxy
deriving Show
newtype State a b = State {runState :: a -> (b, a)}
newtype Cont a b = Cont {runCont :: (b -> a) -> a}
newtype Star m a b = Star {runStar :: a -> m b}
newtype Costar m a b = Costar {runCostar :: m a -> b}
newtype Yoneda m a = Yoneda {runYoneda :: forall b. (a -> b) -> m b}
data Coyoneda m a = forall b. Coyoneda (b -> a) (m b)
Exercise 3
Functors, contravariant functors, bifunctors and profunctors are related to each other in several different ways. However, this is obscured by the fact that the only way to choose the free parameters for type class instances is to partially apply the corresponding type constructors. Working around this restriction requires some clever tricks with wrappers.
Implement the instances that witness the relations between the different kinds of functors. While doing so, try to find a way to use the flip
and join
functions with the respective wrappers.
Most of the same considerations apply as in exercise 1.
module Week2.Exercise3 where
import Control.Monad (join)
import Data.Bifunctor
import Data.Functor.Contravariant
import Data.Profunctor
newtype WrappedBifunctor m a b = WrapBifunctor {unwrapBifunctor :: m a b}
deriving Show
newtype WrappedProfunctor m a b = WrapProfunctor {unwrapProfunctor :: m a b}
deriving Show
newtype Flip m a b = Flip {runFlip :: m b a}
deriving Show
newtype Join m a = Join {runJoin :: m a a}
instance Bifunctor m => Functor (WrappedBifunctor m a) where
fmap f (WrapBifunctor x) = _
instance Profunctor m => Functor (WrappedProfunctor m a) where
fmap f (WrapProfunctor x) = _
instance Bifunctor m => Functor (Flip m a) where
fmap f (Flip x) = _
instance Profunctor m => Contravariant (Flip m a) where
contramap f (Flip x) = _
instance Bifunctor m => Bifunctor (Flip m) where
bimap f g (Flip x) = _
instance Bifunctor m => Functor (Join m) where
fmap f (Join x) = _