Create persistent `Map` populated from `main`

Don’t know if the answer here would be too involved but a hint of what I need to learn would be great.

data RobotPart = RobotPart
  {
    partId :: Int
  , name :: T.Text
  , description :: T.Text
  , cost :: Double
  } deriving Show

From main I’m reading in a file and turning the data into [(Int, RobotPart)]. I want to create a Map using Map.fromList and have it persist for the life of the program and have it accessible to other functions that take user input such as getPart 1 and compareParts 1 2.

In JS I would I would ask something like, “how to dynamically populate a module level object”, and the answer would be (skinny version in pseudo code for brevity)

const partsDb = list => {
  const myMap = new Map()
  if (list == undefined && myMap.size > 0 ) {
    return myMap
  } else {
    myMap.populate list 
    return myMay
  }
}

The key here is that list is an optional parameter

The Haskell program will essentially be

partsDB :: Map.Map Int RobotPart 

main = do
  - read the file
  - x = `[(Int,RobotPart)]` process the data to this form
  - somehow set: `partsDB.fromList x`

getPart = do
  - getLine
  - partsDb.lookup ...
  - print result

comparePartPrices = do
  - getLine
  - process input to parts
  - perform compare
  - print result

…so in other words, you’re trying to disguise an inherently-mutable data source - a file in this case - as a regular (immutable) Haskell value:

No, but my intuition is all imperative (JavaScript, early C#). I just read a chapter in a book last week on IO which made a big point of how stuff needs to stay in the IO context, no escape hatch, but my mind just lead me right down a habitual path.

…yeah, the ol’ “force of habit” - using I/O in Haskell is a common cause of relapse.

Back to the current problem: if all you intend to do is read from partsDB, the simplest option is to use the reader-monad transformer to convey it throughout your program to where it’s needed, ideally as a new ADT. As for main:

main :: IO ()
main = do ...
          partsDB <- dbFromFile filepath
          ...
          runM programM partsDB >>= ...
          ...

dbFromFile :: FilePath -> IO (Map.Map Int RobotPart)
runM :: M a -> Map.Map Int RobotPart -> IO a
programM :: M a
                        ⋮

where M is the (monadic) ADT.

2 Likes

You don’t actually need anything fancy, you just need to use monads. I think that you might need to go back over the section on monads in your book, especially if it introduced IO with do notation before monads themselves. Do notation is an incredibly clever piece of syntax, but it obscures what’s actually happening if you aren’t intimately familiar with >>= and >>. This code is not elegant, there are definitely problems with it in terms of style and best practices, but it’s deliberately simple in order to demonstrate what’s going on with do notation and how >>= allows you to make a piece of data “persist for the life of the program” and “have it [be] accessible to other functions”:

import Data.Map as Map

data RobotPart = RobotPart
  {
    partId :: Int
  , name :: String
  , description :: String
  , cost :: Double
  } deriving Show

type MyMap = Map.Map Int RobotPart

-- The next three definitions exist just to generate a map without me having
-- to write the parsing myself
robotArm :: RobotPart
robotArm  = RobotPart 1 "arm"  "its the arm"    4.2

robotHead :: RobotPart
robotHead = RobotPart 2 "head" "its the head"  10.1

createIOMap :: String -> IO MyMap
createIOMap str = return . Map.fromList $ [(1, robotArm), (2, robotHead)]
-- In your program all of this will be replaced with your function that takes
-- a string and returns an IO Map of robot parts

-- All of the Maybes here are because Map.lookup returns a Maybe value
getPart :: MyMap -> IO ()
getPart myMap = do
  input <- getLine
  putStrLn $ handleFailure $ name <$> Map.lookup (read input) myMap
    where
      handleFailure :: Maybe String -> String
      handleFailure (Just str) = str
      handleFailure Nothing    = "Lookup failed"

-- This doesn't handle the domain correctly, but I don't want to write out the whole logic
comparePartPrices :: MyMap -> IO ()
comparePartPrices myMap = do
  first  <- getLine
  second <- getLine
  putStrLn $ handleMessage $ comparison (read first) (read second)
    where
      comparison :: Int -> Int -> Bool
      comparison n m = (cost <$> Map.lookup n myMap) < (cost <$> Map.lookup m myMap)

      handleMessage :: Bool -> String
      handleMessage True  = "The second one costs more"
      handleMessage False = "Either the first costs more, they cost the same, or the look up failed"

main :: IO ()
main = do
  inputText <- readFile "myfile.txt"
  myMap <- createIOMap inputText
  getPart myMap
  comparePartPrices myMap
  getPart myMap
  putStrLn "Hello"
  getPart myMap
  comparePartPrices myMap
  putStrLn "Compare again?"
  comparePartPrices myMap
  getPart myMap
  putStrLn "Goodbye"

The long string of function calls in main is just to show that you can reuse the map multiple times, it exists throughout all of main and everything ‘has access’ to it, in the sense that it’s a piece of data with a name that you can pass into your functions. The putStrLns are there to show that you don’t need to use myMap every line. (I also changed Text to String, for simplicity.) One part about the code that you should try to ignore for the purposes of learning from this is that there are a lot of Maybe values hanging around, and helper functions to deal with them. That is solely because Map.lookup returns a Maybe v instead of just a v, so you need to account for that when you’re passing the result of a lookup around. But, again, that isn’t important for your main question.

Do notation translates into >>= and >>. Without do, and with indentation to make it readable instead of one long line, main looks like this:

-- This is not concise syntax, so if you type it into your IDE hlint will tell
-- you to change it, but it's semantically the same as above.
main' :: IO ()
main' = 
  readFile "myfile.txt" 
    >>= 
      \inputText 
        -> createIOMap inputText 
          >>= 
            \myMap
              -> getPart myMap 
              >> comparePartPrices myMap 
              >> getPart myMap
              >> putStrLn "Hello"
              >> getPart myMap
              >> comparePartPrices myMap
              >> putStrLn "Compare again?"
              >> comparePartPrices myMap
              >> getPart myMap
              >> putStrLn "Goodbye"

When you use name <- value syntax in a do block, you’re really writing value >>= \name ->. That is, you’re taking the monadic value value, turning everything after it into a function of name, and then giving both of those to >>=. So, if you want to have a piece of data of type t that ‘persists’ and ‘is accessible’, but the value is ‘stuck’ in the IO monad, you use >>= to feed it through to your functions that take t by itself and return something else of type IO.

Like I said at the beginning, this isn’t high quality code, but as far as I understand what your question is, this is a simple way to do what you’re trying to do and it demonstrates how IO is a monad. There are fancier ways to do this, and there are also just better, more sound ways to do it, but from your question it felt to me like you’re really just having issues with the idea of monads and what do notation actually is.

So my advice ultimately is the same as above: go over the sections of your book on monads and I/O again. It has been said a million times but I’ll repeat it, the best way to learn monads is to just follow the types. Stare at the type of >>= for as many hours as it takes until it makes sense, writing as much practice code as you can. It’s exactly the same as learning the epsilon-delta definition of a limit. Stare at the picture for as long as it takes until you understand what’s going on, and then worry about forcing yourself to become comfortable with the mechanics of manipulating absolute value inequalities.

I don’t think that you should worry about learning what a monad transformer is, yet, especially if your goal is just to read a specification file once that tells you what each robot part is and then turn that into a map of parts that you’ll use for the rest of the program. But let me know if I misunderstood what your issue actually is.

1 Like

Thank you for that! Your use of IO types, >>= & >> are very helpful.
I think you suggestion for learning is spot on. After @atravers post I took a look at Reader and realized I had not learned about Monad yet and needed to do so.

That could be useful - JS has supported the async/await model of asynchronous programming since 2017.

Taking the hint from JS along with:

async        :: ((forall a . Await a) -> b) -> IO b  -- primitive
type Await a = IO a -> a

class Monad m where
    return   :: a -> m a
    (>>=)    :: m a -> (a -> m b) -> m b

instance Monad IO where
    return x = async $ \ await -> x
    m >>= k  = async $ \ await -> let !x = await m in
                                  let !y = await (k x) in
                                  y

If needed, there are also some tutorials about the monadic interface.

2 Likes