module Utils where import Data.Char(isSpace) import Control.Monad.Trans.Class(lift, MonadTrans) import Control.Monad(mzero) import Network.Download (openURI) import System.Environment(getEnv) import System.Process import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as BL import Control.Monad.Trans.Maybe import Codec.Compression.GZip(decompress) import Text.Printf(printf) import System.IO (hPutStrLn) -- | Strip whitespace from beginning and end of string. strip :: String -> String strip = lstripAndReverse . lstripAndReverse where lstripAndReverse = reverse . lstrip where lstrip = dropWhile isSpace lift2 :: (Monad (t1 m), Monad m, MonadTrans t, MonadTrans t1) => m a -> t (t1 m) a lift2 = lift . lift invokePager :: String -> IO () invokePager text = do pager <- getEnv "PAGER" (Just stdin,_,_,_) <- createProcess CreateProcess { cmdspec = ShellCommand pager, cwd = Nothing, env = Nothing, std_in = CreatePipe, std_out = Inherit, std_err = Inherit, close_fds = False, create_group = False } hPutStrLn stdin text type Hash = String fetchTorrentFile :: Hash -> MaybeT IO B.ByteString fetchTorrentFile hash = lift (openURI $ printf "http://torrage.com/torrent/%s.torrent" hash) >>= \res' -> case res' of Left _ -> mzero Right bs -> let lazy_bs = BL.fromChunks [bs] in return . BL.toStrict $ decompress lazy_bs