Jump to content
Main menu
Main menu
move to sidebar
hide
Navigation
Haskell
Wiki community
Recent changes
Random page
HaskellWiki
Search
Search
Create account
Log in
Personal tools
Create account
Log in
Pages for logged out editors
learn more
Contributions
Talk
Editing
Ru/IO Inside
(section)
Page
Discussion
English
Read
Edit
View history
Tools
Tools
move to sidebar
hide
Actions
Read
Edit
View history
General
What links here
Related changes
Special pages
Page information
Warning:
You are not logged in. Your IP address will be publicly visible if you make any edits. If you
log in
or
create an account
, your edits will be attributed to your username, along with other benefits.
Anti-spam check. Do
not
fill this in!
== IO actions as values == By this point you should understand why it's impossible to use IO actions inside non-IO (pure) procedures. Such procedures just don't get a "baton"; they don't know any "world" value to pass to an IO action. The RealWorld type is an abstract datatype, so pure functions also can't construct RealWorld values by themselves, and it's a strict type, so 'undefined' also can't be used. So, the prohibition of using IO actions inside pure procedures is just a type system trick (as it usually is in Haskell :)). But while pure code can't _execute_ IO actions, it can work with them as with any other functional values - they can be stored in data structures, passed as parameters, returned as results, collected in lists, and partially applied. But an IO action will remain a functional value because we can't apply it to the last argument - of type RealWorld. In order to _execute_ the IO action we need to apply it to some RealWorld value. That can be done only inside some IO procedure, in its "actions chain". And real execution of this action will take place only when this procedure is called as part of the process of "calculating the final value of world" for 'main'. Look at this example: <haskell> main world0 = let get2chars = getChar >> getChar ((), world1) = putStr "Press two keys" world0 (answer, world2) = get2chars world1 in ((), world2) </haskell> Here we first bind a value to 'get2chars' and then write a binding involving 'putStr'. But what's the execution order? It's not defined by the order of the 'let' bindings, it's defined by the order of processing "world" values! You can arbitrarily reorder the binding statements - the execution order will be defined by the data dependency with respect to the "world" values that get passed around. Let's see what this 'main' looks like in the 'do' notation: <haskell> main = do let get2chars = getChar >> getChar putStr "Press two keys" get2chars return () </haskell> As you can see, we've eliminated two of the 'let' bindings and left only the one defining 'get2chars'. The non-'let' statements are executed in the exact order in which they're written, because they pass the "world" value from statement to statement as we described above. Thus, this version of the function is much easier to understand because we don't have to mentally figure out the data dependency of the "world" value. Moreover, IO actions like 'get2chars' can't be executed directly because they are functions with a RealWorld parameter. To execute them, we need to supply the RealWorld parameter, i.e. insert them in the 'main' chain, placing them in some 'do' sequence executed from 'main' (either directly in the 'main' function, or indirectly in an IO function called from 'main'). Until that's done, they will remain like any function, in partially evaluated form. And we can work with IO actions as with any other functions - bind them to names (as we did above), save them in data structures, pass them as function parameters and return them as results - and they won't be performed until you give them the magic RealWorld parameter! === Example: a list of IO actions === Let's try defining a list of IO actions: <haskell> ioActions :: [IO ()] ioActions = [(print "Hello!"), (putStr "just kidding"), (getChar >> return ()) ] </haskell> I used additional parentheses around each action, although they aren't really required. If you still can't believe that these actions won't be executed immediately, just recall the real type of this list: <haskell> ioActions :: [RealWorld -> ((), RealWorld)] </haskell> Well, now we want to execute some of these actions. No problem, just insert them into the 'main' chain: <haskell> main = do head ioActions ioActions !! 1 last ioActions </haskell> Looks strange, right? :) Really, any IO action that you write in a 'do' statement (or use as a parameter for the '>>'/'>>=' operators) is an expression returning a result of type 'IO a' for some type 'a'. Typically, you use some function that has the type 'x -> y -> ... -> IO a' and provide all the x, y, etc. parameters. But you're not limited to this standard scenario - don't forget that Haskell is a functional language and you're free to compute the functional value required (recall that "IO a" is really a function type) in any possible way. Here we just extracted several functions from the list - no problem. This functional value can also be constructed on-the-fly, as we've done in the previous example - that's also OK. Want to see this functional value passed as a parameter? Just look at the definition of 'when'. Hey, we can buy, sell, and rent these IO actions just like we can with any other functional values! For example, let's define a function that executes all the IO actions in the list: <haskell> sequence_ :: [IO a] -> IO () sequence_ [] = return () sequence_ (x:xs) = do x sequence_ xs </haskell> No black magic - we just extract IO actions from the list and insert them into a chain of IO operations that should be performed one after another (in the same order that they occurred in the list) to "compute the final world value" of the entire 'sequence_' call. With the help of 'sequence_', we can rewrite our last 'main' function as: <haskell> main = sequence_ ioActions </haskell> Haskell's ability to work with IO actions as with any other (functional and non-functional) values allows us to define control structures of arbitrary complexity. Try, for example, to define a control structure that repeats an action until it returns the 'False' result: <haskell> while :: IO Bool -> IO () while action = ??? </haskell> Most programming languages don't allow you to define control structures at all, and those that do often require you to use a macro-expansion system. In Haskell, control structures are just trivial functions anyone can write. === Example: returning an IO action as a result === How about returning an IO action as the result of a function? Well, we've done this each time we've defined an IO procedure - they all return IO actions that need a RealWorld value to be performed. While we usually just execute them as part of a higher-level IO procedure, it's also possible to just collect them without actual execution: <haskell> main = do let a = sequence ioActions b = when True getChar c = getChar >> getChar putStr "These 'let' statements are not executed!" </haskell> These assigned IO procedures can be used as parameters to other procedures, or written to global variables, or processed in some other way, or just executed later, as we did in the example with 'get2chars'. But how about returning a parameterized IO action from an IO procedure? Let's define a procedure that returns the i'th byte from a file represented as a Handle: <haskell> readi h i = do hSeek h AbsoluteSeek i hGetChar h </haskell> So far so good. But how about a procedure that returns the i'th byte of a file with a given name without reopening it each time? <haskell> readfilei :: String -> IO (Integer -> IO Char) readfilei name = do h <- openFile name ReadMode return (readi h) </haskell> As you can see, it's an IO procedure that opens a file and returns... another IO procedure that will read the specified byte. But we can go further and include the 'readi' body in 'readfilei': <haskell> readfilei name = do h <- openFile name ReadMode let readi h i = do hSeek h AbsoluteSeek i hGetChar h return (readi h) </haskell> That's a little better. But why do we add 'h' as a parameter to 'readi' if it can be obtained from the environment where 'readi' is now defined? An even shorter version is this: <haskell> readfilei name = do h <- openFile name ReadMode let readi i = do hSeek h AbsoluteSeek i hGetChar h return readi </haskell> What have we done here? We've build a parameterized IO action involving local names inside 'readfilei' and returned it as the result. Now it can be used in the following way: <haskell> main = do myfile <- readfilei "test" a <- myfile 0 b <- myfile 1 print (a,b) </haskell> This way of using IO actions is very typical for Haskell programs - you just construct one or more IO actions that you need, with or without parameters, possibly involving the parameters that your "constructor" received, and return them to the caller. Then these IO actions can be used in the rest of the program without any knowledge about your internal implementation strategy. One thing this can be used for is to partially emulate the OOP (or more precisely, the ADT) programming paradigm. === Example: a memory allocator generator === As an example, one of my programs has a module which is a memory suballocator. It receives the address and size of a large memory block and returns two procedures - one to allocate a subblock of a given size and the other to free the allocated subblock: <haskell> memoryAllocator :: Ptr a -> Int -> IO (Int -> IO (Ptr b), Ptr c -> IO ()) memoryAllocator buf size = do ...... let alloc size = do ... ... free ptr = do ... ... return (alloc, free) </haskell> How this is implemented? 'alloc' and 'free' work with references created inside the memoryAllocator procedure. Because the creation of these references is a part of the memoryAllocator IO actions chain, a new independent set of references will be created for each memory block for which memoryAllocator is called: <haskell> memoryAllocator buf size = do start <- newIORef buf end <- newIORef (buf `plusPtr` size) ... </haskell> These two references are read and written in the 'alloc' and 'free' definitions (we'll implement a very simple memory allocator for this example): <haskell> ... let alloc size = do addr <- readIORef start writeIORef start (addr `plusPtr` size) return addr let free ptr = do writeIORef start ptr </haskell> What we've defined here is just a pair of closures that use state available at the moment of their definition. As you can see, it's as easy as in any other functional language, despite Haskell's lack of direct support for impure functions. The following example uses procedures, returned by memoryAllocator, to simultaneously allocate/free blocks in two independent memory buffers: <haskell> main = do buf1 <- mallocBytes (2^16) buf2 <- mallocBytes (2^20) (alloc1, free1) <- memoryAllocator buf1 (2^16) (alloc2, free2) <- memoryAllocator buf2 (2^20) ptr11 <- alloc1 100 ptr21 <- alloc2 1000 free1 ptr11 free2 ptr21 ptr12 <- alloc1 100 ptr22 <- alloc2 1000 </haskell> === Example: emulating OOP with record types === Let's implement the classical OOP example: drawing figures. There are figures of different types: circles, rectangles and so on. The task is to create a heterogeneous list of figures. All figures in this list should support the same set of operations: draw, move and so on. We will represent these operations as IO procedures. Instead of a "class" let's define a structure containing implementations of all the procedures required: <haskell> data Figure = Figure { draw :: IO (), move :: Displacement -> IO () } type Displacement = (Int, Int) -- horizontal and vertical displacement in points </haskell> The constructor of each figure's type should just return a Figure record: <haskell> circle :: Point -> Radius -> IO Figure rectangle :: Point -> Point -> IO Figure type Point = (Int, Int) -- point coordinates type Radius = Int -- circle radius in points </haskell> We will "draw" figures by just printing their current parameters. Let's start with a simplified implementation of the 'circle' and 'rectangle' constructors, without actual 'move' support: <haskell> circle center radius = do let description = " Circle at "++show center++" with radius "++show radius return $ Figure { draw = putStrLn description } rectangle from to = do let description = " Rectangle "++show from++"-"++show to) return $ Figure { draw = putStrLn description } </haskell> As you see, each constructor just returns a fixed 'draw' procedure that prints parameters with which the concrete figure was created. Let's test it: <haskell> drawAll :: [Figure] -> IO () drawAll figures = do putStrLn "Drawing figures:" mapM_ draw figures main = do figures <- sequence [circle (10,10) 5, circle (20,20) 3, rectangle (10,10) (20,20), rectangle (15,15) (40,40)] drawAll figures </haskell> Now let's define "full-featured" figures that can actually be moved around. In order to achieve this, we should provide each figure with a mutable variable that holds each figure's current screen location. The type of this variable will be "IORef Point". This variable should be created in the figure constructor and manipulated in IO procedures (closures) enclosed in the Figure record: <haskell> circle center radius = do centerVar <- newIORef center let drawF = do center <- readIORef centerVar putStrLn (" Circle at "++show center ++" with radius "++show radius) let moveF (addX,addY) = do (x,y) <- readIORef centerVar writeIORef centerVar (x+addX, y+addY) return $ Figure { draw=drawF, move=moveF } rectangle from to = do fromVar <- newIORef from toVar <- newIORef to let drawF = do from <- readIORef fromVar to <- readIORef toVar putStrLn (" Rectangle "++show from++"-"++show to) let moveF (addX,addY) = do (fromX,fromY) <- readIORef fromVar (toX,toY) <- readIORef toVar writeIORef fromVar (fromX+addX, fromY+addY) writeIORef toVar (toX+addX, toY+addY) return $ Figure { draw=drawF, move=moveF } </haskell> Now we can test the code which moves figures around: <haskell> main = do figures <- sequence [circle (10,10) 5, rectangle (10,10) (20,20)] drawAll figures mapM_ (\fig -> move fig (10,10)) figures drawAll figures </haskell> It's important to realize that we are not limited to including only IO actions in a record that's intended to simulate a C++/Java-style interface. The record can also include values, IORefs, pure functions - in short, any type of data. For example, we can easily add to the Figure interface fields for area and origin: <haskell> data Figure = Figure { draw :: IO (), move :: Displacement -> IO (), area :: Double, origin :: IORef Point } </haskell>
Summary:
Please note that all contributions to HaskellWiki are considered to be released under simple permissive license (see
HaskellWiki:Copyrights
for details). If you don't want your writing to be edited mercilessly and redistributed at will, then don't submit it here.
You are also promising us that you wrote this yourself, or copied it from a public domain or similar free resource.
DO NOT SUBMIT COPYRIGHTED WORK WITHOUT PERMISSION!
Cancel
Editing help
(opens in new window)
Toggle limited content width