#ifndef MIN_VERSION_filepath
#if __GLASGOW_HASKELL__ >= 709
#define MIN_VERSION_filepath(a,b,c) 1
#else
#define MIN_VERSION_filepath(a,b,c) 0
#endif
#endif
module Development.Shake.FilePath(
    module System.FilePath, module System.FilePath.Posix,
    dropDirectory1, takeDirectory1, normaliseEx,
#if !MIN_VERSION_filepath(1,4,0)
    (-<.>),
#endif
    toNative, toStandard,
    exe
    ) where
import System.Info.Extra
import qualified System.FilePath as Native
import System.FilePath hiding
    (splitExtension, takeExtension, replaceExtension, dropExtension, addExtension
    ,hasExtension, (<.>), splitExtensions, takeExtensions, dropExtensions
#if MIN_VERSION_filepath(1,4,0)
    ,(-<.>)
#endif
    )
import System.FilePath.Posix
    (splitExtension, takeExtension, replaceExtension, dropExtension, addExtension
    ,hasExtension, (<.>), splitExtensions, takeExtensions, dropExtensions
#if MIN_VERSION_filepath(1,4,0)
    ,(-<.>)
#endif
    )
#if !MIN_VERSION_filepath(1,4,0)
infixr 7  -<.>
(-<.>) :: FilePath -> String -> FilePath
(-<.>) = replaceExtension
#endif
dropDirectory1 :: FilePath -> FilePath
dropDirectory1 = drop 1 . dropWhile (not . isPathSeparator)
takeDirectory1 :: FilePath -> FilePath
takeDirectory1 = takeWhile (not . isPathSeparator)
normaliseEx :: FilePath -> FilePath
normaliseEx xs | a:b:xs <- xs, isWindows && sep a && sep b = '/' : f ('/':xs) 
               | otherwise = f xs
    where
        sep = Native.isPathSeparator
        f o = toNative $ deslash o $ (++"/") $ concatMap ('/':) $ reverse $ g 0 $ reverse $ split o
        deslash o x
            | x == "/" = case (pre,pos) of
                (True,True) -> "/"
                (True,False) -> "/."
                (False,True) -> "./"
                (False,False) -> "."
            | otherwise = (if pre then id else tail) $ (if pos then id else init) x
            where pre = sep $ head $ o ++ " "
                  pos = sep $ last $ " " ++ o
        g i [] = replicate i ".."
        g i ("..":xs) = g (i+1) xs
        g i (".":xs) = g i xs
        g 0 (x:xs) = x : g 0 xs
        g i (x:xs) = g (i1) xs
        split xs = if null ys then [] else a : split b
            where (a,b) = break sep $ ys
                  ys = dropWhile sep xs
toNative :: FilePath -> FilePath
toNative = if isWindows then map (\x -> if x == '/' then '\\' else x) else id
toStandard :: FilePath -> FilePath
toStandard = if isWindows then map (\x -> if x == '\\' then '/' else x) else id
exe :: String
exe = if isWindows then "exe" else ""