module Darcs.Util.URL (
isValidLocalPath, isHttpUrl, isSshUrl, isRelative, isAbsolute,
isSshNopath, SshFilePath, sshRepo, sshUhost, sshFile, sshFilePathOf, splitSshUrl,
sshCanonRepo
) 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 ( (</>) )
import System.FilePath.Posix ( joinPath, splitDirectories )
isRelative :: String -> Bool
isRelative :: String -> Bool
isRelative String
"" = String -> Bool
forall a. HasCallStack => String -> a
error String
"Empty filename in isRelative"
isRelative String
f = String -> Bool
FP.isRelative String
f
isAbsolute :: String -> Bool
isAbsolute :: String -> Bool
isAbsolute String
"" = String -> Bool
forall a. HasCallStack => String -> a
error String
"isAbsolute called with empty filename"
isAbsolute String
f = String -> Bool
FP.isAbsolute String
f
isValidLocalPath :: String -> Bool
isValidLocalPath :: String -> Bool
isValidLocalPath String
s =
String -> Bool
FP.isValid String
s Bool -> Bool -> Bool
&&
(String -> Bool
FP.hasDrive String
s Bool -> Bool -> Bool
|| Bool -> Bool
not (Char
':' Char -> String -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` String
FP.pathSeparators) String
s))
isHttpUrl :: String -> Bool
isHttpUrl :: String -> Bool
isHttpUrl String
u =
let u' :: String
u' = (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isSpace String
u in
(String
"http://" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
u') Bool -> Bool -> Bool
|| (String
"https://" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
u')
isSshUrl :: String -> Bool
isSshUrl :: String -> Bool
isSshUrl String
s = String -> Bool
isu' ((Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isSpace String
s)
where
isu' :: String -> Bool
isu' String
s'
| String
"ssh://" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
s' = Bool
True
| String
"://" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isInfixOf` String
s' = Bool
False
| String -> Bool
isValidLocalPath String
s' = Bool
False
| Bool
otherwise = String
":" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isInfixOf` String
s'
isSshNopath :: String -> Bool
isSshNopath :: String -> Bool
isSshNopath String
s = case String -> String
forall a. [a] -> [a]
reverse String
s of
Char
':':x :: String
x@(Char
_:Char
_:String
_) -> Char
':' Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` String
x
String
_ -> Bool
False
splitSshUrl :: String -> SshFilePath
splitSshUrl :: String -> SshFilePath
splitSshUrl String
s | String
"ssh://" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
s =
let s' :: String
s' = Int -> String -> String
forall a. Int -> [a] -> [a]
drop (String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
"ssh://") (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isSpace String
s
(String
dir, String
file) = Char -> String -> (String, String)
cleanrepodir Char
'/' String
s'
in
SshFP { sshUhost :: String
sshUhost = (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'/') String
s'
, sshRepo :: String
sshRepo = String
dir
, sshFile :: String
sshFile = String
file }
splitSshUrl String
s =
let (String
dir, String
file) = Char -> String -> (String, String)
cleanrepodir Char
':' String
s in
SshFP { sshUhost :: String
sshUhost = (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isSpace (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
':') String
s
, sshRepo :: String
sshRepo = String
dir
, sshFile :: String
sshFile = String
file }
cleanrepourl :: String -> (String, String)
cleanrepourl :: String -> (String, String)
cleanrepourl String
zzz | String
dd String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
zzz = ([], Int -> String -> String
forall a. Int -> [a] -> [a]
drop (String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
dd) String
zzz)
where dd :: String
dd = String
darcsdirString -> String -> String
forall a. [a] -> [a] -> [a]
++String
"/"
cleanrepourl (Char
z:String
zs) =
let (String
repo',String
file) = String -> (String, String)
cleanrepourl String
zs in
(Char
z Char -> String -> String
forall a. a -> [a] -> [a]
: String
repo', String
file)
cleanrepourl String
"" = ([],[])
cleanrepodir :: Char -> String -> (String, String)
cleanrepodir :: Char -> String -> (String, String)
cleanrepodir Char
sep = String -> (String, String)
cleanrepourl (String -> (String, String))
-> (String -> String) -> String -> (String, String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
sep)
data SshFilePath = SshFP { SshFilePath -> String
sshUhost :: String
, SshFilePath -> String
sshRepo :: String
, SshFilePath -> String
sshFile :: String }
sshFilePathOf :: SshFilePath -> String
sshFilePathOf :: SshFilePath -> String
sshFilePathOf (SshFP String
uhost String
dir String
file) = String
uhost String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":" String -> String -> String
forall a. [a] -> [a] -> [a]
++ (String
dir String -> String -> String
</> String
darcsdir String -> String -> String
</> String
file)
sshCanonRepo :: SshFilePath -> String
sshCanonRepo :: SshFilePath -> String
sshCanonRepo (SshFP String
uhost String
repo String
_) =
String
uhost String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":" String -> String -> String
forall a. [a] -> [a] -> [a]
++ ([String] -> String
joinPath ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
canondir ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String -> [String]
splitDirectories String
repo)
where
canondir :: String -> String
canondir [] = String
""
canondir (Char
x:String
xs) | Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'/' = String
"/"
| Bool
otherwise = (Char
xChar -> String -> String
forall a. a -> [a] -> [a]
:String
xs)