Skip to content

Commit 351903e

Browse files
Allow ** wildcards in globs.
These are inspired by a plan described in a comment in #2522, and only implement a quite limited form of recursive matching: only a single ** wildcard is accepted, it must be the final directory, and, if a ** wildcard is present, the file name must include a wildcard. Or-patterns are not implemented, for simplicity. Closes #3178, #2030.
1 parent 0e7ad1d commit 351903e

File tree

20 files changed

+436
-97
lines changed

20 files changed

+436
-97
lines changed

Cabal/Cabal.cabal

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -73,6 +73,8 @@ extra-source-files:
7373
tests/ParserTests/regressions/Octree-0.5.cabal
7474
tests/ParserTests/regressions/Octree-0.5.expr
7575
tests/ParserTests/regressions/Octree-0.5.format
76+
tests/ParserTests/regressions/bad-glob-syntax.cabal
77+
tests/ParserTests/regressions/bad-glob-syntax.check
7678
tests/ParserTests/regressions/common.cabal
7779
tests/ParserTests/regressions/common.expr
7880
tests/ParserTests/regressions/common.format
@@ -112,6 +114,10 @@ extra-source-files:
112114
tests/ParserTests/regressions/nothing-unicode.check
113115
tests/ParserTests/regressions/nothing-unicode.expr
114116
tests/ParserTests/regressions/nothing-unicode.format
117+
tests/ParserTests/regressions/pre-1.6-glob.cabal
118+
tests/ParserTests/regressions/pre-1.6-glob.check
119+
tests/ParserTests/regressions/pre-3.0-globstar.cabal
120+
tests/ParserTests/regressions/pre-3.0-globstar.check
115121
tests/ParserTests/regressions/shake.cabal
116122
tests/ParserTests/regressions/shake.expr
117123
tests/ParserTests/regressions/shake.format
@@ -259,6 +265,7 @@ library
259265
Distribution.Simple.GHCJS
260266
Distribution.Simple.Haddock
261267
Distribution.Simple.Doctest
268+
Distribution.Simple.Glob
262269
Distribution.Simple.HaskellSuite
263270
Distribution.Simple.Hpc
264271
Distribution.Simple.Install
@@ -480,6 +487,7 @@ test-suite unit-tests
480487
UnitTests.Distribution.Compat.ReadP
481488
UnitTests.Distribution.Compat.Time
482489
UnitTests.Distribution.Compat.Graph
490+
UnitTests.Distribution.Simple.Glob
483491
UnitTests.Distribution.Simple.Program.Internal
484492
UnitTests.Distribution.Simple.Utils
485493
UnitTests.Distribution.SPDX

Cabal/ChangeLog.md

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,9 @@
88
out of its misery (#4383).
99
* Added `Eta` to `CompilerFlavor` and to known compilers.
1010
* `cabal haddock` now generates per-component documentation (#5226).
11+
* Allow `**` wildcards in `data-files`, `extra-source-files` and
12+
`extra-doc-files`. These allow a limited form of recursive
13+
matching. (#3178 et al).
1114

1215
----
1316

Cabal/Distribution/PackageDescription/Check.hs

Lines changed: 19 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -48,6 +48,7 @@ import Distribution.Pretty (prettyShow)
4848
import Distribution.Simple.BuildPaths (autogenPathsModuleName)
4949
import Distribution.Simple.BuildToolDepends
5050
import Distribution.Simple.CCompiler
51+
import Distribution.Simple.Glob
5152
import Distribution.Simple.Utils hiding (findPackageDesc, notice)
5253
import Distribution.System
5354
import Distribution.Text
@@ -1045,6 +1046,24 @@ checkPaths pkg =
10451046
, (GHC, flags) <- options bi
10461047
, path <- flags
10471048
, isInsideDist path ]
1049+
++
1050+
[ PackageDistInexcusable $
1051+
"In the 'data-files' field: " ++ explainGlobSyntaxError pat err
1052+
| pat <- dataFiles pkg
1053+
, Left err <- [parseFileGlob (specVersion pkg) pat]
1054+
]
1055+
++
1056+
[ PackageDistInexcusable $
1057+
"In the 'extra-source-files' field: " ++ explainGlobSyntaxError pat err
1058+
| pat <- extraSrcFiles pkg
1059+
, Left err <- [parseFileGlob (specVersion pkg) pat]
1060+
]
1061+
++
1062+
[ PackageDistInexcusable $
1063+
"In the 'extra-doc-files' field: " ++ explainGlobSyntaxError pat err
1064+
| pat <- extraDocFiles pkg
1065+
, Left err <- [parseFileGlob (specVersion pkg) pat]
1066+
]
10481067
where
10491068
isOutsideTree path = case splitDirectories path of
10501069
"..":_ -> True
@@ -1269,25 +1288,6 @@ checkCabalVersion pkg =
12691288
[ display (Dependency name (eliminateWildcardSyntax versionRange))
12701289
| Dependency name versionRange <- testedWithUsingWildcardSyntax ]
12711290

1272-
-- check use of "data-files: data/*.txt" syntax
1273-
, checkVersion [1,6] (not (null dataFilesUsingGlobSyntax)) $
1274-
PackageDistInexcusable $
1275-
"Using wildcards like "
1276-
++ commaSep (map quote $ take 3 dataFilesUsingGlobSyntax)
1277-
++ " in the 'data-files' field requires 'cabal-version: >= 1.6'. "
1278-
++ "Alternatively if you require compatibility with earlier Cabal "
1279-
++ "versions then list all the files explicitly."
1280-
1281-
-- check use of "extra-source-files: mk/*.in" syntax
1282-
, checkVersion [1,6] (not (null extraSrcFilesUsingGlobSyntax)) $
1283-
PackageDistInexcusable $
1284-
"Using wildcards like "
1285-
++ commaSep (map quote $ take 3 extraSrcFilesUsingGlobSyntax)
1286-
++ " in the 'extra-source-files' field requires "
1287-
++ "'cabal-version: >= 1.6'. Alternatively if you require "
1288-
++ "compatibility with earlier Cabal versions then list all the files "
1289-
++ "explicitly."
1290-
12911291
-- check use of "source-repository" section
12921292
, checkVersion [1,6] (not (null (sourceRepos pkg))) $
12931293
PackageDistInexcusable $
@@ -1358,11 +1358,6 @@ checkCabalVersion pkg =
13581358
| otherwise = check cond pc
13591359

13601360
buildInfoField field = map field (allBuildInfo pkg)
1361-
dataFilesUsingGlobSyntax = filter usesGlobSyntax (dataFiles pkg)
1362-
extraSrcFilesUsingGlobSyntax = filter usesGlobSyntax (extraSrcFiles pkg)
1363-
usesGlobSyntax str = case parseFileGlob str of
1364-
Just (FileGlob _ _) -> True
1365-
_ -> False
13661361

13671362
versionRangeExpressions =
13681363
[ dep | dep@(Dependency _ vr) <- allBuildDepends pkg

Cabal/Distribution/Simple/Glob.hs

Lines changed: 177 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,177 @@
1+
{-# LANGUAGE FlexibleContexts #-}
2+
{-# LANGUAGE RankNTypes #-}
3+
4+
-----------------------------------------------------------------------------
5+
-- |
6+
-- Module : Distribution.Simple.Glob
7+
-- Copyright : Isaac Jones, Simon Marlow 2003-2004
8+
-- License : BSD3
9+
-- portions Copyright (c) 2007, Galois Inc.
10+
--
11+
-- Maintainer : [email protected]
12+
-- Portability : portable
13+
--
14+
-- Simple file globbing.
15+
16+
module Distribution.Simple.Glob (
17+
matchFileGlob,
18+
matchDirFileGlob,
19+
fileGlobMatches,
20+
parseFileGlob,
21+
explainGlobSyntaxError,
22+
GlobSyntaxError(..),
23+
GlobPat,
24+
) where
25+
26+
import Prelude ()
27+
import Distribution.Compat.Prelude
28+
29+
import Distribution.Simple.Utils
30+
import Distribution.Verbosity
31+
import Distribution.Version
32+
33+
import System.FilePath (joinPath, splitExtensions, splitDirectories, takeExtensions, (</>))
34+
35+
-- Note throughout that we use splitDirectories, not splitPath. On
36+
-- Posix, this makes no difference, but, because Windows accepts both
37+
-- slash and backslash as its path separators, if we left in the
38+
-- separators from the glob we might not end up properly normalised.
39+
40+
data GlobSyntaxError
41+
= StarInDirectory
42+
| StarInFileName
43+
| StarInExtension
44+
| NoExtensionOnStar
45+
| EmptyGlob
46+
| LiteralFileNameGlobStar
47+
| VersionDoesNotSupportGlobStar
48+
| VersionDoesNotSupportGlob
49+
deriving (Eq, Show)
50+
51+
explainGlobSyntaxError :: FilePath -> GlobSyntaxError -> String
52+
explainGlobSyntaxError filepath StarInDirectory =
53+
"invalid file glob '" ++ filepath
54+
++ "'. A wildcard '**' is only allowed as the final parent"
55+
++ " directory. Stars must not otherwise appear in the parent"
56+
++ " directories."
57+
explainGlobSyntaxError filepath StarInExtension =
58+
"invalid file glob '" ++ filepath
59+
++ "'. Wildcards '*' are only allowed as the"
60+
++ " file's base name, not in the file extension."
61+
explainGlobSyntaxError filepath StarInFileName =
62+
"invalid file glob '" ++ filepath
63+
++ "'. Wildcards '*' may only totally replace the"
64+
++ " file's base name, not only parts of it."
65+
explainGlobSyntaxError filepath NoExtensionOnStar =
66+
"invalid file glob '" ++ filepath
67+
++ "'. If a wildcard '*' is used it must be with an file extension."
68+
explainGlobSyntaxError filepath LiteralFileNameGlobStar =
69+
"invalid file glob '" ++ filepath
70+
++ "'. If a wildcard '**' is used as a parent directory, the"
71+
++ " file's base name must be a wildcard '*'."
72+
explainGlobSyntaxError _ EmptyGlob =
73+
"invalid file glob. A glob cannot be the empty string."
74+
explainGlobSyntaxError filepath VersionDoesNotSupportGlobStar =
75+
"invalid file glob '" ++ filepath
76+
++ "'. Using the double-star syntax requires 'cabal-version: 3.0'"
77+
++ " or greater. Alternatively, for compatibility with earlier Cabal"
78+
++ " versions, list the included directories explicitly."
79+
explainGlobSyntaxError filepath VersionDoesNotSupportGlob =
80+
"invalid file glob '" ++ filepath
81+
++ "'. Using star wildcards requires 'cabal-version: >= 1.6'. "
82+
++ "Alternatively if you require compatibility with earlier Cabal "
83+
++ "versions then list all the files explicitly."
84+
85+
data IsRecursive = Recursive | NonRecursive
86+
87+
data GlobPat = PatStem String GlobPat
88+
-- ^ A single subdirectory component + remainder.
89+
| PatMatch IsRecursive String
90+
-- ^ First argument: Is this a @**/*.ext@ pattern?
91+
-- Second argument: the extensions to accept.
92+
| PatLit FilePath
93+
-- ^ Literal file name.
94+
95+
fileGlobMatches :: GlobPat -> FilePath -> Bool
96+
fileGlobMatches pat = fileGlobMatchesSegments pat . splitDirectories
97+
98+
fileGlobMatchesSegments :: GlobPat -> [FilePath] -> Bool
99+
fileGlobMatchesSegments _ [] = False
100+
fileGlobMatchesSegments pat (seg : segs) = case pat of
101+
PatStem dir pat' ->
102+
dir == seg && fileGlobMatchesSegments pat' segs
103+
PatMatch Recursive ext ->
104+
ext == takeExtensions (foldl' (flip const) seg segs)
105+
PatMatch NonRecursive ext ->
106+
null segs && ext == takeExtensions seg
107+
PatLit filename ->
108+
null segs && filename == seg
109+
110+
parseFileGlob :: Version -> FilePath -> Either GlobSyntaxError GlobPat
111+
parseFileGlob version filepath = case reverse (splitDirectories filepath) of
112+
[] ->
113+
Left EmptyGlob
114+
(filename : "**" : segments)
115+
| allowGlobStar -> do
116+
ext <- case splitExtensions filename of
117+
("*", ext) | '*' `elem` ext -> Left StarInExtension
118+
| null ext -> Left NoExtensionOnStar
119+
| otherwise -> Right ext
120+
_ -> Left LiteralFileNameGlobStar
121+
foldM addStem (PatMatch Recursive ext) segments
122+
| otherwise -> Left VersionDoesNotSupportGlobStar
123+
(filename : segments) -> do
124+
pat <- case splitExtensions filename of
125+
("*", ext) | not allowGlob -> Left VersionDoesNotSupportGlob
126+
| '*' `elem` ext -> Left StarInExtension
127+
| null ext -> Left NoExtensionOnStar
128+
| otherwise -> Right (PatMatch NonRecursive ext)
129+
(_, ext) | '*' `elem` ext -> Left StarInExtension
130+
| '*' `elem` filename -> Left StarInFileName
131+
| otherwise -> Right (PatLit filename)
132+
foldM addStem pat segments
133+
where
134+
allowGlob = version >= mkVersion [1,6]
135+
allowGlobStar = version >= mkVersion [3,0]
136+
addStem pat seg
137+
| '*' `elem` seg = Left StarInDirectory
138+
| otherwise = Right (PatStem seg pat)
139+
140+
matchFileGlob :: Verbosity -> Version -> FilePath -> IO [FilePath]
141+
matchFileGlob verbosity version = matchDirFileGlob verbosity version "."
142+
143+
-- The returned values do not include the supplied @dir@ prefix.
144+
matchDirFileGlob :: Verbosity -> Version -> FilePath -> FilePath -> IO [FilePath]
145+
matchDirFileGlob verbosity version dir filepath = case parseFileGlob version filepath of
146+
Left err -> die' verbosity $ explainGlobSyntaxError filepath err
147+
Right pat -> do
148+
-- This function might be called from the project root with dir as
149+
-- ".". Walking the tree starting there involves going into .git/
150+
-- and dist-newstyle/, which is a lot of work for no reward, so
151+
-- extract the constant prefix from the pattern and start walking
152+
-- there. If the pattern is **/*.blah, then of course we'll have
153+
-- to walk the whole thing anyway, but that's what the user asked
154+
-- for!
155+
let (prefixSegments, pat') = splitConstantPrefix pat
156+
joinedPrefix = joinPath prefixSegments
157+
files <- getDirectoryContentsRecursive (dir </> joinedPrefix)
158+
case filter (fileGlobMatches pat') files of
159+
[] -> die' verbosity $
160+
"filepath wildcard '" ++ filepath
161+
++ "' does not match any files."
162+
matches -> return $ fmap (joinedPrefix </>) matches
163+
164+
unfoldr' :: (a -> Either r (b, a)) -> a -> ([b], r)
165+
unfoldr' f a = case f a of
166+
Left r -> ([], r)
167+
Right (b, a') -> case unfoldr' f a' of
168+
(bs, r) -> (b : bs, r)
169+
170+
-- | Extract the (possibly null) constant prefix from the pattern.
171+
-- This has the property that, if @(pref, pat') = splitConstantPrefix pat@,
172+
-- then @pat === foldr PatStem pat' pref@.
173+
splitConstantPrefix :: GlobPat -> ([FilePath], GlobPat)
174+
splitConstantPrefix = unfoldr' step
175+
where
176+
step (PatStem seg pat) = Right (seg, pat)
177+
step pat = Left pat

Cabal/Distribution/Simple/Haddock.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,7 @@ import Distribution.Package
4242
import qualified Distribution.ModuleName as ModuleName
4343
import Distribution.PackageDescription as PD hiding (Flag)
4444
import Distribution.Simple.Compiler hiding (Flag)
45+
import Distribution.Simple.Glob
4546
import Distribution.Simple.Program.GHC
4647
import Distribution.Simple.Program.ResponseFile
4748
import Distribution.Simple.Program
@@ -258,7 +259,7 @@ haddock pkg_descr lbi suffixes flags' = do
258259
CBench _ -> when (flag haddockBenchmarks) $ smsg >> doExe component
259260

260261
for_ (extraDocFiles pkg_descr) $ \ fpath -> do
261-
files <- matchFileGlob fpath
262+
files <- matchFileGlob verbosity (specVersion pkg_descr) fpath
262263
for_ files $ copyFileTo verbosity (unDir $ argOutputDir commonArgs)
263264

264265
-- ------------------------------------------------------------------------------

Cabal/Distribution/Simple/Install.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -33,10 +33,11 @@ import Distribution.Package
3333
import Distribution.PackageDescription
3434
import Distribution.Simple.LocalBuildInfo
3535
import Distribution.Simple.BuildPaths (haddockName, haddockPref)
36+
import Distribution.Simple.Glob (matchDirFileGlob)
3637
import Distribution.Simple.Utils
3738
( createDirectoryIfMissingVerbose
3839
, installDirectoryContents, installOrdinaryFile, isInSearchPath
39-
, die', info, noticeNoWrap, warn, matchDirFileGlob )
40+
, die', info, noticeNoWrap, warn )
4041
import Distribution.Simple.Compiler
4142
( CompilerFlavor(..), compilerFlavor )
4243
import Distribution.Simple.Setup
@@ -235,7 +236,7 @@ installDataFiles :: Verbosity -> PackageDescription -> FilePath -> IO ()
235236
installDataFiles verbosity pkg_descr destDataDir =
236237
flip traverse_ (dataFiles pkg_descr) $ \ file -> do
237238
let srcDataDir = dataDir pkg_descr
238-
files <- matchDirFileGlob srcDataDir file
239+
files <- matchDirFileGlob verbosity (specVersion pkg_descr) srcDataDir file
239240
let dir = takeDirectory file
240241
createDirectoryIfMissingVerbose verbosity True (destDataDir </> dir)
241242
sequence_ [ installOrdinaryFile verbosity (srcDataDir </> file')

Cabal/Distribution/Simple/SrcDist.hs

Lines changed: 8 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -52,6 +52,7 @@ import Distribution.Package
5252
import Distribution.ModuleName
5353
import qualified Distribution.ModuleName as ModuleName
5454
import Distribution.Version
55+
import Distribution.Simple.Glob
5556
import Distribution.Simple.Utils
5657
import Distribution.Simple.Setup
5758
import Distribution.Simple.PreProcess
@@ -137,16 +138,16 @@ listPackageSources :: Verbosity -- ^ verbosity
137138
listPackageSources verbosity pkg_descr0 pps = do
138139
-- Call helpers that actually do all work.
139140
ordinary <- listPackageSourcesOrdinary verbosity pkg_descr pps
140-
maybeExecutable <- listPackageSourcesMaybeExecutable pkg_descr
141+
maybeExecutable <- listPackageSourcesMaybeExecutable verbosity pkg_descr
141142
return (ordinary, maybeExecutable)
142143
where
143144
pkg_descr = filterAutogenModules pkg_descr0
144145

145146
-- | List those source files that may be executable (e.g. the configure script).
146-
listPackageSourcesMaybeExecutable :: PackageDescription -> IO [FilePath]
147-
listPackageSourcesMaybeExecutable pkg_descr =
147+
listPackageSourcesMaybeExecutable :: Verbosity -> PackageDescription -> IO [FilePath]
148+
listPackageSourcesMaybeExecutable verbosity pkg_descr =
148149
-- Extra source files.
149-
fmap concat . for (extraSrcFiles pkg_descr) $ \fpath -> matchFileGlob fpath
150+
fmap concat . for (extraSrcFiles pkg_descr) $ \fpath -> matchFileGlob verbosity (specVersion pkg_descr) fpath
150151

151152
-- | List those source files that should be copied with ordinary permissions.
152153
listPackageSourcesOrdinary :: Verbosity
@@ -208,12 +209,13 @@ listPackageSourcesOrdinary verbosity pkg_descr pps =
208209
-- Data files.
209210
, fmap concat
210211
. for (dataFiles pkg_descr) $ \filename ->
211-
matchFileGlob (dataDir pkg_descr </> filename)
212+
fmap (fmap (dataDir pkg_descr </>)) $
213+
matchDirFileGlob verbosity (specVersion pkg_descr) (dataDir pkg_descr) filename
212214

213215
-- Extra doc files.
214216
, fmap concat
215217
. for (extraDocFiles pkg_descr) $ \ filename ->
216-
matchFileGlob filename
218+
matchFileGlob verbosity (specVersion pkg_descr) filename
217219

218220
-- License file(s).
219221
, return (licenseFiles pkg_descr)

0 commit comments

Comments
 (0)