{-# LINE 1 "libraries/ghci/GHCi/Utils.hsc" #-}
{-# LANGUAGE CPP #-}
module GHCi.Utils
( getGhcHandle
, readGhcHandle
)
where
import Prelude
import Foreign.C
import GHC.IO.Handle (Handle())
{-# LINE 26 "libraries/ghci/GHCi/Utils.hsc" #-}
import System.Posix
{-# LINE 28 "libraries/ghci/GHCi/Utils.hsc" #-}
{-# LINE 52 "libraries/ghci/GHCi/Utils.hsc" #-}
getGhcHandle :: CInt -> IO Handle
getGhcHandle :: CInt -> IO Handle
getGhcHandle CInt
fd = Fd -> IO Handle
fdToHandle (Fd -> IO Handle) -> Fd -> IO Handle
forall a b. (a -> b) -> a -> b
$ CInt -> Fd
Fd CInt
fd
{-# LINE 55 "libraries/ghci/GHCi/Utils.hsc" #-}
readGhcHandle :: String -> IO Handle
readGhcHandle :: String -> IO Handle
readGhcHandle String
s = do
{-# LINE 68 "libraries/ghci/GHCi/Utils.hsc" #-}
let fd :: CInt
fd = String -> CInt
forall a. Read a => String -> a
Prelude.read String
s
{-# LINE 70 "libraries/ghci/GHCi/Utils.hsc" #-}
getGhcHandle fd