module System.Path.Windows (
Path,
AbsFile, RelFile, AbsDir, RelDir,
Abs, Rel, File, Dir,
AbsRelFile, AbsRelDir, AbsFileDir, RelFileDir,
AbsRel, FileDir, AbsRelFileDir,
AbsPath, RelPath, FilePath, DirPath,
AbsRelPath, FileDirPath,
asPath,
asRelFile, asRelDir, asAbsFile, asAbsDir,
asRelPath, asAbsPath, asFilePath, asDirPath,
path, maybe, maybePath, parse, parsePath,
relFile, relDir, absFile, absDir,
abs, rel, absRel, file, dir, fileDir,
relPath, absPath, filePath, dirPath,
rootDir, currentDir, emptyFile,
toString,
isAbsoluteString, isRelativeString, equalFilePath,
pathSeparator, pathSeparators, isPathSeparator,
Core.extSeparator, Core.isExtSeparator,
Core.searchPathSeparator, Core.isSearchPathSeparator,
addTrailingPathSeparator, dropTrailingPathSeparator,
hasTrailingPathSeparator,
testAll,
) where
import qualified System.Path.RegularExpression as RegEx
import qualified System.Path.Internal.PartClass as Class
import qualified System.Path.Internal as Core
import System.Path.RegularExpression ((-|-))
import Data.Tagged (Tagged(Tagged), untag)
import Data.Char (isAlpha, toLower)
import Data.Monoid (mempty, (<>))
import qualified Test.QuickCheck as QC
import Prelude hiding (FilePath, maybe, abs)
data Windows = Windows
_osDummy :: Windows
_osDummy = Windows
type System = Windows
type Path = Core.Path System
type AbsFile = Core.AbsFile System
type RelFile = Core.RelFile System
type AbsDir = Core.AbsDir System
type RelDir = Core.RelDir System
type AbsRelFile = Core.AbsRelFile System
type AbsRelDir = Core.AbsRelDir System
type AbsFileDir = Core.AbsFileDir System
type RelFileDir = Core.RelFileDir System
type AbsRelFileDir = Core.AbsRelFileDir System
type Abs fd = Core.Abs System fd
type Rel fd = Core.Rel System fd
type File ar = Core.File System ar
type Dir ar = Core.Dir System ar
type AbsRel fd = Core.AbsRel System fd
type FileDir ar = Core.FileDir System ar
type AbsPath fd = Core.AbsPath System fd
type RelPath fd = Core.RelPath System fd
type FilePath ar = Core.FilePath System ar
type DirPath ar = Core.DirPath System ar
type AbsRelPath fd = Core.AbsRelPath System fd
type FileDirPath ar = Core.FileDirPath System ar
asPath :: (Class.AbsOrRel ar, Class.FileOrDir fd) => String -> Path ar fd
asPath = Core.asPath
asRelFile :: String -> RelFile
asRelFile = Core.asRelFile
asRelDir :: String -> RelDir
asRelDir = Core.asRelDir
asAbsFile :: String -> AbsFile
asAbsFile = Core.asAbsFile
asAbsDir :: String -> AbsDir
asAbsDir = Core.asAbsDir
asRelPath :: (Class.FileOrDir fd) => String -> RelPath fd
asRelPath = Core.asRelPath
asAbsPath :: (Class.FileOrDir fd) => String -> AbsPath fd
asAbsPath = Core.asAbsPath
asFilePath :: (Class.AbsOrRel ar) => String -> FilePath ar
asFilePath = Core.asFilePath
asDirPath :: (Class.AbsOrRel ar) => String -> DirPath ar
asDirPath = Core.asDirPath
maybe, maybePath ::
(Class.AbsRel ar, Class.FileDir fd) => String -> Maybe (Path ar fd)
maybe = Core.maybe
maybePath = Core.maybe
parse, parsePath ::
(Class.AbsRel ar, Class.FileDir fd) => String -> Either String (Path ar fd)
parse = Core.parse
parsePath = Core.parse
path :: (Class.AbsRel ar, Class.FileDir fd) => String -> Path ar fd
path = Core.path
relFile :: String -> RelFile
relFile = Core.relFile
relDir :: String -> RelDir
relDir = Core.relDir
absFile :: String -> AbsFile
absFile = Core.absFile
absDir :: String -> AbsDir
absDir = Core.absDir
rel :: (Class.FileDir fd) => String -> Rel fd
rel = Core.rel
abs :: (Class.FileDir fd) => String -> Abs fd
abs = Core.abs
absRel :: (Class.FileDir fd) => String -> AbsRel fd
absRel = Core.absRel
file :: (Class.AbsRel ar) => String -> File ar
file = Core.file
dir :: (Class.AbsRel ar) => String -> Dir ar
dir = Core.dir
fileDir :: (Class.AbsRel ar) => String -> FileDir ar
fileDir = Core.fileDir
relPath :: (Class.FileDir fd) => String -> RelPath fd
relPath = Core.relPath
absPath :: (Class.FileDir fd) => String -> AbsPath fd
absPath = Core.absPath
filePath :: (Class.AbsRel ar) => String -> FilePath ar
filePath = Core.filePath
dirPath :: (Class.AbsRel ar) => String -> DirPath ar
dirPath = Core.dirPath
rootDir :: AbsDir
rootDir = Core.rootDir
currentDir :: RelDir
currentDir = Core.currentDir
emptyFile :: RelFile
emptyFile = Core.emptyFile
toString :: (Class.AbsRel ar, Class.FileDir fd) => Path ar fd -> String
toString = Core.toString
instance Core.System Windows where
pathSeparator = Tagged pathSeparator
splitAbsolute = Tagged $ RegEx.run $
RegEx.single isPathSeparator
-|-
driveRegEx <> (RegEx.single isPathSeparator -|- mempty)
canonicalize = Tagged $ map toLower
splitDrive = Tagged $ RegEx.run driveRegEx
genDrive = Tagged $ fmap (:":") $ QC.choose ('a', 'z')
driveRegEx :: RegEx.Parser Char
driveRegEx = RegEx.single isAlpha <> RegEx.single (':'==)
withOS :: Tagged System a -> a
withOS = untag
equalFilePath :: String -> String -> Bool
equalFilePath = withOS Core.equalFilePath
isAbsoluteString :: String -> Bool
isAbsoluteString = withOS Core.isAbsoluteString
isRelativeString :: String -> Bool
isRelativeString = withOS Core.isRelativeString
pathSeparator :: Char
pathSeparator = '\\'
pathSeparators :: [Char]
pathSeparators = withOS Core.pathSeparators
isPathSeparator :: Char -> Bool
isPathSeparator = withOS Core.isPathSeparator
addTrailingPathSeparator :: String -> String
addTrailingPathSeparator = (++[pathSeparator])
dropTrailingPathSeparator :: String -> String
dropTrailingPathSeparator = init
hasTrailingPathSeparator :: String -> Bool
hasTrailingPathSeparator = isPathSeparator . last
testAll :: [(String, IO ())]
testAll = Core.testAll Windows