[Haskell-cafe] Re: do

Brandon S. Allbery KF8NH allbery at ece.cmu.edu
Mon Oct 15 23:59:25 EDT 2007


I actually got this done several hours ago, but my DSL is being  
annoying tonight...

Anyway, here's a simple example of how to do explicit/non-monadic I/O  
in GHC.  (It *only* works in GHC; other compilers have different  
internal implementations of IO.)  I specifically modeled it to  
highlight its resemblance to State.

{-# OPTIONS_GHC -fno-implicit-prelude -fglasgow-exts #-}

import GHC.Base
import GHC.IOBase
import GHC.IO
import GHC.Handle (stdout)

{-
   This is horrible evil to demonstrate how to do I/O without the  
help of
   the IO monad.  And yes, it is very much a help.

   The trick here is that the type IO is a state-like type:  a value
   constructor which wraps a function.  Thus, working with it manually
   requires that we have a runIO.(*)  Naively, this looks like  
unsafePerformIO;
   but in fact it is not, as unsafePerformIO uses the magic builtin  
RealWorld#
   to create a new State# RealWorld on the fly, but in fact we are  
passing on
   the one we get from somewhere else (ultimately, the initial state  
for main).
   (Additionally, we don't unwrap the resulting tuple; we return it.)
   This is why runIO is really *safePerformIO* (i.e. entirely normal  
I/O).

   (*) Well, not absolutely.  GHC.IOBase uses unIO instead:
         unIO (IO f) = f
       I think this is a little cleaner, and better demonstrates how  
IO is
       really not all that special, but simply a way to pass state  
around.
-}

-- treat IO like State, for demonstration purposes
runIO          :: IO a -> State# RealWorld -> (# State# RealWorld,a #)
runIO (IO f) s =  f s

-- And here's our simple "hello, world" demo program
main :: IO ()
main =  IO (\s -> runIO (putStrLn' "hello, world") s)

-- this is just to demonstrate how to compose I/O actions.  we could  
just
-- call the real putStrLn above instead; it is operationally identical.

-- write a string followed by newline to stdout
-- this is completely normal!
putStrLn' :: String -> IO ()
putStrLn' =  hPutStrLn' stdout

-- write a string followed by newline to a Handle
hPutStrLn'       :: Handle -> String -> IO ()
hPutStrLn' h str =  IO (\s -> let (# s',_ #) = runIO (hPutStr' h str) s
                                in runIO (hPutChar h '\n') s')

-- write a string, iteratively, to a Handle
hPutStr'          :: Handle -> String -> IO ()
hPutStr' _ []     =  IO (\s -> (# s,() #))
hPutStr' h (c:cs) =  IO (\s -> let (# s',_ #) = runIO (hPutChar h c) s
                                 in runIO (hPutStr' h cs) s')


-- 
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery at kf8nh.com
system administrator [openafs,heimdal,too many hats] allbery at ece.cmu.edu
electrical and computer engineering, carnegie mellon university    KF8NH




More information about the Haskell-Cafe mailing list