Difference between revisions of "Output/Input"

From HaskellWiki
Jump to navigation Jump to search
(All-new content and category!)
m
 
(63 intermediate revisions by the same user not shown)
Line 1: Line 1:
  +
Regarding <code>IO a</code>, Haskell's monadic I/O type:
   
  +
<blockquote>
<div style="border-left:1px solid lightgray; padding: 1em" alt="blockquote">
 
  +
Some operations are primitive actions,
Still, today, over 25 years after the introduction of the concept of monads to the world of functional programming, beginning functional programmers struggle to grasp the concept of monads. This struggle is exemplified by the numerous blog posts about the effort of trying to learn about monads. From our own experience we notice that even at university level, bachelor level students often struggle to comprehend monads and consistently score poorly on monad-related exam questions.
 
  +
corresponding to conventional I/O operations. Special operations (methods in the class <code>Monad</code>, see Section 6.3.6)
  +
sequentially compose actions, corresponding to sequencing operators (such as the semicolon) in imperative
  +
languages.
   
  +
:<small>[https://www.haskell.org/definition/haskell2010.pdf The Haskell 2010 Report], (page 107 of 329).</small>
Considering that the concept of monads is not likely to disappear from the functional programming landscape any time soon, it is vital that we, as the functional programming community, somehow overcome the problems novices encounter when first studying monads.
 
  +
</blockquote>
   
  +
So for I/O, the monadic interface merely provides [[Monad tutorials timeline|an abstract way]] to sequence its actions. However there is another, more direct approach to sequencing:
<tt>[https://pms.cs.ru.nl/iris-diglib/src/getContent.php?id=2017-Steenvoorden-SupportLearning Visual Support for Learning Monads], Tim Steenvoorden, Jurriën Stutterheim, Erik Barendsen and Rinus Plasmeijer.</tt>
 
</div>
 
   
  +
<haskell>
...so where are students of Haskell most likely to have their first encounter with this irksome interface? Here's a hint:
 
  +
Control.Parallel.pseq :: a -> b -> b
  +
</haskell>
   
  +
(as opposed to the [[seq|<b>non</b>]]-sequential <code>Prelude.seq</code>.) That means a more direct way of preserving [[Referential transparency|referential transparency]] is also needed. For simple teletype I/O:
<div style="border-left:1px solid lightgray; padding: 1em" alt="blockquote">
 
<code>IO</code> is the monad you cannot avoid.
 
   
  +
<haskell>
<tt>[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>
 
  +
data OI
</div>
 
  +
partOI :: OI -> (OI, OI)
  +
getChar :: OI -> Char
  +
putChar :: Char -> OI -> ()
  +
</haskell>
   
  +
where:
If bachelor-level students are often struggling to comprehend the monadic interface, then it has ''no place whatsoever'' in any introductory Haskell course! I/O in Haskell must therefore be totally independent of the monadic interface. The introduction of this interface, including its basic operations, should be deferred to an advanced course of study where it can join functors, applicatives, arrows and maybe even category theory itself: only then should students be introduced to monadic I/O.
 
   
  +
* <code>OI</code> isn't an ordinary Haskell type - ordinary Haskell types represent values without (externally-visible) side-effects, hence <code>OI</code> being abstract.
A [https://www.interaction-design.org/literature/article/kiss-keep-it-simple-stupid-a-design-principle simple] general-purpose model of I/O for non-strict functional languages remains an [[Open research problems|open research problem]]...
 
   
  +
* The action <code>partOI</code> is needed because each <code>OI</code> value can only be used once.
[[Category:Rants and comments]]
 
  +
  +
* The action <code>getChar</code> obtains the the next character of input.
  +
  +
* The function <code>putChar</code> expects a character, and returns an action which will output the given character.
  +
  +
<br>
  +
  +
Now for a few other I/O interfaces - if <code>seq</code> was actually sequential:
  +
  +
* [[Monad|monad]]
  +
  +
:<haskell>
  +
type M a = OI -> a
  +
  +
unit :: a -> M a
  +
unit x = \ u -> let !_ = partOI u in x
  +
  +
bind :: M a -> (a -> M b) -> M b
  +
bind m k = \ u -> let !(u1, u2) = partOI u in
  +
let !x = m u1 in
  +
let !y = k x u2 in
  +
y
  +
  +
getcharM :: M Char
  +
getcharM = getChar
  +
  +
putcharM :: Char -> M ()
  +
putcharM = putChar
  +
</haskell>
  +
  +
* [[Comonad|comonad]]:
  +
  +
:<haskell>
  +
type C a = (OI, a)
  +
  +
extract :: C a -> a
  +
extract (u, x) = let !_ = partOI u in x
  +
  +
duplicate :: C a -> C (C a)
  +
duplicate (u, x) = let !(u1, u2) = partOI u in
  +
(u2, (u1, x))
  +
  +
extend :: (C a -> b) -> C a -> C b
  +
extend h (u, x) = let !(u1, u2) = partOI u in
  +
let !y = h (u1, x) in
  +
(u2, y)
  +
  +
getcharC :: C () -> Char
  +
getcharC (u, ()) = getChar u
  +
  +
putcharC :: C Char -> ()
  +
putcharC (u, c) = putChar c u
  +
</haskell>
  +
  +
* [[Arrow|arrow]]:
  +
  +
:<haskell>
  +
type A b c = (OI -> b) -> (OI -> c)
  +
  +
arr :: (b -> c) -> A b c
  +
arr f = \ c' u -> let !x = c' u in f x
  +
  +
both :: A b c -> A b' c' -> A (b, b') (c, c')
  +
f' `both` g' = \ c' u -> let !(u1:u2:u3:_) = partsOI u in
  +
let !(x, x') = c' u1 in
  +
let !y = f' (unit x) u2 in
  +
let !y' = g' (unit x') u3 in
  +
(y, y')
  +
where
  +
unit x u = let !_ = partOI u in x
  +
  +
getcharA :: A () Char
  +
getcharA = \ c' u -> let !(u1, u2) = partOI u in
  +
let !_ = c' u1 in
  +
let !ch = getChar u2 in
  +
ch
  +
  +
putcharA :: A Char ()
  +
putcharA = \ c' u -> let !(u1, u2) = partOI u in
  +
let !ch = c' u1 in
  +
let !z = putChar ch u2 in
  +
z
  +
</haskell>
  +
  +
The <code>OI</code> interface can also be used to implement [https://web.archive.org/web/20210414160729/https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.91.3579&rep=rep1&type=pdf I/O models used in earlier versions] of Haskell:
  +
  +
* dialogues[https://www.haskell.org/definition/haskell-report-1.2.ps.gz <span></span>][https://dl.acm.org/doi/pdf/10.1145/130697.130699 <span></span>]:
  +
  +
:<haskell>
  +
runD :: ([Response] -> [Request]) -> OI -> ()
  +
runD d u = foldr (\ (!_) -> id) () $ yet $ \ l -> zipWith respond (d l) (partsOI u)
  +
  +
yet :: (a -> a) -> a
  +
yet f = f (yet f)
  +
  +
respond :: Request -> OI -> Response
  +
respond Getq u = let !c = getChar u in Getp c
  +
respond (Putq c) u = let !_ = putChar c u in Putp
  +
  +
data Request = Getq | Putq Char
  +
data Response = Getp Char | Putp
  +
</haskell>
  +
  +
* [[Continuation|continuations]]:
  +
  +
:<haskell>
  +
type Answer = OI -> ()
  +
  +
runK :: Answer -> OI -> ()
  +
runK a u = a u
  +
  +
doneK :: Answer
  +
doneK = \ u -> let !_ = partOI u in ()
  +
  +
getcharK :: (Char -> Answer) -> Answer
  +
getcharK k = \ u -> let !(u1, u2) = partOI u in
  +
let !c = getChar u1 in
  +
let !a = k c in
  +
a u2
  +
  +
putcharK :: Char -> Answer -> Answer
  +
putcharK c a = \ u -> let !(u1, u2) = partOI u in
  +
let !_ = putChar c u1 in
  +
a u2
  +
</haskell>
  +
  +
...and even <i>that</i> <s><i>world</i></s> state-passing style used in GHC, and by [https://web.archive.org/web/20130607204300/https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.17.935&rep=rep1&type=pdf Clean], [https://staff.science.uva.nl/c.u.grelck/publications/HerhSchoGrelDAMP09.pdf Single-Assignment C] and as part of the I/O model used for the verification of interactive programs in [https://cakeml.org/vstte18.pdf CakeML], remembering that <code>OI</code> values can only be used once:
  +
  +
<haskell>
  +
newtype World = W OI
  +
  +
getcharL :: World -> (Char, World)
  +
getcharL (W u) = let !(u1, u2) = partOI u in
  +
let !c = getChar u1 in
  +
(c, W u2)
  +
  +
putcharL :: Char -> World -> World
  +
putcharL c (W u) = let !(u1, u2) = partOI u in
  +
let !_ = putChar c u1 in
  +
W u2
  +
</haskell>
  +
  +
(Rewriting those examples to use <code>pseq</code> is left as an exercise.)
  +
  +
See also:
  +
  +
* [[Plainly partible]]
  +
* [[Disposing of dismissives]]
  +
* [[IO then abstraction]]
  +
  +
[[Category:Theoretical foundations]]

Latest revision as of 22:02, 16 September 2024

Regarding IO a, Haskell's monadic I/O type:

Some operations are primitive actions, corresponding to conventional I/O operations. Special operations (methods in the class Monad, see Section 6.3.6) sequentially compose actions, corresponding to sequencing operators (such as the semicolon) in imperative languages.

The Haskell 2010 Report, (page 107 of 329).

So for I/O, the monadic interface merely provides an abstract way to sequence its actions. However there is another, more direct approach to sequencing:

Control.Parallel.pseq :: a -> b -> b

(as opposed to the non-sequential Prelude.seq.) That means a more direct way of preserving referential transparency is also needed. For simple teletype I/O:

data OI
partOI  :: OI -> (OI, OI)
getChar :: OI -> Char
putChar :: Char -> OI -> ()

where:

  • OI isn't an ordinary Haskell type - ordinary Haskell types represent values without (externally-visible) side-effects, hence OI being abstract.
  • The action partOI is needed because each OI value can only be used once.
  • The action getChar obtains the the next character of input.
  • The function putChar expects a character, and returns an action which will output the given character.


Now for a few other I/O interfaces - if seq was actually sequential:

type M a   =  OI -> a

unit       :: a -> M a
unit x     =  \ u -> let !_ = partOI u in x 

bind       :: M a -> (a -> M b) -> M b
bind m k   =  \ u -> let !(u1, u2) = partOI u in
                     let !x = m u1 in
                     let !y = k x u2 in
                     y

getcharM   :: M Char
getcharM   =  getChar

putcharM   :: Char -> M () 
putcharM   =  putChar
type C a         =  (OI, a)

extract          :: C a -> a
extract (u, x)   =  let !_ = partOI u in x

duplicate        :: C a -> C (C a)
duplicate (u, x) =  let !(u1, u2) = partOI u in
                    (u2, (u1, x))

extend           :: (C a -> b) -> C a -> C b
extend h (u, x)  =  let !(u1, u2) = partOI u in
                    let !y        = h (u1, x) in
                    (u2, y)

getcharC         :: C () -> Char
getcharC (u, ()) =  getChar u

putcharC         :: C Char -> ()
putcharC (u, c)  =  putChar c u
type A b c   =  (OI -> b) -> (OI -> c)

arr          :: (b -> c) -> A b c
arr f        =  \ c' u -> let !x = c' u in f x

both         :: A b c -> A b' c' -> A (b, b') (c, c')
f' `both` g' =  \ c' u -> let !(u1:u2:u3:_) = partsOI u in
                          let !(x, x')      = c' u1 in
                          let !y            = f' (unit x) u2 in
                          let !y'           = g' (unit x') u3 in
                          (y, y')
                where
                  unit x u = let !_ = partOI u in x

getcharA     :: A () Char
getcharA     =  \ c' u -> let !(u1, u2) = partOI u in
                          let !_        = c' u1 in
                          let !ch       = getChar u2 in
                          ch     

putcharA     :: A Char ()
putcharA     =  \ c' u -> let !(u1, u2) = partOI u in
                          let !ch       = c' u1 in
                          let !z        = putChar ch u2 in
                          z

The OI interface can also be used to implement I/O models used in earlier versions of Haskell:

  • dialogues:
runD :: ([Response] -> [Request]) -> OI -> ()
runD d u = foldr (\ (!_) -> id) () $ yet $ \ l -> zipWith respond (d l) (partsOI u)

yet :: (a -> a) -> a
yet f = f (yet f)

respond :: Request -> OI -> Response
respond Getq     u = let !c = getChar u in Getp c
respond (Putq c) u = let !_ = putChar c u in Putp

data Request  = Getq | Putq Char
data Response = Getp Char | Putp
type Answer = OI -> ()

runK :: Answer -> OI -> ()
runK a u = a u

doneK :: Answer
doneK = \ u -> let !_ = partOI u in ()

getcharK :: (Char -> Answer) -> Answer
getcharK k   = \ u -> let !(u1, u2) = partOI u in
                      let !c        = getChar u1 in
                      let !a        = k c in
                      a u2

putcharK :: Char -> Answer -> Answer
putcharK c a = \ u -> let !(u1, u2) = partOI u in
                      let !_        = putChar c u1 in
                      a u2

...and even that world state-passing style used in GHC, and by Clean, Single-Assignment C and as part of the I/O model used for the verification of interactive programs in CakeML, remembering that OI values can only be used once:

newtype World = W OI

getcharL :: World -> (Char, World)
getcharL (W u) = let !(u1, u2) = partOI u in
                 let !c = getChar u1 in
                 (c, W u2)

putcharL :: Char -> World -> World
putcharL c (W u) = let !(u1, u2) = partOI u in
                   let !_ = putChar c u1 in
                   W u2

(Rewriting those examples to use pseq is left as an exercise.)

See also: