Difference between revisions of "IO Semantics"

From HaskellWiki
Jump to navigation Jump to search
m
m (Various changes)
Line 1: Line 1:
 
[[Category:Theoretical_foundations]]
 
[[Category:Theoretical_foundations]]
== Semantics of IO: A Free Approach ==
+
== Semantics of <code>IO</code>: A Free Approach ==
   
The following is inspired by [https://lukepalmer.wordpress.com/2008/03/29/io-monad-the-continuation-presentation Luke Palmer's post] on the topic. This only describes one possible semantics of <hask>IO a</hask>; your actually implementation may vary.
+
The following is inspired by [https://lukepalmer.wordpress.com/2008/03/29/io-monad-the-continuation-presentation Luke Palmer's post] on the topic. This only describes one possible semantics of <code>IO a</code>; your actual implementation may vary.
   
The idea is to define <hask>IO</hask> as
+
The idea is to define <code>IO</code> as
 
<haskell>
 
<haskell>
 
data IO a = Done a
 
data IO a = Done a
Line 11: Line 11:
 
</haskell>
 
</haskell>
   
For simplicity this an example of <hask>IO</hask> that only gives semantics for teletype IO.
+
For simplicity, this an example of <code>IO</code> that only gives semantics for teletype I/O.
   
Think of <hask>IO a</hask> as a tree whose leaves are <hask>Done a</hask> that holds the result of the program. <hask>PutChar</hask> is a node that has one child tree and the node holds one character of data. <hask>GetChar</hask> is a node that has many children; it has one child for every <hask>Char</hask>, but <hask>GetChar</hask> holds no data itself.
+
Think of <code>IO a</code> as a tree whose leaves are <code>Done a</code> that holds the result of the program:
  +
* <code>PutChar</code> is a node that has one child tree and the node holds one character of data.
  +
* <code>GetChar</code> is a node that has many children; it has one child for every <code>Char</code>, but <code>GetChar</code> holds no data itself.
   
This tree contains all the information needed to execute teletype interactions.
+
This tree contains all the information needed to execute teletype interactions. One interprets (or executes) an <code>IO a</code> by tracing a route from root of the tree to a leaf:
  +
* If a <code>PutChar</code> node is encountered, the character data contained at that node is output to the terminal and then its subtree is executed. It is at this point that Haskell code is evaluated in order to determine what character should be displayed before continuing.
One interprets (or executes) an <hask>IO a</hask> by tracing a route from root of the tree to a leaf.
 
  +
* If a <code>GetChar</code> node is encountered, a character is read from the terminal (blocking if necessary) and the subtree corresponding to the character received is executed.
  +
* If <code>Done</code> is encountered, the program ends.
   
If a <hask>PutChar</hask> node is encountered, the character data contained at that node is output to the terminal and then its subtree is executed. It is at this point that Haskell code evaluated in order to determine what character should be displayed before continuing. If a <hask>GetChar</hask> node is encountered, a character is read from the terminal (blocking if necessary) and the subtree corresponding to the character received is executed. If <hask>Done</hask> is encountered the program ends. <hask>Done</hask> holds the result of the computation, but in the case of <hask>main :: IO ()</hask> the data is of type <hask>()</hask> and thus contains no information and is ignored.
+
<code>Done</code> holds the result of the computation, but in the case of <code>Main.main :: IO ()</code> the data is of type <code>()</code> and thus contains no information and is ignored.
   
This execution is not done anywhere in a haskell program, rather it is done by the run-time system.
+
This execution is not done anywhere in a Haskell program, rather it is done by the run-time system.
   
 
The monadic operations are defined as follows:
 
The monadic operations are defined as follows:
 
 
<haskell>
 
<haskell>
 
return :: a -> IO a
 
return :: a -> IO a
 
return x = Done x
 
return x = Done x
   
(>>=) :: IO a -> (a -> IO b) -> IO b
+
(>>=) :: IO a -> (a -> IO b) -> IO b
Done x >>= f = f x
+
Done x >>= f = f x
 
PutChar c x >>= f = PutChar c (x >>= f)
 
PutChar c x >>= f = PutChar c (x >>= f)
GetChar g >>= f = GetChar (\c -> g c >>= f)
+
GetChar g >>= f = GetChar (\c -> g c >>= f)
 
</haskell>
 
</haskell>
   
As you can see <hask>return</hask> is just another name for <hask>Done</hask>. The bind operation takes a tree <hask>x</hask> and a function <hask>f</hask> and replaces the <hask>Done</hask> nodes (the leaves) of <hask>x</hask> by a new tree produce by applying <hask>f</hask> to the data held in the <hask>Done</hask> nodes.
+
As you can see <code>return</code> is just another name for <code>Done</code>. The bind operation <code>(>>=)</code> takes a tree <code>x</code> and a function <code>f</code> and replaces the <code>Done</code> nodes (the leaves) of <code>x</code> by a new tree produced by applying <code>f</code> to the data held in the <code>Done</code> nodes.
   
The primitive IO commands are defined using these constructors.
+
The primitive I/O commands are defined using these constructors.
 
<haskell>
 
<haskell>
 
putChar :: Char -> IO ()
 
putChar :: Char -> IO ()
Line 45: Line 48:
 
</haskell>
 
</haskell>
   
The function <hask>putChar</hask> builds a small <hask>IO ()</hask> tree that contains one <hask>PutChar</hask> node holding the character data followed by <hask>Done</hask>.
+
* The function <code>putChar</code> builds a small <code>IO ()</code> tree that contains one <code>PutChar</code> node holding the character data followed by <code>Done</code>.
   
The function <hask>getChar</hask> builds a short <hask>IO Char</hask> tree that begins with a <hask>GetChar</hask> that holds one <hask>Done</hask> node holding every character.
+
* The function <code>getChar</code> builds a short <code>IO Char</code> tree that begins with a <code>GetChar</code> node that holds one <code>Done</code> node for every character.
   
Other teletype commands can be defined in terms of these primitives
+
Other teletype commands can be defined in terms of these primitives:
 
<haskell>
 
<haskell>
 
putStr :: String -> IO ()
 
putStr :: String -> IO ()
Line 55: Line 58:
 
</haskell>
 
</haskell>
   
More generally speaking, <hask>IO a</hask> will represent the desired interaction with the operating system. For every system call there will be a corresponding constructor in <hask>IOTree</hask> of the form
+
More generally speaking, <code>IO a</code> will represent the desired interaction with the operating system. For every system call there will be a corresponding I/O-tree constructor of the form:
 
<haskell>
 
<haskell>
 
| SysCallName p1 p2 ... pn (r -> IO a)
 
| SysCallName p1 p2 ... pn (r -> IO a)
 
</haskell>
 
</haskell>
where <hask>p1</hask> ... <hask>pn</hask> are the parameters for the system call, and <hask>r</hask> is the result of the system call. (Thus <hask>PutChar</hask> and <hask>GetChar</hask> will not occur as constructors of <hask>IOTree</hask> if they don't correspond to system calls)
+
where <code>p1</code> ... <code>pn</code> are the parameters for the system call, and <code>r</code> is the result of the system call. (Thus <code>PutChar</code> and <code>GetChar</code> will not occur as constructors for I/O trees if they don't correspond to system calls).
   
 
== Further reading ==
 
== Further reading ==
  +
  +
* [https://www.cs.nott.ac.uk/~psztxa/publ/beast.pdf Beauty in the Beast: A Functional Semantics for the Awkward Squad]
  +
::Wouter Swierstra, Thorsten Altenkirch (2007).
   
 
* [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.15.736&rep=rep1&type=pdf Semantics of ''fixIO'']
 
* [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.15.736&rep=rep1&type=pdf Semantics of ''fixIO'']

Revision as of 11:31, 22 December 2021

Semantics of IO: A Free Approach

The following is inspired by Luke Palmer's post on the topic. This only describes one possible semantics of IO a; your actual implementation may vary.

The idea is to define IO as

data IO a = Done a
          | PutChar Char (IO a)
          | GetChar (Char -> IO a)

For simplicity, this an example of IO that only gives semantics for teletype I/O.

Think of IO a as a tree whose leaves are Done a that holds the result of the program:

  • PutChar is a node that has one child tree and the node holds one character of data.
  • GetChar is a node that has many children; it has one child for every Char, but GetChar holds no data itself.

This tree contains all the information needed to execute teletype interactions. One interprets (or executes) an IO a by tracing a route from root of the tree to a leaf:

  • If a PutChar node is encountered, the character data contained at that node is output to the terminal and then its subtree is executed. It is at this point that Haskell code is evaluated in order to determine what character should be displayed before continuing.
  • If a GetChar node is encountered, a character is read from the terminal (blocking if necessary) and the subtree corresponding to the character received is executed.
  • If Done is encountered, the program ends.

Done holds the result of the computation, but in the case of Main.main :: IO () the data is of type () and thus contains no information and is ignored.

This execution is not done anywhere in a Haskell program, rather it is done by the run-time system.

The monadic operations are defined as follows:

return :: a -> IO a
return x = Done x

(>>=)  :: IO a -> (a -> IO b) -> IO b
Done x      >>= f = f x
PutChar c x >>= f = PutChar c (x >>= f)
GetChar g   >>= f = GetChar (\c -> g c >>= f)

As you can see return is just another name for Done. The bind operation (>>=) takes a tree x and a function f and replaces the Done nodes (the leaves) of x by a new tree produced by applying f to the data held in the Done nodes.

The primitive I/O commands are defined using these constructors.

putChar :: Char -> IO ()
putChar x = PutChar x (Done ())

getChar :: IO Char
getChar = GetChar (\c -> Done c)
  • The function putChar builds a small IO () tree that contains one PutChar node holding the character data followed by Done.
  • The function getChar builds a short IO Char tree that begins with a GetChar node that holds one Done node for every character.

Other teletype commands can be defined in terms of these primitives:

putStr :: String -> IO ()
putStr = mapM_ putChar

More generally speaking, IO a will represent the desired interaction with the operating system. For every system call there will be a corresponding I/O-tree constructor of the form:

	| SysCallName p1 p2 ... pn (r -> IO a)

where p1 ... pn are the parameters for the system call, and r is the result of the system call. (Thus PutChar and GetChar will not occur as constructors for I/O trees if they don't correspond to system calls).

Further reading

Wouter Swierstra, Thorsten Altenkirch (2007).
Levent Erkök, John Launchbury, Andrew Moran. In Fixed Points in Computer Science Workshop, FICS'01 (2001).
Simon Peyton Jones. In "Engineering theories of software construction", ed. Tony Hoare, Manfred Broy, Ralf Steinbruggen, IOS Press, ISBN 1 58603 1724, 2001, pages 47-96.
Roy L. Crole, Andrew D. Gordon. Mathematical Structures in Computer Science 9(2): 125-158 (1999).
Andrew Gordon. In International Workshop on Computer Science Logic, January 1995. Springer Berlin Heidelberg.
Andrew Gordon. In FPCA '93: Conference on Functional Programming Languages and Computer Architecture, Copenhagen, June 1993. ACM Press.
Andrew Gordon. Cambridge University Press. Revision of 1992 PhD dissertation.