{-# LANGUAGE CPP #-}
module Agda.Utils.FileName
( AbsolutePath(AbsolutePath)
, filePath
, mkAbsolute
, absolute
, canonicalizeAbsolutePath
, sameFile
, doesFileExistCaseSensitive
, isNewerThan
, relativizeAbsolutePath
) where
import System.Directory
import System.FilePath
import Control.Applicative ( liftA2 )
import Control.DeepSeq
#ifdef mingw32_HOST_OS
import Control.Exception ( bracket )
import System.Win32 ( findFirstFile, findClose, getFindDataFileName )
#endif
import Data.Function
import Data.Hashable ( Hashable )
import Data.Text ( Text )
import qualified Data.Text as Text
import Agda.Utils.Monad
import Agda.Utils.Pretty
import Agda.Utils.Impossible
newtype AbsolutePath = AbsolutePath { AbsolutePath -> Text
textPath :: Text }
deriving (Int -> AbsolutePath -> ShowS
[AbsolutePath] -> ShowS
AbsolutePath -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [AbsolutePath] -> ShowS
$cshowList :: [AbsolutePath] -> ShowS
show :: AbsolutePath -> FilePath
$cshow :: AbsolutePath -> FilePath
showsPrec :: Int -> AbsolutePath -> ShowS
$cshowsPrec :: Int -> AbsolutePath -> ShowS
Show, AbsolutePath -> AbsolutePath -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AbsolutePath -> AbsolutePath -> Bool
$c/= :: AbsolutePath -> AbsolutePath -> Bool
== :: AbsolutePath -> AbsolutePath -> Bool
$c== :: AbsolutePath -> AbsolutePath -> Bool
Eq, Eq AbsolutePath
AbsolutePath -> AbsolutePath -> Bool
AbsolutePath -> AbsolutePath -> Ordering
AbsolutePath -> AbsolutePath -> AbsolutePath
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AbsolutePath -> AbsolutePath -> AbsolutePath
$cmin :: AbsolutePath -> AbsolutePath -> AbsolutePath
max :: AbsolutePath -> AbsolutePath -> AbsolutePath
$cmax :: AbsolutePath -> AbsolutePath -> AbsolutePath
>= :: AbsolutePath -> AbsolutePath -> Bool
$c>= :: AbsolutePath -> AbsolutePath -> Bool
> :: AbsolutePath -> AbsolutePath -> Bool
$c> :: AbsolutePath -> AbsolutePath -> Bool
<= :: AbsolutePath -> AbsolutePath -> Bool
$c<= :: AbsolutePath -> AbsolutePath -> Bool
< :: AbsolutePath -> AbsolutePath -> Bool
$c< :: AbsolutePath -> AbsolutePath -> Bool
compare :: AbsolutePath -> AbsolutePath -> Ordering
$ccompare :: AbsolutePath -> AbsolutePath -> Ordering
Ord, Eq AbsolutePath
Int -> AbsolutePath -> Int
AbsolutePath -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: AbsolutePath -> Int
$chash :: AbsolutePath -> Int
hashWithSalt :: Int -> AbsolutePath -> Int
$chashWithSalt :: Int -> AbsolutePath -> Int
Hashable, AbsolutePath -> ()
forall a. (a -> ()) -> NFData a
rnf :: AbsolutePath -> ()
$crnf :: AbsolutePath -> ()
NFData)
filePath :: AbsolutePath -> FilePath
filePath :: AbsolutePath -> FilePath
filePath = Text -> FilePath
Text.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. AbsolutePath -> Text
textPath
instance Pretty AbsolutePath where
pretty :: AbsolutePath -> Doc
pretty = FilePath -> Doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. AbsolutePath -> FilePath
filePath
mkAbsolute :: FilePath -> AbsolutePath
mkAbsolute :: FilePath -> AbsolutePath
mkAbsolute FilePath
f
| FilePath -> Bool
isAbsolute FilePath
f =
Text -> AbsolutePath
AbsolutePath forall a b. (a -> b) -> a -> b
$ FilePath -> Text
Text.pack forall a b. (a -> b) -> a -> b
$ ShowS
dropTrailingPathSeparator forall a b. (a -> b) -> a -> b
$ ShowS
normalise FilePath
f
| Bool
otherwise = forall a. HasCallStack => a
__IMPOSSIBLE__
absolute :: FilePath -> IO AbsolutePath
absolute :: FilePath -> IO AbsolutePath
absolute FilePath
f = FilePath -> AbsolutePath
mkAbsolute forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
Bool
ex <- FilePath -> IO Bool
doesFileExist FilePath
f forall (m :: * -> *). Monad m => m Bool -> m Bool -> m Bool
`or2M` FilePath -> IO Bool
doesDirectoryExist FilePath
f
if Bool
ex then do
FilePath
dir <- FilePath -> IO FilePath
canonicalizePath (ShowS
takeDirectory FilePath
f)
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath
dir FilePath -> ShowS
</> ShowS
takeFileName FilePath
f)
else do
FilePath
cwd <- IO FilePath
getCurrentDirectory
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath
cwd FilePath -> ShowS
</> FilePath
f)
canonicalizeAbsolutePath :: AbsolutePath -> IO AbsolutePath
canonicalizeAbsolutePath :: AbsolutePath -> IO AbsolutePath
canonicalizeAbsolutePath (AbsolutePath Text
f) =
Text -> AbsolutePath
AbsolutePath forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Text
Text.pack forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO FilePath
canonicalizePath (Text -> FilePath
Text.unpack Text
f)
sameFile :: AbsolutePath -> AbsolutePath -> IO Bool
sameFile :: AbsolutePath -> AbsolutePath -> IO Bool
sameFile = forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 FilePath -> FilePath -> Bool
equalFilePath forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (FilePath -> IO FilePath
canonicalizePath forall b c a. (b -> c) -> (a -> b) -> a -> c
. AbsolutePath -> FilePath
filePath)
doesFileExistCaseSensitive :: FilePath -> IO Bool
#ifdef mingw32_HOST_OS
doesFileExistCaseSensitive f = do
doesFileExist f `and2M` do
bracket (findFirstFile f) (findClose . fst) $
fmap (takeFileName f ==) . getFindDataFileName . snd
#else
doesFileExistCaseSensitive :: FilePath -> IO Bool
doesFileExistCaseSensitive = FilePath -> IO Bool
doesFileExist
#endif
isNewerThan :: FilePath -> FilePath -> IO Bool
isNewerThan :: FilePath -> FilePath -> IO Bool
isNewerThan FilePath
new FilePath
old = do
Bool
newExist <- FilePath -> IO Bool
doesFileExist FilePath
new
Bool
oldExist <- FilePath -> IO Bool
doesFileExist FilePath
old
if Bool -> Bool
not (Bool
newExist Bool -> Bool -> Bool
&& Bool
oldExist)
then forall (m :: * -> *) a. Monad m => a -> m a
return Bool
newExist
else do
UTCTime
newT <- FilePath -> IO UTCTime
getModificationTime FilePath
new
UTCTime
oldT <- FilePath -> IO UTCTime
getModificationTime FilePath
old
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ UTCTime
newT forall a. Ord a => a -> a -> Bool
>= UTCTime
oldT
relativizeAbsolutePath ::
AbsolutePath
-> AbsolutePath
-> Maybe FilePath
relativizeAbsolutePath :: AbsolutePath -> AbsolutePath -> Maybe FilePath
relativizeAbsolutePath AbsolutePath
apath AbsolutePath
aroot
| FilePath
rest forall a. Eq a => a -> a -> Bool
/= FilePath
path = forall a. a -> Maybe a
Just FilePath
rest
| Bool
otherwise = forall a. Maybe a
Nothing
where
path :: FilePath
path = AbsolutePath -> FilePath
filePath AbsolutePath
apath
root :: FilePath
root = AbsolutePath -> FilePath
filePath AbsolutePath
aroot
rest :: FilePath
rest = FilePath -> ShowS
makeRelative FilePath
root FilePath
path