module Debian.URI ( module Network.URI , URIString , uriToString' , fileFromURI , fileFromURIStrict , dirFromURI ) where import Control.Exception (ErrorCall(ErrorCall), try) --import Control.Monad.Trans (MonadIO) import qualified Data.ByteString.Lazy.Char8 as L import qualified Data.ByteString as B import Data.Maybe (catMaybes) import Network.URI import System.Directory (getDirectoryContents) import System.Exit import System.Unix.Process (lazyCommand, collectOutput) import Text.Regex (mkRegex, matchRegex) uriToString' uri = uriToString id uri "" instance Ord URI where compare a b = compare (uriToString' a) (uriToString' b) -- |If the URI type could be read and showed this wouldn't be necessary. type URIString = String fileFromURI :: URI -> IO (Either ErrorCall L.ByteString) fileFromURI uri = case (uriScheme uri, uriAuthority uri) of ("file:", Nothing) -> try (L.readFile (uriPath uri)) ("ssh:", Just auth) -> cmdOutput ("ssh " ++ uriUserInfo auth ++ uriRegName auth ++ uriPort auth ++ " cat " ++ show (uriPath uri)) _ -> cmdOutput ("curl -s -g '" ++ uriToString' uri ++ "'") fileFromURIStrict :: URI -> IO (Either ErrorCall B.ByteString) fileFromURIStrict uri = case (uriScheme uri, uriAuthority uri) of ("file:", Nothing) -> try (B.readFile (uriPath uri)) ("ssh:", Just auth) -> cmdOutputStrict ("ssh " ++ uriUserInfo auth ++ uriRegName auth ++ uriPort auth ++ " cat " ++ show (uriPath uri)) _ -> cmdOutputStrict ("curl -s -g '" ++ uriToString' uri ++ "'") -- | Parse the text returned when a directory is listed by a web -- server. This is currently only known to work with Apache. -- NOTE: there is a second copy of this function in -- Extra:Extra.Net. Please update both locations if you make changes. webServerDirectoryContents :: L.ByteString -> [String] webServerDirectoryContents text = catMaybes . map (second . matchRegex re) . lines . L.unpack $ text where re = mkRegex "( IO (Either ErrorCall [String]) dirFromURI uri = case (uriScheme uri, uriAuthority uri) of ("file:", Nothing) -> try (getDirectoryContents (uriPath uri)) ("ssh:", Just auth) -> cmdOutput ("ssh " ++ uriUserInfo auth ++ uriRegName auth ++ uriPort auth ++ " ls -1 " ++ uriPath uri) >>= return . either Left (Right . lines . L.unpack) _ -> cmdOutput ("curl -s -g '" ++ uriToString' uri ++ "/'") >>= return . either Left (Right . webServerDirectoryContents) cmdOutput :: String -> IO (Either ErrorCall L.ByteString) cmdOutput cmd = do (out, _err, code) <- lazyCommand cmd L.empty >>= return . collectOutput case code of (ExitSuccess : _) -> return (Right out) (ExitFailure _ : _) -> return . Left . ErrorCall $ "Failure: " ++ show cmd [] -> return . Left . ErrorCall $ "Failure: no exit code" cmdOutputStrict :: String -> IO (Either ErrorCall B.ByteString) cmdOutputStrict cmd = do (out, _err, code) <- lazyCommand cmd L.empty >>= return . f . collectOutput case code of (ExitSuccess : _) -> return (Right out) (ExitFailure _ : _) -> return . Left . ErrorCall $ "Failure: " ++ show cmd [] -> return . Left . ErrorCall $ "Failure: no exit code" where f :: (L.ByteString, L.ByteString, [ExitCode]) -> (B.ByteString, B.ByteString, [ExitCode]) f (o, e, c) = (toStrict o, toStrict e, c) toLazy :: B.ByteString -> L.ByteString toLazy b = L.fromChunks [b] toStrict :: L.ByteString -> B.ByteString toStrict b = B.concat (L.toChunks b)