{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# OPTIONS_GHC -Wall -fno-warn-orphans #-}
{-# OPTIONS_GHC -Wno-deprecations #-}
module Uniform.Filenames
( module Uniform.Filenames,
module Uniform.Error,
Abs,
Rel,
File,
Dir,
Path,
toFilePath,
)
where
import Path hiding ((</>), addExtension)
import qualified Path
import qualified Path.IO as PathIO
import qualified System.FilePath as S
import Uniform.Error(ErrIO, callIO)
import Uniform.Strings
import Uniform.PathShowCase ()
takeBaseName' :: FilePath -> FilePath
takeBaseName' :: FilePath -> FilePath
takeBaseName' = FilePath -> FilePath
S.takeBaseName
homeDir :: Path Abs Dir
homeDir :: Path Abs Dir
homeDir = FilePath -> Path Abs Dir
makeAbsDir FilePath
"/home/frank/" :: Path Abs Dir
homeDir2 :: ErrIO (Path Abs Dir)
homeDir2 :: ErrIO (Path Abs Dir)
homeDir2 = forall a. IO a -> ErrIO a
callIO forall (m :: * -> *). MonadIO m => m (Path Abs Dir)
PathIO.getHomeDir :: ErrIO (Path Abs Dir)
currentDir :: ErrIO (Path Abs Dir)
currentDir :: ErrIO (Path Abs Dir)
currentDir = forall a. IO a -> ErrIO a
callIO forall (m :: * -> *). MonadIO m => m (Path Abs Dir)
PathIO.getCurrentDir
setCurrentDir :: Path Abs Dir -> ErrIO ()
setCurrentDir :: Path Abs Dir -> ErrIO ()
setCurrentDir Path Abs Dir
path = forall (m :: * -> *) b. MonadIO m => Path b Dir -> m ()
PathIO.setCurrentDir (forall a. a -> a
unPath Path Abs Dir
path)
stripProperPrefix' :: Path b Dir -> Path b t -> ErrIO (Path Rel t)
stripProperPrefix' :: forall b t. Path b Dir -> Path b t -> ErrIO (Path Rel t)
stripProperPrefix' Path b Dir
dir Path b t
fn = forall (m :: * -> *) b t.
MonadThrow m =>
Path b Dir -> Path b t -> m (Path Rel t)
Path.stripProperPrefix (forall a. a -> a
unPath Path b Dir
dir) (forall a. a -> a
unPath Path b t
fn)
stripProperPrefixMaybe :: Path b Dir -> Path b t -> Maybe (Path Rel t)
stripProperPrefixMaybe :: forall b t. Path b Dir -> Path b t -> Maybe (Path Rel t)
stripProperPrefixMaybe Path b Dir
dir Path b t
fn = forall (m :: * -> *) b t.
MonadThrow m =>
Path b Dir -> Path b t -> m (Path Rel t)
Path.stripProperPrefix (forall a. a -> a
unPath Path b Dir
dir) (forall a. a -> a
unPath Path b t
fn)
unPath :: a -> a
unPath :: forall a. a -> a
unPath = forall a. a -> a
id
makeRelFile :: FilePath -> Path Rel File
makeRelDir :: FilePath -> Path Rel Dir
makeAbsFile :: FilePath -> Path Abs File
makeAbsDir :: FilePath -> Path Abs Dir
makeRelFile :: FilePath -> Path Rel File
makeRelFile FilePath
fn = forall a. Partial => FilePath -> Maybe a -> a
fromJustNote (FilePath
"makeRelFile " forall a. [a] -> [a] -> [a]
++ FilePath
fn) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Rel File)
Path.parseRelFile FilePath
fn
makeRelDir :: FilePath -> Path Rel Dir
makeRelDir FilePath
fn = forall a. Partial => FilePath -> Maybe a -> a
fromJustNote (FilePath
"makeRelDir " forall a. [a] -> [a] -> [a]
++ FilePath
fn) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Rel Dir)
Path.parseRelDir FilePath
fn
makeAbsFile :: FilePath -> Path Abs File
makeAbsFile FilePath
fn = forall a. Partial => FilePath -> Maybe a -> a
fromJustNote (FilePath
"makeAbsFile " forall a. [a] -> [a] -> [a]
++ FilePath
fn) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs File)
Path.parseAbsFile FilePath
fn
makeAbsDir :: FilePath -> Path Abs Dir
makeAbsDir FilePath
fn = forall a. Partial => FilePath -> Maybe a -> a
fromJustNote (FilePath
"makeAbsDir " forall a. [a] -> [a] -> [a]
++ FilePath
fn) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs Dir)
Path.parseAbsDir FilePath
fn
makeRelFileT :: Text -> Path Rel File
makeRelDirT :: Text -> Path Rel Dir
makeAbsFileT :: Text -> Path Abs File
makeAbsDirT :: Text -> Path Abs Dir
makeRelFileT :: Text -> Path Rel File
makeRelFileT = FilePath -> Path Rel File
makeRelFile forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
t2s
makeRelDirT :: Text -> Path Rel Dir
makeRelDirT = FilePath -> Path Rel Dir
makeRelDir forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
t2s
makeAbsFileT :: Text -> Path Abs File
makeAbsFileT = FilePath -> Path Abs File
makeAbsFile forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
t2s
makeAbsDirT :: Text -> Path Abs Dir
makeAbsDirT = FilePath -> Path Abs Dir
makeAbsDir forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
t2s
toShortFilePath :: Path df ar -> FilePath
toShortFilePath :: forall df ar. Path df ar -> FilePath
toShortFilePath = FilePath -> FilePath
S.dropTrailingPathSeparator forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall df ar. Path df ar -> FilePath
toFilePath
instance Zeros (Path Abs Dir) where
zero :: Path Abs Dir
zero = FilePath -> Path Abs Dir
makeAbsDir FilePath
"/"
instance Zeros (Path Abs File) where
zero :: Path Abs File
zero = FilePath -> Path Abs File
makeAbsFile FilePath
"/zero"
instance Zeros (Path Rel Dir) where
zero :: Path Rel Dir
zero = FilePath -> Path Rel Dir
makeRelDir FilePath
"./"
instance Zeros (Path Rel File) where
zero :: Path Rel File
zero = FilePath -> Path Rel File
makeRelFile FilePath
"zero"
newtype Extension = Extension FilePath deriving (Int -> Extension -> FilePath -> FilePath
[Extension] -> FilePath -> FilePath
Extension -> FilePath
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [Extension] -> FilePath -> FilePath
$cshowList :: [Extension] -> FilePath -> FilePath
show :: Extension -> FilePath
$cshow :: Extension -> FilePath
showsPrec :: Int -> Extension -> FilePath -> FilePath
$cshowsPrec :: Int -> Extension -> FilePath -> FilePath
Show, ReadPrec [Extension]
ReadPrec Extension
Int -> ReadS Extension
ReadS [Extension]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Extension]
$creadListPrec :: ReadPrec [Extension]
readPrec :: ReadPrec Extension
$creadPrec :: ReadPrec Extension
readList :: ReadS [Extension]
$creadList :: ReadS [Extension]
readsPrec :: Int -> ReadS Extension
$creadsPrec :: Int -> ReadS Extension
Read, Extension -> Extension -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Extension -> Extension -> Bool
$c/= :: Extension -> Extension -> Bool
== :: Extension -> Extension -> Bool
$c== :: Extension -> Extension -> Bool
Eq, Eq Extension
Extension -> Extension -> Bool
Extension -> Extension -> Ordering
Extension -> Extension -> Extension
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 :: Extension -> Extension -> Extension
$cmin :: Extension -> Extension -> Extension
max :: Extension -> Extension -> Extension
$cmax :: Extension -> Extension -> Extension
>= :: Extension -> Extension -> Bool
$c>= :: Extension -> Extension -> Bool
> :: Extension -> Extension -> Bool
$c> :: Extension -> Extension -> Bool
<= :: Extension -> Extension -> Bool
$c<= :: Extension -> Extension -> Bool
< :: Extension -> Extension -> Bool
$c< :: Extension -> Extension -> Bool
compare :: Extension -> Extension -> Ordering
$ccompare :: Extension -> Extension -> Ordering
Ord)
unExtension :: Extension -> FilePath
unExtension :: Extension -> FilePath
unExtension (Extension FilePath
e) = FilePath
e
makeExtension :: FilePath -> Extension
makeExtension :: FilePath -> Extension
makeExtension = FilePath -> Extension
Extension
makeExtensionT :: Text -> Extension
makeExtensionT :: Text -> Extension
makeExtensionT = FilePath -> Extension
Extension forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
t2s
class Filenames fp fr where
getFileName :: fp -> fr
class Filenames3 fp file where
type FileResultT fp file
(</>), addFileName :: fp -> file -> FileResultT fp file
(</>) = forall fp file.
Filenames3 fp file =>
fp -> file -> FileResultT fp file
addFileName
class Filenames5 dir fil res where
stripPrefix :: dir -> fil -> Maybe res
instance Filenames5 (Path b Dir) (Path b t) (Path Rel t) where
stripPrefix :: Path b Dir -> Path b t -> Maybe (Path Rel t)
stripPrefix Path b Dir
d Path b t
f = forall (m :: * -> *) b t.
MonadThrow m =>
Path b Dir -> Path b t -> m (Path Rel t)
Path.stripProperPrefix (forall a. a -> a
unPath Path b Dir
d) (forall a. a -> a
unPath Path b t
f)
class Filenames4 fp file where
type FileResultT4 fp file
addDir :: fp -> file -> FileResultT4 fp file
class Filenames1 fp where
getImmediateParentDir :: fp -> FilePath
getParentDir :: fp -> FilePath
getNakedFileName :: fp -> FilePath
getNakedDir :: fp -> FilePath
instance Filenames FilePath FilePath where
getFileName :: FilePath -> FilePath
getFileName = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (FilePath, FilePath)
S.splitFileName
instance Filenames3 FilePath FilePath where
type FileResultT FilePath FilePath = FilePath
addFileName :: FilePath -> FilePath -> FileResultT FilePath FilePath
addFileName = FilePath -> FilePath -> FilePath
S.combine
instance Filenames (Path ar File) (Path Rel File) where
getFileName :: Path ar File -> Path Rel File
getFileName = forall ar. Path ar File -> Path Rel File
Path.filename forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> a
unPath
instance Filenames3 (Path b Dir) FilePath where
type FileResultT (Path b Dir) FilePath = (Path b File)
addFileName :: Path b Dir -> FilePath -> FileResultT (Path b Dir) FilePath
addFileName Path b Dir
p FilePath
d =
if forall a. CharChains a => a -> Bool
null' FilePath
d
then forall a. Partial => FilePath -> a
error (FilePath
"addFileName with empty file" forall a. [a] -> [a] -> [a]
++ FilePath
d)
else forall b t. Path b Dir -> Path Rel t -> Path b t
(Path.</>) (forall a. a -> a
unPath Path b Dir
p) (forall a. a -> a
unPath Path Rel File
d2)
where
d2 :: Path Rel File
d2 = FilePath -> Path Rel File
makeRelFile FilePath
d :: Path Rel File
instance Filenames4 FilePath FilePath where
type FileResultT4 FilePath FilePath = FilePath
addDir :: FilePath -> FilePath -> FileResultT4 FilePath FilePath
addDir FilePath
p FilePath
d = if forall a. CharChains a => a -> Bool
null' FilePath
d then FilePath
p else FilePath
p forall fp file.
Filenames3 fp file =>
fp -> file -> FileResultT fp file
</> FilePath
d
instance Filenames4 (Path b Dir) FilePath where
type FileResultT4 (Path b Dir) FilePath = (Path b Dir)
addDir :: Path b Dir -> FilePath -> FileResultT4 (Path b Dir) FilePath
addDir Path b Dir
p FilePath
d =
if forall a. CharChains a => a -> Bool
null' FilePath
d
then Path b Dir
p
else Path b Dir
p forall fp file.
Filenames3 fp file =>
fp -> file -> FileResultT fp file
</> Path Rel Dir
d2
where
d2 :: Path Rel Dir
d2 = FilePath -> Path Rel Dir
makeRelDir FilePath
d :: Path Rel Dir
instance Filenames4 (Path b Dir) (Path Rel t) where
type FileResultT4 (Path b Dir) (Path Rel t) = (Path b t)
addDir :: Path b Dir -> Path Rel t -> FileResultT4 (Path b Dir) (Path Rel t)
addDir Path b Dir
p Path Rel t
d = forall b t. Path b Dir -> Path Rel t -> Path b t
(Path.</>) (forall a. a -> a
unPath Path b Dir
p) (forall a. a -> a
unPath Path Rel t
d)
instance Filenames3 (Path b Dir) (Path Rel t) where
type FileResultT (Path b Dir) (Path Rel t) = (Path b t)
addFileName :: Path b Dir -> Path Rel t -> FileResultT (Path b Dir) (Path Rel t)
addFileName Path b Dir
p Path Rel t
d = forall b t. Path b Dir -> Path Rel t -> Path b t
(Path.</>) (forall a. a -> a
unPath Path b Dir
p) (forall a. a -> a
unPath Path Rel t
d)
instance Filenames1 (Path ar File) where
getNakedFileName :: Path ar File -> FilePath
getNakedFileName = forall fp. Filenames1 fp => fp -> FilePath
getNakedFileName forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall df ar. Path df ar -> FilePath
toFilePath
getImmediateParentDir :: Path ar File -> FilePath
getImmediateParentDir = forall fp. Filenames1 fp => fp -> FilePath
getImmediateParentDir forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall df ar. Path df ar -> FilePath
toFilePath
getParentDir :: Path ar File -> FilePath
getParentDir = forall fp. Filenames1 fp => fp -> FilePath
getParentDir forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall df ar. Path df ar -> FilePath
toFilePath
getNakedDir :: Path ar File -> FilePath
getNakedDir = forall a. Partial => FilePath -> a
error FilePath
"getNakedDir for Filenamse1 Path ar File) not existing"
instance Filenames1 (Path ar Dir) where
getNakedFileName :: Path ar Dir -> FilePath
getNakedFileName = forall a. Partial => FilePath -> a
error FilePath
"getNakedFileName not from Dir"
getImmediateParentDir :: Path ar Dir -> FilePath
getImmediateParentDir = forall fp. Filenames1 fp => fp -> FilePath
getImmediateParentDir forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall df ar. Path df ar -> FilePath
toFilePath
getParentDir :: Path ar Dir -> FilePath
getParentDir = forall fp. Filenames1 fp => fp -> FilePath
getParentDir forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall df ar. Path df ar -> FilePath
toFilePath
getNakedDir :: Path ar Dir -> FilePath
getNakedDir = forall fp. Filenames1 fp => fp -> FilePath
getNakedDir forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall df ar. Path df ar -> FilePath
toFilePath
instance Filenames1 FilePath where
getNakedFileName :: FilePath -> FilePath
getNakedFileName = forall fp. Extensions fp => fp -> fp
removeExtension forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall fp fr. Filenames fp fr => fp -> fr
getFileName
getImmediateParentDir :: FilePath -> FilePath
getImmediateParentDir = (forall a. [a] -> Int -> a
!! Int
1) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> [FilePath]
S.splitDirectories
getParentDir :: FilePath -> FilePath
getParentDir = FilePath -> FilePath
S.takeDirectory
getNakedDir :: FilePath -> FilePath
getNakedDir = (forall a. [a] -> Int -> a
!! Int
0) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> [FilePath]
S.splitDirectories
class (Eq (ExtensionType fp)) => Extensions fp where
type ExtensionType fp
getExtension :: fp -> ExtensionType fp
removeExtension :: fp -> fp
addExtension :: ExtensionType fp -> fp -> fp
(<.>) :: fp -> ExtensionType fp -> fp
(<.>) fp
f ExtensionType fp
e = forall fp. Extensions fp => ExtensionType fp -> fp -> fp
addExtension ExtensionType fp
e fp
f
setExtension :: ExtensionType fp -> fp -> fp
setExtension ExtensionType fp
ext = forall fp. Extensions fp => ExtensionType fp -> fp -> fp
addExtension ExtensionType fp
ext forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall fp. Extensions fp => fp -> fp
removeExtension
hasExtension :: ExtensionType fp -> fp -> Bool
hasExtension ExtensionType fp
e = (ExtensionType fp
e forall a. Eq a => a -> a -> Bool
==) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall fp. Extensions fp => fp -> ExtensionType fp
getExtension
prop_add_has :: ExtensionType fp -> fp -> Bool
prop_add_has ExtensionType fp
e fp
f = forall fp. Extensions fp => ExtensionType fp -> fp -> Bool
hasExtension ExtensionType fp
e (forall fp. Extensions fp => ExtensionType fp -> fp -> fp
addExtension ExtensionType fp
e fp
f)
prop_add_add_has :: ExtensionType fp -> ExtensionType fp -> fp -> Bool
prop_add_add_has ExtensionType fp
e1 ExtensionType fp
e2 fp
f =
forall fp. Extensions fp => ExtensionType fp -> fp -> Bool
hasExtension
ExtensionType fp
e1
(forall fp. Extensions fp => ExtensionType fp -> fp -> fp
setExtension ExtensionType fp
e1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall fp. Extensions fp => ExtensionType fp -> fp -> fp
setExtension ExtensionType fp
e2 forall a b. (a -> b) -> a -> b
$ fp
f)
prop_set_get :: ExtensionType fp -> fp -> Bool
prop_set_get ExtensionType fp
e fp
f = ((ExtensionType fp
e forall a. Eq a => a -> a -> Bool
==) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall fp. Extensions fp => fp -> ExtensionType fp
getExtension) (forall fp. Extensions fp => ExtensionType fp -> fp -> fp
setExtension ExtensionType fp
e fp
f)
instance Extensions FilePath where
type ExtensionType FilePath = FilePath
getExtension :: FilePath -> ExtensionType FilePath
getExtension = forall a. CharChains a => Char -> a -> a
removeChar Char
'.' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (FilePath, FilePath)
S.splitExtension
addExtension :: ExtensionType FilePath -> FilePath -> FilePath
addExtension ExtensionType FilePath
e FilePath
fp = FilePath
fp FilePath -> FilePath -> FilePath
S.<.> ExtensionType FilePath
e
removeExtension :: FilePath -> FilePath
removeExtension = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (FilePath, FilePath)
S.splitExtension
instance Extensions (Path ar File) where
type ExtensionType (Path ar File) = Extension
getExtension :: Path ar File -> ExtensionType (Path ar File)
getExtension Path ar File
f = FilePath -> Extension
Extension FilePath
e
where
e :: FilePath
e = forall fp. Extensions fp => fp -> ExtensionType fp
getExtension forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall df ar. Path df ar -> FilePath
toFilePath forall a b. (a -> b) -> a -> b
$ Path ar File
f
setExtension :: ExtensionType (Path ar File) -> Path ar File -> Path ar File
setExtension ExtensionType (Path ar File)
e Path ar File
f =
forall a. Partial => FilePath -> Maybe a -> a
fromJustNote FilePath
"setExtension" forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) b.
MonadThrow m =>
FilePath -> Path b File -> m (Path b File)
Path.setFileExtension (Extension -> FilePath
unExtension ExtensionType (Path ar File)
e) Path ar File
f
addExtension :: ExtensionType (Path ar File) -> Path ar File -> Path ar File
addExtension = forall fp. Extensions fp => ExtensionType fp -> fp -> fp
setExtension
removeExtension :: Path ar File -> Path ar File
removeExtension = forall fp. Extensions fp => ExtensionType fp -> fp -> fp
setExtension (FilePath -> Extension
Extension FilePath
"")