GHC as a library - getting output from GHCI
Mads Lindstrøm
mads_lindstroem at yahoo.dk
Wed May 9 18:25:27 EDT 2007
Hi
While wrapIO works in most cases, try running this:
:m +Control.Concurrent
forkIO (let foo = do threadDelay 1000000; print "A"; foo in foo)
I am not saying that this makes wrapIO unusable - just that it is not
bulletproof. If not using forkIO is ok, then this is a much easier
solution, than creating a separate process for running "GHC as a
library" - that is having the GUI in one process and having "GHC as a
library in a child process.
Greetings,
Mads
Matthew Danish wrote:
> On Wed, May 09, 2007 at 10:48:15PM +0200, Mads Lindstr?m wrote:
> > Hi
> >
> > Look at System.Posix.IO
> >
> > I do not know if that module can do what you want. But it does deal with
> > FileDescriptors and handles.
> >
> > Maybe the dup function can help you. According to
> > http://www2.lib.uchicago.edu/~keith//tcl-course/topics/processes.html it
> > does:
> >
> > "The dup implements the dup system call, which duplicates one desired
> > open file descriptor into another. This can be used connect standard
> > input or standard output to a pipe. This sample code shows how a parent
> > process can fork the standard Unix sort command and then feed it data to
> > be sorted. A simple extension would allow the child to write the results
> > back to the parent."
> >
> > But I have not tested it yet, and I am not really familiar with Unix
> > inter-process communication.
> >
>
> Right, good thinking. This is what I've come up with for Unix-only:
>
> > module WrapIO where
> > import System.IO
> > import System.Posix.IO
> > import Control.Exception
>
> > wrapIO :: IO a -> IO (a, String)
> > wrapIO action = do
> > oldStdOutput <- dup stdOutput
> > (rd, wr) <- createPipe
> > dupTo wr stdOutput
> > v <- action
> > h <- fdToHandle rd
> > closeFd wr
> > s <- hGetContents h
> > return (v, s)
> > `finally` do
> > dupTo oldStdOutput stdOutput
> > closeFd oldStdOutput
>
> Unfortunately, dupTo will not work on Win32 afaik.
>
More information about the Glasgow-haskell-users
mailing list