module Darcs.Util.Path
    ( FileName( )
    , fp2fn
    , fn2fp
    , fn2ps
    , ps2fn
    , breakOnDir
    , normPath
    , ownName
    , superName
    , movedirfilename
    , encodeWhite
    , decodeWhite
    , encodeWhiteName
    , decodeWhiteName
    , isParentOrEqOf
    
    , AbsolutePath
    , makeAbsolute
    , ioAbsolute
    , rootDirectory
    
    , AbsolutePathOrStd
    , makeAbsoluteOrStd
    , ioAbsoluteOrStd
    , useAbsoluteOrStd
    , stdOut
    
    , AbsoluteOrRemotePath
    , ioAbsoluteOrRemote
    , isRemote
    
    , SubPath
    , makeSubPathOf
    , simpleSubPath
    , isSubPathOf
    , floatSubPath
    
    , sp2fn
    , FilePathOrURL(..)
    , FilePathLike(toFilePath)
    , getCurrentDirectory
    , setCurrentDirectory
    , getUniquePathName
    , doesPathExist
    
    , isMaliciousPath
    , isMaliciousSubPath
    
    , filterFilePaths
    , filterPaths
    
    
    
    , Name
    , unsafeMakeName
    , eqAnycase
    , AnchoredPath(..)
    , anchoredRoot
    , appendPath
    , anchorPath
    , isPrefix
    , parent, parents, catPaths, flatten, makeName, appendToName
    
    , floatPath, replacePrefixPath ) where
import Prelude ()
import Darcs.Prelude
import Data.List
    ( isPrefixOf
    , isSuffixOf
    , stripPrefix
    , intersect
    , inits
    )
import Data.Char ( isSpace, chr, ord, toLower )
import Control.Exception ( tryJust, bracket_ )
import Control.Monad ( when )
import System.IO.Error ( isDoesNotExistError )
import qualified Darcs.Util.Workaround as Workaround ( getCurrentDirectory )
import qualified System.Directory ( setCurrentDirectory )
import System.Directory ( doesDirectoryExist, doesFileExist )
import qualified System.FilePath.Posix as FilePath ( normalise, isRelative )
import qualified System.FilePath as NativeFilePath ( takeFileName, takeDirectory )
import System.FilePath( (</>), splitDirectories, normalise, dropTrailingPathSeparator )
import System.Posix.Files ( isDirectory, getSymbolicLinkStatus )
import Darcs.Util.ByteString ( encodeLocale, decodeLocale )
import qualified Data.ByteString.Char8 as BC
import qualified Data.ByteString       as B
import Data.Binary
import Darcs.Util.Global ( darcsdir )
import Darcs.Util.URL ( isAbsolute, isRelative, isSshNopath )
newtype FileName = FN FilePath deriving ( Eq, Ord )
instance Show FileName where
   showsPrec d (FN fp) = showParen (d > appPrec) $ showString "fp2fn " . showsPrec (appPrec + 1) fp
      where appPrec = 10
instance Binary FileName where
  put (FN h) = put h
  get = FN `fmap` get
fp2fn :: FilePath -> FileName
fp2fn = FN
fn2fp :: FileName -> FilePath
fn2fp (FN fp) = fp
fn2ps :: FileName -> B.ByteString
fn2ps (FN fp) = encodeLocale $ encodeWhite fp
ps2fn :: B.ByteString -> FileName
ps2fn ps = FN $ decodeWhite $ decodeLocale ps
sp2fn :: SubPath -> FileName
sp2fn = fp2fn . toFilePath
encodeWhite :: FilePath -> String
encodeWhite (c:cs) | isSpace c || c == '\\' =
    '\\' : show (ord c) ++ "\\" ++ encodeWhite cs
encodeWhite (c:cs) = c : encodeWhite cs
encodeWhite [] = []
decodeWhite :: String -> FilePath
decodeWhite cs_ = go cs_ [] False
 where go "" acc True  = reverse acc 
       go "" _   False = cs_         
       go ('\\':cs) acc _ =
         case break (=='\\') cs of
           (theord, '\\':rest) ->
             go rest (chr (read theord) :acc) True
           _ -> error "malformed filename"
       go (c:cs) acc modified = go cs (c:acc) modified
encodeWhiteName :: Name -> B.ByteString
encodeWhiteName = encodeLocale . encodeWhite . decodeLocale . unName
decodeWhiteName :: B.ByteString -> Name
decodeWhiteName = Name . encodeLocale . decodeWhite . decodeLocale
ownName :: FileName -> FileName
ownName (FN f) =  case breakLast '/' f of Nothing -> FN f
                                          Just (_,f') -> FN f'
superName :: FileName -> FileName
superName fn = case normPath fn of
                FN f -> case breakLast '/' f of
                        Nothing -> FN "."
                        Just (d,_) -> FN d
breakOnDir :: FileName -> Maybe (FileName,FileName)
breakOnDir (FN p) = case breakFirst '/' p of
                      Nothing -> Nothing
                      Just (d,f) | d == "." -> breakOnDir $ FN f
                                 | otherwise -> Just (FN d, FN f)
normPath :: FileName -> FileName
normPath (FN p) = FN $ norm p
norm :: String -> String
norm ('.':'/':s) = norm s
norm ('/':s)     = norm s
norm "."         = ""
norm s = go s [] False
 where go "" _   False = s           
       go "" acc True  = reverse acc
       go ('/':r)         acc _ | sep r = go r acc True
       go ('/':'.':r)     acc _ | sep r = go r acc True
       go ('/':'.':'.':r) acc _ | sep r = go r (doDotDot acc) True
       go (c:s') acc changed = go s' (c:acc) changed
       
       doDotDot ""                       = ".."
       doDotDot acc@('.':'.':r) | sep r  = '.':'.':'/':acc
       doDotDot acc = let a' = dropWhile (/='/') acc in 
                       if null a' then "" else tail a'
       
       sep ('/':_) = True
       sep []      = True 
       sep _       = False
breakFirst :: Char -> String -> Maybe (String,String)
breakFirst c = bf []
    where bf a (r:rs) | r == c = Just (reverse a,rs)
                      | otherwise = bf (r:a) rs
          bf _ [] = Nothing
breakLast :: Char -> String -> Maybe (String,String)
breakLast c l = case breakFirst c (reverse l) of
                Nothing -> Nothing
                Just (a,b) -> Just (reverse b, reverse a)
isParentOrEqOf :: FileName -> FileName -> Bool
isParentOrEqOf fn1 fn2 = case stripPrefix (fn2fp fn1) (fn2fp fn2) of
    Just ('/' : _) -> True
    Just [] -> True
    _ -> False
movedirfilename :: FileName -> FileName -> FileName -> FileName
movedirfilename old new name =
    if name' == old'
        then new
        else case stripPrefix old' name' of
            Just rest@('/':_) -> fp2fn $ "./" ++ new' ++ rest
            _ -> name
        where old' = fn2fp $ normPath old
              new' = fn2fp $ normPath new
              name' = fn2fp $ normPath name
class FilePathOrURL a where
  toPath :: a -> String
class FilePathOrURL a => FilePathLike a where
  toFilePath :: a -> FilePath
newtype SubPath      = SubPath FilePath deriving (Eq, Ord)
newtype AbsolutePath = AbsolutePath FilePath deriving (Eq, Ord)
data AbsolutePathOrStd = AP AbsolutePath | APStd deriving (Eq, Ord)
data AbsoluteOrRemotePath = AbsP AbsolutePath | RmtP String deriving (Eq, Ord)
instance FilePathOrURL AbsolutePath where
  toPath (AbsolutePath x) = x
instance FilePathOrURL SubPath where
  toPath (SubPath x) = x
instance CharLike c => FilePathOrURL [c] where
  toPath = toFilePath
instance FilePathOrURL AbsoluteOrRemotePath where
  toPath (AbsP a) = toPath a
  toPath (RmtP r) = r
instance FilePathOrURL FileName where
  toPath = fn2fp
instance FilePathLike FileName where
  toFilePath = fn2fp
instance FilePathLike AbsolutePath where
  toFilePath (AbsolutePath x) = x
instance FilePathLike SubPath where
  toFilePath (SubPath x) = x
class CharLike c where
  toChar :: c -> Char
instance CharLike Char where
  toChar = id
instance CharLike c => FilePathLike [c] where
  toFilePath = map toChar
makeSubPathOf :: AbsolutePath -> AbsolutePath -> Maybe SubPath
makeSubPathOf (AbsolutePath p1) (AbsolutePath p2) =
 
 if p1 == p2 || (p1 ++ "/") `isPrefixOf` p2
    then Just $ SubPath $ drop (length p1 + 1) p2
    else Nothing
simpleSubPath :: FilePath -> Maybe SubPath
simpleSubPath x | null x = bug "simpleSubPath called with empty path"
                | isRelative x = Just $ SubPath $ FilePath.normalise $ pathToPosix x
                | otherwise = Nothing
isSubPathOf :: SubPath -> SubPath -> Bool
isSubPathOf (SubPath p1) (SubPath p2) =
    p1 == "" || p1 == p2 || (p1 ++ "/") `isPrefixOf` p2
doesDirectoryReallyExist :: FilePath -> IO Bool
doesDirectoryReallyExist f = do
    x <- tryJust (\x -> if isDoesNotExistError x then Just () else Nothing) $
        isDirectory <$> getSymbolicLinkStatus f
    return $ case x of
        Left () -> False
        Right y -> y
doesPathExist :: FilePath -> IO Bool
doesPathExist p = do
   dir_exists <- doesDirectoryExist p
   file_exists <- doesFileExist p
   return $ dir_exists || file_exists
ioAbsolute :: FilePath -> IO AbsolutePath
ioAbsolute dir =
    do isdir <- doesDirectoryReallyExist dir
       here <- getCurrentDirectory
       if isdir
         then bracket_ (setCurrentDirectory dir)
                       (setCurrentDirectory $ toFilePath here)
                       getCurrentDirectory
         else let super_dir = case NativeFilePath.takeDirectory dir of
                                "" ->  "."
                                d  -> d
                  file = NativeFilePath.takeFileName dir
              in do abs_dir <- if dir == super_dir
                               then return $ AbsolutePath dir
                               else ioAbsolute super_dir
                    return $ makeAbsolute abs_dir file
makeAbsolute :: AbsolutePath -> FilePath -> AbsolutePath
makeAbsolute a dir = if not (null dir) && isAbsolute dir
                     then AbsolutePath (normSlashes dir')
                     else ma a dir'
  where
    dir' = FilePath.normalise $ pathToPosix dir
    
    
    ma here ('.':'.':'/':r) = ma (takeDirectory here) r
    ma here ".." = takeDirectory here
    ma here "." = here
    ma here "" = here
    ma here r = here /- ('/':r)
(/-) :: AbsolutePath -> String -> AbsolutePath
x /- ('/':r) = x /- r
(AbsolutePath "/") /- r = AbsolutePath ('/':simpleClean r)
(AbsolutePath x) /- r = AbsolutePath (x++'/':simpleClean r)
simpleClean :: String -> String
simpleClean = normSlashes . reverse . dropWhile (=='/') . reverse . pathToPosix
rootDirectory :: AbsolutePath
rootDirectory = AbsolutePath "/"
makeAbsoluteOrStd :: AbsolutePath -> String -> AbsolutePathOrStd
makeAbsoluteOrStd _ "-" = APStd
makeAbsoluteOrStd a p = AP $ makeAbsolute a p
stdOut :: AbsolutePathOrStd
stdOut = APStd
ioAbsoluteOrStd :: String -> IO AbsolutePathOrStd
ioAbsoluteOrStd "-" = return APStd
ioAbsoluteOrStd p = AP `fmap` ioAbsolute p
useAbsoluteOrStd :: (AbsolutePath -> a) -> a -> AbsolutePathOrStd -> a
useAbsoluteOrStd _ f APStd = f
useAbsoluteOrStd f _ (AP x) = f x
ioAbsoluteOrRemote :: String -> IO AbsoluteOrRemotePath
ioAbsoluteOrRemote p = do
  isdir <- doesDirectoryExist p
  if not isdir
     then return $ RmtP $
          case () of _ | isSshNopath p    -> p++"."
                       | "/" `isSuffixOf` p -> init p
                       | otherwise          -> p
     else AbsP `fmap` ioAbsolute p
isRemote :: AbsoluteOrRemotePath -> Bool
isRemote (RmtP _) = True
isRemote _ = False
takeDirectory :: AbsolutePath -> AbsolutePath
takeDirectory (AbsolutePath x) =
    case reverse $ drop 1 $ dropWhile (/='/') $ reverse x of
    "" -> AbsolutePath "/"
    x' -> AbsolutePath x'
instance Show AbsolutePath where
 show = show . toFilePath
instance Show SubPath where
 show = show . toFilePath
instance Show AbsolutePathOrStd where
    show (AP a) = show a
    show APStd = "standard input/output"
instance Show AbsoluteOrRemotePath where
    show (AbsP a) = show a
    show (RmtP r) = show r
pathToPosix :: FilePath -> FilePath
pathToPosix = map convert where
#ifdef WIN32
  convert '\\' = '/'
#endif
  convert c = c
normSlashes :: FilePath -> FilePath
#ifndef WIN32
normSlashes ('/':p) = '/' : dropWhile (== '/') p
#endif
normSlashes p = p
getCurrentDirectory :: IO AbsolutePath
getCurrentDirectory = AbsolutePath `fmap` Workaround.getCurrentDirectory
setCurrentDirectory :: FilePathLike p => p -> IO ()
setCurrentDirectory = System.Directory.setCurrentDirectory . toFilePath
isMaliciousPath :: String -> Bool
isMaliciousPath fp =
    not (isExplicitlyRelative fp) || isGenerallyMalicious fp
isMaliciousSubPath :: String -> Bool
isMaliciousSubPath fp =
    not (FilePath.isRelative fp) || isGenerallyMalicious fp
isGenerallyMalicious :: String -> Bool
isGenerallyMalicious fp =
    splitDirectories fp `contains_any` [ "..", darcsdir ]
 where
    contains_any a b = not . null $ intersect a b
isExplicitlyRelative :: String -> Bool
isExplicitlyRelative ('.':'/':_) = True  
isExplicitlyRelative _ = False
filterPaths :: [AnchoredPath]
            -> AnchoredPath
            -> t
            -> Bool
filterPaths files p _ = any (\x -> x `isPrefix` p || p `isPrefix` x) files
filterFilePaths :: [FilePath]
                -> AnchoredPath
                -> t
                -> Bool
filterFilePaths = filterPaths . map floatPath
getUniquePathName :: Bool -> (FilePath -> String) -> (Int -> FilePath) -> IO FilePath
getUniquePathName talkative buildMsg buildName = go (1)
 where
  go :: Int -> IO FilePath
  go i = do
    exists <- doesPathExist thename
    if not exists
       then do when (i /= 1 && talkative) $ putStrLn $ buildMsg thename
               return thename
       else go $ i+1
    where thename = buildName i
floatSubPath :: SubPath -> AnchoredPath
floatSubPath = floatPath . fn2fp . sp2fn
 
newtype Name = Name { unName :: B.ByteString } deriving (Eq, Show, Ord)
newtype AnchoredPath = AnchoredPath [Name] deriving (Eq, Show, Ord)
isPrefix :: AnchoredPath -> AnchoredPath -> Bool
(AnchoredPath a) `isPrefix` (AnchoredPath b) = a `isPrefixOf` b
appendPath :: AnchoredPath -> Name -> AnchoredPath
appendPath (AnchoredPath p) n =
    case n of
      (Name s) | B.null s -> AnchoredPath p
               | s == BC.pack "." -> AnchoredPath p
               | otherwise -> AnchoredPath $ p ++ [n]
catPaths :: AnchoredPath -> AnchoredPath -> AnchoredPath
catPaths (AnchoredPath p) (AnchoredPath n) = AnchoredPath $ p ++ n
parent :: AnchoredPath -> AnchoredPath
parent (AnchoredPath x) = AnchoredPath (init x)
parents :: AnchoredPath -> [AnchoredPath]
parents (AnchoredPath x) = map AnchoredPath . init . inits $ x
anchorPath :: FilePath -> AnchoredPath -> FilePath
anchorPath dir p = dir </> decodeLocale (flatten p)
flatten :: AnchoredPath -> BC.ByteString
flatten (AnchoredPath []) = BC.singleton '.'
flatten (AnchoredPath p) = BC.intercalate (BC.singleton '/')
                                           [ n | (Name n) <- p ]
makeName :: String -> Name
makeName ".." = error ".. is not a valid AnchoredPath component name"
makeName n | '/' `elem` n = error "/ may not occur in a valid AnchoredPath component name"
           | otherwise = Name $ encodeLocale n
floatPath :: FilePath -> AnchoredPath
floatPath = make . splitDirectories . normalise . dropTrailingPathSeparator
  where make ["."] = AnchoredPath []
        make x = AnchoredPath $ map (Name . encodeLocale) x
anchoredRoot :: AnchoredPath
anchoredRoot = AnchoredPath []
replacePrefixPath :: AnchoredPath -> AnchoredPath -> AnchoredPath -> AnchoredPath
replacePrefixPath (AnchoredPath []) b c = catPaths b c
replacePrefixPath (AnchoredPath (r:p)) b (AnchoredPath (r':p'))
    | r == r' = replacePrefixPath (AnchoredPath p) b (AnchoredPath p')
    | otherwise = AnchoredPath []
replacePrefixPath _ _ _ = AnchoredPath []
appendToName :: AnchoredPath -> String -> AnchoredPath
appendToName (AnchoredPath p) s = AnchoredPath (init p++[Name finalname])
    where suffix = encodeLocale s
          finalname | suffix `elem` (BC.tails lastname) = lastname
                    | otherwise = BC.append lastname suffix
          lastname = case last p of
                        Name name -> name
unsafeMakeName :: B.ByteString -> Name
unsafeMakeName = Name
eqAnycase :: Name -> Name -> Bool
eqAnycase (Name a) (Name b) = BC.map toLower a == BC.map toLower b