Copyright | 2010 John Millikin |
---|---|
License | MIT |
Maintainer | jmillikin@gmail.com |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
High‐level, byte‐based file and directory path manipulations. You probably want to import Filesystem.Path.CurrentOS instead, since it handles detecting which rules to use in the current compilation.
Synopsis
- data FilePath
- empty :: FilePath
- null :: FilePath -> Bool
- root :: FilePath -> FilePath
- directory :: FilePath -> FilePath
- parent :: FilePath -> FilePath
- filename :: FilePath -> FilePath
- dirname :: FilePath -> FilePath
- basename :: FilePath -> FilePath
- absolute :: FilePath -> Bool
- relative :: FilePath -> Bool
- append :: FilePath -> FilePath -> FilePath
- (</>) :: FilePath -> FilePath -> FilePath
- concat :: [FilePath] -> FilePath
- commonPrefix :: [FilePath] -> FilePath
- stripPrefix :: FilePath -> FilePath -> Maybe FilePath
- collapse :: FilePath -> FilePath
- splitDirectories :: FilePath -> [FilePath]
- extension :: FilePath -> Maybe Text
- extensions :: FilePath -> [Text]
- hasExtension :: FilePath -> Text -> Bool
- addExtension :: FilePath -> Text -> FilePath
- (<.>) :: FilePath -> Text -> FilePath
- dropExtension :: FilePath -> FilePath
- replaceExtension :: FilePath -> Text -> FilePath
- addExtensions :: FilePath -> [Text] -> FilePath
- dropExtensions :: FilePath -> FilePath
- replaceExtensions :: FilePath -> [Text] -> FilePath
- splitExtension :: FilePath -> (FilePath, Maybe Text)
- splitExtensions :: FilePath -> (FilePath, [Text])
Documentation
Instances
NFData FilePath Source # | |
Defined in Filesystem.Path.Internal | |
Monoid FilePath | |
Semigroup FilePath | |
Data FilePath Source # | |
Defined in Filesystem.Path.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FilePath -> c FilePath gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FilePath toConstr :: FilePath -> Constr dataTypeOf :: FilePath -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FilePath) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FilePath) gmapT :: (forall b. Data b => b -> b) -> FilePath -> FilePath gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FilePath -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FilePath -> r gmapQ :: (forall d. Data d => d -> u) -> FilePath -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> FilePath -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> FilePath -> m FilePath gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FilePath -> m FilePath gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FilePath -> m FilePath | |
IsString FilePath | |
Defined in Filesystem.Path.CurrentOS fromString :: String -> FilePath | |
Show FilePath | |
Eq FilePath Source # | |
Ord FilePath Source # | |
Basic properties
directory :: FilePath -> FilePath Source #
Retrieves the FilePath
’s directory. If the path is already a
directory, it is returned unchanged.
filename :: FilePath -> FilePath Source #
Retrieve a FilePath
’s filename component.
filename "foo/bar.txt" == "bar.txt"
dirname :: FilePath -> FilePath Source #
Retrieve a FilePath
’s directory name. This is only the
file name of the directory, not its full path.
dirname "foo/bar/baz.txt" == "bar" dirname "/" == ""
Since: 0.4.1
basename :: FilePath -> FilePath Source #
Retrieve a FilePath
’s basename component.
basename "foo/bar.txt" == "bar"
Basic operations
append :: FilePath -> FilePath -> FilePath Source #
Appends two FilePath
s. If the second path is absolute, it is returned
unchanged.
commonPrefix :: [FilePath] -> FilePath Source #
Find the greatest common prefix between a list of FilePath
s.
stripPrefix :: FilePath -> FilePath -> Maybe FilePath Source #
Remove a prefix from a path.
stripPrefix
"/foo/" "/foo/bar/baz.txt" == Just "bar/baz.txt"stripPrefix
"/foo/" "/bar/baz.txt" == Nothing
This function operates on logical prefixes, rather than by counting
characters. The prefix "/foo/bar/baz"
is interpreted the path
("/foo/bar/", "baz")
, and will be stripped accordingly:
stripPrefix
"/foo/bar/baz" "/foo/bar/baz/qux" == NothingstripPrefix
"/foo/bar/baz" "/foo/bar/baz.txt" == Just ".txt"
Since: 0.4.1
collapse :: FilePath -> FilePath Source #
Remove intermediate "."
and ".."
directories from a path.
collapse
"/foo/./bar" == "/foo/bar"collapse
"/foo/bar/../baz" == "/foo/baz"collapse
"/foo/../../bar" == "/bar"collapse
"./foo/bar" == "./foo/baz"
Note that if any of the elements are symbolic links, collapse
may change
which file the path resolves to.
Since: 0.2
splitDirectories :: FilePath -> [FilePath] Source #
expand a FilePath into a list of the root name, directories, and file name
Since: 0.4.7
Extensions
extension :: FilePath -> Maybe Text Source #
Get a FilePath
’s last extension, or Nothing
if it has no
extensions.
extensions :: FilePath -> [Text] Source #
Get a FilePath
’s full extension list.
hasExtension :: FilePath -> Text -> Bool Source #
Get whether a FilePath
’s last extension is the predicate.
addExtensions :: FilePath -> [Text] -> FilePath Source #
Append many extensions to the end of a FilePath
.
replaceExtensions :: FilePath -> [Text] -> FilePath Source #
Remove all extensions from a FilePath
, and replace them with a new
list.
splitExtension :: FilePath -> (FilePath, Maybe Text) Source #
splitExtension p = (dropExtension
p,extension
p)
splitExtensions :: FilePath -> (FilePath, [Text]) Source #
splitExtensions p = (dropExtensions
p,extensions
p)