system-filepath-0.4.14.1: High-level, byte-based file and directory path manipulations (deprecated)
Copyright2010 John Millikin
LicenseMIT
Maintainerjmillikin@gmail.com
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Filesystem.Path

Description

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

Documentation

data FilePath Source #

Instances

Instances details
NFData FilePath Source # 
Instance details

Defined in Filesystem.Path.Internal

Methods

rnf :: FilePath -> ()

Monoid FilePath 
Instance details

Defined in Filesystem.Path

Semigroup FilePath 
Instance details

Defined in Filesystem.Path

Methods

(<>) :: FilePath -> FilePath -> FilePath

sconcat :: NonEmpty FilePath -> FilePath

stimes :: Integral b => b -> FilePath -> FilePath

Data FilePath Source # 
Instance details

Defined in Filesystem.Path.Internal

Methods

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 
Instance details

Defined in Filesystem.Path.CurrentOS

Methods

fromString :: String -> FilePath

Show FilePath 
Instance details

Defined in Filesystem.Path.CurrentOS

Methods

showsPrec :: Int -> FilePath -> ShowS

show :: FilePath -> String

showList :: [FilePath] -> ShowS

Eq FilePath Source # 
Instance details

Defined in Filesystem.Path.Internal

Methods

(==) :: FilePath -> FilePath -> Bool

(/=) :: FilePath -> FilePath -> Bool

Ord FilePath Source # 
Instance details

Defined in Filesystem.Path.Internal

Methods

compare :: FilePath -> FilePath -> Ordering

(<) :: FilePath -> FilePath -> Bool

(<=) :: FilePath -> FilePath -> Bool

(>) :: FilePath -> FilePath -> Bool

(>=) :: FilePath -> FilePath -> Bool

max :: FilePath -> FilePath -> FilePath

min :: FilePath -> FilePath -> FilePath

empty :: FilePath Source #

A file path with no root, directory, or filename

Basic properties

null :: FilePath -> Bool Source #

null p = (p == empty)

root :: FilePath -> FilePath Source #

Retrieves the FilePath’s root.

directory :: FilePath -> FilePath Source #

Retrieves the FilePath’s directory. If the path is already a directory, it is returned unchanged.

parent :: FilePath -> FilePath Source #

Retrieves the FilePath’s parent directory.

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"

absolute :: FilePath -> Bool Source #

Test whether a path is absolute.

relative :: FilePath -> Bool Source #

Test whether a path is relative.

Basic operations

append :: FilePath -> FilePath -> FilePath Source #

Appends two FilePaths. If the second path is absolute, it is returned unchanged.

(</>) :: FilePath -> FilePath -> FilePath Source #

An alias for append.

concat :: [FilePath] -> FilePath Source #

A fold over append.

commonPrefix :: [FilePath] -> FilePath Source #

Find the greatest common prefix between a list of FilePaths.

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" == Nothing
stripPrefix "/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.

addExtension :: FilePath -> Text -> FilePath Source #

Append an extension to the end of a FilePath.

(<.>) :: FilePath -> Text -> FilePath Source #

An alias for addExtension.

dropExtension :: FilePath -> FilePath Source #

Remove a FilePath’s last extension.

replaceExtension :: FilePath -> Text -> FilePath Source #

Replace a FilePath’s last extension.

addExtensions :: FilePath -> [Text] -> FilePath Source #

Append many extensions to the end of a FilePath.

dropExtensions :: FilePath -> FilePath Source #

Remove all extensions from 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)

Orphan instances

Monoid FilePath Source # 
Instance details

Semigroup FilePath Source # 
Instance details

Methods

(<>) :: FilePath -> FilePath -> FilePath

sconcat :: NonEmpty FilePath -> FilePath

stimes :: Integral b => b -> FilePath -> FilePath