Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Library for manipulating a more structured version of FilePath. Note: the library should use System.FilePath functionality but does not do so yet.
- data FPath = FPath {
- fpathMbDir :: !(Maybe FilePath)
- fpathBase :: !String
- fpathMbSuff :: !(Maybe String)
- fpathSuff :: FPath -> String
- class FPATH f where
- class FPathError e
- emptyFPath :: FPath
- fpathFromStr :: FilePath -> FPath
- mkFPathFromDirsFile :: Show s => [s] -> s -> FPath
- fpathToStr :: FPath -> FilePath
- fpathIsEmpty :: FPath -> Bool
- fpathSetBase :: String -> FPath -> FPath
- fpathSetSuff :: String -> FPath -> FPath
- fpathSetDir :: FilePath -> FPath -> FPath
- fpathUpdBase :: (String -> String) -> FPath -> FPath
- fpathRemoveSuff :: FPath -> FPath
- fpathRemoveDir :: FPath -> FPath
- fpathIsAbsolute :: FPath -> Bool
- fpathAppendDir :: FPath -> FilePath -> FPath
- fpathUnAppendDir :: FPath -> FilePath -> FPath
- fpathPrependDir :: FilePath -> FPath -> FPath
- fpathUnPrependDir :: FilePath -> FPath -> FPath
- fpathSplitDirBy :: FilePath -> FPath -> Maybe (String, String)
- mkTopLevelFPath :: String -> FilePath -> FPath
- type SearchPath = [String]
- type FileSuffixes = [FileSuffix]
- type FileSuffixesWith x = [FileSuffixWith x]
- type FileSuffix = Maybe String
- type FileSuffixWith x = (Maybe String, x)
- mkInitSearchPath :: FPath -> SearchPath
- searchPathFromFPath :: FPath -> SearchPath
- searchPathFromFPaths :: [FPath] -> SearchPath
- searchPathFromString :: String -> [String]
- searchFPathFromLoc :: FilePath -> FPath -> [(FilePath, FPath)]
- searchLocationsForReadableFilesWith :: (loc -> FPath -> [(loc, FPath, [e])]) -> Bool -> [loc] -> FileSuffixesWith s -> FPath -> IO [(FPath, loc, s, [e])]
- searchLocationsForReadableFiles :: (loc -> FPath -> [(loc, FPath, [e])]) -> Bool -> [loc] -> FileSuffixes -> FPath -> IO [(FPath, loc, [e])]
- searchPathForReadableFiles :: Bool -> SearchPath -> FileSuffixes -> FPath -> IO [FPath]
- searchPathForReadableFile :: SearchPath -> FileSuffixes -> FPath -> IO (Maybe FPath)
- fpathEnsureExists :: FPath -> IO ()
- filePathMkPrefix :: FilePath -> FilePath
- filePathUnPrefix :: FilePath -> FilePath
- filePathCoalesceSeparator :: FilePath -> FilePath
- filePathMkAbsolute :: FilePath -> FilePath
- filePathUnAbsolute :: FilePath -> FilePath
- fpathGetModificationTime :: FPath -> IO UTCTime
- fpathDirSep :: String
- fpathDirSepChar :: Char
- fpathOpenOrStdin :: FPath -> IO (FPath, Handle)
- openFPath :: FPath -> IOMode -> Bool -> IO (String, Handle)
FPath datatype, FPATH class for overloaded construction
File path representation making explicit (possible) directory, base and (possible) suffix
FPath | |
|
Construct a FPath from some type
emptyFPath :: FPath Source #
Empty FPath
Construction, deconstruction, predicates
fpathFromStr :: FilePath -> FPath Source #
Construct FPath from FilePath
mkFPathFromDirsFile :: Show s => [s] -> s -> FPath Source #
fpathToStr :: FPath -> FilePath Source #
Conversion to FilePath
fpathIsEmpty :: FPath -> Bool Source #
Is FPath empty?
fpathRemoveSuff :: FPath -> FPath Source #
Remove suffix
fpathRemoveDir :: FPath -> FPath Source #
Remove dir
fpathIsAbsolute :: FPath -> Bool Source #
fpathUnAppendDir :: FPath -> FilePath -> FPath Source #
Remove common trailing part of dir. Note: does not check whether it really is a suffix.
fpathUnPrependDir :: FilePath -> FPath -> FPath Source #
Remove directory (prefix), using fpathSplitDirBy
fpathSplitDirBy :: FilePath -> FPath -> Maybe (String, String) Source #
Split FPath into given directory (prefix) and remainder, fails if not a prefix
Make FPath from FilePath, setting the suffix when absent
SearchPath
type SearchPath = [String] Source #
type FileSuffixes = [FileSuffix] Source #
type FileSuffixesWith x = [FileSuffixWith x] Source #
FileSuffix with extra payload
type FileSuffix = Maybe String Source #
type FileSuffixWith x = (Maybe String, x) Source #
FileSuffix with extra payload
mkInitSearchPath :: FPath -> SearchPath Source #
searchPathFromFPaths :: [FPath] -> SearchPath Source #
searchPathFromString :: String -> [String] Source #
searchLocationsForReadableFilesWith Source #
:: (loc -> FPath -> [(loc, FPath, [e])]) | get the locations for a name, possibly with errors |
-> Bool | stop when first is found |
-> [loc] | locations to search |
-> FileSuffixesWith s | suffixes to try, with associated info |
-> FPath | search for a path |
-> IO [(FPath, loc, s, [e])] |
Search for file in locations, with possible suffices
searchLocationsForReadableFiles Source #
:: (loc -> FPath -> [(loc, FPath, [e])]) | get the locations for a name, possibly with errors |
-> Bool | stop when first is found |
-> [loc] | locations to search |
-> FileSuffixes | suffixes to try |
-> FPath | search for a path |
-> IO [(FPath, loc, [e])] |
Search for file in locations, with possible suffices
searchPathForReadableFiles :: Bool -> SearchPath -> FileSuffixes -> FPath -> IO [FPath] Source #
searchPathForReadableFile :: SearchPath -> FileSuffixes -> FPath -> IO (Maybe FPath) Source #
fpathEnsureExists :: FPath -> IO () Source #
Path as prefix
filePathMkPrefix :: FilePath -> FilePath Source #
Construct a filepath to be a prefix (i.e. ending with /
as last char)
filePathUnPrefix :: FilePath -> FilePath Source #
Remove from a filepath a possibly present /
as last char
filePathMkAbsolute :: FilePath -> FilePath Source #
Make a filepath an absolute filepath by prefixing with /
filePathUnAbsolute :: FilePath -> FilePath Source #
Make a filepath an relative filepath by removing prefixed /
-s
Misc
fpathDirSep :: String Source #