[Hiding IO Bryan O'Sullivan **20080409061727] { move ./examples/ch29/HandleT.hs ./examples/ch16/MonadHandle.hs adddir ./examples/ch17 addfile ./examples/ch16/HandleIO.hs addfile ./examples/ch16/handleIO.ghci addfile ./examples/ch16/monadio.ghci hunk ./en/ch16-monad-case.xml 823 + + + + Hiding the IO monad + + The blessing and curse of the IO monad is that + it is extremely powerful. If we believe that careful use of + types helps us to avoid programming mistakes, then the + IO monad should be a great source of unease. + Because the IO monad imposes no restrictions on + what we can do, it leaves us vulnerable to all kinds of + accidents. + + How can we tame its power? Let's say that we would like to + guarantee to ourselves that a piece of code can read and write + files on the local filesystem, but that it will not access the + network. We can't use the plain IO monad, because + it won't restrict us. + + + Using a newtype + + Let's create a module that provides a small set of + functionality for reading and writing files. + + &HandleIO.hs:module; + + Our first approach to creating a restricted version of + IO is to wrap it with a &newtype;. + + &HandleIO.hs:newtype; + + We do the by-now familiar trick of exporting the type + constructor and the runHandleIO execution + function from our module, but not the data constructor. This + will prevent code running within the HandleIO + monad from getting hold of the IO monad that it + wraps. + + All that remains is for us to wrap each of the actions we + want our monad to allow. This is a simple matter of wrapping + each IO with a HandleIO data + constructor. + + &HandleIO.hs:actions; + + We can now use our restricted HandleIO monad + to perform I/O. + + &HandleIO.hs:safeHello; + + To run this action, we use + runHandleIO. + + &handleIO.ghci:HandleIO; + + If we try to sequence an action that runs in the + HandleIO monad with one that is not permitted, + the type system forbids it. + + &handleIO.ghci:bad; + + + + Designing for unexpected uses + + There's one small, but significant, problem with our + HandleIO monad: it doesn't take into account the + possibility that we might occasionally need an escape hatch. + If we define a monad like this, it is likely that we will + occasionally need to perform an I/O action that isn't allowed + for by the design of our monad. + + Our purpose in defining a monad like this is to make it + easier for us to write solid code in the common case, not to + make corner cases impossible. Let's thus give ourselves a + way out. + + The Control.Monad.Trans module defines a + standard escape hatch, the MonadIO + type class. This defines a single function, + liftIO, which lets us embed an + IO action in another monad. + + &monadio.ghci:MonadIO; + + Our implementation of this type class is trivial: we just + wrap IO with our data constructor. + + &HandleIO.hs:MonadIO; + + With judicious use of liftIO, we can + escape our shackles and invoke IO actions where + necessary. + + &HandleIO.hs:tidyHello; + + + Automatic derivation and MonadIO + + We could have had the compiler automatically derive an + instance of MonadIO for us by adding the type + class to the deriving clause of + HandleIO. This would be our usual strategy in + production code. The only reason we didn't do this was to + introduce MonadIO after the initial + concepts. + + + + + Using type classes + + Write me! + hunk ./en/ch17-monad-trans.xml 3 - - FIXME (Monad Transformers / DONS) - FIXME. + + Monad transformers + + Monads provide a powerful way to build computations with + effects. Each of the standard monads is specialised to do exactly + one thing. Quite often, this does not fit our real world + needs. + + Recall the Parse type that we developed in + . When we introduced monads, we + mentioned that this type was a state monad in disguise. However, + it's a little more complex than the standard State + monad, because it uses the Either type to allow the + possibility of a parsing failure. If a parse fails early on, we + want to stop parsing, not continue in some broken state. + + Even if we were to recast Parse as an instance of + the Monad type class, we can't simply drop it and use + State instead. The State monad uses the + default implementation of fail: this calls + error, which throws an exception that we + can't catch in pure code. The State monad thus + appears to allow for failure, without + actually being any use. Once again, we recommend that you almost + always avoid using fail. + + There is no joy in the prospect of having to hand-craft a new + monad every time we want behaviour that differs slightly from that + provided by some standard monad. Fortunately, we can + combine monads by layering them: for example, + we can take the standard State monad, and add the + possibility of failure to it. + + We call one of these layering monads a monad + transfomer, because it modifies the behaviour of an + underlying monad. This finally gives us an explanation of the + name of the standard mtl library, where most of the + standard monads are defined: it's the monad transformer library. + It defines both normal monads and transformer versions of most of + them. + hunk ./examples/ch16/HandleIO.hs 1 +{-- snippet module --} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} + +module HandleIO + ( + HandleIO + , Handle + , IOMode(..) + , runHandleIO + , openFile + , hClose + , hPutStrLn + ) where + +import System.IO (Handle, IOMode(..)) +import qualified System.IO +{-- /snippet module --} +import System.Directory (removeFile) + +{-- snippet MonadIO --} +import Control.Monad.Trans (MonadIO(..)) + +instance MonadIO HandleIO where + liftIO = HandleIO +{-- /snippet MonadIO --} + +{-- snippet newtype --} +newtype HandleIO a = HandleIO { runHandleIO :: IO a } + deriving (Monad) +{-- /snippet newtype --} + +{-- snippet actions --} +openFile :: FilePath -> IOMode -> HandleIO Handle +openFile path mode = HandleIO (System.IO.openFile path mode) + +hClose :: Handle -> HandleIO () +hClose = HandleIO . System.IO.hClose + +hPutStrLn :: Handle -> String -> HandleIO () +hPutStrLn h s = HandleIO (System.IO.hPutStrLn h s) +{-- /snippet actions --} + +{-- snippet safeHello --} +safeHello :: FilePath -> HandleIO () +safeHello path = do + h <- openFile path WriteMode + hPutStrLn h "hello world" + hClose h +{-- /snippet safeHello --} + +{-- snippet tidyHello --} +tidyHello :: FilePath -> HandleIO () +tidyHello path = do + safeHello path + liftIO (removeFile path) +{-- /snippet tidyHello --} hunk ./examples/ch16/MonadHandle.hs 1 -module HandleT +{-# LANGUAGE FunctionalDependencies, GeneralizedNewtypeDeriving, + MultiParamTypeClasses, TypeSynonymInstances #-} + +module MonadHandle hunk ./examples/ch16/MonadHandle.hs 12 +import Control.Monad.Writer hunk ./examples/ch16/MonadHandle.hs 14 -import System.IO (Handle, hClose) +import System.IO (IOMode(..)) + +class Monad m => MonadHandle h m | m -> h where + openFile :: FilePath -> IOMode -> m h + hPutStrLn :: h -> String -> m () + hClose :: h -> m () + +instance MonadHandle System.IO.Handle IO where + openFile = System.IO.openFile + hPutStrLn = System.IO.hPutStrLn + hClose = System.IO.hClose + +safeHello :: MonadHandle h m => FilePath -> m () +safeHello path = do + h <- openFile path WriteMode + hPutStrLn h "hello world" + hClose h hunk ./examples/ch16/MonadHandle.hs 32 -class MonadIO m => MonadHandle m where - hGetContents :: Handle -> m String - hGetContents = liftIO . System.IO.hGetContents +data Event = Open FilePath IOMode + | PutStrLn String String + | Close String + deriving (Show) hunk ./examples/ch16/MonadHandle.hs 37 - hPutStr :: Handle -> String -> m () - hPutStr h = liftIO . System.IO.hPutStr h +newtype WriterIO a = W { runW :: Writer [Event] a } + deriving (Monad, MonadWriter [Event]) hunk ./examples/ch16/MonadHandle.hs 40 - hPutStrLn :: Handle -> String -> m () - hPutStrLn h = liftIO . System.IO.hPutStrLn h +runWriterIO :: WriterIO a -> (a, [Event]) +runWriterIO = runWriter . runW hunk ./examples/ch16/MonadHandle.hs 43 -instance MonadHandle IO +instance MonadHandle FilePath WriterIO where + openFile path mode = tell [Open path mode] >> return path + hPutStrLn h str = tell [PutStrLn h str] + hClose h = tell [Close h] hunk ./examples/ch16/handleIO.ghci 1 +--# HandleIO +:load HandleIO +runHandleIO (safeHello "hello_world_101.txt") +:m +System.Directory +removeFile "hello_world_101.txt" + +--# bad +runHandleIO (safeHello "goodbye" >> removeFile "goodbye") hunk ./examples/ch16/monadio.ghci 1 +--# MonadIO +:m +Control.Monad.Trans +:info MonadIO }