module Darcs.Util.URL (
isValidLocalPath, isHttpUrl, isSshUrl, isRelative, isAbsolute,
isSshNopath, SshFilePath, sshRepo, sshUhost, sshFile, sshFilePathOf, splitSshUrl
) where
import Darcs.Prelude
import Darcs.Util.Global ( darcsdir )
import Data.List ( isPrefixOf, isInfixOf )
import Data.Char ( isSpace )
import qualified System.FilePath as FP
( hasDrive
, isAbsolute
, isRelative
, isValid
, pathSeparators
)
import System.FilePath ( (</>) )
isRelative :: String -> Bool
isRelative "" = error "Empty filename in isRelative"
isRelative f = FP.isRelative f
isAbsolute :: String -> Bool
isAbsolute "" = error "isAbsolute called with empty filename"
isAbsolute f = FP.isAbsolute f
isValidLocalPath :: String -> Bool
isValidLocalPath s =
FP.isValid s &&
(FP.hasDrive s || not (':' `elem` takeWhile (`notElem` FP.pathSeparators) s))
isHttpUrl :: String -> Bool
isHttpUrl u =
let u' = dropWhile isSpace u in
("http://" `isPrefixOf` u') || ("https://" `isPrefixOf` u')
isSshUrl :: String -> Bool
isSshUrl s = isu' (dropWhile isSpace s)
where
isu' s'
| "ssh://" `isPrefixOf` s' = True
| "://" `isInfixOf` s' = False
| isValidLocalPath s' = False
| otherwise = ":" `isInfixOf` s'
isSshNopath :: String -> Bool
isSshNopath s = case reverse s of
':':x@(_:_:_) -> ':' `notElem` x
_ -> False
splitSshUrl :: String -> SshFilePath
splitSshUrl s | "ssh://" `isPrefixOf` s =
let s' = drop (length "ssh://") $ dropWhile isSpace s
(dir, file) = cleanrepodir '/' s'
in
SshFP { sshUhost = takeWhile (/= '/') s'
, sshRepo = dir
, sshFile = file }
splitSshUrl s =
let (dir, file) = cleanrepodir ':' s in
SshFP { sshUhost = dropWhile isSpace $ takeWhile (/= ':') s
, sshRepo = dir
, sshFile = file }
cleanrepourl :: String -> (String, String)
cleanrepourl zzz | dd `isPrefixOf` zzz = ([], drop (length dd) zzz)
where dd = darcsdir++"/"
cleanrepourl (z:zs) =
let (repo',file) = cleanrepourl zs in
(z : repo', file)
cleanrepourl "" = ([],[])
cleanrepodir :: Char -> String -> (String, String)
cleanrepodir sep = cleanrepourl . drop 1 . dropWhile (/= sep)
data SshFilePath = SshFP { sshUhost :: String
, sshRepo :: String
, sshFile :: String }
sshFilePathOf :: SshFilePath -> String
sshFilePathOf (SshFP uhost dir file) = uhost ++ ":" ++ (dir </> darcsdir </> file)