module Neovim.Test (
    testWithEmbeddedNeovim,
    Seconds(..),
    ) where
import           Neovim
import qualified Neovim.Context.Internal      as Internal
import           Neovim.RPC.Common            (newRPCConfig, RPCConfig)
import           Neovim.RPC.EventHandler      (runEventHandler)
import           Neovim.RPC.SocketReader      (runSocketReader)
import           Control.Concurrent
import           Control.Concurrent.STM       (atomically, putTMVar)
import           Control.Exception.Lifted
import           Control.Monad.Reader         (runReaderT)
import           Control.Monad.State          (runStateT)
import           Control.Monad.Trans.Resource (runResourceT)
import           GHC.IO.Exception             (ioe_filename)
import           System.Directory
import           System.Exit                  (ExitCode (..))
import           System.IO                    (Handle)
import           System.Process
import           Text.PrettyPrint.ANSI.Leijen (red, text, putDoc, (<$$>))
newtype Seconds = Seconds Word
testWithEmbeddedNeovim
    :: Maybe FilePath 
    -> Seconds        
    -> r              
    -> st             
    -> Neovim r st a  
    -> IO ()
testWithEmbeddedNeovim file timeout r st (Internal.Neovim a) =
    runTest `catch` catchIfNvimIsNotOnPath
  where
    runTest = do
        (_, _, ph, cfg) <- startEmbeddedNvim file timeout
        let testCfg = Internal.retypeConfig r st cfg
        void $ runReaderT (runStateT (runResourceT a) st) testCfg
        
        
        
        let Internal.Neovim q = vim_command "qa!"
        void . forkIO . void $ runReaderT (runStateT (runResourceT q) st ) testCfg
        waitForProcess ph >>= \case
            ExitFailure i ->
                fail $ "Neovim returned with an exit status of: " ++ show i
            ExitSuccess ->
                return ()
catchIfNvimIsNotOnPath :: IOException -> IO ()
catchIfNvimIsNotOnPath e = case ioe_filename e of
    Just "nvim" ->
        putDoc . red $ text "The neovim executable 'nvim' is not on the PATH."
                    <$$> text "You may not be testing fully!"
    _           ->
        throw e
startEmbeddedNvim
    :: Maybe FilePath
    -> Seconds
    -> IO (Handle, Handle, ProcessHandle, Internal.Config RPCConfig st)
startEmbeddedNvim file (Seconds timeout) = do
    args <- case file of
                Nothing ->
                    return []
                Just f -> do
                    
                    
                    unlessM (doesFileExist f) . fail $ "File not found: " ++ f
                    return [f]
    (Just hin, Just hout, _, ph) <-
        createProcess (proc "nvim" (["-n","-u","NONE","--embed"] ++ args))
            { std_in = CreatePipe
            , std_out = CreatePipe
            }
    cfg <- Internal.newConfig (pure Nothing) newRPCConfig
    void . forkIO $ runSocketReader
                    hout
                    (cfg { Internal.pluginSettings = Nothing })
    void . forkIO $ runEventHandler
                    hin
                    (cfg { Internal.pluginSettings = Nothing })
    atomically $ putTMVar
                    (Internal.globalFunctionMap cfg)
                    (Internal.mkFunctionMap [])
    void . forkIO $ do
        threadDelay $ (fromIntegral timeout) * 1000 * 1000
        getProcessExitCode ph >>= maybe (terminateProcess ph) (\_ -> return ())
    return (hin, hout, ph, cfg)