Difference between revisions of "IO, partible-style"

From HaskellWiki
Jump to navigation Jump to search
m (Small change of formatting)
m (Linked "Output/Input")
(14 intermediate revisions by the same user not shown)
Line 1: Line 1:
  +
<div style="border-left:1px solid lightgray; padding: 1em" alt="blockquote">
  +
It is interesting that novices in lazy functional programming in general expect that there is some direct (side-effecting) I/O using a function call.
   
  +
<tt>[https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.55.1076&rep=rep1&type=pdf A Partial Rehabilitation of Side-Effecting I/O:], Manfred Schmidt-Schauß.</tt>
<i><code>IO</code> is the [monadic type] you cannot avoid.</i>
 
<tt>
+
</div>
* [https://image.slidesharecdn.com/functionalconf2019-whyishaskellsohard2-191116135003/95/why-is-haskell-so-hard-and-how-to-deal-with-it-53-638.jpg Why Haskell is so HARD? (And how to deal with it)]; Saurabh Nanda.
 
</tt>
 
   
  +
...like how I/O works in [https://www.smlnj.org/sml.html Standard ML]?
::...but you kept looking anyway, and here you are!
 
 
<i>
 
[...] the input/output story for purely-functional languages was weak and unconvincing, let alone error recovery, concurrency, etc. Over the last few years, a surprising solution has emerged: the monad. I say "surprising" because anything with as exotic a name as "monad" - derived from category theory, one of the most abstract branches of mathematics - is unlikely to be very useful to red-blooded programmers. But one of the joys of functional programming is the way in which apparently-exotic theory can have a direct and practical application, and the monadic story is a good example.
 
</i>
 
<tt>
 
* [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.
 
</tt>
 
 
::...with that (''ahem'') "joy" leading to more than a few [[Monad tutorials timeline|helpful guides about the topic]] - that monadic interface: it's abstract alright!
 
 
__TOC__
 
<sub> </sub>
 
----
 
 
=== <code>IO</code>, <u>using</u> <code>OI</code> ===
 
 
Our definition of <code>IO</code> is a type synonym:
 
 
<haskell>
 
type IO a = OI -> a
 
</haskell>
 
 
with <code>OI</code> being an abstract [[Plainly partible|partible]] type:
 
 
<haskell>
 
data OI a
 
primitive primPartOI :: OI -> (OI, OI)
 
 
instance Partible OI where
 
part = primPartOI
 
</haskell>
 
 
Like <code>primPartOI</code>, most other primitives for the <code>OI</code> type also accept an <code>OI</code>-value as their last (or only) argument e.g:
 
 
<haskell>
 
primitive primGetChar :: OI -> Char
 
primitive primPutChar :: Char -> OI -> ()
 
 
</haskell>
 
 
Borrowing the running example from Philip Wadler's [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.91.3579&rep=rep1&type=pdf How to Declare an Imperative]:
 
 
<haskell>
 
echo :: OI -> ()
 
echo u = let !(u1:u2:u3:_) = parts u
 
!c = primGetChar u1 in
 
if c == '\n' then
 
()
 
else
 
let !_ = primPutChar c u2
 
in echo u3
 
</haskell>
 
 
Wadler also provides an [https://www.smlnj.org/sml.html SML] version:
 
   
 
<pre>
 
<pre>
Line 67: Line 13:
 
()
 
()
 
else
 
else
(putcML c; echoML ())
+
let val _ = putcML c in
  +
echoML ()
  +
end
 
end
 
end
 
</pre>
 
</pre>
   
  +
Alright, now look at this:
in which we replace SML's sequencing operator <code>;</code>:
 
   
<pre>
+
<haskell>
  +
echo :: OI -> ()
  +
echo u = let !(u1:u2:u3:_) = parts u
  +
!c = primGetChar u1 in
  +
if c == '\n' then
  +
()
  +
else
  +
let !_ = primPutChar c u2 in
  +
echo u3
  +
</haskell>
  +
  +
So how is this possible?
  +
<br>
  +
<br>
  +
__TOC__
  +
<sub> </sub>
  +
----
  +
=== <u>Wadler's </u><code>echo</code> ===
  +
  +
Those two versions of that small program are based on the running example from Philip Wadler's [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.91.3579&rep=rep1&type=pdf How to Declare an Imperative]. If we compare the two:
  +
  +
{|
  +
|<pre>
 
val echoML : unit -> unit
 
val echoML : unit -> unit
fun echoML () = let val c = getcML () in
+
fun echoML () =
  +
let val c = getcML () in
 
if c = #"\n" then
 
if c = #"\n" then
 
()
 
()
Line 84: Line 55:
 
end
 
end
 
</pre>
 
</pre>
 
If we compare it to our Haskell version:
 
 
{|
 
 
|<haskell>
 
|<haskell>
 
echo :: OI -> ()
 
echo :: OI -> ()
Line 95: Line 62:
 
()
 
()
 
else
 
else
let !_ = primPutChar c u2
+
let !_ = primPutChar c u2 in
in echo u3
+
echo u3
   
 
--
 
--
 
</haskell>
 
</haskell>
|<pre>
 
val echoML : unit -> unit
 
fun echoML () =
 
let val c = getcML () in
 
if c = #"\n" then
 
()
 
else
 
let val _ = putcML c in
 
echoML ()
 
end
 
end
 
</pre>
 
 
|}
 
|}
...we can now see just how similar the two versions of <code>echo</code> really are: apart from the obvious changes of syntax, the Haskell version replaces all use of <code>unit</code>-values with <code>OI</code>-values, and adds an extra call to <code>parts</code> to provide them.
 
   
  +
...we can see just how similar the two versions of <code>echo</code> really are: apart from the obvious changes of syntax and names:
So there you have it: for the price of some extra calls and bindings, we can have SML-style I/O in Haskell. Furthermore, as SML has been available since 1997, there should be plenty of I/O tutorials to choose from...
 
  +
* the Haskell version replaces the <code>unit</code> arguments for <code>echoML</code> and <code>getcML</code>,
  +
* and provides an extra argument for <code>putcML</code>,
  +
* with the replacement parameter <code>u</code> being used to define the new local bindings <code>u1</code>, <code>u2</code> and <code>u3</code> as the result of a call to <code>parts</code>.
   
  +
So for the price of some extra calls and bindings, we can have SML-style I/O in Haskell. Furthermore, as the prevailing [https://smlfamily.github.io/sml97-defn.pdf definition for Standard ML] has been available since 1997, there should be plenty of I/O tutorials to choose from...
At this point, you may be tempted to try something like:
 
  +
  +
----
  +
=== <u>Resisting temptation</u> ===
  +
  +
If you're now thinking about using something like:
   
 
<pre>
 
<pre>
type IO a = () -> a
 
 
 
primitive might_get_Char :: () -> Char
 
primitive might_get_Char :: () -> Char
 
primitive might_put_Char :: Char -> ()
 
primitive might_put_Char :: Char -> ()
 
 
</pre>
 
</pre>
   
While this ''might'' work in some situations, it's unreliable in general. Why?
+
to achieve a more direct translation...'''don't''' - it ''might'' for this small program, but it just isn't reliable in general. Why?
   
* ''Short answer'': unlike SML, Haskell's nonstrict evaluation means expressions should be referentially transparent.
+
* ''Short answer'': unlike SML, Haskell's nonstrict evaluation means expressions should be [[Referential transparency|referentially transparent]].
 
* ''Long answer'': read section 2.2 (pages 4-5) of Wadler's [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.91.3579&rep=rep1&type=pdf paper].
 
* ''Long answer'': read section 2.2 (pages 4-5) of Wadler's [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.91.3579&rep=rep1&type=pdf paper].
 
* ''Longer answer'': read Lennart Augustsson's [https://augustss.blogspot.com/2011/05/more-points-for-lazy-evaluation-in.html More points for lazy evaluation].
 
* ''Longer answer'': read Lennart Augustsson's [https://augustss.blogspot.com/2011/05/more-points-for-lazy-evaluation-in.html More points for lazy evaluation].
 
* ''Extended answer'': read John Hughes's [https://www.cse.chalmers.se/~rjmh/Papers/whyfp.pdf Why Functional Programming Matters].
 
* ''Extended answer'': read John Hughes's [https://www.cse.chalmers.se/~rjmh/Papers/whyfp.pdf Why Functional Programming Matters].
   
But - if after all that - you're still not convinced, then perhaps you'll be happier programming in [https://www.smlnj.org/sml.html SML]...
+
But, if after all that, you're still not convinced...a small functional language which combines non-strictness with effect-centric definitions in a similar fashion can be found [http://h2.jaguarpaw.co.uk/posts/impure-lazy-language here] - ''"have fun!"''
   
  +
----
  +
===<code>OI</code><u>: what is it?</u> ===
   
  +
<code>OI</code> is an abstract [[Plainly partible|partible]] type:
...you're still here: ''nice!'' &nbsp;Now for a small example - here's <code>interact</code>, using those <code>OI</code>-based definitions:
 
   
 
<haskell>
 
<haskell>
  +
data OI a
interact :: (String -> String) -> OI -> ()
 
  +
primitive primPartOI :: OI -> (OI, OI)
interact f v = let !(u1, u2) = part v
 
  +
gets = map primGetChar $ parts u1
 
  +
instance Partible OI where
puts s = foldr (\!_ -> id) () $ zipWith primPutChar s $ parts u2
 
in
+
part = primPartOI
  +
</haskell>
puts $ f $ gets
 
  +
  +
Like <code>primPartOI</code>, most other primitives for the <code>OI</code> type also accept an <code>OI</code>-value as their last (or only) argument e.g:
  +
  +
<haskell>
  +
primitive primGetChar :: OI -> Char
  +
primitive primPutChar :: Char -> OI -> ()
  +
  +
</haskell>
  +
  +
For consistency, the last argument of a <code>OI</code>-based definition should also be an <code>OI</code>-value:
  +
  +
<haskell>
  +
interact :: (String -> String) -> OI -> ()
  +
interact d u = let !(u1, u2) = part u in
  +
putStr (d $ getContents u1) u2
  +
  +
putStr :: String -> OI -> ()
  +
putStr s u = foldr (\(!_) -> id) () $ zipWith primPutChar s $ parts u
  +
  +
getContents :: OI -> String
  +
getContents u = case map getChar (parts u) of
  +
l@(!c:_) -> l
  +
l -> l
 
</haskell>
 
</haskell>
 
<sub> </sub>
 
<sub> </sub>
  +
----
  +
=== <code>IO</code>, <u>using</u> <code>OI</code> ===
  +
  +
So how do we get from <code>IO</code> to <code>OI</code>?
  +
* Haskell is now used far and wide, so good ol' ''"search and replace"'' is a non-starter!
  +
* There are some who [https://www.humprog.org/~stephen//research/papers/kell17some-preprint.pdf still prefer C], and there are others who are content with <code>IO</code> - convincing them to switch will probably take a lot more than a solitary page on some wiki!
  +
  +
Fortunately, it's quite easy to define <code>IO</code> with <code>OI</code>:
  +
  +
<haskell>
  +
type IO a = OI -> a
  +
</haskell>
  +
  +
...provided you followed that hint about putting the <code>OI</code> argument last:
  +
  +
<haskell>
  +
interact :: (String -> String) -> IO ()
  +
putStr :: String -> IO ()
  +
getContents :: IO String
  +
  +
primitive primGetChar :: IO Char
  +
primitive primPutChar :: Char -> IO ()
  +
  +
</haskell>
  +
  +
Of course, a realistic implementation of <code>IO</code> in Haskell requires [[Monad|''that'']] interface:
  +
  +
<haskell>
  +
unitIO :: a -> IO a
  +
unitIO x = \ u -> let !_ = part u in x
  +
  +
bindIO :: IO a -> (a -> IO b) -> IO b
  +
bindIO m k = \ u -> let !(u1, u2) = part u in
  +
let !x = m u1 in
  +
let !y = k x u2 in
  +
y
  +
</haskell>
  +
  +
You didn't put the <code>OI</code> argument last? Oh well, there's always the [[Applicative functor|applicative]] interface...
  +
 
----
 
----
 
=== <u>Some annoyances</u> ===
 
=== <u>Some annoyances</u> ===
   
* ''Extra parameters and arguments'' - As noted in Paul Hudak and Raman S. Sundaresh's [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.49.695&rep=rep1&type=pdf On the Expressiveness of Purely Functional I/O Systems], passing around all those <code>OI</code>-values ''correctly'' can be tedious for large definitions.
+
* ''Extra parameters and arguments'' - As noted by Sigbjørn Finne and Simon Peyton Jones in [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.46.1260&rep=rep1&type=pdf Programming Reactive Systems in Haskell], passing around all those <code>OI</code>-values ''correctly'' can be tedious for large definitions.
   
 
* ''Polymorphic references'' - It's been known for a very long time in the SML community that naive declarations for operations using ''mutable references'' breaks type safety:
 
* ''Polymorphic references'' - It's been known for a very long time in the SML community that naive declarations for operations using ''mutable references'' breaks type safety:
Line 210: Line 234:
 
=== <u>One solution</u> ===
 
=== <u>One solution</u> ===
   
* ''Extra parameters and arguments'' - What is needed is a succinct interface to "hide the plumbing" used to pass around <code>OI</code>-values:
+
* ''Extra parameters and arguments'' - What is needed is a succinct interface to "hide the plumbing" used to pass around <code>OI</code>-values. Here's one we prepared earlier:
   
 
:<haskell>
 
:<haskell>
  +
unitIO :: a -> IO a
instance Monad ((->) OI) where
 
return x = \u -> case part u of !_ -> x
+
unitIO x = \ u -> let !_ = part u in x
  +
m >>= k = \u -> case part u of
 
(u1, u2) -> case m u1 of
+
bindIO :: IO a -> (a -> IO b) -> IO b
  +
bindIO m k = \ u -> let !(u1, u2) = part u in
!x -> k x u2
 
  +
let !x = m u1 in
  +
let !y = k x u2 in
  +
y
 
</haskell>
 
</haskell>
   
Line 233: Line 260:
   
 
instance Monad ((->) OI) where
 
instance Monad ((->) OI) where
return x = \u -> case part u of !_ -> x
+
return = unitIO
m >>= k = \u -> case part u of
+
(>>=) = bindIO
  +
(u1, u2) -> case m u1 of
 
!x -> k x u2
 
   
 
getChar :: IO Char
 
getChar :: IO Char
Line 256: Line 282:
 
-- these are now local, private entities --
 
-- these are now local, private entities --
 
type IO a = OI -> a
 
type IO a = OI -> a
  +
  +
unitIO :: a -> IO a
  +
unitIO x = \ u -> let !_ = part u in x
  +
  +
bindIO :: IO a -> (a -> IO b) -> IO b
  +
bindIO m k = \ u -> let !(u1, u2) = part u in
  +
let !x = m u1 in
  +
let !y = k x u2 in
  +
y
   
 
data OI a
 
data OI a
Line 272: Line 307:
 
</haskell>
 
</haskell>
   
:With the <code>IO</code> type now made abstract, the only way to use <code>IO</code>-values is by using:
+
:With <code>IO</code> now abstract, the only way to use <code>IO</code>-actions is by using:
   
 
:* the visible <code>IO</code> operations: <code>getChar</code>, <code>putChar</code>, etc.
 
:* the visible <code>IO</code> operations: <code>getChar</code>, <code>putChar</code>, etc.
 
:* the monadic interface - <code>Monad(return, (>>=), …)</code> (or via Haskell's <code>do</code>-notation).
 
:* the monadic interface - <code>Monad(return, (>>=), …)</code> (or via Haskell's <code>do</code>-notation).
   
:The key here is the type of <code>(>>=)</code>, for <code>IO</code>-values:
+
:So how does making <code>IO</code> an ADT prevent polymophic references? It's all to do with the type of <code>(>>=)</code> when used with <code>IO</code>-actions:
   
 
:<haskell>
 
:<haskell>
Line 291: Line 326:
 
|}
 
|}
   
:...it's a function, so the value it receives will be rendered monomorphic in the function's result (of type <code>IO b</code>).
+
:...it's a function, so the value it receives will be rendered monomorphic in it's result (of type <code>IO b</code>).
   
:As <code>(>>=)</code> is now the only <code>IO</code> operation which can retrieve a result from an <code>IO</code>-value, mutable references (<code>IORef …</code>) simply cannot be used polymorphically.
+
:As <code>(>>=)</code> is now the only <code>IO</code> operation which can retrieve a result from an <code>IO</code>-action, mutable references (<code>IORef …</code>) simply cannot be used polymorphically.
 
----
 
----
 
=== <u>GHC's solution</u> ===
 
=== <u>GHC's solution</u> ===
Line 321: Line 356:
 
:<haskell>
 
:<haskell>
 
getChar :: IO Char
 
getChar :: IO Char
getChar = IO $ \(IOS u) -> let !(u1, u2) = parts u
+
getChar = IO $ \(IOS u) -> let !(u1, u2) = part u
 
!c = primGetChar u1
 
!c = primGetChar u1
 
in (IOS u2, c)
 
in (IOS u2, c)
   
 
putChar :: Char -> IO ()
 
putChar :: Char -> IO ()
putChar c = IO $ \(IOS u) -> let !(u1, u2) = parts u
+
putChar c = IO $ \(IOS u) -> let !(u1, u2) = part u
 
!t = primPutChar c u1
 
!t = primPutChar c u1
 
in (IOS u2, t)
 
in (IOS u2, t)
Line 337: Line 372:
 
:<haskell>
 
:<haskell>
 
instance Monad IO where
 
instance Monad IO where
return x = IO $ \!s -> (s, x)
+
return x = IO $ \(!s) -> (s, x)
IO m >>= k = IO $ \!s -> let !(s', x) = m s
+
IO m >>= k = IO $ \(!s) -> let !(s', x) = m s
!IO w = k x
+
!(IO w) = k x
in w s'
+
in w s'
 
</haskell>
 
</haskell>
   
Line 358: Line 393:
 
=== <u>Further reading</u> ===
 
=== <u>Further reading</u> ===
   
  +
If you've managed to get all the way to here:
If you've managed to get all the way to here, [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.52.3656&rep=rep1&type=pdf State in Haskell] by John Launchbury and Simon Peyton Jones is also worth reading, if you're interested in how GHC eventually arrived at its current definition of <code>IO</code>.
 
  +
* [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.52.3656&rep=rep1&type=pdf State in Haskell] by John Launchbury and Simon Peyton Jones is also worth reading, if you're interested in how GHC eventually arrived at its current definition of <code>IO</code>.
  +
* [[Output/Input]] provides more details about the type <code>OI -> a</code>.
   
 
[[Category:Tutorials]]
 
[[Category:Tutorials]]

Revision as of 12:35, 14 January 2022

It is interesting that novices in lazy functional programming in general expect that there is some direct (side-effecting) I/O using a function call.

A Partial Rehabilitation of Side-Effecting I/O:, Manfred Schmidt-Schauß.

...like how I/O works in Standard ML?

val echoML    : unit -> unit
fun echoML () = let val c = getcML () in
                if c = #"\n" then
                  ()
                else
                  let val _ = putcML c in
                  echoML ()
                  end
                end

Alright, now look at this:

echo         :: OI -> ()
echo u       =  let !(u1:u2:u3:_) = parts u
                    !c            = primGetChar u1 in
                if c == '\n' then
                  ()
                else
                  let !_ = primPutChar c u2 in
                  echo u3

So how is this possible?


Wadler's echo

Those two versions of that small program are based on the running example from Philip Wadler's How to Declare an Imperative. If we compare the two:

val echoML    : unit -> unit
fun echoML () =
                let val c = getcML () in
                if c = #"\n" then
                  ()
                else
                  let val _ = putcML c in
                  echoML ()
                  end
                end
echo   :: OI -> ()
echo u =  let !(u1:u2:u3:_) = parts u
              !c            = primGetChar u1 in
          if c == '\n' then
            ()
          else
            let !_ = primPutChar c u2 in
            echo u3

--

...we can see just how similar the two versions of echo really are: apart from the obvious changes of syntax and names:

  • the Haskell version replaces the unit arguments for echoML and getcML,
  • and provides an extra argument for putcML,
  • with the replacement parameter u being used to define the new local bindings u1, u2 and u3 as the result of a call to parts.

So for the price of some extra calls and bindings, we can have SML-style I/O in Haskell. Furthermore, as the prevailing definition for Standard ML has been available since 1997, there should be plenty of I/O tutorials to choose from...


Resisting temptation

If you're now thinking about using something like:

primitive might_get_Char :: () -> Char
primitive might_put_Char :: Char -> ()

to achieve a more direct translation...don't - it might for this small program, but it just isn't reliable in general. Why?

But, if after all that, you're still not convinced...a small functional language which combines non-strictness with effect-centric definitions in a similar fashion can be found here - "have fun!"


OI: what is it?

OI is an abstract partible type:

data OI a
primitive primPartOI :: OI -> (OI, OI)

instance Partible OI where
    part = primPartOI

Like primPartOI, most other primitives for the OI type also accept an OI-value as their last (or only) argument e.g:

primitive primGetChar :: OI -> Char
primitive primPutChar :: Char -> OI -> ()
        

For consistency, the last argument of a OI-based definition should also be an OI-value:

interact      :: (String -> String) -> OI -> ()
interact d u  =  let !(u1, u2) = part u in
                 putStr (d $ getContents u1) u2

putStr        :: String -> OI -> ()
putStr s u    =  foldr (\(!_) -> id) () $ zipWith primPutChar s $ parts u

getContents   :: OI -> String
getContents u =  case map getChar (parts u) of
                   l@(!c:_) -> l
                   l        -> l


IO, using OI

So how do we get from IO to OI?

  • Haskell is now used far and wide, so good ol' "search and replace" is a non-starter!
  • There are some who still prefer C, and there are others who are content with IO - convincing them to switch will probably take a lot more than a solitary page on some wiki!

Fortunately, it's quite easy to define IO with OI:

type IO a = OI -> a

...provided you followed that hint about putting the OI argument last:

interact      :: (String -> String) -> IO ()
putStr        :: String -> IO ()
getContents   :: IO String

primitive primGetChar :: IO Char
primitive primPutChar :: Char -> IO ()
        

Of course, a realistic implementation of IO in Haskell requires that interface:

unitIO     :: a -> IO a
unitIO x   =  \ u -> let !_ = part u in x 

bindIO     :: IO a -> (a -> IO b) -> IO b
bindIO m k =  \ u -> let !(u1, u2) = part u in
                     let !x = m u1 in
                     let !y = k x u2 in
                     y

You didn't put the OI argument last? Oh well, there's always the applicative interface...


Some annoyances

  • Extra parameters and arguments - As noted by Sigbjørn Finne and Simon Peyton Jones in Programming Reactive Systems in Haskell, passing around all those OI-values correctly can be tedious for large definitions.
  • Polymorphic references - It's been known for a very long time in the SML community that naive declarations for operations using mutable references breaks type safety:
primitive newPolyRef :: a -> OI -> PolyRef a
primitive readPolyRef :: PolyRef a -> OI -> a
primitive writePolyRef :: PolyRef a -> a -> OI -> ()

kah_BOOM u = let …
                 !vehicle = newPolyRef undefined u1
                 !_       = writePolyRef ("0" :: [Char]) u2
                 !crash   = readPolyRef vehicle u3
                 burn     = 1 :: Int
             in
                 crash + burn
SML's solution is to make all mutable references monomorphic through the use of dedicated syntax:
let val r = ref (…)
         ⋮
One alternative for Haskell would be to extend type signatures to support monomorphic type-variables:
primitive newIORef   :: monomo a . a -> OI -> IORef a
primitive readIORef  :: monomo a . IORef a -> OI -> a
primitive writeIORef :: monomo a . IORef a -> a -> OI -> ()

{- would be rejected by the extended type system: 
kah_BOOM u = let !(u1:u2:u3:_) = parts u
                 !vehicle      = newIORef undefined u1          -- vehicle :: monomo a . IORef a
                 !_            = writeIORef ("0" :: [Char]) u2  -- vehicle :: IORef [Char]
                 !crash        = readIORef vehicle u3           -- vehicle :: IORef [Char] ≠ IORef Int
                 burn          = 1 :: Int
             in
                 crash + burn
-}
In standard Haskell, one of the few places this already occurs (albeit implicitly) is the parameters of a function:
{- will be rejected by the standard Haskell type system

ker_plunk f = (f True, f 'b')

-}

One solution

  • Extra parameters and arguments - What is needed is a succinct interface to "hide the plumbing" used to pass around OI-values. Here's one we prepared earlier:
unitIO     :: a -> IO a
unitIO x   =  \ u -> let !_ = part u in x 

bindIO     :: IO a -> (a -> IO b) -> IO b
bindIO m k =  \ u -> let !(u1, u2) = part u in
                     let !x = m u1 in
                     let !y = k x u2 in
                     y
  • Polymorphic references - we now make IO into an abstract data type:
module Abstract.IO
(
    Monad (..),
    getChar, putChar, 
    newIORef, readIORef, writeIORef,
                 
)
where

instance Monad ((->) OI) where
     return = unitIO
     (>>=)  = bindIO


getChar    :: IO Char
getChar    =  primGetChar

putChar    :: Char -> IO ()
putChar    =  primPutChar

newIORef   :: a -> IO (IORef a)
newIORef   =  primNewIORef

readIORef  :: IORef a -> IO a
readIORef  =  primReadIORef

writeIORef :: IORef a -> a -> IO ()
writeIORef =  primWriteIORef


 -- these are now local, private entities --
type IO a = OI -> a

unitIO     :: a -> IO a
unitIO x   =  \ u -> let !_ = part u in x 

bindIO     :: IO a -> (a -> IO b) -> IO b
bindIO m k =  \ u -> let !(u1, u2) = part u in
                     let !x = m u1 in
                     let !y = k x u2 in
                     y

data OI a
primitive primPartOI  :: OI -> (OI, OI)

primitive primGetChar :: OI -> Char
primitive primPutChar :: Char -> OI -> ()
        

data IORef
primitive primNewIORef    :: a -> OI -> IORef a
primitive primReadIORef   :: IORef a -> OI -> a
primitive primWriteIORef  :: IORef a -> a -> OI -> ()
        
With IO now abstract, the only way to use IO-actions is by using:
  • the visible IO operations: getChar, putChar, etc.
  • the monadic interface - Monad(return, (>>=), …) (or via Haskell's do-notation).
So how does making IO an ADT prevent polymophic references? It's all to do with the type of (>>=) when used with IO-actions:
(>>=) :: IO a -> (a -> IO b) -> IO b
in particular, the type of the second argument:
(a -> IO b)
...it's a function, so the value it receives will be rendered monomorphic in it's result (of type IO b).
As (>>=) is now the only IO operation which can retrieve a result from an IO-action, mutable references (IORef …) simply cannot be used polymorphically.

GHC's solution

newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #))

...you may have noticed that we've already made liberal use of one Haskell extension - bang-patterns - and it would be useful to stay as close as possible to standard Haskell, so we'll simplify matters:

newtype IO a = IO (IOState -> (IOState, a))  -- unboxed-tuple replaced by standard one 

type IOState = State# RealWorld

Now to make the changes:

  • to the type - IOState uses an OI-value:
newtype IOState = IOS OI
  • to the I/O-specific operations - each one will use the OI-value in the initial state to provide two new OI-values: one to make up the final state; the other being used by the OI-primitive:
getChar   :: IO Char
getChar   =  IO $ \(IOS u) -> let !(u1, u2) = part u
                                  !c        = primGetChar u1
                              in  (IOS u2, c)

putChar   :: Char -> IO ()
putChar c =  IO $ \(IOS u) -> let !(u1, u2) = part u
                                  !t        = primPutChar c u1
                              in  (IOS u2, t)

 -- etc.
  • to the overloaded operations - you've probably seen it all before:
instance Monad IO where
    return x   = IO $ \(!s) -> (s, x)
    IO m >>= k = IO $ \(!s) -> let !(s', x) = m s
                                   !(IO w)  = k x
                               in  w s'
(...if you haven't: it's ye ol' pass-the-planet state-passing technique.)

One aspect which doesn't change is IO and its operations being abstract. In fact, the need is even more pressing: in addition to preventing the misuse of certain OI-operations, being an abstract data type prevents IOState-values from being erroneously reused.


Conclusions

  • Why is Haskell I/O monadic - to avoid having to use extra arguments and parameters everywhere.
  • Why is Haskell I/O abstract - to ensure I/O works as intended, by preventing the misuse of internal data.
  • Why is Haskell I/O unusual - because of Haskell's nonstrict evaluation and thus its focus on referential transparency, contrary to most other programming languages.

Further reading

If you've managed to get all the way to here:

  • State in Haskell by John Launchbury and Simon Peyton Jones is also worth reading, if you're interested in how GHC eventually arrived at its current definition of IO.
  • Output/Input provides more details about the type OI -> a.