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 committed Apr 25, 2018
1 parent c750ef8 commit 8a00e00
Show file tree
Hide file tree
Showing 18 changed files with 387 additions and 74 deletions.
2 changes: 2 additions & 0 deletions Cabal/Cabal.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -258,6 +258,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 @@ -479,6 +480,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
3 changes: 3 additions & 0 deletions Cabal/ChangeLog.md
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,9 @@
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. (#3178 et al).

----

Expand Down
24 changes: 21 additions & 3 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 @@ -1358,11 +1377,10 @@ 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
usesGlobSyntax = not . isLiteralFileGlob

versionRangeExpressions =
[ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
Expand Down
145 changes: 145 additions & 0 deletions Cabal/Distribution/Simple/Glob.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,145 @@
{-# 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,
isLiteralFileGlob,
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 (splitExtensions, splitPath, takeExtensions)

data GlobSyntaxError
= StarInDirectory
| StarInFileName
| StarInExtension
| NoExtensionOnStar
| EmptyGlob
| LiteralFileNameGlobStar
| VersionDoesNotSupportGlobStar
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: 2.4'"
++ " or greater. Alternatively, for compatibility with earlier Cabal"
++ " versions, list the included directories explicitly."

data IsRecursive = Recursive | NonRecursive

data GlobPat = PatStem String GlobPat -- ^ A single subdirectory component + remainder.
| PatMatch IsRecursive -- ^ Is this a **/*.ext pattern?
String -- ^ Extensions
| PatLit FilePath -- ^ Literal file name.

isLiteralFileGlob :: FilePath -> Bool
isLiteralFileGlob filepath = case parseFileGlob (mkVersion [2,4]) filepath of
Left _ -> False
Right pat -> check pat
where
check (PatStem _ pat) = check pat
check (PatMatch _ _) = False
check (PatLit _) = True

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

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 (splitPath 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) | '*' `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
allowGlobStar = version >= mkVersion [2,4]
addStem pat seg
| '*' `elem` seg = Left StarInDirectory
| otherwise = Right (PatStem seg pat)

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

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
files <- getDirectoryContentsRecursive dir
case filter (fileGlobMatches pat) files of
[] -> die' verbosity $
"filepath wildcard '" ++ filepath
++ "' does not match any files."
matches -> return matches
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
13 changes: 7 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,12 @@ listPackageSourcesOrdinary verbosity pkg_descr pps =
-- Data files.
, fmap concat
. for (dataFiles pkg_descr) $ \filename ->
matchFileGlob (dataDir pkg_descr </> filename)
matchFileGlob 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
53 changes: 2 additions & 51 deletions Cabal/Distribution/Simple/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -108,12 +108,6 @@ module Distribution.Simple.Utils (
isInSearchPath,
addLibraryPath,

-- * simple file globbing
matchFileGlob,
matchDirFileGlob,
parseFileGlob,
FileGlob(..),

-- * modification time
moreRecentFile,
existsAndIsMoreRecentThan,
Expand Down Expand Up @@ -219,9 +213,8 @@ import System.Exit
( exitWith, ExitCode(..) )
import System.FilePath
( normalise, (</>), (<.>)
, getSearchPath, joinPath, takeDirectory, splitFileName
, splitExtension, splitExtensions, splitDirectories
, searchPathSeparator )
, getSearchPath, joinPath, takeDirectory, splitExtension
, splitDirectories, searchPathSeparator )
import System.IO
( Handle, hSetBinaryMode, hGetContents, stderr, stdout, hPutStr, hFlush
, hClose, hSetBuffering, BufferMode(..) )
Expand Down Expand Up @@ -1111,48 +1104,6 @@ addLibraryPath os paths = addEnv
else (key,value ++ (searchPathSeparator:pathsString)):xs
| otherwise = (key,value):addEnv xs

----------------
-- File globbing

data FileGlob
-- | No glob at all, just an ordinary file
= NoGlob FilePath

-- | dir prefix and extension, like @\"foo\/bar\/\*.baz\"@ corresponds to
-- @FileGlob \"foo\/bar\" \".baz\"@
| FileGlob FilePath String

parseFileGlob :: FilePath -> Maybe FileGlob
parseFileGlob filepath = case splitExtensions filepath of
(filepath', ext) -> case splitFileName filepath' of
(dir, "*") | '*' `elem` dir
|| '*' `elem` ext
|| null ext -> Nothing
| null dir -> Just (FileGlob "." ext)
| otherwise -> Just (FileGlob dir ext)
_ | '*' `elem` filepath -> Nothing
| otherwise -> Just (NoGlob filepath)

matchFileGlob :: FilePath -> IO [FilePath]
matchFileGlob = matchDirFileGlob "."

matchDirFileGlob :: FilePath -> FilePath -> IO [FilePath]
matchDirFileGlob dir filepath = case parseFileGlob filepath of
Nothing -> die $ "invalid file glob '" ++ filepath
++ "'. Wildcards '*' are only allowed in place of the file"
++ " name, not in the directory name or file extension."
++ " If a wildcard is used it must be with an file extension."
Just (NoGlob filepath') -> return [filepath']
Just (FileGlob dir' ext) -> do
files <- getDirectoryContents (dir </> dir')
case [ dir' </> file
| file <- files
, let (name, ext') = splitExtensions file
, not (null name) && ext' == ext ] of
[] -> die $ "filepath wildcard '" ++ filepath
++ "' does not match any files."
matches -> return matches

--------------------
-- Modification time

Expand Down
Loading

0 comments on commit 8a00e00

Please sign in to comment.