Cabal-3.11.0.0: A framework for packaging Haskell software
CopyrightIsaac Jones Simon Marlow 2003-2004
LicenseBSD3 portions Copyright (c) 2007, Galois Inc.
Maintainercabal-devel@haskell.org
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Distribution.Simple.Glob.Internal

Description

Internal module for simple file globbing. Please import Distribution.Simple.Glob instead.

Synopsis

Documentation

data Glob Source #

A filepath specified by globbing.

Constructors

GlobDir !GlobPieces !Glob
dirGlob/glob
GlobDirRecursive !GlobPieces

**/glob, where ** denotes recursively traversing all directories and matching filenames on glob.

GlobFile !GlobPieces

A file glob.

GlobDirTrailing

Trailing dir; a glob ending in /.

Instances

Instances details
Parsec Glob Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Methods

parsec :: CabalParsing m => m Glob Source #

Pretty Glob Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Structured Glob Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Binary Glob Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Methods

put :: Glob -> Put #

get :: Get Glob #

putList :: [Glob] -> Put #

Generic Glob Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Associated Types

type Rep Glob 
Instance details

Defined in Distribution.Simple.Glob.Internal

Methods

from :: Glob -> Rep Glob x #

to :: Rep Glob x -> Glob #

Show Glob Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Methods

showsPrec :: Int -> Glob -> ShowS #

show :: Glob -> String #

showList :: [Glob] -> ShowS #

Eq Glob Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Methods

(==) :: Glob -> Glob -> Bool #

(/=) :: Glob -> Glob -> Bool #

type Rep Glob Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

type GlobPieces = [GlobPiece] Source #

A single directory or file component of a globbed path

data GlobPiece Source #

A piece of a globbing pattern

Constructors

WildCard

A wildcard *

Literal String

A literal string dirABC

Union [GlobPieces]

A union of patterns, e.g. dir{a,*.txt,c}...

Instances

Instances details
Structured GlobPiece Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Binary GlobPiece Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Methods

put :: GlobPiece -> Put #

get :: Get GlobPiece #

putList :: [GlobPiece] -> Put #

Generic GlobPiece Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Associated Types

type Rep GlobPiece 
Instance details

Defined in Distribution.Simple.Glob.Internal

type Rep GlobPiece = D1 ('MetaData "GlobPiece" "Distribution.Simple.Glob.Internal" "Cabal-3.11.0.0-inplace" '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]))))
Show GlobPiece Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Eq GlobPiece Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

type Rep GlobPiece Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

type Rep GlobPiece = D1 ('MetaData "GlobPiece" "Distribution.Simple.Glob.Internal" "Cabal-3.11.0.0-inplace" '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

Cabal package globbing errors

data GlobResult a Source #

Constructors

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 matchDirFileGlob, and, for 'data-files', relative to 'data-dir').

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

Instances details
Functor GlobResult Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Methods

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

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

Show a => Show (GlobResult a) Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Eq a => Eq (GlobResult a) Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Methods

(==) :: GlobResult a -> GlobResult a -> Bool #

(/=) :: GlobResult a -> GlobResult a -> Bool #

Ord a => Ord (GlobResult a) Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

runDirFileGlob Source #

Arguments

:: Verbosity 
-> Maybe CabalSpecVersion

If the glob we are running should care about the cabal spec, and warnings such as GlobWarnMultiDot, then this should be the version. If you want to run a glob but don't care about any of the cabal-spec restrictions on globs, use Nothing!

-> 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)