GHC as a library - getting output from GHCI
Matthew Danish
mdanish at andrew.cmu.edu
Wed May 9 17:50:44 EDT 2007
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.
--
-- Matthew Danish -- user: mrd domain: cmu.edu
-- OpenPGP public key: C24B6010 on keyring.debian.org
More information about the Glasgow-haskell-users
mailing list