module Procex.Quick
  ( (<!|),
    (<<<),
    (<|),
    (|!>),
    (|>),
    capture,
    captureNoThrow,
    captureLazy,
    captureLazyNoThrow,
    captureErr,
    captureErrNoThrow,
    captureErrLazy,
    captureErrLazyNoThrow,
    captureFd,
    captureFdLazy,
    captureFdLazyNoThrow,
    pipeArgStrIn,
    mq,
    quickCmd,
    QuickCmd,
    quickCmdArg,
    QuickCmdArg,
    toByteString,
    ToByteString,
  )
where

import Control.Concurrent.Async (Async, async, cancel)
import Control.DeepSeq (force)
import qualified Data.ByteString as BS
import Data.ByteString.Lazy (ByteString)
import qualified Data.ByteString.Lazy as B
import qualified Data.ByteString.Lazy.UTF8 as B
import Procex.Core
import Procex.Process
import System.IO (Handle, hClose)
import System.IO.Unsafe (unsafeInterleaveIO)
import System.Posix.Process (ProcessStatus)
import System.Posix.Types (Fd)

-- | A helper class to convert to bytestrings with UTF-8 encoding
class ToByteString a where
  toByteString :: a -> B.ByteString

instance a ~ Char => ToByteString [a] where
  toByteString :: [a] -> ByteString
toByteString = [a] -> ByteString
String -> ByteString
B.fromString

instance ToByteString B.ByteString where
  toByteString :: ByteString -> ByteString
toByteString = ByteString -> ByteString
forall a. a -> a
id

instance ToByteString BS.ByteString where
  toByteString :: ByteString -> ByteString
toByteString = ByteString -> ByteString
B.fromStrict

-- | A helper class to allow lightweight syntax for executing commands
class QuickCmdArg a where
  quickCmdArg :: a -> Cmd -> Cmd

class QuickCmd a where
  quickCmd :: Cmd -> a

instance QuickCmdArg String where
  quickCmdArg :: String -> Cmd -> Cmd
quickCmdArg String
s = ByteString -> Cmd -> Cmd
passArg (ByteString -> Cmd -> Cmd) -> ByteString -> Cmd -> Cmd
forall a b. (a -> b) -> a -> b
$ String -> ByteString
B.fromString String
s

instance QuickCmdArg ByteString where
  quickCmdArg :: ByteString -> Cmd -> Cmd
quickCmdArg = ByteString -> Cmd -> Cmd
passArg

instance QuickCmdArg (Cmd -> Cmd) where
  quickCmdArg :: (Cmd -> Cmd) -> Cmd -> Cmd
quickCmdArg = (Cmd -> Cmd) -> Cmd -> Cmd
forall a. a -> a
id

instance {-# OVERLAPPABLE #-} (QuickCmdArg a, QuickCmd b) => QuickCmd (a -> b) where
  quickCmd :: Cmd -> a -> b
quickCmd Cmd
cmd a
arg = Cmd -> b
forall a. QuickCmd a => Cmd -> a
quickCmd (Cmd -> b) -> Cmd -> b
forall a b. (a -> b) -> a -> b
$ a -> Cmd -> Cmd
forall a. QuickCmdArg a => a -> Cmd -> Cmd
quickCmdArg a
arg Cmd
cmd

instance (a ~ ()) => QuickCmd (IO a) where
  quickCmd :: Cmd -> IO a
quickCmd = Cmd -> IO a
Cmd -> IO ()
run

instance QuickCmd Cmd where
  quickCmd :: Cmd -> Cmd
quickCmd = Cmd -> Cmd
forall a. a -> a
id

-- | >>> mq "cat" "/dev/null" (pipeArgIn 1 $ mq "cat" "/dev/null") <<< "somestr"
--
-- The first argument is the path, and the subsequent arguments are 'QuickCmdArg'.
-- At the end you will either have an @IO ()@ (synchronous execution) or 'Cmd' (which you can further use).
mq ::
  (QuickCmd a, ToByteString b) =>
  -- | The path to the executable, uses PATH
  b ->
  -- | Either a 'Cmd', an @IO ()@, or a function that takes @Cmd -> Cmd@ , 'String' or 'ByteString'
  a
mq :: b -> a
mq b
path = Cmd -> a
forall a. QuickCmd a => Cmd -> a
quickCmd (Cmd -> a) -> Cmd -> a
forall a b. (a -> b) -> a -> b
$ ByteString -> Cmd
makeCmd (b -> ByteString
forall a. ToByteString a => a -> ByteString
toByteString b
path)

-- | Pipe from the right command to the left command.
-- Returns the left command modified.
infixl 1 <|

(<|) :: QuickCmd a => Cmd -> Cmd -> a
<| :: Cmd -> Cmd -> a
(<|) Cmd
x Cmd
y = Cmd -> a
forall a. QuickCmd a => Cmd -> a
quickCmd (Cmd -> a) -> Cmd -> a
forall a b. (a -> b) -> a -> b
$ Fd -> Fd -> Cmd -> Cmd -> Cmd
pipeIn Fd
1 Fd
0 Cmd
y Cmd
x

-- | Pipe from the right command's stderr to the left command.
-- Returns the left command modified.
infixl 1 <!|

(<!|) :: QuickCmd a => Cmd -> Cmd -> a
<!| :: Cmd -> Cmd -> a
(<!|) Cmd
x Cmd
y = Cmd -> a
forall a. QuickCmd a => Cmd -> a
quickCmd (Cmd -> a) -> Cmd -> a
forall a b. (a -> b) -> a -> b
$ Fd -> Fd -> Cmd -> Cmd -> Cmd
pipeIn Fd
2 Fd
0 Cmd
y Cmd
x

-- | Pipe from the left command to the right command.
-- Returns the left command modified.
infixl 1 |>

(|>) :: QuickCmd a => Cmd -> Cmd -> a
|> :: Cmd -> Cmd -> a
(|>) Cmd
x Cmd
y = Cmd -> a
forall a. QuickCmd a => Cmd -> a
quickCmd (Cmd -> a) -> Cmd -> a
forall a b. (a -> b) -> a -> b
$ Fd -> Fd -> Cmd -> Cmd -> Cmd
pipeOut Fd
0 Fd
1 Cmd
y Cmd
x

-- | Pipe from the left command's stderr to the right command.
-- Returns the left command modified.
infixl 1 |!>

(|!>) :: QuickCmd a => Cmd -> Cmd -> a
|!> :: Cmd -> Cmd -> a
(|!>) Cmd
x Cmd
y = Cmd -> a
forall a. QuickCmd a => Cmd -> a
quickCmd (Cmd -> a) -> Cmd -> a
forall a b. (a -> b) -> a -> b
$ Fd -> Fd -> Cmd -> Cmd -> Cmd
pipeOut Fd
0 Fd
2 Cmd
y Cmd
x

-- | Pass a string as stdin.
infixl 1 <<<

(<<<) :: (QuickCmd a, ToByteString b) => Cmd -> b -> a
<<< :: Cmd -> b -> a
(<<<) Cmd
cmd b
str = Cmd -> a
forall a. QuickCmd a => Cmd -> a
quickCmd (Cmd -> a) -> Cmd -> a
forall a b. (a -> b) -> a -> b
$ Fd -> (Async ProcessStatus -> Handle -> IO ()) -> Cmd -> Cmd
pipeHIn Fd
0 (\Async ProcessStatus
_ Handle
h -> Handle -> ByteString -> IO ()
B.hPut Handle
h (b -> ByteString
forall a. ToByteString a => a -> ByteString
toByteString b
str) IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Handle -> IO ()
hClose Handle
h) Cmd
cmd

-- This function is pretty much never useful. If you want to handle the output
-- of the command, use `capture` or similar.
-- The problem is that it creates a new thread in the background, when
-- what we really want is to handle the output in the foreground, because
-- when our foreground is done executing, it will not wait for the background threads
-- to stop executing too.
---- | Handle the output from stdout.
--infixl 1 >>>
--
--(>>>) :: QuickCmd a => Cmd -> (ByteString -> IO ()) -> a
--(>>>) cmd handler = quickCmd $ pipeHOut 1 (\_ h -> B.hGetContents h >>= handler) cmd

-- Disabled with same reason as for `>>>`.
---- | Handle the output from stderr.
----infixl 1 !>>>
----
----(!>>>) :: QuickCmd a => Cmd -> (ByteString -> IO ()) -> a
----(!>>>) cmd handler = quickCmd $ pipeHOut 2 (\_ h -> B.hGetContents h >>= handler) cmd

-- | Pass an argument of the form @\/proc\/self\/fd\/\<n\>@ to the process,
-- where `n` is the reader end of a pipe which the passed string is written to.
pipeArgStrIn :: ToByteString b => b -> Cmd -> Cmd
pipeArgStrIn :: b -> Cmd -> Cmd
pipeArgStrIn b
str = (Async ProcessStatus -> Handle -> IO ()) -> Cmd -> Cmd
pipeArgHIn (\Async ProcessStatus
_ Handle
h -> Handle -> ByteString -> IO ()
B.hPut Handle
h (b -> ByteString
forall a. ToByteString a => a -> ByteString
toByteString b
str) IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Handle -> IO ()
hClose Handle
h)

-- Disabled with same reason as for `>>>`.
--pipeArgStrOut :: (ByteString -> IO ()) -> Cmd -> Cmd
--pipeArgStrOut handler = pipeArgHOut (\_ h -> B.hGetContents h >>= handler)

attachFinalizer :: IO () -> ByteString -> IO ByteString
attachFinalizer :: IO () -> ByteString -> IO ByteString
attachFinalizer IO ()
finalizer ByteString
str = [ByteString] -> ByteString
B.fromChunks ([ByteString] -> ByteString) -> IO [ByteString] -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ByteString] -> IO [ByteString]
go (ByteString -> [ByteString]
B.toChunks ByteString
str)
  where
    go :: [BS.ByteString] -> IO [BS.ByteString]
    go :: [ByteString] -> IO [ByteString]
go [] = IO [ByteString] -> IO [ByteString]
forall a. IO a -> IO a
unsafeInterleaveIO (IO [ByteString] -> IO [ByteString])
-> IO [ByteString] -> IO [ByteString]
forall a b. (a -> b) -> a -> b
$ IO ()
finalizer IO () -> IO [ByteString] -> IO [ByteString]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [ByteString] -> IO [ByteString]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
    go (ByteString
x : [ByteString]
xs) = (ByteString
x ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
:) ([ByteString] -> [ByteString])
-> IO [ByteString] -> IO [ByteString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ByteString] -> IO [ByteString]
go [ByteString]
xs

captureFdLazy' :: Fd -> (Async ProcessStatus -> IO ()) -> Cmd -> IO ByteString
captureFdLazy' :: Fd -> (Async ProcessStatus -> IO ()) -> Cmd -> IO ByteString
captureFdLazy' Fd
fd Async ProcessStatus -> IO ()
finalizer Cmd
cmd = do
  (Async ProcessStatus
status, [Item [Handle]
h]) <- [Fd] -> Cmd -> IO (Async ProcessStatus, [Handle])
captureFdsAsHandles [Item [Fd]
Fd
fd] Cmd
cmd
  ByteString
out <- Handle -> IO ByteString
B.hGetContents Handle
Item [Handle]
h
  IO () -> ByteString -> IO ByteString
attachFinalizer (Async ProcessStatus -> IO ()
finalizer Async ProcessStatus
status) ByteString
out

-- | Capture the output of the fd of the command lazily.
-- If the process exits with a non-zero exit code,
-- reading from the bytestring will throw 'Procex.Process.CmdException'.
captureFdLazy :: Fd -> Cmd -> IO ByteString
captureFdLazy :: Fd -> Cmd -> IO ByteString
captureFdLazy Fd
fd = Fd -> (Async ProcessStatus -> IO ()) -> Cmd -> IO ByteString
captureFdLazy' Fd
fd Async ProcessStatus -> IO ()
waitCmd

-- | Capture the output of the fd of the command lazily. Ignores process exit code.
captureFdLazyNoThrow :: Fd -> Cmd -> IO ByteString
captureFdLazyNoThrow :: Fd -> Cmd -> IO ByteString
captureFdLazyNoThrow Fd
fd = Fd -> (Async ProcessStatus -> IO ()) -> Cmd -> IO ByteString
captureFdLazy' Fd
fd (IO () -> Async ProcessStatus -> IO ()
forall a b. a -> b -> a
const (IO () -> Async ProcessStatus -> IO ())
-> IO () -> Async ProcessStatus -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

-- | Capture the stdout of the command lazily.
-- If the process exits with a non-zero exit code,
-- reading from the bytestring will throw 'Procex.Process.CmdException'.
captureLazy :: Cmd -> IO ByteString
captureLazy :: Cmd -> IO ByteString
captureLazy = Fd -> Cmd -> IO ByteString
captureFdLazy Fd
1

-- | Capture the stderr of the command lazily.
-- If the process exits with a non-zero exit code,
-- reading from the bytestring will throw 'Procex.Process.CmdException'.
captureErrLazy :: Cmd -> IO ByteString
captureErrLazy :: Cmd -> IO ByteString
captureErrLazy = Fd -> Cmd -> IO ByteString
captureFdLazy Fd
2

-- | Capture the stdout of the command lazily. Ignores process exit code.
captureLazyNoThrow :: Cmd -> IO ByteString
captureLazyNoThrow :: Cmd -> IO ByteString
captureLazyNoThrow = Fd -> Cmd -> IO ByteString
captureFdLazyNoThrow Fd
1

-- | Capture the stderr of the command lazily. Ignores process exit code.
captureErrLazyNoThrow :: Cmd -> IO ByteString
captureErrLazyNoThrow :: Cmd -> IO ByteString
captureErrLazyNoThrow = Fd -> Cmd -> IO ByteString
captureFdLazyNoThrow Fd
2

captureFd :: Fd -> Cmd -> IO (Async ProcessStatus, Handle)
captureFd :: Fd -> Cmd -> IO (Async ProcessStatus, Handle)
captureFd Fd
fd Cmd
cmd = (\(Async ProcessStatus
status, [Item [Handle]
h]) -> (Async ProcessStatus
status, Handle
Item [Handle]
h)) ((Async ProcessStatus, [Handle]) -> (Async ProcessStatus, Handle))
-> IO (Async ProcessStatus, [Handle])
-> IO (Async ProcessStatus, Handle)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Fd] -> Cmd -> IO (Async ProcessStatus, [Handle])
captureFdsAsHandles [Item [Fd]
Fd
fd] Cmd
cmd

-- | Capture the stdout of the command strictly, err if the command exits with a non-zero exit code.
capture :: Cmd -> IO ByteString
capture :: Cmd -> IO ByteString
capture Cmd
cmd = do
  (Async ProcessStatus
status, [Item [Handle]
h]) <- [Fd] -> Cmd -> IO (Async ProcessStatus, [Handle])
captureFdsAsHandles [Item [Fd]
1] Cmd
cmd
  ByteString
out <- ByteString -> ByteString
forall a. NFData a => a -> a
force (ByteString -> ByteString) -> IO ByteString -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Handle -> IO ByteString
B.hGetContents Handle
Item [Handle]
h
  Async ProcessStatus -> IO ()
waitCmd Async ProcessStatus
status
  ByteString -> IO ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
out

-- | Capture the stdout of the command strictly. Ignores process exit code.
captureNoThrow :: Cmd -> IO ByteString
captureNoThrow :: Cmd -> IO ByteString
captureNoThrow Cmd
cmd = do
  (Async ProcessStatus
status, [Item [Handle]
h]) <- [Fd] -> Cmd -> IO (Async ProcessStatus, [Handle])
captureFdsAsHandles [Item [Fd]
1] Cmd
cmd
  ByteString
out <- ByteString -> ByteString
forall a. NFData a => a -> a
force (ByteString -> ByteString) -> IO ByteString -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Handle -> IO ByteString
B.hGetContents Handle
Item [Handle]
h
  Async ()
_ <- IO () -> IO (Async ())
forall a. IO a -> IO (Async a)
async (IO () -> IO (Async ()))
-> (Async ProcessStatus -> IO ())
-> Async ProcessStatus
-> IO (Async ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async ProcessStatus -> IO ()
forall a. Async a -> IO ()
cancel (Async ProcessStatus -> IO (Async ()))
-> Async ProcessStatus -> IO (Async ())
forall a b. (a -> b) -> a -> b
$ Async ProcessStatus
status
  ByteString -> IO ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
out

-- | Capture the stderr of the command strictly, err if the command exits with a non-zero exit code.
captureErr :: Cmd -> IO ByteString
captureErr :: Cmd -> IO ByteString
captureErr Cmd
cmd = do
  (Async ProcessStatus
status, [Item [Handle]
h]) <- [Fd] -> Cmd -> IO (Async ProcessStatus, [Handle])
captureFdsAsHandles [Item [Fd]
2] Cmd
cmd
  ByteString
out <- ByteString -> ByteString
forall a. NFData a => a -> a
force (ByteString -> ByteString) -> IO ByteString -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Handle -> IO ByteString
B.hGetContents Handle
Item [Handle]
h
  Async ProcessStatus -> IO ()
waitCmd Async ProcessStatus
status
  ByteString -> IO ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
out

-- | Capture the stderr of the command strictly. Ignores process exit code.
captureErrNoThrow :: Cmd -> IO ByteString
captureErrNoThrow :: Cmd -> IO ByteString
captureErrNoThrow Cmd
cmd = do
  (Async ProcessStatus
status, [Item [Handle]
h]) <- [Fd] -> Cmd -> IO (Async ProcessStatus, [Handle])
captureFdsAsHandles [Item [Fd]
2] Cmd
cmd
  ByteString
out <- ByteString -> ByteString
forall a. NFData a => a -> a
force (ByteString -> ByteString) -> IO ByteString -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Handle -> IO ByteString
B.hGetContents Handle
Item [Handle]
h
  Async ()
_ <- IO () -> IO (Async ())
forall a. IO a -> IO (Async a)
async (IO () -> IO (Async ()))
-> (Async ProcessStatus -> IO ())
-> Async ProcessStatus
-> IO (Async ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async ProcessStatus -> IO ()
forall a. Async a -> IO ()
cancel (Async ProcessStatus -> IO (Async ()))
-> Async ProcessStatus -> IO (Async ())
forall a b. (a -> b) -> a -> b
$ Async ProcessStatus
status
  ByteString -> IO ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
out