Glob-0.5.1: Globbing library

System.FilePath.Glob

Contents

Description

A library for globbing: matching patterns against file paths.

Basic usage: match (compile pattern) filepath.

Basic usage in IO: globDir [compile pattern] directory.

Synopsis

Data type

data Pattern Source

An abstract data type representing a compiled pattern.

Note that the Eq instance cannot tell you whether two patterns behave in the same way; only whether they compile to the same Pattern. For instance, compile "x" and compile "[x]" may or may not compare equal, though a match will behave the exact same way no matter which Pattern is used.

Functions

Compilation

compile :: String -> PatternSource

Compiles a glob pattern from its textual representation into a Pattern object.

For the most part, a character matches itself. Recognized operators are as follows:

?
Matches any character except path separators.
*
Matches any number of characters except path separators, including the empty string.
[..]
Matches any of the enclosed characters. Ranges of characters can be specified by separating the endpoints with a '-'. '-' or ']' can be matched by including them as the first character(s) in the list. Never matches path separators: [/] matches nothing at all. Named character classes can also be matched: [:x:] within [] specifies the class named x, which matches certain predefined characters. See below for a full list.
[^..] or [!..]
Like [..], but matches any character not listed. Note that [^-x] is not the inverse of [-x], but the range [^-x].
<m-n>
Matches any integer in the range m to n, inclusive. The range may be open-ended by leaving out either number: "<->", for instance, matches any integer.
**/
Matches any number of characters, including path separators, excluding the empty string.

Supported character classes:

[:alnum:]
Equivalent to "0-9A-Za-z".
[:alpha:]
Equivalent to "A-Za-z".
[:blank:]
Equivalent to "\t ".
[:cntrl:]
Equivalent to "\0-\x1f\x7f".
[:digit:]
Equivalent to "0-9".
[:graph:]
Equivalent to "!-~".
[:lower:]
Equivalent to "a-z".
[:print:]
Equivalent to " -~".
[:punct:]
Equivalent to "!-/:-@[-`{-~".
[:space:]
Equivalent to "\t-\r ".
[:upper:]
Equivalent to "A-Z".
[:xdigit:]
Equivalent to "0-9A-Fa-f".

Note that path separators (typically '/') have to be matched explicitly or using the **/ pattern. In addition, extension separators (typically '.') have to be matched explicitly at the beginning of the pattern or after any path separator.

If a system supports multiple path separators, any one of them will match any of them. For instance, on Windows, '/' will match itself as well as '\'.

Error recovery will be performed: erroneous operators will not be considered operators, but matched as literal strings. Such operators include:

  • An empty [] or [^] or [!]
  • A [ or < without a matching ] or >
  • A malformed <>: e.g. nonnumeric characters or no hyphen

So, e.g. [] will match the string "[]".

decompile :: Pattern -> StringSource

Decompiles a Pattern object into its textual representation: essentially the inverse of compile.

Note, however, that due to internal optimization, decompile . compile is not the identity function. Instead, compile . decompile is.

Be careful with CompOptions: decompile always produces a String which can be passed to compile to get back the same Pattern. compileWith options . decompile is not the identity function unless options is compDefault.

simplify :: Pattern -> PatternSource

Simplifies a Pattern object: removes redundant "./", for instance. The resulting Pattern matches the exact same input as the original one, with some differences:

  • The output of globDir will differ: for example, globbing for "./*" gives "./foo", but after simplification this'll be only "foo".
  • Decompiling the simplified Pattern will obviously not give the original.
  • The simplified Pattern is a bit faster to match with and uses less memory, since some redundant data is removed.

For the last of the above reasons, if you're performance-conscious and not using globDir, you should always simplify after calling compile.

Options

data CompOptions Source

Options which can be passed to the tryCompileWith or compileWith functions: with these you can selectively toggle certain features at compile time.

Note that some of these options depend on each other: classes can never occur if ranges aren't allowed, for instance.

Constructors

CompOptions 

Fields

characterClasses :: Bool

Allow character classes, [[:...:]].

characterRanges :: Bool

Allow character ranges, [...].

numberRanges :: Bool

Allow open ranges, <...>.

wildcards :: Bool

Allow wildcards, * and ?.

recursiveWildcards :: Bool

Allow recursive wildcards, **/.

pathSepInRanges :: Bool

Allow path separators in character ranges.

If true, a[/]b never matches anything (since character ranges can't match path separators); if false and errorRecovery is enabled, a[/]b matches itself, i.e. a file named ]b in the subdirectory a[.

errorRecovery :: Bool

If the input is invalid, recover by turning any invalid part into literals. For instance, with characterRanges enabled, [abc is an error by default (unclosed character range); with errorRecovery, the [ is turned into a literal match, as though characterRanges were disabled.

compileWith :: CompOptions -> String -> PatternSource

Like compile, but recognizes operators according to the given CompOptions instead of the defaults.

If an error occurs and errorRecovery is disabled, error will be called.

tryCompileWith :: CompOptions -> String -> Either String PatternSource

A safe version of compileWith.

If an error occurs and errorRecovery is disabled, the error message will be returned in a Left.

Predefined option sets

compDefault :: CompOptionsSource

The default set of compilation options: closest to the behaviour of the zsh shell, with errorRecovery enabled.

All options are enabled.

compPosix :: CompOptionsSource

Options for POSIX-compliance, as described in man 7 glob.

numberRanges, recursiveWildcards, and pathSepInRanges are disabled.

Matching

match :: Pattern -> FilePath -> BoolSource

Matches the given Pattern against the given FilePath, returning True if the pattern matches and False otherwise.

globDir :: [Pattern] -> FilePath -> IO ([[FilePath]], [FilePath])Source

Matches each given Pattern against the contents of the given FilePath, recursively. The result pair's first component contains the matched paths, grouped for each given Pattern, and the second contains all paths which were not matched by any Pattern. The results are not in any defined order.

The given directory is prepended to all the matches: the returned paths are all valid from the point of view of the current working directory.

If multiple Patterns match a single FilePath, that path will be included in multiple groups.

Two FilePaths which can be canonicalized to the same file (e.g. "foo" and "./foo") may appear separately if explicit matching on paths beginning with "." is done. Looking for ".*/*", for instance, will cause "./foo" to return as a match but "foo" to not be matched.

This function is different from a simple filter over all the contents of the directory: the matching is performed relative to the directory, so that for instance the following is true:

 fmap (head.fst) (globDir [compile "*"] dir) == getDirectoryContents dir

(With the exception that that glob won't match anything beginning with ..)

If the given FilePath is [], getCurrentDirectory will be used.

Note that in some cases results outside the given directory may be returned: for instance the .* pattern matches the .. directory.

Any results deeper than in the given directory are enumerated lazily, using unsafeInterleaveIO.

Directories without read permissions are returned as entries but their contents, of course, are not.

globDir1 :: Pattern -> FilePath -> IO [FilePath]Source

A convenience wrapper on top of globDir, for when you only have one Pattern you care about.

Options

data MatchOptions Source

Options which can be passed to the matchWith or globDirWith functions: with these you can selectively toggle certain features at matching time.

Constructors

MatchOptions 

Fields

matchDotsImplicitly :: Bool

Allow *, ?, and **/ to match . at the beginning of paths.

ignoreCase :: Bool

Case-independent matching.

ignoreDotSlash :: Bool

Treat ./ as a no-op in both paths and patterns.

(Of course e.g. ../ means something different and will not be ignored.)

matchWith :: MatchOptions -> Pattern -> FilePath -> BoolSource

Like match, but applies the given MatchOptions instead of the defaults.

globDirWith :: MatchOptions -> [Pattern] -> FilePath -> IO ([[FilePath]], [FilePath])Source

Like globDir, but applies the given MatchOptions instead of the defaults when matching.

Predefined option sets

matchDefault :: MatchOptionsSource

The default set of execution options: closest to the behaviour of the zsh shell.

Currently identical to matchPosix.

matchPosix :: MatchOptionsSource

Options for POSIX-compliance, as described in man 7 glob.

ignoreDotSlash is enabled, the rest are disabled.

Miscellaneous

commonDirectory :: Pattern -> (FilePath, Pattern)Source

Factors out the directory component of a Pattern. Useful in conjunction with globDir.

Preserves the number of path separators: commonDirectory (compile "foo///bar") becomes ("foo///", compile "bar").