Skip to content

Instantly share code, notes, and snippets.

@fishtreesugar
Last active April 22, 2016 03:10
Show Gist options
  • Save fishtreesugar/8d1293c484335e737abf to your computer and use it in GitHub Desktop.
Save fishtreesugar/8d1293c484335e737abf to your computer and use it in GitHub Desktop.
WIP
#!/usr/bin/env stack
{- stack
--resolver lts-5.11
--install-ghc
runghc
--package wreq
--package text
--package containers
--package lens
-}
{-# LANGUAGE OverloadedStrings #-}
import Network.Wreq
import Control.Lens
import Data.Text (Text, pack, unpack, append, stripPrefix, stripSuffix)
import Data.Text.Encoding as E
import qualified Data.Text.IO as TIO
import Text.Printf
import qualified Data.ByteString.Lazy as B
import qualified Network.Wreq.Session as S
douban_username, douban_password, spbid, ck :: Text
douban_username = ""
douban_password = ""
spbid = ""
ck = ""
main :: IO ()
main = S.withSession $ \s -> do
login douban_username douban_password s
heartResp <- S.getWith opts s hearts_url
let Just body = heartResp ^? responseBody
print $ E.decodeUtf8 $ B.toStrict $ body
return ()
where
hearts_url = "http://douban.fm/j/v2/redheart"
opts = defaults & param "type" .~ ["liked"]
& param "spbid" .~ [spbid]
& param "ck" .~ [ck]
type Artist = Text
type Title = Text
type FileName = Text
buildFileName :: Artist -> Title -> FileName
buildFileName artist title = pack $ printf "%s-%s.mp3" (unpack artist) (unpack title)
login :: Text -> Text -> S.Session -> IO ()
login username password session =
do raw_captcha_id <- get_captcha_id
let Just captcha_id = stripQuote raw_captcha_id
TIO.putStrLn $ append captcha_url_prefix captcha_id
captcha_solution <- TIO.getLine
_ <- S.post session loginUrl ["source" := ("radio" :: Text)
, "alias" := username
, "form_password" := password
, "captcha_id" := captcha_id
, "captcha_solution" := captcha_solution
, "remember" := ("on" :: Text)
, "task" := ("sync_channel_list" :: Text)]
return ()
where
loginUrl = "http://douban.fm//j/login"
captcha_url_prefix = "http://douban.fm/misc/captcha?size=m&id="
stripQuote str = stripPrefix "\"" str >>= stripSuffix "\""
get_captcha_id :: IO Text
get_captcha_id = do r <- get "http://douban.fm/j/new_captcha"
return $ E.decodeUtf8 $ B.toStrict $ r ^. responseBody
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment