wnpClient/app/Main.hs

81 lines
2.3 KiB
Haskell

module Main where
import Control.Exception
import Control.Monad
import qualified Data.ByteString.Char8 as B8
import GHC.IO.Encoding (setLocaleEncoding)
import Lib
import Network.HTTP.Client
import Network.HTTP.Simple
import Network.URI
import System.Directory
import System.Exit
import System.FilePath
import System.IO
import System.Signal
main :: IO ()
main = do
setLocaleEncoding utf8
createDirectoryIfMissing False =<< workingDir
join $ (writeFile <$> fileName) <*> pure ""
installHandler sigINT sigIntHandler
installHandler sigTERM sigIntHandler
forever $ do
end <- isEOF
if end
then sigIntHandler sigTERM
else do
line <- getLine
dispatch line
dispatch :: String -> IO ()
dispatch ('T' : 'I' : 'T' : 'L' : 'E' : ':' : title) = writeToFile title 0
dispatch ('A' : 'R' : 'T' : 'I' : 'S' : 'T' : ':' : artist) = writeToFile artist 1
dispatch ('A' : 'L' : 'B' : 'U' : 'M' : ':' : album) = writeToFile album 2
dispatch ('C' : 'O' : 'V' : 'E' : 'R' : ':' : cover) = handleCover cover
dispatch _ = return ()
writeToFile :: String -> Int -> IO ()
writeToFile text position = do
contents <- lines <$> (readFile =<< fileName)
let newContent = unlines $ take position contents ++ [text] ++ drop (position + 1) contents
bracketOnError
(openTempFile "." "temp")
( \(tempName, tempHandle) -> do
hClose tempHandle
removeFile tempName
)
( \(tempName, tempHandle) -> do
hPutStr tempHandle newContent
hClose tempHandle
renameFile tempName =<< fileName
)
handleCover :: String -> IO ()
handleCover url = do
contents <- lines <$> (readFile =<< fileName)
if length contents > 3 && (contents !! 3) /= url && url /= ""
then do
writeToFile url 3
request <- parseRequest url
let coverFileName = Prelude.last . pathSegments . getUri $ request
join $ B8.writeFile <$> coverName <*> (getResponseBody <$> httpBS request)
else writeToFile url 3
-- B8.writeFile coverName $ getResponseBody resp
fileName :: IO FilePath
fileName = (</> "wnpClient.txt") <$> workingDir
coverName :: IO FilePath
coverName = (</> "cover.jpg") <$> workingDir
workingDir :: IO FilePath
workingDir = (</> ".wnpClient") <$> getHomeDirectory
sigIntHandler :: System.Signal.Handler
sigIntHandler _ = do
join $ (writeFile <$> fileName) <*> pure ""
hPutStrLn stderr ("Handle exit")
exitSuccess