[Haskell] line-based interactive program

Peter Achten P.Achten at cs.ru.nl
Thu Jul 14 07:17:48 EDT 2005


At 12:02 PM 7/12/2005, Wolfgang Jeltsch wrote:
>Am Montag, 11. Juli 2005 15:51 schrieben Sie:
> > [...]
>
> > I am always interested in functional I/O solutions that adopt the
> > "world-as-value" paradigm (or the more verbose "explicit multiple
> > environment passing" paradigm) that has been exploited in Clean's file I/O
> > system and GUI library. Your idea sounds interesting, but your explanation
> > above of runFileIO and finishFileIO raises a few questions:
> >
> > (1) Suppose you have a file with content "abcde" at path p. What does the
> > following program fragment yield?
> > do
> >          (r1,h1) <- runFileIO p readEntireFile
> >          (r2,h2) <- runFileIO p readEntireFile
> >          return hd r1 : hd r2
>
>You mean return hd r1 : hd r2 : [], don't you?
Sure, forgive my rusty Haskell...

> > where readEntireFile reads the entire file and returns it as a string. I
> > can imagine several results: [a,a], [a,b], [a,_|_], [_|_,_|_], _|_.
>
>I decided to distinguish between read-only I/O and write-permitted I/O.  If
>readEntireFile is declared as read-only I/O (which would be sensible) then
>the above code would return ['a','a'] since multiple read-only actions are
>allowed at the same time.

['a','a'] is a good result in case of multiple readers. But how do you 
distinguish between read-only I/O and write-permitted I/O? In your example 
you introduced:
>     readChar :: FileIO Char
>     writeChar :: Char -> FileIO ()
Both belong to the FileIO monad. This also relates to the question at the 
bottom of the previous e-mail.

> > (2) Can a writer interfere with a reader? Let writeFile :: Integer -> Char
> > -> FileIO () write n times a given char to a file. What is then the result
> > of:
> > do
> >         (r1,h1) <- runFileIO p readEntireFile
> >          (r2,h2) <- runFileIO p (writeFile 5 'X')
> >          return (r2,r1)
> > Does it yield ((),"abcde"), ((),"XXXXX"), (_|_,"abcde"), or _|_? What is
> > the result when (r1,r2) is returned instead of (r2,r1)?
>
>An important aim concerning my approach is that resulting states and results
>of actions shall be independent of evaluation order.  So swapping the
>components of a result pair should never make a difference instead of
>swapping the components, of course.
>
>When execution comes to the point where the writeFile actions has to be
>started, p is already opened for reading.  So the second runFileIO would
>return _|_ and the pattern matching would fail.  Alas, I didn't think about
>how to implement fail for those lazy I/O monads so far.
>
>The problem here is, of course, that I just want to return two values and 
>have
>to use a lifted pair in order to do this while an unlifted pair would make
>more sense.  If we try to simulate the effect of using an unlifted pair, we
>probably would use a lazy pattern for matching.  If you would do so, r2 and
>h2 would just become _|_ so that the result of the whole action would just be
>(_|_,"abcde").
>
>A better solution would be to let runFileIO throw an exception or return
>values of type Maybe (result,FileIOHandle).
>
>Thanks for asking this question.  It reveals problems I didn't think about so
>far.
>
> > (3) One of the advantages of an explicit environment passing scheme is that
> > you get true functional behaviour of programs. As an example, in Clean you
> > can write a function that tests the content of a file, and if successfull
> > proceeds with the remainder, and otherwise with its argument file. (Clean
> > code ahead):
> > parseInt :: Int File -> (Int,File)
> > parseInt n file
> >
> >      | ok && isDigit c = parseInt (n*10+d) file1
> >      | otherwise       = (n,file)
> >
> > where (ok,c,file1)    = sfreadc file
> >        d               = toInt c - toInt '0'
> > Does your scheme allow such kind of behavior?
>
>Currently not.  However, I think it would be possible by creating an
>appropriate instance of MonadPlus for read-only actions.  mzero would denote
>some kind of failing and action1 `mplus` action2 would denote an action which
>would first try to execute action1 and if action1 fails try to execute
>action2 starting with the local state (file pointer position or whatever)
>that was present before running action1.  Failure of read actions etc. should
>result in the action being equivalent to mzero.  So parseInt would become
>something like this:
>
>         parseInt :: Int -> FileReadIO Int
>         parseInt n =
>                 (do
>                         c <- readChar
>                         if isDigit c
>                                 then parseInt (10 * n + (ord c - ord '0'))
>                                 else mzero)
>                 `mplus` return n
>
>Thanks for asking this question since it helps me to improve my idea.
Here you introduce a FileReadIO monad. Is this the way you intend to 
distinguish between read-only actions and write-permitted actions? That 
seems okay.

Minor detail: you use readChar :: FileIO Char within FileReadIO monad. That 
won't type check.

> > > An extended version of this approach shall also handle situations like
> > > pure reading of files where not all read operations have to be carried
> > > out if they are not needed to produce the desired result.  In this case,
> > > finishFileIO would just close the file without previously executing the
> > > remainder of the file I/O action.  The problem is that it cannot be
> > > assured that as yet unevaluated parts of the result aren't evaluated
> > > after exeuction of finishFileIO.  Therefore, if evaluation after
> > > finishing demands the execution of read operations these operations shall
> > > not actually be executed but instead _|_ shall be returned.
> >
> > This scheme forces the programmer to carefully plan calls to finishFileIO.
> > Let's assume that the readEntireFile is a pure reader of files, then the
> > program fragment:
> > do
> >          (r1,h1) <- runFileIO p readEntireFile
> >          finishFileIO h1
> >          ... computations that use r1 ...
> > always use _|_ for r1. It is not always the case that
> > do
> >          (r1,h1) <- runFileIO p readEntireFile
> >          ... computations that use r1 ...
> >          finishFileIO h1
> > solves the problem, in particular when the computations that use r1 are
> > pure functions. You'd have to "connect" r1 to the WorldIO monad before
> > doing finishFileIO on h1.
>
>Hmm, I wasn't aware of the fact that in such cases the result actually 
>depends
>on evaluation order, something which I wanted to avoid.  However, if I choose
>to not provide a finishFileIO for read-only actions and implement some kind
>of implicit file closing when the whole file is read, it can be indeterminate
>if a future runFileIO on the same file fails or not since the question if the
>file is already closed or not might depend on evaluation order.
>
>The only solution I can imagine at the moment is to let finishFileIO force 
>the
>execution of the remaining I/O also in case of read-only actions.  But this
>would make implementing something like getContents impossible. :-(  Do you
>have an idea for a better approach?
Hmm (thinking...). No.

> > How can you tell a function is a pure reader?
>
>By its type.
See above comments: unless you use a separate type for readers like 
FileReadIO, or provide additional information to runFileIO I don't think 
you can distinguish them.

> > [...]
>
> > Good luck with your thesis. I'd like to see the final result.
>
>Thank you, that's nice. :-)  Alas, the thesis will be in German so if you
>don't understand German all you can do is to see if I will translate the
>relevant parts into English. :-(  Of course, the code will also tell a lot.
Please don't go through the trouble of translating to English. My German is 
fairly rusty, but I should be able to manage. We're neighbours after all.

> > Regards,
> > Peter Achten
>
>Best wishes,
>Wolfgang Jeltsch
>_______________________________________________
>Haskell mailing list
>Haskell at haskell.org
>http://www.haskell.org/mailman/listinfo/haskell




More information about the Haskell mailing list