{-# LANGUAGE CPP #-}
module Hakyll.Core.UnixFilter
    ( unixFilter
    , unixFilterLBS
    ) where
import           Control.Concurrent      (forkIO)
import           Control.Concurrent.MVar (newEmptyMVar, putMVar, takeMVar)
import           Control.DeepSeq         (deepseq)
import           Control.Monad           (forM_)
import           Data.ByteString.Lazy    (ByteString)
import qualified Data.ByteString.Lazy    as LB
import           Data.IORef              (newIORef, readIORef, writeIORef)
import           System.Exit             (ExitCode (..))
import           System.IO               (Handle, hClose, hFlush, hGetContents,
                                          hPutStr, hSetEncoding, localeEncoding)
import           System.Process
import           Hakyll.Core.Compiler
unixFilter :: String           
           -> [String]         
           -> String           
           -> Compiler String  
unixFilter = unixFilterWith writer reader
  where
    writer handle input = do
        hSetEncoding handle localeEncoding
        hPutStr handle input
    reader handle = do
        hSetEncoding handle localeEncoding
        out <- hGetContents handle
        deepseq out (return out)
unixFilterLBS :: String               
              -> [String]             
              -> ByteString           
              -> Compiler ByteString  
unixFilterLBS = unixFilterWith LB.hPutStr $ \handle -> do
    out <- LB.hGetContents handle
    LB.length out `seq` return out
unixFilterWith :: Monoid o
               => (Handle -> i -> IO ())  
               -> (Handle -> IO o)        
               -> String                  
               -> [String]                
               -> i                       
               -> Compiler o              
unixFilterWith writer reader programName args input = do
    debugCompiler ("Executing external program " ++ programName)
    (output, err, exitCode) <- unsafeCompiler $
        unixFilterIO writer reader programName args input
    forM_ (lines err) debugCompiler
    case exitCode of
        ExitSuccess   -> return output
        ExitFailure e -> fail $
            "Hakyll.Core.UnixFilter.unixFilterWith: " ++
            unwords (programName : args) ++ " gave exit code " ++ show e ++
            ". (Error: " ++ err ++ ")"
unixFilterIO :: Monoid o
             => (Handle -> i -> IO ())
             -> (Handle -> IO o)
             -> String
             -> [String]
             -> i
             -> IO (o, String, ExitCode)
unixFilterIO writer reader programName args input = do
    
    
    
    
    
    
    
    
#ifdef mingw32_HOST_OS
    let pr = shell $ unwords (programName : args)
#else
    let pr = proc programName args
#endif
    (Just inh, Just outh, Just errh, pid) <-
        createProcess pr
                { std_in  = CreatePipe
                , std_out = CreatePipe
                , std_err = CreatePipe
                }
    
    lock   <- newEmptyMVar
    outRef <- newIORef mempty
    errRef <- newIORef ""
    
    _ <- forkIO $ writer inh input >> hFlush inh >> hClose inh
    
    _ <- forkIO $ do
        out <- reader outh
        hClose outh
        writeIORef outRef out
        putMVar lock ()
    
    _ <- forkIO $ do
        hSetEncoding errh localeEncoding
        err <- hGetContents errh
        _   <- deepseq err (return err)
        hClose errh
        writeIORef errRef err
        putMVar lock ()
    
    takeMVar lock
    takeMVar lock
    exitCode <- waitForProcess pid
    out      <- readIORef outRef
    err      <- readIORef errRef
    return (out, err, exitCode)