Created
November 3, 2020 16:57
-
-
Save bkyrlach/c08a1891cd36277b26f36e1910504f64 to your computer and use it in GitHub Desktop.
This file contains 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
module Traverse where | |
import Prelude hiding (Monad, Functor, Either, Left, Right, map, traverse, pure) | |
-- So, you probably already have a natural intuition for | |
-- the fact that types are similar to the idea of sets | |
-- from mathematics. | |
-- So, lets imagine all of the sets (types) we can describe | |
-- in Haskell. We understand how to work with the inhabitants | |
-- of these sets (values of these types). We can write | |
-- functions, and do all sorts of computations. Here's a | |
-- trivial example. | |
x :: Int | |
x = 3 | |
inc :: Int -> Int | |
inc a = a + 1 | |
y :: Int | |
y = inc x | |
-- All of the above should be really straightfoward. Now, lets | |
-- introduce a twist. Now say we want to talk about lists of | |
-- values. | |
xs :: [Int] | |
xs = [1..5] | |
-- So far so good, right? I actually skipped over something | |
-- there, but for now, we'll move on to a hopefully compelling | |
-- example. What if I want to use my function `inc` on my | |
-- list of Int values? | |
-- inc xs | |
-- The above statement obviously doesn't compile. Now, because | |
-- you've been programming for awhile, you probably already | |
-- know what the answer is. Or, at least, you might assume that | |
-- what I really want to do is to increment each value in my `xs` | |
-- list. | |
-- However, I want you to think a little more broadly. The function | |
-- you probably wanted to reach for `map`, actually does something | |
-- profound. It takes a function designed for our 'Haskell' | |
-- universe, and enables it to work on values inside the 'List` | |
-- universe. (An astute reader might notice that 'List` is part of | |
-- the Haskell universe, a point we'll return to later). | |
-- As with all things Haskell, there's a broader mathematical | |
-- concept at play here, which relates to the idea of | |
-- Category Theory. | |
-- Category theory is all about composition and re-use. I | |
-- should, as always, caveat that with, this is a basic | |
-- and flawed explanation, but it should help put you on | |
-- the path to understanding. :) | |
-- So, a category is a construct that contains two kinds of | |
-- things, and some laws that govern those things. The two | |
-- things that comprise any category are... | |
-- Objects | |
-- Arrows (which are relationships between objects) | |
-- And the rules are... | |
-- Each object must have an identity arrow (an arrow from | |
-- that object to itself). | |
-- Arrows must be able to compose in the natural way. That | |
-- is to say, if I have objects `a`, `b`, and `c`, and an | |
-- arrow from `a` to `b` (we'll call that arrow `f`), and | |
-- another arrow from `b` to `c` (we'll call that arrow | |
-- `g`), that it is possible to compose `f` and `g` such | |
-- that I get a new arrow (we'll call that new arrow `h`) | |
-- that goes from `a` to `c`. | |
-- That's a lot to take in, but we're close to some practical | |
-- examples. | |
-- First, we talked about the `Haskell` universe. Is the | |
-- `Haskell` universe a category? Lets try and see if we can | |
-- make such a category. | |
-- Parts... | |
-- Object -> Haskell Type (not a value, but a type) | |
-- Arrow -> Haskell Function (relationship between types) | |
-- Laws... | |
-- ID -> id :: a -> a | |
-- compose -> `.` :: (b -> c) -> (a -> b) -> (a -> c) | |
-- So, with the above, we can see that our `Haskell` | |
-- universe is a category! We're getting closer, but we're | |
-- not done yet! | |
-- Next, is `List` a category? | |
-- Parts... | |
-- Object -> [a] | |
-- Arrow -> All functions of the shape [a] -> [b] | |
-- Laws... | |
-- ID -> id :: [a] -> [a] | |
-- compose -> `lc` :: ([b] -> [c]) -> ([a] -> [b]) -> ([a] -> [c]) | |
-- So far this checks out, but what does this have to do with | |
-- `map`? Well, we talked about how `map` takes a function | |
-- from the `Haskell` universe and makes it work in the `List` | |
-- universe. Turns out that we've discovered a new part of | |
-- category theory! | |
-- Part of category theory deals with the relationship between | |
-- categories (universes). The mathematical term for this | |
-- relationship is `Functor`. A `Functor` between two categories | |
-- `A` and `B` is like a portal between universes. A valid | |
-- `Functor` has to have two key components. | |
-- A mapping for the objects of the source category to the | |
-- destination category. | |
-- A mapping for the arrows of the source category to the | |
-- destination category. | |
-- If that second item sounded a lot like `map`, that's because | |
-- it is! But, before we go there, why don't we just see what | |
-- a Haskell description of this idea looks like. | |
class Functor f where | |
map :: f a -> (a -> b) -> f b | |
pure :: a -> f a | |
-- From the type signatures, we can see how this describes | |
-- exactly the mathematical concept we just discussed. Lets | |
-- see what an instance of this looks like for our `list` | |
-- category. | |
instance Functor [] where | |
map [] _ = [] | |
map (x:xs) f = (f x):(map xs f) | |
pure a = [a] | |
-- Basically, `Functor` describes what it means to map between | |
-- universes (categories). Even if the destination universe has | |
-- crazy gravity, or different physics, it preserves the meaning | |
-- of the stuff we bring in from our universe. We can even try | |
-- it out! | |
-- Here are some values from our universe wandering around the | |
-- `List` universe. | |
myList :: [Int] | |
myList = [1..5] | |
-- Remember that 'inc' function from before? We can just use | |
-- it in our new universe, thanks to our portal (functor). | |
changedList :: [Int] | |
changedList = map myList inc | |
-- In the case of list, the new universe is pretty familiar to | |
-- us. The only "new" thing is that each inhabitant (value) of | |
-- each set (type) is really zero or more things. To make sure | |
-- this is clear, think of these two definitions. | |
-- Int in our universe. | |
universeInt :: Int | |
universeInt = 3 | |
-- Int in `List` universe. | |
listInt :: [Int] | |
listInt = [] -- Note that there's no Int here at all! | |
-- That is, of course, just one possible value of 'listInt'. It | |
-- could also just as easily have been... | |
-- listInt = [1..5] | |
-- listInt = [1..] | |
-- listInt = [1..1000000] | |
-- See how that differs from `Int` in our normal universe? So, the | |
-- `Functor` idea allows me to take stuff from my normal universe | |
-- and use it in a new universe. Don't worry, I haven't forgotten | |
-- about traverse, but we have a few more concepts to go over before | |
-- we get there. | |
-- Just to show you how powerful this universe concept is, lets | |
-- imagine a new universe. `Haskell` doesn't have a concept of | |
-- `null`, right? But sometimes we might want to think about a | |
-- universe where sometimes a value doesn't exist. So, first, lets | |
-- define that universe. | |
data Optional a = | |
Some a | |
| None | |
deriving (Show,Eq) | |
-- Much like the `List` universe, our new `Optional` universe has | |
-- a new, interesting rule that doesn't exist in our `Haskell` universe. | |
-- Now we just need to open a portal... | |
instance Functor Optional where | |
map None _ = None | |
map (Some a) f = Some $ f a | |
pure a = Some a | |
-- Something important here that I didn't point out last time. It's | |
-- the job of the portal to make sure that the mapping is correct. | |
-- So, as you can see above, the portal (functor) has to make a decision | |
-- about how functions from our `Haskell` universe should operate in | |
-- the new universe. Specifically, our `Haskell` universe doesn't have the | |
-- concept of a missing value (no null). That means functions from our | |
-- universe don't work in the new universe in all cases. | |
-- In the above code, the functor makes the decision that, if there wasn't | |
-- a value to go into the function from our universe, we'll just say that | |
-- we don't get a value out of the function from our universe. | |
-- With that, we can now use 'inc' in this new universe too! | |
presentInt :: Optional Int | |
presentInt = Some 3 | |
nowIncremented :: Optional Int | |
nowIncremented = map presentInt inc | |
absentInt :: Optional Int | |
absentInt = None | |
nowIncremented' :: Optional Int | |
nowIncremented' = map absentInt inc | |
-- We're nearing the home stretch here, but we have to talk about one | |
-- more thing. Our category theory laws state that arrows in our category | |
-- must compose, and all of our categories we've defined so far satisfy | |
-- that law. But we're missing one important compositional tool. | |
-- Imagine we wanted to use our new universe to help us define a useful | |
-- function that will safely divide integer values by two. What I mean | |
-- by "safely" here, is that we want our function to return an integer | |
-- value, and you can't represent the result of dividing an odd number by | |
-- two with an integer correctly. | |
-- So, because we now have a way to represent the absence of a value, we'll | |
-- define our new function to return the integer result of the division by | |
-- two for even numbers, and return the absence of a value when asked to | |
-- divide an odd number. | |
safeDivideByTwo :: Int -> Optional Int | |
safeDivideByTwo n = if ((rem n 2) == 0) then (Some $ quot n 2) else None | |
-- This function is obviously kind of silly, but hopefully simple enough | |
-- to make understanding the following a little easier. So, we can | |
-- easily use this function, but we have an issue. To demonstrate this | |
-- issue, lets see what this function looks like in our normal universe. | |
divideByTwo :: Int -> Int | |
divideByTwo n = if ((rem n 2) == 0) then (quot n 2) else -9999999 | |
-- Note the sentinel value above of -9999999. This illustrates how our | |
-- new universe is helping us, but what about the problem I mentioned. | |
-- Well, for our Haskell universe function, we can easily compose it. | |
divideByFour :: Int -> Int | |
divideByFour = divideByTwo . divideByTwo | |
-- But, as stated above, this function is problematic. Why don't we | |
-- instead compose our new "safe" function? | |
-- safeDivideByFour :: Int -> MaybeInt | |
-- safeDivideByFour = safeDivideByTwo . safeDivideByTwo | |
-- As you might have guessed due to the fact that it's commented | |
-- out, the above code doesn't compile. If we look at the inputs and | |
-- outputs of 'safeDivideByTwo', we can easily see why. The function | |
-- accepts an 'Int' as an input, and returns an 'Optional Int' as an | |
-- output. Obviously we can't feed an 'Optional Int` into the function. | |
-- Thankfully, category theory has the solution for this as well. | |
-- Enter the 'monad'. Now, this is a word that causes a lot of | |
-- consternation amongst functional programming neophytes, but don't | |
-- let that deter you. I'm not even going to try and tell you what | |
-- "it" is. Instead, I'm just going to show you what it does. | |
class Monad m where | |
bind :: m a -> (a -> m b) -> m b | |
-- For the astute Haskeller, you might note that we put 'pure' on | |
-- 'Functor' above, whereas in the stdlib, 'pure' goes here. This | |
-- is merely for teaching sake. :) | |
-- If you compare the above to our definition of 'map' for 'Functor' | |
-- you might notice a startling similarity. (Here's 'map' again | |
-- for reference). | |
-- map :: (Functor f) => f a -> (a -> b) -> f b | |
-- But, what should be more interesting is that the signature of | |
-- 'bind' here is exactly the thing we were trying to do with our | |
-- 'safeDivideByTwo' before. | |
-- So, first, obviously, we need to define 'Monad' for our | |
-- 'Optional' universe. | |
instance Monad Optional where | |
bind None _ = None | |
bind (Some a) f = f a | |
-- And now we can define 'safeDivideByFour' using this new | |
-- operation! | |
safeDivideByFour :: Int -> Optional Int | |
safeDivideByFour n = bind (safeDivideByTwo n) safeDivideByTwo | |
-- While this isn't exactly as elegant as '.' in our Haskell | |
-- universe, this does enable us to get our desired result. | |
-- Now, at last, we can finally get to traverse. | |
-- Honestly, you might be able to understand 'traverse' from | |
-- the signature, now that you understand 'monad' and | |
-- 'functor'. | |
traverse :: (Monad m, Functor m) => [a] -> (a -> m b) -> m [b] | |
traverse [] _ = pure [] | |
traverse (x:xs) f = bind (f x) (\y -> map (traverse xs f) (\ys -> y:ys)) | |
-- Lets see it in action! | |
evenInts :: [Int] | |
evenInts = [2,4..10] | |
divByTwo :: Optional [Int] | |
divByTwo = traverse evenInts safeDivideByTwo | |
-- If this helps, maybe it's useful to think of our 'Functor' portal | |
-- a little bit like time travel. When you use it to hop universes, you | |
-- are really creating a divergent timeline. We can see that in action | |
-- if we try to use map instead of traverse. | |
-- divByTwo :: [Optional Int] | |
-- divByTwo = map evenInts safeDivideByTwo | |
-- In this version, each of our `Int` values is in its own divergent | |
-- timeline. If one of those `Int` values failed to safely divide, we'd | |
-- still get back a List. Some of the values would be absent, and some | |
-- would be present. Now, this is useful for some applications! | |
-- However, there are also times where we want continuity. If, instead of | |
-- 'safeDivideByTwo' this was 'depositMoney', and the absence of a value | |
-- indicated a failed transaction. We might expect or want the whole | |
-- transaction to fail if any part of it failed. | |
-- In this analogy, 'traverse' is like 'map', but it instead will keep | |
-- the timelines from diverging. This might be more easily evident if | |
-- we used a more down to earth example, so here... | |
-- First, we'll introduce a new universe. In this universe, all values | |
-- are either a useful computational value, or a value that indicates | |
-- an incomplete computation. | |
data Either l r = | |
Right r | |
| Left l | |
deriving (Show, Eq) | |
-- We'll need our portal, of course. | |
instance Functor (Either l) where | |
map (Left lv) _ = Left lv | |
map (Right rv) f = Right $ f rv | |
pure rv = Right rv | |
-- And we might as well 'monad' it up | |
instance Monad (Either l) where | |
bind (Left lv) _ = Left lv | |
bind (Right rv) f = f rv | |
-- setting power over 5 or below 0 will cause the next | |
-- power setting to fry the circuit | |
setPower :: Int -> Either String Int | |
setPower plevel = if (0 <= plevel && plevel <= 5) then Right plevel else Left "Danger!" | |
-- Using traverse, our function will "automagically" stop | |
-- sending power commands after the first "out of bounds" setting | |
powerInputs :: [Int] | |
powerInputs = [1,2,3,10,5,-4] | |
powerResults = traverse powerInputs setPower | |
-- Compare this to using map | |
powerResults' = map powerInputs setPower | |
-- *Traverse> :load Traverse | |
-- [1 of 1] Compiling Traverse ( Traverse.hs, interpreted ) | |
-- Ok, one module loaded. | |
-- *Traverse> powerResults | |
-- Left "Danger!" | |
-- *Traverse> powerResults' | |
-- [Right 1,Right 2,Right 3,Left "Danger!",Right 5,Left "Danger!"] | |
-- In the first example, we get back the first "Danger!" that is | |
-- computed, saving our circuit (no further calls to set power occur). | |
-- In the second example, we see that we have in fact called 'setPower' | |
-- after getting a "Danger!", thereby ensuring our circuit is destroyed. |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment