Generalizing Dijkstra's Algorithm
Earlier this week, I wrote a simplified implementation of Dijkstra’s algorithm. You can read the article for details or just look at the full code implementation here on GitHub. This implementation is fine to use within a particular project for a particular purpose, but it doesn’t generalize very well. Today we’ll explore how to make this idea more general.
I chose to do this without looking at any existing implementations of Dijkstra’s algorithm in Haskell libraries to see how my approach would be different. So at the end of this series I’ll also spend some time comparing my approach to some other ideas that exist in the Haskell world.
Parameterizing the Graph Type
So why doesn’t this approach generalize? Well, for the obvious reason that my module defines a specific type for the graph:
data Graph = Graph
{ graphEdges :: HashMap String [(String, Int)] }
So, for someone else to re-use this code from the perspective of a different project, they would have to take whatever graph information they had, and turn it into this specific type. And their data might not map very well into String
values for the nodes, and they might also have a different cost type in mind than the simple Int
value, with Double
being the most obvious example.
So we could parameterize the graph type and allow more customization of the underlying values.
data Graph node cost = Graph
{ graphEdges :: HashMap node [(node, cost)] }
The function signature would have to change to reflect this, and we would have to impose some additional constraints on these types:
findShortestDistance :: (Hashable node, Eq node, Num cost, Ord cost) =>
Graph node cost -> node -> node -> Distance cost
Graph Enumeration
But this would still leave us with an important problem. Sometimes you don’t want to have to enumerate the whole graph. As is, the expression you submit as the "graph" to the function must have every edge enumerated, or it won’t give you the right answer. But many times, you won’t want to list every edge because they are so numerous. Rather, you want to be able to list every edge simply from a particular node. For example:
edgesForNode :: Graph node cost -> node -> [(node, cost)]
How can we capture this behavior more generally in Haskell?
Using a Typeclass
Well one of the tools we typically turn to for this task is a typeclass. We might want to define something like this:
class DijkstraGraph graph where
dijkstraEdges :: graph node cost -> node -> [(node, cost)]
However, it quickly gets a bit strange to try to do this with a simple typeclass because of the node
and cost
parameters. It’s difficult to resolve the constraints we end up needing because these parameters aren’t really part of our class.
Using a Multi-Param Typeclass
We could instead try having a multi-param typeclass like this:
{-# LANGUAGE MultiParamTypeClasses #-}
class DijkstraGraph graph node cost where
dijkstraEdges :: graph -> node -> [(node, cost)]
This actually works more smoothly than the previous try. We can construct an instance (if we allow flexible instances).
{-# LANGUAGE FlexibleInstances #-}
import qualified Data.HashMap as HM
import Data.Maybe (fromMaybe)
instance DijkstraGraph (Graph String Int) String Int where
dijkstraEdges g n = fromMaybe [] (HM.lookup n (edges g))
And we can actually use this class in our function now! It mainly requires changing around a few of our type signatures. We can start with our DijkstraState
type, which must now be parameterized by the node
and cost
:
data DijkstraState node cost = DijkstraState
{ visitedSet :: HashSet node
, distanceMap :: HashMap node (Distance cost)
, nodeQueue :: MinPrioHeap (Distance cost) node
}
And, of course, we would also like to generalize the type signature of our findShortestDistance
function. In its simplest form, we would like use this:
findShortestDistance :: graph -> node -> node -> Distance cost
However, a couple extra items are necessary to make this work. First, as above, our function is the correct place to assign constraints to the node
and cost
types. The node type must fit into our hashing structures, so it should fulfill Eq
and Hashable
. The cost type must be Ord
and Num
in order for us to perform our addition operations and use it for the heap. And last of course, we have to add the constraint regarding the DijkstraGraph
itself:
findShortestDistance ::
(Hashable node, Eq node, Num cost, Ord cost, DijkstraGraph graph) =>
graph -> node -> node -> Distance cost
Now, if we want to use the graph
, node
, and cost
types within the “inner” type signatures of our function, we need one more thing. We need a forall
specifier on the function so that the compiler knows we are referring to the same types.
{-# LANGUAGE ScopedTypeVariables #-}
findShortestDistance :: forall graph node cost.
(Hashable node, Eq node, Num cost, Ord cost, DijkstraGraph graph) =>
graph -> node -> node -> Distance cost
We can now make one change to our function so that it works with our class.
processQueue :: DijkstraState node cost -> HashMap node (Distance cost)
processQueue = ...
-- Previously
-- allNeighbors = fromMaybe [] (HM.lookup node (edges graph))
-- Updated
allNeighbors = dijkstraEdges graph node
And now we’re done! We can again, verify the behavior. However, we do run into some difficulties in that we need some extra type specifiers to help the compiler figure everything out.
graph1 :: Graph String Int
graph1 = Graph $ HM.fromList
[ ("A", [("D", 100), ("B", 1), ("C", 20)])
, ("B", [("D", 50)])
, ("C", [("D", 20)])
, ("D", [])
]
...
>> :set -XFlexibleContexts
>> findShortestDistance graph1 :: Distance Int
Dist 40
Conclusion
Below in the appendix is the full code for this part. You can also take a look at it on Github here.
For various reasons, I don’t love this attempt at generalizing. I especially don't like the "re-statement" of the parameter types in the instance. The parameters are part of the Graph
type and are separately parameters of the class. This is what leads to the necessity of specifying the Distance Int
type in the GHCI session above. We could avoid this if we don't parameterize our Graph
type, which is definitely an option.
In the next part of this series, we'll make a second attempt at generalizing this algorithm!
Appendix
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Dijkstra2 where
import Data.Hashable (Hashable)
import qualified Data.Heap as H
import Data.Heap (MinPrioHeap)
import qualified Data.HashSet as HS
import Data.HashSet (HashSet)
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HM
import Data.Maybe (fromMaybe)
data Distance a = Dist a | Infinity
deriving (Show, Eq)
instance (Ord a) => Ord (Distance a) where
Infinity <= Infinity = True
Infinity <= Dist x = False
Dist x <= Infinity = True
Dist x <= Dist y = x <= y
addDist :: (Num a) => Distance a -> Distance a -> Distance a
addDist (Dist x) (Dist y) = Dist (x + y)
addDist _ _ = Infinity
(!??) :: (Hashable k, Eq k) => HashMap k (Distance d) -> k -> Distance d
(!??) distanceMap key = fromMaybe Infinity (HM.lookup key distanceMap)
newtype Graph node cost = Graph
{ edges :: HashMap node [(node, cost)] }
class DijkstraGraph graph node cost where
dijkstraEdges :: graph -> node -> [(node, cost)]
instance DijkstraGraph (Graph String Int) String Int where
dijkstraEdges g n = fromMaybe [] (HM.lookup n (edges g))
data DijkstraState node cost = DijkstraState
{ visitedSet :: HashSet node
, distanceMap :: HashMap node (Distance cost)
, nodeQueue :: MinPrioHeap (Distance cost) node
}
findShortestDistance :: forall graph node cost. (Hashable node, Eq node, Num cost, Ord cost, DijkstraGraph graph node cost) => graph -> node -> node -> Distance cost
findShortestDistance graph src dest = processQueue initialState !?? dest
where
initialVisited = HS.empty
initialDistances = HM.singleton src (Dist 0)
initialQueue = H.fromList [(Dist 0, src)]
initialState = DijkstraState initialVisited initialDistances initialQueue
processQueue :: DijkstraState node cost -> HashMap node (Distance cost)
processQueue ds@(DijkstraState v0 d0 q0) = case H.view q0 of
Nothing -> d0
Just ((minDist, node), q1) -> if node == dest then d0
else if HS.member node v0 then processQueue (ds {nodeQueue = q1})
else
-- Update the visited set
let v1 = HS.insert node v0
-- Get all unvisited neighbors of our current node
allNeighbors = dijkstraEdges graph node
unvisitedNeighbors = filter (\(n, _) -> not (HS.member n v1)) allNeighbors
-- Fold each neighbor and recursively process the queue
in processQueue $ foldl (foldNeighbor node) (DijkstraState v1 d0 q1) unvisitedNeighbors
foldNeighbor current ds@(DijkstraState v1 d0 q1) (neighborNode, cost) =
let altDistance = addDist (d0 !?? current) (Dist cost)
in if altDistance < d0 !?? neighborNode
then DijkstraState v1 (HM.insert neighborNode altDistance d0) (H.insert (altDistance, neighborNode) q1)
else ds
graph1 :: Graph String Int
graph1 = Graph $ HM.fromList
[ ("A", [("D", 100), ("B", 1), ("C", 20)])
, ("B", [("D", 50)])
, ("C", [("D", 20)])
, ("D", [])
]
Dijkstra's Algorithm in Haskell
In some of my recent streaming sessions (some of which you can see on my YouTube chanel), I spent some time playing around with Dijkstra’s algorithm. I wrote my own version of it in Haskell, tried to generalize it to work in different settings, and then used it in some examples. So for the next couple weeks I’ll be writing about those results. Today I’ll start though with a quick overview of a basic Haskell approach to the problem.
Note: This article will follow the “In Depth” reading style I talked about last week. I’ll be including all the details of my code, so if you want to follow along with this article, everything should compile and work! I’ll list dependencies, imports, and the complete code in an appendix at the end.
Pseudocode
Before we can understand how to write this algorithm in Haskell specifically, we need to take a quick look at the pseudo code. This is adapted from the Wikipedia description
function Dijkstra(Graph, source):
for each vertex v in Graph.Vertices:
dist[v] <- INFINITY
add v to Q
dist[source] <- 0
while Q is not empty:
u <- vertex in Q with min dist[u]
remove u from Q
for each neighbor v of u still in Q:
alt <- dist[u] + Graph.Edges(u, v)
if alt < dist[v] and dist[u] is not INFINITY:
dist[v] <- alt
return dist[]
There are a few noteworthy items here. This code references two main structures. We have dist
, the mapping of nodes to distances. There is also Q
, which has a special operation “vertex in Q
with min dist[u]
”. It also has the operation “still in Q
”. We can actually separate this into two items. We can have one structure to track the minimum distance to nodes, and then we have a second to track which ones are “visited”.
With this in mind, we can break the "Dijkstra Process" into 5 distinct steps.
- Define our type signature
- Initialize a structure with the different items (
Q
,dist
, etc.) in their initial states - Write a loop for processing each element from the queue.
- Write an inner loop for processing each “neighbor” we encounter of the items pulled from the queue.
- Get our answer from the final structure.
These steps will help us organize our code. Before we dive into the algorithm itself though, we’ll want a few helpers!
Helpers
There are a few specific items that aren’t really part of the algorithm, but they’ll make things a lot smoother for us. First, we’re going to define a new “Distance” type. This will include a general numeric type for the distance but also include an “Infinity” constructor, which will help us represent the idea of an unreachable value.
data Distance a = Dist a | Infinity
deriving (Show, Eq)
We want to ensure this type has a reasonable ordering, and that we can add values with it in a sensible way. If we rely on a simple integer type maxBound
, we’ll end up with arithmetic overflow problems.
instance (Ord a) => Ord (Distance a) where
Infinity <= Infinity = True
Infinity <= Dist x = False
Dist x <= Infinity = True
Dist x <= Dist y = x <= y
addDist :: (Num a) => Distance a -> Distance a -> Distance a
addDist (Dist x) (Dist y) = Dist (x + y)
addDist _ _ = Infinity
Now we’ll be tracking our distances with a Hash Map. So as an extra convenience, we’ll add an operator that will look up a particular item in our map, returning its distance if that exists, but otherwise returning “Infinity” if it does not.
(!??) :: (Hashable k, Eq k) => HashMap k (Distance d) -> k -> Distance d
(!??) distanceMap key = fromMaybe Infinity (HM.lookup key distanceMap)
Type Signature
Now we move on to the next step in our process: defining a type signature. To start, we need to ask, "what kind of graph are we working with?" We’ll generalize this in the future, but for now let’s assume we are defining our graph entirely as a map of “Nodes” (represented by string names) to “Edges”, which are tuples of names and costs for the distance.
newtype Graph = Graph
{ edges :: HashMap String [(String, Int)] }
Our dijkstra function will take such a graph, a starting point (the source), and an ending point (the destination) as its parameters. It will return the “Distance” from the start to the end (which could be infinite). For now, we’ll exclude returning the full path, but we’ll get to that by the end of the series.
findShortestDistance :: Graph -> String -> String -> Distance Int
With our graph defined more clearly now, we’ll want to define one more “stateful” type to use within our algorithm. From reading the pseudo code, we want this to contain three structures that vary with each iteration.
- A set of nodes we’ve visited.
- The distance map, from nodes to their “current” distance values
- A queue allowing us to find the “unvisited node with the smallest current distance”.
For the first two items, it's straightforward to see what types we use. A HashSet
of strings will suffice for the visited set, and likewise a HashMap
will help us track distances. For the queue, we need to be a little clever, but a priority heap using the distance and the node will be most helpful.
data DijkstraState = DijkstraState
{ visitedSet :: HashSet String
, distanceMap :: HashMap String (Distance Int)
, nodeQueue :: MinPrioHeap (Distance Int) String
}
Initializing Values
Now for step 2, let’s build our initial state, taking the form of the DijkstraState
type we defined above. Initially, we will consider that there are no visited nodes. Then we’ll define that the only distance we have is a distance of “0” to the source node. We’ll also want to store this pair in the queue, so that the source is the first node we pull out of our queue.
findShortestDistance :: Graph -> String -> String -> Distance Int
findShortestDistance graph src dest = ...
where
initialVisited = HS.empty
initialDistances = HM.singleton src (Dist 0)
initialQueue = H.fromList [(Dist 0, src)]
initialState = DijkstraState initialVisited initialDistances initialQueue
...
Processing the Queue
Now we’ll write a looping function that will process the elements in our queue. This function will return for us the mapping of nodes to distances. It will take the current DijkstraState
as its input. Remember that the most basic method we have of looping in Haskell, particularly when it comes to a “while” loop, is a recursive function.
Every recursive function needs at least one base case. So let’s start with one of those. If the queue is empty, we can return the map as it is.
findShortestDistance graph src dest = ...
where
...
processQueue :: DijkstraState -> HashMap String (Distance Int)
processQueue ds@(DijkstraState v0 d0 q0) = case H.view q0 of
Nothing -> d0
...
Next there are cases of the queue containing at least one element. Suppose this element is our destination. We can also return the distance map immediately here, as it will already contain the distance to that point.
findShortestDistance graph src dest = ...
where
...
processQueue :: DijkstraState -> HashMap String (Distance Int)
processQueue ds@(DijkstraState v0 d0 q0) = case H.view q0 of
Nothing -> d0
Just ((minDist, node), q1) -> if node == dest then d0
else ...
One last base case: if the node is already visited, then we can immediately recurse, except plugging in the new queue q1
for the old queue.
findShortestDistance graph src dest = ...
where
...
processQueue :: DijkstraState -> HashMap String (Distance Int)
processQueue ds@(DijkstraState v0 d0 q0) = case H.view q0 of
Nothing -> d0
Just ((minDist, node), q1) -> if node == dest then d0
else if HS.member node v0 then processQueue (ds {nodeQueue = q1})
else ...
Now, on to the recursive case. In this case we will do 3 things.
- Pull a new node from our heap and consider that node “visited”
- Get all the “neighbors” of this node
- Process each neighbor and update its distance
Most of the work in step 3 will happen in our “inner loop”. The basics for the first two steps are quite easy.
findShortestDistance graph src dest = ...
where
...
processQueue :: DijkstraState -> HashMap String (Distance Int)
processQueue ds@(DijkstraState v0 d0 q0) = case H.view q0 of
Nothing -> d0
Just ((minDist, node), q1) -> if node == dest then d0
else if HS.member node v0 then processQueue (ds {nodeQueue = q1})
else
-- Update the visited set
let v1 = HS.insert node v0
-- Get all unvisited neighbors of our current node
allNeighbors = fromMaybe [] (HM.lookup node (edges graph))
unvisitedNeighbors = filter (\(n, _) -> not (HS.member n v1)) allNeighbors
Now we just need to process each neighbor. We can do this using a fold. Our “folding function” will have a type signature that incorporates the current node as a “fixed” argument while otherwise following the a -> b -> a
pattern of a left fold. Each step will incorporate a new node with its cost and update the DijkstraState
. This means the a
value in our folding function is DijkstraState
, while the b
value is (String, Int)
.
foldNeighbor :: String -> DijkstraState -> (String, Int) -> DijkstraState
With this type signature set, we can now complete our processQueue
function before implementing this inner loop. We call a foldl
over the new neighbors, and then we recurse over the resulting DijkstraState
.
findShortestDistance graph src dest = ...
where
...
processQueue :: DijkstraState -> HashMap String (Distance Int)
processQueue ds@(DijkstraState v0 d0 q0) = case H.view q0 of
...
else
-- Update the visited set
let v1 = HS.insert coord v0
-- Get all unvisited neighbors of our current node
allNeighbors = fromMaybe [] (HM.lookup node (edges graph))
unvisitedNeighbors = filter (\(n, _) -> not (HS.member n v1)) allNeighbors
-- Fold each neighbor and recursively process the queue
in processQueue $ foldl (foldNeighbor node) (DijkstraState v1 d0 q1) unvisitedNeighbors
The Final Fold
Now let’s write this final fold, our “inner loop” function foldNeighbor
. The core job of this function is to calculate the “alternative” distance to the given neighbor by going “through” the current node. This consists of taking the distance from the source to the current node (which is stored in the distance map) and adding it to the specific edge cost from the current to this new node.
foldNeighbor :: String -> DijkstraState -> (String, Int) -> DijkstraState
foldNeighbor current (DijkstraState v1 d0 q1) (neighborNode, cost) =
let altDistance = addDist (d0 !?? current) (Dist cost)
...
We can then compare this distance to the existing distance we have to the neighbor in our distance map (or Infinity
if it doesn’t exist, remember).
foldNeighbor current ds@(DijkstraState _ d0 _) (neighborNode, cost) =
let altDistance = addDist (d0 !?? current) (Dist cost)
in if altDistance < d0 !?? neighborNode
...
If the alternative distance is smaller, we update the distance map by associating the neighbor node with the alternative distance and return the new DijkstraState
. We also insert the new distance into our queue. If the alternative distance is not better, we make no changes, and return the original state.
foldNeighbor current ds@(DijkstraState _ d0 _) (neighborNode, cost) =
let altDistance = addDist (d0 !?? current) (Dist cost)
in if altDistance < d0 !?? neighborNode
then DijkstraState v1 (HM.insert neighborNode altDistance d0) (H.insert (altDistance, neighborNode) q1)
else ds
Now we are essentially done! All that’s left to do is run the process queue function from the top level and get the distance for the destination point.
findShortestDistance :: Graph -> String -> String -> Distance Int
findShortestDistance graph src dest = processQueue initialState !?? dest
where
initialState = ...
processQueue = ...
Our code is complete, and we can construct a simple example and see that it works!
graph1 :: Graph
graph1 = Graph $ HM.fromList
[ ("A", [("D", 100), ("B", 1), ("C", 20)])
, ("B", [("D", 50)])
, ("C", [("D", 20)])
, ("D", [])
]
...
{- GHCI -}
>> findShortestDistance graph1 “A” “D”
40
Next Steps
This algorithm is nice, but it’s very limited and specific to how we’ve constructed the Graph
type. What if we wanted to expose a more general API to users?
Read on to see how to do this in the next part of this series!
Appendix
Here is the complete code for this article, including imports!
module DijkstraSimple where
{- required packages:
containers, unordered-containers, hashable
-}
import qualified Data.HashMap.Strict as HM
import Data.HashMap.Strict (HashMap)
import qualified Data.Heap as H
import Data.Heap (MinPrioHeap)
import qualified Data.HashSet as HS
import Data.HashSet (HashSet)
import Data.Hashable (Hashable)
import Data.Maybe (fromMaybe)
data Distance a = Dist a | Infinity
deriving (Show, Eq)
instance (Ord a) => Ord (Distance a) where
Infinity <= Infinity = True
Infinity <= Dist x = False
Dist x <= Infinity = True
Dist x <= Dist y = x <= y
addDist :: (Num a) => Distance a -> Distance a -> Distance a
addDist (Dist x) (Dist y) = Dist (x + y)
addDist _ _ = Infinity
(!??) :: (Hashable k, Eq k) => HashMap k (Distance d) -> k -> Distance d
(!??) distanceMap key = fromMaybe Infinity (HM.lookup key distanceMap)
newtype Graph = Graph
{ edges :: HashMap String [(String, Int)] }
data DijkstraState = DijkstraState
{ visitedSet :: HashSet String
, distanceMap :: HashMap String (Distance Int)
, nodeQueue :: MinPrioHeap (Distance Int) String
}
findShortestDistance :: Graph -> String -> String -> Distance Int
findShortestDistance graph src dest = processQueue initialState !?? dest
where
initialVisited = HS.empty
initialDistances = HM.singleton src (Dist 0)
initialQueue = H.fromList [(Dist 0, src)]
initialState = DijkstraState initialVisited initialDistances initialQueue
processQueue :: DijkstraState -> HashMap String (Distance Int)
processQueue ds@(DijkstraState v0 d0 q0) = case H.view q0 of
Nothing -> d0
Just ((minDist, node), q1) -> if node == dest then d0
else if HS.member node v0 then processQueue (ds {nodeQueue = q1})
else
-- Update the visited set
let v1 = HS.insert node v0
-- Get all unvisited neighbors of our current node
allNeighbors = fromMaybe [] (HM.lookup node (edges graph))
unvisitedNeighbors = filter (\(n, _) -> not (HS.member n v1)) allNeighbors
-- Fold each neighbor and recursively process the queue
in processQueue $ foldl (foldNeighbor node) (DijkstraState v1 d0 q1) unvisitedNeighbors
foldNeighbor current ds@(DijkstraState v1 d0 q1) (neighborNode, cost) =
let altDistance = addDist (d0 !?? current) (Dist cost)
in if altDistance < d0 !?? neighborNode
then DijkstraState v1 (HM.insert neighborNode altDistance d0) (H.insert (altDistance, neighborNode) q1)
else ds
graph1 :: Graph
graph1 = Graph $ HM.fromList
[ ("A", [("D", 100), ("B", 1), ("C", 20)])
, ("B", [("D", 50)])
, ("C", [("D", 20)])
, ("D", [])
]
Reading Style Results!
Earlier this week I proposed a poll, asking you what your preferred “Reading Style” is for Haskell articles. The results were fairly evenly split, although one answer did stand out a bit. Here are the results:
- In Depth Reading: 32%
- Quick Reference Guide: 23.8%
- General Haskell: 23.8%
- Code Ideas: 20.5%
The winner was In Depth Reading, which is really good for me to know! When I read personally, I tend not to have the patience to follow an entire article and copy the code from it. But apparently you, my readers, do enjoy it!
In a sense, this is good because I’ve often written with this style in mind. I tend to dislike tutorials that assume too much about the reader’s knowledge and what other tools they might be using. So I often try to make sure I include everything that might be important.
Going forward, I’ll try to have a good balance of article types, but with a slight emphasis on in depth tutorials. I’ll be tagging articles with their different types so you know what to expect when you’re reading it.
This will start next week, as I start writing about my work exploring Dijkstra’s algorithm. So check back in on Monday!
What's Your Reading Style?
I’ve been writing about Haskell for almost six years now. I’ve gone through a few different writing styles during that time, but I’m curious which of these most suit you, my readers! So for the first time, I’d like to take a poll and see what you think!
Here are four styles I could think of for how I would read an online programming article. Pick one of these to vote in this poll! (I’ll explain each option more below if you find these confusing).
If you have a style I haven’t thought of, you can email me (james@mondaymorninghaskell.me) and let me know! Here are the explanations in case you’re not sure.
In-Depth Reading
This is when you’re following the code I’m writing line-by-line, and you’ve got your editor open trying it out for yourself. You’re probably copying 10 or more lines of code from the article into your editor to see how it works.
Quick Reference Guide
This describes when you have a particular problem you’re trying to solve, like “what’s the best way to sort a list in Haskell?” or “How do I do a for-loop in Haskell?”. You want to find a code solution in the article so you can incorporate that code into your own project, but you don’t want to have to copy more than 4-5 lines of code.
This style also applies if you’re looking for a step-by-step guide to doing something with Haskell that isn’t specifically a code issue like, “How do I deploy a Haskell application on Heroku?”.
Learning Code Ideas
This means you’re interested in what Haskell code looks like, but you don’t specifically intend to copy any code from the article into your own work.
General Haskell Reader
This is you if you’re more interested in what Haskell is used for, and what distinguishes it from other languages. You want to read about these topics at the conceptual level without wading through a lot of code examples.
Vote!
I’ve probably done all of these approaches at some point. I’ve written many “project-oriented” series with an “In Depth” style in mind, especially around web skills and machine learning. Most of my work this year has been more along the lines of a “Quick Reference Guide”. The other two styles are less common, so if that’s what people are looking for I’d be very interested to hear about that! So let me know what you think! Cast your vote, and I’ll go through the results next week!
I'm Streaming on Twitch!
We’re done with our Data Structures series now, but before I get started with new material, I’d like to remind you that I do live coding most days of the week on Twitch! My streaming schedule usually looks something like this (all times are US Pacific time):
Monday: 30 minute stream (mid-day)
Tuesday: 30 minute stream (morning)
Wednesday: 30 minute stream (morning)
Thursday: 60 minute stream (evening)
Saturday: 60 minute stream (mid-day)
My exact timing varies a lot so you can follow me on Twitter as well to know when I’m going live! I try to give a 30-minute heads up before I start.
Starting in a couple weeks I’ll be writing about some of the work I’ve been doing on stream related to Dijkstra’s Algorithm in Haskell. I’ve published a few of the streaming sessions where I was working on this problem, so you can take a look at those past sessions now on my YouTube channel if you want to get a head start on this topic!
My next stream is tonight at 7:30 US Pacific time (GMT-07). I’ll be trying to make more IDEs and code editors work with Haskell, so be sure to check that out!
Data Structures: In Depth eBook!
Last week, we highlighted our new eBooks page with our At a Glance eBook. This week, as promised, we're releasing our new Data Structures: In Depth eBook.
This new eBook takes a deeper look at the topics and functions covered in our Data Structures series. You'll learn how Haskell's principle of immutability affects the design of its data structures, and see many more code examples for each function.
Best of all, this eBook gives you the chance to practice your skills with two problems for each data structure. The first problem will force you to come up with your own solution using the structure, and the second will let you see the performance characteristics of the structure by improving an existing solution to a problem.
After reading through the the 67 pages of this book and finishing the 18 problems, you'll be ready to use the right structure to solve any problem that comes your way in Haskell! So don't miss out! Find it on our eBooks page today!
Data Structures: At a Glance!
To cap off the Data Structures Series, we have a couple more resources to help you. The first of these is available right now, and you can check it out on our newly added eBooks page.
This first resouce is the "Data Structures At a Glance" eBook. It will allow you to get a super quick overview of all nine of the data structures in the series. All the type signatures of the most important functions for each structure are compressed on a sinigle page, so this can serve as an effective reference guide as you're trying to learn the structures.
The eBook is available on our eBooks page. It is free to download but uses "Pay What You Want" pricing so you can contribute to Monday Morning Haskell if you've really enjoyed our material!
Next Monday, we'll be coming out with our second Data Structure resource, so stay tuned for that!
Data Structures: Heaps!
Today we finish our Data Structures series! We have one more structure to look at, and that is the Heap! This structure often gets overlooked when people think of data structures, since its role is a bit narrow and specific. You can look at the full rundown on the series page here. If you've missed any of our previous structure summaries, here's the list:
That's all for our Data Structures series! The blog will be back soon with more content!
Data Structures: Sequences!
Haskell's basic "list" type works like a singly linked list. However, the lack of access to elements at the back means it isn't useful for a lot of algorithms. A double ended linked list (AKA a queue) allows a lot more flexibility.
In Haskell, we can get this double-ended behavior with the Sequence
type. This type works like lists in some ways, but it has a lot of unique operators and mechanics. So it's worth reading up on it here in the latest part of our Data Structures Series. Here's a quick review of the series so far:
We have one more structure to look at next time, so this series is going to bleed into August a bit, so make sure to come back next week!
Data Structures: Vectors!
Last week we started looking at less common Haskell data structures, starting with Arrays. Today we're taking one step further and looking at Vectors. These combine some of the performance mechanics of arrays with the API of lists. Many operations are quite a bit faster than you can find with lists.
For a full review, here's a list of the structures we've covered so far:
We've got two more structures coming up, so stay tuned!
Data Structures: Arrays!
Throughout July we've been exploring different data structures in Haskell. I started out with a general process called 10 Steps for understanding Data Structures in Haskell. And I've now applied that process to five structures in Haskell:
Today we're going to start exploring some lesser-known structures in Haskell. Today's new structure is Arrays. While these are commonplace in other languages, you don't see them as often in Haskell, and Haskell's array behavior is a bit different from what you'll see elsewhere. So head over to the article page to read about it!
Data Structures: Hash Maps!
Throughout this month we've been exploring the basics of many different data structures in Haskell. I started out with a general process called 10 Steps for understanding Data Structures in Haskell. And I've now applied that process to four common structures in Haskell:
Today we're taking the next logical step in the progression and looking at Hash Maps. Starting later this week, we'll start looking as lesser-known Haskell structures that don't fit some of the common patterns we've been seeing so far! So keep an eye on this blog page as well as the Data Structures Series page!
Data Structures: Hash Sets!
Last week I presented 10 Steps for understanding Data Structures in Haskell. In our new Data Structures Series you'll be able to see these steps applied to all the different data structures we can use in Haskell.
Today, marks the fourth article in this series, describing the Hash Set
data type. If you missed the last few parts, you can also head to the Series Page and take a look!
Data Structures: Maps!
Last week I presented 10 Steps for understanding Data Structures in Haskell. In our new Data Structures Series you'll be able to see these steps applied to all the different data structures we can use in Haskell.
Today, we're debuting the third part of the series, looking at the Map
data type. If you missed the last couple parts, you can also head to the Series Page and take a look!
Data Structures: Sets!
Earlier this week I presented 10 Steps for understanding Data Structures in Haskell. In our new Data Structures Series you'll be able to see these steps applied to all the different data structures we can use in Haskell.
Today, for the first time, you can take a look at the second part of this series, on the Set
data type. If you missed the first part on lists, you can also find that over here.
10 Steps to Understanding Data Structures in Haskell
Last year I completed Advent of Code, which presented a lot of interesting algorithmic challenges. One thing these problems really forced me to do was focus more clearly on using appropriate data structures, often going beyond the basics.
And looking back on that, it occurred to me that I hadn't really seen many tutorials on Haskell structures beyond lists and maps. Nor in fact, had I thought to write any myself! I've touched on sequences and arrays, but usually in the context of another topic, rather than focusing on the structure itself.
So after thinking about it, I decided it seemed worthwhile to start doing some material providing an overview on all the different structures you can use in Haskell. So data structures will be our "blog topic" starting in this month of July, and probably actually going into August. I'll be adding these overviews in a permanent series, so each blog post over the next few Mondays and Thursdays will link to the newest installment in that series.
But even beyond providing a basic overview of each type, I thought it would be helpful to come up with a process for learning new data structures - a process I could apply to learning any structure in any langugage. Going to the relevant API page can always be a little overwhelming. Where do you start? Which functions do you actually need?
So I made a list of the 10 steps you should take when learning the API for a data structure in a new language. The first of these have to do with reminding yourself what the structure is used for. Then you get down to the most important actions to get yourself started using that structure in code.
The 10 Steps
- What operations does it support most efficiently? (What is it good at?)
- What is it not as good at?
- How many parameters does the type use and what are their constraints.
- How do I initialize the structure?
- How do I get the size of the structure?
- How do I add items to the structure?
- How do I access (or get) elements from the structure?
- If possible, how do I delete elements from the structure?
- How do I combine two of these structures?
- How should I import the functions of this structure?
Each part of the series will run through these steps for a new structure, focusing on the basic API functions you'll need to know. To see my first try at using this approach where I go over the basic list type, head over to the first part of the series! As I update the series with more advanced structures I'll add more links to this post.
If you want to quickly see all the APIs for the structures we'll be covering, head to our eBooks page and download the FREE Data Structures at a Glance eBook!
A Brief Look at Asynchronous Exceptions
We've covered a lot of different exception mechanisms this month. Today we'll cover just one more concept that will serve as a teaser for some future exploration of concurrency. All the exception mechanisms we've looked at so are serial in nature. We call a certain IO function from our main thread, and we block the program until that operation finishes. However, exceptions can also happen in an asynchronous way. This can happen in a couple different ways.
First, as we'll learn later this year, we can fork different threads for our program to run, and it is possible to raise an exception in a different thread! If you're interested in exploring how this works, the relevant functions you should learn about are forkIO
and throwTo
:
forkIO :: IO () -> IO ThreadId
throwTo :: (Exception e) => ThreadId -> e -> IO ()
The first will take an IO action and run it on a new thread, returning the ID of that thread. The section function then allows you to raise an exception in that thread using the ID. We'll look into the details of this function at a later date.
However, there are also certain asynchronous exceptions that can occur no matter what we do. At any point, our program could theoretically run out of memory (StackOverflow
or HeapOverflow
), and our program will have to abort the execution of our program in an asynchronous manner. So even if we aren't specially forking new threads, we still might encounter these kinds of exceptions.
The mask
function is a special utility that prevents an action from being interrupted by an asynchronous exception.
mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b
However, just from looking at the type signature, this function is rather confusing. It takes one argument, a function that takes another function as its input! As we can read in the documentation though, the most common use case for this function is to protect a resource to make sure we release it even if an exception is thrown while performing a computation with it.
Lucky for us, the bracket function already handles this case, as we've discussed. So the chances that you'll have to manually use mask
are not very high.
This wraps up our discussion of exceptions for now on Monday Morning Haskell! We'll be sure to touch on this subject again when we get to concurrency in a few months. If you want a summary of this month's articles in your inbox, there's still time to subscribe to our monthly newsletter! You won't want to miss what's coming up next week!
Catching Before Production: Assert Statements in Haskell
We've spent a lot of time this month going over exceptions, which are ways to signal within our program that something unexpected has happened. These will often result in an early termination for our program even if we catch them. But by catching them, we can typically provide more helpful error messages and logs. Exceptions are intended for use in production code. You don't want them to ever go off, but they are there .
However, there are other bugs that you really want to catch before they ever make it into production. You don't want to formally recognize them in the type system because other parts of the program shouldn't have to deal with those possibilities. In these cases, it is common practice for programmers to use "assert" statements instead.
We'll start with a simple example in Python. We'll write a function to adjust a price, first by subtracting and second by taking the square root. Of course, you cannot take the square root of a negative number (and prices shouldn't be negative anyways). So we'll assert that the price is non-negative before we take the root.
def adjustPrice(input):
adjustedDown = input - 400.0
assert (adjustedDown >= 0)
return $ sqrt(adjustedDown)
In Haskell we also have an assert function. It looks a bit like throw
in the sense that its type signature looks pure, but can actually cause an error.
assert :: Bool -> a -> a
If the boolean input is "true", nothing happens. The function will return the second input as its output. But if the boolean is false, then it will throw an exception. This is useful because it will provide us with more information about where the error occurred. So let's rewrite the above function in Haskell.
adjustPrice :: Double -> Double
adjustPrice input = assert (adjustedDown >= 0.0) (sqrt adjustedDown)
where
adjustedDown = input - 400.0
If we give it a bad input, we'll get a helpful error message with the file and line number where the assertion occurred:
main :: IO ()
main = do
let result = adjustPrice 325.0
print result
...
>> stack exec my-program
my-program: Assertion failed
CallStack (from HasCallStack):
assert, called at src/Lib.hs in MyProgram-0.1.0.0:Lib
Without using the asssert, our function would simply return NaN
and continue on! It would be much harder for us to track down where the bug came from. Ideally, we would catch a case like this in unit testing. And it might indicate that our "adjustment" is too high (perhaps it should be 40.0 instead of 400.0).
For the sake of efficiency, assert statements are turned off in executable code. This is why it is imperative that you write a unit test to uncover the assertion problem. In order to run your program with assertions, you'll need to use the fno-ignore-asserts
GHC option. This is usually off for executables, but on for test suites.
We have one more concept to talk about with exception handling, so get ready for that! If you want a summary of all the topics we talked about this month, make sure to subscribe to our monthly newsletter!
Resources and "Bracket"
During our focus on the IO Monad, we learned a few things about opening and closing file handles. One useful tidbit we learned from this process was the "bracket" pattern. This pattern allows us to manage the acquisition and release of resources in our system. The IO monad is very often concerned with external resources, whether files on our filesystem or operating system resources like thread locks and process IDs.
The general rule behind these kinds of resources is that we do not want our program to be in a state where they are unreachable by code. Another way of saying this is that any code that acquires a release must make sure to release it. For the example of file handles, we can acquire the resource with openFile
and release it with hClose
.
processFile :: FilePath -> IO ()
processFile fp = do
-- Acquire resource
fileHandle <- openFile fp ReadMode
-- ... Do something with the file
-- Release the resource
hClose fileHandle
Now we might want to call this function with an exception handler so that our program doesn't crash if we encounter a serious problem:
main :: IO ()
main = do
handle ioHandler (processFile "my_file.txt"
...
where
ioHandler :: IOError -> IO ()
ioHandler e = putStr "Handled Exception: " >> print e
However, this error handler doesn't have access to the file handle. So it can't actually ensure the handle gets closed. So if our error occurs during the "do something" part of the function, this file handle will still be open.
But now suppose we need to do a second operation on this file that appends to it. If we still have a "Read Mode" handle open, we're not going to be able to open it for appending. So if our handler doesn't close the file, we'll encounter a potentially unnecessary error.
main :: IO ()
main = do
handle ioHandler (processFile "my_file.txt")
-- Might fail!
appendOperation "my_file.txt"
where
ioHandler :: IOError -> IO ()
ioHandler e = putStr "Handled Exception: " >> print e
The solution to this problem is to use the "bracket" pattern of resource usage. Under this pattern, our IO operation has 3 stages:
- Acquire the resource
- Use the resource
- Release the resource
The bracket
function has three input arguments for these stages, though the order is 1 -> 3 -> 2:
bracket
:: IO a -- 1. Acquire the resource
-> (a -> IO b) -- 3. Release the resource
-> (a -> IO c) -- 2. Use the resource
-> IO c -- Final result
Let's add some semantic clarity to this type:
bracket
:: IO resource -- 1. Acquire
-> (resource -> IO extra) -- 3. Release
-> (resource -> IO result) -- 2. Use
-> IO result -- Result
The "resource" is often a Handle
object, thread ID, or an object representing a concurrent lock. The "extra" type is usually the unit ()
. Most operations that release resources have no essential return value. So no other part of our computation takes this "extra" type as an input.
Now, even if an exception is raised by our operation, the "release" part of the code will be run. So if we rewrite our code in the following way, the file handle will get closed and we'll be able to perform the append operation, even if an exception occurs:
processFile :: FilePath -> IO ()
processFile fp = bracket
(openFile fp ReadMode) -- 1. Acquire resource
hClose -- 3. Release resource
(\fileHandle -> do ... -- 2. Use resource)
main :: IO ()
main = do
handle ioHandler (processFile "my_file.txt")
appendOperation "my_file.txt"
where
ioHandler :: IOError -> IO ()
ioHandler e = putStr "Handled Exception: " >> print e
As we discussed in May, the withFile
helper does this for you automatically.
Now there are a few different variations you can use with bracket
. If you don't need the resource as part of your computation, you can use bracket_
with an underscore. This follows the pattern of other monad functions like mapM_
and forM_
where the underscore indicates we don't use part of the result of a computation.
bracket_
:: IO resource -- 1. Acquire
-> (IO extra) -- 3. Release
-> (IO result) -- 2. Use
-> IO result -- Result
If you're passing around some kind of global manager object of data and state, this function may simplify your code.
There is also bracketOnError
. This will only run the "release" action if an error is encountered. If the "do something" step succeeds, the release step is skipped. So it might apply more if you're trying to use this function as an alternative to handle
.
bracketOnError
:: IO resource -- 1. Acquire
-> (resource -> IO extra) -- 3. Release if error
-> (resource -> IO result) -- 2. Use the resource
-> IO result -- Result
The last example is finally
.
finally
:: IO result
-> IO extra
-> IO result
This function is less directly related to resource management. It simply specifies a second action (returning "extra") that will be run once the primary computation ("result") is done, no matter if it succeeds or fails with an exception.
This might remind us of the pattern in other languages of "try/catch/finally". In Haskell, bracket
will give you the behavior of the "finally" concept. But if you don't need the resource acquisition step, then you use the finally
function.
Hopefully these tricks are helping you to write cleaner Haskell code. We just have a couple more exception patterns to go over this month. If you think you've missed something, you can scroll back on the blog. But you can also subscribe to our mailing list to get a summary at the end of every month!
Further Filtering
In our previous article we explored the functions catchJust
and handleJust
. These allow us to do some more specific filtering on the exceptions we're trying to catch. With catch
and handle
, we'll catch all exceptions of a particular type. And in many cases, especially where we have pre-defined our own error type, this is a useful behavior.
However, we can also consider cases with built-in error types, like IOError
. There are a lot of different IO errors our program could throw. And sometimes, we only watch to catch a few of them.
Let's consider just two of these examples. In both actions of this function, we'll open a file and print its first line. But in the first example, the file itself does not exist. In the second example, the file exists, but we'll also open the file in "Write Mode" while we're reading it.
main :: IO ()
main = do
action1
action2
where
action1 = do
h <- openFile "does_not_exist.txt" ReadMode
firstLine <- hGetLine h
putStrLn firstLine
hClose h
action2 = do
h <- openFile "does_exist.txt" ReadMode
firstLine <- hGetLine h
putStrLn firstLine
h2 <- openFile "does_exist.txt" WriteMode
hPutStrLn h2 "Hello World"
hClose h
These will cause two different kinds of IOError
. But we can catch them both with a handler function:
main :: IO ()
main = do
handle handler action1
handle handler action2
where
action1 = do
h <- openFile "does_not_exist.txt" ReadMode
firstLine <- hGetLine h
putStrLn firstLine
hClose h
action2 = do
h <- openFile "does_exist.txt" ReadMode
firstLine <- hGetLine h
putStrLn firstLine
h2 <- openFile "does_exist.txt" WriteMode
hPutStrLn h2 "Hello World"
hClose h
handler :: IOError -> IO ()
handler e = print e
And now we can run this and see both errors are printed.
>> stack exec my-program
does_not_exist.txt: openFile: does not exist (No such file or directory)
First line
does_exist.txt: openFile: resource busy (file is locked)
But suppose we only anticipated our program encountering the "does not exist" error. We don't expect a "resource busy" error, so we want our program to crash if it happens so we are forced to fix it. We need to filter the error types and use handleJust
instead.
Luckily, there are many predicates on IOErrors
like isDoesNotExistError
. We can use this to write our own predicate:
-- Library function
isDoesNotExistError :: IOError -> Bool
-- Our predicate
filterIO :: IOError -> Maybe IOError
filterIO e = if isDoesNotExistError e
then Just e
else Nothing
Now let's quickly recall the type signatures of catchJust
and handleJust
:
catchJust :: Exception e =>
(e -> Maybe b) ->
IO a ->
(b -> IO a) ->
IO a
handleJust :: Exception e =>
(e -> Maybe b) ->
(b -> IO a) ->
IO a ->
IO a
We can rewrite our function now so it only captures the "does not exist" error. We'll add the predicate, and use it with handleJust
, along with our existing handler.
main :: IO ()
main = do
handleJust filterIO handler action1
handleJust filterIO handler action2
where
action1 = do
h <- openFile "does_not_exist.txt" ReadMode
firstLine <- hGetLine h
putStrLn firstLine
hClose h
action2 = do
h <- openFile "does_exist.txt" ReadMode
firstLine <- hGetLine h
putStrLn firstLine
h2 <- openFile "does_exist.txt" WriteMode
hPutStrLn h2 "Hello World"
hClose h
handler :: IOError -> IO ()
handler e = putStr "Caught error: " >> print e
filterIO :: IOError -> Maybe IOError
filterIO e = if isDoesNotExistError e
then Just e
else Nothing
When we run the program, we'll see that the first error is caught. We see our custom message "Caught error" instead of the program name. But in the second instance, our program crashes!
>> stack exec my-program
Caught error: does_not_exist.txt: openFile: does not exist (no such file or directory)
First line
my-program: does_exist.txt: openFile: resource busy (file is locked)
Hopefully this provides you with a clear and practical example of how you can use these filtering functions for handling your errors! Next time, we'll take a deeper look at the "bracket" pattern. We touched on this during IO month, but it's an important concept, and there are more helper functions we can incorporate with it! So make sure to stop back here later in the week. And also make sure to subscribe to our monthly newsletter if you haven't already!