How to write to other file descriptors than stdout and stderr

This question is similar to this stackexchange post Is it possible to write to other file descriptors in C? - Unix & Linux Stack Exchange

Now, every process is free to use file descriptors as they please. Except that 0, 1 and 2 are by convention reserved for stdin, stdout and stderr. Other fds are generally not special, but in shells (which are just one type of application), fds 0 to <some-value> where some value is at least 9 are reserved for usage by the user (of the shell). The shell will not mingle with them for its own internal soup.

How can i do this in haskell? I couldn’t directly find a relevant function with hoogle, so i tried working backwards starting at the low level API. I found some FFI to c_write. ghc-9.6.4-release/libraries/base/System/Posix/Internals.hs?ref_type=tags#L495 and ghc-9.6.4-release/libraries/base/System/Posix/Internals.hs?ref_type=tags#L608

The only function that i found that takes a file descriptor and is being exported is this one ghc-9.6.4-release/libraries/base/GHC/IO/FD.hs?ref_type=tags#L618

I tried making a simple program using this function.

module Main (main) where

import Data.ByteString.Internal
import Debug.Trace
import Foreign.ForeignPtr
import GHC.IO.Device
import GHC.IO.FD
import GHC.IO.Handle.FD
import Prelude
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import System.IO
import System.IO (IOMode(..))
import System.Posix.Types

deriving instance Show IODeviceType

newFD :: IO (FD, IODeviceType)
newFD =
  let io_device_type = Just (RawDevice, CDev 0, CIno 0)
  in  mkFD 3 WriteMode io_device_type False True

main :: IO ()
main = do
  putStrLn "Starting program"
  (fd, io_device_type) <- newFD
  traceShowM fd
  traceShowM io_device_type
  let (BS payload length) = T.encodeUtf8 ("Hello world" :: T.Text)
  withForeignPtr payload $ \pl -> do
    writeRawBufferPtr "string for debugging?" fd pl 0 (fromIntegral length)
  return ()

Output

Starting program
3
RawDevice
handles: string for debugging?: invalid argument (Invalid argument)

Questions

  • Why does it print “invalid argument”? Which argument is invalid and what should it be instead?
  • What are CDev and CIno?
  • Why do i have to specify an IODeviceType? Linux write API does not have a parameter for a device type https://linux.die.net/man/2/write
  • Are there any other functions that accept file descriptors directly that i missed? (GHC 9.6.4)
  • Any other suggestions for improvement of this program are welcome.

As for why… Sometimes i want to “hack” into existing programs that use stdout and stderr for their own purposes. I want to log some debug statements but keep the ability to mix stdout, stderr and other output into a single file. If i were to log to a file directly i don’t think this would be possible. And also I’m interested in the low level bits of Haskell.

fdWrite, perhaps?

1 Like