module System.Touched.Procedure ( Procedure(..)
, AsyncIO
, async
, AsyncCmd
, cmd
) where
import Control.Concurrent ( forkIO
, killThread
, ThreadId
)
import System.Process
import System.IO (Handle)
data Procedure a b = Procedure { fork :: a -> IO b
, kill :: b -> IO ()
, exec :: a
}
instance Show (Procedure a b) where
show = const "{Procedure Type}"
type AsyncIO = Procedure (IO ()) ThreadId
async :: IO () -> AsyncIO
async io = Procedure { fork = forkIO
, kill = killThread
, exec = io
}
type CmdHandles = (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
procId :: CmdHandles -> ProcessHandle
procId (_,_,_,id) = id
type AsyncCmd = Procedure CreateProcess CmdHandles
cmd :: String -> AsyncCmd
cmd cmdString = Procedure { fork = createProcess
, kill = terminateProcess . procId
, exec = shell cmdString
}