Difference between revisions of "Avoiding IO"

From HaskellWiki
Jump to navigation Jump to search
(unsafePerformIO is for encapsulating function that have no observable side effects)
m
Line 4: Line 4:
 
It is hard to test them, because they can in principle depend on every state of the real world.
 
It is hard to test them, because they can in principle depend on every state of the real world.
 
Thus in order to maintain modularity you should avoid IO wherever possible.
 
Thus in order to maintain modularity you should avoid IO wherever possible.
It is too tempting to get rid of IO by <hask>unsafePerformIO</hask>,
+
It is too tempting to get rid of IO by <hask>unsafePerformIO</hask>, but we want to present some clean techniques to avoid IO.
but we want to present some clean techniques to avoid IO.
 
   
 
== Lazy construction ==
 
== Lazy construction ==
Line 34: Line 33:
 
writeFile "foo" (concat $ replicate 10 "bar")
 
writeFile "foo" (concat $ replicate 10 "bar")
 
</haskell>
 
</haskell>
which also ensures proper closing of the handle <hask>h</hask>
 
in case of failure.
 
   
 
which also ensures proper closing of the handle <hask>h</hask> in case of failure.
Since you have now an expression for the complete result as string,
 
  +
you have a simple object that can be re-used in other contexts.
 
E.g. you can also easily compute the length of the written string using <hask>length</hask>
+
Since you have now an expression for the complete result as string, you have a simple object that can be re-used in other contexts. E.g., you can also easily compute the length of the written string using <hask>length</hask> without bothering the file system, again.
without bothering the file system, again.
 
   
 
== Writer monad ==
 
== Writer monad ==
Line 70: Line 66:
 
This state can be hidden in a State monad.
 
This state can be hidden in a State monad.
   
Example: A function which computes a random value
+
Example: A function which computes a random value with respect to a custom distribution (<hask>distInv</hask> is the inverse of the distribution function) can be defined via IO
  +
with respect to a custom distribution
 
(<hask>distInv</hask> is the inverse of the distribution function)
 
can be defined via IO
 
 
<haskell>
 
<haskell>
 
randomDist :: (Random a, Num a) => (a -> a) -> IO a
 
randomDist :: (Random a, Num a) => (a -> a) -> IO a
 
randomDist distInv = liftM distInv (randomRIO (0,1))
 
randomDist distInv = liftM distInv (randomRIO (0,1))
 
</haskell>
 
</haskell>
  +
 
but [[Humor/Erlkönig|there is no need to do so]].
 
but [[Humor/Erlkönig|there is no need to do so]].
  +
You don't need the state of the whole world
 
just for remembering the state of a random number generator.
+
You don't need the state of the whole world just for remembering the state of a random number generator, instead you can use something similar to this:
What about
 
 
<haskell>
 
<haskell>
 
randomDist :: (RandomGen g, Random a, Num a) => (a -> a) -> State g a
 
randomDist :: (RandomGen g, Random a, Num a) => (a -> a) -> State g a
 
randomDist distInv = liftM distInv (State (randomR (0,1)))
 
randomDist distInv = liftM distInv (State (randomR (0,1)))
 
</haskell>
 
</haskell>
  +
? You can get actual values by running the <hask>State</hask> as follows:
+
You can get actual values by running the <hask>State</hask> as follows:
  +
 
<haskell>
 
<haskell>
 
evalState (randomDist distInv) (mkStdGen an_arbitrary_seed)
 
evalState (randomDist distInv) (mkStdGen an_arbitrary_seed)
Line 99: Line 95:
 
<hask>STArray</hask> as replacement for <hask>IOArray</hask>,
 
<hask>STArray</hask> as replacement for <hask>IOArray</hask>,
 
<hask>STUArray</hask> as replacement for <hask>IOUArray</hask>,
 
<hask>STUArray</hask> as replacement for <hask>IOUArray</hask>,
and you can define new operations in ST, but then you need to resort to unsafe operations.
+
and you can define new operations in ST, but then you need to resort to unsafe operations, using the <hask>unsafeIOtoST</hask> function.
 
You can escape from ST to non-monadic code in a safe, and in many cases efficient, way.
 
You can escape from ST to non-monadic code in a safe, and in many cases efficient, way.
   
Line 105: Line 101:
   
 
Say you have written the function
 
Say you have written the function
  +
 
<haskell>
 
<haskell>
 
translate :: String -> IO String
 
translate :: String -> IO String
Line 110: Line 107:
 
do dict <- readDictionary "english-german.dict"
 
do dict <- readDictionary "english-german.dict"
 
return (Map.findWithDefault word word dict)
 
return (Map.findWithDefault word word dict)
.
 
 
</haskell>
 
</haskell>
  +
You can only call this function within the IO monad
 
and it is also not very efficient, since for every translation the dictionary must be read from disk.
+
You can only call this function within the IO monad, and it is not very efficient either, since for every translation the dictionary must be read from disk. You can rewrite this function in a way that it generates a non-monadic function that can be used anywhere.
  +
You can rewrite this function in a way that it generates a non-monadic function that can be used anywhere.
 
 
<haskell>
 
<haskell>
 
makeTranslator :: IO (String -> String)
 
makeTranslator :: IO (String -> String)
Line 126: Line 122:
 
putStr (unlines (map translate ["foo", "bar"]))
 
putStr (unlines (map translate ["foo", "bar"]))
 
</haskell>
 
</haskell>
  +
I call this Applicative Functor style,
 
because you can use the application operator from <hask>Control.Applicative</hask>.
+
I call this Applicative Functor style because you can use the application operator from <hask>Control.Applicative</hask>:
  +
 
<haskell>
 
<haskell>
 
makeTranslator <*> getLine
 
makeTranslator <*> getLine
Line 140: Line 137:
   
 
As an example consider the function
 
As an example consider the function
  +
 
<haskell>
 
<haskell>
 
localeTextIO :: String -> IO String
 
localeTextIO :: String -> IO String
 
</haskell>
 
</haskell>
  +
 
which converts an English phrase to the currently configured user language of the system.
 
which converts an English phrase to the currently configured user language of the system.
 
You can abstract the <hask>IO</hask> away using
 
You can abstract the <hask>IO</hask> away using
  +
 
<haskell>
 
<haskell>
 
class Monad m => Locale m where
 
class Monad m => Locale m where
Line 155: Line 155:
 
localeText = Identity
 
localeText = Identity
 
</haskell>
 
</haskell>
  +
 
where the first instance can be used for the application and the second one for "dry" tests.
 
where the first instance can be used for the application and the second one for "dry" tests.
 
For more sophisticated tests, you may load a dictionary into a <hask>Map</hask> and use this for translation.
 
For more sophisticated tests, you may load a dictionary into a <hask>Map</hask> and use this for translation.
  +
 
<haskell>
 
<haskell>
 
newtype Interpreter a = Interpreter (Reader (Map String String) a)
 
newtype Interpreter a = Interpreter (Reader (Map String String) a)
Line 166: Line 168:
 
== Last resort ==
 
== Last resort ==
   
  +
The method of last resort is <hask>unsafePerformIO</hask>. When you apply it, think about how to reduce its use and how you can encapsulate it in a library with a well chosen interface. Since <hask>unsafePerformIO</hask> makes functions look like non-IO functions, they should also behave like non-IO functions. E.g. file access must not be hidden in <hask>unsafePerformIO</hask>, whereas careful memory manipulation may be safe – see for instance the <hask>Data.ByteString</hask> module.
The method of last resort is <hask>unsafePerformIO</hask>.
 
When you apply it, think about how to reduce its use
 
and how you can encapsulate it in a library with a well chosen interface.
 
Since <hask>unsafePerformIO</hask> makes functions look like non-IO functions,
 
they should also behave like non-IO functions.
 
E.g. file access must not be hidden in <hask>unsafePerformIO</hask>,
 
whereas careful memory manipulation may be safe.
 
See for instance the <hask>Data.ByteString</hask> module.
 
You may define new operations in the <hask>ST</hask> monad using <hask>unsafeIOToST</hask>.
 
   
 
[[Category:Monad]]
 
[[Category:Monad]]

Revision as of 11:40, 19 December 2010

Haskell requires an explicit type for operations involving input and output. This way it makes a problem explicit, that exists in every language: Input and output functions can have so many effects, that the type signature says more or less that almost everything must be expected. It is hard to test them, because they can in principle depend on every state of the real world. Thus in order to maintain modularity you should avoid IO wherever possible. It is too tempting to get rid of IO by unsafePerformIO, but we want to present some clean techniques to avoid IO.

Lazy construction

You can avoid a series of output functions by constructing a complex data structure with non-IO code and output it with one output function.

Instead of

-- import Control.Monad (replicateM_)
replicateM_ 10 (putStr "foo")

you can also create the complete string and output it with one call of putStr:

putStr (concat $ replicate 10 "foo")

Similarly,

do
  h <- openFile "foo" WriteMode
  replicateM_ 10 (hPutStr h "bar")
  hClose h

can be shortened to

writeFile "foo" (concat $ replicate 10 "bar")

which also ensures proper closing of the handle h in case of failure.

Since you have now an expression for the complete result as string, you have a simple object that can be re-used in other contexts. E.g., you can also easily compute the length of the written string using length without bothering the file system, again.

Writer monad

If the only reason that you need IO is to output information (e.g. logging, collecting statistics), a Writer monad might do the job. This technique works just fine with lazy construction, especially if the lazy object that you need to create is a Monoid.

An inefficient example of logging:

logText :: (MonadWriter String m) => String -> m ()
logText text = tell (text ++ "\n")

  do
    logText "Before operation A"
    opA
    logText "After operation A"

State monad

If you want to maintain a running state, it is tempting to use IORef. But this is not necessary, since there is the comfortable State monad and its transformer counterpart.

Another example is random number generation. In cases where no real random numbers are required, but only arbitrary numbers, you do not need access to the outside world. You can simply use a pseudo random number generator with an explicit state. This state can be hidden in a State monad.

Example: A function which computes a random value with respect to a custom distribution (distInv is the inverse of the distribution function) can be defined via IO

randomDist :: (Random a, Num a) => (a -> a) -> IO a
randomDist distInv = liftM distInv (randomRIO (0,1))

but there is no need to do so.

You don't need the state of the whole world just for remembering the state of a random number generator, instead you can use something similar to this:

randomDist :: (RandomGen g, Random a, Num a) => (a -> a) -> State g a
randomDist distInv = liftM distInv (State (randomR (0,1)))

You can get actual values by running the State as follows:

evalState (randomDist distInv) (mkStdGen an_arbitrary_seed)

ST monad

In some cases a state monad is simply not efficient enough. Say the state is an array and the update operations are modification of single array elements. For this kind of application the State Thread monad ST was invented. It provides STRef as replacement for IORef, STArray as replacement for IOArray, STUArray as replacement for IOUArray, and you can define new operations in ST, but then you need to resort to unsafe operations, using the unsafeIOtoST function. You can escape from ST to non-monadic code in a safe, and in many cases efficient, way.

Applicative functor style

Say you have written the function

translate :: String -> IO String
translate word =
   do dict <- readDictionary "english-german.dict"
      return (Map.findWithDefault word word dict)

You can only call this function within the IO monad, and it is not very efficient either, since for every translation the dictionary must be read from disk. You can rewrite this function in a way that it generates a non-monadic function that can be used anywhere.

makeTranslator :: IO (String -> String)
makeTranslator =
   do dict <- readDictionary "english-german.dict"
      return (\word -> Map.findWithDefault word word dict)

main :: IO ()
main =
   do translate <- makeTranslator
      putStr (unlines (map translate ["foo", "bar"]))

I call this Applicative Functor style because you can use the application operator from Control.Applicative:

makeTranslator <*> getLine


Custom monad type class

If you only use a small set of IO operations in otherwise non-IO code you may define a custom monad type class which implements just these functions. You can then implement these functions based on IO for the application and without IO for the test suite.

As an example consider the function

localeTextIO :: String -> IO String

which converts an English phrase to the currently configured user language of the system. You can abstract the IO away using

class Monad m => Locale m where
   localeText :: String -> m String

instance Locale IO where
   localeText = localeTextIO

instance Locale Identity where
   localeText = Identity

where the first instance can be used for the application and the second one for "dry" tests. For more sophisticated tests, you may load a dictionary into a Map and use this for translation.

newtype Interpreter a = Interpreter (Reader (Map String String) a)

instance Locale Interpreter where
   localeText text = Interpreter $ fmap (Map.findWithDefault text text) ask

Last resort

The method of last resort is unsafePerformIO. When you apply it, think about how to reduce its use and how you can encapsulate it in a library with a well chosen interface. Since unsafePerformIO makes functions look like non-IO functions, they should also behave like non-IO functions. E.g. file access must not be hidden in unsafePerformIO, whereas careful memory manipulation may be safe – see for instance the Data.ByteString module.