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 putStrLn
s 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.