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 |
Internal module for simple file globbing. Please import Distribution.Simple.Glob instead.
Synopsis
- data Glob
- type GlobPieces = [GlobPiece]
- data GlobPiece
- = WildCard
- | Literal String
- | Union [GlobPieces]
- matchGlob :: FilePath -> Glob -> IO [FilePath]
- matchGlobPieces :: GlobPieces -> String -> Bool
- parseFileGlob :: CabalSpecVersion -> FilePath -> Either GlobSyntaxError Glob
- enableMultidot :: CabalSpecVersion -> Bool
- dispGlobPieces :: GlobPieces -> Doc
- isGlobEscapedChar :: Char -> Bool
- data GlobSyntaxError
- explainGlobSyntaxError :: FilePath -> GlobSyntaxError -> String
- data GlobResult a
- runDirFileGlob :: Verbosity -> Maybe CabalSpecVersion -> FilePath -> Glob -> IO [GlobResult FilePath]
- isRecursiveInRoot :: Glob -> Bool
- checkNameMatches :: CabalSpecVersion -> GlobPieces -> String -> Maybe (GlobResult ())
- fileGlobMatches :: CabalSpecVersion -> Glob -> FilePath -> Maybe (GlobResult ())
Documentation
A filepath specified by globbing.
GlobDir !GlobPieces !Glob | dirGlob/glob |
GlobDirRecursive !GlobPieces |
|
GlobFile !GlobPieces | A file glob. |
GlobDirTrailing | Trailing dir; a glob ending in |
Instances
type GlobPieces = [GlobPiece] Source #
A single directory or file component of a globbed path
A piece of a globbing pattern
WildCard | A wildcard |
Literal String | A literal string |
Union [GlobPieces] | A union of patterns, e.g. |
Instances
Structured GlobPiece Source # | |||||
Defined in Distribution.Simple.Glob.Internal | |||||
Binary GlobPiece Source # | |||||
Generic GlobPiece Source # | |||||
Defined in Distribution.Simple.Glob.Internal
| |||||
Show GlobPiece Source # | |||||
Eq GlobPiece Source # | |||||
type Rep GlobPiece Source # | |||||
Defined in Distribution.Simple.Glob.Internal type Rep GlobPiece = D1 ('MetaData "GlobPiece" "Distribution.Simple.Glob.Internal" "Cabal-3.12.0.0-0d16" 'False) (C1 ('MetaCons "WildCard" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Literal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "Union" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [GlobPieces])))) |
Matching
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
Parsing & printing
Parsing globs in a cabal package
Parsing globs otherwise
dispGlobPieces :: GlobPieces -> Doc Source #
isGlobEscapedChar :: Char -> Bool Source #
Cabal package globbing errors
data GlobSyntaxError Source #
StarInDirectory | |
StarInFileName | |
StarInExtension | |
NoExtensionOnStar | |
EmptyGlob | |
LiteralFileNameGlobStar | |
VersionDoesNotSupportGlobStar | |
VersionDoesNotSupportGlob |
Instances
Show GlobSyntaxError Source # | |
Defined in Distribution.Simple.Glob.Internal showsPrec :: Int -> GlobSyntaxError -> ShowS # show :: GlobSyntaxError -> String # showList :: [GlobSyntaxError] -> ShowS # | |
Eq GlobSyntaxError Source # | |
Defined in Distribution.Simple.Glob.Internal (==) :: GlobSyntaxError -> GlobSyntaxError -> Bool # (/=) :: GlobSyntaxError -> GlobSyntaxError -> Bool # |
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.Internal fmap :: (a -> b) -> GlobResult a -> GlobResult b # (<$) :: a -> GlobResult b -> GlobResult a # | |
Show a => Show (GlobResult a) Source # | |
Defined in Distribution.Simple.Glob.Internal showsPrec :: Int -> GlobResult a -> ShowS # show :: GlobResult a -> String # showList :: [GlobResult a] -> ShowS # | |
Eq a => Eq (GlobResult a) Source # | |
Defined in Distribution.Simple.Glob.Internal (==) :: GlobResult a -> GlobResult a -> Bool # (/=) :: GlobResult a -> GlobResult a -> Bool # | |
Ord a => Ord (GlobResult a) Source # | |
Defined in Distribution.Simple.Glob.Internal 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 # |
:: 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.
isRecursiveInRoot :: Glob -> Bool Source #
Is the root of this relative glob path a directory-recursive wildcard, e.g. **/*.txt
?
checkNameMatches :: CabalSpecVersion -> GlobPieces -> String -> Maybe (GlobResult ()) Source #
Check how the string matches the glob under this cabal version
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
)