--------------------------------------------------------------------------------
{-# LANGUAGE TemplateHaskell #-}
module Patat.Images.Kitty
    ( backend
    ) where


--------------------------------------------------------------------------------
import           Control.Exception           (throwIO)
import           Control.Monad               (unless, void, when)
import qualified Data.Aeson                  as A
import qualified Data.List                   as L
import           Patat.Cleanup               (Cleanup)
import qualified Patat.Images.Internal       as Internal
import Data.Functor (($>))
import           System.Environment          (lookupEnv)
import           System.Process              (readProcess)


--------------------------------------------------------------------------------
backend :: Internal.Backend
backend :: Backend
backend = (Config Config -> IO Handle) -> Backend
forall a. FromJSON a => (Config a -> IO Handle) -> Backend
Internal.Backend Config Config -> IO Handle
new


--------------------------------------------------------------------------------
data Config = Config deriving (Config -> Config -> Bool
(Config -> Config -> Bool)
-> (Config -> Config -> Bool) -> Eq Config
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Config -> Config -> Bool
$c/= :: Config -> Config -> Bool
== :: Config -> Config -> Bool
$c== :: Config -> Config -> Bool
Eq)
instance A.FromJSON Config where parseJSON :: Value -> Parser Config
parseJSON Value
_ = Config -> Parser Config
forall (m :: * -> *) a. Monad m => a -> m a
return Config
Config


--------------------------------------------------------------------------------
new :: Internal.Config Config -> IO Internal.Handle
new :: Config Config -> IO Handle
new Config Config
config = do
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Config Config
config Config Config -> Config Config -> Bool
forall a. Eq a => a -> a -> Bool
== Config Config
forall a. Config a
Internal.Auto) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
        Maybe String
term <- String -> IO (Maybe String)
lookupEnv String
"TERM"
        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Bool -> (String -> Bool) -> Maybe String -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (String
"kitty" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`L.isInfixOf`) Maybe String
term) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ BackendNotSupported -> IO ()
forall e a. Exception e => e -> IO a
throwIO (BackendNotSupported -> IO ()) -> BackendNotSupported -> IO ()
forall a b. (a -> b) -> a -> b
$
            String -> BackendNotSupported
Internal.BackendNotSupported String
"TERM does not indicate kitty"

    Handle -> IO Handle
forall (m :: * -> *) a. Monad m => a -> m a
return Handle :: (String -> IO (IO ())) -> Handle
Internal.Handle {hDrawImage :: String -> IO (IO ())
Internal.hDrawImage = String -> IO (IO ())
drawImage}


--------------------------------------------------------------------------------
drawImage :: FilePath -> IO Cleanup
drawImage :: String -> IO (IO ())
drawImage String
path = [String] -> IO ()
icat [String
"--align=center", String
path] IO () -> IO () -> IO (IO ())
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> [String] -> IO ()
icat [String
"--clear"]
  where
    icat :: [String] -> IO ()
icat [String]
args = IO String -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO String -> IO ()) -> IO String -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> [String] -> String -> IO String
readProcess
        String
"kitty" (String
"+kitten" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: String
"icat" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: String
"--transfer-mode=stream" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
args) String
""