Copyright | Isaac Jones Simon Marlow 2003-2004 |
---|---|
License | BSD3 portions Copyright (c) 2007, Galois Inc. |
Maintainer | cabal-devel@haskell.org |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Simple file globbing.
Synopsis
- data Glob
- data GlobResult a
- globMatches :: [GlobResult a] -> [a]
- fileGlobMatches :: CabalSpecVersion -> Glob -> FilePath -> Maybe (GlobResult ())
- matchGlob :: FilePath -> Glob -> IO [FilePath]
- matchGlobPieces :: GlobPieces -> String -> Bool
- matchDirFileGlob :: forall dir (allowAbs :: AllowAbsolute) (file :: FileOrDir). Verbosity -> CabalSpecVersion -> Maybe (SymbolicPath CWD ('Dir dir)) -> SymbolicPathX allowAbs dir file -> IO [SymbolicPathX allowAbs dir file]
- matchDirFileGlobWithDie :: forall dir (allowAbs :: AllowAbsolute) (file :: FileOrDir). Verbosity -> (forall res. Verbosity -> CabalException -> IO [res]) -> CabalSpecVersion -> Maybe (SymbolicPath CWD ('Dir dir)) -> SymbolicPathX allowAbs dir file -> IO [SymbolicPathX allowAbs dir file]
- runDirFileGlob :: Verbosity -> Maybe CabalSpecVersion -> FilePath -> Glob -> IO [GlobResult FilePath]
- parseFileGlob :: CabalSpecVersion -> FilePath -> Either GlobSyntaxError Glob
- data GlobSyntaxError
- explainGlobSyntaxError :: FilePath -> GlobSyntaxError -> String
- isRecursiveInRoot :: Glob -> Bool
Globs
A filepath specified by globbing.
Instances
Matching on globs
data GlobResult a Source #
GlobMatch a | The glob matched the value supplied. |
GlobWarnMultiDot a | The glob did not match the value supplied because the cabal-version is too low and the extensions on the file did not precisely match the glob's extensions, but rather the glob was a proper suffix of the file's extensions; i.e., if not for the low cabal-version, it would have matched. |
GlobMissingDirectory a | The glob couldn't match because the directory named doesn't
exist. The directory will be as it appears in the glob (i.e.,
relative to the directory passed to |
GlobMatchesDirectory a | The glob matched a directory when we were looking for files only. It didn't match a file! Since: Cabal-3.12.0.0 |
Instances
Functor GlobResult Source # | |
Defined in Distribution.Simple.Glob fmap :: (a -> b) -> GlobResult a -> GlobResult b # (<$) :: a -> GlobResult b -> GlobResult a # | |
Show a => Show (GlobResult a) Source # | |
Defined in Distribution.Simple.Glob showsPrec :: Int -> GlobResult a -> ShowS # show :: GlobResult a -> String # showList :: [GlobResult a] -> ShowS # | |
Eq a => Eq (GlobResult a) Source # | |
Defined in Distribution.Simple.Glob (==) :: GlobResult a -> GlobResult a -> Bool # (/=) :: GlobResult a -> GlobResult a -> Bool # | |
Ord a => Ord (GlobResult a) Source # | |
Defined in Distribution.Simple.Glob compare :: GlobResult a -> GlobResult a -> Ordering # (<) :: GlobResult a -> GlobResult a -> Bool # (<=) :: GlobResult a -> GlobResult a -> Bool # (>) :: GlobResult a -> GlobResult a -> Bool # (>=) :: GlobResult a -> GlobResult a -> Bool # max :: GlobResult a -> GlobResult a -> GlobResult a # min :: GlobResult a -> GlobResult a -> GlobResult a # |
globMatches :: [GlobResult a] -> [a] Source #
Extract the matches from a list of GlobResult
s.
Note: throws away the GlobMissingDirectory
results; chances are
that you want to check for these and error out if any are present.
Since: Cabal-3.12.0.0
fileGlobMatches :: CabalSpecVersion -> Glob -> FilePath -> Maybe (GlobResult ()) Source #
How/does the glob match the given filepath, according to the cabal version?
Since this is pure, we don't make a distinction between matching on
directories or files (i.e. this function won't return GlobMatchesDirectory
)
matchGlob :: FilePath -> Glob -> IO [FilePath] Source #
Match a Glob
against the file system, starting from a
given root directory. The results are all relative to the given root.
Since: Cabal-3.12.0.0
matchGlobPieces :: GlobPieces -> String -> Bool Source #
Match a globbing pattern against a file path component
matchDirFileGlob :: forall dir (allowAbs :: AllowAbsolute) (file :: FileOrDir). Verbosity -> CabalSpecVersion -> Maybe (SymbolicPath CWD ('Dir dir)) -> SymbolicPathX allowAbs dir file -> IO [SymbolicPathX allowAbs dir file] Source #
This will die'
when the glob matches no files, or if the glob
refers to a missing directory, or if the glob fails to parse.
The Version
argument must be the spec version of the package
description being processed, as globs behave slightly differently
in different spec versions.
The first FilePath
argument is the directory that the glob is
relative to. It must be a valid directory (and hence it can't be
the empty string). The returned values will not include this
prefix.
The second FilePath
is the glob itself.
matchDirFileGlobWithDie :: forall dir (allowAbs :: AllowAbsolute) (file :: FileOrDir). Verbosity -> (forall res. Verbosity -> CabalException -> IO [res]) -> CabalSpecVersion -> Maybe (SymbolicPath CWD ('Dir dir)) -> SymbolicPathX allowAbs dir file -> IO [SymbolicPathX allowAbs dir file] Source #
Like matchDirFileGlob
but with customizable die
Since: Cabal-3.6.0.0
:: Verbosity | |
-> Maybe CabalSpecVersion | If the glob we are running should care about the cabal spec, and warnings such as |
-> FilePath | |
-> Glob | |
-> IO [GlobResult FilePath] |
Match files against a pre-parsed glob, starting in a directory.
The Version
argument must be the spec version of the package
description being processed, as globs behave slightly differently
in different spec versions.
The FilePath
argument is the directory that the glob is relative
to. It must be a valid directory (and hence it can't be the empty
string). The returned values will not include this prefix.
Parsing globs
data GlobSyntaxError Source #
StarInDirectory | |
StarInFileName | |
StarInExtension | |
NoExtensionOnStar | |
EmptyGlob | |
LiteralFileNameGlobStar | |
VersionDoesNotSupportGlobStar | |
VersionDoesNotSupportGlob |
Instances
Show GlobSyntaxError Source # | |
Defined in Distribution.Simple.Glob showsPrec :: Int -> GlobSyntaxError -> ShowS # show :: GlobSyntaxError -> String # showList :: [GlobSyntaxError] -> ShowS # | |
Eq GlobSyntaxError Source # | |
Defined in Distribution.Simple.Glob (==) :: GlobSyntaxError -> GlobSyntaxError -> Bool # (/=) :: GlobSyntaxError -> GlobSyntaxError -> Bool # |
Utility
isRecursiveInRoot :: Glob -> Bool Source #
Is the root of this relative glob path a directory-recursive wildcard, e.g. **/*.txt
?