Copyright | © 2016 All rights reserved. |
---|---|
License | GPL-3 |
Maintainer | Evan Cofsky <> |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
- addExtension :: FilePath os ar -> String -> FilePath os ar
- combine :: DirPath os ar -> RelPath os fd -> Path os ar fd
- currentDir :: RelDir
- dropExtension :: FilePath os ar -> FilePath os ar
- dropExtensions :: FilePath os ar -> FilePath os ar
- dropFileName :: FilePath os ar -> DirPath os ar
- emptyFile :: RelFile
- mapFileName :: (String -> String) -> FilePath os ar -> FilePath os ar
- mapFileNameF :: Functor f => (String -> f String) -> FilePath os ar -> f (FilePath os ar)
- replaceBaseName :: FilePath os ar -> String -> FilePath os ar
- replaceDirectory :: FilePath os ar1 -> DirPath os ar2 -> FilePath os ar2
- replaceExtension :: FilePath os ar -> String -> FilePath os ar
- replaceFileName :: FilePath os ar -> String -> FilePath os ar
- rootDir :: AbsDir
- splitDirName :: DirPath os ar -> Maybe (DirPath os ar, RelDir os)
- splitExtension :: FilePath os ar -> (FilePath os ar, String)
- splitExtensions :: FilePath os ar -> (FilePath os ar, String)
- splitFileName :: FilePath os ar -> (DirPath os ar, RelFile os)
- splitPath :: (AbsRel ar, FileOrDir fd) => Path os ar fd -> (Bool, [RelDir os], Maybe (RelFile os))
- takeBaseName :: FilePath os ar -> RelFile os
- takeDirName :: DirPath os ar -> Maybe (RelDir os)
- takeDirectory :: FilePath os ar -> DirPath os ar
- takeExtension :: FilePath os ar -> String
- takeExtensions :: FilePath os ar -> String
- takeFileName :: FilePath os ar -> RelFile os
- takeSuperDirectory :: DirPath os ar -> Maybe (DirPath os ar)
- toString :: (AbsRel ar, FileDir fd) => Path ar fd -> String
- dirFromFile :: FilePath os ar -> DirPath os ar
- dirFromFileDir :: FileDirPath os ar -> DirPath os ar
- dynamicMakeAbsolute :: System os => AbsDir os -> AbsRelPath os fd -> AbsPath os fd
- dynamicMakeAbsoluteFromCwd :: System os => AbsRelPath os fd -> IO (AbsPath os fd)
- equalFilePath :: String -> String -> Bool
- fileFromDir :: DirPath os ar -> Maybe (FilePath os ar)
- fileFromFileDir :: FileDirPath os ar -> Maybe (FilePath os ar)
- fromFileDir :: FileDir fd => FileDirPath os ar -> Maybe (Path os ar fd)
- genericMakeAbsolute :: (System os, AbsRel ar) => AbsDir os -> Path os ar fd -> AbsPath os fd
- genericMakeAbsoluteFromCwd :: (System os, AbsRel ar) => Path os ar fd -> IO (AbsPath os fd)
- joinPath :: FileDir fd => [String] -> RelPath os fd
- makeAbsolute :: System os => AbsDir os -> RelPath os fd -> AbsPath os fd
- makeAbsoluteFromCwd :: System os => RelPath os fd -> IO (AbsPath os fd)
- makeRelative :: (System os, FileDir fd) => AbsDir os -> AbsPath os fd -> RelPath os fd
- makeRelativeMaybe :: (System os, FileDir fd) => AbsDir os -> AbsPath os fd -> Maybe (RelPath os fd)
- normalise :: System os => Path os ar fd -> Path os ar fd
- pathMap :: FileDir fd => (String -> String) -> Path os ar fd -> Path os ar fd
- toFileDir :: FileDir fd => Path os ar fd -> FileDirPath os ar
- isAbsolute :: AbsRel ar => Path os ar fd -> Bool
- isRelative :: AbsRel ar => Path os ar fd -> Bool
- isAbsoluteString :: String -> Bool
- isRelativeString :: String -> Bool
- hasAnExtension :: FilePath os ar -> Bool
- hasExtension :: String -> FilePath os ar -> Bool
- extSeparator :: Char
- searchPathSeparator :: Char
- isExtSeparator :: Char -> Bool
- isSearchPathSeparator :: Char -> Bool
- genericAddExtension :: FileDir fd => Path os ar fd -> String -> Path os ar fd
- genericDropExtension :: FileDir fd => Path os ar fd -> Path os ar fd
- genericDropExtensions :: FileDir fd => Path os ar fd -> Path os ar fd
- genericSplitExtension :: FileDir fd => Path os ar fd -> (Path os ar fd, String)
- genericSplitExtensions :: FileDir fd => Path os ar fd -> (Path os ar fd, String)
- genericTakeExtension :: FileDir fd => Path os ar fd -> String
- genericTakeExtensions :: FileDir fd => Path os ar fd -> String
- parse :: (AbsRel ar, FileDir fd) => String -> Either String (Path ar fd)
- toText :: (AbsRel ar, FileDir fd) => Path ar fd -> Text
- type AbsFile = AbsFile System
- type RelFile = RelFile System
- type AbsDir = AbsDir System
- type RelDir = RelDir System
- type AbsRelFile = AbsRelFile System
- type AbsRelDir = AbsRelDir System
- type File ar = File System ar
- absFile :: IsText t => t -> AbsFile
- relFile :: IsText t => t -> RelFile
- absDir :: IsText t => t -> AbsDir
- relDir :: IsText t => t -> RelDir
- absRelFile :: IsText t => t -> AbsRelFile
- absRelDir :: IsText t => t -> AbsRelDir
- (</>) :: DirPath os ar -> RelPath os fd -> Path os ar fd
- (<.>) :: FilePath os ar -> String -> FilePath os ar
- (<++>) :: FilePath os ar -> String -> FilePath os ar
Documentation
addExtension :: FilePath os ar -> String -> FilePath os ar #
currentDir :: RelDir #
dropExtension :: FilePath os ar -> FilePath os ar #
dropExtensions :: FilePath os ar -> FilePath os ar #
dropFileName :: FilePath os ar -> DirPath os ar #
mapFileName :: (String -> String) -> FilePath os ar -> FilePath os ar #
mapFileNameF :: Functor f => (String -> f String) -> FilePath os ar -> f (FilePath os ar) #
replaceBaseName :: FilePath os ar -> String -> FilePath os ar #
replaceDirectory :: FilePath os ar1 -> DirPath os ar2 -> FilePath os ar2 #
replaceExtension :: FilePath os ar -> String -> FilePath os ar #
replaceFileName :: FilePath os ar -> String -> FilePath os ar #
splitDirName :: DirPath os ar -> Maybe (DirPath os ar, RelDir os) #
splitExtension :: FilePath os ar -> (FilePath os ar, String) #
splitExtensions :: FilePath os ar -> (FilePath os ar, String) #
splitFileName :: FilePath os ar -> (DirPath os ar, RelFile os) #
splitPath :: (AbsRel ar, FileOrDir fd) => Path os ar fd -> (Bool, [RelDir os], Maybe (RelFile os)) #
takeBaseName :: FilePath os ar -> RelFile os #
takeDirName :: DirPath os ar -> Maybe (RelDir os) #
takeDirectory :: FilePath os ar -> DirPath os ar #
takeExtension :: FilePath os ar -> String #
takeExtensions :: FilePath os ar -> String #
takeFileName :: FilePath os ar -> RelFile os #
takeSuperDirectory :: DirPath os ar -> Maybe (DirPath os ar) #
Auxillary Manipulation Functions
dirFromFile :: FilePath os ar -> DirPath os ar #
dirFromFileDir :: FileDirPath os ar -> DirPath os ar #
dynamicMakeAbsolute :: System os => AbsDir os -> AbsRelPath os fd -> AbsPath os fd #
dynamicMakeAbsoluteFromCwd :: System os => AbsRelPath os fd -> IO (AbsPath os fd) #
equalFilePath :: String -> String -> Bool #
fileFromDir :: DirPath os ar -> Maybe (FilePath os ar) #
fileFromFileDir :: FileDirPath os ar -> Maybe (FilePath os ar) #
fromFileDir :: FileDir fd => FileDirPath os ar -> Maybe (Path os ar fd) #
genericMakeAbsolute :: (System os, AbsRel ar) => AbsDir os -> Path os ar fd -> AbsPath os fd #
genericMakeAbsoluteFromCwd :: (System os, AbsRel ar) => Path os ar fd -> IO (AbsPath os fd) #
makeAbsolute :: System os => AbsDir os -> RelPath os fd -> AbsPath os fd #
makeAbsoluteFromCwd :: System os => RelPath os fd -> IO (AbsPath os fd) #
makeRelative :: (System os, FileDir fd) => AbsDir os -> AbsPath os fd -> RelPath os fd #
makeRelativeMaybe :: (System os, FileDir fd) => AbsDir os -> AbsPath os fd -> Maybe (RelPath os fd) #
Path Predicates
isAbsolute :: AbsRel ar => Path os ar fd -> Bool #
isRelative :: AbsRel ar => Path os ar fd -> Bool #
isAbsoluteString :: String -> Bool #
isRelativeString :: String -> Bool #
hasAnExtension :: FilePath os ar -> Bool #
hasExtension :: String -> FilePath os ar -> Bool #
Separators
extSeparator :: Char #
isExtSeparator :: Char -> Bool #
isSearchPathSeparator :: Char -> Bool #
Generic Manipulation Functions
genericAddExtension :: FileDir fd => Path os ar fd -> String -> Path os ar fd #
genericDropExtension :: FileDir fd => Path os ar fd -> Path os ar fd #
genericDropExtensions :: FileDir fd => Path os ar fd -> Path os ar fd #
genericSplitExtension :: FileDir fd => Path os ar fd -> (Path os ar fd, String) #
genericSplitExtensions :: FileDir fd => Path os ar fd -> (Path os ar fd, String) #
genericTakeExtension :: FileDir fd => Path os ar fd -> String #
genericTakeExtensions :: FileDir fd => Path os ar fd -> String #
type AbsRelFile = AbsRelFile System #
absRelFile :: IsText t => t -> AbsRelFile Source #