Skip to content

Commit

Permalink
Allow ** wildcards in globs.
Browse files Browse the repository at this point in the history
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.
  • Loading branch information
quasicomputational authored and 23Skidoo committed May 8, 2018
1 parent 218c7bf commit 5e83ef2
Show file tree
Hide file tree
Showing 21 changed files with 445 additions and 100 deletions.
8 changes: 8 additions & 0 deletions Cabal/Cabal.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -73,6 +73,8 @@ extra-source-files:
tests/ParserTests/regressions/Octree-0.5.cabal
tests/ParserTests/regressions/Octree-0.5.expr
tests/ParserTests/regressions/Octree-0.5.format
tests/ParserTests/regressions/bad-glob-syntax.cabal
tests/ParserTests/regressions/bad-glob-syntax.check
tests/ParserTests/regressions/common.cabal
tests/ParserTests/regressions/common.expr
tests/ParserTests/regressions/common.format
Expand Down Expand Up @@ -112,6 +114,10 @@ extra-source-files:
tests/ParserTests/regressions/nothing-unicode.check
tests/ParserTests/regressions/nothing-unicode.expr
tests/ParserTests/regressions/nothing-unicode.format
tests/ParserTests/regressions/pre-1.6-glob.cabal
tests/ParserTests/regressions/pre-1.6-glob.check
tests/ParserTests/regressions/pre-3.0-globstar.cabal
tests/ParserTests/regressions/pre-3.0-globstar.check
tests/ParserTests/regressions/shake.cabal
tests/ParserTests/regressions/shake.expr
tests/ParserTests/regressions/shake.format
Expand Down Expand Up @@ -259,6 +265,7 @@ library
Distribution.Simple.GHCJS
Distribution.Simple.Haddock
Distribution.Simple.Doctest
Distribution.Simple.Glob
Distribution.Simple.HaskellSuite
Distribution.Simple.Hpc
Distribution.Simple.Install
Expand Down Expand Up @@ -480,6 +487,7 @@ test-suite unit-tests
UnitTests.Distribution.Compat.ReadP
UnitTests.Distribution.Compat.Time
UnitTests.Distribution.Compat.Graph
UnitTests.Distribution.Simple.Glob
UnitTests.Distribution.Simple.Program.Internal
UnitTests.Distribution.Simple.Utils
UnitTests.Distribution.SPDX
Expand Down
12 changes: 12 additions & 0 deletions Cabal/ChangeLog.md
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,18 @@
out of its misery (#4383).
* Added `Eta` to `CompilerFlavor` and to known compilers.
* `cabal haddock` now generates per-component documentation (#5226).
* Allow `**` wildcards in `data-files`, `extra-source-files` and
`extra-doc-files`. These allow a limited form of recursive
matching, and require `cabal-version: 3.0`.

Wildcard syntax errors (misplaced `*`, etc) are also now detected
by `cabal check`.

`FileGlob`, `parseFileGlob`, `matchFileGlob` and `matchDirFileGlob`
have beem moved from `Distribution.Simple.Utils` to a new file,
`Distribution.Simple.Glob` and `FileGlob` has been made abstract.

(#5284, #3178, et al.)

----

Expand Down
43 changes: 19 additions & 24 deletions Cabal/Distribution/PackageDescription/Check.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,6 +48,7 @@ import Distribution.Pretty (prettyShow)
import Distribution.Simple.BuildPaths (autogenPathsModuleName)
import Distribution.Simple.BuildToolDepends
import Distribution.Simple.CCompiler
import Distribution.Simple.Glob
import Distribution.Simple.Utils hiding (findPackageDesc, notice)
import Distribution.System
import Distribution.Text
Expand Down Expand Up @@ -1045,6 +1046,24 @@ checkPaths pkg =
, (GHC, flags) <- options bi
, path <- flags
, isInsideDist path ]
++
[ PackageDistInexcusable $
"In the 'data-files' field: " ++ explainGlobSyntaxError pat err
| pat <- dataFiles pkg
, Left err <- [parseFileGlob (specVersion pkg) pat]
]
++
[ PackageDistInexcusable $
"In the 'extra-source-files' field: " ++ explainGlobSyntaxError pat err
| pat <- extraSrcFiles pkg
, Left err <- [parseFileGlob (specVersion pkg) pat]
]
++
[ PackageDistInexcusable $
"In the 'extra-doc-files' field: " ++ explainGlobSyntaxError pat err
| pat <- extraDocFiles pkg
, Left err <- [parseFileGlob (specVersion pkg) pat]
]
where
isOutsideTree path = case splitDirectories path of
"..":_ -> True
Expand Down Expand Up @@ -1269,25 +1288,6 @@ checkCabalVersion pkg =
[ display (Dependency name (eliminateWildcardSyntax versionRange))
| Dependency name versionRange <- testedWithUsingWildcardSyntax ]

-- check use of "data-files: data/*.txt" syntax
, checkVersion [1,6] (not (null dataFilesUsingGlobSyntax)) $
PackageDistInexcusable $
"Using wildcards like "
++ commaSep (map quote $ take 3 dataFilesUsingGlobSyntax)
++ " in the 'data-files' field requires 'cabal-version: >= 1.6'. "
++ "Alternatively if you require compatibility with earlier Cabal "
++ "versions then list all the files explicitly."

-- check use of "extra-source-files: mk/*.in" syntax
, checkVersion [1,6] (not (null extraSrcFilesUsingGlobSyntax)) $
PackageDistInexcusable $
"Using wildcards like "
++ commaSep (map quote $ take 3 extraSrcFilesUsingGlobSyntax)
++ " in the 'extra-source-files' field requires "
++ "'cabal-version: >= 1.6'. Alternatively if you require "
++ "compatibility with earlier Cabal versions then list all the files "
++ "explicitly."

-- check use of "source-repository" section
, checkVersion [1,6] (not (null (sourceRepos pkg))) $
PackageDistInexcusable $
Expand Down Expand Up @@ -1358,11 +1358,6 @@ checkCabalVersion pkg =
| otherwise = check cond pc

buildInfoField field = map field (allBuildInfo pkg)
dataFilesUsingGlobSyntax = filter usesGlobSyntax (dataFiles pkg)
extraSrcFilesUsingGlobSyntax = filter usesGlobSyntax (extraSrcFiles pkg)
usesGlobSyntax str = case parseFileGlob str of
Just (FileGlob _ _) -> True
_ -> False

versionRangeExpressions =
[ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
Expand Down
177 changes: 177 additions & 0 deletions Cabal/Distribution/Simple/Glob.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,177 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}

-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Simple.Glob
-- Copyright : Isaac Jones, Simon Marlow 2003-2004
-- License : BSD3
-- portions Copyright (c) 2007, Galois Inc.
--
-- Maintainer : [email protected]
-- Portability : portable
--
-- Simple file globbing.

module Distribution.Simple.Glob (
matchFileGlob,
matchDirFileGlob,
fileGlobMatches,
parseFileGlob,
explainGlobSyntaxError,
GlobSyntaxError(..),
GlobPat,
) where

import Prelude ()
import Distribution.Compat.Prelude

import Distribution.Simple.Utils
import Distribution.Verbosity
import Distribution.Version

import System.FilePath (joinPath, splitExtensions, splitDirectories, takeExtensions, (</>))

-- Note throughout that we use splitDirectories, not splitPath. On
-- Posix, this makes no difference, but, because Windows accepts both
-- slash and backslash as its path separators, if we left in the
-- separators from the glob we might not end up properly normalised.

data GlobSyntaxError
= StarInDirectory
| StarInFileName
| StarInExtension
| NoExtensionOnStar
| EmptyGlob
| LiteralFileNameGlobStar
| VersionDoesNotSupportGlobStar
| VersionDoesNotSupportGlob
deriving (Eq, Show)

explainGlobSyntaxError :: FilePath -> GlobSyntaxError -> String
explainGlobSyntaxError filepath StarInDirectory =
"invalid file glob '" ++ filepath
++ "'. A wildcard '**' is only allowed as the final parent"
++ " directory. Stars must not otherwise appear in the parent"
++ " directories."
explainGlobSyntaxError filepath StarInExtension =
"invalid file glob '" ++ filepath
++ "'. Wildcards '*' are only allowed as the"
++ " file's base name, not in the file extension."
explainGlobSyntaxError filepath StarInFileName =
"invalid file glob '" ++ filepath
++ "'. Wildcards '*' may only totally replace the"
++ " file's base name, not only parts of it."
explainGlobSyntaxError filepath NoExtensionOnStar =
"invalid file glob '" ++ filepath
++ "'. If a wildcard '*' is used it must be with an file extension."
explainGlobSyntaxError filepath LiteralFileNameGlobStar =
"invalid file glob '" ++ filepath
++ "'. If a wildcard '**' is used as a parent directory, the"
++ " file's base name must be a wildcard '*'."
explainGlobSyntaxError _ EmptyGlob =
"invalid file glob. A glob cannot be the empty string."
explainGlobSyntaxError filepath VersionDoesNotSupportGlobStar =
"invalid file glob '" ++ filepath
++ "'. Using the double-star syntax requires 'cabal-version: 3.0'"
++ " or greater. Alternatively, for compatibility with earlier Cabal"
++ " versions, list the included directories explicitly."
explainGlobSyntaxError filepath VersionDoesNotSupportGlob =
"invalid file glob '" ++ filepath
++ "'. Using star wildcards requires 'cabal-version: >= 1.6'. "
++ "Alternatively if you require compatibility with earlier Cabal "
++ "versions then list all the files explicitly."

data IsRecursive = Recursive | NonRecursive

data GlobPat = PatStem String GlobPat
-- ^ A single subdirectory component + remainder.
| PatMatch IsRecursive String
-- ^ First argument: Is this a @**/*.ext@ pattern?
-- Second argument: the extensions to accept.
| PatLit FilePath
-- ^ Literal file name.

fileGlobMatches :: GlobPat -> FilePath -> Bool
fileGlobMatches pat = fileGlobMatchesSegments pat . splitDirectories

fileGlobMatchesSegments :: GlobPat -> [FilePath] -> Bool
fileGlobMatchesSegments _ [] = False
fileGlobMatchesSegments pat (seg : segs) = case pat of
PatStem dir pat' ->
dir == seg && fileGlobMatchesSegments pat' segs
PatMatch Recursive ext ->
ext == takeExtensions (foldl' (flip const) seg segs)
PatMatch NonRecursive ext ->
null segs && ext == takeExtensions seg
PatLit filename ->
null segs && filename == seg

parseFileGlob :: Version -> FilePath -> Either GlobSyntaxError GlobPat
parseFileGlob version filepath = case reverse (splitDirectories filepath) of
[] ->
Left EmptyGlob
(filename : "**" : segments)
| allowGlobStar -> do
ext <- case splitExtensions filename of
("*", ext) | '*' `elem` ext -> Left StarInExtension
| null ext -> Left NoExtensionOnStar
| otherwise -> Right ext
_ -> Left LiteralFileNameGlobStar
foldM addStem (PatMatch Recursive ext) segments
| otherwise -> Left VersionDoesNotSupportGlobStar
(filename : segments) -> do
pat <- case splitExtensions filename of
("*", ext) | not allowGlob -> Left VersionDoesNotSupportGlob
| '*' `elem` ext -> Left StarInExtension
| null ext -> Left NoExtensionOnStar
| otherwise -> Right (PatMatch NonRecursive ext)
(_, ext) | '*' `elem` ext -> Left StarInExtension
| '*' `elem` filename -> Left StarInFileName
| otherwise -> Right (PatLit filename)
foldM addStem pat segments
where
allowGlob = version >= mkVersion [1,6]
allowGlobStar = version >= mkVersion [3,0]
addStem pat seg
| '*' `elem` seg = Left StarInDirectory
| otherwise = Right (PatStem seg pat)

matchFileGlob :: Verbosity -> Version -> FilePath -> IO [FilePath]
matchFileGlob verbosity version = matchDirFileGlob verbosity version "."

-- The returned values do not include the supplied @dir@ prefix.
matchDirFileGlob :: Verbosity -> Version -> FilePath -> FilePath -> IO [FilePath]
matchDirFileGlob verbosity version dir filepath = case parseFileGlob version filepath of
Left err -> die' verbosity $ explainGlobSyntaxError filepath err
Right pat -> do
-- This function might be called from the project root with dir as
-- ".". Walking the tree starting there involves going into .git/
-- and dist-newstyle/, which is a lot of work for no reward, so
-- extract the constant prefix from the pattern and start walking
-- there. If the pattern is **/*.blah, then of course we'll have
-- to walk the whole thing anyway, but that's what the user asked
-- for!
let (prefixSegments, pat') = splitConstantPrefix pat
joinedPrefix = joinPath prefixSegments
files <- getDirectoryContentsRecursive (dir </> joinedPrefix)
case filter (fileGlobMatches pat') files of
[] -> die' verbosity $
"filepath wildcard '" ++ filepath
++ "' does not match any files."
matches -> return $ fmap (joinedPrefix </>) matches

unfoldr' :: (a -> Either r (b, a)) -> a -> ([b], r)
unfoldr' f a = case f a of
Left r -> ([], r)
Right (b, a') -> case unfoldr' f a' of
(bs, r) -> (b : bs, r)

-- | Extract the (possibly null) constant prefix from the pattern.
-- This has the property that, if @(pref, pat') = splitConstantPrefix pat@,
-- then @pat === foldr PatStem pat' pref@.
splitConstantPrefix :: GlobPat -> ([FilePath], GlobPat)
splitConstantPrefix = unfoldr' step
where
step (PatStem seg pat) = Right (seg, pat)
step pat = Left pat
3 changes: 2 additions & 1 deletion Cabal/Distribution/Simple/Haddock.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,7 @@ import Distribution.Package
import qualified Distribution.ModuleName as ModuleName
import Distribution.PackageDescription as PD hiding (Flag)
import Distribution.Simple.Compiler hiding (Flag)
import Distribution.Simple.Glob
import Distribution.Simple.Program.GHC
import Distribution.Simple.Program.ResponseFile
import Distribution.Simple.Program
Expand Down Expand Up @@ -258,7 +259,7 @@ haddock pkg_descr lbi suffixes flags' = do
CBench _ -> when (flag haddockBenchmarks) $ smsg >> doExe component

for_ (extraDocFiles pkg_descr) $ \ fpath -> do
files <- matchFileGlob fpath
files <- matchFileGlob verbosity (specVersion pkg_descr) fpath
for_ files $ copyFileTo verbosity (unDir $ argOutputDir commonArgs)

-- ------------------------------------------------------------------------------
Expand Down
5 changes: 3 additions & 2 deletions Cabal/Distribution/Simple/Install.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,10 +33,11 @@ import Distribution.Package
import Distribution.PackageDescription
import Distribution.Simple.LocalBuildInfo
import Distribution.Simple.BuildPaths (haddockName, haddockPref)
import Distribution.Simple.Glob (matchDirFileGlob)
import Distribution.Simple.Utils
( createDirectoryIfMissingVerbose
, installDirectoryContents, installOrdinaryFile, isInSearchPath
, die', info, noticeNoWrap, warn, matchDirFileGlob )
, die', info, noticeNoWrap, warn )
import Distribution.Simple.Compiler
( CompilerFlavor(..), compilerFlavor )
import Distribution.Simple.Setup
Expand Down Expand Up @@ -235,7 +236,7 @@ installDataFiles :: Verbosity -> PackageDescription -> FilePath -> IO ()
installDataFiles verbosity pkg_descr destDataDir =
flip traverse_ (dataFiles pkg_descr) $ \ file -> do
let srcDataDir = dataDir pkg_descr
files <- matchDirFileGlob srcDataDir file
files <- matchDirFileGlob verbosity (specVersion pkg_descr) srcDataDir file
let dir = takeDirectory file
createDirectoryIfMissingVerbose verbosity True (destDataDir </> dir)
sequence_ [ installOrdinaryFile verbosity (srcDataDir </> file')
Expand Down
14 changes: 8 additions & 6 deletions Cabal/Distribution/Simple/SrcDist.hs
Original file line number Diff line number Diff line change
Expand Up @@ -52,6 +52,7 @@ import Distribution.Package
import Distribution.ModuleName
import qualified Distribution.ModuleName as ModuleName
import Distribution.Version
import Distribution.Simple.Glob
import Distribution.Simple.Utils
import Distribution.Simple.Setup
import Distribution.Simple.PreProcess
Expand Down Expand Up @@ -137,16 +138,16 @@ listPackageSources :: Verbosity -- ^ verbosity
listPackageSources verbosity pkg_descr0 pps = do
-- Call helpers that actually do all work.
ordinary <- listPackageSourcesOrdinary verbosity pkg_descr pps
maybeExecutable <- listPackageSourcesMaybeExecutable pkg_descr
maybeExecutable <- listPackageSourcesMaybeExecutable verbosity pkg_descr
return (ordinary, maybeExecutable)
where
pkg_descr = filterAutogenModules pkg_descr0

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

-- | List those source files that should be copied with ordinary permissions.
listPackageSourcesOrdinary :: Verbosity
Expand Down Expand Up @@ -208,12 +209,13 @@ listPackageSourcesOrdinary verbosity pkg_descr pps =
-- Data files.
, fmap concat
. for (dataFiles pkg_descr) $ \filename ->
matchFileGlob (dataDir pkg_descr </> filename)
fmap (fmap (dataDir pkg_descr </>)) $
matchDirFileGlob verbosity (specVersion pkg_descr) (dataDir pkg_descr) filename

-- Extra doc files.
, fmap concat
. for (extraDocFiles pkg_descr) $ \ filename ->
matchFileGlob filename
matchFileGlob verbosity (specVersion pkg_descr) filename

-- License file(s).
, return (licenseFiles pkg_descr)
Expand Down
Loading

0 comments on commit 5e83ef2

Please sign in to comment.