Difference between revisions of "IO Semantics"

From HaskellWiki
Jump to navigation Jump to search
m
m
 
(13 intermediate revisions by 3 users not shown)
Line 1: Line 1:
 
[[Category:Theoretical_foundations]]
 
[[Category:Theoretical_foundations]]
== Semantics of IO: A Continuation Approach ==
 
   
  +
<i>
The following is inspired by [http://luqui.org/blog/archives/2008/03/29/io-monad-the-continuation-presentation/ Luke Palmer's post]. This only describes one possible semantics of <hask>IO a</hask>; your actually implementation may vary.
 
  +
Note:
  +
* For simplicity, the examples here only gives semantics for teletype I/O.
  +
* These are only some of the various ways to describe the semantics of </i><code>IO a</code><i>; your actual implementation may vary.
  +
</i>
   
  +
== A free approach ==
The idea to to define <hask>IO</hask> as
 
  +
  +
(Inspired by [https://lukepalmer.wordpress.com/2008/03/29/io-monad-the-continuation-presentation Luke Palmer's post].)
  +
  +
The idea is to define <code>IO</code> as
 
<haskell>
 
<haskell>
  +
data IO a = Done a
newtype IO a = IO {runIO :: (a -> IOTree) -> IOTree}
 
  +
| PutChar Char (IO a)
  +
| GetChar (Char -> IO a)
 
</haskell>
 
</haskell>
  +
This is equivalent to defining <hask>IO</hask> as <hask>Cont IOTree</hask> from the [[monad template library]]. The monad functions for <hask>IO</hask> are derived from the monad functions for <hask>Cont</hask>.
 
  +
Think of <code>IO a</code> as a tree:
  +
* <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 character, but <code>GetChar</code> holds no data itself.
  +
* <code>Done a</code> (a leaf) is a node that holds the result of the program.
  +
  +
This tree contains all the information needed to execute basic 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.
  +
* 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 a <code>Done</code> node is encountered, the program ends.
  +
  +
<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 ignored as it contains no information.
  +
  +
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:
 
<haskell>
 
<haskell>
return x = IO (\k -> k x)
+
return :: a -> IO a
  +
return x = Done x
x >>= f = IO (\k -> runIO x (\a -> runIO (f a) k))
 
  +
  +
(>>=) :: 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)
 
</haskell>
 
</haskell>
<hask>IOTree</hask> is the ultimate result of a program. For simplicity we will give an example of <hask>IOTree</hask> that gives semantics for teletype IO.
 
<haskell>
 
data IOTree = Done
 
| PutChar Char IOTree
 
| GetChar (Char -> IOTree)
 
</haskell>
 
(This is a tree because the <hask>GetChar</hask> node has one subtree for every character)
 
   
  +
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.
<hask>IOTree</hask> contains all the information needed to execute teletype interactions.
 
One interprets (or executes) an <hask>IOTree</hask> by tracing a route from root of the tree to a leaf.
 
   
  +
The primitive I/O commands are defined using these constructors.
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 only at this point that Haskell code is ever necessarily 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.
 
The primitive IO commands are defined using these constructors.
 
 
<haskell>
 
<haskell>
 
putChar :: Char -> IO ()
 
putChar :: Char -> IO ()
putChar x = IO (\k -> PutChar x (k ()))
+
putChar x = PutChar x (Done ())
   
 
getChar :: IO Char
 
getChar :: IO Char
getChar = IO (\k -> GetChar (\x -> k x))
+
getChar = GetChar (\c -> Done c)
 
</haskell>
 
</haskell>
   
  +
* 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>.
If the <hask>PutChar</hask> constructor was defined (isomorphically) as
 
  +
* 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 commands can be defined in terms of these primitives:
 
<haskell>
 
<haskell>
| PutChar Char (() -> IOTree)
+
putStr :: String -> IO ()
  +
putStr = mapM_ putChar
 
</haskell>
 
</haskell>
   
  +
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:
Then the primitive IO commands could be defined directly in terms of these constructors:
 
  +
<haskell>
  +
| SysCallName p1 p2 ... pn (r -> IO a)
  +
</haskell>
  +
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).
  +
  +
== A more direct style ==
  +
  +
<blockquote>
  +
Here is the key idea:
  +
  +
:A value of type <code>IO a</code> is an “action” that, when performed, may do some input/output, before delivering a value of type <code>a</code>.
  +
  +
:<small>[[#readmore|Tackling the Awkward Squad]] (page 5 of 60).</small>
  +
</blockquote>
  +
  +
It also has a [https://www.interaction-design.org/literature/topics/keep-it-simple-stupid simple] translation:
  +
<pre>
  +
type IO a = (->) OI a
  +
. . . .
  +
an action that __| | | |
  +
| | |
  +
when performed __________| | |
  +
| |
  +
may do some input/output ___| |
  +
|
  +
before delivering a value _____|
  +
</pre>
  +
  +
Think of an <code>IO a</code> action as an entity which:
  +
* can be used like other Haskell functions,
  +
* but may also have effects like procedures.
  +
  +
This combination of [[Denotative|denotative]] and imperative features is enough to provide basic interactions. An <code>IO a</code> action works by calling it when applied to an <code>OI</code> argument, subject to certain conditions:
  +
* Each <code>OI</code> value should be distinct from all others, to help preserve [[Referential transparency|referential transparency]].
  +
* Each <code>OI</code> value should be used at most once, to ensure actions can be used like other functions.
   
  +
As for the <code>OI</code> type itself:
 
<haskell>
 
<haskell>
  +
data OI -- no constructors are visible to the user
putChar :: Char -> IO ()
 
  +
</haskell>
putChar = IO . PutChar
 
   
  +
Most <code>OI</code> values would then be provided by one or more specific actions:
getChar :: IO Char
 
  +
<haskell>
getChar = IO GetChar
 
  +
foreign import partOI :: OI -> (OI, OI)
  +
  +
partsOI :: OI -> [OI]
  +
partsOI u = let !(u1, u2) = partOI u in u1 : partsOI u2
 
</haskell>
 
</haskell>
   
  +
but in the case of <code>Main.main :: IO ()</code> the initial argument is provided directly by the implementation. It is from this initial argument that all other <code>OI</code> values in the program are obtained.
   
  +
Not being able to define <code>OI</code> values directly in Haskell means actions in a Haskell program cannot work until the program, applied to its initial <code>OI</code> argument, is called by the run-time system.
Other teletype commands can be defined in terms of these primitives
 
  +
  +
The monadic operations are defined as follows:
 
<haskell>
 
<haskell>
  +
instance Monad ((->) OI)
putStr :: String -> IO ()
 
  +
where
putStr = mapM_ putChar
 
  +
return x = \ u -> let !_ = partOI u in x
  +
  +
m >>= k = \ u -> let !(u1, u2) = partOI u
  +
!x = m u1
  +
!y = k x u2 in
  +
in y
 
</haskell>
 
</haskell>
  +
More generally speaking, <hask>IOTree</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
 
  +
Note that both methods use their <code>OI</code> parameters, with <code>return</code> simply returning its other parameter <code>x</code> to the caller. The bind operation <code>(>>=)</code> takes an action <code>m</code> and a function <code>k</code> and uses new <code>OI</code> values to call <code>m</code> to obtain <code>x</code>, then call <code>k x</code> to obtain the result <code>y</code>.
  +
  +
Other actions can be declared:
  +
 
<haskell>
 
<haskell>
  +
foreign import getChar :: OI -> Char
| SysCallName p1 p2 ... pn (r -> IOTree)
 
  +
foreign import putChar :: Char -> OI -> ()
 
</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)
 
   
  +
or defined:
We said that the ultimate result of a program is an <hask>IOTree</hask>, however the main function has type <hask>IO ()</hask>. This is isomorphic to <hask>(() -> IOTree) -> IOTree</hask>, or equivalently <hask>IOTree -> IOTree</hask> which is not right.
 
   
  +
<haskell>
The simple solution to this is that the runtime system produces an <hask>IOTree</hask> from main by evaluating <hask>runIO main (\() -> Done) :: IOTree</hask>. Here <hask>\() -> Done</hask> represents the "rest of the program", which in this case is nothing.
 
  +
getLine :: OI -> [Char]
  +
getLine = do c <- getChar
  +
if c == ’\n’ then return ""
  +
else do cs <- getLine
  +
return (c:cs)
   
  +
putStr :: [Char] -> OI -> ()
The sophisticated solution to this problem is that <hask>main</hask> is passed to the operating system which will bind the next program (perhaps a shell) to <hask>main</hask>. Thus the semantics of our Haskell program becomes embedded into the semantics of the entire operating system run.
 
  +
putStr cs = foldr (\ !(_) -> id) () . zipWith putChar cs . partsOI
  +
</haskell>
  +
  +
In more fully-featured implementations, each system call would have its own declaration:
   
The type for <hask>IO a</hask> that we have given contains invalid programs such as
 
 
<haskell>
 
<haskell>
  +
primitive primSysCallName :: T1 -> T2 -> ... -> OI -> Tr
IO (\k -> filterTree (not . isPutChar) (k ())) :: IO ()
 
 
</haskell>
 
</haskell>
  +
which would remove the output of any future <hask>putChar</hask> commands. However, none of these illegal programs can be generated from the monadic interface and the primitive operations provided.
 
  +
<haskell>
  +
foreign import ... extnSysCallName :: T1 -> T2 -> ... -> OI -> Tr
  +
</haskell>
  +
  +
where:
  +
* <code>T1</code>, <code>T2</code> ... are the types of the parameters for the system call,
  +
* and <code>Tr</code> is the type of the system call's result.
  +
  +
== <span id="readmore"></span> Further reading ==
  +
  +
* [https://www.haskell.org/definition/haskell2010.pdf The Haskell 2010 Report]
  +
::ed. Simon Marlow Marlow, 2010.
  +
  +
* [http://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.722.8440&rep=rep1&type=pdf A Functional Specification of Effects]
  +
::Wouter Swierstra. Ph.D. thesis, University of Nottingham. (2009).
  +
  +
* [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. In: Proceedings of the ACM SIGPLAN Workshop on Haskell, Haskell ’07, ACM, New York, NY, USA, pages 25–36 (2007).
  +
  +
* [https://www.scss.tcd.ie/publications/tech-reports/reports.06/TCD-CS-2006-19.pdf A Semantic Framework for Deterministic Functional Input/Output]
  +
::Malcolm Dowse. PhD dissertation, University of Dublin, Trinity College (2006).
  +
  +
* [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.15.736&rep=rep1&type=pdf Semantics of ''fixIO'']
  +
::Levent Erkök, John Launchbury, Andrew Moran. In Fixed Points in Computer Science Workshop, FICS'01 (2001).
  +
  +
* [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.13.9123&rep=rep1&type=pdf Tackling the Awkward Squad: monadic input/output, concurrency, exceptions, and foreign-language calls in Haskell]
  +
::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.
  +
  +
* [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.52.6409&rep=rep1&type=pdf Relating operational and denotational semantics for input/output effects]
  +
::Roy L. Crole, Andrew D. Gordon. Mathematical Structures in Computer Science 9(2): 125-158 (1999).
  +
  +
* [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.91.3579&rep=rep1&type=pdf How to Declare an Imperative]
  +
::Philip Wadler. ACM Computing Surveys, 29(3): 240-263, September 1997.
  +
  +
* [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.52.6922&rep=rep1&type=pdf Monadic I/O in Haskell 1.3]
  +
::Andrew D. Gordon and Kevin Hammond. In: Proceedings of the Haskell Workshop, La Jolla, California, June 1995.
  +
  +
* [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.16.5894&rep=rep1&type=pdf A Sound Metalogical Semantics for Input/Output Effects]
  +
::Andrew Gordon. In International Workshop on Computer Science Logic, January 1995. Springer Berlin Heidelberg.
  +
  +
* [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.16.3541&rep=rep1&type=pdf An Operational Semantics for I/O in a Lazy Functional Language]
  +
::Andrew Gordon. In FPCA '93: Conference on Functional Programming Languages and Computer Architecture, Copenhagen, June 1993. ACM Press.
  +
  +
* [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.134.5784&rep=rep1&type=pdf Functional Programming and Input/Output]
  +
::Andrew Gordon. Cambridge University Press. Revision of 1992 PhD dissertation.
  +
  +
* [https://www.cl.cam.ac.uk/techreports/UCAM-CL-TR-160.pdf PFL+: A Kernel Scheme for Functional I/O]
  +
::Andrew Gordon. Computer Laboratory Technical Report Number 160, University of Cambridge (1989).
  +
  +
* [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.45.8497&rep=rep1&type=pdf Interactive Functional Programs: A Method and a Formal Semantics]
  +
::Simon Thompson. Technical Report 48, Computing Laboratory, University of Kent, Canterbury, UK, November 1987.

Latest revision as of 10:36, 5 April 2024


Note:

  • For simplicity, the examples here only gives semantics for teletype I/O.
  • These are only some of the various ways to describe the semantics of IO a; your actual implementation may vary.

A free approach

(Inspired by Luke Palmer's post.)

The idea is to define IO as

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

Think of IO a as a tree:

  • 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 character, but GetChar holds no data itself.
  • Done a (a leaf) is a node that holds the result of the program.

This tree contains all the information needed to execute basic 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 a Done node 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 ignored as it contains no information.

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 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).

A more direct style

Here is the key idea:

A value of type IO a is an “action” that, when performed, may do some input/output, before delivering a value of type a.
Tackling the Awkward Squad (page 5 of 60).

It also has a simple translation:

            type IO a = (->) OI a
                  .       .  .  .
 an action that __|       |  |  |
                          |  |  |
 when performed __________|  |  |
                             |  |
 may do some input/output ___|  |
                                |
 before delivering a value _____|

Think of an IO a action as an entity which:

  • can be used like other Haskell functions,
  • but may also have effects like procedures.

This combination of denotative and imperative features is enough to provide basic interactions. An IO a action works by calling it when applied to an OI argument, subject to certain conditions:

  • Each OI value should be distinct from all others, to help preserve referential transparency.
  • Each OI value should be used at most once, to ensure actions can be used like other functions.

As for the OI type itself:

data OI  -- no constructors are visible to the user

Most OI values would then be provided by one or more specific actions:

foreign import partOI  :: OI -> (OI, OI)

partsOI                :: OI -> [OI]
partsOI u              = let !(u1, u2) = partOI u in u1 : partsOI u2

but in the case of Main.main :: IO () the initial argument is provided directly by the implementation. It is from this initial argument that all other OI values in the program are obtained.

Not being able to define OI values directly in Haskell means actions in a Haskell program cannot work until the program, applied to its initial OI argument, is called by the run-time system.

The monadic operations are defined as follows:

instance Monad ((->) OI)
  where
        return x =  \ u -> let !_ = partOI u in x 

        m >>= k  =  \ u -> let !(u1, u2) = partOI u
                               !x = m u1
                               !y = k x u2 in
                           in y

Note that both methods use their OI parameters, with return simply returning its other parameter x to the caller. The bind operation (>>=) takes an action m and a function k and uses new OI values to call m to obtain x, then call k x to obtain the result y.

Other actions can be declared:

foreign import getChar :: OI -> Char
foreign import putChar :: Char -> OI -> ()

or defined:

getLine                :: OI -> [Char]
getLine                = do c <- getChar
                            if c == \n then return ""
                                         else do cs <- getLine
                                              return (c:cs)

putStr                 :: [Char] -> OI -> ()
putStr cs              = foldr (\ !(_) -> id) () . zipWith putChar cs . partsOI

In more fully-featured implementations, each system call would have its own declaration:

primitive primSysCallName :: T1 -> T2 -> ... -> OI -> Tr
foreign import ... extnSysCallName :: T1 -> T2 -> ... -> OI -> Tr

where:

  • T1, T2 ... are the types of the parameters for the system call,
  • and Tr is the type of the system call's result.

Further reading

ed. Simon Marlow Marlow, 2010.
Wouter Swierstra. Ph.D. thesis, University of Nottingham. (2009).
Wouter Swierstra, Thorsten Altenkirch. In: Proceedings of the ACM SIGPLAN Workshop on Haskell, Haskell ’07, ACM, New York, NY, USA, pages 25–36 (2007).
Malcolm Dowse. PhD dissertation, University of Dublin, Trinity College (2006).
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).
Philip Wadler. ACM Computing Surveys, 29(3): 240-263, September 1997.
Andrew D. Gordon and Kevin Hammond. In: Proceedings of the Haskell Workshop, La Jolla, California, June 1995.
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.
Andrew Gordon. Computer Laboratory Technical Report Number 160, University of Cambridge (1989).
Simon Thompson. Technical Report 48, Computing Laboratory, University of Kent, Canterbury, UK, November 1987.