Skip to content

Instantly share code, notes, and snippets.

@friedbrice
Last active May 7, 2019 16:52
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 friedbrice/15fab3f085dcd77447d8b55486d8b478 to your computer and use it in GitHub Desktop.
Save friedbrice/15fab3f085dcd77447d8b55486d8b478 to your computer and use it in GitHub Desktop.
"Mmm, Cake" or "A Method of Application Wiring for Large-Scale Haskell Programs"
module App where
-- Write the parts of your program that do IO in MTL style,
-- but don't use the `MonadIO` class. -_-
-- This is Layer 2. Layer 3 (not shown) is business logic.
class Foo m where
foo :: String -> m ()
class Bar m where
bar :: m String
myProgram :: (Monad m, Foo m, Bar m) => m ()
myProgram = undefined
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
-- Create a newtype IO' that instances the needed classes,
-- but don't export IO' or the instances. -_-
-- (Notice, no module decl here.)
-- This is Layer 1.
import App
import Control.Monad.Reader
data FooHandle
-- call some external library code, no need to test
foo' :: FooHandle -> String -> IO ()
foo' = undefined
data BarHandle
-- call some external library code, no need to test
bar' :: BarHandle -> IO String
bar' = undefined
data Config = Config
{ fooHandle :: FooHandle
, barHandle :: BarHandle
}
-- should be straightforward enough, no need to test
getConfig :: IO Config
getConfig = undefined
newtype IO' a = IO' { getIO' :: ReaderT Config IO a }
deriving (Functor, Applicative, Monad)
instance Foo IO' where
foo str = IO' $ do
conf <- ask
liftIO $ foo' (fooHandle conf) str
instance Bar IO' where
bar = IO' $ do
conf <- ask
liftIO $ bar' (barHandle conf)
main :: IO ()
main = getConfig >>= (runReaderT . getIO') myProgram
@friedbrice
Copy link
Author

Notice, the title says this is "for Large Scale Haskell Programs." For small-scale programs, there are much simpler methods (e.g. pass callbacks that do the I/O when you decide you want to test some function).

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment