convering Fds to Handles

Is there a way to convert an Fd variable to a Handle variable? Specifically, I'd like to use "pipe" from the Posix library to create a pipe and then pass one end of it to runProcess as its stdin. Abe

Is there a way to convert an Fd variable to a Handle variable? Specifically, I'd like to use "pipe" from the Posix library to create a pipe and then pass one end of it to runProcess as its stdin.
You can use the (undocumented) function Posix.fdToHandle I have had problems with pipes and runProcess, now I am using forkProcess/executeFile/getProcessStatus and it works properly. -- Sébastien

Sebastien Carlier
Specifically, I'd like to use "pipe" from the Posix library to create a pipe and then pass one end of it to runProcess as its stdin.
You may want to take a look at POpen (available from hslibs cvs, or http://www.01.246.ne.jp/~juhp/haskell/popenhs/). Process output works well, though it still has some problems with lazy process input.
I have had problems with pipes and runProcess, now I am using forkProcess/executeFile/getProcessStatus and it works properly.
Non-lazy IO presumably? Do you have an example you can show? Jens

Hi,
I have had problems with pipes and runProcess, now I am using forkProcess/executeFile/getProcessStatus and it works properly.
Non-lazy IO presumably? Do you have an example you can show?
Sure: ---_%--- cut here ---_%--- module Main where import IO import Posix import System main = do (ri, wi) <- createPipe (ro, wo) <- createPipe rih <- fdToHandle ri woh <- fdToHandle wo runProcess "/bin/cat" [] Nothing Nothing (Just rih) (Just woh) Nothing wih <- fdToHandle wi hPutStrLn wih (replicate 10000 'a') roh <- fdToHandle ro cs <- hGetContents roh fdClose wi putStrLn (show $ length cs) ---_%--- cut here ---_%--- I am using GHC 5.03 from the HEAD (May 12 2002), on MacOS X. Older versions of GHC on Linux exhibit the same behavior. Output:
localhost% ghc -o foo -package posix Main.hs localhost% ./foo /bin/cat: stdin: Resource temporarily unavailable 8192 localhost%
It seems that the output is truncated to some buffer size, and I couldn't get rid of the error message. If you set up the file descriptors yourself (using dupTo, fdClose, forkProcess, and executeFile as appropriate), it seems to works better (no error message, and no limit on input/ouput size). Is runProcess broken? Or does the above example abuse its power? -- Sébastien

Sebastien Carlier
I have had problems with pipes and runProcess, now I am using forkProcess/executeFile/getProcessStatus and it works properly.
Non-lazy IO presumably? Do you have an example you can show?
Sure:
---_%--- cut here ---_%--- <snip> ---_%--- cut here ---_%---
It seems that the output is truncated to some buffer size, and I couldn't get rid of the error message.
If you set up the file descriptors yourself (using dupTo, fdClose, forkProcess, and executeFile as appropriate), it seems to works better (no error message, and no limit on input/ouput size).
I meant do you have an example of your working code. Jens

I meant do you have an example of your working code.
Sure.
localhost% cat Main.hs
module Main where
import SubProcess
main = do cs <- subprocess "/bin/cat" [] (Just $ replicate 10000 $ 'a') putStrLn $ show $ length cs
localhost% ghc -package posix --make -o foo Main.hs ghc-5.03: chasing modules from: Main.hs Compiling SubProcess ( SubProcess.lhs, SubProcess.o ) Compiling Main ( Main.hs, ./Main.o ) ghc: linking ... localhost% ./foo 10000 localhost%
Note that is does leave zombie processes, since getProcessStatus is never called. I think, maybe appending something like the following to the ouput would work: output ++ (seq (unsafePerformIO childStatus) []) where childStatus = hClose roh ; getProcessStatus True False pid You would return childStatus along with the ouput. If the end of the string is reached, the zombie child will be reaped automatically. If you prematurely decide to stop reading the ouput, you have to call childStatus manually. I didn't bother to test it, because I didn't care about zombie processes. -- Sébastien

* Sebastien Carlier
I meant do you have an example of your working code.
Sure.
I'm sorry if this is a bit off-topic, but I got the following error when compiling Sebastien's code (with my ghc-5.02.3-2mdk): SubProcess.lhs:5: failed to load interface for `Posix': Could not find interface file for `Posix' while my Posix library files found in /usr/lib/ghc-5.02.3/imports/posix/ and also my /usr/lib/ghc-5.02.3/package.conf seems perfectly normal any hints pls? -- Regards, Jerry

On Friday, May 17, 2002, at 11:58 AM, Jerry, JiJie wrote:
SubProcess.lhs:5: failed to load interface for `Posix': Could not find interface file for `Posix'
while my Posix library files found in /usr/lib/ghc-5.02.3/imports/posix/ and also my /usr/lib/ghc-5.02.3/package.conf seems perfectly normal
any hints pls?
Make sure you added -package posix to you compilation command. -- Sébastien

Hi, I'm sorry to bother everyone again with this simple append' stuff -- below is my revised append' function 1) append' :: [[a]] -> a -> [[a]] 2) append' [] y = [[y]] 3) append' (x:xs) y = 4) case xs of [] -> foldr (:) [y] x 5) (z:zs) -> (init (x:xs)) ++ [(last xs)++[y]] -- to achieve append' [] 1 = [[1]] append' [[1]] 2 = [[1, 2]] append' [[1], [2]] 3 = [[1], [2, 3]] -- and ghc gives the following compile error: p3a.hs:4: Cannot unify the type-signature variable `a' with the type `[a]' Expected type: [a] Inferred type: a In the list element: y In the second argument of `foldr', namely `([y])' make: *** [p3a] Error 1 -- now this is something I _really_ don't understand: -- x is of type [a], [y] is of type [a], and isn't foldr (:) [a] [a] -- perfectly valid?! Much thanx in advance -- Regards, Jerry

On Fri, 17 May 2002, Jerry wrote:
Hi, I'm sorry to bother everyone again with this simple append' stuff -- now this is something I _really_ don't understand: -- x is of type [a], [y] is of type [a], and isn't foldr (:) [a] [a] -- perfectly valid?!
:type foldr forall a b. (a -> b -> b) -> b -> [a] -> b now foldr is used with (:) which has type a -> [a] ->[a] so, to find the type of foldr (:) the type (a-> b -> b) must be unified with (:):: c->[c] -> [c] therefore, (replacing a with c and b with [c]) foldr (:) :: [c] -> [c] -> [c] which is what you expected. however, you forgot. 1) append' :: [[a]] -> a -> [[a]] 2) append' [] y = [[y]] 3) append' (x:xs) y = 4) case xs of [] -> foldr (:) [y] x 5) (z:zs) -> (init (x:xs)) ++ [(last xs)++[y]] in "case of [] -> foldr (:) [y] x", foldr (:) [y] x :: [c], the same type as x. but append' works on lists of type [[c]] adds a element of type c and returns something of type [[c]], as you have declared in the type declaration of append'. so, what is the real problem? the type given by foldr (:) [y] x :: [c] doesn't match the resultant type of append', namely [[c]] Also, another good thing to check is that all branches of a case statement have the same type. If something x =case x of True -> 3; False -> "lala" could compile, what would be it's type?? (Hint, if you come from the dynamically typed world and do want to do something of the sort, there is the Either type. case x of True -> Left 3; False -> Right "lala" Jay Cox

Hi Sebastian,
Sebastien Carlier
I meant do you have an example of your working code.
Sure.
[SubProcess.lhs] Great, thank you! Looks like you got it right: that's the first code I have seen with working reading in of a string to a subprocess. I think it would be useful to have this included in the Haskell libraries. I'd be happy to fold it into POpen too, though I rather like the name SubProcess. Jens

Hi, Jens,
I think it would be useful to have this included in the Haskell libraries. I'd be happy to fold it into POpen too, though I rather like the name SubProcess.
Sure, please do. I'm not overly fond of the name I gave it, popen is definitely better. Maybe it would be a good thing to add a remark to the documentation of runProcess, to mention popen. Also, I think runProcess can be made to work with pipes, but it requires some cheating with unsafePerformIO to force the child to close the file descriptors... Fork is the tool of the demon ! -- Sébastien
participants (6)
-
Abraham Egnor
-
Jay Cox
-
Jens Petersen
-
Jerry
-
Jerry, JiJie
-
Sebastien Carlier