module Turtle.Bytes (
    
      stdin
    , input
    , inhandle
    , stdout
    , output
    , outhandle
    , append
    , stderr
    , strict
    
    , proc
    , shell
    , procs
    , shells
    , inproc
    , inshell
    , inprocWithErr
    , inshellWithErr
    , procStrict
    , shellStrict
    , procStrictWithErr
    , shellStrictWithErr
    , system
    , stream
    , streamWithErr
    , systemStrict
    , systemStrictWithErr
    ) where
import Control.Applicative
import Control.Concurrent.Async (Async, Concurrently(..))
import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Managed (MonadManaged(..))
import Data.ByteString (ByteString)
import Data.Text (Text)
import Filesystem.Path (FilePath)
import Prelude hiding (FilePath)
import System.Exit (ExitCode(..))
import System.IO (Handle)
import Turtle.Internal (ignoreSIGPIPE)
import Turtle.Prelude (ProcFailed(..), ShellFailed(..))
import Turtle.Shell (Shell(..), FoldShell(..), fold, sh)
import qualified Control.Concurrent.Async      as Async
import qualified Control.Concurrent.STM        as STM
import qualified Control.Concurrent.MVar       as MVar
import qualified Control.Concurrent.STM.TQueue as TQueue
import qualified Control.Exception             as Exception
import qualified Control.Foldl
import qualified Control.Monad
import qualified Control.Monad.Managed         as Managed
import qualified Data.ByteString
import qualified Data.Text
import qualified Foreign
import qualified System.IO
import qualified System.Process                as Process
import qualified Turtle.Prelude
stdin :: Shell ByteString
stdin = inhandle System.IO.stdin
input :: FilePath -> Shell ByteString
input file = do
    handle <- using (Turtle.Prelude.readonly file)
    inhandle handle
inhandle :: Handle -> Shell ByteString
inhandle handle = Shell (\(FoldShell step begin done) -> do
    let loop x = do
            eof <- System.IO.hIsEOF handle
            if eof
                then done x
                else do
                    bytes <- Data.ByteString.hGetSome handle defaultChunkSize
                    x'    <- step x bytes
                    loop $! x'
    loop $! begin )
  where
    
    defaultChunkSize :: Int
    defaultChunkSize = 32 * 1024  2 * Foreign.sizeOf (undefined :: Int)
stdout :: MonadIO io => Shell ByteString -> io ()
stdout s = sh (do
    bytes <- s
    liftIO (Data.ByteString.hPut System.IO.stdout bytes) )
output :: MonadIO io => FilePath -> Shell ByteString -> io ()
output file s = sh (do
    handle <- using (Turtle.Prelude.writeonly file)
    bytes  <- s
    liftIO (Data.ByteString.hPut handle bytes) )
outhandle :: MonadIO io => Handle -> Shell ByteString -> io ()
outhandle handle s = sh (do
    bytes <- s
    liftIO (Data.ByteString.hPut handle bytes) )
append :: MonadIO io => FilePath -> Shell ByteString -> io ()
append file s = sh (do
    handle <- using (Turtle.Prelude.appendonly file)
    bytes  <- s
    liftIO (Data.ByteString.hPut handle bytes) )
stderr :: MonadIO io => Shell ByteString -> io ()
stderr s = sh (do
    bytes <- s
    liftIO (Data.ByteString.hPut System.IO.stderr bytes) )
strict :: MonadIO io => Shell ByteString -> io ByteString
strict s = do
    listOfByteStrings <- fold s Control.Foldl.list
    return (Data.ByteString.concat listOfByteStrings)
proc
    :: MonadIO io
    => Text
    
    -> [Text]
    
    -> Shell ByteString
    
    -> io ExitCode
    
proc cmd args =
    system
        ( (Process.proc (Data.Text.unpack cmd) (map Data.Text.unpack args))
            { Process.std_in  = Process.CreatePipe
            , Process.std_out = Process.Inherit
            , Process.std_err = Process.Inherit
            } )
shell
    :: MonadIO io
    => Text
    
    -> Shell ByteString
    
    -> io ExitCode
    
shell cmdline =
    system
        ( (Process.shell (Data.Text.unpack cmdline))
            { Process.std_in  = Process.CreatePipe
            , Process.std_out = Process.Inherit
            , Process.std_err = Process.Inherit
            } )
procs
    :: MonadIO io
    => Text
    
    -> [Text]
    
    -> Shell ByteString
    
    -> io ()
procs cmd args s = do
    exitCode <- proc cmd args s
    case exitCode of
        ExitSuccess -> return ()
        _           -> liftIO (Exception.throwIO (ProcFailed cmd args exitCode))
shells
    :: MonadIO io
    => Text
    
    -> Shell ByteString
    
    -> io ()
    
shells cmdline s = do
    exitCode <- shell cmdline s
    case exitCode of
        ExitSuccess -> return ()
        _           -> liftIO (Exception.throwIO (ShellFailed cmdline exitCode))
procStrict
    :: MonadIO io
    => Text
    
    -> [Text]
    
    -> Shell ByteString
    
    -> io (ExitCode, ByteString)
    
procStrict cmd args =
    systemStrict (Process.proc (Data.Text.unpack cmd) (map Data.Text.unpack args))
shellStrict
    :: MonadIO io
    => Text
    
    -> Shell ByteString
    
    -> io (ExitCode, ByteString)
    
shellStrict cmdline = systemStrict (Process.shell (Data.Text.unpack cmdline))
procStrictWithErr
    :: MonadIO io
    => Text
    
    -> [Text]
    
    -> Shell ByteString
    
    -> io (ExitCode, ByteString, ByteString)
    
procStrictWithErr cmd args =
    systemStrictWithErr (Process.proc (Data.Text.unpack cmd) (map Data.Text.unpack args))
shellStrictWithErr
    :: MonadIO io
    => Text
    
    -> Shell ByteString
    
    -> io (ExitCode, ByteString, ByteString)
    
shellStrictWithErr cmdline =
    systemStrictWithErr (Process.shell (Data.Text.unpack cmdline))
halt :: Async a -> IO ()
halt a = do
    m <- Async.poll a
    case m of
        Nothing        -> Async.cancel a
        Just (Left  e) -> Exception.throwIO e
        Just (Right _) -> return ()
system
    :: MonadIO io
    => Process.CreateProcess
    
    -> Shell ByteString
    
    -> io ExitCode
    
system p s = liftIO (do
    let open = do
            (m, Nothing, Nothing, ph) <- Process.createProcess p
            case m of
                Just hIn -> System.IO.hSetBuffering hIn (System.IO.BlockBuffering Nothing)
                _        -> return ()
            return (m, ph)
    
    mvar <- MVar.newMVar False
    let close handle = do
            MVar.modifyMVar_ mvar (\finalized -> do
                Control.Monad.unless finalized
                    (ignoreSIGPIPE (System.IO.hClose handle))
                return True )
    let close' (Just hIn, ph) = do
            close hIn
            Process.terminateProcess ph
        close' (Nothing , ph) = do
            Process.terminateProcess ph
    let handle (Just hIn, ph) = do
            let feedIn :: (forall a. IO a -> IO a) -> IO ()
                feedIn restore =
                    restore (ignoreSIGPIPE (outhandle hIn s))
                    `Exception.finally` close hIn
            Exception.mask (\restore ->
                Async.withAsync (feedIn restore) (\a ->
                    restore (Process.waitForProcess ph) <* halt a ) )
        handle (Nothing , ph) = do
            Process.waitForProcess ph
    Exception.bracket open close' handle )
systemStrict
    :: MonadIO io
    => Process.CreateProcess
    
    -> Shell ByteString
    
    -> io (ExitCode, ByteString)
    
systemStrict p s = liftIO (do
    let p' = p
            { Process.std_in  = Process.CreatePipe
            , Process.std_out = Process.CreatePipe
            , Process.std_err = Process.Inherit
            }
    let open = do
            (Just hIn, Just hOut, Nothing, ph) <- liftIO (Process.createProcess p')
            System.IO.hSetBuffering hIn (System.IO.BlockBuffering Nothing)
            return (hIn, hOut, ph)
    
    mvar <- MVar.newMVar False
    let close handle = do
            MVar.modifyMVar_ mvar (\finalized -> do
                Control.Monad.unless finalized
                    (ignoreSIGPIPE (System.IO.hClose handle))
                return True )
    Exception.bracket open (\(hIn, _, ph) -> close hIn >> Process.terminateProcess ph) (\(hIn, hOut, ph) -> do
        let feedIn :: (forall a. IO a -> IO a) -> IO ()
            feedIn restore =
                restore (ignoreSIGPIPE (outhandle hIn s))
                `Exception.finally` close hIn
        Async.concurrently
            (Exception.mask (\restore ->
                Async.withAsync (feedIn restore) (\a ->
                    restore (Process.waitForProcess ph) <* halt a ) ))
            (Data.ByteString.hGetContents hOut) ) )
systemStrictWithErr
    :: MonadIO io
    => Process.CreateProcess
    
    -> Shell ByteString
    
    -> io (ExitCode, ByteString, ByteString)
    
systemStrictWithErr p s = liftIO (do
    let p' = p
            { Process.std_in  = Process.CreatePipe
            , Process.std_out = Process.CreatePipe
            , Process.std_err = Process.CreatePipe
            }
    let open = do
            (Just hIn, Just hOut, Just hErr, ph) <- liftIO (Process.createProcess p')
            System.IO.hSetBuffering hIn (System.IO.BlockBuffering Nothing)
            return (hIn, hOut, hErr, ph)
    
    mvar <- MVar.newMVar False
    let close handle = do
            MVar.modifyMVar_ mvar (\finalized -> do
                Control.Monad.unless finalized
                    (ignoreSIGPIPE (System.IO.hClose handle))
                return True )
    Exception.bracket open (\(hIn, _, _, ph) -> close hIn >> Process.terminateProcess ph) (\(hIn, hOut, hErr, ph) -> do
        let feedIn :: (forall a. IO a -> IO a) -> IO ()
            feedIn restore =
                restore (ignoreSIGPIPE (outhandle hIn s))
                `Exception.finally` close hIn
        runConcurrently $ (,,)
            <$> Concurrently (Exception.mask (\restore ->
                    Async.withAsync (feedIn restore) (\a ->
                        restore (Process.waitForProcess ph) <* halt a ) ))
            <*> Concurrently (Data.ByteString.hGetContents hOut)
            <*> Concurrently (Data.ByteString.hGetContents hErr) ) )
inproc
    :: Text
    
    -> [Text]
    
    -> Shell ByteString
    
    -> Shell ByteString
    
inproc cmd args =
    stream (Process.proc (Data.Text.unpack cmd) (map Data.Text.unpack args))
inshell
    :: Text
    
    -> Shell ByteString
    
    -> Shell ByteString
    
inshell cmd = stream (Process.shell (Data.Text.unpack cmd))
waitForProcessThrows :: Process.ProcessHandle -> IO ()
waitForProcessThrows ph = do
    exitCode <- Process.waitForProcess ph
    case exitCode of
        ExitSuccess   -> return ()
        ExitFailure _ -> Exception.throwIO exitCode
stream
    :: Process.CreateProcess
    
    -> Shell ByteString
    
    -> Shell ByteString
    
stream p s = do
    let p' = p
            { Process.std_in  = Process.CreatePipe
            , Process.std_out = Process.CreatePipe
            , Process.std_err = Process.Inherit
            }
    let open = do
            (Just hIn, Just hOut, Nothing, ph) <- liftIO (Process.createProcess p')
            System.IO.hSetBuffering hIn (System.IO.BlockBuffering Nothing)
            return (hIn, hOut, ph)
    
    mvar <- liftIO (MVar.newMVar False)
    let close handle = do
            MVar.modifyMVar_ mvar (\finalized -> do
                Control.Monad.unless finalized (System.IO.hClose handle)
                return True )
    (hIn, hOut, ph) <- using (Managed.managed (Exception.bracket open (\(hIn, _, ph) -> close hIn >> Process.terminateProcess ph)))
    let feedIn :: (forall a. IO a -> IO a) -> IO ()
        feedIn restore =
            restore (sh (do
                bytes <- s
                liftIO (Data.ByteString.hPut hIn bytes) ) )
            `Exception.finally` close hIn
    a <- using
        (Managed.managed (\k ->
            Exception.mask (\restore ->
                Async.withAsync (feedIn restore) k ) ))
    inhandle hOut <|> (liftIO (waitForProcessThrows ph *> halt a) *> empty)
streamWithErr
    :: Process.CreateProcess
    
    -> Shell ByteString
    
    -> Shell (Either ByteString ByteString)
    
streamWithErr p s = do
    let p' = p
            { Process.std_in  = Process.CreatePipe
            , Process.std_out = Process.CreatePipe
            , Process.std_err = Process.CreatePipe
            }
    let open = do
            (Just hIn, Just hOut, Just hErr, ph) <- liftIO (Process.createProcess p')
            System.IO.hSetBuffering hIn (System.IO.BlockBuffering Nothing)
            return (hIn, hOut, hErr, ph)
    
    mvar <- liftIO (MVar.newMVar False)
    let close handle = do
            MVar.modifyMVar_ mvar (\finalized -> do
                Control.Monad.unless finalized (System.IO.hClose handle)
                return True )
    (hIn, hOut, hErr, ph) <- using (Managed.managed (Exception.bracket open (\(hIn, _, _, ph) -> close hIn >> Process.terminateProcess ph)))
    let feedIn :: (forall a. IO a -> IO a) -> IO ()
        feedIn restore =
            restore (sh (do
                bytes <- s
                liftIO (Data.ByteString.hPut hIn bytes) ) )
            `Exception.finally` close hIn
    queue <- liftIO TQueue.newTQueueIO
    let forwardOut :: (forall a. IO a -> IO a) -> IO ()
        forwardOut restore =
            restore (sh (do
                bytes <- inhandle hOut
                liftIO (STM.atomically (TQueue.writeTQueue queue (Just (Right bytes)))) ))
            `Exception.finally` STM.atomically (TQueue.writeTQueue queue Nothing)
    let forwardErr :: (forall a. IO a -> IO a) -> IO ()
        forwardErr restore =
            restore (sh (do
                bytes <- inhandle hErr
                liftIO (STM.atomically (TQueue.writeTQueue queue (Just (Left  bytes)))) ))
            `Exception.finally` STM.atomically (TQueue.writeTQueue queue Nothing)
    let drain = Shell (\(FoldShell step begin done) -> do
            let loop x numNothing
                    | numNothing < 2 = do
                        m <- STM.atomically (TQueue.readTQueue queue)
                        case m of
                            Nothing -> loop x $! numNothing + 1
                            Just e  -> do
                                x' <- step x e
                                loop x' numNothing
                    | otherwise      = return x
            x1 <- loop begin (0 :: Int)
            done x1 )
    a <- using
        (Managed.managed (\k ->
            Exception.mask (\restore ->
                Async.withAsync (feedIn restore) k ) ))
    b <- using
        (Managed.managed (\k ->
            Exception.mask (\restore ->
                Async.withAsync (forwardOut restore) k ) ))
    c <- using
        (Managed.managed (\k ->
            Exception.mask (\restore ->
                Async.withAsync (forwardErr restore) k ) ))
    let l `also` r = do
            _ <- l <|> (r *> STM.retry)
            _ <- r
            return ()
    let waitAll = STM.atomically (Async.waitSTM a `also` (Async.waitSTM b `also` Async.waitSTM c))
    drain <|> (liftIO (waitForProcessThrows ph *> waitAll) *> empty)
inprocWithErr
    :: Text
    
    -> [Text]
    
    -> Shell ByteString
    
    -> Shell (Either ByteString ByteString)
    
inprocWithErr cmd args =
    streamWithErr (Process.proc (Data.Text.unpack cmd) (map Data.Text.unpack args))
inshellWithErr
    :: Text
    
    -> Shell ByteString
    
    -> Shell (Either ByteString ByteString)
    
inshellWithErr cmd = streamWithErr (Process.shell (Data.Text.unpack cmd))