Skip to content

Instantly share code, notes, and snippets.

@Kazark
Created August 7, 2020 15:00
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save Kazark/6403fe430b36f7b32470a6b6c22477b6 to your computer and use it in GitHub Desktop.
Save Kazark/6403fe430b36f7b32470a6b6c22477b6 to your computer and use it in GitHub Desktop.
Exercises to familiarize yourself with many standard typeclasses
We are going to be redefining a bunch of things that are in prelude in order to
make them explicit and all in one place:
> {-# LANGUAGE NoImplicitPrelude #-}
It is best for learning to be able to write concretized signatures of typeclass
functions when defining instances:
> {-# LANGUAGE InstanceSigs #-}
We're going to have a couple empty types, so:
> {-# LANGUAGE EmptyCase #-}
Welcome to these exercises on functional container abstractions!
> module FunctionalAbstractions where
Let's consider first a series of types that could contain a certain number of
things, but are generic (or parametrically polymorphic) on what type of things
they contain. Naturally, we'll start with zero, i.e. with a type that cannot
contain any of the things:
> data Zero a
Hold on though, that zero is too hardcore; not only can it not hold any things,
the type is entirely uninhabited, i.e. it holds no values at all. So what about
this, a type with a phantom parameter:
> data Phantom a = Phantom
This type, while it cannot contain any of the things, at least is inhabited. Two
kinds of zero; interesting. Wonder how that will work out.
What's next? One, right? No, wait! What about a half? Or, rather "zero or one":
> data Maybe a = Nothing | Just a
Okay, now let's do one, which from another viewpoing is the identity functor
> newtype Id a = Id a
Closely related to one, is plus one:
> data OneAnd f a = OneAnd a (f a)
Next a specialization of pair, as two:
> data Two a = Two a a
This is tedious. Let's jump from two to any number of things:
> data List a = Nil a | Cons a (List a)
Though maybe you will want to enforce that you have at least one sometimes; a
non-empty list:
> newtype NonEmptyL a = NonEmptyL (OneAnd List a)
I have also encountered times where I needed to know that there was at least two
things in the list, though I've never hit a scenario where I needed more than
that, so we can just lean on `OneAnd` for that:
> type AtLeast2 a = OneAnd NonEmptyL a
On the other hand, there are other ways to do arbitrary-length types than just
singly-linked lists, e.g.:
> data BTree a = Empty | Leaf a | Fork (BTree a) a (BTree a)
Having run up the number hierarchy a bit, let's do some logic types. First "and":
> data Pair a b = Pair a b
Next "or":
> data Either a b = Left a | Right b
Next "and/or":
> data AndOr a b = LeftOnly a | Both a b | RightOnly b
Next "if/then", i.e. the a parameter of type a can be produced if the hypothesis
r holds:
> newtype Cont r a = Cont { runCont :: r -> a }
The following function will be needed to express some laws:
> id :: a -> a
> id x = x
Now the game is to see which datatypes fit which abstractions. The rules of the
game are called laws. `Functor` has two (<$> is also known as map or fmap):
* Identity: fmap id == id
Which yields the following free theorem:
* Composition: fmap (f . g) == fmap f . fmap g
> class Functor f where
> (<$>) :: (a -> b) -> f a -> f b
`Applicative` has the following laws (<*> is also known as apply):
* Identity: pure id <*> v = v
* Composition: pure (.) <*> u <*> v <*> w = u <*> (v <*> w)
* Homomorphism: pure f <*> pure x = pure (f x)
* Interchange: u <*> pure y = pure ($ y) <*> u
> class Functor f => Applicative f where
> pure :: a -> f a
> (<*>) :: f (a -> b) -> f a -> f b
`Alternative` is a monoid on applicative functors, which implies the following
laws:
* Left identity: empty <|> x = x
* Right identity: x <|> empty = x
* Associativity: x <|> y <|> z = (x <|> y) <|> z = x <|> (y <|> z)
> class Applicative f => Alternative f where
> empty :: f a
> (<|>) :: f a -> f a -> f a
`Monad` has the following laws (>>= is also called bind; we could add
`return` but it is just the same as `pure` for `Applicative`):
* Left identity: pure a >>= k = k a
* Right identity: m >>= pure = m
* Associativity: m >>= (\x -> k x >>= h) = (m >>= k) >>= h
There is also an ugly law that relates it to `Applicative` which I omit here.
> class Applicative f => Monad f where
> (>>=) :: a -> f b -> f a -> f b
`MonadPlus` is a monoid on monads:
> class (Alternative m, Monad m) => MonadPlus m where
> mzero :: m a
> mzero = empty
> mplus :: m a -> m a -> m a
> mplus = (<|>)
`Contravariant`, that is, a contravariant version of `Functor`, has the
following laws:
* Identity: contramap id = id
Which yields the following free theorem:
* Composition: contramap (g . f) = contramap f . contramap g
> class Contravariant f where
> contramap :: (b -> a) -> f a -> f b
`Bifunctor` has the following laws:
* bimap id id ≡ id
Which yields the following free theorem:
* bimap (f . g) (h . i) ≡ bimap f h . bimap g i
> class Bifunctor f where
> bimap :: (a -> c) -> (b -> d) -> f a b -> f c d
`Profunctor` has the following laws:
* dimap id id ≡ id
Which yields the following free theorem:
* dimap (f . g) (h . i) ≡ dimap g h . dimap f i
> class Profunctor f where
> dimap :: (c -> a) -> (b -> d) -> f a b -> f c d
`Comonad`, the dual of `Moand`, has the following laws:
* extend extract = id
* extract . extend f = f
* extend f . extend g = extend (f . extend g)
> class Functor f => Comomand f where
> extract :: f a -> a
> extend :: (f a -> b) -> f a -> f b
Now the exercises. (Bonus points for all exercises: show that your instance is
law-abiding.)
Exericse 1: Does `Zero` have a `Functor` instance?
instance Functor Zero where
(<$>) :: (a -> b) -> Zero a -> Zero b
f <$> x = _
Exercise 2: Does `Phantom` have a `Functor` instance?
instance Functor Phantom where
(<$>) :: (a -> b) -> Phantom a -> Phantom b
f <$> x = _
Exercise 3: Does `Maybe` have a `Functor` instance?
instance Functor Maybe where
(<$>) :: (a -> b) -> Maybe a -> Maybe b
f <$> x = _
Exercise 4: Does `Id` have a `Functor` instance?
instance Functor Id where
(<$>) :: (a -> b) -> Id a -> Id b
f <$> x = _
Exercise 5: Does `OneAnd` have a `Functor`? If so, under what conditions instance?
instance Functor OneAnd f where
(<$>) :: (a -> b) -> OneAnd f a -> OneAnd f b
f <$> x = _
Exercise 6: Does `Two` have a `Functor` instance?
instance Functor Two where
(<$>) :: (a -> b) -> Two a -> Two b
f <$> x = _
Exercise 7: Does `List` have a `Functor` instance?
instance Functor List where
(<$>) :: (a -> b) -> List a -> List b
f <$> x = _
Exercise 8: Does `NonEmptyL` have a `Functor` instance?
instance Functor NonEmptyL where
(<$>) :: (a -> b) -> NonEmptyL a -> NonEmptyL b
f <$> x = _
Exercise 9: Does `AtLeast2` have a `Functor` instance?
instance Functor AtLeast2 where
(<$>) :: (a -> b) -> AtLeast2 a -> AtLeast2 b
f <$> x = _
Exercise 10: Does `BTree` have a `Functor` instance?
instance Functor BTree where
(<$>) :: (a -> b) -> BTree a -> BTree b
f <$> x = _
Exercise 11: Does `Pair` have a `Functor`? or `Pair z`, rather instance?
instance Functor (Pair z) where
(<$>) :: (a -> b) -> Pair z a -> Pair z b
f <$> x = _
Exercise 12: Hm, what about `Pair`'s other type argument? Doesn't it work
fundamentally the same way? How would this best be expressed?
...
Exercise 13: Does `Either z` have a `Functor` instance?
instance Functor (Either z) where
(<$>) :: (a -> b) -> Either z a -> Either z b
f <$> x = _
Exercise 14: Again, what about `Either`'s other type argument?
...
Exercise 15: Does `AndOr z` have a `Functor` instance?
instance Functor (AndOr z) where
(<$>) :: (a -> b) -> AndOr z a -> AndOr z b
f <$> x = _
Exercise 16: What about `AndOr`'s other type argument?
...
Exercise 17: Does `Cont r` have a `Functor` instance?
instance Functor (Cont r) where
(<$>) :: (a -> b) -> Cont r a -> Cont r b
f <$> x = _
Exercise 18: What about `Cont`'s other type argument? Is the answer similar to
the answer to this question for Exercises 12, 14, and 16, or different?
Exericse 19: Does `Zero` have an `Applicative` instance?
instance Applicative Zero where
pure :: a -> Zero a
pure x = _
(<*>) :: Zero (a -> b) -> Zero a -> Zero b
f <*> x = _
Exercise 20: Does `Phantom` have an `Applicative` instance?
instance Applicative Phantom where
pure :: a -> Phantom a
pure x = _
(<*>) :: Phantom (a -> b) -> Phantom a -> Phantom b
f <*> x = _
Exercise 21: Does `Maybe` have an `Applicative` instance?
instance Applicative Maybe where
pure :: a -> Maybe a
pure x = _
(<*>) :: Maybe (a -> b) -> Maybe a -> Maybe b
f <*> x = _
Exercise 22: Does `Id` have an `Applicative` instance?
instance Applicative Id where
pure :: a -> Id a
pure x = _
(<*>) :: Id (a -> b) -> Id a -> Id b
f <*> x = _
Exercise 23: Does `OneAnd` have an `Applicative`? If so, under what conditions instance?
instance Applicative OneAnd where
pure :: a -> OneAnd a
pure x = _
(<*>) :: OneAnd (a -> b) -> OneAnd a -> OneAnd b
f <*> x = _
Exercise 24: Does `Two` have an `Applicative` instance?
instance Applicative Two where
pure :: a -> Two a
pure x = _
(<*>) :: Two (a -> b) -> Two a -> Two b
f <*> x = _
Exercise 25: Does `List` have an `Applicative` instance?
instance Applicative List where
pure :: a -> List a
pure x = _
(<*>) :: List (a -> b) -> List a -> List b
f <*> x = _
Exercise 26: Does `NonEmptyL` have an `Applicative` instance?
instance Applicative NonEmptyL where
pure :: a -> NonEmptyL a
pure x = _
(<*>) :: NonEmptyL (a -> b) -> NonEmptyL a -> NonEmptyL b
f <*> x = _
Exercise 27: Does `AtLeast2` have an `Applicative` instance?
instance Applicative AtLeast2 where
pure :: a -> AtLeast2 a
pure x = _
(<*>) :: AtLeast2 (a -> b) -> AtLeast2 a -> AtLeast2 b
f <*> x = _
Exercise 28: Does `BTree` have an `Applicative` instance?
instance Applicative BTree where
pure :: a -> BTree a
pure x = _
(<*>) :: BTree (a -> b) -> BTree a -> BTree b
f <*> x = _
Exercise 29: Does `Pair z` have an `Applicative` instance? How does the answer to this compare
with the answer for `Two`, which is essentially a specialized pair?
instance Applicative (Pair z) where
pure :: a -> Pair z a
pure x = _
(<*>) :: Pair z (a -> b) -> Pair z a -> Pair z b
f <*> x = _
Exercise 30: Does `Either z` have an `Applicative` instance?
instance Applicative (Either z) where
pure :: a -> Either z a
pure x = _
(<*>) :: Either z (a -> b) -> Either z a -> Either z b
f <*> x = _
Exercise 31: Does `AndOr z` have an `Applicative` instance?
instance Applicative (AndOr z) where
pure :: a -> AndOr z a
pure x = _
(<*>) :: AndOr z (a -> b) -> AndOr z a -> AndOr z b
f <*> x = _
Exercise 32: Does `Cont r` have an `Applicative` instance?
instance Applicative (Cont r) where
pure :: a -> Cont r a
pure x = _
(<*>) :: Cont r (a -> b) -> Cont r a -> Cont r b
f <*> x = _
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment