module Distribution.PackageDescription.Parse (
readGenericPackageDescription,
parseGenericPackageDescription,
readPackageDescription,
parsePackageDescription,
ParseResult(..),
FieldDescr(..),
LineNo,
TestSuiteStanza(..),
BenchmarkStanza(..),
readHookedBuildInfo,
parseHookedBuildInfo,
pkgDescrFieldDescrs,
libFieldDescrs,
foreignLibFieldDescrs,
executableFieldDescrs,
binfoFieldDescrs,
sourceRepoFieldDescrs,
testSuiteFieldDescrs,
benchmarkFieldDescrs,
flagFieldDescrs
) where
import Prelude ()
import Distribution.Compat.Prelude
import Distribution.Types.Dependency
import Distribution.Types.ForeignLib
import Distribution.Types.ForeignLibType
import Distribution.Types.UnqualComponentName
import Distribution.Types.CondTree
import Distribution.Types.PackageId
import Distribution.ParseUtils hiding (parseFields)
import Distribution.PackageDescription
import Distribution.PackageDescription.Utils
import Distribution.Package
import Distribution.ModuleName
import Distribution.Version
import Distribution.Verbosity
import Distribution.Compiler
import Distribution.PackageDescription.Configuration
import Distribution.Simple.Utils
import Distribution.Text
import Distribution.Compat.ReadP hiding (get)
import Data.List (partition, (\\))
import System.Directory (doesFileExist)
import Control.Monad (mapM)
import Text.PrettyPrint
(vcat, ($$), (<+>), text, render,
comma, fsep, nest, ($+$), punctuate)
pkgDescrFieldDescrs :: [FieldDescr PackageDescription]
pkgDescrFieldDescrs =
[ simpleField "name"
disp parse
packageName (\name pkg -> pkg{package=(package pkg){pkgName=name}})
, simpleField "version"
disp parse
packageVersion (\ver pkg -> pkg{package=(package pkg){pkgVersion=ver}})
, simpleField "cabal-version"
(either disp disp) (liftM Left parse +++ liftM Right parse)
specVersionRaw (\v pkg -> pkg{specVersionRaw=v})
, simpleField "build-type"
(maybe mempty disp) (fmap Just parse)
buildType (\t pkg -> pkg{buildType=t})
, simpleField "license"
disp parseLicenseQ
license (\l pkg -> pkg{license=l})
, simpleField "license-file"
showFilePath parseFilePathQ
(\pkg -> case licenseFiles pkg of
[x] -> x
_ -> "")
(\l pkg -> pkg{licenseFiles=licenseFiles pkg ++ [l]})
, listField "license-files"
showFilePath parseFilePathQ
(\pkg -> case licenseFiles pkg of
[_] -> []
xs -> xs)
(\ls pkg -> pkg{licenseFiles=ls})
, simpleField "copyright"
showFreeText parseFreeText
copyright (\val pkg -> pkg{copyright=val})
, simpleField "maintainer"
showFreeText parseFreeText
maintainer (\val pkg -> pkg{maintainer=val})
, simpleField "stability"
showFreeText parseFreeText
stability (\val pkg -> pkg{stability=val})
, simpleField "homepage"
showFreeText parseFreeText
homepage (\val pkg -> pkg{homepage=val})
, simpleField "package-url"
showFreeText parseFreeText
pkgUrl (\val pkg -> pkg{pkgUrl=val})
, simpleField "bug-reports"
showFreeText parseFreeText
bugReports (\val pkg -> pkg{bugReports=val})
, simpleField "synopsis"
showFreeText parseFreeText
synopsis (\val pkg -> pkg{synopsis=val})
, simpleField "description"
showFreeText parseFreeText
description (\val pkg -> pkg{description=val})
, simpleField "category"
showFreeText parseFreeText
category (\val pkg -> pkg{category=val})
, simpleField "author"
showFreeText parseFreeText
author (\val pkg -> pkg{author=val})
, listField "tested-with"
showTestedWith parseTestedWithQ
testedWith (\val pkg -> pkg{testedWith=val})
, listFieldWithSep vcat "data-files"
showFilePath parseFilePathQ
dataFiles (\val pkg -> pkg{dataFiles=val})
, simpleField "data-dir"
showFilePath parseFilePathQ
dataDir (\val pkg -> pkg{dataDir=val})
, listFieldWithSep vcat "extra-source-files"
showFilePath parseFilePathQ
extraSrcFiles (\val pkg -> pkg{extraSrcFiles=val})
, listFieldWithSep vcat "extra-tmp-files"
showFilePath parseFilePathQ
extraTmpFiles (\val pkg -> pkg{extraTmpFiles=val})
, listFieldWithSep vcat "extra-doc-files"
showFilePath parseFilePathQ
extraDocFiles (\val pkg -> pkg{extraDocFiles=val})
]
storeXFieldsPD :: UnrecFieldParser PackageDescription
storeXFieldsPD (f@('x':'-':_),val) pkg =
Just pkg{ customFieldsPD =
customFieldsPD pkg ++ [(f,val)]}
storeXFieldsPD _ _ = Nothing
libFieldDescrs :: [FieldDescr Library]
libFieldDescrs =
[ listFieldWithSep vcat "exposed-modules" disp parseModuleNameQ
exposedModules (\mods lib -> lib{exposedModules=mods})
, commaListFieldWithSep vcat "reexported-modules" disp parse
reexportedModules (\mods lib -> lib{reexportedModules=mods})
, listFieldWithSep vcat "signatures" disp parseModuleNameQ
signatures (\mods lib -> lib{signatures=mods})
, boolField "exposed"
libExposed (\val lib -> lib{libExposed=val})
] ++ map biToLib binfoFieldDescrs
where biToLib = liftField libBuildInfo (\bi lib -> lib{libBuildInfo=bi})
storeXFieldsLib :: UnrecFieldParser Library
storeXFieldsLib (f@('x':'-':_), val) l@(Library { libBuildInfo = bi }) =
Just $ l {libBuildInfo =
bi{ customFieldsBI = customFieldsBI bi ++ [(f,val)]}}
storeXFieldsLib _ _ = Nothing
foreignLibFieldDescrs :: [FieldDescr ForeignLib]
foreignLibFieldDescrs =
[ simpleField "type"
disp parse
foreignLibType (\x flib -> flib { foreignLibType = x })
, listField "options"
disp parse
foreignLibOptions (\x flib -> flib { foreignLibOptions = x })
, simpleField "lib-version-info"
(maybe mempty disp) (fmap Just parse)
foreignLibVersionInfo (\x flib -> flib { foreignLibVersionInfo = x })
, simpleField "lib-version-linux"
(maybe mempty disp) (fmap Just parse)
foreignLibVersionLinux (\x flib -> flib { foreignLibVersionLinux = x })
, listField "mod-def-file"
showFilePath parseFilePathQ
foreignLibModDefFile (\x flib -> flib { foreignLibModDefFile = x })
]
++ map biToFLib binfoFieldDescrs
where biToFLib = liftField foreignLibBuildInfo $ \bi flib ->
flib { foreignLibBuildInfo = bi }
storeXFieldsForeignLib :: UnrecFieldParser ForeignLib
storeXFieldsForeignLib (f@('x':'-':_), val)
l@(ForeignLib { foreignLibBuildInfo = bi }) =
Just $ l { foreignLibBuildInfo = bi {
customFieldsBI = (f,val):customFieldsBI bi
}
}
storeXFieldsForeignLib _ _ = Nothing
executableFieldDescrs :: [FieldDescr Executable]
executableFieldDescrs =
[ simpleField "main-is"
showFilePath parseFilePathQ
modulePath (\xs exe -> exe{modulePath=xs})
, simpleField "scope"
disp parse
exeScope (\sc exe -> exe{exeScope=sc})
]
++ map biToExe binfoFieldDescrs
where biToExe = liftField buildInfo (\bi exe -> exe{buildInfo=bi})
storeXFieldsExe :: UnrecFieldParser Executable
storeXFieldsExe (f@('x':'-':_), val) e@(Executable { buildInfo = bi }) =
Just $ e {buildInfo = bi{ customFieldsBI = (f,val):customFieldsBI bi}}
storeXFieldsExe _ _ = Nothing
data TestSuiteStanza = TestSuiteStanza {
testStanzaTestType :: Maybe TestType,
testStanzaMainIs :: Maybe FilePath,
testStanzaTestModule :: Maybe ModuleName,
testStanzaBuildInfo :: BuildInfo
}
emptyTestStanza :: TestSuiteStanza
emptyTestStanza = TestSuiteStanza Nothing Nothing Nothing mempty
testSuiteFieldDescrs :: [FieldDescr TestSuiteStanza]
testSuiteFieldDescrs =
[ simpleField "type"
(maybe mempty disp) (fmap Just parse)
testStanzaTestType (\x suite -> suite { testStanzaTestType = x })
, simpleField "main-is"
(maybe mempty showFilePath) (fmap Just parseFilePathQ)
testStanzaMainIs (\x suite -> suite { testStanzaMainIs = x })
, simpleField "test-module"
(maybe mempty disp) (fmap Just parseModuleNameQ)
testStanzaTestModule (\x suite -> suite { testStanzaTestModule = x })
]
++ map biToTest binfoFieldDescrs
where
biToTest = liftField testStanzaBuildInfo
(\bi suite -> suite { testStanzaBuildInfo = bi })
storeXFieldsTest :: UnrecFieldParser TestSuiteStanza
storeXFieldsTest (f@('x':'-':_), val) t@(TestSuiteStanza { testStanzaBuildInfo = bi }) =
Just $ t {testStanzaBuildInfo = bi{ customFieldsBI = (f,val):customFieldsBI bi}}
storeXFieldsTest _ _ = Nothing
validateTestSuite :: LineNo -> TestSuiteStanza -> ParseResult TestSuite
validateTestSuite line stanza =
case testStanzaTestType stanza of
Nothing -> return $
emptyTestSuite { testBuildInfo = testStanzaBuildInfo stanza }
Just tt@(TestTypeUnknown _ _) ->
return emptyTestSuite {
testInterface = TestSuiteUnsupported tt,
testBuildInfo = testStanzaBuildInfo stanza
}
Just tt | tt `notElem` knownTestTypes ->
return emptyTestSuite {
testInterface = TestSuiteUnsupported tt,
testBuildInfo = testStanzaBuildInfo stanza
}
Just tt@(TestTypeExe ver) ->
case testStanzaMainIs stanza of
Nothing -> syntaxError line (missingField "main-is" tt)
Just file -> do
when (isJust (testStanzaTestModule stanza)) $
warning (extraField "test-module" tt)
return emptyTestSuite {
testInterface = TestSuiteExeV10 ver file,
testBuildInfo = testStanzaBuildInfo stanza
}
Just tt@(TestTypeLib ver) ->
case testStanzaTestModule stanza of
Nothing -> syntaxError line (missingField "test-module" tt)
Just module_ -> do
when (isJust (testStanzaMainIs stanza)) $
warning (extraField "main-is" tt)
return emptyTestSuite {
testInterface = TestSuiteLibV09 ver module_,
testBuildInfo = testStanzaBuildInfo stanza
}
where
missingField name tt = "The '" ++ name ++ "' field is required for the "
++ display tt ++ " test suite type."
extraField name tt = "The '" ++ name ++ "' field is not used for the '"
++ display tt ++ "' test suite type."
data BenchmarkStanza = BenchmarkStanza {
benchmarkStanzaBenchmarkType :: Maybe BenchmarkType,
benchmarkStanzaMainIs :: Maybe FilePath,
benchmarkStanzaBenchmarkModule :: Maybe ModuleName,
benchmarkStanzaBuildInfo :: BuildInfo
}
emptyBenchmarkStanza :: BenchmarkStanza
emptyBenchmarkStanza = BenchmarkStanza Nothing Nothing Nothing mempty
benchmarkFieldDescrs :: [FieldDescr BenchmarkStanza]
benchmarkFieldDescrs =
[ simpleField "type"
(maybe mempty disp) (fmap Just parse)
benchmarkStanzaBenchmarkType
(\x suite -> suite { benchmarkStanzaBenchmarkType = x })
, simpleField "main-is"
(maybe mempty showFilePath) (fmap Just parseFilePathQ)
benchmarkStanzaMainIs
(\x suite -> suite { benchmarkStanzaMainIs = x })
]
++ map biToBenchmark binfoFieldDescrs
where
biToBenchmark = liftField benchmarkStanzaBuildInfo
(\bi suite -> suite { benchmarkStanzaBuildInfo = bi })
storeXFieldsBenchmark :: UnrecFieldParser BenchmarkStanza
storeXFieldsBenchmark (f@('x':'-':_), val)
t@(BenchmarkStanza { benchmarkStanzaBuildInfo = bi }) =
Just $ t {benchmarkStanzaBuildInfo =
bi{ customFieldsBI = (f,val):customFieldsBI bi}}
storeXFieldsBenchmark _ _ = Nothing
validateBenchmark :: LineNo -> BenchmarkStanza -> ParseResult Benchmark
validateBenchmark line stanza =
case benchmarkStanzaBenchmarkType stanza of
Nothing -> return $
emptyBenchmark { benchmarkBuildInfo = benchmarkStanzaBuildInfo stanza }
Just tt@(BenchmarkTypeUnknown _ _) ->
return emptyBenchmark {
benchmarkInterface = BenchmarkUnsupported tt,
benchmarkBuildInfo = benchmarkStanzaBuildInfo stanza
}
Just tt | tt `notElem` knownBenchmarkTypes ->
return emptyBenchmark {
benchmarkInterface = BenchmarkUnsupported tt,
benchmarkBuildInfo = benchmarkStanzaBuildInfo stanza
}
Just tt@(BenchmarkTypeExe ver) ->
case benchmarkStanzaMainIs stanza of
Nothing -> syntaxError line (missingField "main-is" tt)
Just file -> do
when (isJust (benchmarkStanzaBenchmarkModule stanza)) $
warning (extraField "benchmark-module" tt)
return emptyBenchmark {
benchmarkInterface = BenchmarkExeV10 ver file,
benchmarkBuildInfo = benchmarkStanzaBuildInfo stanza
}
where
missingField name tt = "The '" ++ name ++ "' field is required for the "
++ display tt ++ " benchmark type."
extraField name tt = "The '" ++ name ++ "' field is not used for the '"
++ display tt ++ "' benchmark type."
binfoFieldDescrs :: [FieldDescr BuildInfo]
binfoFieldDescrs =
[ boolField "buildable"
buildable (\val binfo -> binfo{buildable=val})
, commaListField "build-tools"
disp parse
buildTools (\xs binfo -> binfo{buildTools=xs})
, commaListField "build-tool-depends"
disp parse
buildToolDepends (\xs binfo -> binfo{buildToolDepends=xs})
, commaListFieldWithSep vcat "build-depends"
disp parse
targetBuildDepends (\xs binfo -> binfo{targetBuildDepends=xs})
, commaListFieldWithSep vcat "mixins"
disp parse
mixins (\xs binfo -> binfo{mixins=xs})
, spaceListField "cpp-options"
showToken parseTokenQ'
cppOptions (\val binfo -> binfo{cppOptions=val})
, spaceListField "cc-options"
showToken parseTokenQ'
ccOptions (\val binfo -> binfo{ccOptions=val})
, spaceListField "ld-options"
showToken parseTokenQ'
ldOptions (\val binfo -> binfo{ldOptions=val})
, commaListField "pkgconfig-depends"
disp parse
pkgconfigDepends (\xs binfo -> binfo{pkgconfigDepends=xs})
, listField "frameworks"
showToken parseTokenQ
frameworks (\val binfo -> binfo{frameworks=val})
, listField "extra-framework-dirs"
showToken parseFilePathQ
extraFrameworkDirs (\val binfo -> binfo{extraFrameworkDirs=val})
, listFieldWithSep vcat "c-sources"
showFilePath parseFilePathQ
cSources (\paths binfo -> binfo{cSources=paths})
, listFieldWithSep vcat "js-sources"
showFilePath parseFilePathQ
jsSources (\paths binfo -> binfo{jsSources=paths})
, simpleField "default-language"
(maybe mempty disp) (option Nothing (fmap Just parseLanguageQ))
defaultLanguage (\lang binfo -> binfo{defaultLanguage=lang})
, listField "other-languages"
disp parseLanguageQ
otherLanguages (\langs binfo -> binfo{otherLanguages=langs})
, listField "default-extensions"
disp parseExtensionQ
defaultExtensions (\exts binfo -> binfo{defaultExtensions=exts})
, listField "other-extensions"
disp parseExtensionQ
otherExtensions (\exts binfo -> binfo{otherExtensions=exts})
, listField "extensions"
disp parseExtensionQ
oldExtensions (\exts binfo -> binfo{oldExtensions=exts})
, listFieldWithSep vcat "extra-libraries"
showToken parseTokenQ
extraLibs (\xs binfo -> binfo{extraLibs=xs})
, listFieldWithSep vcat "extra-ghci-libraries"
showToken parseTokenQ
extraGHCiLibs (\xs binfo -> binfo{extraGHCiLibs=xs})
, listField "extra-lib-dirs"
showFilePath parseFilePathQ
extraLibDirs (\xs binfo -> binfo{extraLibDirs=xs})
, listFieldWithSep vcat "includes"
showFilePath parseFilePathQ
includes (\paths binfo -> binfo{includes=paths})
, listFieldWithSep vcat "install-includes"
showFilePath parseFilePathQ
installIncludes (\paths binfo -> binfo{installIncludes=paths})
, listField "include-dirs"
showFilePath parseFilePathQ
includeDirs (\paths binfo -> binfo{includeDirs=paths})
, listField "hs-source-dirs"
showFilePath parseFilePathQ
hsSourceDirs (\paths binfo -> binfo{hsSourceDirs=paths})
, listFieldWithSep vcat "other-modules"
disp parseModuleNameQ
otherModules (\val binfo -> binfo{otherModules=val})
, listFieldWithSep vcat "autogen-modules"
disp parseModuleNameQ
autogenModules (\val binfo -> binfo{autogenModules=val})
, optsField "ghc-prof-options" GHC
profOptions (\val binfo -> binfo{profOptions=val})
, optsField "ghcjs-prof-options" GHCJS
profOptions (\val binfo -> binfo{profOptions=val})
, optsField "ghc-shared-options" GHC
sharedOptions (\val binfo -> binfo{sharedOptions=val})
, optsField "ghcjs-shared-options" GHCJS
sharedOptions (\val binfo -> binfo{sharedOptions=val})
, optsField "ghc-options" GHC
options (\path binfo -> binfo{options=path})
, optsField "ghcjs-options" GHCJS
options (\path binfo -> binfo{options=path})
, optsField "jhc-options" JHC
options (\path binfo -> binfo{options=path})
, optsField "hugs-options" Hugs
options (const id)
, optsField "nhc98-options" NHC
options (const id)
]
storeXFieldsBI :: UnrecFieldParser BuildInfo
storeXFieldsBI (f@('x':'-':_),val) bi = Just bi{ customFieldsBI = (f,val):customFieldsBI bi }
storeXFieldsBI _ _ = Nothing
flagFieldDescrs :: [FieldDescr Flag]
flagFieldDescrs =
[ simpleField "description"
showFreeText parseFreeText
flagDescription (\val fl -> fl{ flagDescription = val })
, boolField "default"
flagDefault (\val fl -> fl{ flagDefault = val })
, boolField "manual"
flagManual (\val fl -> fl{ flagManual = val })
]
sourceRepoFieldDescrs :: [FieldDescr SourceRepo]
sourceRepoFieldDescrs =
[ simpleField "type"
(maybe mempty disp) (fmap Just parse)
repoType (\val repo -> repo { repoType = val })
, simpleField "location"
(maybe mempty showFreeText) (fmap Just parseFreeText)
repoLocation (\val repo -> repo { repoLocation = val })
, simpleField "module"
(maybe mempty showToken) (fmap Just parseTokenQ)
repoModule (\val repo -> repo { repoModule = val })
, simpleField "branch"
(maybe mempty showToken) (fmap Just parseTokenQ)
repoBranch (\val repo -> repo { repoBranch = val })
, simpleField "tag"
(maybe mempty showToken) (fmap Just parseTokenQ)
repoTag (\val repo -> repo { repoTag = val })
, simpleField "subdir"
(maybe mempty showFilePath) (fmap Just parseFilePathQ)
repoSubdir (\val repo -> repo { repoSubdir = val })
]
setupBInfoFieldDescrs :: [FieldDescr SetupBuildInfo]
setupBInfoFieldDescrs =
[ commaListFieldWithSep vcat "setup-depends"
disp parse
setupDepends (\xs binfo -> binfo{setupDepends=xs})
]
readAndParseFile :: (FilePath -> (String -> IO a) -> IO a)
-> (String -> ParseResult a)
-> Verbosity
-> FilePath -> IO a
readAndParseFile withFileContents' parser verbosity fpath = do
exists <- doesFileExist fpath
unless exists $
die' verbosity $
"Error Parsing: file \"" ++ fpath ++ "\" doesn't exist. Cannot continue."
withFileContents' fpath $ \str -> case parser str of
ParseFailed e -> do
let (line, message) = locatedErrorMsg e
dieWithLocation' verbosity fpath line message
ParseOk warnings x -> do
traverse_ (warn verbosity . showPWarning fpath) $ reverse warnings
return x
readHookedBuildInfo :: Verbosity -> FilePath -> IO HookedBuildInfo
readHookedBuildInfo =
readAndParseFile withFileContents parseHookedBuildInfo
readPackageDescription :: Verbosity -> FilePath -> IO GenericPackageDescription
readPackageDescription = readGenericPackageDescription
readGenericPackageDescription :: Verbosity -> FilePath -> IO GenericPackageDescription
readGenericPackageDescription =
readAndParseFile withUTF8FileContents parseGenericPackageDescription
stanzas :: [Field] -> [[Field]]
stanzas [] = []
stanzas (f:fields) = (f:this) : stanzas rest
where
(this, rest) = break isStanzaHeader fields
isStanzaHeader :: Field -> Bool
isStanzaHeader (F _ f _) = f == "executable"
isStanzaHeader _ = False
mapSimpleFields :: (Field -> ParseResult Field) -> [Field]
-> ParseResult [Field]
mapSimpleFields f = traverse walk
where
walk fld@F{} = f fld
walk (IfBlock l c fs1 fs2) = do
fs1' <- traverse walk fs1
fs2' <- traverse walk fs2
return (IfBlock l c fs1' fs2')
walk (Section ln n l fs1) = do
fs1' <- traverse walk fs1
return (Section ln n l fs1')
constraintFieldNames :: [String]
constraintFieldNames = ["build-depends"]
parseConstraint :: Field -> ParseResult [Dependency]
parseConstraint (F l n v)
| n `elem` constraintFieldNames = runP l n (parseCommaList parse) v
parseConstraint f = userBug $ "Constraint was expected (got: " ++ show f ++ ")"
libFieldNames :: [String]
libFieldNames = map fieldName libFieldDescrs
++ buildInfoNames ++ constraintFieldNames
buildInfoNames :: [String]
buildInfoNames = map fieldName binfoFieldDescrs
++ map fst deprecatedFieldsBuildInfo
newtype StT s m a = StT { runStT :: s -> m (a,s) }
instance Functor f => Functor (StT s f) where
fmap g (StT f) = StT $ fmap (first g) . f
#if __GLASGOW_HASKELL__ >= 710
instance (Monad m) => Applicative (StT s m) where
#else
instance (Monad m, Functor m) => Applicative (StT s m) where
#endif
pure a = StT (\s -> return (a,s))
(<*>) = ap
instance Monad m => Monad (StT s m) where
#if __GLASGOW_HASKELL__ < 710
return a = StT (\s -> return (a,s))
#endif
StT f >>= g = StT $ \s -> do
(a,s') <- f s
runStT (g a) s'
getSt :: Monad m => StT s m s
getSt = StT $ \s -> return (s, s)
modify :: Monad m => (s -> s) -> StT s m ()
modify f = StT $ \s -> return ((),f s)
lift :: Monad m => m a -> StT s m a
lift m = StT $ \s -> m >>= \a -> return (a,s)
evalStT :: Monad m => StT s m a -> s -> m a
evalStT st s = liftM fst $ runStT st s
type PM a = StT [Field] ParseResult a
peekField :: PM (Maybe Field)
peekField = liftM listToMaybe getSt
skipField :: PM ()
skipField = modify tail
parsePackageDescription :: String -> ParseResult GenericPackageDescription
parsePackageDescription = parseGenericPackageDescription
parseGenericPackageDescription :: String -> ParseResult GenericPackageDescription
parseGenericPackageDescription file = do
fields0 <- readFields file `catchParseError` \err ->
let tabs = findIndentTabs file in
case err of
TabsError tabLineNo -> reportTabsError
[ t | t@(lineNo',_) <- tabs
, lineNo' >= tabLineNo ]
_ -> parseFail err
let cabalVersionNeeded =
head $ [ minVersionBound versionRange
| Just versionRange <- [ simpleParse v
| F _ "cabal-version" v <- fields0 ] ]
++ [mkVersion [0]]
minVersionBound versionRange =
case asVersionIntervals versionRange of
[] -> mkVersion [0]
((LowerBound version _, _):_) -> version
handleFutureVersionParseFailure cabalVersionNeeded $ do
let sf = sectionizeFields fields0
fields <- mapSimpleFields deprecField sf
flip evalStT fields $ do
header_fields <- getHeader []
pkg <- lift $ parseFields pkgDescrFieldDescrs
storeXFieldsPD
emptyPackageDescription
header_fields
(repos, flags, mcsetup, mlib, sub_libs, flibs, exes, tests, bms) <- getBody pkg
warnIfRest
maybeWarnCabalVersion (not $ oldSyntax fields0) pkg
checkForUndefinedFlags flags mlib sub_libs exes tests
return $ GenericPackageDescription
pkg { sourceRepos = repos, setupBuildInfo = mcsetup }
flags mlib sub_libs flibs exes tests bms
where
oldSyntax = all isSimpleField
reportTabsError tabs =
syntaxError (fst (head tabs)) $
"Do not use tabs for indentation (use spaces instead)\n"
++ " Tabs were used at (line,column): " ++ show tabs
maybeWarnCabalVersion newsyntax pkg
| newsyntax && specVersion pkg < mkVersion [1,2]
= lift $ warning $
"A package using section syntax must specify at least\n"
++ "'cabal-version: >= 1.2'."
maybeWarnCabalVersion newsyntax pkg
| not newsyntax && specVersion pkg >= mkVersion [1,2]
= lift $ warning $
"A package using 'cabal-version: "
++ displaySpecVersion (specVersionRaw pkg)
++ "' must use section syntax. See the Cabal user guide for details."
where
displaySpecVersion (Left version) = display version
displaySpecVersion (Right versionRange) =
case asVersionIntervals versionRange of
[] -> display versionRange
((LowerBound version _, _):_) -> display (orLaterVersion version)
maybeWarnCabalVersion _ _ = return ()
handleFutureVersionParseFailure cabalVersionNeeded parseBody =
(unless versionOk (warning message) >> parseBody)
`catchParseError` \parseError -> case parseError of
TabsError _ -> parseFail parseError
_ | versionOk -> parseFail parseError
| otherwise -> fail message
where versionOk = cabalVersionNeeded <= cabalVersion
message = "This package requires at least Cabal version "
++ display cabalVersionNeeded
sectionizeFields :: [Field] -> [Field]
sectionizeFields fs
| oldSyntax fs =
let
(hdr0, exes0) = break ((=="executable") . fName) fs
(hdr, libfs0) = partition (not . (`elem` libFieldNames) . fName) hdr0
(deps, libfs) = partition ((== "build-depends") . fName)
libfs0
exes = unfoldr toExe exes0
toExe [] = Nothing
toExe (F l e n : r)
| e == "executable" =
let (efs, r') = break ((=="executable") . fName) r
in Just (Section l "executable" n (deps ++ efs), r')
toExe _ = cabalBug "unexpected input to 'toExe'"
in
hdr ++
(if null libfs then []
else [Section (lineNo (head libfs)) "library" "" (deps ++ libfs)])
++ exes
| otherwise = fs
isSimpleField F{} = True
isSimpleField _ = False
warnIfRest :: PM ()
warnIfRest = do
s <- getSt
case s of
[] -> return ()
_ -> lift $ warning "Ignoring trailing declarations."
getHeader :: [Field] -> PM [Field]
getHeader acc = peekField >>= \mf -> case mf of
Just f@F{} -> skipField >> getHeader (f:acc)
_ -> return (reverse acc)
getBody :: PackageDescription
-> PM ([SourceRepo], [Flag]
,Maybe SetupBuildInfo
,(Maybe (CondTree ConfVar [Dependency] Library))
,[(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
,[(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
,[(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
,[(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
,[(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)])
getBody pkg = peekField >>= \mf -> case mf of
Just (Section line_no sec_type sec_label sec_fields)
| sec_type == "executable" -> do
when (null sec_label) $ lift $ syntaxError line_no
"'executable' needs one argument (the executable's name)"
exename <- lift $ runP line_no "executable" parseTokenQ sec_label
flds <- collectFields parseExeFields sec_fields
skipField
(repos, flags, csetup, mlib, sub_libs, flibs, exes, tests, bms) <- getBody pkg
return (repos, flags, csetup, mlib, sub_libs, flibs, (mkUnqualComponentName exename, flds): exes, tests, bms)
| sec_type == "foreign-library" -> do
when (null sec_label) $ lift $ syntaxError line_no
"'foreign-library' needs one argument (the library's name)"
libname <- lift $ runP line_no "foreign-library" parseTokenQ sec_label
flds <- collectFields parseForeignLibFields sec_fields
let hasType ts = foreignLibType ts /= foreignLibType mempty
if onAllBranches hasType flds
then do
skipField
(repos, flags, csetup, mlib, sub_libs, flibs, exes, tests, bms) <- getBody pkg
return (repos, flags, csetup, mlib, sub_libs, (mkUnqualComponentName libname, flds):flibs, exes, tests, bms)
else lift $ syntaxError line_no $
"Foreign library \"" ++ libname
++ "\" is missing required field \"type\" or the field "
++ "is not present in all conditional branches. The "
++ "available test types are: "
++ intercalate ", " (map display knownForeignLibTypes)
| sec_type == "test-suite" -> do
when (null sec_label) $ lift $ syntaxError line_no
"'test-suite' needs one argument (the test suite's name)"
testname <- lift $ runP line_no "test" parseTokenQ sec_label
flds <- collectFields (parseTestFields line_no) sec_fields
let hasType ts = testInterface ts /= testInterface mempty
if onAllBranches hasType flds
then do
skipField
(repos, flags, csetup, mlib, sub_libs, flibs, exes, tests, bms) <- getBody pkg
return (repos, flags, csetup, mlib, sub_libs, flibs, exes,
(mkUnqualComponentName testname, flds) : tests, bms)
else lift $ syntaxError line_no $
"Test suite \"" ++ testname
++ "\" is missing required field \"type\" or the field "
++ "is not present in all conditional branches. The "
++ "available test types are: "
++ intercalate ", " (map display knownTestTypes)
| sec_type == "benchmark" -> do
when (null sec_label) $ lift $ syntaxError line_no
"'benchmark' needs one argument (the benchmark's name)"
benchname <- lift $ runP line_no "benchmark" parseTokenQ sec_label
flds <- collectFields (parseBenchmarkFields line_no) sec_fields
let hasType ts = benchmarkInterface ts /= benchmarkInterface mempty
if onAllBranches hasType flds
then do
skipField
(repos, flags, csetup, mlib, sub_libs, flibs, exes, tests, bms) <- getBody pkg
return (repos, flags, csetup, mlib, sub_libs, flibs, exes,
tests, (mkUnqualComponentName benchname, flds) : bms)
else lift $ syntaxError line_no $
"Benchmark \"" ++ benchname
++ "\" is missing required field \"type\" or the field "
++ "is not present in all conditional branches. The "
++ "available benchmark types are: "
++ intercalate ", " (map display knownBenchmarkTypes)
| sec_type == "library" -> do
mb_libname <- if null sec_label
then return Nothing
else fmap Just . lift
$ runP line_no "library" parseTokenQ sec_label
flds <- collectFields parseLibFields sec_fields
skipField
(repos, flags, csetup, mlib, sub_libs, flibs, exes, tests, bms) <- getBody pkg
case mb_libname of
Just libname ->
return (repos, flags, csetup, mlib, (mkUnqualComponentName libname, flds) : sub_libs, flibs, exes, tests, bms)
Nothing -> do
when (isJust mlib) $ lift $ syntaxError line_no
"There can only be one (public) library section in a package description."
return (repos, flags, csetup, Just flds, sub_libs, flibs, exes, tests, bms)
| sec_type == "flag" -> do
when (null sec_label) $ lift $
syntaxError line_no "'flag' needs one argument (the flag's name)"
flag <- lift $ parseFields
flagFieldDescrs
warnUnrec
(emptyFlag (mkFlagName (lowercase sec_label)))
sec_fields
skipField
(repos, flags, csetup, mlib, sub_libs, flibs, exes, tests, bms) <- getBody pkg
return (repos, flag:flags, csetup, mlib, sub_libs, flibs, exes, tests, bms)
| sec_type == "source-repository" -> do
when (null sec_label) $ lift $ syntaxError line_no $
"'source-repository' needs one argument, "
++ "the repo kind which is usually 'head' or 'this'"
kind <- case simpleParse sec_label of
Just kind -> return kind
Nothing -> lift $ syntaxError line_no $
"could not parse repo kind: " ++ sec_label
repo <- lift $ parseFields
sourceRepoFieldDescrs
warnUnrec
(emptySourceRepo kind)
sec_fields
skipField
(repos, flags, csetup, mlib, sub_libs, flibs, exes, tests, bms) <- getBody pkg
return (repo:repos, flags, csetup, mlib, sub_libs, flibs, exes, tests, bms)
| sec_type == "custom-setup" -> do
unless (null sec_label) $ lift $
syntaxError line_no "'setup' expects no argument"
flds <- lift $ parseFields
setupBInfoFieldDescrs
warnUnrec
mempty
sec_fields
skipField
(repos, flags, csetup0, mlib, sub_libs, flibs, exes, tests, bms) <- getBody pkg
when (isJust csetup0) $ lift $ syntaxError line_no
"There can only be one 'custom-setup' section in a package description."
return (repos, flags, Just flds, mlib, sub_libs, flibs, exes, tests, bms)
| otherwise -> do
lift $ warning $ "Ignoring unknown section type: " ++ sec_type
skipField
getBody pkg
Just f@(F {}) -> do
_ <- lift $ syntaxError (lineNo f) $
"Plain fields are not allowed in between stanzas: " ++ show f
skipField
getBody pkg
Just f@(IfBlock {}) -> do
_ <- lift $ syntaxError (lineNo f) $
"If-blocks are not allowed in between stanzas: " ++ show f
skipField
getBody pkg
Nothing -> return ([], [], Nothing, Nothing, [], [], [], [], [])
collectFields :: ([Field] -> PM a) -> [Field]
-> PM (CondTree ConfVar [Dependency] a)
collectFields parser allflds = do
let simplFlds = [ F l n v | F l n v <- allflds ]
condFlds = [ f | f@IfBlock{} <- allflds ]
sections = [ s | s@Section{} <- allflds ]
traverse_
(\(Section l n _ _) -> lift . warning $
"Unexpected section '" ++ n ++ "' on line " ++ show l)
sections
a <- parser simplFlds
deps <- liftM concat
. traverse (lift . parseConstraint)
. filter isConstraint
$ simplFlds
ifs <- traverse processIfs condFlds
return (CondNode a deps ifs)
where
isConstraint (F _ n _) = n `elem` constraintFieldNames
isConstraint _ = False
processIfs (IfBlock l c t e) = do
cnd <- lift $ runP l "if" parseCondition c
t' <- collectFields parser t
e' <- case e of
[] -> return Nothing
es -> do fs <- collectFields parser es
return (Just fs)
return (CondBranch cnd t' e')
processIfs _ = cabalBug "processIfs called with wrong field type"
parseLibFields :: [Field] -> PM Library
parseLibFields = lift . parseFields libFieldDescrs storeXFieldsLib emptyLibrary
parseExeFields :: [Field] -> PM Executable
parseExeFields = lift . parseFields executableFieldDescrs
storeXFieldsExe emptyExecutable
parseForeignLibFields :: [Field] -> PM ForeignLib
parseForeignLibFields =
lift . parseFields foreignLibFieldDescrs
storeXFieldsForeignLib
emptyForeignLib
parseTestFields :: LineNo -> [Field] -> PM TestSuite
parseTestFields line fields = do
x <- lift $ parseFields testSuiteFieldDescrs storeXFieldsTest
emptyTestStanza fields
lift $ validateTestSuite line x
parseBenchmarkFields :: LineNo -> [Field] -> PM Benchmark
parseBenchmarkFields line fields = do
x <- lift $ parseFields benchmarkFieldDescrs storeXFieldsBenchmark
emptyBenchmarkStanza fields
lift $ validateBenchmark line x
checkForUndefinedFlags ::
[Flag] ->
Maybe (CondTree ConfVar [Dependency] Library) ->
[(UnqualComponentName, CondTree ConfVar [Dependency] Library)] ->
[(UnqualComponentName, CondTree ConfVar [Dependency] Executable)] ->
[(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)] ->
PM ()
checkForUndefinedFlags flags mlib sub_libs exes tests = do
let definedFlags = map flagName flags
traverse_ (checkCondTreeFlags definedFlags) (maybeToList mlib)
traverse_ (checkCondTreeFlags definedFlags . snd) sub_libs
traverse_ (checkCondTreeFlags definedFlags . snd) exes
traverse_ (checkCondTreeFlags definedFlags . snd) tests
checkCondTreeFlags :: [FlagName] -> CondTree ConfVar c a -> PM ()
checkCondTreeFlags definedFlags ct = do
let fv = nub $ freeVars ct
unless (all (`elem` definedFlags) fv) $
fail $ "These flags are used without having been defined: "
++ intercalate ", " [ unFlagName fn | fn <- fv \\ definedFlags ]
onAllBranches :: forall v c a. Monoid a => (a -> Bool) -> CondTree v c a -> Bool
onAllBranches p = go mempty
where
go :: a -> CondTree v c a -> Bool
go acc ct = let acc' = acc `mappend` condTreeData ct
in p acc' || any (goBranch acc') (condTreeComponents ct)
goBranch :: a -> CondBranch v c a -> Bool
goBranch _ (CondBranch _ _ Nothing) = False
goBranch acc (CondBranch _ t (Just e)) = go acc t && go acc e
parseFields :: [FieldDescr a]
-> UnrecFieldParser a
-> a
-> [Field]
-> ParseResult a
parseFields descrs unrec ini fields =
do (a, unknowns) <- foldM (parseField descrs unrec) (ini, []) fields
unless (null unknowns) $ warning $ render $
text "Unknown fields:" <+>
commaSep (map (\(l,u) -> u ++ " (line " ++ show l ++ ")")
(reverse unknowns))
$+$
text "Fields allowed in this section:" $$
nest 4 (commaSep $ map fieldName descrs)
return a
where
commaSep = fsep . punctuate comma . map text
parseField :: [FieldDescr a]
-> UnrecFieldParser a
-> (a,[(Int,String)])
-> Field
-> ParseResult (a, [(Int,String)])
parseField (FieldDescr name _ parser : fields) unrec (a, us) (F line f val)
| name == f = parser line val a >>= \a' -> return (a',us)
| otherwise = parseField fields unrec (a,us) (F line f val)
parseField [] unrec (a,us) (F l f val) = return $
case unrec (f,val) a of
Just a' -> (a',us)
Nothing -> (a, (l,f):us)
parseField _ _ _ _ = cabalBug "'parseField' called on a non-field"
deprecatedFields :: [(String,String)]
deprecatedFields =
deprecatedFieldsPkgDescr ++ deprecatedFieldsBuildInfo
deprecatedFieldsPkgDescr :: [(String,String)]
deprecatedFieldsPkgDescr = [ ("other-files", "extra-source-files") ]
deprecatedFieldsBuildInfo :: [(String,String)]
deprecatedFieldsBuildInfo = [ ("hs-source-dir","hs-source-dirs") ]
deprecField :: Field -> ParseResult Field
deprecField (F line fld val) = do
fld' <- case lookup fld deprecatedFields of
Nothing -> return fld
Just newName -> do
warning $ "The field \"" ++ fld
++ "\" is deprecated, please use \"" ++ newName ++ "\""
return newName
return (F line fld' val)
deprecField _ = cabalBug "'deprecField' called on a non-field"
parseHookedBuildInfo :: String -> ParseResult HookedBuildInfo
parseHookedBuildInfo inp = do
fields <- readFields inp
let ss@(mLibFields:exes) = stanzas fields
mLib <- parseLib mLibFields
biExes <- mapM parseExe (maybe ss (const exes) mLib)
return (mLib, biExes)
where
parseLib :: [Field] -> ParseResult (Maybe BuildInfo)
parseLib (bi@(F _ inFieldName _:_))
| lowercase inFieldName /= "executable" = liftM Just (parseBI bi)
parseLib _ = return Nothing
parseExe :: [Field] -> ParseResult (UnqualComponentName, BuildInfo)
parseExe (F line inFieldName mName:bi)
| lowercase inFieldName == "executable"
= do bis <- parseBI bi
return (mkUnqualComponentName mName, bis)
| otherwise = syntaxError line "expecting 'executable' at top of stanza"
parseExe (_:_) = cabalBug "`parseExe' called on a non-field"
parseExe [] = syntaxError 0 "error in parsing buildinfo file. Expected executable stanza"
parseBI st = parseFields binfoFieldDescrs storeXFieldsBI emptyBuildInfo st
findIndentTabs :: String -> [(Int,Int)]
findIndentTabs = concatMap checkLine
. zip [1..]
. lines
where
checkLine (lineno, l) =
let (indent, _content) = span isSpace l
tabCols = map fst . filter ((== '\t') . snd) . zip [0..]
addLineNo = map (\col -> (lineno,col))
in addLineNo (tabCols indent)