filepattern-0.1.3: File path glob-like matching
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.FilePattern

Description

A module for matching files using patterns such as "src/**/*.png" for all .png files recursively under the src directory. See ?== for the semantics of FilePattern values. Features:

  • All matching is O(n). Most functions precompute some information given only one argument.
  • Use match and substitute to extract suitable strings from the * and ** matches, and substitute them back into other patterns.
  • Use step and matchMany to perform bulk matching of many patterns against many paths simultaneously.
  • Use System.FilePattern.Directory to perform optimised directory traverals using patterns.
Synopsis

Documentation

type FilePattern = String Source #

A type synonym for file patterns, containing ** and *. For the syntax and semantics of FilePattern see ?==.

Most FilePath values lacking literal . and .. components are suitable as FilePattern values which match only that specific file. On Windows \ is treated as equivalent to /.

You can write FilePattern values as a literal string, or build them up using the operators <.> and </> (but be aware that "" </> "foo" produces "./foo").

(?==) :: FilePattern -> FilePath -> Bool Source #

Match a FilePattern against a FilePath. There are two special forms:

  • * matches part of a path component, excluding any separators.
  • ** as a path component matches an arbitrary number of path components.

Some examples:

  • test.c matches test.c and nothing else.
  • *.c matches all .c files in the current directory, so file.c matches, but file.h and dir/file.c don't.
  • **/*.c matches all .c files anywhere on the filesystem, so file.c, dir/file.c, dir1/dir2/file.c and /path/to/file.c all match, but file.h and dir/file.h don't.
  • dir/*/* matches all files one level below dir, so dir/one/file.c and dir/two/file.h match, but file.c, one/dir/file.c, dir/file.h and dir/one/two/file.c don't.

Patterns with constructs such as foo/../bar will never match normalised FilePath values, so are unlikely to be correct.

match :: FilePattern -> FilePath -> Maybe [String] Source #

Like ?==, but returns Nothing on if there is no match, otherwise Just with the list of fragments matching each wildcard. For example:

isJust (match p x) == (p ?== x)
match "**/*.c" "test.txt" == Nothing
match "**/*.c" "foo.c" == Just ["","foo"]
match "**/*.c" "bar/baz/foo.c" == Just ["bar/baz/","foo"]

On Windows any \ path separators will be replaced by /.

substitute :: Partial => FilePattern -> [String] -> FilePath Source #

Given a successful match, substitute it back in to a pattern with the same arity. Raises an error if the number of parts does not match the arity of the pattern.

p ?== x ==> substitute (fromJust $ match p x) p == x
substitute "**/*.c" ["dir","file"] == "dir/file.c"

arity :: FilePattern -> Int Source #

How many * and ** elements are there.

arity "test.c" == 0
arity "**/*.c" == 2

Multiple patterns and paths

step :: [(a, FilePattern)] -> Step a Source #

Efficient matching of a set of FilePatterns against a set of FilePaths. First call step passing in all the FilePatterns, with a tag for each one. Next call the methods of Step, providing the components of the FilePaths in turn.

Useful for efficient bulk searching, particularly directory scanning, where you can avoid descending into directories which cannot match.

step_ :: [FilePattern] -> Step () Source #

Like step but using () as the tag for each FilePattern.

data Step a Source #

The result of step, used to process successive path components of a set of FilePaths.

Constructors

Step 

Fields

Instances

Instances details
Functor Step Source # 
Instance details

Defined in System.FilePattern.Step

Methods

fmap :: (a -> b) -> Step a -> Step b #

(<$) :: a -> Step b -> Step a #

Semigroup (Step a) Source # 
Instance details

Defined in System.FilePattern.Step

Methods

(<>) :: Step a -> Step a -> Step a #

sconcat :: NonEmpty (Step a) -> Step a #

stimes :: Integral b => b -> Step a -> Step a #

Monoid (Step a) Source # 
Instance details

Defined in System.FilePattern.Step

Methods

mempty :: Step a #

mappend :: Step a -> Step a -> Step a #

mconcat :: [Step a] -> Step a #

data StepNext Source #

What we know about the next step values.

Constructors

StepOnly [String]

All components not listed will result in dull Step values from stepApply, with stepNext being StepOnly [] and stepDone being []. The field is a set - their order is irrelevant but there will be no duplicates in values arising from step.

StepEverything

All calls to stepApply will return stepNext being StepEverything with a non-empty stepDone.

StepUnknown

We have no additional information about the output from stepApply.

matchMany :: [(a, FilePattern)] -> [(b, FilePath)] -> [(a, b, [String])] Source #

Efficiently match many FilePatterns against many FilePaths in a single operation. Note that the returned matches are not guaranteed to be in any particular order.

matchMany [(a, pat)] [(b, path)] == maybeToList (map (a,b,) (match pat path))