September 20, 2012
IOSpec package provides several modules that give a pure specification of functions in the IO monad. It is now available in Fedora. Install it using:
$ sudo yum install ghc-IOSpec-devel
To import a specific Fork module (for example), you can use:
Prelude> :m + Test.IOSpec.Fork
Test.IOSpec.Teletype provides a pure specification of the getChar and putChar functions. A simple example of echo is shown below:
{-# LANGUAGE NPlusKPatterns #-}
import Prelude hiding (getChar, putChar)
import qualified Prelude (putStrLn)
import qualified Data.Stream as Stream
import Test.IOSpec hiding (putStrLn)
import Test.QuickCheck
import Data.Char (ord)
echo :: IOSpec Teletype ()
echo = getChar >>= putChar >> echo
copy :: Effect ()
copy = ReadChar (\x -> Print x copy)
takeOutput :: Int -> Effect () -> String
takeOutput 0 _ = ""
takeOutput (n + 1) (Print c xs) = c : takeOutput n xs
takeOutput _ _ = error "Echo.takeOutput"
withInput :: Stream.Stream Char -> Effect a -> Effect a
withInput stdin (Done x) = Done x
withInput stdin (Print c e) = Print c (withInput stdin e)
withInput stdin (ReadChar f) = withInput (Stream.tail stdin)
(f (Stream.head stdin))
echoProp :: Stream.Stream Char -> Property
echoProp input =
forAll (choose (1,10000)) $ \n ->
takeOutput n (withInput input (evalIOSpec echo singleThreaded))
== takeOutput n (withInput input copy)
main = do
Prelude.putStrLn "Testing echo..."
quickCheck echoProp
You can compile it using:
$ ghc --make Echo.hs
[1 of 1] Compiling Main ( Echo.hs, Echo.o )
Linking Echo ...
Test it using:
$ ./Echo
Testing echo...
+++ OK, passed 100 tests.
The Test.IOSpec.IORef provides a pure specification of mutable variables. An example is shown below:
import Test.IOSpec
import Test.QuickCheck
readOnce :: Int -> IOSpec IORefS Int
readOnce x = do ref <- newIORef x
readIORef ref
readTwice :: Int -> IOSpec IORefS Int
readTwice x = do ref <- newIORef x
readIORef ref
readIORef ref
readIORefProp :: Int -> Bool
readIORefProp x =
let once = evalIOSpec (readOnce x) singleThreaded
twice = evalIOSpec (readTwice x) singleThreaded
in once == twice
main = quickCheck readIORefProp
You can compile it using:
$ ghc --make Refs.hs
[1 of 1] Compiling Main ( Refs.hs, Refs.o )
Linking Refs ...
Test it using:
$ ./Refs
+++ OK, passed 100 tests.