From fb5636483871fbafe9b286b377c339c8ddf8b4f8 Mon Sep 17 00:00:00 2001
From: tv <tv@krebsco.de>
Date: Thu, 7 Feb 2019 18:42:36 +0100
Subject: initial commit

---
 src/Flameshot/Internal/Process.hs | 89 +++++++++++++++++++++++++++++++++++++++
 1 file changed, 89 insertions(+)
 create mode 100644 src/Flameshot/Internal/Process.hs

(limited to 'src/Flameshot/Internal')

diff --git a/src/Flameshot/Internal/Process.hs b/src/Flameshot/Internal/Process.hs
new file mode 100644
index 0000000..c435d48
--- /dev/null
+++ b/src/Flameshot/Internal/Process.hs
@@ -0,0 +1,89 @@
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE MultiWayIf #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE RecordWildCards #-}
+module Flameshot.Internal.Process (run,Callbacks(..)) where
+
+import Control.Concurrent (forkIO,threadDelay)
+import Control.Concurrent.Async (race)
+import Control.Exception
+import Control.Monad.Extended (untilM_,unless)
+import Data.Text (Text)
+import qualified Data.Text.IO as T
+import System.Exit
+import System.IO (BufferMode(LineBuffering),hSetBuffering)
+import System.IO (Handle,hClose,hPutStr,hIsEOF)
+import System.IO.Error (catchIOError,isDoesNotExistError)
+import System.Process
+import System.Posix.Process (getProcessGroupIDOf)
+import System.Posix.Signals (Signal,signalProcessGroup,killProcess)
+import System.Posix.Types (ProcessGroupID)
+
+data Callbacks = Callbacks
+    { onOutLine :: Pid -> Text -> IO ()
+    , onErrLine :: Pid -> Text -> IO ()
+    , onError :: Pid -> SomeException -> IO ()
+    , onExit :: Pid -> ExitCode -> IO ()
+    , onStart :: Pid -> IO ()
+    }
+
+run :: FilePath
+     -> [String]
+     -> Maybe FilePath
+     -> Maybe [(String, String)]
+     -> String
+     -> Maybe Int
+     -> Callbacks
+     -> IO ()
+run path args cwd env input hTimeout Callbacks{..} =
+    f `catch` onError (-1)
+  where
+    f = withCreateProcess p $ \(Just inh) (Just outh) (Just errh) ph -> do
+      Just pid <- getPid ph
+      pgid <- getProcessGroupIDOf pid
+
+      onStart pid
+
+      mapM_ forkIO [
+          hPutStr inh input `finally` hClose inh,
+          hWithLines outh (onOutLine pid),
+          hWithLines errh (onErrLine pid)
+        ]
+
+      case hTimeout of
+        Just time ->
+          race (threadDelay time) (waitForProcess ph) >>= \case
+            Left () -> onError pid (SomeException (ErrorCall "timeout"))
+            Right code -> onExit pid code
+        Nothing ->
+          waitForProcess ph >>= onExit pid
+
+      killProcessGroup pgid
+
+    p = (proc path args)
+          { cwd = cwd
+          , env = env
+          , std_in = CreatePipe
+          , std_out = CreatePipe
+          , std_err = CreatePipe
+          , close_fds = True
+          , create_group = True
+          , new_session = True
+          }
+
+
+
+killProcessGroup :: ProcessGroupID -> IO ()
+killProcessGroup = signalProcessGroup' killProcess
+
+signalProcessGroup' :: Signal -> ProcessGroupID -> IO ()
+signalProcessGroup' sig pgid =
+    catchIOError
+      (signalProcessGroup sig pgid)
+      (\e -> unless (isDoesNotExistError e) $ ioError e)
+
+hWithLines :: Handle -> (Text -> IO ()) -> IO ()
+hWithLines h f = do
+    hSetBuffering h LineBuffering
+    untilM_ (hIsEOF h) (T.hGetLine h >>= f) `finally` hClose h
-- 
cgit v1.2.3