Skip to content

Instantly share code, notes, and snippets.

@eborden
Last active June 7, 2017 02:37
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save eborden/6ec131fe78d24bce404580ff2958a9b8 to your computer and use it in GitHub Desktop.
Save eborden/6ec131fe78d24bce404580ff2958a9b8 to your computer and use it in GitHub Desktop.
An example of using MTL and "mock" interpretation.
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Main where
import Prelude hiding (readFile, writeFile)
import Control.Monad.Trans
import Control.Monad.State
import qualified System.IO as SIO
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Maybe
-- First we define a type class to abstract over a simple file system.
-- It can write to a file path and read from a file path. Simple.
-- A complete file system would of course be more complex.
class Monad m => MonadFS m where
writeFile :: FilePath -> String -> m ()
readFile :: FilePath -> m String
-- Then we make an instance for our file system over IO. Again this is
-- very simple. We just sub in `writeFile` and `readFile` from `System.IO`.
instance MonadFS IO where
writeFile = SIO.writeFile
readFile = SIO.readFile
-- Now lets make a pure version of our file system. We'll call it `VirtualFS`.
-- This is just the `StateT` monad transformer. It contains a Map to model our simple
-- file system.
newtype VirtualFS m a = VirtualFS { runVirtualFS :: StateT (Map FilePath String) m a }
-- We can use `GeneralizedNewtypeDeriving` to derive a host of useful type classes
-- like Functor, Monad, etc.
deriving (Functor, Applicative, Monad, MonadTrans, MonadState (Map FilePath String))
-- This also has a simple implementation. We just insert "files" in our Map and
-- look them up from the same Map.
instance Monad m => MonadFS (VirtualFS m) where
writeFile path str = do
fs <- get
put $ Map.insert path str fs
readFile path = do
fs <- get
pure . fromMaybe (error "uninitialized file") $ Map.lookup path fs
-- Now we can implement a simple function to write to a file and then read from it.
writeAFileAndReadIt :: MonadFS m => m String
writeAFileAndReadIt = do
writeFile ":test:" "hello world"
readFile ":test:"
main :: IO ()
main = do
-- Now we interpret it with IO
print =<< writeAFileAndReadIt
-- Or we can interpret with our pure virtual fs.
print . flip evalState mempty . runVirtualFS $ writeAFileAndReadIt
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment