[Haskell-cafe] Do monads imply laziness?

Stefan O'Rear stefanor at cox.net
Sat Apr 14 11:22:04 EDT 2007


On Sat, Apr 14, 2007 at 10:56:44AM -0400, Brian Hurt wrote:
> 
> This is probably an off-topic question, but I can't think of a better 
> forum to ask it: does the existance of monads imply laziness in a 
> language, at least at the monadic level?
> 
> Consider the following: a purely functional, eagerly evaluated programming 
> language, that uses monads to encapsulate the awkward squad.  In this 
> programming language, a program generates an IO monad whose encapsulating 
> computation performs side effecting affections- it writes to stdout, say. 
> But this generated monad never has it's value evaluated- the monad is 
> tossed away uninspected.  Does the side effect happen?  If the answer is 
> at least potientially "no", then monads are lazily evaluated, and thus 
> monads imply laziness (at least at the monadic level).  On the other hand, 
> if the answer is "yes", then monads do not imply laziness.

First off, having monadic IO does not mean that there are side effects
at ANY level, consider:

data IOTree = PutChar Char IOTree | GetChar (Char -> IOTree)

type IO = Cont IOTree

putChar ch = Cont $ \x -> PutChar ch (x ())
getChar = Cont $ \x -> GetChar x

No effects, monadic IO!

Secondly, all real languages delay evaluation on a function, so that
IOTree will not be constructed all at once, but incrementally as input
arrives.  If you want it more incremental in a strict language, it
would be simple:

data IOTree = PutChar Char (() -> IOTree) | GetChar (Char -> IOTree)

---------------------------

Just for fun, here is code for monadic IO in the pure subset of O'Caml
(a strict functional language).  All side effects are in 'interp'. 

type iotree = Stop | Put of char * (unit -> iotree) | Get of (char -> iotree);;
type 'a io = ('a -> iotree) -> iotree;;

let putChar ch cont = Put (ch, cont) ;;
let getChar cont = Get cont ;;
let exit cont = Stop ;;

let (>>=) act aft cont = act (fun v -> aft v cont) ;;
let return vl cont = cont vl ;;

let rec interp0 tree = match tree with
            Stop -> ()
          | Put (ch, ct) -> print_char ch ; interp0 (ct ())
          | Get ct -> interp0 (ct (input_char stdin)) ;;
let interp act = interp0 (act (fun x -> Stop)) ;;

--------------------------

Stefan


More information about the Haskell-Cafe mailing list