diff --git a/Database.hs b/Database.hs new file mode 100644 index 0000000..0815b41 --- /dev/null +++ b/Database.hs @@ -0,0 +1,27 @@ +{-# LANGUAGE OverloadedStrings #-} +module Database where + +import qualified Network.MPD as MP +import Types +import Search +import qualified Unsafe.Coerce as C +import qualified Data.Text as TIO +import Data.Text.Encoding +import System.Process +import qualified Data.ByteString.Char8 as B +import Data.String.Utils + +toPath :: String -> MP.Path +{- + - unsafeCoerce is needed because the "Path" + - type is a newtype that represents a ByteString type. + - In the MPD library the Types module is a hidden + - module, so we can't use the constructor for it. + - Therefore we just coerce to that type, which + - is the exact same type anyway + -} +toPath = C.unsafeCoerce . B.pack . strip . head . split "\n" + +addSingle url = do + fullUrl <- readProcess "youtube-dl" ["-g", "-f", "bestaudio", (TIO.unpack url)] "" + MP.withMPD $ MP.add $ toPath fullUrl diff --git a/Main.hs b/Main.hs index 511c269..d6698f0 100644 --- a/Main.hs +++ b/Main.hs @@ -2,9 +2,12 @@ module Main where import Search import Types +import Database +import Data.List +import System.Environment (getArgs) import qualified Data.Text.IO as TIO (putStrLn) main = do - term <- getContents - results <- search term - TIO.putStrLn $ url $ head $ results + term <- getArgs + result <- firstResult $ intercalate " " term + addSingle result diff --git a/Search.hs b/Search.hs index c92d7f2..63c523a 100644 --- a/Search.hs +++ b/Search.hs @@ -1,6 +1,7 @@ module Search where -import Control.Monad (unless) +import Data.Function +import Control.Monad (liftM2, unless, join, (>=>), (<=<)) import System.Info (os) import System.Process (system, rawSystem) import System.Exit (ExitCode(..)) @@ -43,20 +44,16 @@ searchRequest keyword accessTok = "&type=video&access_token=" ++ accessTok -getNewTokens :: OAuth2Client -> IO OAuth2Tokens +getNewTokens :: OAuth2Client -> IO () getNewTokens client = do tokens <- read <$> readFile file newTokens <- refreshTokens client tokens writeFile file (show newTokens) - return newTokens -findTracks :: OAuth2Client -> String -> String -> IO [SearchResult] findTracks client accessTok term = do response <- (try $ simpleHttp $ searchRequest term accessTok) :: IO (Either HttpException BL.ByteString) case response of - (Left _) -> do - tokens <- getNewTokens client - findTracks client (accessToken tokens) term + (Left _) -> getNewTokens client >> search (urlDecode term) (Right resp) -> return $ getItems resp search :: String -> IO [SearchResult] @@ -72,4 +69,16 @@ search term = do putStrLn $ "Received access token: " ++ show (accessToken tokens) writeFile file (show tokens) accessTok <- fmap (accessToken . read) (readFile file) - findTracks client accessTok (urlEncode term) + findTracks client accessTok $ urlEncode term + +firstResult = url . head $. search +allResults = map url $. search +withDescriptions = map ((T.drop 3) . liftM2 (T.append `on` (T.append " : ")) url description) $. search +withTitles = map ((T.drop 3) . liftM2 (T.append `on` (T.append " : ")) url title) $. search +withDescriptionsStr = T.intercalate "\n" $. withDescriptions +withTitlesStr = T.intercalate "\n" $. withTitles + +infixr 8 $. +a $. b = \x -> do + y <- b x + return $ a y