hask-irc/Network/IRC/Handlers/SongSearch.hs

52 lines
2.0 KiB
Haskell
Raw Normal View History

{-# LANGUAGE RecordWildCards, OverloadedStrings, ScopedTypeVariables, NoImplicitPrelude, FlexibleContexts #-}
module Network.IRC.Handlers.SongSearch (getMsgHandler) where
import qualified Data.Configurator as CF
2014-05-10 21:45:16 +05:30
import ClassyPrelude hiding (try)
import Control.Exception
import Control.Monad.Reader
import Data.Aeson
import Data.Aeson.Types (emptyArray)
2014-05-10 21:45:16 +05:30
import Data.Text (strip)
import Network.Curl.Aeson
import Network.HTTP.Base
import Network.IRC.Types
getMsgHandler :: MsgHandlerName -> Maybe MsgHandler
getMsgHandler "songsearch" = Just $ newMsgHandler { msgHandlerRun = songSearch }
getMsgHandler _ = Nothing
data Song = NoSong | Song { url :: Text, name :: Text, artist :: Text }
deriving (Show, Eq)
instance FromJSON Song where
parseJSON (Object o) = Song <$> o .: "Url" <*> o .: "SongName" <*> o .: "ArtistName"
parseJSON a | a == emptyArray = return NoSong
2014-05-10 21:45:16 +05:30
parseJSON _ = mempty
songSearch :: MonadMsgHandler m => Message -> m (Maybe Command)
songSearch ChannelMsg { .. } = if "!m " `isPrefixOf` msg
then do
BotConfig { .. } <- ask
liftIO $ do
2014-05-10 21:45:16 +05:30
let query = strip . drop 3 $ msg
mApiKey <- CF.lookup config "songsearch.tinysong_apikey"
2014-05-10 21:45:16 +05:30
map (Just . ChannelMsgReply) $ case mApiKey of
Nothing -> -- do log "tinysong api key not found in config"
return $ "Error while searching for " ++ query
Just apiKey -> do
2014-05-10 21:45:16 +05:30
let apiUrl = "http://tinysong.com/b/" ++ urlEncode (unpack query)
++ "?format=json&key=" ++ apiKey
result <- try $ curlAesonGet apiUrl >>= evaluate
return $ case result of
Left (_ :: CurlAesonException) -> "Error while searching for " ++ query
Right song -> case song of
Song { .. } -> "Listen to " ++ artist ++ " - " ++ name ++ " at " ++ url
NoSong -> "No song found for: " ++ query
else return Nothing
songSearch _ = return Nothing