Search code examples
haskellstate-monad

Hide a function parameter in Haskell?


I need to backup some data to access it later.

At the interface level, I have two functions:

  • put: backs up data and returns a backup_Id.

  • get: retrieves data given a backup_Id.

My current code requires me to supply these two functions with the backup parameter.

import Data.Maybe

data Data = Data String deriving Show

type Backup = [(String,Data)]

put :: Backup -> String -> IO Backup
put boilerPlate a = 
    do let id = "id" ++ show(length (boilerPlate))
       putStrLn $ id ++": " ++ a
       return ((id,(Data a)):boilerPlate)

get :: Backup -> String -> Maybe Data
get boilerPlate id = lookup id (boilerPlate)

It works OK.

In the following sample, two values are backed up. The second one is retrieved.

main :: IO ()
main = do
    let bp0 = []
    bp1 <- put bp0 "a"
    bp2 <- put bp1 "b"
    let result = get bp2 "id1"
    putStrLn $ "Looking for id1: " ++ show (fromJust(result))

But I need to simplify the signatures of put and get by getting rid of all the backup parameters.

I need something that looks like this:

main = do
    put "a"
    put "b"    
    let result = get "id1"

What is the simplest way to achieve this?


Solution

  • Here's an example using StateT. Note that the function names are changed because State and StateT already have get and put functions.

    module Main where
    import Control.Monad.State
    
    data Data = Data String deriving Show
    type Backup = [(String,Data)]
    
    save :: String -> StateT Backup IO ()
    save a = do
      backup <- get
      let id = "id" ++ ((show . length) backup)
      liftIO $ putStrLn $ id ++ ": " ++ a
      put ((id, Data a):backup)
    
    retrieve :: String -> StateT Backup IO (Maybe Data)
    retrieve id = do
      backup <- get
      return $ lookup id backup
    
    run :: IO (Maybe Data)
    run = flip evalStateT [] $ do
      save "a"
      save "b"
      retrieve "id1"
    
    main :: IO ()
    main = do
      result <- run
      print result
    

    The State monad threads a 'mutable' value through a computation. StateT combines State with other monads; in this case, allowing the use of IO.

    As dfeuer mentioned, it is possible to make save and retrieve a bit more general with these types:

    save :: (MonadState Backup m, MonadIO m) => String -> m ()
    retrieve :: (MonadState Backup m, MonadIO m) => String -> m (Maybe Data)
    

    (This also requires {-# LANGUAGE FlexibleContexts #-}) The advantage of this approach is that it allows our functions to work with any monad that provides the Backup state and IO. In particular, we can add effects to the monad and the functions will still work.

    All this monad / monad transformer stuff can be pretty confusing at first, but it's actually pretty elegant once you get used to it. The advantage is that you can easily see what kind of effects are required in each function. That being said, I don't want you to think that there are things that Haskell can't do, so here's another way to achieve your goal which does away with the state monad in favor of a mutable reference.

    module Main where
    import Data.IORef
    
    data Data = Data String deriving Show
    type Backup = [(String,Data)]
    
    mkSave :: IORef Backup -> String -> IO ()
    mkSave r a = do
      backup <- readIORef r
      let id = "id" ++ ((show . length) backup)
      putStrLn $ id ++ ": " ++ a
      writeIORef r ((id, Data a):backup)
    
    mkRetrieve :: IORef Backup -> String -> IO (Maybe Data)
    mkRetrieve r id = do
      backup <- readIORef r
      return $ lookup id backup
    
    main :: IO ()
    main = do
      ref <- newIORef []
      let save = mkSave ref
          retrieve = mkRetrieve ref
      save "a"
      save "b"
      result <- retrieve "id0"
      print result
    

    Just be warned that this isn't usually the recommended approach.