Difference between revisions of "Output/Input"

From HaskellWiki
Jump to navigation Jump to search
(Quotes reorganised or removed)
Line 345: Line 345:
 
=== <u>See also</u> ===
 
=== <u>See also</u> ===
   
  +
* [[Plainly partible]]
* [https://pqnelson.github.io/2021/07/29/monadic-io-in-ml.html Monadic IO in Standard ML]
 
 
* [[Disposing of dismissives]]
 
* [[Disposing of dismissives]]
 
* [[IO then abstraction]]
 
* [[IO then abstraction]]
 
* [https://okmij.org/ftp/Computation/IO-monad-history.html The IO monad in 1965]
 
* [https://okmij.org/ftp/Computation/IO-monad-history.html The IO monad in 1965]
 
* [https://pqnelson.github.io/2021/07/29/monadic-io-in-ml.html Monadic IO in Standard ML]

Revision as of 19:56, 24 August 2022


Clearing away the smoke and mirrors

The implementation in GHC uses the following one:

type IO a  =  World -> (a, World)

An IO computation is a function that (logically) takes the state of the world, and returns a modified world as well as the return value. Of course, GHC does not actually pass the world around; instead, it passes a dummy “token,” to ensure proper sequencing of actions in the presence of lazy evaluation, and performs input and output as actual side effects!

A History of Haskell: Being Lazy With Class, Paul Hudak, John Hughes, Simon Peyton Jones and Philip Wadler.

...so what starts out as an I/O action of type:

World -> (a, World)

is changed by GHC to approximately:

() -> (a, ())

...because "logically" a function in Haskell has no observable effects - being exact requires a change of notation:

() --> (a, ())

The "result" (of type a) can then be "returned" directly:

() --> a

Previously seen

Variants of () --> a have appeared elsewhere - examples include:

The use of λ, and in particular (to avoid an irrelevant bound variable) of λ() , to delay and possibly avoid evaluation is exploited repeatedly in our model of ALGOL 60. A function that requires an argument-list of length zero is called a none-adic function.

(\ () -> ) :: () --> a
abstype 'a Job = JOB of unit -> 'a

data Job a = JOB (() --> a)

A value of type Obs 𝜏 is called an observer. Such a value observes (i.e. views or inspects) a state and returns a value of type 𝜏. [...] An observer type Obs 𝜏 may be viewed as an implicit function space from the set of states to the type 𝜏.

type Obs tau = State --> tau

The type 'a io is represented by a function expecting a dummy argument of type unit and returning a value of type 'a.

type 'a io = unit -> a

type Io a = () --> a
class IO[A](run: () => A)

class Io a where run :: () --> a
type IO<'T> = private | Action of (unit -> 'T)

data IO t = Action (() --> t)

Let's say you want to implement IO in SML :

structure Io : MONAD =
struct
  type 'a t = unit -> 'a
         ⋮
end

type T a = () --> a
newtype IO a = IO { runIO :: () --> a }
(deftype #export (IO a)
  (-> Void a))

type IO a = (-->) Void a
abstract class SimpleIO<A> {
    abstract A run()
}

class SimpleIO a where
    run :: () --> a
__construct :: (-> a) -> IO a

[...] The parameter to the constructor must be a zero-parameter [none-adic] function that returns a value.

data IO a = IO (() --> a)
__construct :: (() --> a) -> IO a
__construct = IO

IO is a very simple monad that implements a slightly modified version of our abstract interface with the difference that instead of wrapping a value a, it wraps a side effect function () -> a.

data IO a = Wrap (() --> a)

The definition of IO<> is simple:

public delegate T IO<out T>();

[...]

  • IO<T> is used to represent a impure function. When a IO<T> function is applied, it returns a T value, with side effects.

type IO t = () --> t

So let’s implement the IO Monad right now and here. Given that OCaml is strict and that the order of function applications imposes the order of evaluation, the IO Monad is just a thunk, e.g.,

type 'a io = unit -> 'a

type Io a = () --> a

[...] So suspend () -> A offers us the exact same guarantees as IO<A>.

As long as we have its special case IO c = () ~> c, we can represent (up to isomorphism) […] a ~> c […]

where ~> is used instead of -->.

Avoiding alternate annotations

Having to deal with both -> and --> is annoying - another option is to use a different argument type, instead of ():

  • page 15 of Non-Imperative Functional Programming by Nobuo Yamashita:
type a :-> b = OI a -> b
data Time_ a = GetCurrentTime (UTCTime -> a)

[...] The type Id can be hidden by the synonym data type

:: Create a  :==  Id -> a

type Create a = Id -> a

An early implementation of Fran represented behaviors as implied in the formal semantics:

data Behavior a = Behavior (Time -> a)

Of these, it is the implementation of OI a in Yamashita's oi package which is most interesting as its values are monousal - once used, their contents remain constant. This single-use property also appears in the implementation of the abstract decision type described by F. Warren Burton in Nondeterminism with Referential Transparency in Functional Programming Languages.


IO, redefined

Based on these and other observations, a reasonable distillment of these examples would be OI -> a, which then implies:

type IO a = OI -> a

Using Burton's pseudodata approach:

 -- abstract; single-use I/O-access mediator
data Exterior
getchar :: Exterior -> Char
putchar :: Char -> Exterior -> ()

 -- from section 2 of Burton's paper
data Tree a = Node { contents :: a,
                     left     :: Tree a,
                     right    :: Tree a }

 -- utility definitions
type OI  =  Tree Exterior

getChar' :: OI -> Char
getChar' =  getchar . contents

putChar' :: Char -> OI -> ()
putChar' c = putchar c . contents

part     :: OI -> (OI, OI)
parts    :: OI -> [OI]

part t   =  (left t, right t)
parts t  =  let !(t1, t2) = part t in
            t1 : parts t2

Of course, in an actual implementation OI would be abstract like World, and for similar reasons. This permits a simpler implementation for OI and its values, instead of being based on (theoretically) infinite structured values like binary trees. That simplicity has benefits for the OI interface, in this case:

data OI
part :: OI -> (OI, OI)
getChar' :: OI -> Char
putChar' :: Char -> OI -> ()


See also