> 
> main :: World ()
> getFileSystem :: World (FileSystem ())
> joinFileSystem :: FileSystem a -> World a
> 
> writeCh :: Char -> File ()
> readCh :: File Char
> 
> If a sophisticated decompositions of the world are chosen, it should
> be easier to optimise functions locally and globally and to exploit
> the parallelism of interactive function. But this proposal may need
> the annotation of uniqness. 
> 
> Another possibility is something like this:
> 
> main :: ST World ()
> runFileSystem :: ST FileSystem a -> ST World a   -- or syncFileSystem
> runFile :: ST File a -> ST FileSystem a          --    syncFile
> 
> writeCh :: Char -> ST File ()
> readCh :: ST File Char
> 
> main = do
>       runFileSystem  $ do { ... }              -- implicit parallelism
>       runEventSystem $ do { ... } 
>       ...
>       return ()
> 

I've been thinking about a similar problem with mixing mutable variables
and IO operations.  

I want to be able to run actions on a MutVar monad so that imperative
programming can be encapsulated within pure functional code.  But then
at another time I want to set some of these variables from IO operations
so the result must be the IO monad.  

Conceptually I think that what I want is to say that there are IO
operations and MutVar operations going on in parallel

    type System = (IO a, MutVar b)

and make System into some sort of monad to keep everything linear
(waving my hands around the type variables)

    system `bind` {choose 
          (a -> IO b)   update the IO component of System
          (u -> MutVar v) update the MutVar component of System
          }

I've used existential types in System and overloaded the bind operation.

(I could keep going in this vein subdividing System into monads for each
variable and overload on each of them and I think I end up reinventing
concurrency where each state transformer thread is a distinct process
which updates its own piece of the system state.)

The examples that you have with runFileSystem suggest to me the
subtyping of monads where runFileSystem is an explicit monad coercion.
If I have a monad hierarchy

        Action
            IO
                FileIO
                EventIO
            Runnable
                MutVar

and overload (perhaps dynamically) bind on all of the monads I could
have these combinations

    MutVar `bind` MutVar -> MutVar
        This remains runnable.  The state vanishes as a result of running.

    MutVar `bind` IO -> Action
    Action `bind` MutVar -> Action
        These must synchronise globally.  The state must be the union of
        the states of each monad in the hierarchy.  bind updates the
        appropriate part depending on the actual kind of the monad.

    FileIO `bind` FileIO -> FileIO
        Pure file IO operations needn't interact with the event system.
    
    FileIO `bind` EventIO -> IO
        Mixed IO operations may need to interact with each other.
    

-- 
Anthony Shipman                 "You've got to be taught before it's too late,
TUSC Computer Systems Pty Ltd    Before you are six or seven or eight,
666 Doncaster Rd, Doncaster      To hate all the people your relatives hate,
Melbourne, Australia, 3108       You've got to be carefully taught."  R&H



Reply via email to