Last active
February 21, 2016 17:56
-
-
Save remydagostino/5a3e46a79094a6b4b4e2 to your computer and use it in GitHub Desktop.
Getting the hang of haskell typeclasses
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE MultiParamTypeClasses #-} | |
{-# LANGUAGE FlexibleInstances #-} | |
module Main where | |
import Data.Monoid (Monoid, mempty, mappend, mconcat) | |
------------------------------ | |
-- Part 1: Make a silly monoid instance for Int | |
{- | |
We also need to wrap up strings with a newtype that we will | |
be using later. This is the easiest way to make sure our string | |
instances don't conflict with list instances. | |
-} | |
instance Monoid Int where | |
mempty = 0 | |
mappend = (+) | |
newtype ShoutyStr = ShoutyStr String | |
instance Show ShoutyStr where | |
show (ShoutyStr str) = show str | |
instance Action Int ShoutyStr where | |
act n (ShoutyStr s) = ShoutyStr $ s ++ (replicate n '!') | |
------------------------------ | |
-- Part 2: Our Action typeclass | |
{- | |
`act` is a function that takes a monoid and a thing and produces a thing of the | |
same type. It might be a different for each different combination of monoids and | |
kind of thing but the laws guarentee that the thing that pops out the other end | |
will have to depend largely on the monoid. This rules out many possible | |
implementations that would ignore the monoid and just operate on the thing. | |
``` | |
instance Action Int String where | |
act _ thing = thing ++ '!' | |
``` | |
While this would satisfy the first law... | |
``` | |
act (append 2 mempty) "Hello" ≡ "Hello" ≡ act 2 "Hello" | |
``` | |
... the second law is left wanting! | |
``` | |
act 2 (act 3 "Hello") ≡ "Hello!!" ≢ act (append 2 3) "Hello" | |
``` | |
-} | |
-- Action class laws | |
-- 1. act (append m mempty) a == act m a | |
-- 2. act m2 (act m1 a) == act (append m1 m2) a | |
class (Monoid m) => Action m a where | |
act :: m -> a -> a | |
------------------------------ | |
-- Part 3: A proper instance for Int String | |
{- | |
It turns out this second law is a bit tricky, even when we try to use the | |
provided monoid. | |
This implementation tries to repeat the string a number of times equal to the | |
provided number: | |
``` | |
instance Action Int String where | |
act n s = mconcat $ take n (repeat s) | |
act 1 (act 0 "Hello") ≡ "" | |
act (mappend 1 0) "Hello" ≡ "Hello" | |
``` | |
So we learn that the behavior of `act` is must be defined solely by the behavior | |
of the monoid instance. We can deduce that, the result of running `act` on | |
something has to pass it through in the case of `mempty`. If `act` is going to | |
modify the value of the provided thing, then it needs to do it in a way that is | |
consistent with the way the monoid is concatenated. Another way to put this is | |
that the work that `act` does needs to be able to be divided into multiple calls | |
to `act` with each call doing an amount of work equal to the biggness of the | |
provided monoid. | |
``` | |
instance Action Int String where | |
act n s = s ++ (replicate n '!') | |
``` | |
-} | |
test3 = do | |
print $ act (5 :: Int) (ShoutyStr "Hello") | |
print $ act (mappend (5 :: Int) mempty) (ShoutyStr "Hello") | |
print $ act (1 :: Int) (act (0 :: Int) (ShoutyStr "Hello")) | |
print $ act (mappend (1 :: Int) (0 :: Int)) (ShoutyStr "Hello") | |
print $ act (2 :: Int) (act (3 :: Int) (ShoutyStr "Hello")) | |
print $ act (mappend (2 :: Int) (3 :: Int)) (ShoutyStr "Hello") | |
------------------------------ | |
-- Part 4: Going Deeper | |
{- | |
It is possible to make an instance of our action class which applies a | |
constraint onlyto the right-hand side of the typeclass! | |
This reads: We have an instance of the Action class for any Monoid and any Maybe | |
of an X as long as there is already an Action instance for the that Monoid and | |
an X. | |
I think it's mindblowing to think we could have a whole tonne of action | |
instances defined and then we drop these two lines and suddenly all of our | |
existing instances now work on Maybe types as well! | |
It's like we had all these instances | |
``` | |
Action Int String | |
Action (List String) Int | |
Action String Vector | |
``` | |
And now we have all of these too! | |
``` | |
Action Int (Maybe String) | |
Action (List String) (Maybe Int) | |
Action String (Maybe Vector) | |
``` | |
The kind of crazy thing is that this recurses infinitely too, so we also have | |
all of these! | |
``` | |
Action Int (Maybe (Maybe String)) | |
Action Int (Maybe (Maybe (Maybe String))) | |
``` | |
Wild! | |
-} | |
--instance (Monoid m, Action m a) => Action m (Maybe a) where | |
-- act m ma = fmap (act m) ma | |
test4 = do | |
print $ act (5 :: Int) (Just (ShoutyStr "Hello")) | |
print $ act (5 :: Int) (Just (Just (ShoutyStr "Hello"))) | |
print $ act (5 :: Int) (Nothing :: Maybe ShoutyStr) | |
-- Part 2: Define a list type | |
------------------------------ | |
-- Part 5: Let's do it again | |
{- | |
That thing with the Maybe type was a lot of fun, let's do it again! | |
Let's make an instance for Action which provides new Action instances for lists. | |
-} | |
--instance (Monoid m, Action m a) => Action m (ActionList a) where | |
-- act m xs = fmap (act m) xs | |
test5 = do | |
print $ act (5 :: Int) [ShoutyStr "Hello", ShoutyStr "World"] | |
print $ act (5 :: Int) [Just (ShoutyStr "Hello"), Just (ShoutyStr "World"), Nothing] | |
------------------------------ | |
-- Part 6: Typeclass Magic | |
{- | |
Oh gosh. Are you seeing what I'm seeing? Our implementation for Action over | |
lists and Maybes are identical. We could generalize even further! | |
-} | |
instance (Monoid m, Action m a, Functor f) => Action m (f a) where | |
act m xs = fmap (act m) xs |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment