How not to use monads

Recently I have watched a video titled “Optionals and errors in Haskell & Rust - monads by example”. In the video, the author makes a simple application simulating the retrieval of a HTML document via URL and checking if the document contains the title. This is a half-simulated experience, aimed at the beginners to demonstrate how the error handling is done in Rust and Haskell.

However, author in his code has made quite a few bad decisions. And that’s what I want to make a focus of this blog: how one should not use monads and handle errors in Haskell.

Author’s original source looks like this:

{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE OverloadedRecordUpdate #-}

import Control.Monad (forM_)
import Data.List (isInfixOf)
import Data.Maybe (fromMaybe)
import Text.Printf (printf)

data Error = Error (String) deriving (Show)

data Doc = Doc {head :: Maybe Head}

data Head = Head {title :: Maybe String}

data Summary = Summary
  { title :: Maybe String,
    ok :: Bool
  }
  deriving (Show)

readDoc :: String -> Either Error Doc
readDoc url =
  if
      | isInfixOf "fail" url -> Left $ Error $ printf "Bad read of %s" url
      | otherwise ->
          Right $
            if
                | isInfixOf "head-missing" url -> Doc {head = Nothing}
                | isInfixOf "title-missing" url ->
                    Doc {head = Just Head {title = Nothing}}
                | isInfixOf "title-empty" url ->
                    Doc {head = Just Head {title = Just ""}}
                | otherwise ->
                    Doc
                      { head =
                          Just Head {title = Just $ printf "Title of %s" url}
                      }

buildSummary :: Doc -> Summary
buildSummary doc =
  Summary {title = doc.head >>= (.title), ok = True}

readAndBuildSummary :: String -> Summary
readAndBuildSummary url = case readDoc url of
  Left err -> Summary {title = Nothing, ok = False}
  Right doc -> buildSummary doc

isTitleNonEmpty :: Doc -> Maybe Bool
isTitleNonEmpty doc = do
  head <- doc.head
  title <- head.title
  return $ not $ null title

isTitleNonEmpty' :: Doc -> Maybe Bool
isTitleNonEmpty' doc = not <$> null <$> (doc.head >>= (.title))

isTitleNonEmpty'' :: Doc -> Maybe Bool
isTitleNonEmpty'' doc = not . null <$> (doc.head >>= (.title))

readWhetherTitleNonEmpty :: String -> Either Error (Maybe Bool)
readWhetherTitleNonEmpty url = do
  doc <- readDoc url
  return $ isTitleNonEmpty doc

readWhetherTitleNonEmpty' :: String -> Either Error (Maybe Bool)
readWhetherTitleNonEmpty' url = isTitleNonEmpty <$> readDoc url

main :: IO ()
main = do
  let urls = ["good", "title-empty", "title-missing", "head-missing", "fail"]
  forM_ urls $ \url -> do
    putStrLn $ printf "Checking \"https://%s/\":" url
    -- Summary.
    let summary = readAndBuildSummary url
    putStrLn $ printf "  Summary: %s" $ show summary
    putStrLn $ printf "  Title: %s" $ fromMaybe "" summary.title
    -- Has title.
    let hasTitle = readWhetherTitleNonEmpty url
    -- let hasTitleSure = either (const False) id $ fromMaybe False <$> hasTitle
    let hasTitleSure = fromMaybe False $ either (const Nothing) id hasTitle
    putStrLn $
      printf "  Has title: %s vs %s" (show hasTitle) (show hasTitleSure)

He then proceeded to wrapping this code in IO monad and ended up with the following:

{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE OverloadedRecordUpdate #-}

import Control.Monad (forM_)
import Data.Functor ((<&>))
import Data.List (isInfixOf)
import Data.Maybe (fromMaybe)
import Text.Printf (printf)

data Error = Error (String) deriving (Show)

data Doc = Doc {head :: Maybe Head}

data Head = Head {title :: Maybe String}

data Summary = Summary
  { title :: Maybe String,
    ok :: Bool
  }
  deriving (Show)

-- readDoc

readDoc :: String -> IO (Either Error Doc)
readDoc url =
  return
    if
        | isInfixOf "fail" url -> Left $ Error $ printf "Bad read of %s" url
        | otherwise ->
            Right $
              if
                  | isInfixOf "head-missing" url -> Doc {head = Nothing}
                  | isInfixOf "title-missing" url ->
                      Doc {head = Just Head {title = Nothing}}
                  | isInfixOf "title-empty" url ->
                      Doc {head = Just Head {title = Just ""}}
                  | otherwise ->
                      Doc
                        { head =
                            Just Head {title = Just $ printf "Title of %s" url}
                        }

-- buildSummary

buildSummary :: Doc -> Summary
buildSummary doc =
  Summary {title = doc.head >>= (.title), ok = True}

-- readAndBuildSummary

readAndBuildSummary :: String -> IO Summary
readAndBuildSummary url = do
  docOrError <- readDoc url
  return $ case docOrError of
    Left err -> Summary {title = Nothing, ok = False}
    Right doc -> buildSummary doc

readAndBuildSummary' :: String -> IO Summary
readAndBuildSummary' url =
  readDoc url >>= \docOrError -> return $ case docOrError of
    Left err -> Summary {title = Nothing, ok = True}
    Right doc -> buildSummary doc

readAndBuildSummary'' :: String -> IO Summary
readAndBuildSummary'' url =
  readDoc url <&> \case
    Left err -> Summary {title = Nothing, ok = True}
    Right doc -> buildSummary doc

-- isTitleNonEmpty

isTitleNonEmpty :: Doc -> Maybe Bool
isTitleNonEmpty doc = do
  head <- doc.head
  title <- head.title
  return $ not $ null title

isTitleNonEmpty' :: Doc -> Maybe Bool
isTitleNonEmpty' doc = not <$> null <$> (doc.head >>= (.title))

isTitleNonEmpty'' :: Doc -> Maybe Bool
isTitleNonEmpty'' doc = not . null <$> (doc.head >>= (.title))

-- readWhetherTitleNonEmpty

readWhetherTitleNonEmpty :: String -> IO (Either Error (Maybe Bool))
readWhetherTitleNonEmpty url = do
  docOrError <- readDoc url
  return $ do
    doc <- docOrError
    return $ isTitleNonEmpty doc

readWhetherTitleNonEmpty' :: String -> IO (Either Error (Maybe Bool))
readWhetherTitleNonEmpty' url =
  readDoc url >>= \docOrError ->
    return $ docOrError >>= \doc -> return $ isTitleNonEmpty doc

readWhetherTitleNonEmpty'' :: String -> IO (Either Error (Maybe Bool))
readWhetherTitleNonEmpty'' url = (isTitleNonEmpty <$>) <$> readDoc url

readWhetherTitleNonEmpty''' :: String -> IO (Either Error (Maybe Bool))
readWhetherTitleNonEmpty''' url = readDoc url <&> (<&> isTitleNonEmpty)

-- main

main :: IO ()
main = do
  let urls = ["good", "title-empty", "title-missing", "head-missing", "fail"]
  forM_ urls $ \url -> do
    putStrLn $ printf "Checking \"https://%s/\":" url
    -- Summary.
    summary <- readAndBuildSummary url
    putStrLn $ printf "  Summary: %s" $ show summary
    putStrLn $ printf "  Title: %s" $ fromMaybe "" summary.title
    -- Has title.
    hasTitle <- readWhetherTitleNonEmpty url
    -- let hasTitleSure = either (const False) id $ fromMaybe False <$> hasTitle
    let hasTitleSure = fromMaybe False $ either (const Nothing) id hasTitle
    putStrLn $
      printf "  Has title: %s vs %s" (show hasTitle) (show hasTitleSure)

I see a few issues with this code:

  1. the abuse of IO monad
  2. the excessive (an I mean unnecessary) use of Maybe monad
  3. too many unnecessary readDoc calls (bear in mind: it is supposed to be a network call + document parse, so quite a heavy function)

Improvements

My suggestions on how to make their code better:

  1. only stick to IO where the function is actually interacting with the external world; in this case this would be either main or readDoc (when it actually makes a network call)
  2. eliminate the abuse of Maybe Bool - in the functions where the Maybe Bool is used (isTitleNonEmpty and its variations) just Bool would suffice
  3. only call readDoc once and use the result down the pipeline, no need to call it multiple times (readAndBuildSummary, readWhetherTitleNonEmpty)
  4. reduce the nested if statements to guard expressions
  5. replace the case eitherValue expressions with the either function
  6. remove the dead / unused / unnecessary code (like those duplicated functions - readWhetherTitleNonEmpty', readWhetherTitleNonEmpty'' and readWhetherTitleNonEmpty''')

Use IO monad only for the functions which interact with the outside world

IO monad tells compiler and the people who read the code the function operates outside of the program internals. Like actually performing input-output, working with network, operating system, etc.

You can think of any such function as an unsafe part of an application.

In the example above, most of the functions do not comply with that - they are simply a side-effect of poor monad operations and could be easily changed as follows:

isTitleNonEmpty :: Doc -> Maybe Bool
isTitleNonEmpty doc = do
  head <- doc.head
  title <- head.title
  return $ not $ null title

buildSummary :: Doc -> Summary
buildSummary doc =
  Summary {title = doc.head >>= (.title), ok = True}

-- there is absolutely no need for this function
readWhetherTitleNonEmpty :: String -> IO (Either Error (Maybe Bool))
readWhetherTitleNonEmpty url = do
  docOrError <- readDoc url
  return $ do
    doc <- docOrError
    return $ isTitleNonEmpty doc

-- this is also redundant
readAndBuildSummary :: String -> IO Summary
readAndBuildSummary url = do
  docOrError <- readDoc url
  return $ case docOrError of
    Left err -> Summary {title = Nothing, ok = False}
    Right doc -> buildSummary doc

-- this is the (reduced) existing code
main__old :: IO ()
main__old = do
  let url = "good"

  putStrLn $ printf "Checking \"https://%s/\":" url

  summary <- readAndBuildSummary url

  putStrLn $ printf "  Summary: %s" $ show summary
  putStrLn $ printf "  Title: %s" $ fromMaybe "" summary.title

  hasTitle <- readWhetherTitleNonEmpty url

-- note how the document is only passed down to the functions which actually operate on the document
-- the only two functions using `IO` monad here are `main` and `readDoc`, as both perform input-output operations
main :: IO ()
main = do
  let url = "good"

  putStrLn $ printf "Checking \"https://%s/\":" url

  docOrError <- readDoc url

  let summary = case docOrError of
    Left err -> Summary {title = Nothing, ok = False}
    Right doc -> buildSummary doc

  putStrLn $ printf "  Summary: %s" $ show summary
  putStrLn $ printf "  Title: %s" $ fromMaybe "" summary.title

  let hasTitle = isTitleNonEmpty doc

Reduce calls to IO functions

Pure functions must return the exact same value for the same arguments, regardless of how many times they are called.

IO (and a lot of other monads, like Reader, Writer, etc.) work around this rule by changing the outside world. So even though a function technically returns the same value every time, the side-effect of an IO monad can potentially change something elsewhere, outside of the function itself.

This makes the programs non-pure and might cause a lot of negative impact. These side effects are what is thought to be the root of all evils in (functional) programming. They make it hard to figure out what a program actually does. They make the functions and programs hard to test and prove to be correct.

From the performance perspective, if a function actually does change the outside world, it can’t be memoized and it won’t be optimized by the compiler to only use its result, computed once.

Think calling a function which tries to create a user in a system or drop a database table. This would happen on every call. If you call such function twice, it will most likely fail (due to database failures, hopefully).

But what if the function creates data instead and there are no checks for duplicates in the external system? Like appending a log line. If such function was to be called multiple times, it can quickly bloat the storage. This is a potential security issue as well.

So instead of calling such functions (recap: functions returning IO monad), why not call them once and store the result? Then the entire program can operate on the stored result value.

Of course, there are plethora of cases where such behaviour (calling such functions multiple times) is actually desired. But in the sample code from above, this is not the case.

Check the transformed code from the previous point how this solution is utilized:

main :: IO ()
main = do
  let url = "good"

  putStrLn $ printf "Checking \"https://%s/\":" url

  -- store the result of fetching a document by its URL
  docOrError <- readDoc url

  -- work on the stored value instead of sending an extra HTTP request
  let summary = case docOrError of
    Left err -> Summary {title = Nothing, ok = False}
    Right doc -> buildSummary doc

  putStrLn $ printf "  Summary: %s" $ show summary
  putStrLn $ printf "  Title: %s" $ fromMaybe "" summary.title

  -- work on the stored value again, preventing one more HTTP request
  let hasTitle = case docOrError of
    Left err -> False
    Right doc -> isTitleNonEmpty doc

Eliminate the abuse of Maybe Bool

There’s simply no need to go overboard with Maybe in methods which simply check whether something is present or not.

Maybe Bool introduces a tri-state:

  • Just False
  • Just True
  • Nothing

In cases where this is desired, is much better to represent each of the state with a semantic value:

type HeaderPresence = NoHeader | EmptyHeader | HasHeader

This way the code is much easier to follow and debug.

For the sample in question even this approach is redundant - the function simply checks whether the value (title) is present or not, so a simple Bool would suffice:

isTitleNonEmpty__old :: Doc -> Maybe Bool
isTitleNonEmpty__old doc = do
  head <- doc.head
  title <- head.title
  return $ not $ null title

isTitleNonEmpty :: Doc -> Bool
isTitleNonEmpty doc =
  not $ null title
  where
    title = doc.head doc >>= head.title

main__old :: IO ()
main__old = do
  let url = "good"

  docOrError <- readDoc url

  hasTitle <- case docOrError of
    Left err -> None
    Right doc -> isTitleNonEmpty__old doc

  let hasTitleSure = fromMaybe False $ either (const Nothing) id hasTitle

  putStrLn $
    printf "  Has title: %s vs %s" (show hasTitle) (show hasTitleSure)

main :: IO ()
main = do
  let url = "good"

  putStrLn $ printf "Checking \"https://%s/\":" url

  docOrError <- readDoc url

  -- a simple True | False value, no need to mess with Maybe
  let hasTitle = case docOrError of
    Left err -> False
    Right doc -> isTitleNonEmpty doc

  -- note: no need to wrap & unwrap Maybe and Either
  putStrLn $ printf "  Has title: %s" (show hasTitle)

Reduce the nested if statements - use guard expressions

The original readDoc function uses a rather unnecessarily bulky if statement:

readDoc :: String -> IO (Either Error Doc)
readDoc url =
  return
    if
        | isInfixOf "fail" url -> Left $ Error $ printf "Bad read of %s" url
        | otherwise ->
            Right $
              if
                  | isInfixOf "head-missing" url -> Doc {head = Nothing}
                  | isInfixOf "title-missing" url ->
                      Doc {head = Just Head {title = Nothing}}
                  | isInfixOf "title-empty" url ->
                      Doc {head = Just Head {title = Just ""}}
                  | otherwise ->
                      Doc
                        { head =
                            Just Head {title = Just $ printf "Title of %s" url}
                        }

Haskell provides a built-in language feature for just this case, which really does make code cleaner a lot:

readDoc :: String -> IO (Either Error Doc)

readDoc url
  | isInfixOf "fail" url = return $ Left $ Error $ printf "Bad read of %s" url
  | isInfixOf "head-missing" url = return $ Right Doc { head = Nothing }
  | isInfixOf "title-missing" url = return $ Right Doc { head = Just Head { title = Nothing } }
  | isInfixOf "title-empty" url = return $ Right Doc { head = Just Head { title = Just "" } }
  | otherwise = return $ Right Doc { head = Just Head { title = Just $ printf "Title of %s" url } }

Use existing functions on monads instead of case statements

In my experience, for the most part, you want to simply apply a function to a Maybe or an Either.

And, again, for the most part, you either ignore one of the states of the monad (be it Nothing or Left), or apply a different function to it.

There are handy helper functions for these situations which do make the code cleaner - fromMaybe and either.

Consider few examples:

hasTitle__old <- case docOrError of
  Left err -> None
  Right doc -> isTitleNonEmpty__old doc

hasTitle <- either (const None) (isTitleNonEmpty__old)
let summary__old = case docOrError of
  Left err -> Summary {title = Nothing, ok = False}
  Right doc -> buildSummary doc

-- needs a nice helper function
invalid_summary = Summary { title = Nothing, ok = False }

let summary = either invalid_summary buildSummary
let hasTitle__old = case docOrError of
  Left err -> False
  Right doc -> isTitleNonEmpty doc

let hasTitle = either (const False) isTitleNonEmpty

End result

Here’s what the code looks like when applying all of the above suggestions and tidying up the code:

{-# LANGUAGE DuplicateRecordFields #-}

import Control.Monad (forM_)
import Data.List (isInfixOf)
import Data.Maybe (fromMaybe)
import Text.Printf (printf)

newtype Error = Error String deriving (Show)

newtype Doc = Doc {_head :: Maybe Head}

newtype Head = Head {title :: Maybe String}

data Summary = Summary
  { title :: Maybe String,
    ok :: Bool
  }
  deriving (Show)

-- helpers for Repl.It is meh with language extensions

docHead :: Doc -> Maybe Head
docHead = _head

headTitle :: Head -> Maybe String
headTitle = title

summaryTitle :: Summary -> Maybe String
summaryTitle = title

-- implementations

readDoc :: String -> IO (Either Error Doc)
readDoc url
  | "fail" `isInfixOf` url = return $ Left $ Error $ printf "Bad read of %s" url
  | "head-missing" `isInfixOf` url = return $ Right Doc {_head = Nothing}
  | "title-missing" `isInfixOf` url = return $ Right Doc {_head = Just Head {title = Nothing}}
  | "title-empty" `isInfixOf` url = return $ Right Doc {_head = Just Head {title = Just ""}}
  | otherwise = return $ Right Doc {_head = Just Head {title = Just $ printf "Title of %s" url}}

buildSummary :: Doc -> Summary
buildSummary doc =
  Summary {title = docHead doc >>= headTitle, ok = True}

invalidSummary :: Summary
invalidSummary = Summary {title = Nothing, ok = False}

readAndBuildSummary :: Either Error Doc -> Summary
readAndBuildSummary = either invalidSummary buildSummary

readAndBuildTitle :: Summary -> String
readAndBuildTitle summary = fromMaybe "" (summaryTitle summary)

isTitleNonEmpty :: Doc -> Bool
isTitleNonEmpty doc =
  not $ null title
  where
    title = docHead doc >>= headTitle

readWhetherTitleNonEmpty :: Either Error Doc -> Bool
readWhetherTitleNonEmpty = either (const False) isTitleNonEmpty

-- main

main :: IO ()
main = do
  let urls = ["good", "title-empty", "title-missing", "head-missing", "fail"]

  forM_ urls $ \url -> do
    putStrLn $ printf "Checking \"https://%s/\":" url

    docOrError <- readDoc url

    -- Summary
    let summary = readAndBuildSummary docOrError
    let title = readAndBuildTitle summary

    putStrLn $ printf "  Summary: %s" $ show summary
    putStrLn $ printf "  Title: %s" $ title

    -- Has title
    let hasTitle = readWhetherTitleNonEmpty docOrError

    putStrLn $ printf "  Has title: %s" (show hasTitle)

Floyd-Warshall algorithm, revised

In this blog I would like to brush upon Floyd-Warshall algorithm implementation I have described previously.

See, generally, when explaining Floyd-Warshall algorithm, the graph is given as an adjacency matrix - an V x V matrix, where V is the number of vertices (nodes) in a graph and each matrix value representing the distance between each vertex. For instance, the value G[1][3] = 12 represents the edge from vertex 1 to vertex 3 with the value of 12.

Aside from adjacency matrix, there are two other common ways to represent a graph:

  • incidence matrix of size V x E for V vertices and E edges, where each row represents an edge value (G[i][j] > 0 for edge i -> j, G[i][j] < 0 for edge j -> i, G[i][j] = 0 for no edge between vertices i and j)
  • adjacency list, where each vertex is represented as an object with a list of its connections

Consider the graph from the previous blog:

It can be represented in three different ways:

adjacency list:

v0: [ [2 -> 1] ]
v1: [ [2 -> 6], [0 -> 7] ]
v2: [ [3 -> 5] ]
v3: [ [1 -> 2] ]

adjacency matrix:

   |  v0  v1  v2  v3
---+------------------
v0 |   0   0   1   0
v1 |   7   0   6   0
v2 |   0   0   0   5
v3 |   0   2   0   0

incidence matrix:

   |  e0  e1  e2  e3  e4
---+---------------------
v0 |   0   0   0   7   0
v1 |   0   0   2   0   0
v2 |   1   0   0   0   6
v3 |   0   5   0   0   0

However, arguably the most common and most memory-efficient way to represent graph in a real-world application would be the adjacency list.

Hence I thought a bit of a revised implementation is needed, since the previous one (aka “classic” implementation) relies on matrices. And those matrices contain quite a bit of unused data. Take the graph above as an example: it has 4 vertices and 5 edges. An adjacency matrix would use 16 numbers, incidence matrix would use 20 numbers and adjacency list would use 5 tuples of 2 numbers (10 numbers, so to speak).

“Classic” Floyd-Warshall algorithm implementation constructs an additional matrix for the shortest paths’ distances (at most it can reuse the existing one representing the graph itself) and an additional V x V matrix for path reconstruction.

With a graph represented as an adjacency list (or just a list of node objects), the algorithm can use something like a dictionary (or a hashmap) to reduce the memory consumption. Subjectively, it also becomes easier to read and understand the algorithm.

First, we’d need few definitions:

class Node
{
    public string Name;
    public Dictionary<Node, int> Connections;

    public Node(string name)
    {
        this.Name = name;
        this.Connections = new Dictionary<Node, int>();
    }

    public override string ToString()
    {
        return this.Name;
    }
}

class Graph
{
    public List<Node> Nodes;

    public Graph()
    {
        this.Nodes = new List<Node>();
    }
}

class Path
{
    public Node From;
    public Node To;
    public List<Node> Nodes;
    public int Distance;

    public Path(Node from, Node to)
    {
        this.Distance = 0;
        this.From = from;
        this.To = to;
        this.Nodes = new List<Node>();
    }
}

The Path class is a bit excessive, as it really only needs a list of Node objects, but I decided to make it verbose on purpose - to make it easier to debug.

The algorithm then becomes like this:

Dictionary<(Node from, Node to), Node> FindAllPaths(Graph g)
{
    var distance = new Dictionary<(Node from, Node to), int>();
    var pathThrough = new Dictionary<(Node from, Node to), Node>();

    foreach (var nodeFrom in g.Nodes)
    {
        foreach (var nodeTo in g.Nodes)
        {
            if (nodeFrom == nodeTo)
            {
                distance.Add((nodeFrom, nodeTo), 0);
            }
            else
            {
                distance.Add((nodeFrom, nodeTo), int.MaxValue);
            }
        }

        foreach (var nodeTo in nodeFrom.Connections.Keys)
        {
            distance[(nodeFrom, nodeTo)] = nodeFrom.Connections[nodeTo];
            pathThrough.Add((nodeFrom, nodeTo), nodeTo);
        }

        pathThrough.Add((nodeFrom, nodeFrom), nodeFrom);
    }

    foreach (var nodeThrough in g.Nodes)
    {
        foreach (var nodeFrom in g.Nodes)
        {
            foreach (var nodeTo in g.Nodes)
            {
                if (nodeFrom == nodeTo || distance[(nodeThrough, nodeTo)] == int.MaxValue || distance[(nodeFrom, nodeThrough)] == int.MaxValue)
                {
                    continue;
                }

                if (distance[(nodeFrom, nodeTo)] > distance[(nodeFrom, nodeThrough)] + distance[(nodeThrough, nodeTo)])
                {
                    distance[(nodeFrom, nodeTo)] = distance[(nodeFrom, nodeThrough)] + distance[(nodeThrough, nodeTo)];
                    pathThrough[(nodeFrom, nodeTo)] = pathThrough[(nodeFrom, nodeThrough)];
                }
            }
        }
    }

    return pathThrough;
}

One can easily see the separate parts of the algorithm - initializing the intermediate storage (for the paths and distances) and actually finding the shortest paths. It is pretty much the same algorithm as before with the only difference being the use of dictionary instead of a matrix.

Path reconstruction bit is also a little bit different (not too much though):

Path ReconstructPath(Node from, Node to, Dictionary<(Node from, Node to), Node> allPaths)
{
    if (!allPaths.ContainsKey((from, to)))
    {
        return null;
    }

    var path = new Path(from, to);

    var tempNode = from;

    path.Nodes.Add(tempNode);

    while (tempNode != to)
    {
        var nextNode = allPaths[(tempNode, to)];

        path.Distance += tempNode.Connections[nextNode];
        path.Nodes.Add(nextNode);

        tempNode = nextNode;
    }

    return path;
}

Now, there is one major improvement we can make to this algorithm. See, when we initialize the dictionaries for paths and distances, we follow the same logic as with the classic implementation, putting in the values for edges which do not exist in a graph:

foreach (var nodeFrom in g.Nodes)
{
    // this bit will add entries for inexistent edges
    foreach (var nodeTo in g.Nodes)
    {
        if (nodeFrom == nodeTo)
        {
            distance.Add((nodeFrom, nodeTo), 0);
        }
        else
        {
            distance.Add((nodeFrom, nodeTo), int.MaxValue);
        }
    }

    // ...
}

But as a matter of fact, we do not really have to store these values - instead, we could simply have a check whether the needed entry exists in the dictionary or not:

Dictionary<(Node from, Node to), Node> FindAllPaths(Graph g)
{
    var distance = new Dictionary<(Node from, Node to), int>();
    var pathThrough = new Dictionary<(Node from, Node to), Node>();

    foreach (var nodeFrom in g.Nodes)
    {
        // -- no more unnecessary entries --

        foreach (var nodeTo in nodeFrom.Connections.Keys)
        {
            distance.Add((nodeFrom, nodeTo), nodeFrom.Connections[nodeTo]);
            pathThrough.Add((nodeFrom, nodeTo), nodeTo);
        }

        pathThrough.Add((nodeFrom, nodeFrom), nodeFrom);
    }

    foreach (var nodeThrough in g.Nodes)
    {
        foreach (var nodeFrom in g.Nodes)
        {
            foreach (var nodeTo in g.Nodes)
            {
                if (nodeFrom == nodeTo)
                {
                    continue;
                }

                // ++ but one extra check here, to prevent unnecessary iterations ++
                if (!distance.ContainsKey((nodeFrom, nodeThrough)) || !distance.ContainsKey((nodeThrough, nodeTo)))
                {
                    continue;
                }

                // ++ and one extra check here, to annotate the existence of a new, indirect shortest path between nodeFrom and nodeTo ++
                if (!distance.ContainsKey((nodeFrom, nodeTo)) || distance[(nodeFrom, nodeTo)] > distance[(nodeFrom, nodeThrough)] + distance[(nodeThrough, nodeTo)])
                {
                    distance[(nodeFrom, nodeTo)] = distance[(nodeFrom, nodeThrough)] + distance[(nodeThrough, nodeTo)];
                    pathThrough[(nodeFrom, nodeTo)] = pathThrough[(nodeFrom, nodeThrough)];
                }
            }
        }
    }

    return pathThrough;
}

For that matter, we don’t really need to have a separate dictionary for path reconstruction - since both distance and pathThrough dictionaries serve the same purpose (have the exact same key, but different value), we can smash those two together and use even less memory:

Dictionary<(Node from, Node to), (Node through, int distance)> FindAllPaths(Graph g)
{
    var pathThrough = new Dictionary<(Node from, Node to), (Node through, int distance)>();

    foreach (var nodeFrom in g.Nodes)
    {
        foreach (var nodeTo in nodeFrom.Connections.Keys)
        {
            pathThrough.Add((nodeFrom, nodeTo), (nodeTo, nodeFrom.Connections[nodeTo]));
        }

        pathThrough.Add((nodeFrom, nodeFrom), (nodeFrom, 0));
    }

    foreach (var nodeThrough in g.Nodes)
    {
        foreach (var nodeFrom in g.Nodes)
        {
            foreach (var nodeTo in g.Nodes)
            {
                if (nodeFrom == nodeTo)
                {
                    continue;
                }

                if (!pathThrough.ContainsKey((nodeFrom, nodeThrough)) || !pathThrough.ContainsKey((nodeThrough, nodeTo)))
                {
                    continue;
                }

                if (!pathThrough.ContainsKey((nodeFrom, nodeTo)) || pathThrough[(nodeFrom, nodeTo)].distance > pathThrough[(nodeFrom, nodeThrough)].distance + pathThrough[(nodeThrough, nodeTo)].distance)
                {
                    pathThrough[(nodeFrom, nodeTo)] = (nodeThrough, pathThrough[(nodeFrom, nodeThrough)].distance + pathThrough[(nodeThrough, nodeTo)].distance);
                }
            }
        }
    }

    return pathThrough;
}

Essentially, nothing special - just using the tuples for both the intermediate node and the distance for the shortest paths.

And with a tiny bit of a change, path reconstruction:

Path ReconstructPath(Node from, Node to, Dictionary<(Node from, Node to), (Node through, int distance)> allPaths)
{
    if (!allPaths.ContainsKey((from, to)))
    {
        return null;
    }

    var path = new Path(from, to);

    var tempNode = from;

    path.Nodes.Add(tempNode);

    while (tempNode != to)
    {
        var (nextNode, distance) = allPaths[(tempNode, to)];

        path.Distance += distance;
        path.Nodes.Add(nextNode);

        tempNode = nextNode;
    }

    return path;
}

Parser monad

Few years ago I did a course project for the “Functional programming” course at Jagiellonian University. The project was to implement a program for solving systems of equations… in Haskell.

For me back then, the entire concept of monads was quite foreign and scary, so I implemented a very crude state machine to parse the equations as strings from STDIN:

parseRow :: String -> Integer -> [Integer] -> [String] -> ([Integer], [String])
parseRow [] state coefficients var_names
    | state == 7 = (reverse coefficients, reverse var_names)
    | otherwise = error ("Invalid equation (state: " ++ show state ++ "; coefficients: " ++ show coefficients ++ "; var_names: " ++ show var_names ++ ")")

parseRow (c:cs) state coefficients var_names
    | (state == 1) && (c == '-') = parseRow cs 2 ((-1) : coefficients) var_names
    | state == 1 && isNum c = parseRow cs 3 (c_int : coefficients) var_names
    | state == 1 && isAlpha c = parseRow cs 4 (1 : coefficients) ([c] : var_names)
    | state == 2 && isNum c = parseRow cs 3 (repl_k : drop 1 coefficients) var_names
    | state == 2 && isAlpha c = parseRow cs 4 coefficients ([c] : var_names)
    | (state == 3) && (c == '=') = parseRow cs 5 coefficients var_names
    | state == 3 && isAlpha c = parseRow cs 4 coefficients ([c] : var_names)
    | state == 3 && isNum c = parseRow cs 3 (new_k : drop 1 coefficients) var_names
    | (state == 4) && (c == '-') = parseRow cs 2 ((-1) : coefficients) var_names
    | (state == 4) && (c == '+') = parseRow cs 2 (1 : coefficients) var_names
    | state == 4 && isAlphaNum c = parseRow cs 4 coefficients (new_v : drop 1 var_names)
    | (state == 4) && (c == '=') = parseRow cs 5 coefficients var_names
    | (state == 5) && (c == '-') = parseRow cs 6 ((-1) : coefficients) var_names
    | state == 5 && isNum c = parseRow cs 7 (c_int : coefficients) var_names
    | state == 6 && isNum c = parseRow cs 7 (repl_k : drop 1 coefficients) var_names
    | state == 7 && isNum c = parseRow cs 7 (new_k : drop 1 coefficients) var_names
    | otherwise = parseRow cs state coefficients var_names
    where
        k = abs $ head coefficients
        k_sign = sign (head coefficients)
        c_int = atoi c
        new_k = k_sign * ((k * 10) + c_int)
        repl_k = k_sign * c_int
        v = if not (null var_names) then head var_names else []
        new_v = v ++ [c]

parseLine :: String -> ([Integer], [String])
parseLine s = parseRow s 1 [] []

However, recently I (hopefully) got a grip of monads, so I decided to modify my old project in Haskell to make it prettier.

One of the improvements I made was the parsing part. Since one of the requirements for the course project was to not use any third-party libraries, I decided to stick to this and implement a parser monad.

This proved to be an interesting task and made the entire parsing part quite neat:

equationFactor :: Parser Fraction
equationFactor = do
    _sign <- factorSign

    zeroOrMore (sat isSpace)

    factor <- fmap (fromMaybe (1%1)) (zeroOrOne rationalFactor)

    return (_sign * factor)

equationMember :: Parser (Fraction, String)
equationMember = do
    factor <- equationFactor

    zeroOrMore (sat isSpace)
    zeroOrOne (sat (== '*'))
    zeroOrMore (sat isSpace)

    nameFirst <- oneOrMore (sat isAlpha)
    nameRest <- zeroOrMore (sat isAlphaNum)

    zeroOrMore (sat isSpace)

    return (factor, nameFirst ++ nameRest)

-- An equation consists of a list of pairs (factor, variable name) and a free member
equation :: Parser ([(Fraction, String)], Fraction)
equation = do
    members <- oneOrMore equationMember

    zeroOrMore (sat isSpace)
    sat (== '=')
    zeroOrMore (sat isSpace)

    freeMember <- rationalFactor

    return (members, freeMember)

This is all possible thanks to the Parser monad. Under the cut - the implementation details.

Read more

ConfigScript

Once upon a time I thought OGRE was overly too complicated - all those unnecessary script files, custom formats, a ton of setup hassle. That was until I tried figuring out an entire modern 3D rendering stack from scratch. That’s when I realized configuring a rendering process (rendering pipeline) can be tricky. And that’s when I realized configuring application with config files can be helpful. OGRE suddenly became very appealing to me and I really began to appreciate all the work the devs have put into it.

One good aspect of OGRE was the “unnecessary” script and configuration files. But the syntax of those files looked much cleaner than that of JSON:

// This is a comment
object_keyword Example/ObjectName
{
    attribute_name "some value"

    object_keyword2 "Nested Object"
    {
        other_attribute 1 2 3
        // and so on..
    }
}

I thought if I could harvest anything from OGRE into my OpenGL application, that would be the configuration based on this format (rather than Lua or whatever scripts).

Hence I crafted this simple grammar in ANTLR4 to parse these files:

grammar ConfigScript;

config : (object | comment)* EOF ;

object
    : Identifier '{' property* '}'
    | Identifier STRING '{' (property)* '}'
    ;

property : Identifier propertyValue ;

propertyValue
    : vector
    | INT
    | FLOAT
    | BOOL
    | STRING
    | objectValue
    ;

objectValue
    : '{' property* '}'
    | STRING '{' (property)* '}'
    ;

vector
    : INT+
    | FLOAT+
    ;

comment : LINE_COMMENT | BLOCK_COMMENT ;

STRING : DOUBLE_QUOTED_STRING | SINGLE_QUOTED_STRING ;

BOOL : 'true' | 'false' ;

DOUBLE_QUOTED_STRING : '"' DoubleQuoteStringChar* '"' ;
SINGLE_QUOTED_STRING : '\'' SingleQuoteStringChar* '\'' ;

Identifier : ALPHA (ALPHA | NUM)* ;

fragment SingleQuoteStringChar : ~['\r\n] ;
    // : ~['\\\r\n]
    // | SimpleEscapeSequence ;

fragment DoubleQuoteStringChar : ~["\r\n] ;
    // : ~["\\\r\n]
    // | SimpleEscapeSequence ;

// fragment SimpleEscapeSequence : '\\' ['"?abfnrtv\\] ;

INT : '0'
    | '-'? [1-9] [0-9]*
    ;

FLOAT : ('+' | '-')? NUM+ '.' NUM+ ;

WHITESPACE : [ \r\n\t]+ -> skip ;
ALPHA : [a-zA-Z_] ;
NUM : [0-9] ;

LINE_COMMENT : '//' ~[\r\n]* -> skip ;
BLOCK_COMMENT : '/*' .*? '*/' -> skip ;

The only difference is that the object name can only be a quoted string:

// This is a comment
object_keyword "Example/ObjectName" // <--- this can not be just Example/ObjectName
{
    attribute_name "some value"

    object_keyword2 "Nested Object"
    {
        other_attribute 1 2 3
        // and so on..
        /* block comment */
    }
}

The only thing left with this parser thing is to compile it and use in a project.

Read more

OpenGL: advanced samples

Damn this blog was long coming - I picked my interest in shaders over a decade ago, started to actually learn something in early 2021 and started writing this blog at the end of 2021. Now the time has finally come to share this with the world!

For a long time I was keen in learning low-level computer graphics APIs and algorithms, but only recently actually made any progress towards that goal. I have spent few weeks if not months learning about shaders, graphics pipeline and rendering techniques, so this write-up was long forecoming. There might be some mistakes, since I am not an expert in CG and OpenGL and there is a big chunk missing, namely rendering animated 3D models, compute shaders and tesselation, but I hope to fix those in the future.

One might ask: why OpenGL? Why not Vulkan (or DirectX 12)? Why even bother with these emulaiton techniques - why not jump straight to raytracing? Well, it is the end of October 2022 at the moment of publishing this blog, the most recent GPU on the market is GeForce RTX 4090, which is yet to arrive and its RRP (recommended retailer price) is A$2959 (as advertised by nVidia):

RTX4090 price as of October 2022

And most of those cards are gone in a blink of an eye and used for mining whatever-coins. My PC runs GTX1080, which is still more than enough for most of the games I play (being Genshin Impact at most).

I think it is still not a widely spread consumer market, and whilst raytracing, DLSS and all those fine things sound super cool and nice, it is still a niche market. That is not to say I won’t be looking into that in the near future. I just think OpenGL still has place in this world, at least as a starting point to build a decent understanding of the modern graphics pipeline, some basic rendering techniques and justify switching to more recent APIs. OpenGL as well as DirectX 11 are still a very feasible fallback for those sytems which do not run top-notch hardware or are struggling running those massive open-world games in anything higher than 1080p@60fps.

In this blog I will try to condense the knowledge I have acquired. I will skip most basic parts such as initializing context, creating window and so on, since most of the tutorials and articles on the Internet focus on those topics. Unlike most tutorials and articles out there, this blog will be all about rendering techniques.

This article was heavily inspired by few blogs on russian website (Habr), namely “super-modern OpenGL” (part 1 and part 2) - they are quite messy and lack a lot of material on really interesting topics (again, rendering techniques). This blog partially builds on top of those two and uses a lot more other materials (references provided).

This blog is enormous, so blow is the table of contents for the topics covered. Feel free to jump straight to the topic that picks your interest, screenshots are provided:

The source code is available on GitHub.

Read more

Message compression formats in a web application

I have seen quite a few web applications which are passing heaps of data between client and server. Pretty much all of them use JSON for that purpose. And whilst that solves the business problem, some of those applications aim to provide nearly real-time user experience, and that’s where the issues arise.

With the rise of web sockets, RTC and HTTP2 tech, the data transfer speed issues might be not so noticeable, but the more data app tries to transfer, the more pressing the matter gets. This issue also becomes more apparent on the server side - server has to process a lot more data in a request thread.

At The Trade Desk I have observed an approach, where we are transferring a list of strings (later we converted them to integers to widen the bandwidth) between high-loaded services (think 15 million requests per second with a hard time bound on request processing of 100 milliseconds).

I thought this is a cool concept, worth exploring deeper. For this matter, I have searched the Internet for similar approaches.

One of the readings was an article on the russian resource about speeding up a web application by switching from HTTP1 to HTTP2, utilizing various data compression formats: for static assets - WEBP, AVIF and progressive JPEG; for general data - various stream compression algorithms - GZIP, Brotli and ZSTD; alongside with different data serialization formats - MessagePack.

I decided to expand my search in the direction of serialization formats. In this article I compare few of those and focus on their performance in serializing different kinds of data (lists, nested objects, integers and strings, large and small datasets) and the serialization & deserialization performance in browser and the compression rates.

The formats covered are:

One of the optimizations we have achieved at The Trade Desk was 7 times reduction in data size by switching from string IDs to integer values. Think "something-else" we used to operate everywhere was assigned an integer ID of 4092. Now that int is 4 bytes long, whereas the string value is 14 bytes long. That is more than 3x reduction in size, but you have to still store the mapping somewhere, which we already did (in our case).

But the overall idea is worth researching too - how much compression each format provides when working with long lists of strings and long lists of ints.

To make the thing more interesting, I came up with few various data types to be messed around:

  • a simple object Pet { name: string, kind: enum Kind { CAT, DOG } }
  • an object with an array of string identifiers StringIdsResource { ids: string[] }
  • an object with an array of integer identifiers StringIdsResource { ids: int[] }

As mentioned before, the metrics I’m going to be focusing on are:

  • encoding & decoding performance in browser environment
  • encoded message length (raw, as UTF-8 string and base-64 encoded UTF-8 string)
  • amount of runtime (bundled code) required to work with the format

To make it quick and easy, here’s the summary (time measured in browser, on a nested object with a list of 1000 children of various data types):

Serializer Encoding time Decoding time Encoded data size (byte array) Compression Encoded data size (base-64 utf-8 encoded) Bundle size
Avro 12ms 4ms 30003 77.16% 40004 111.7kb
BSON 10ms 11ms 98912 24.71% 131884 98.0kb
CBOR 3ms 4ms 89017 32.24% 118692 30.1kb
MessagePack 3ms 3ms 89017 32.24% 118692 27.7kb
Protobuf 13ms 3ms 38000 71.07% 50668 76.6kb
Protobuf, compiled 6ms 1ms 38000 71.07% 50668 30.0kb
Flatbuffers 9ms 3ms 32052 75.60% 42736 3.1kb
Thrift (binary) 42ms 6ms 45009 65.74% 60012 109.7kb
Thrift (compact) 33ms 11ms 36005 72.59% 48008 109.7kb

Few learnings:

  • Thrift is quite slow and not that straightforward to use (after all, it was designed to provide entire communication layer for an application), but provides decent compression rate
  • Protobuf and Avro provide by far the most compact output (because of schema provided)
  • Protobuf library (protobufjs), unlike Avro, can’t handle enumerations (Protobufjs requires raw integer values to be used whereas Avro supports semantic, string values)
  • Cap’n’Proto seems outdated and its JS plugin did not get any support for few years now, have to check the TS version
  • FlatBuffers is quite low-level and tricky to use (much more effort than those other tools)

My take on these results is that:

  • Protobuf, when using a compiled serialzier/deserializer for specific message(-s):
    • has a comfortable API
    • fast serialization / deserialization in browser
    • decent compression rate
    • relatively small bundle size increase
  • Flatbuffers:
    • great compression rate
    • tiny bundle size impact
    • great performance in browser
    • super-cumbersome API (well, that’s low-level trade-offs for ya)

The source code for the tests could be found on my GitHub repo.

Under the cut you will find a stream of consciousness - my notes whilst implementing the tests for these tech.

Read more

Jargon-free functional programming. Part 1: problem statement

Basics

Let me introduce you functional programming with as few jargonisms and buzz-words as possible.

Shall we start with a simple problem to solve: get a random board game from top-10 games on BoardGamesGeek website and print out its rank and title.

BoardGameGeek website has an API: a request GET https://boardgamegeek.com/xmlapi2/hot?type=boardgame will return an XML document like this:

<?xml version="1.0" encoding="utf-8"?>

<items termsofuse="https://boardgamegeek.com/xmlapi/termsofuse">
    <item id="361545" rank="1">
        <thumbnail value="https://cf.geekdo-images.com/lD8s_SQPObXTPevz-aAElA__thumb/img/YZG-deJK2vFm4NMOaniqZwwlaAE=/fit-in/200x150/filters:strip_icc()/pic6892102.png" />
        <name value="Twilight Inscription" />
        <yearpublished value="2022" />
    </item>

    <item id="276182" rank="2">
        <thumbnail value="https://cf.geekdo-images.com/4q_5Ox7oYtK3Ma73iRtfAg__thumb/img/TU4UOoot_zqqUwCEmE_wFnLRRCY=/fit-in/200x150/filters:strip_icc()/pic4650725.jpg" />
        <name value="Dead Reckoning" />
        <yearpublished value="2022" />
    </item>
</items>

In JavaScript a solution to this problem might look something like this:

fetch(`https://boardgamegeek.com/xmlapi2/hot?type=boardgame`)
    .then(response => response.text())
    .then(response => new DOMParser().parseFromString(response, "text/xml"))
    .then(doc => {
        const items = Array.from(doc.querySelectorAll('items item'));

        return items.map(item => {
            const rank = item.getAttribute('rank');
            const name = item.querySelector('name').getAttribute('value');

            return { rank, name };
        });
    })
    .then(games => {
        const randomRank = Math.floor((Math.random() * 100) % 10);

        return games[randomRank];
    })
    .then(randomTop10Game => {
        const log = `#${randomTop10Game.rank}: ${randomTop10Game.name}`;

        console.log(log);
    });

Quick and easy, quite easy to understand - seems good enough.

How about we write some tests for it? Oh, now it becomes a little bit clunky - we need to mock fetch call (Fetch API) and the Math.random. Oh, and the DOMParser with its querySelector and querySelectorAll calls too. Probably even console.log method as well. Okay, we will probably need to modify the original code to make testing easier (if even possible). How about we split the program into separate blocks of code?

const fetchAPIResponse = () =>
    fetch(`https://boardgamegeek.com/xmlapi2/hot?type=boardgame`)
        .then(response => response.text());

const getResponseXML = (response) =>
    new DOMParser().parseFromString(response, "text/xml");

const extractGames = (doc) => {
    const items = Array.from(doc.querySelectorAll('items item'));

    return items.map(item => {
        const rank = item.getAttribute('rank');
        const name = item.querySelector('name').getAttribute('value');

        return { rank, name };
    });
};

const getRandomTop10Game = (games) => {
    const randomRank = Math.floor((Math.random() * 100) % 10);

    return games[randomRank];
};

const printGame = (game) => {
    const log = `#${game.rank}: ${game.name}`;

    console.log(log);
};

fetchAPIResponse()
    .then(response => getResponseXML(response))
    .then(doc => extractGames(doc))
    .then(games => getRandomTop10Game(games))
    .then(game => printGame(game));

Okay, now we can test some of the bits of the program without too much of a hassle - we could test that every call of getRandomGame returns a different value (which might not be true) but within the given list of values. We could test the extractGames function on a mock XML document and verify it extracts all the <item> nodes and its <name> child. Testing fetchAPIResponse and getResponseXML and printGame functions, though, would be a bit tricky without either mocking the fetch, console.log and DOMParser or actually calling those functions.

Read more

Jargon-free functional programming. Part 2: functional wrappers

Disclaimer

A big disclaimer before diving too deep: I am going to introduce all of the concepts without relying on any frameworks, libraries, specific programming languages and whatnot - just sticking to the hand-written TypeScript. This might seem like a lot of boilerplate and overhead for little benefit, but (with notes of a philosophy) the biggest benefit is in the cost of detecting and fixing errors in the code:

  • IDE highlighting an error (and maybe even suggesting a fix) - mere seconds of developer’s time
  • Local build (compiling the code locally, before pushing the code to the repository) - minutes, maybe tens of minutes
  • CI server build, running all the tests possible - around an hour
  • Pre-production environment (manual testing on dedicated QA / staging environment or even testing on production) - around few hours, may involve other people
  • Production - measured in days or months and risking the reputation with the customers

Hence if we could detect the errors while writing the code the first time - we could potentially save ourselves a fortune measured in both time and money.

Fancy-less introduction to functional programming

The ideas of functional programming are quite simple. In functional programming the assumption is that every function only operates on the arguments it has been passed and nothing else. It can not change the “outer world” - it can have values temporarily assigned to internal constants, nothing more - take it as there are no variables. A function should always return the same result for the same arguments, so functions are always predictable, no matter how many times you call them.

That sounds good and nice, but how does that solve the issues of the above problem, you might ask. For the most part the functions we have extracted already comply with the ideas of functional programming - do they not?

Well, not really. For once, fetching the data from the API is a big questionmark on how it fits into the picture of functional programming. Leaving the fetching aside, we have a random call in the middle. We also log some output to the console (and thus change the “outer world”, outside the printGame function).

For a lot of things like those, functional programming tries to separate the “pure functional operations” and “impure operations”.

See, in functional programming you operate these “pure functions”, which only use constants and inputs to produce their outputs. So a program would be nothing but a chain of function calls. With “simple” functions, returning the values which the next function in the chain can take as an input argument, this is quite easy.

Take the code above as an example:

fetchAPIResponse()
    .then(response => getResponseXML(response))
    .then(doc => extractGames(doc))
    .then(games => getRandomTop10Game(games))
    .then(game => printGame(game));

This could have been written as

fetchAPIResponse()
    .then(response =>
        printGame(
            getRandomTop10Game(
                extractGames(
                    getResponseXML(response)
                )
            )
        )
    );

Since each next function in the chain accepts exactly the type the previous function has returned, they all combine quite well.

JFYI: in other languages and some libraries there are operators to combine functions into one big function:

fetchAPIResponse()
    .then(response =>
        _.flow([ getResponseXML, extractGames, getRandomTop10Game, printGame ])(response)
    );

or

fetchAPIResponse()
    .then(response ->
        getResponseXML.andThen(extractGames).andThen(getRandomTop10Game).andThen(printGame).aplly(response)
    );

You will understand why this matters in a minute.

There are also functions which need to interact with the outer world. In that case, functional programming suggests that we wrap them in specific constructions and do not run them immediately. Instead, we weave them into the program, describing what would happen to the result of the wrapped function call when we get one. This makes programs again, “pure functional”, “safe” (as in not operating outside of the boundaries of the program itself, all is contained in the function call chains). Then, once we run the program, we enter the world of “unsafe” and execute all those wrapped functions and run the rest of the code once we get the results in place.

Sounds a bit hard to comprehend.

Let me rephrase this with few bits of code.

For the problem above, we are trying to get the response of an API somewhere in the outer world. This is said to be an “unsafe” operation, since the data lives outside of the program, so we need to wrap this operation in a “safe” manner. Essentially, we will create an object which describes an intention to run the fetch call and then write our program around this object to describe how this data will be processed down the line, when we actually run the program (and the fetch request together with it).

Let’s go through the thought process all together: we first need a class to wrap an unsafe function without executing it:

class IO {
    constructor(private intentionFunc: Function;) {
    }
}

We then need a way to explicitly execute this function when we are ready to do so:

class IO {
    constructor(private intentionFunc: Function;) {
    }

    unsafeRun() {
        this.intentionFunc();
    }
}

The last piece is we want to be able to chain this function with some other function in a safe manner (e.g. again, wrap the chained function):

class IO {
    constructor(private intentionFunc: Function) {
    }

    andThen(func: Function) {
        return new IO(() => func(this.intentionFunc()));
    }

    unsafeRun() {
        this.intentionFunc();
    }
}

Essentially, we save the function we intend to run in the intentionFunc member of an IO class. When we want to describe what would happen to the result of the data, we return a new IO object with a new function - a combination of a function we will call around the call to the function we saved. This is important to understand why we return a new object: so that we do not mutate the original object.

You might see this new IO thing is very similar to the Promise available in JS runtime already. The similarities are obvious: we also have this chaining with the then method. The call to the then method also returns a new object.

But the main issue with Promise is that they start running the code you passed in the constructor immediately. And that is exactly the issue we are trying to resolve.

Now, let us see how we would use this new IO class in the original problem:

new IO(() => fetch(`https://boardgamegeek.com/xmlapi2/hot?type=boardgame`))

That would not work, however, since fetch call will return a Promise. So we need to somehow work with Promise instances instead. Let me postpone this discussion for a short while.

Spoiler: we could have tried implementing an unpromisify helper which would make the fetch call synchronous, something like this:

const unpromisify = (promiseFn: Function) => {
    const state = { isReady: false, result: undefined, error: undefined };

    promiseFn()
        .then((result) => {
            state.result = result;
            state.isReady = true;
        })
        .catch((error) => {
            state.error = error;
            state.isReady = true;
        });

    while (!state.isReady);

    if (state.error) {
        throw state.error;
    }

    return state.result;
};

But in JS world, promises start executing not immediately, but once you leave the context of a currently running function. So having that endless while loop, waiting for a promise to get resolved has zero effect since this loop will be running until the end of days, but unless you exit the function beforehand, the promise won’t start executing because JS is single threaded and the execution queue / event loop prevents you from running the promise immediately.

End of spoiler

Read more

Jargon-free functional programming. TL;DR

This is a boiled-down version of a much longer read, Jargon-free functional programming, giving a brief and visual introduction to the concepts of a real-world functional programming. This blog is aimed at people who already know something about programming and want to learn what the heck functional programming is, how is it different to “normal” programming and how does it look like in a real world.

In a non-functional world, the code we write depends on anything - a function, aside from its arguments, is free to use environment variables, global variables, outer scope, dependency injection - pretty much anything.

Moreover, it can modify all of the above (including outer scope, global and environment variables, etc.).

In a functional programming world we restrict a function to only rely on its arguments (or nothing at all).

But what about things like databases, user input, network communication, exceptions?

A typical application involving all of the above could be explained algorithmically as the endless loop, waiting for some input to appear before doing something (waiting for database query to complete, waiting for user to provide input, waiting for a network request to complete).

And every step of the program is described as a sequence of actions (potentially involving some rather trivial decision making). This approach is known as “imperative programming” and is very commonly used.

In reality, however, every step of this algorithm can go wrong in many different ways - each step is free to modify some global state (think OS and filesystem), it can fail terribly with an exception. Moreover, anything from the outside world (think OS or dependency injection) can break into the program and change any value or state of the program.

In a functional programming world, functions (and programs) are not described as sequences of commands - instead, they are more like recipes for calculations that will happen once all the requirements are provided.

The way to handle all the nifty things such as exceptions, networking, databases, etc. is to wrap a function which works with a result of the “unsafe” operation in a safe container. This container won’t execute the function - just hold it for a while. However, this container would have two special properties: an ability to run the underlying function when it is deemed safe and an ability to be connected to other containers of the same type.

Each container will perform its very specific role - handling exceptions to return a value instead of breaking, running some input-output operations (incl. networking and databases), etc. We assume containers already do these operations in a safe manner - meaning they do not change anything in the program outside of themselves (think global variables, outer scope, etc.) and they always return a value. They only execute the function they wrap once requested explicitly.

By making it so that safe containers of different types can not be chained, we eliminate the chance of unexpected program failure. And we make sure at any point in time we can say what a program is doing exactly by just looking at its types.

By connecting such containers in a chain, we make programs.

But these chains do not do anything until they are explicitly executed.

A program is a chain of functions, wrapped in “safe” constructs, which is executed “at the end / edge of the world” - meaning program is thought to be executed only once. If all the blocks of this chain of containers succeed - the entire program succeeds.

If any of the blocks fails - the program does not exit or terminates, the failed block simply returns a different value.

All the logic is hidden in those “safe” constructs - it is isolated from the rest of the world.

Those containers are only allowed access to their direct arguments. It is guaranteed to never break and always return a value (which might be wrapped in another “safe” construct).

A program made of these safe recipes on how to calculate the result is just another recipe itself - essentially a series of recipes.

This safe set of recipes is then thrown together with a bunch of inputs into a grinder called “real world”, where nothing is safe and everything can happen (theoretically).

In the grinder, the dish is being cooked from the inputs, following the recipes thrown to the grinder. The result of this cooking might be another program itself, which can then be recycled by being thrown back into the grinder - that would happen if a program enters the (infinite) loop, waiting for some inputs - it is essentially becomes a new program, which also needs to be executed when all the requirements are met.

In order to build one of those containers, one starts by creating a simple class.

The class must hold a function without running it.

There should be a way to link (chain) this container with some other function, creating a new safe container.

And finally there should be a way to execute the function wrapped by this safe container.

The details of each container’ implementation is what makes them different. For few examples, the container which makes an arbitrary function safe (in this case we assume it does some input-output stuff) could look like this:

class IO <A> {
    constructor(private f: () => A) {
    }

    andThen<B>(g: (_: A) => B) {
        return new IO(() => g(this.f()));
    }

    unsafeRun() {
        this.f();
    }
}

A container which wraps a function returning a Promise might look similar (except all the dancing around Promise API):

class PromiseIO <A> {
    constructor(private readonly f: () => Promise<A>) {}

    andThen<B>(g: (_: A) => B) {
        return new PromiseIO<B>(() => this.unsafeRun().then(g));
    }

    unsafeRun() {
        return this.f();
    }
}

You can see the pattern - these classes all have very similar interface. Hence you can extract it:

interface Container <A> {
    andThen<B>(g: (_: A) => B): Container<B>;
}

class IO <A> implements Container <A> { ... }

class PromiseIO <A> implements Container <A> { ... }

Then you can create a container which wraps a function which might throw an exception (together with its error handler):

class Try <A> implements Container <A> {
    constructor(private readonly f: () => Container<A>, private readonly errorHandler: (_: unknown) => Container<A>) {}

    andThen<B>(g: (_: A) => B) {
        return new Try<B, E>(
            () => this.f().andThen(g),
            (e) => this.errorHandler(e).andThen(g)
        );
    }

    unsafeRun() {
        try {
            return this.f();
        } catch (e) {
            return this.errorHandler(e);
        }
    }
}

Then you can write programs using these containers:

const fetchSomeResponse = () => new PromiseIO(() => fetch('/').then(r => r.text()));

const processResponse = (response: string) =>
    new Try(
        () => new IO(() => console.log('OK', response)),
        (e) => new IO(() => console.error('ERR', e))
    );

const program = fetchSomeResponse()
    .andThen(processResponse)
    .andThen(t => t.unsafeRunTry())
    .andThen(io => (io as IO<void>).unsafeRun())
    .unsafeRun();

The next article contains a few examples and explains the above in bloody details, using TypeScript and a (semi-)real-world problem and a step-by-step approach to arrivin at the above concepts. It also introduces few more of those containers so you can actually go out and understand some (if not most) of the real-world applications made with functional paradigm. Or even build your own!

.gitignore is not ignoring

This is going to be a very short blog. I have been struggling with this issue for few days now - having a seemingly valid .gitignore file which does not make Git ignore any of the files.

The .gitignore file contents:

node_modules

**/*.bundle.js
*.log

*compiled-proto*
*compiled-bundle*

Running git status:

$ git st
On branch master
Untracked files:
  (use "git add <file>..." to include in what will be committed)
        node_modules/
        test1/flatbuffers-compiled-proto/
        test5/index.bundle.js
        test5/test5-avro.bundle.js
        test5/test5-bson.bundle.js
        test5/test5-cbor.bundle.js
        test5/test5-flatbuffers-compiled-proto/
        test5/test5-flatbuffers-compiled.bundle.js
        test5/test5-messagepack.bundle.js
        test5/test5-protobuf-compiled-proto.js
        test5/test5-protobuf-compiled.bundle.js
        test5/test5-protobuf.bundle.js

nothing added to commit but untracked files present (use "git add" to track)

Weird, isn’t it?

There is a command which checks if a given path (whatever you pass as a parameter to the command, so technically just a string) would be ignored by any of the rules in .gitignore file or not:

git check-ignore --verbose <path>

Let’s run it on my repo:

$ git check-ignore --verbose node_modules

No output means the path (in this case - node_modules) will not be ignored. Which should not be the case - there’s a rule as the first line of the .gitignore file, right?!

The issue seems to be somewhat hidden - the file was saved in the UTF16-LE encoding, since I have used PowerShell to initialize the file with echo 'node_modules' >> .gitignore:

And seems like the valid encoding for .gitignore file would be UTF-8. Let’s use VSCode itself to save it in UTF-8 instead and try it again:

$ git check-ignore --verbose node_modules
.gitignore:1:node_modules       node_modules

That output tells us the rule in the first line, namely node_modules (no asterisks or slashes) ignores the path node_modules. Issue solved!