diff --git a/Cabal-syntax/src/Distribution/PackageDescription/FieldGrammar.hs b/Cabal-syntax/src/Distribution/PackageDescription/FieldGrammar.hs index cf6f0536b041128a5aaa6499d754215e718661df..ea077bbee220ede9b9e4829f217a09c08b959c1e 100644 --- a/Cabal-syntax/src/Distribution/PackageDescription/FieldGrammar.hs +++ b/Cabal-syntax/src/Distribution/PackageDescription/FieldGrammar.hs @@ -268,6 +268,7 @@ data TestSuiteStanza = TestSuiteStanza , _testStanzaMainIs :: Maybe FilePath , _testStanzaTestModule :: Maybe ModuleName , _testStanzaBuildInfo :: BuildInfo + , _testStanzaCodeGenerators :: [String] } instance L.HasBuildInfo TestSuiteStanza where @@ -289,6 +290,10 @@ testStanzaBuildInfo :: Lens' TestSuiteStanza BuildInfo testStanzaBuildInfo f s = fmap (\x -> s { _testStanzaBuildInfo = x }) (f (_testStanzaBuildInfo s)) {-# INLINE testStanzaBuildInfo #-} +testStanzaCodeGenerators :: Lens' TestSuiteStanza [String] +testStanzaCodeGenerators f s = fmap (\x -> s { _testStanzaCodeGenerators = x }) (f (_testStanzaCodeGenerators s)) +{-# INLINE testStanzaCodeGenerators #-} + testSuiteFieldGrammar :: ( FieldGrammar c g, Applicative (g TestSuiteStanza), Applicative (g BuildInfo) , c (Identity ModuleName) @@ -296,6 +301,7 @@ testSuiteFieldGrammar , c (List CommaFSep (Identity ExeDependency) ExeDependency) , c (List CommaFSep (Identity LegacyExeDependency) LegacyExeDependency) , c (List CommaFSep (Identity PkgconfigDependency) PkgconfigDependency) + , c (List CommaFSep Token String) , c (List CommaVCat (Identity Dependency) Dependency) , c (List CommaVCat (Identity Mixin) Mixin) , c (List FSep (MQuoted Extension) Extension) @@ -315,23 +321,20 @@ testSuiteFieldGrammar = TestSuiteStanza <*> optionalFieldAla "main-is" FilePathNT testStanzaMainIs <*> optionalField "test-module" testStanzaTestModule <*> blurFieldGrammar testStanzaBuildInfo buildInfoFieldGrammar + <*> monoidalFieldAla "code-generators" (alaList' CommaFSep Token) testStanzaCodeGenerators + ^^^ availableSince CabalSpecV3_6 [] -- TODO 3_8 validateTestSuite :: Position -> TestSuiteStanza -> ParseResult TestSuite validateTestSuite pos stanza = case _testStanzaTestType stanza of - Nothing -> return $ - emptyTestSuite { testBuildInfo = _testStanzaBuildInfo stanza } + Nothing -> pure basicTestSuite Just tt@(TestTypeUnknown _ _) -> - pure emptyTestSuite - { testInterface = TestSuiteUnsupported tt - , testBuildInfo = _testStanzaBuildInfo stanza - } + pure basicTestSuite + { testInterface = TestSuiteUnsupported tt } Just tt | tt `notElem` knownTestTypes -> - pure emptyTestSuite - { testInterface = TestSuiteUnsupported tt - , testBuildInfo = _testStanzaBuildInfo stanza - } + pure basicTestSuite + { testInterface = TestSuiteUnsupported tt } Just tt@(TestTypeExe ver) -> case _testStanzaMainIs stanza of Nothing -> do @@ -340,22 +343,18 @@ validateTestSuite pos stanza = case _testStanzaTestType stanza of Just file -> do when (isJust (_testStanzaTestModule stanza)) $ parseWarning pos PWTExtraBenchmarkModule (extraField "test-module" tt) - pure emptyTestSuite - { testInterface = TestSuiteExeV10 ver file - , testBuildInfo = _testStanzaBuildInfo stanza - } + pure basicTestSuite + { testInterface = TestSuiteExeV10 ver file } Just tt@(TestTypeLib ver) -> case _testStanzaTestModule stanza of Nothing -> do - parseFailure pos (missingField "test-module" tt) - pure emptyTestSuite + parseFailure pos (missingField "test-module" tt) + pure emptyTestSuite Just module_ -> do when (isJust (_testStanzaMainIs stanza)) $ parseWarning pos PWTExtraMainIs (extraField "main-is" tt) - pure emptyTestSuite - { testInterface = TestSuiteLibV09 ver module_ - , testBuildInfo = _testStanzaBuildInfo stanza - } + pure basicTestSuite + { testInterface = TestSuiteLibV09 ver module_ } where missingField name tt = "The '" ++ name ++ "' field is required for the " @@ -363,6 +362,11 @@ validateTestSuite pos stanza = case _testStanzaTestType stanza of extraField name tt = "The '" ++ name ++ "' field is not used for the '" ++ prettyShow tt ++ "' test suite type." + basicTestSuite = + emptyTestSuite { + testBuildInfo = _testStanzaBuildInfo stanza + , testCodeGenerators = _testStanzaCodeGenerators stanza + } unvalidateTestSuite :: TestSuite -> TestSuiteStanza unvalidateTestSuite t = TestSuiteStanza @@ -370,6 +374,7 @@ unvalidateTestSuite t = TestSuiteStanza , _testStanzaMainIs = ma , _testStanzaTestModule = mo , _testStanzaBuildInfo = testBuildInfo t + , _testStanzaCodeGenerators = testCodeGenerators t } where (ty, ma, mo) = case testInterface t of diff --git a/Cabal-syntax/src/Distribution/PackageDescription/Parsec.hs b/Cabal-syntax/src/Distribution/PackageDescription/Parsec.hs index b4a8a6dae1d8b3ff8b0966ca07bda1e35a015349..5f19e740e75177c0d192843cf0e1c4d2c00e01dc 100644 --- a/Cabal-syntax/src/Distribution/PackageDescription/Parsec.hs +++ b/Cabal-syntax/src/Distribution/PackageDescription/Parsec.hs @@ -566,7 +566,7 @@ instance FromBuildInfo ForeignLib where fromBuildInfo' n bi = set L.foreignLibNa instance FromBuildInfo Executable where fromBuildInfo' n bi = set L.exeName n $ set L.buildInfo bi emptyExecutable instance FromBuildInfo TestSuiteStanza where - fromBuildInfo' _ bi = TestSuiteStanza Nothing Nothing Nothing bi + fromBuildInfo' _ bi = TestSuiteStanza Nothing Nothing Nothing bi [] instance FromBuildInfo BenchmarkStanza where fromBuildInfo' _ bi = BenchmarkStanza Nothing Nothing Nothing bi @@ -671,7 +671,7 @@ onAllBranches p = go mempty -- Post parsing checks ------------------------------------------------------------------------------- --- | Check that we +-- | Check that we -- -- * don't use undefined flags (very bad) -- * define flags which are unused (just bad) diff --git a/Cabal-syntax/src/Distribution/Types/TestSuite.hs b/Cabal-syntax/src/Distribution/Types/TestSuite.hs index 3eab5f81fd87d860fce0e9094a7064c6a2528989..b904f7709e5c0817707306a38d4f714153948718 100644 --- a/Cabal-syntax/src/Distribution/Types/TestSuite.hs +++ b/Cabal-syntax/src/Distribution/Types/TestSuite.hs @@ -26,7 +26,8 @@ import qualified Distribution.Types.BuildInfo.Lens as L data TestSuite = TestSuite { testName :: UnqualComponentName, testInterface :: TestSuiteInterface, - testBuildInfo :: BuildInfo + testBuildInfo :: BuildInfo, + testCodeGenerators :: [String] } deriving (Generic, Show, Read, Eq, Typeable, Data) @@ -42,7 +43,8 @@ instance Monoid TestSuite where mempty = TestSuite { testName = mempty, testInterface = mempty, - testBuildInfo = mempty + testBuildInfo = mempty, + testCodeGenerators = mempty } mappend = (<>) @@ -50,7 +52,8 @@ instance Semigroup TestSuite where a <> b = TestSuite { testName = combine' testName, testInterface = combine testInterface, - testBuildInfo = combine testBuildInfo + testBuildInfo = combine testBuildInfo, + testCodeGenerators = combine testCodeGenerators } where combine field = field a `mappend` field b combine' field = case ( unUnqualComponentName $ field a diff --git a/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.expr b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.expr index 30e676cff1125ae3c9c14fa88c45600800846e34..d754955f46d9dca807fd48aedba13bd1f87a853a 100644 --- a/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.expr +++ b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.expr @@ -1,366 +1,393 @@ -GenericPackageDescription - {condBenchmarks = [], - condExecutables = [], - condForeignLibs = [], - condLibrary = Just - CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName "base") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [4, 0])) - (EarlierVersion (mkVersion [4, 7]))) - mainLibSet, - Dependency - (PackageName "AC-Vector") - (OrLaterVersion (mkVersion [2, 3, 0])) - mainLibSet, - Dependency - (PackageName "QuickCheck") - (OrLaterVersion (mkVersion [2, 4, 0])) - mainLibSet], - condTreeData = Library - {exposedModules = [ModuleName "Data.Octree"], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [EnableExtension - ScopedTypeVariables], - options = PerCompilerFlavor [] [], - otherExtensions = [], - otherLanguages = [], - otherModules = [ModuleName - "Data.Octree.Internal"], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor [] [], - sharedOptions = PerCompilerFlavor [] [], - staticOptions = PerCompilerFlavor [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [4, 0])) - (EarlierVersion - (mkVersion - [4, 7]))) - mainLibSet, - Dependency - (PackageName - "AC-Vector") - (OrLaterVersion - (mkVersion - [2, 3, 0])) - mainLibSet, - Dependency - (PackageName - "QuickCheck") - (OrLaterVersion - (mkVersion - [2, 4, 0])) - mainLibSet], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}, - condSubLibraries = [], - condTestSuites = [_×_ - (UnqualComponentName "test_Octree") - CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName "base") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [4, 0])) - (EarlierVersion (mkVersion [4, 7]))) - mainLibSet, - Dependency - (PackageName "AC-Vector") - (OrLaterVersion (mkVersion [2, 3, 0])) - mainLibSet, - Dependency - (PackageName "QuickCheck") - (OrLaterVersion (mkVersion [2, 4, 0])) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor [] [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] [], - sharedOptions = PerCompilerFlavor - [] [], - staticOptions = PerCompilerFlavor - [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [4, - 0])) - (EarlierVersion - (mkVersion - [4, - 7]))) - mainLibSet, - Dependency - (PackageName - "AC-Vector") - (OrLaterVersion - (mkVersion - [2, - 3, - 0])) - mainLibSet, - Dependency - (PackageName - "QuickCheck") - (OrLaterVersion - (mkVersion - [2, - 4, - 0])) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteExeV10 - (mkVersion [1, 0]) - "tests/test_Octree.hs", - testName = UnqualComponentName ""}}, - _×_ - (UnqualComponentName "readme") - CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName "base") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [4, 0])) - (EarlierVersion (mkVersion [4, 7]))) - mainLibSet, - Dependency - (PackageName "AC-Vector") - (OrLaterVersion (mkVersion [2, 3, 0])) - mainLibSet, - Dependency - (PackageName "QuickCheck") - (OrLaterVersion (mkVersion [2, 4, 0])) - mainLibSet, - Dependency - (PackageName "markdown-unlit") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - ["-pgmL", - "markdown-unlit"] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] [], - sharedOptions = PerCompilerFlavor - [] [], - staticOptions = PerCompilerFlavor - [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [4, - 0])) - (EarlierVersion - (mkVersion - [4, - 7]))) - mainLibSet, - Dependency - (PackageName - "AC-Vector") - (OrLaterVersion - (mkVersion - [2, - 3, - 0])) - mainLibSet, - Dependency - (PackageName - "QuickCheck") - (OrLaterVersion - (mkVersion - [2, - 4, - 0])) - mainLibSet, - Dependency - (PackageName - "markdown-unlit") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteExeV10 - (mkVersion [1, 0]) "README.lhs", - testName = UnqualComponentName ""}}], - genPackageFlags = [], - gpdScannedVersion = Nothing, - packageDescription = PackageDescription - {author = "Michal J. Gajda", - benchmarks = [], - bugReports = "mailto:mjgajda@googlemail.com", - buildTypeRaw = Just Simple, - category = "Data", - copyright = "Copyright by Michal J. Gajda '2012", - customFieldsPD = [], - dataDir = ".", - dataFiles = [], - description = "Octree data structure is relatively shallow data structure for space partitioning.", - executables = [], - extraDocFiles = [], - extraSrcFiles = [], - extraTmpFiles = [], - foreignLibs = [], - homepage = "https://github.com/mgajda/octree", - library = Nothing, - licenseFiles = [SymbolicPath "LICENSE"], - licenseRaw = Right BSD3, - maintainer = "mjgajda@googlemail.com", - package = PackageIdentifier - {pkgName = PackageName "Octree", - pkgVersion = mkVersion [0, 5]}, - pkgUrl = "http://hackage.haskell.org/package/octree", - setupBuildInfo = Nothing, - sourceRepos = [SourceRepo - {repoBranch = Nothing, - repoKind = RepoHead, - repoLocation = Just "git@github.com:mgajda/octree.git", - repoModule = Nothing, - repoSubdir = Nothing, - repoTag = Nothing, - repoType = Just (KnownRepoType Git)}], - specVersion = CabalSpecV1_8, - stability = "beta", - subLibraries = [], - synopsis = "Simple unbalanced Octree for storing data about 3D points", - testSuites = [], - testedWith = [_×_ GHC (ThisVersion (mkVersion [7, 0, 4])), - _×_ GHC (ThisVersion (mkVersion [7, 4, 1])), - _×_ GHC (ThisVersion (mkVersion [7, 4, 2])), - _×_ GHC (ThisVersion (mkVersion [7, 6, 0]))]}} +GenericPackageDescription { + packageDescription = + PackageDescription { + specVersion = CabalSpecV1_8, + package = PackageIdentifier { + pkgName = PackageName "Octree", + pkgVersion = mkVersion [0, 5]}, + licenseRaw = Right BSD3, + licenseFiles = [ + SymbolicPath "LICENSE"], + copyright = + "Copyright by Michal J. Gajda '2012", + maintainer = + "mjgajda@googlemail.com", + author = "Michal J. Gajda", + stability = "beta", + testedWith = [ + _×_ + GHC + (ThisVersion + (mkVersion [7, 0, 4])), + _×_ + GHC + (ThisVersion + (mkVersion [7, 4, 1])), + _×_ + GHC + (ThisVersion + (mkVersion [7, 4, 2])), + _×_ + GHC + (ThisVersion + (mkVersion [7, 6, 0]))], + homepage = + "https://github.com/mgajda/octree", + pkgUrl = + "http://hackage.haskell.org/package/octree", + bugReports = + "mailto:mjgajda@googlemail.com", + sourceRepos = [ + SourceRepo { + repoKind = RepoHead, + repoType = Just + (KnownRepoType Git), + repoLocation = Just + "git@github.com:mgajda/octree.git", + repoModule = Nothing, + repoBranch = Nothing, + repoTag = Nothing, + repoSubdir = Nothing}], + synopsis = + "Simple unbalanced Octree for storing data about 3D points", + description = + "Octree data structure is relatively shallow data structure for space partitioning.", + category = "Data", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = []}, + gpdScannedVersion = Nothing, + genPackageFlags = [], + condLibrary = Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName "Data.Octree"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [ + ModuleName + "Data.Octree.Internal"], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [ + EnableExtension + ScopedTypeVariables], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 0])) + (EarlierVersion + (mkVersion [4, 7]))) + mainLibSet, + Dependency + (PackageName "AC-Vector") + (OrLaterVersion + (mkVersion [2, 3, 0])) + mainLibSet, + Dependency + (PackageName "QuickCheck") + (OrLaterVersion + (mkVersion [2, 4, 0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 0])) + (EarlierVersion + (mkVersion [4, 7]))) + mainLibSet, + Dependency + (PackageName "AC-Vector") + (OrLaterVersion + (mkVersion [2, 3, 0])) + mainLibSet, + Dependency + (PackageName "QuickCheck") + (OrLaterVersion + (mkVersion [2, 4, 0])) + mainLibSet], + condTreeComponents = []}, + condSubLibraries = [], + condForeignLibs = [], + condExecutables = [], + condTestSuites = [ + _×_ + (UnqualComponentName + "test_Octree") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + "tests/test_Octree.hs", + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 0])) + (EarlierVersion + (mkVersion [4, 7]))) + mainLibSet, + Dependency + (PackageName "AC-Vector") + (OrLaterVersion + (mkVersion [2, 3, 0])) + mainLibSet, + Dependency + (PackageName "QuickCheck") + (OrLaterVersion + (mkVersion [2, 4, 0])) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 0])) + (EarlierVersion + (mkVersion [4, 7]))) + mainLibSet, + Dependency + (PackageName "AC-Vector") + (OrLaterVersion + (mkVersion [2, 3, 0])) + mainLibSet, + Dependency + (PackageName "QuickCheck") + (OrLaterVersion + (mkVersion [2, 4, 0])) + mainLibSet], + condTreeComponents = []}, + _×_ + (UnqualComponentName "readme") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + "README.lhs", + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + ["-pgmL", "markdown-unlit"] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 0])) + (EarlierVersion + (mkVersion [4, 7]))) + mainLibSet, + Dependency + (PackageName "AC-Vector") + (OrLaterVersion + (mkVersion [2, 3, 0])) + mainLibSet, + Dependency + (PackageName "QuickCheck") + (OrLaterVersion + (mkVersion [2, 4, 0])) + mainLibSet, + Dependency + (PackageName "markdown-unlit") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 0])) + (EarlierVersion + (mkVersion [4, 7]))) + mainLibSet, + Dependency + (PackageName "AC-Vector") + (OrLaterVersion + (mkVersion [2, 3, 0])) + mainLibSet, + Dependency + (PackageName "QuickCheck") + (OrLaterVersion + (mkVersion [2, 4, 0])) + mainLibSet, + Dependency + (PackageName "markdown-unlit") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}], + condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/common-conditional.expr b/Cabal-tests/tests/ParserTests/regressions/common-conditional.expr index b2cca2ada9bfe08465f3f050618f5fa2094d560b..874b496426793bd4f04c4f691b1a5039b4206044 100644 --- a/Cabal-tests/tests/ParserTests/regressions/common-conditional.expr +++ b/Cabal-tests/tests/ParserTests/regressions/common-conditional.expr @@ -1,706 +1,691 @@ -GenericPackageDescription - {condBenchmarks = [], - condExecutables = [], - condForeignLibs = [], - condLibrary = Just - CondNode - {condTreeComponents = [CondBranch - {condBranchCondition = `Var (PackageFlag (FlagName "foo"))`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [CondBranch - {condBranchCondition = `Var (OS Windows)`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName - "Win32") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - condTreeData = Library - {exposedModules = [], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [Dependency - (PackageName - "Win32") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}}], - condTreeConstraints = [Dependency - (PackageName - "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [4, - 10])) - (EarlierVersion - (mkVersion - [4, - 11]))) - mainLibSet, - Dependency - (PackageName - "containers") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - condTreeData = Library - {exposedModules = [], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [Dependency - (PackageName - "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [4, - 10])) - (EarlierVersion - (mkVersion - [4, - 11]))) - mainLibSet, - Dependency - (PackageName - "containers") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}}], - condTreeConstraints = [Dependency - (PackageName "ghc-prim") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeData = Library - {exposedModules = [ModuleName "ElseIf"], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Just Haskell2010, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor [] [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor [] [], - sharedOptions = PerCompilerFlavor [] [], - staticOptions = PerCompilerFlavor [] [], - targetBuildDepends = [Dependency - (PackageName - "ghc-prim") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}, - condSubLibraries = [], - condTestSuites = [_×_ - (UnqualComponentName "tests") - CondNode - {condTreeComponents = [CondBranch - {condBranchCondition = `Var (OS Windows)`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = False, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [], - virtualModules = []}, - testInterface = TestSuiteUnsupported - (TestTypeUnknown - "" - (mkVersion - [])), - testName = UnqualComponentName - ""}}}, - CondBranch - {condBranchCondition = `Var (PackageFlag (FlagName "foo"))`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [CondBranch - {condBranchCondition = `Var (OS Windows)`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName - "Win32") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [Dependency - (PackageName - "Win32") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteUnsupported - (TestTypeUnknown - "" - (mkVersion - [])), - testName = UnqualComponentName - ""}}}, - CondBranch - {condBranchCondition = `Var (OS Windows)`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName - "Win32") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [Dependency - (PackageName - "Win32") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteUnsupported - (TestTypeUnknown - "" - (mkVersion - [])), - testName = UnqualComponentName - ""}}}], - condTreeConstraints = [Dependency - (PackageName - "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [4, - 10])) - (EarlierVersion - (mkVersion - [4, - 11]))) - mainLibSet, - Dependency - (PackageName - "containers") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [Dependency - (PackageName - "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [4, - 10])) - (EarlierVersion - (mkVersion - [4, - 11]))) - mainLibSet, - Dependency - (PackageName - "containers") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteUnsupported - (TestTypeUnknown - "" - (mkVersion - [])), - testName = UnqualComponentName - ""}}}], - condTreeConstraints = [Dependency - (PackageName "HUnit") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor [] [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] [], - sharedOptions = PerCompilerFlavor - [] [], - staticOptions = PerCompilerFlavor - [] [], - targetBuildDepends = [Dependency - (PackageName - "HUnit") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteExeV10 - (mkVersion [1, 0]) "Tests.hs", - testName = UnqualComponentName ""}}], - genPackageFlags = [MkPackageFlag - {flagDefault = True, - flagDescription = "", - flagManual = True, - flagName = FlagName "foo"}], - gpdScannedVersion = Nothing, - packageDescription = PackageDescription - {author = "", - benchmarks = [], - bugReports = "", - buildTypeRaw = Just Simple, - category = "", - copyright = "", - customFieldsPD = [], - dataDir = ".", - dataFiles = [], - description = "", - executables = [], - extraDocFiles = [], - extraSrcFiles = [], - extraTmpFiles = [], - foreignLibs = [], - homepage = "", - library = Nothing, - licenseFiles = [], - licenseRaw = Left NONE, - maintainer = "", - package = PackageIdentifier - {pkgName = PackageName "common-conditional", - pkgVersion = mkVersion [0]}, - pkgUrl = "", - setupBuildInfo = Nothing, - sourceRepos = [SourceRepo - {repoBranch = Nothing, - repoKind = RepoHead, - repoLocation = Just "https://github.com/hvr/-.git", - repoModule = Nothing, - repoSubdir = Nothing, - repoTag = Nothing, - repoType = Just (KnownRepoType Git)}], - specVersion = CabalSpecV3_0, - stability = "", - subLibraries = [], - synopsis = "Common-stanza demo demo", - testSuites = [], - testedWith = []}} +GenericPackageDescription { + packageDescription = + PackageDescription { + specVersion = CabalSpecV3_0, + package = PackageIdentifier { + pkgName = PackageName + "common-conditional", + pkgVersion = mkVersion [0]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [ + SourceRepo { + repoKind = RepoHead, + repoType = Just + (KnownRepoType Git), + repoLocation = Just + "https://github.com/hvr/-.git", + repoModule = Nothing, + repoBranch = Nothing, + repoTag = Nothing, + repoSubdir = Nothing}], + synopsis = + "Common-stanza demo demo", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = []}, + gpdScannedVersion = Nothing, + genPackageFlags = [ + MkPackageFlag { + flagName = FlagName "foo", + flagDescription = "", + flagDefault = True, + flagManual = True}], + condLibrary = Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName "ElseIf"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "ghc-prim") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "ghc-prim") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `Var (PackageFlag (FlagName "foo"))`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 10])) + (EarlierVersion + (mkVersion [4, 11]))) + mainLibSet, + Dependency + (PackageName "containers") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 10])) + (EarlierVersion + (mkVersion [4, 11]))) + mainLibSet, + Dependency + (PackageName "containers") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `Var (OS Windows)`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "Win32") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "Win32") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}, + condBranchIfFalse = Nothing}]}, + condSubLibraries = [], + condForeignLibs = [], + condExecutables = [], + condTestSuites = [ + _×_ + (UnqualComponentName "tests") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + "Tests.hs", + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "HUnit") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "HUnit") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `Var (OS Windows)`, + condBranchIfTrue = CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = + TestSuiteUnsupported + (TestTypeUnknown + "" + (mkVersion [])), + testBuildInfo = BuildInfo { + buildable = False, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = Nothing}, + CondBranch { + condBranchCondition = + `Var (PackageFlag (FlagName "foo"))`, + condBranchIfTrue = CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = + TestSuiteUnsupported + (TestTypeUnknown + "" + (mkVersion [])), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 10])) + (EarlierVersion + (mkVersion [4, 11]))) + mainLibSet, + Dependency + (PackageName "containers") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 10])) + (EarlierVersion + (mkVersion [4, 11]))) + mainLibSet, + Dependency + (PackageName "containers") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `Var (OS Windows)`, + condBranchIfTrue = CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = + TestSuiteUnsupported + (TestTypeUnknown + "" + (mkVersion [])), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "Win32") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "Win32") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}, + CondBranch { + condBranchCondition = + `Var (OS Windows)`, + condBranchIfTrue = CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = + TestSuiteUnsupported + (TestTypeUnknown + "" + (mkVersion [])), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "Win32") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "Win32") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}, + condBranchIfFalse = Nothing}]}], + condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/common.expr b/Cabal-tests/tests/ParserTests/regressions/common.expr index 0273441bfdc85531c35e7be1316700a9a2504978..9a1c7a53df0f7c31fcc9103fbbfd11c778253b08 100644 --- a/Cabal-tests/tests/ParserTests/regressions/common.expr +++ b/Cabal-tests/tests/ParserTests/regressions/common.expr @@ -1,182 +1,205 @@ -GenericPackageDescription - {condBenchmarks = [], - condExecutables = [], - condForeignLibs = [], - condLibrary = Just - CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName "ghc-prim") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeData = Library - {exposedModules = [ModuleName "ElseIf"], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Just Haskell2010, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor [] [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor [] [], - sharedOptions = PerCompilerFlavor [] [], - staticOptions = PerCompilerFlavor [] [], - targetBuildDepends = [Dependency - (PackageName - "ghc-prim") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}, - condSubLibraries = [], - condTestSuites = [_×_ - (UnqualComponentName "tests") - CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName "HUnit") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor [] [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] [], - sharedOptions = PerCompilerFlavor - [] [], - staticOptions = PerCompilerFlavor - [] [], - targetBuildDepends = [Dependency - (PackageName - "HUnit") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteExeV10 - (mkVersion [1, 0]) "Tests.hs", - testName = UnqualComponentName ""}}], - genPackageFlags = [], - gpdScannedVersion = Nothing, - packageDescription = PackageDescription - {author = "", - benchmarks = [], - bugReports = "", - buildTypeRaw = Just Simple, - category = "", - copyright = "", - customFieldsPD = [_×_ "x-revision" "1", - _×_ "x-follows-version-policy" ""], - dataDir = ".", - dataFiles = [], - description = "", - executables = [], - extraDocFiles = [], - extraSrcFiles = [], - extraTmpFiles = [], - foreignLibs = [], - homepage = "", - library = Nothing, - licenseFiles = [], - licenseRaw = Left NONE, - maintainer = "", - package = PackageIdentifier - {pkgName = PackageName "common", pkgVersion = mkVersion [0]}, - pkgUrl = "", - setupBuildInfo = Nothing, - sourceRepos = [SourceRepo - {repoBranch = Nothing, - repoKind = RepoHead, - repoLocation = Just "https://github.com/hvr/-.git", - repoModule = Nothing, - repoSubdir = Nothing, - repoTag = Nothing, - repoType = Just (KnownRepoType Git)}], - specVersion = CabalSpecV1_10, - stability = "", - subLibraries = [], - synopsis = "Common-stanza demo demo", - testSuites = [], - testedWith = []}} +GenericPackageDescription { + packageDescription = + PackageDescription { + specVersion = CabalSpecV1_10, + package = PackageIdentifier { + pkgName = PackageName "common", + pkgVersion = mkVersion [0]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [ + SourceRepo { + repoKind = RepoHead, + repoType = Just + (KnownRepoType Git), + repoLocation = Just + "https://github.com/hvr/-.git", + repoModule = Nothing, + repoBranch = Nothing, + repoTag = Nothing, + repoSubdir = Nothing}], + synopsis = + "Common-stanza demo demo", + description = "", + category = "", + customFieldsPD = [ + _×_ "x-revision" "1", + _×_ + "x-follows-version-policy" + ""], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = []}, + gpdScannedVersion = Nothing, + genPackageFlags = [], + condLibrary = Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName "ElseIf"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "ghc-prim") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "ghc-prim") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + condSubLibraries = [], + condForeignLibs = [], + condExecutables = [], + condTestSuites = [ + _×_ + (UnqualComponentName "tests") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + "Tests.hs", + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "HUnit") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "HUnit") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}], + condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/common2.expr b/Cabal-tests/tests/ParserTests/regressions/common2.expr index 611ad39242c8f648dc173b74d9d70c1694472bd1..f74c75224ef543fd8c02710d66fa9516f951e76a 100644 --- a/Cabal-tests/tests/ParserTests/regressions/common2.expr +++ b/Cabal-tests/tests/ParserTests/regressions/common2.expr @@ -1,731 +1,728 @@ -GenericPackageDescription - {condBenchmarks = [], - condExecutables = [], - condForeignLibs = [], - condLibrary = Just - CondNode - {condTreeComponents = [CondBranch - {condBranchCondition = `Var (OS Windows)`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName - "Win32") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - condTreeData = Library - {exposedModules = [], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [Dependency - (PackageName - "Win32") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}}], - condTreeConstraints = [Dependency - (PackageName "base") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [4, 10])) - (EarlierVersion (mkVersion [4, 11]))) - mainLibSet, - Dependency - (PackageName "containers") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "ghc-prim") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeData = Library - {exposedModules = [ModuleName "ElseIf"], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Just Haskell2010, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor [] [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor [] [], - sharedOptions = PerCompilerFlavor [] [], - staticOptions = PerCompilerFlavor [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [4, 10])) - (EarlierVersion - (mkVersion - [4, - 11]))) - mainLibSet, - Dependency - (PackageName - "containers") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "ghc-prim") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}, - condSubLibraries = [_×_ - (UnqualComponentName "internal") - CondNode - {condTreeComponents = [CondBranch - {condBranchCondition = `Var (OS Windows)`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName - "Win32") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - condTreeData = Library - {exposedModules = [], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [Dependency - (PackageName - "Win32") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - libExposed = True, - libName = LSubLibName - (UnqualComponentName - "internal"), - libVisibility = LibraryVisibilityPrivate, - reexportedModules = [], - signatures = []}}}], - condTreeConstraints = [Dependency - (PackageName "base") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [4, 10])) - (EarlierVersion (mkVersion [4, 11]))) - mainLibSet, - Dependency - (PackageName "containers") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "ghc-prim") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeData = Library - {exposedModules = [ModuleName "ElseIf2"], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Just Haskell2010, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor [] [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] [], - sharedOptions = PerCompilerFlavor - [] [], - staticOptions = PerCompilerFlavor - [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [4, - 10])) - (EarlierVersion - (mkVersion - [4, - 11]))) - mainLibSet, - Dependency - (PackageName - "containers") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "ghc-prim") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - libExposed = True, - libName = LSubLibName - (UnqualComponentName "internal"), - libVisibility = LibraryVisibilityPrivate, - reexportedModules = [], - signatures = []}}], - condTestSuites = [_×_ - (UnqualComponentName "tests") - CondNode - {condTreeComponents = [CondBranch - {condBranchCondition = `Var (OS Windows)`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName - "Win32") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [Dependency - (PackageName - "Win32") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteUnsupported - (TestTypeUnknown - "" - (mkVersion - [])), - testName = UnqualComponentName - ""}}}, - CondBranch - {condBranchCondition = `Var (OS Windows)`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName - "Win32") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [Dependency - (PackageName - "Win32") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteUnsupported - (TestTypeUnknown - "" - (mkVersion - [])), - testName = UnqualComponentName - ""}}}, - CondBranch - {condBranchCondition = `Var (OS Windows)`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = False, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [], - virtualModules = []}, - testInterface = TestSuiteUnsupported - (TestTypeUnknown - "" - (mkVersion - [])), - testName = UnqualComponentName - ""}}}], - condTreeConstraints = [Dependency - (PackageName "base") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [4, 10])) - (EarlierVersion (mkVersion [4, 11]))) - mainLibSet, - Dependency - (PackageName "containers") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "HUnit") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor [] [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] [], - sharedOptions = PerCompilerFlavor - [] [], - staticOptions = PerCompilerFlavor - [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [4, - 10])) - (EarlierVersion - (mkVersion - [4, - 11]))) - mainLibSet, - Dependency - (PackageName - "containers") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "HUnit") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteExeV10 - (mkVersion [1, 0]) "Tests.hs", - testName = UnqualComponentName ""}}], - genPackageFlags = [], - gpdScannedVersion = Nothing, - packageDescription = PackageDescription - {author = "", - benchmarks = [], - bugReports = "", - buildTypeRaw = Just Simple, - category = "", - copyright = "", - customFieldsPD = [], - dataDir = ".", - dataFiles = [], - description = "", - executables = [], - extraDocFiles = [], - extraSrcFiles = [], - extraTmpFiles = [], - foreignLibs = [], - homepage = "", - library = Nothing, - licenseFiles = [], - licenseRaw = Left NONE, - maintainer = "", - package = PackageIdentifier - {pkgName = PackageName "common", pkgVersion = mkVersion [0]}, - pkgUrl = "", - setupBuildInfo = Nothing, - sourceRepos = [SourceRepo - {repoBranch = Nothing, - repoKind = RepoHead, - repoLocation = Just "https://github.com/hvr/-.git", - repoModule = Nothing, - repoSubdir = Nothing, - repoTag = Nothing, - repoType = Just (KnownRepoType Git)}], - specVersion = CabalSpecV2_2, - stability = "", - subLibraries = [], - synopsis = "Common-stanza demo demo", - testSuites = [], - testedWith = []}} +GenericPackageDescription { + packageDescription = + PackageDescription { + specVersion = CabalSpecV2_2, + package = PackageIdentifier { + pkgName = PackageName "common", + pkgVersion = mkVersion [0]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [ + SourceRepo { + repoKind = RepoHead, + repoType = Just + (KnownRepoType Git), + repoLocation = Just + "https://github.com/hvr/-.git", + repoModule = Nothing, + repoBranch = Nothing, + repoTag = Nothing, + repoSubdir = Nothing}], + synopsis = + "Common-stanza demo demo", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = []}, + gpdScannedVersion = Nothing, + genPackageFlags = [], + condLibrary = Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName "ElseIf"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 10])) + (EarlierVersion + (mkVersion [4, 11]))) + mainLibSet, + Dependency + (PackageName "containers") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "ghc-prim") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 10])) + (EarlierVersion + (mkVersion [4, 11]))) + mainLibSet, + Dependency + (PackageName "containers") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "ghc-prim") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `Var (OS Windows)`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "Win32") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "Win32") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}, + condSubLibraries = [ + _×_ + (UnqualComponentName "internal") + CondNode { + condTreeData = Library { + libName = LSubLibName + (UnqualComponentName + "internal"), + exposedModules = [ + ModuleName "ElseIf2"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPrivate, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 10])) + (EarlierVersion + (mkVersion [4, 11]))) + mainLibSet, + Dependency + (PackageName "containers") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "ghc-prim") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 10])) + (EarlierVersion + (mkVersion [4, 11]))) + mainLibSet, + Dependency + (PackageName "containers") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "ghc-prim") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `Var (OS Windows)`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LSubLibName + (UnqualComponentName + "internal"), + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPrivate, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "Win32") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "Win32") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}], + condForeignLibs = [], + condExecutables = [], + condTestSuites = [ + _×_ + (UnqualComponentName "tests") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + "Tests.hs", + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 10])) + (EarlierVersion + (mkVersion [4, 11]))) + mainLibSet, + Dependency + (PackageName "containers") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "HUnit") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 10])) + (EarlierVersion + (mkVersion [4, 11]))) + mainLibSet, + Dependency + (PackageName "containers") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "HUnit") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `Var (OS Windows)`, + condBranchIfTrue = CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = + TestSuiteUnsupported + (TestTypeUnknown + "" + (mkVersion [])), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "Win32") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "Win32") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}, + CondBranch { + condBranchCondition = + `Var (OS Windows)`, + condBranchIfTrue = CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = + TestSuiteUnsupported + (TestTypeUnknown + "" + (mkVersion [])), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "Win32") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "Win32") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}, + CondBranch { + condBranchCondition = + `Var (OS Windows)`, + condBranchIfTrue = CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = + TestSuiteUnsupported + (TestTypeUnknown + "" + (mkVersion [])), + testBuildInfo = BuildInfo { + buildable = False, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}], + condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/common3.expr b/Cabal-tests/tests/ParserTests/regressions/common3.expr index d4ce4267c9b65db48d92e23cb6eda355a6fca367..91c43cb0755c6595aa173c43a75947718254eda6 100644 --- a/Cabal-tests/tests/ParserTests/regressions/common3.expr +++ b/Cabal-tests/tests/ParserTests/regressions/common3.expr @@ -1,212 +1,229 @@ -GenericPackageDescription - {condBenchmarks = [], - condExecutables = [], - condForeignLibs = [], - condLibrary = Just - CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName "ghc-prim") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeData = Library - {exposedModules = [ModuleName "ElseIf"], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Just Haskell2010, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor [] [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor [] [], - sharedOptions = PerCompilerFlavor [] [], - staticOptions = PerCompilerFlavor [] [], - targetBuildDepends = [Dependency - (PackageName - "ghc-prim") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}, - condSubLibraries = [], - condTestSuites = [_×_ - (UnqualComponentName "tests") - CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName "base") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [4, 10])) - (EarlierVersion (mkVersion [4, 11]))) - mainLibSet, - Dependency - (PackageName "containers") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "HUnit") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor [] [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] [], - sharedOptions = PerCompilerFlavor - [] [], - staticOptions = PerCompilerFlavor - [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [4, - 10])) - (EarlierVersion - (mkVersion - [4, - 11]))) - mainLibSet, - Dependency - (PackageName - "containers") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "HUnit") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteExeV10 - (mkVersion [1, 0]) "Tests.hs", - testName = UnqualComponentName ""}}], - genPackageFlags = [], - gpdScannedVersion = Nothing, - packageDescription = PackageDescription - {author = "", - benchmarks = [], - bugReports = "", - buildTypeRaw = Just Simple, - category = "", - copyright = "", - customFieldsPD = [_×_ "x-revision" "1", - _×_ "x-follows-version-policy" ""], - dataDir = ".", - dataFiles = [], - description = "", - executables = [], - extraDocFiles = [], - extraSrcFiles = [], - extraTmpFiles = [], - foreignLibs = [], - homepage = "", - library = Nothing, - licenseFiles = [], - licenseRaw = Left NONE, - maintainer = "", - package = PackageIdentifier - {pkgName = PackageName "common", pkgVersion = mkVersion [0]}, - pkgUrl = "", - setupBuildInfo = Nothing, - sourceRepos = [SourceRepo - {repoBranch = Nothing, - repoKind = RepoHead, - repoLocation = Just "https://github.com/hvr/-.git", - repoModule = Nothing, - repoSubdir = Nothing, - repoTag = Nothing, - repoType = Just (KnownRepoType Git)}], - specVersion = CabalSpecV2_2, - stability = "", - subLibraries = [], - synopsis = "Common-stanza demo demo", - testSuites = [], - testedWith = []}} +GenericPackageDescription { + packageDescription = + PackageDescription { + specVersion = CabalSpecV2_2, + package = PackageIdentifier { + pkgName = PackageName "common", + pkgVersion = mkVersion [0]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [ + SourceRepo { + repoKind = RepoHead, + repoType = Just + (KnownRepoType Git), + repoLocation = Just + "https://github.com/hvr/-.git", + repoModule = Nothing, + repoBranch = Nothing, + repoTag = Nothing, + repoSubdir = Nothing}], + synopsis = + "Common-stanza demo demo", + description = "", + category = "", + customFieldsPD = [ + _×_ "x-revision" "1", + _×_ + "x-follows-version-policy" + ""], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = []}, + gpdScannedVersion = Nothing, + genPackageFlags = [], + condLibrary = Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName "ElseIf"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "ghc-prim") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "ghc-prim") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + condSubLibraries = [], + condForeignLibs = [], + condExecutables = [], + condTestSuites = [ + _×_ + (UnqualComponentName "tests") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + "Tests.hs", + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 10])) + (EarlierVersion + (mkVersion [4, 11]))) + mainLibSet, + Dependency + (PackageName "containers") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "HUnit") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 10])) + (EarlierVersion + (mkVersion [4, 11]))) + mainLibSet, + Dependency + (PackageName "containers") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "HUnit") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}], + condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/generics-sop.expr b/Cabal-tests/tests/ParserTests/regressions/generics-sop.expr index dfddaf29a02c1fd46ac7ad290edfc6f3335709bb..b549eb51f714cb29bb98a3f9c73725057f9f9a08 100644 --- a/Cabal-tests/tests/ParserTests/regressions/generics-sop.expr +++ b/Cabal-tests/tests/ParserTests/regressions/generics-sop.expr @@ -1,810 +1,833 @@ -GenericPackageDescription - {condBenchmarks = [], - condExecutables = [], - condForeignLibs = [], - condLibrary = Just - CondNode - {condTreeComponents = [CondBranch - {condBranchCondition = `CNot (Var (Impl GHC (OrLaterVersion (mkVersion [7,8]))))`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName - "tagged") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [0, - 7])) - (EarlierVersion - (mkVersion - [0, - 9]))) - mainLibSet], - condTreeData = Library - {exposedModules = [], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [Dependency - (PackageName - "tagged") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [0, - 7])) - (EarlierVersion - (mkVersion - [0, - 9]))) - mainLibSet], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}}, - CondBranch - {condBranchCondition = `CNot (Var (Impl GHC (OrLaterVersion (mkVersion [8,0]))))`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName - "transformers-compat") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [0, - 3])) - (EarlierVersion - (mkVersion - [0, - 6]))) - mainLibSet, - Dependency - (PackageName - "transformers") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [0, - 3])) - (EarlierVersion - (mkVersion - [0, - 6]))) - mainLibSet], - condTreeData = Library - {exposedModules = [], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [Dependency - (PackageName - "transformers-compat") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [0, - 3])) - (EarlierVersion - (mkVersion - [0, - 6]))) - mainLibSet, - Dependency - (PackageName - "transformers") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [0, - 3])) - (EarlierVersion - (mkVersion - [0, - 6]))) - mainLibSet], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}}, - CondBranch - {condBranchCondition = `Var (Impl GHC (OrLaterVersion (mkVersion [7,8])))`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [], - condTreeData = Library - {exposedModules = [], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [EnableExtension - AutoDeriveTypeable], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}}, - CondBranch - {condBranchCondition = `Var (Impl GHC (EarlierVersion (mkVersion [7,10])))`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [], - condTreeData = Library - {exposedModules = [], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [EnableExtension - OverlappingInstances], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}}], - condTreeConstraints = [Dependency - (PackageName "base") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [4, 7])) - (EarlierVersion (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "template-haskell") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [2, 8])) - (EarlierVersion (mkVersion [2, 13]))) - mainLibSet, - Dependency - (PackageName "ghc-prim") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [0, 3])) - (EarlierVersion (mkVersion [0, 6]))) - mainLibSet, - Dependency - (PackageName "deepseq") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [1, 3])) - (EarlierVersion (mkVersion [1, 5]))) - mainLibSet], - condTreeData = Library - {exposedModules = [ModuleName "Generics.SOP", - ModuleName "Generics.SOP.GGP", - ModuleName "Generics.SOP.TH", - ModuleName "Generics.SOP.Dict", - ModuleName "Generics.SOP.Type.Metadata", - ModuleName "Generics.SOP.BasicFunctors", - ModuleName "Generics.SOP.Classes", - ModuleName "Generics.SOP.Constraint", - ModuleName "Generics.SOP.Instances", - ModuleName "Generics.SOP.Metadata", - ModuleName "Generics.SOP.NP", - ModuleName "Generics.SOP.NS", - ModuleName "Generics.SOP.Universe", - ModuleName "Generics.SOP.Sing"], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [EnableExtension CPP, - EnableExtension - ScopedTypeVariables, - EnableExtension - TypeFamilies, - EnableExtension - RankNTypes, - EnableExtension - TypeOperators, - EnableExtension - GADTs, - EnableExtension - ConstraintKinds, - EnableExtension - MultiParamTypeClasses, - EnableExtension - TypeSynonymInstances, - EnableExtension - FlexibleInstances, - EnableExtension - FlexibleContexts, - EnableExtension - DeriveFunctor, - EnableExtension - DeriveFoldable, - EnableExtension - DeriveTraversable, - EnableExtension - DefaultSignatures, - EnableExtension - KindSignatures, - EnableExtension - DataKinds, - EnableExtension - FunctionalDependencies], - defaultLanguage = Just Haskell2010, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [SymbolicPath "src"], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor ["-Wall"] [], - otherExtensions = [EnableExtension - OverloadedStrings, - EnableExtension - PolyKinds, - EnableExtension - UndecidableInstances, - EnableExtension - TemplateHaskell, - EnableExtension - DeriveGeneric, - EnableExtension - StandaloneDeriving], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor [] [], - sharedOptions = PerCompilerFlavor [] [], - staticOptions = PerCompilerFlavor [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [4, 7])) - (EarlierVersion - (mkVersion - [5]))) - mainLibSet, - Dependency - (PackageName - "template-haskell") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [2, 8])) - (EarlierVersion - (mkVersion - [2, - 13]))) - mainLibSet, - Dependency - (PackageName - "ghc-prim") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [0, 3])) - (EarlierVersion - (mkVersion - [0, 6]))) - mainLibSet, - Dependency - (PackageName - "deepseq") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [1, 3])) - (EarlierVersion - (mkVersion - [1, 5]))) - mainLibSet], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}, - condSubLibraries = [], - condTestSuites = [_×_ - (UnqualComponentName "doctests") - CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "doctest") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [0, 13])) - (EarlierVersion (mkVersion [0, 14]))) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [_×_ - "x-doctest-options" - "--preserve-it"], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Just Haskell2010, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [SymbolicPath "test"], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - ["-Wall", "-threaded"] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] [], - sharedOptions = PerCompilerFlavor - [] [], - staticOptions = PerCompilerFlavor - [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "doctest") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [0, - 13])) - (EarlierVersion - (mkVersion - [0, - 14]))) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteExeV10 - (mkVersion [1, 0]) "doctests.hs", - testName = UnqualComponentName ""}}, - _×_ - (UnqualComponentName "generics-sop-examples") - CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName "base") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [4, 6])) - (EarlierVersion (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "generics-sop") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Just Haskell2010, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [SymbolicPath "test"], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - ["-Wall"] [], - otherExtensions = [], - otherLanguages = [], - otherModules = [ModuleName - "HTransExample"], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] [], - sharedOptions = PerCompilerFlavor - [] [], - staticOptions = PerCompilerFlavor - [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [4, - 6])) - (EarlierVersion - (mkVersion - [5]))) - mainLibSet, - Dependency - (PackageName - "generics-sop") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteExeV10 - (mkVersion [1, 0]) "Example.hs", - testName = UnqualComponentName ""}}], - genPackageFlags = [], - gpdScannedVersion = Nothing, - packageDescription = PackageDescription - {author = "Edsko de Vries <edsko@well-typed.com>, Andres L\246h <andres@well-typed.com>", - benchmarks = [], - bugReports = "", - buildTypeRaw = Just Custom, - category = "Generics", - copyright = "", - customFieldsPD = [], - dataDir = ".", - dataFiles = [], - description = concat - ["A library to support the definition of generic functions.\n", - "Datatypes are viewed in a uniform, structured way:\n", - "the choice between constructors is represented using an n-ary\n", - "sum, and the arguments of each constructor are represented using\n", - "an n-ary product.\n", - "\n", - "The module \"Generics.SOP\" is the main module of this library and contains\n", - "more detailed documentation.\n", - "\n", - "Examples of using this library are provided by the following\n", - "packages:\n", - "\n", - "* @<https://hackage.haskell.org/package/basic-sop basic-sop>@ basic examples,\n", - "\n", - "* @<https://hackage.haskell.org/package/pretty-sop pretty-sop>@ generic pretty printing,\n", - "\n", - "* @<https://hackage.haskell.org/package/lens-sop lens-sop>@ generically computed lenses,\n", - "\n", - "* @<https://hackage.haskell.org/package/json-sop json-sop>@ generic JSON conversions.\n", - "\n", - "A detailed description of the ideas behind this library is provided by\n", - "the paper:\n", - "\n", - "* Edsko de Vries and Andres L\246h.\n", - "<http://www.andres-loeh.de/TrueSumsOfProducts True Sums of Products>.\n", - "Workshop on Generic Programming (WGP) 2014.\n"], - executables = [], - extraDocFiles = [], - extraSrcFiles = ["CHANGELOG.md"], - extraTmpFiles = [], - foreignLibs = [], - homepage = "", - library = Nothing, - licenseFiles = [SymbolicPath "LICENSE"], - licenseRaw = Right BSD3, - maintainer = "andres@well-typed.com", - package = PackageIdentifier - {pkgName = PackageName "generics-sop", - pkgVersion = mkVersion [0, 3, 1, 0]}, - pkgUrl = "", - setupBuildInfo = Just - SetupBuildInfo - {defaultSetupDepends = False, - setupDepends = [Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "Cabal") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "cabal-doctest") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [1, 0, 2])) - (EarlierVersion - (mkVersion [1, 1]))) - mainLibSet]}, - sourceRepos = [SourceRepo - {repoBranch = Nothing, - repoKind = RepoHead, - repoLocation = Just - "https://github.com/well-typed/generics-sop", - repoModule = Nothing, - repoSubdir = Nothing, - repoTag = Nothing, - repoType = Just (KnownRepoType Git)}], - specVersion = CabalSpecV1_10, - stability = "", - subLibraries = [], - synopsis = "Generic Programming using True Sums of Products", - testSuites = [], - testedWith = [_×_ GHC (ThisVersion (mkVersion [7, 8, 4])), - _×_ GHC (ThisVersion (mkVersion [7, 10, 3])), - _×_ GHC (ThisVersion (mkVersion [8, 0, 1])), - _×_ GHC (ThisVersion (mkVersion [8, 0, 2])), - _×_ GHC (ThisVersion (mkVersion [8, 2, 1])), - _×_ - GHC - (IntersectVersionRanges - (OrLaterVersion (mkVersion [8, 3])) - (EarlierVersion (mkVersion [8, 4])))]}} +GenericPackageDescription { + packageDescription = + PackageDescription { + specVersion = CabalSpecV1_10, + package = PackageIdentifier { + pkgName = PackageName + "generics-sop", + pkgVersion = mkVersion + [0, 3, 1, 0]}, + licenseRaw = Right BSD3, + licenseFiles = [ + SymbolicPath "LICENSE"], + copyright = "", + maintainer = + "andres@well-typed.com", + author = + "Edsko de Vries <edsko@well-typed.com>, Andres L\246h <andres@well-typed.com>", + stability = "", + testedWith = [ + _×_ + GHC + (ThisVersion + (mkVersion [7, 8, 4])), + _×_ + GHC + (ThisVersion + (mkVersion [7, 10, 3])), + _×_ + GHC + (ThisVersion + (mkVersion [8, 0, 1])), + _×_ + GHC + (ThisVersion + (mkVersion [8, 0, 2])), + _×_ + GHC + (ThisVersion + (mkVersion [8, 2, 1])), + _×_ + GHC + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [8, 3])) + (EarlierVersion + (mkVersion [8, 4])))], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [ + SourceRepo { + repoKind = RepoHead, + repoType = Just + (KnownRepoType Git), + repoLocation = Just + "https://github.com/well-typed/generics-sop", + repoModule = Nothing, + repoBranch = Nothing, + repoTag = Nothing, + repoSubdir = Nothing}], + synopsis = + "Generic Programming using True Sums of Products", + description = + concat + [ + "A library to support the definition of generic functions.\n", + "Datatypes are viewed in a uniform, structured way:\n", + "the choice between constructors is represented using an n-ary\n", + "sum, and the arguments of each constructor are represented using\n", + "an n-ary product.\n", + "\n", + "The module \"Generics.SOP\" is the main module of this library and contains\n", + "more detailed documentation.\n", + "\n", + "Examples of using this library are provided by the following\n", + "packages:\n", + "\n", + "* @<https://hackage.haskell.org/package/basic-sop basic-sop>@ basic examples,\n", + "\n", + "* @<https://hackage.haskell.org/package/pretty-sop pretty-sop>@ generic pretty printing,\n", + "\n", + "* @<https://hackage.haskell.org/package/lens-sop lens-sop>@ generically computed lenses,\n", + "\n", + "* @<https://hackage.haskell.org/package/json-sop json-sop>@ generic JSON conversions.\n", + "\n", + "A detailed description of the ideas behind this library is provided by\n", + "the paper:\n", + "\n", + "* Edsko de Vries and Andres L\246h.\n", + "<http://www.andres-loeh.de/TrueSumsOfProducts True Sums of Products>.\n", + "Workshop on Generic Programming (WGP) 2014.\n"], + category = "Generics", + customFieldsPD = [], + buildTypeRaw = Just Custom, + setupBuildInfo = Just + SetupBuildInfo { + setupDepends = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "Cabal") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "cabal-doctest") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [1, 0, 2])) + (EarlierVersion + (mkVersion [1, 1]))) + mainLibSet], + defaultSetupDepends = False}, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = ".", + extraSrcFiles = [ + "CHANGELOG.md"], + extraTmpFiles = [], + extraDocFiles = []}, + gpdScannedVersion = Nothing, + genPackageFlags = [], + condLibrary = Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName "Generics.SOP", + ModuleName "Generics.SOP.GGP", + ModuleName "Generics.SOP.TH", + ModuleName "Generics.SOP.Dict", + ModuleName + "Generics.SOP.Type.Metadata", + ModuleName + "Generics.SOP.BasicFunctors", + ModuleName + "Generics.SOP.Classes", + ModuleName + "Generics.SOP.Constraint", + ModuleName + "Generics.SOP.Instances", + ModuleName + "Generics.SOP.Metadata", + ModuleName "Generics.SOP.NP", + ModuleName "Generics.SOP.NS", + ModuleName + "Generics.SOP.Universe", + ModuleName "Generics.SOP.Sing"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "src"], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [ + EnableExtension CPP, + EnableExtension + ScopedTypeVariables, + EnableExtension TypeFamilies, + EnableExtension RankNTypes, + EnableExtension TypeOperators, + EnableExtension GADTs, + EnableExtension ConstraintKinds, + EnableExtension + MultiParamTypeClasses, + EnableExtension + TypeSynonymInstances, + EnableExtension + FlexibleInstances, + EnableExtension + FlexibleContexts, + EnableExtension DeriveFunctor, + EnableExtension DeriveFoldable, + EnableExtension + DeriveTraversable, + EnableExtension + DefaultSignatures, + EnableExtension KindSignatures, + EnableExtension DataKinds, + EnableExtension + FunctionalDependencies], + otherExtensions = [ + EnableExtension + OverloadedStrings, + EnableExtension PolyKinds, + EnableExtension + UndecidableInstances, + EnableExtension TemplateHaskell, + EnableExtension DeriveGeneric, + EnableExtension + StandaloneDeriving], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + ["-Wall"] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 7])) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "template-haskell") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [2, 8])) + (EarlierVersion + (mkVersion [2, 13]))) + mainLibSet, + Dependency + (PackageName "ghc-prim") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 3])) + (EarlierVersion + (mkVersion [0, 6]))) + mainLibSet, + Dependency + (PackageName "deepseq") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [1, 3])) + (EarlierVersion + (mkVersion [1, 5]))) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 7])) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "template-haskell") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [2, 8])) + (EarlierVersion + (mkVersion [2, 13]))) + mainLibSet, + Dependency + (PackageName "ghc-prim") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 3])) + (EarlierVersion + (mkVersion [0, 6]))) + mainLibSet, + Dependency + (PackageName "deepseq") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [1, 3])) + (EarlierVersion + (mkVersion [1, 5]))) + mainLibSet], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `CNot (Var (Impl GHC (OrLaterVersion (mkVersion [7,8]))))`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "tagged") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 7])) + (EarlierVersion + (mkVersion [0, 9]))) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "tagged") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 7])) + (EarlierVersion + (mkVersion [0, 9]))) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}, + CondBranch { + condBranchCondition = + `CNot (Var (Impl GHC (OrLaterVersion (mkVersion [8,0]))))`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName + "transformers-compat") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 3])) + (EarlierVersion + (mkVersion [0, 6]))) + mainLibSet, + Dependency + (PackageName "transformers") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 3])) + (EarlierVersion + (mkVersion [0, 6]))) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName + "transformers-compat") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 3])) + (EarlierVersion + (mkVersion [0, 6]))) + mainLibSet, + Dependency + (PackageName "transformers") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 3])) + (EarlierVersion + (mkVersion [0, 6]))) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}, + CondBranch { + condBranchCondition = + `Var (Impl GHC (OrLaterVersion (mkVersion [7,8])))`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [ + EnableExtension + AutoDeriveTypeable], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = Nothing}, + CondBranch { + condBranchCondition = + `Var (Impl GHC (EarlierVersion (mkVersion [7,10])))`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [ + EnableExtension + OverlappingInstances], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}, + condSubLibraries = [], + condForeignLibs = [], + condExecutables = [], + condTestSuites = [ + _×_ + (UnqualComponentName "doctests") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + "doctests.hs", + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "test"], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + ["-Wall", "-threaded"] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [ + _×_ + "x-doctest-options" + "--preserve-it"], + targetBuildDepends = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "doctest") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 13])) + (EarlierVersion + (mkVersion [0, 14]))) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "doctest") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 13])) + (EarlierVersion + (mkVersion [0, 14]))) + mainLibSet], + condTreeComponents = []}, + _×_ + (UnqualComponentName + "generics-sop-examples") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + "Example.hs", + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "test"], + otherModules = [ + ModuleName "HTransExample"], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + ["-Wall"] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 6])) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "generics-sop") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 6])) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "generics-sop") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}], + condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/hasktorch.expr b/Cabal-tests/tests/ParserTests/regressions/hasktorch.expr index 2ddf3ba05566d15253dc27795f3eafbb6a62bc44..92b76bbb0eb882499b229407deb01e7bb0ab0bda 100644 --- a/Cabal-tests/tests/ParserTests/regressions/hasktorch.expr +++ b/Cabal-tests/tests/ParserTests/regressions/hasktorch.expr @@ -10080,7 +10080,8 @@ GenericPackageDescription { (PackageName "generic-lens") (OrLaterVersion (mkVersion [0])) mainLibSet], - mixins = []}}, + mixins = []}, + testCodeGenerators = []}, condTreeConstraints = [ Dependency (PackageName "QuickCheck") diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5055.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5055.expr index 96577831b3691a276ac0f301f003fee7f0fce48a..be5e955442b8e93d350c83c2f9d8fbeb6a835a88 100644 --- a/Cabal-tests/tests/ParserTests/regressions/issue-5055.expr +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5055.expr @@ -1,255 +1,278 @@ -GenericPackageDescription - {condBenchmarks = [], - condExecutables = [_×_ - (UnqualComponentName "flag-test-exe") - CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName "base") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [4, 8])) - (EarlierVersion (mkVersion [5]))) - mainLibSet], - condTreeData = Executable - {buildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Just Haskell2010, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor [] [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor [] [], - sharedOptions = PerCompilerFlavor [] [], - staticOptions = PerCompilerFlavor [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [4, - 8])) - (EarlierVersion - (mkVersion - [5]))) - mainLibSet], - virtualModules = []}, - exeName = UnqualComponentName "flag-test-exe", - exeScope = ExecutablePublic, - modulePath = "FirstMain.hs"}}], - condForeignLibs = [], - condLibrary = Nothing, - condSubLibraries = [], - condTestSuites = [_×_ - (UnqualComponentName "flag-cabal-test") - CondNode - {condTreeComponents = [CondBranch - {condBranchCondition = `Var (OS Windows)`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [], - virtualModules = []}, - testInterface = TestSuiteUnsupported - (TestTypeUnknown - "" - (mkVersion - [])), - testName = UnqualComponentName - ""}}}], - condTreeConstraints = [Dependency - (PackageName "base") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [4, 8])) - (EarlierVersion (mkVersion [5]))) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Just Haskell2010, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor [] [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] [], - sharedOptions = PerCompilerFlavor - [] [], - staticOptions = PerCompilerFlavor - [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [4, - 8])) - (EarlierVersion - (mkVersion - [5]))) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteExeV10 - (mkVersion [1, 0]) "SecondMain.hs", - testName = UnqualComponentName ""}}], - genPackageFlags = [], - gpdScannedVersion = Nothing, - packageDescription = PackageDescription - {author = "", - benchmarks = [], - bugReports = "", - buildTypeRaw = Just Simple, - category = "Test", - copyright = "", - customFieldsPD = [], - dataDir = ".", - dataFiles = [], - description = "no type in all branches.", - executables = [], - extraDocFiles = [], - extraSrcFiles = [], - extraTmpFiles = [], - foreignLibs = [], - homepage = "", - library = Nothing, - licenseFiles = [], - licenseRaw = Right BSD3, - maintainer = "", - package = PackageIdentifier - {pkgName = PackageName "issue", - pkgVersion = mkVersion [5055]}, - pkgUrl = "", - setupBuildInfo = Nothing, - sourceRepos = [], - specVersion = CabalSpecV2_0, - stability = "", - subLibraries = [], - synopsis = "no type in all branches", - testSuites = [], - testedWith = []}} +GenericPackageDescription { + packageDescription = + PackageDescription { + specVersion = CabalSpecV2_0, + package = PackageIdentifier { + pkgName = PackageName "issue", + pkgVersion = mkVersion [5055]}, + licenseRaw = Right BSD3, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = + "no type in all branches", + description = + "no type in all branches.", + category = "Test", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = []}, + gpdScannedVersion = Nothing, + genPackageFlags = [], + condLibrary = Nothing, + condSubLibraries = [], + condForeignLibs = [], + condExecutables = [ + _×_ + (UnqualComponentName + "flag-test-exe") + CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "flag-test-exe", + modulePath = "FirstMain.hs", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 8])) + (EarlierVersion + (mkVersion [5]))) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 8])) + (EarlierVersion + (mkVersion [5]))) + mainLibSet], + condTreeComponents = []}], + condTestSuites = [ + _×_ + (UnqualComponentName + "flag-cabal-test") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + "SecondMain.hs", + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 8])) + (EarlierVersion + (mkVersion [5]))) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 8])) + (EarlierVersion + (mkVersion [5]))) + mainLibSet], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `Var (OS Windows)`, + condBranchIfTrue = CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = + TestSuiteUnsupported + (TestTypeUnknown + "" + (mkVersion [])), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}], + condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.expr b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.expr index 51b6add00d7d357c41a75f4a83625651b68fcde3..aac1a2153e64e6438bf7287c2144407a3453f97f 100644 --- a/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.expr +++ b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.expr @@ -1,480 +1,469 @@ -GenericPackageDescription - {condBenchmarks = [], - condExecutables = [_×_ - (UnqualComponentName "jaeger-flamegraph") - CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName "base") - (UnionVersionRanges - (MajorBoundVersion (mkVersion [4, 11, 1, 0])) - (MajorBoundVersion - (mkVersion [4, 12, 0, 0]))) - mainLibSet, - Dependency - (PackageName "jaeger-flamegraph") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "bytestring") - (MajorBoundVersion (mkVersion [0, 10, 8, 2])) - mainLibSet, - Dependency - (PackageName "containers") - (MajorBoundVersion (mkVersion [0, 6, 0, 1])) - mainLibSet, - Dependency - (PackageName "extra") - (MajorBoundVersion (mkVersion [1, 6, 13])) - mainLibSet, - Dependency - (PackageName "aeson") - (MajorBoundVersion (mkVersion [1, 4, 1, 0])) - mainLibSet, - Dependency - (PackageName "optparse-applicative") - (MajorBoundVersion (mkVersion [0, 14, 3, 0])) - mainLibSet, - Dependency - (PackageName "text") - (MajorBoundVersion (mkVersion [1, 2, 3, 1])) - mainLibSet], - condTreeData = Executable - {buildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Just Haskell2010, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [SymbolicPath "exe"], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - ["-Wall", - "-Werror=missing-home-modules", - "-threaded"] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor [] [], - sharedOptions = PerCompilerFlavor [] [], - staticOptions = PerCompilerFlavor [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (UnionVersionRanges - (MajorBoundVersion - (mkVersion - [4, - 11, - 1, - 0])) - (MajorBoundVersion - (mkVersion - [4, - 12, - 0, - 0]))) - mainLibSet, - Dependency - (PackageName - "jaeger-flamegraph") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "bytestring") - (MajorBoundVersion - (mkVersion - [0, - 10, - 8, - 2])) - mainLibSet, - Dependency - (PackageName - "containers") - (MajorBoundVersion - (mkVersion - [0, - 6, - 0, - 1])) - mainLibSet, - Dependency - (PackageName - "extra") - (MajorBoundVersion - (mkVersion - [1, - 6, - 13])) - mainLibSet, - Dependency - (PackageName - "aeson") - (MajorBoundVersion - (mkVersion - [1, - 4, - 1, - 0])) - mainLibSet, - Dependency - (PackageName - "optparse-applicative") - (MajorBoundVersion - (mkVersion - [0, - 14, - 3, - 0])) - mainLibSet, - Dependency - (PackageName - "text") - (MajorBoundVersion - (mkVersion - [1, - 2, - 3, - 1])) - mainLibSet], - virtualModules = []}, - exeName = UnqualComponentName "jaeger-flamegraph", - exeScope = ExecutablePublic, - modulePath = "Main.hs"}}], - condForeignLibs = [], - condLibrary = Just - CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName "base") - (UnionVersionRanges - (MajorBoundVersion (mkVersion [4, 11, 1, 0])) - (MajorBoundVersion (mkVersion [4, 12, 0, 0]))) - mainLibSet, - Dependency - (PackageName "QuickCheck") - (MajorBoundVersion (mkVersion [2, 12, 6, 1])) - mainLibSet], - condTreeData = Library - {exposedModules = [ModuleName "Interval"], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Just Haskell2010, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [SymbolicPath "library"], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - ["-Wall", - "-Werror=missing-home-modules"] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor [] [], - sharedOptions = PerCompilerFlavor [] [], - staticOptions = PerCompilerFlavor [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (UnionVersionRanges - (MajorBoundVersion - (mkVersion - [4, - 11, - 1, - 0])) - (MajorBoundVersion - (mkVersion - [4, - 12, - 0, - 0]))) - mainLibSet, - Dependency - (PackageName - "QuickCheck") - (MajorBoundVersion - (mkVersion - [2, - 12, - 6, - 1])) - mainLibSet], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}, - condSubLibraries = [], - condTestSuites = [_×_ - (UnqualComponentName "tests") - CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName "base") - (UnionVersionRanges - (MajorBoundVersion (mkVersion [4, 11, 1, 0])) - (MajorBoundVersion (mkVersion [4, 12, 0, 0]))) - mainLibSet, - Dependency - (PackageName "jaeger-flamegraph") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "tasty") - (MajorBoundVersion (mkVersion [1, 1, 0, 4])) - mainLibSet, - Dependency - (PackageName "tasty-hspec") - (MajorBoundVersion (mkVersion [1, 1, 5])) - mainLibSet, - Dependency - (PackageName "tasty-quickcheck") - (MajorBoundVersion (mkVersion [0, 10])) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [ExeDependency - (PackageName - "tasty-discover") - (UnqualComponentName - "tasty-discover") - (MajorBoundVersion - (mkVersion - [4, - 2, - 1]))], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Just Haskell2010, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [SymbolicPath "test"], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - ["-Wall", - "-Werror=missing-home-modules", - "-threaded"] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [ModuleName - "IntervalTest"], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] [], - sharedOptions = PerCompilerFlavor - [] [], - staticOptions = PerCompilerFlavor - [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (UnionVersionRanges - (MajorBoundVersion - (mkVersion - [4, - 11, - 1, - 0])) - (MajorBoundVersion - (mkVersion - [4, - 12, - 0, - 0]))) - mainLibSet, - Dependency - (PackageName - "jaeger-flamegraph") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "tasty") - (MajorBoundVersion - (mkVersion - [1, - 1, - 0, - 4])) - mainLibSet, - Dependency - (PackageName - "tasty-hspec") - (MajorBoundVersion - (mkVersion - [1, - 1, - 5])) - mainLibSet, - Dependency - (PackageName - "tasty-quickcheck") - (MajorBoundVersion - (mkVersion - [0, - 10])) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteExeV10 - (mkVersion [1, 0]) "Driver.hs", - testName = UnqualComponentName ""}}], - genPackageFlags = [], - gpdScannedVersion = Nothing, - packageDescription = PackageDescription - {author = "Sam Halliday", - benchmarks = [], - bugReports = "https://github.com/symbiont-io/jaeger-flamegraph/pulls", - buildTypeRaw = Nothing, - category = "Testing", - copyright = "(c) 2018 Symbiont.io", - customFieldsPD = [], - dataDir = ".", - dataFiles = [], - description = concat - ["This is a small tool to convert JSON dumps obtained from a Jaeger\n", - "server (<https://www.jaegertracing.io/>) into a format consumable\n", - "by [FlameGraph](https://github.com/brendangregg/FlameGraph).\n", - "\n", - "First download the traces for your SERVICE limiting to LIMIT traces\n", - "\n", - "> $ curl http://your-jaeger-installation/api/traces?service=SERVICE&limit=LIMIT > input.json\n", - "\n", - "using the [undocumented Jaeger API](https://github.com/jaegertracing/jaeger/issues/456#issuecomment-412560321)\n", - "then use @jaeger-flamegraph@ to convert the data and send to @flamegraph.pl@\n", - "\n", - "> $ jaeger-flamegraph -f input.json | flamegraph.pl > output.svg\n"], - executables = [], - extraDocFiles = [], - extraSrcFiles = [], - extraTmpFiles = [], - foreignLibs = [], - homepage = "", - library = Nothing, - licenseFiles = [SymbolicPath "LICENSE"], - licenseRaw = Left - (License (ELicense (ELicenseId BSD_3_Clause) Nothing)), - maintainer = "Sam Halliday", - package = PackageIdentifier - {pkgName = PackageName "jaeger-flamegraph", - pkgVersion = mkVersion [1, 0, 0]}, - pkgUrl = "", - setupBuildInfo = Nothing, - sourceRepos = [SourceRepo - {repoBranch = Nothing, - repoKind = RepoHead, - repoLocation = Just - "https://github.com/symbiont-io/jaeger-flamegraph", - repoModule = Nothing, - repoSubdir = Nothing, - repoTag = Nothing, - repoType = Just (KnownRepoType Git)}], - specVersion = CabalSpecV2_2, - stability = "", - subLibraries = [], - synopsis = "Generate flamegraphs from Jaeger .json dumps.", - testSuites = [], - testedWith = [_×_ - GHC - (UnionVersionRanges - (MajorBoundVersion (mkVersion [8, 4, 4])) - (MajorBoundVersion (mkVersion [8, 6, 2])))]}} +GenericPackageDescription { + packageDescription = + PackageDescription { + specVersion = CabalSpecV2_2, + package = PackageIdentifier { + pkgName = PackageName + "jaeger-flamegraph", + pkgVersion = mkVersion + [1, 0, 0]}, + licenseRaw = Left + (License + (ELicense + (ELicenseId BSD_3_Clause) + Nothing)), + licenseFiles = [ + SymbolicPath "LICENSE"], + copyright = + "(c) 2018 Symbiont.io", + maintainer = "Sam Halliday", + author = "Sam Halliday", + stability = "", + testedWith = [ + _×_ + GHC + (UnionVersionRanges + (MajorBoundVersion + (mkVersion [8, 4, 4])) + (MajorBoundVersion + (mkVersion [8, 6, 2])))], + homepage = "", + pkgUrl = "", + bugReports = + "https://github.com/symbiont-io/jaeger-flamegraph/pulls", + sourceRepos = [ + SourceRepo { + repoKind = RepoHead, + repoType = Just + (KnownRepoType Git), + repoLocation = Just + "https://github.com/symbiont-io/jaeger-flamegraph", + repoModule = Nothing, + repoBranch = Nothing, + repoTag = Nothing, + repoSubdir = Nothing}], + synopsis = + "Generate flamegraphs from Jaeger .json dumps.", + description = + concat + [ + "This is a small tool to convert JSON dumps obtained from a Jaeger\n", + "server (<https://www.jaegertracing.io/>) into a format consumable\n", + "by [FlameGraph](https://github.com/brendangregg/FlameGraph).\n", + "\n", + "First download the traces for your SERVICE limiting to LIMIT traces\n", + "\n", + "> $ curl http://your-jaeger-installation/api/traces?service=SERVICE&limit=LIMIT > input.json\n", + "\n", + "using the [undocumented Jaeger API](https://github.com/jaegertracing/jaeger/issues/456#issuecomment-412560321)\n", + "then use @jaeger-flamegraph@ to convert the data and send to @flamegraph.pl@\n", + "\n", + "> $ jaeger-flamegraph -f input.json | flamegraph.pl > output.svg\n"], + category = "Testing", + customFieldsPD = [], + buildTypeRaw = Nothing, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = []}, + gpdScannedVersion = Nothing, + genPackageFlags = [], + condLibrary = Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName "Interval"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "library"], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [ + "-Wall", + "-Werror=missing-home-modules"] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (UnionVersionRanges + (MajorBoundVersion + (mkVersion [4, 11, 1, 0])) + (MajorBoundVersion + (mkVersion [4, 12, 0, 0]))) + mainLibSet, + Dependency + (PackageName "QuickCheck") + (MajorBoundVersion + (mkVersion [2, 12, 6, 1])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (UnionVersionRanges + (MajorBoundVersion + (mkVersion [4, 11, 1, 0])) + (MajorBoundVersion + (mkVersion [4, 12, 0, 0]))) + mainLibSet, + Dependency + (PackageName "QuickCheck") + (MajorBoundVersion + (mkVersion [2, 12, 6, 1])) + mainLibSet], + condTreeComponents = []}, + condSubLibraries = [], + condForeignLibs = [], + condExecutables = [ + _×_ + (UnqualComponentName + "jaeger-flamegraph") + CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "jaeger-flamegraph", + modulePath = "Main.hs", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "exe"], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [ + "-Wall", + "-Werror=missing-home-modules", + "-threaded"] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (UnionVersionRanges + (MajorBoundVersion + (mkVersion [4, 11, 1, 0])) + (MajorBoundVersion + (mkVersion [4, 12, 0, 0]))) + mainLibSet, + Dependency + (PackageName + "jaeger-flamegraph") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "bytestring") + (MajorBoundVersion + (mkVersion [0, 10, 8, 2])) + mainLibSet, + Dependency + (PackageName "containers") + (MajorBoundVersion + (mkVersion [0, 6, 0, 1])) + mainLibSet, + Dependency + (PackageName "extra") + (MajorBoundVersion + (mkVersion [1, 6, 13])) + mainLibSet, + Dependency + (PackageName "aeson") + (MajorBoundVersion + (mkVersion [1, 4, 1, 0])) + mainLibSet, + Dependency + (PackageName + "optparse-applicative") + (MajorBoundVersion + (mkVersion [0, 14, 3, 0])) + mainLibSet, + Dependency + (PackageName "text") + (MajorBoundVersion + (mkVersion [1, 2, 3, 1])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (UnionVersionRanges + (MajorBoundVersion + (mkVersion [4, 11, 1, 0])) + (MajorBoundVersion + (mkVersion [4, 12, 0, 0]))) + mainLibSet, + Dependency + (PackageName + "jaeger-flamegraph") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "bytestring") + (MajorBoundVersion + (mkVersion [0, 10, 8, 2])) + mainLibSet, + Dependency + (PackageName "containers") + (MajorBoundVersion + (mkVersion [0, 6, 0, 1])) + mainLibSet, + Dependency + (PackageName "extra") + (MajorBoundVersion + (mkVersion [1, 6, 13])) + mainLibSet, + Dependency + (PackageName "aeson") + (MajorBoundVersion + (mkVersion [1, 4, 1, 0])) + mainLibSet, + Dependency + (PackageName + "optparse-applicative") + (MajorBoundVersion + (mkVersion [0, 14, 3, 0])) + mainLibSet, + Dependency + (PackageName "text") + (MajorBoundVersion + (mkVersion [1, 2, 3, 1])) + mainLibSet], + condTreeComponents = []}], + condTestSuites = [ + _×_ + (UnqualComponentName "tests") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + "Driver.hs", + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [ + ExeDependency + (PackageName "tasty-discover") + (UnqualComponentName + "tasty-discover") + (MajorBoundVersion + (mkVersion [4, 2, 1]))], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "test"], + otherModules = [ + ModuleName "IntervalTest"], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [ + "-Wall", + "-Werror=missing-home-modules", + "-threaded"] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (UnionVersionRanges + (MajorBoundVersion + (mkVersion [4, 11, 1, 0])) + (MajorBoundVersion + (mkVersion [4, 12, 0, 0]))) + mainLibSet, + Dependency + (PackageName + "jaeger-flamegraph") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "tasty") + (MajorBoundVersion + (mkVersion [1, 1, 0, 4])) + mainLibSet, + Dependency + (PackageName "tasty-hspec") + (MajorBoundVersion + (mkVersion [1, 1, 5])) + mainLibSet, + Dependency + (PackageName "tasty-quickcheck") + (MajorBoundVersion + (mkVersion [0, 10])) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (UnionVersionRanges + (MajorBoundVersion + (mkVersion [4, 11, 1, 0])) + (MajorBoundVersion + (mkVersion [4, 12, 0, 0]))) + mainLibSet, + Dependency + (PackageName + "jaeger-flamegraph") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "tasty") + (MajorBoundVersion + (mkVersion [1, 1, 0, 4])) + mainLibSet, + Dependency + (PackageName "tasty-hspec") + (MajorBoundVersion + (mkVersion [1, 1, 5])) + mainLibSet, + Dependency + (PackageName "tasty-quickcheck") + (MajorBoundVersion + (mkVersion [0, 10])) + mainLibSet], + condTreeComponents = []}], + condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/shake.expr b/Cabal-tests/tests/ParserTests/regressions/shake.expr index 36f522c82df907a59ce5216f9b6393b7e7184ee8..30e0f9077c11f2affbe37f32c2ccab7bdea44eeb 100644 --- a/Cabal-tests/tests/ParserTests/regressions/shake.expr +++ b/Cabal-tests/tests/ParserTests/regressions/shake.expr @@ -1,2570 +1,2413 @@ -GenericPackageDescription - {condBenchmarks = [], - condExecutables = [_×_ - (UnqualComponentName "shake") - CondNode - {condTreeComponents = [CondBranch - {condBranchCondition = `Var (Impl GHC (OrLaterVersion (mkVersion [7,8])))`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [], - condTreeData = Executable - {buildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - ["-threaded", - "-with-rtsopts=-I0 -qg -qb"] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [], - virtualModules = []}, - exeName = UnqualComponentName - "shake", - exeScope = ExecutablePublic, - modulePath = ""}}}, - CondBranch - {condBranchCondition = `Var (PackageFlag (FlagName "portable"))`, - condBranchIfFalse = Just - CondNode - {condTreeComponents = [CondBranch - {condBranchCondition = `CNot (Var (OS Windows))`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName - "unix") - (OrLaterVersion - (mkVersion - [2, - 5, - 1])) - mainLibSet], - condTreeData = Executable - {buildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [Dependency - (PackageName - "unix") - (OrLaterVersion - (mkVersion - [2, - 5, - 1])) - mainLibSet], - virtualModules = []}, - exeName = UnqualComponentName - "shake", - exeScope = ExecutablePublic, - modulePath = ""}}}], - condTreeConstraints = [], - condTreeData = Executable - {buildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [], - virtualModules = []}, - exeName = UnqualComponentName - "shake", - exeScope = ExecutablePublic, - modulePath = ""}}, - condBranchIfTrue = CondNode - {condTreeComponents = [CondBranch - {condBranchCondition = `Var (Impl GHC (EarlierVersion (mkVersion [7,6])))`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName - "old-time") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - condTreeData = Executable - {buildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [Dependency - (PackageName - "old-time") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - exeName = UnqualComponentName - "shake", - exeScope = ExecutablePublic, - modulePath = ""}}}], - condTreeConstraints = [], - condTreeData = Executable - {buildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = ["-DPORTABLE"], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [], - virtualModules = []}, - exeName = UnqualComponentName - "shake", - exeScope = ExecutablePublic, - modulePath = ""}}}, - CondBranch - {condBranchCondition = `CNot (Var (OS Windows))`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName - "unix") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - condTreeData = Executable - {buildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [Dependency - (PackageName - "unix") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - exeName = UnqualComponentName - "shake", - exeScope = ExecutablePublic, - modulePath = ""}}}], - condTreeConstraints = [Dependency - (PackageName "base") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [4])) - (EarlierVersion (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "directory") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "hashable") - (OrLaterVersion (mkVersion [1, 1, 2, 3])) - mainLibSet, - Dependency - (PackageName "binary") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "filepath") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "process") - (OrLaterVersion (mkVersion [1, 1])) - mainLibSet, - Dependency - (PackageName "unordered-containers") - (OrLaterVersion (mkVersion [0, 2, 1])) - mainLibSet, - Dependency - (PackageName "bytestring") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "utf8-string") - (OrLaterVersion (mkVersion [0, 3])) - mainLibSet, - Dependency - (PackageName "time") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "random") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "js-jquery") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "js-flot") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "transformers") - (OrLaterVersion (mkVersion [0, 2])) - mainLibSet, - Dependency - (PackageName "extra") - (OrLaterVersion (mkVersion [1, 4, 8])) - mainLibSet, - Dependency - (PackageName "deepseq") - (OrLaterVersion (mkVersion [1, 1])) - mainLibSet, - Dependency - (PackageName "primitive") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeData = Executable - {buildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Just Haskell2010, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [SymbolicPath "src"], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - ["-main-is", - "Run.main", - "-rtsopts"] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [ModuleName - "Development.Make.All", - ModuleName - "Development.Make.Env", - ModuleName - "Development.Make.Parse", - ModuleName - "Development.Make.Rules", - ModuleName - "Development.Make.Type", - ModuleName - "Development.Ninja.All", - ModuleName - "Development.Ninja.Env", - ModuleName - "Development.Ninja.Lexer", - ModuleName - "Development.Ninja.Parse", - ModuleName - "Development.Ninja.Type", - ModuleName - "Development.Shake", - ModuleName - "Development.Shake.Args", - ModuleName - "Development.Shake.ByteString", - ModuleName - "Development.Shake.Classes", - ModuleName - "Development.Shake.CmdOption", - ModuleName - "Development.Shake.Command", - ModuleName - "Development.Shake.Core", - ModuleName - "Development.Shake.Database", - ModuleName - "Development.Shake.Demo", - ModuleName - "Development.Shake.Derived", - ModuleName - "Development.Shake.Errors", - ModuleName - "Development.Shake.FileInfo", - ModuleName - "Development.Shake.FilePath", - ModuleName - "Development.Shake.FilePattern", - ModuleName - "Development.Shake.Forward", - ModuleName - "Development.Shake.Monad", - ModuleName - "Development.Shake.Pool", - ModuleName - "Development.Shake.Profile", - ModuleName - "Development.Shake.Progress", - ModuleName - "Development.Shake.Resource", - ModuleName - "Development.Shake.Rule", - ModuleName - "Development.Shake.Rules.Directory", - ModuleName - "Development.Shake.Rules.File", - ModuleName - "Development.Shake.Rules.Files", - ModuleName - "Development.Shake.Rules.Oracle", - ModuleName - "Development.Shake.Rules.OrderOnly", - ModuleName - "Development.Shake.Rules.Rerun", - ModuleName - "Development.Shake.Shake", - ModuleName - "Development.Shake.Special", - ModuleName - "Development.Shake.Storage", - ModuleName - "Development.Shake.Types", - ModuleName - "Development.Shake.Value", - ModuleName - "General.Bilist", - ModuleName - "General.Binary", - ModuleName - "General.Cleanup", - ModuleName - "General.Concurrent", - ModuleName - "General.Extra", - ModuleName - "General.FileLock", - ModuleName - "General.Intern", - ModuleName - "General.Process", - ModuleName - "General.String", - ModuleName - "General.Template", - ModuleName - "General.Timing", - ModuleName - "Paths_shake", - ModuleName "Run"], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor [] [], - sharedOptions = PerCompilerFlavor [] [], - staticOptions = PerCompilerFlavor [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [4])) - (EarlierVersion - (mkVersion - [5]))) - mainLibSet, - Dependency - (PackageName - "directory") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "hashable") - (OrLaterVersion - (mkVersion - [1, - 1, - 2, - 3])) - mainLibSet, - Dependency - (PackageName - "binary") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "filepath") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "process") - (OrLaterVersion - (mkVersion - [1, 1])) - mainLibSet, - Dependency - (PackageName - "unordered-containers") - (OrLaterVersion - (mkVersion - [0, - 2, - 1])) - mainLibSet, - Dependency - (PackageName - "bytestring") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "utf8-string") - (OrLaterVersion - (mkVersion - [0, 3])) - mainLibSet, - Dependency - (PackageName - "time") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "random") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "js-jquery") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "js-flot") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "transformers") - (OrLaterVersion - (mkVersion - [0, 2])) - mainLibSet, - Dependency - (PackageName - "extra") - (OrLaterVersion - (mkVersion - [1, - 4, - 8])) - mainLibSet, - Dependency - (PackageName - "deepseq") - (OrLaterVersion - (mkVersion - [1, 1])) - mainLibSet, - Dependency - (PackageName - "primitive") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - exeName = UnqualComponentName "shake", - exeScope = ExecutablePublic, - modulePath = "Run.hs"}}], - condForeignLibs = [], - condLibrary = Just - CondNode - {condTreeComponents = [CondBranch - {condBranchCondition = `Var (PackageFlag (FlagName "portable"))`, - condBranchIfFalse = Just - CondNode - {condTreeComponents = [CondBranch - {condBranchCondition = `CNot (Var (OS Windows))`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName - "unix") - (OrLaterVersion - (mkVersion - [2, - 5, - 1])) - mainLibSet], - condTreeData = Library - {exposedModules = [], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [Dependency - (PackageName - "unix") - (OrLaterVersion - (mkVersion - [2, - 5, - 1])) - mainLibSet], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}}], - condTreeConstraints = [], - condTreeData = Library - {exposedModules = [], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}, - condBranchIfTrue = CondNode - {condTreeComponents = [CondBranch - {condBranchCondition = `Var (Impl GHC (EarlierVersion (mkVersion [7,6])))`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName - "old-time") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - condTreeData = Library - {exposedModules = [], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [Dependency - (PackageName - "old-time") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}}], - condTreeConstraints = [], - condTreeData = Library - {exposedModules = [], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = ["-DPORTABLE"], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}}, - CondBranch - {condBranchCondition = `CNot (Var (OS Windows))`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName - "unix") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - condTreeData = Library - {exposedModules = [], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [Dependency - (PackageName - "unix") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}}], - condTreeConstraints = [Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [4, 5])) - mainLibSet, - Dependency - (PackageName "directory") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "hashable") - (OrLaterVersion (mkVersion [1, 1, 2, 3])) - mainLibSet, - Dependency - (PackageName "binary") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "filepath") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "process") - (OrLaterVersion (mkVersion [1, 1])) - mainLibSet, - Dependency - (PackageName "unordered-containers") - (OrLaterVersion (mkVersion [0, 2, 1])) - mainLibSet, - Dependency - (PackageName "bytestring") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "utf8-string") - (OrLaterVersion (mkVersion [0, 3])) - mainLibSet, - Dependency - (PackageName "time") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "random") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "js-jquery") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "js-flot") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "transformers") - (OrLaterVersion (mkVersion [0, 2])) - mainLibSet, - Dependency - (PackageName "extra") - (OrLaterVersion (mkVersion [1, 4, 8])) - mainLibSet, - Dependency - (PackageName "deepseq") - (OrLaterVersion (mkVersion [1, 1])) - mainLibSet], - condTreeData = Library - {exposedModules = [ModuleName "Development.Shake", - ModuleName "Development.Shake.Classes", - ModuleName "Development.Shake.Command", - ModuleName "Development.Shake.Config", - ModuleName "Development.Shake.FilePath", - ModuleName "Development.Shake.Forward", - ModuleName "Development.Shake.Rule", - ModuleName "Development.Shake.Util"], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Just Haskell2010, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [SymbolicPath ".", - SymbolicPath "src"], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor [] [], - otherExtensions = [], - otherLanguages = [], - otherModules = [ModuleName - "Development.Ninja.Env", - ModuleName - "Development.Ninja.Lexer", - ModuleName - "Development.Ninja.Parse", - ModuleName - "Development.Ninja.Type", - ModuleName - "Development.Shake.Args", - ModuleName - "Development.Shake.ByteString", - ModuleName - "Development.Shake.Core", - ModuleName - "Development.Shake.CmdOption", - ModuleName - "Development.Shake.Database", - ModuleName - "Development.Shake.Demo", - ModuleName - "Development.Shake.Derived", - ModuleName - "Development.Shake.Errors", - ModuleName - "Development.Shake.FileInfo", - ModuleName - "Development.Shake.FilePattern", - ModuleName - "Development.Shake.Monad", - ModuleName - "Development.Shake.Pool", - ModuleName - "Development.Shake.Profile", - ModuleName - "Development.Shake.Progress", - ModuleName - "Development.Shake.Resource", - ModuleName - "Development.Shake.Rules.Directory", - ModuleName - "Development.Shake.Rules.File", - ModuleName - "Development.Shake.Rules.Files", - ModuleName - "Development.Shake.Rules.Oracle", - ModuleName - "Development.Shake.Rules.OrderOnly", - ModuleName - "Development.Shake.Rules.Rerun", - ModuleName - "Development.Shake.Shake", - ModuleName - "Development.Shake.Special", - ModuleName - "Development.Shake.Storage", - ModuleName - "Development.Shake.Types", - ModuleName - "Development.Shake.Value", - ModuleName - "General.Bilist", - ModuleName - "General.Binary", - ModuleName - "General.Cleanup", - ModuleName - "General.Concurrent", - ModuleName - "General.Extra", - ModuleName - "General.FileLock", - ModuleName - "General.Intern", - ModuleName - "General.Process", - ModuleName - "General.String", - ModuleName - "General.Template", - ModuleName - "General.Timing", - ModuleName "Paths_shake"], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor [] [], - sharedOptions = PerCompilerFlavor [] [], - staticOptions = PerCompilerFlavor [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (OrLaterVersion - (mkVersion - [4, 5])) - mainLibSet, - Dependency - (PackageName - "directory") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "hashable") - (OrLaterVersion - (mkVersion - [1, - 1, - 2, - 3])) - mainLibSet, - Dependency - (PackageName - "binary") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "filepath") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "process") - (OrLaterVersion - (mkVersion - [1, 1])) - mainLibSet, - Dependency - (PackageName - "unordered-containers") - (OrLaterVersion - (mkVersion - [0, 2, 1])) - mainLibSet, - Dependency - (PackageName - "bytestring") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "utf8-string") - (OrLaterVersion - (mkVersion - [0, 3])) - mainLibSet, - Dependency - (PackageName - "time") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "random") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "js-jquery") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "js-flot") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "transformers") - (OrLaterVersion - (mkVersion - [0, 2])) - mainLibSet, - Dependency - (PackageName - "extra") - (OrLaterVersion - (mkVersion - [1, 4, 8])) - mainLibSet, - Dependency - (PackageName - "deepseq") - (OrLaterVersion - (mkVersion - [1, 1])) - mainLibSet], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}, - condSubLibraries = [], - condTestSuites = [_×_ - (UnqualComponentName "shake-test") - CondNode - {condTreeComponents = [CondBranch - {condBranchCondition = `Var (Impl GHC (OrLaterVersion (mkVersion [7,6])))`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - ["-with-rtsopts=-K1K"] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [], - virtualModules = []}, - testInterface = TestSuiteUnsupported - (TestTypeUnknown - "" - (mkVersion - [])), - testName = UnqualComponentName - ""}}}, - CondBranch - {condBranchCondition = `Var (Impl GHC (OrLaterVersion (mkVersion [7,8])))`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - ["-threaded"] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [], - virtualModules = []}, - testInterface = TestSuiteUnsupported - (TestTypeUnknown - "" - (mkVersion - [])), - testName = UnqualComponentName - ""}}}, - CondBranch - {condBranchCondition = `Var (PackageFlag (FlagName "portable"))`, - condBranchIfFalse = Just - CondNode - {condTreeComponents = [CondBranch - {condBranchCondition = `CNot (Var (OS Windows))`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName - "unix") - (OrLaterVersion - (mkVersion - [2, - 5, - 1])) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [Dependency - (PackageName - "unix") - (OrLaterVersion - (mkVersion - [2, - 5, - 1])) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteUnsupported - (TestTypeUnknown - "" - (mkVersion - [])), - testName = UnqualComponentName - ""}}}], - condTreeConstraints = [], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [], - virtualModules = []}, - testInterface = TestSuiteUnsupported - (TestTypeUnknown - "" - (mkVersion - [])), - testName = UnqualComponentName - ""}}, - condBranchIfTrue = CondNode - {condTreeComponents = [CondBranch - {condBranchCondition = `Var (Impl GHC (EarlierVersion (mkVersion [7,6])))`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName - "old-time") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [Dependency - (PackageName - "old-time") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteUnsupported - (TestTypeUnknown - "" - (mkVersion - [])), - testName = UnqualComponentName - ""}}}], - condTreeConstraints = [], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = ["-DPORTABLE"], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [], - virtualModules = []}, - testInterface = TestSuiteUnsupported - (TestTypeUnknown - "" - (mkVersion - [])), - testName = UnqualComponentName - ""}}}, - CondBranch - {condBranchCondition = `CNot (Var (OS Windows))`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName - "unix") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - [] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [Dependency - (PackageName - "unix") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteUnsupported - (TestTypeUnknown - "" - (mkVersion - [])), - testName = UnqualComponentName - ""}}}], - condTreeConstraints = [Dependency - (PackageName "base") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [4])) - (EarlierVersion (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "directory") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "hashable") - (OrLaterVersion (mkVersion [1, 1, 2, 3])) - mainLibSet, - Dependency - (PackageName "binary") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "filepath") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "process") - (OrLaterVersion (mkVersion [1, 1])) - mainLibSet, - Dependency - (PackageName "unordered-containers") - (OrLaterVersion (mkVersion [0, 2, 1])) - mainLibSet, - Dependency - (PackageName "bytestring") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "utf8-string") - (OrLaterVersion (mkVersion [0, 3])) - mainLibSet, - Dependency - (PackageName "time") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "random") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "js-jquery") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "js-flot") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "transformers") - (OrLaterVersion (mkVersion [0, 2])) - mainLibSet, - Dependency - (PackageName "deepseq") - (OrLaterVersion (mkVersion [1, 1])) - mainLibSet, - Dependency - (PackageName "extra") - (OrLaterVersion (mkVersion [1, 4, 8])) - mainLibSet, - Dependency - (PackageName "QuickCheck") - (OrLaterVersion (mkVersion [2, 0])) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Just Haskell2010, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [SymbolicPath "src"], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - ["-main-is", - "Test.main", - "-rtsopts"] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [ModuleName - "Development.Make.All", - ModuleName - "Development.Make.Env", - ModuleName - "Development.Make.Parse", - ModuleName - "Development.Make.Rules", - ModuleName - "Development.Make.Type", - ModuleName - "Development.Ninja.All", - ModuleName - "Development.Ninja.Env", - ModuleName - "Development.Ninja.Lexer", - ModuleName - "Development.Ninja.Parse", - ModuleName - "Development.Ninja.Type", - ModuleName - "Development.Shake", - ModuleName - "Development.Shake.Args", - ModuleName - "Development.Shake.ByteString", - ModuleName - "Development.Shake.Classes", - ModuleName - "Development.Shake.CmdOption", - ModuleName - "Development.Shake.Command", - ModuleName - "Development.Shake.Config", - ModuleName - "Development.Shake.Core", - ModuleName - "Development.Shake.Database", - ModuleName - "Development.Shake.Demo", - ModuleName - "Development.Shake.Derived", - ModuleName - "Development.Shake.Errors", - ModuleName - "Development.Shake.FileInfo", - ModuleName - "Development.Shake.FilePath", - ModuleName - "Development.Shake.FilePattern", - ModuleName - "Development.Shake.Forward", - ModuleName - "Development.Shake.Monad", - ModuleName - "Development.Shake.Pool", - ModuleName - "Development.Shake.Profile", - ModuleName - "Development.Shake.Progress", - ModuleName - "Development.Shake.Resource", - ModuleName - "Development.Shake.Rule", - ModuleName - "Development.Shake.Rules.Directory", - ModuleName - "Development.Shake.Rules.File", - ModuleName - "Development.Shake.Rules.Files", - ModuleName - "Development.Shake.Rules.Oracle", - ModuleName - "Development.Shake.Rules.OrderOnly", - ModuleName - "Development.Shake.Rules.Rerun", - ModuleName - "Development.Shake.Shake", - ModuleName - "Development.Shake.Special", - ModuleName - "Development.Shake.Storage", - ModuleName - "Development.Shake.Types", - ModuleName - "Development.Shake.Util", - ModuleName - "Development.Shake.Value", - ModuleName - "General.Bilist", - ModuleName - "General.Binary", - ModuleName - "General.Cleanup", - ModuleName - "General.Concurrent", - ModuleName - "General.Extra", - ModuleName - "General.FileLock", - ModuleName - "General.Intern", - ModuleName - "General.Process", - ModuleName - "General.String", - ModuleName - "General.Template", - ModuleName - "General.Timing", - ModuleName - "Paths_shake", - ModuleName "Run", - ModuleName - "Test.Assume", - ModuleName - "Test.Basic", - ModuleName - "Test.Benchmark", - ModuleName "Test.C", - ModuleName - "Test.Cache", - ModuleName - "Test.Command", - ModuleName - "Test.Config", - ModuleName - "Test.Digest", - ModuleName - "Test.Directory", - ModuleName - "Test.Docs", - ModuleName - "Test.Errors", - ModuleName - "Test.FileLock", - ModuleName - "Test.FilePath", - ModuleName - "Test.FilePattern", - ModuleName - "Test.Files", - ModuleName - "Test.Forward", - ModuleName - "Test.Journal", - ModuleName - "Test.Lint", - ModuleName - "Test.Live", - ModuleName - "Test.Makefile", - ModuleName - "Test.Manual", - ModuleName - "Test.Match", - ModuleName - "Test.Monad", - ModuleName - "Test.Ninja", - ModuleName - "Test.Oracle", - ModuleName - "Test.OrderOnly", - ModuleName - "Test.Parallel", - ModuleName - "Test.Pool", - ModuleName - "Test.Progress", - ModuleName - "Test.Random", - ModuleName - "Test.Resources", - ModuleName - "Test.Self", - ModuleName - "Test.Tar", - ModuleName - "Test.Tup", - ModuleName - "Test.Type", - ModuleName - "Test.Unicode", - ModuleName - "Test.Util", - ModuleName - "Test.Verbosity", - ModuleName - "Test.Version"], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] [], - sharedOptions = PerCompilerFlavor - [] [], - staticOptions = PerCompilerFlavor - [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [4])) - (EarlierVersion - (mkVersion - [5]))) - mainLibSet, - Dependency - (PackageName - "directory") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "hashable") - (OrLaterVersion - (mkVersion - [1, - 1, - 2, - 3])) - mainLibSet, - Dependency - (PackageName - "binary") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "filepath") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "process") - (OrLaterVersion - (mkVersion - [1, - 1])) - mainLibSet, - Dependency - (PackageName - "unordered-containers") - (OrLaterVersion - (mkVersion - [0, - 2, - 1])) - mainLibSet, - Dependency - (PackageName - "bytestring") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "utf8-string") - (OrLaterVersion - (mkVersion - [0, - 3])) - mainLibSet, - Dependency - (PackageName - "time") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "random") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "js-jquery") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "js-flot") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "transformers") - (OrLaterVersion - (mkVersion - [0, - 2])) - mainLibSet, - Dependency - (PackageName - "deepseq") - (OrLaterVersion - (mkVersion - [1, - 1])) - mainLibSet, - Dependency - (PackageName - "extra") - (OrLaterVersion - (mkVersion - [1, - 4, - 8])) - mainLibSet, - Dependency - (PackageName - "QuickCheck") - (OrLaterVersion - (mkVersion - [2, - 0])) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteExeV10 - (mkVersion [1, 0]) "Test.hs", - testName = UnqualComponentName ""}}], - genPackageFlags = [MkPackageFlag - {flagDefault = False, - flagDescription = "Obtain FileTime using portable functions", - flagManual = True, - flagName = FlagName "portable"}], - gpdScannedVersion = Nothing, - packageDescription = PackageDescription - {author = "Neil Mitchell <ndmitchell@gmail.com>", - benchmarks = [], - bugReports = "https://github.com/ndmitchell/shake/issues", - buildTypeRaw = Just Simple, - category = "Development, Shake", - copyright = "Neil Mitchell 2011-2017", - customFieldsPD = [], - dataDir = ".", - dataFiles = ["html/viz.js", - "html/profile.html", - "html/progress.html", - "html/shake.js", - "docs/manual/build.bat", - "docs/manual/Build.hs", - "docs/manual/build.sh", - "docs/manual/constants.c", - "docs/manual/constants.h", - "docs/manual/main.c"], - description = concat - ["Shake is a Haskell library for writing build systems - designed as a\n", - "replacement for @make@. See \"Development.Shake\" for an introduction,\n", - "including an example. Further examples are included in the Cabal tarball,\n", - "under the @Examples@ directory. The homepage contains links to a user\n", - "manual, an academic paper and further information:\n", - "<http://shakebuild.com>\n", - "\n", - "To use Shake the user writes a Haskell program\n", - "that imports \"Development.Shake\", defines some build rules, and calls\n", - "the 'Development.Shake.shakeArgs' function. Thanks to do notation and infix\n", - "operators, a simple Shake build system\n", - "is not too dissimilar from a simple Makefile. However, as build systems\n", - "get more complex, Shake is able to take advantage of the excellent\n", - "abstraction facilities offered by Haskell and easily support much larger\n", - "projects. The Shake library provides all the standard features available in other\n", - "build systems, including automatic parallelism and minimal rebuilds.\n", - "Shake also provides more accurate dependency tracking, including seamless\n", - "support for generated files, and dependencies on system information\n", - "(e.g. compiler version)."], - executables = [], - extraDocFiles = ["CHANGES.txt", "README.md"], - extraSrcFiles = ["src/Test/C/constants.c", - "src/Test/C/constants.h", - "src/Test/C/main.c", - "src/Test/MakeTutor/Makefile", - "src/Test/MakeTutor/hellofunc.c", - "src/Test/MakeTutor/hellomake.c", - "src/Test/MakeTutor/hellomake.h", - "src/Test/Tar/list.txt", - "src/Test/Ninja/*.ninja", - "src/Test/Ninja/subdir/*.ninja", - "src/Test/Ninja/*.output", - "src/Test/Progress/*.prog", - "src/Test/Tup/hello.c", - "src/Test/Tup/root.cfg", - "src/Test/Tup/newmath/root.cfg", - "src/Test/Tup/newmath/square.c", - "src/Test/Tup/newmath/square.h", - "src/Paths.hs", - "docs/Manual.md", - "docs/shake-progress.png"], - extraTmpFiles = [], - foreignLibs = [], - homepage = "http://shakebuild.com", - library = Nothing, - licenseFiles = [SymbolicPath "LICENSE"], - licenseRaw = Right BSD3, - maintainer = "Neil Mitchell <ndmitchell@gmail.com>", - package = PackageIdentifier - {pkgName = PackageName "shake", - pkgVersion = mkVersion [0, 15, 11]}, - pkgUrl = "", - setupBuildInfo = Nothing, - sourceRepos = [SourceRepo - {repoBranch = Nothing, - repoKind = RepoHead, - repoLocation = Just - "https://github.com/ndmitchell/shake.git", - repoModule = Nothing, - repoSubdir = Nothing, - repoTag = Nothing, - repoType = Just (KnownRepoType Git)}], - specVersion = CabalSpecV1_18, - stability = "", - subLibraries = [], - synopsis = "Build system library, like Make, but more accurate dependencies.", - testSuites = [], - testedWith = [_×_ GHC (ThisVersion (mkVersion [8, 0, 1])), - _×_ GHC (ThisVersion (mkVersion [7, 10, 3])), - _×_ GHC (ThisVersion (mkVersion [7, 8, 4])), - _×_ GHC (ThisVersion (mkVersion [7, 6, 3])), - _×_ GHC (ThisVersion (mkVersion [7, 4, 2]))]}} +GenericPackageDescription { + packageDescription = + PackageDescription { + specVersion = CabalSpecV1_18, + package = PackageIdentifier { + pkgName = PackageName "shake", + pkgVersion = mkVersion + [0, 15, 11]}, + licenseRaw = Right BSD3, + licenseFiles = [ + SymbolicPath "LICENSE"], + copyright = + "Neil Mitchell 2011-2017", + maintainer = + "Neil Mitchell <ndmitchell@gmail.com>", + author = + "Neil Mitchell <ndmitchell@gmail.com>", + stability = "", + testedWith = [ + _×_ + GHC + (ThisVersion + (mkVersion [8, 0, 1])), + _×_ + GHC + (ThisVersion + (mkVersion [7, 10, 3])), + _×_ + GHC + (ThisVersion + (mkVersion [7, 8, 4])), + _×_ + GHC + (ThisVersion + (mkVersion [7, 6, 3])), + _×_ + GHC + (ThisVersion + (mkVersion [7, 4, 2]))], + homepage = + "http://shakebuild.com", + pkgUrl = "", + bugReports = + "https://github.com/ndmitchell/shake/issues", + sourceRepos = [ + SourceRepo { + repoKind = RepoHead, + repoType = Just + (KnownRepoType Git), + repoLocation = Just + "https://github.com/ndmitchell/shake.git", + repoModule = Nothing, + repoBranch = Nothing, + repoTag = Nothing, + repoSubdir = Nothing}], + synopsis = + "Build system library, like Make, but more accurate dependencies.", + description = + concat + [ + "Shake is a Haskell library for writing build systems - designed as a\n", + "replacement for @make@. See \"Development.Shake\" for an introduction,\n", + "including an example. Further examples are included in the Cabal tarball,\n", + "under the @Examples@ directory. The homepage contains links to a user\n", + "manual, an academic paper and further information:\n", + "<http://shakebuild.com>\n", + "\n", + "To use Shake the user writes a Haskell program\n", + "that imports \"Development.Shake\", defines some build rules, and calls\n", + "the 'Development.Shake.shakeArgs' function. Thanks to do notation and infix\n", + "operators, a simple Shake build system\n", + "is not too dissimilar from a simple Makefile. However, as build systems\n", + "get more complex, Shake is able to take advantage of the excellent\n", + "abstraction facilities offered by Haskell and easily support much larger\n", + "projects. The Shake library provides all the standard features available in other\n", + "build systems, including automatic parallelism and minimal rebuilds.\n", + "Shake also provides more accurate dependency tracking, including seamless\n", + "support for generated files, and dependencies on system information\n", + "(e.g. compiler version)."], + category = "Development, Shake", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [ + "html/viz.js", + "html/profile.html", + "html/progress.html", + "html/shake.js", + "docs/manual/build.bat", + "docs/manual/Build.hs", + "docs/manual/build.sh", + "docs/manual/constants.c", + "docs/manual/constants.h", + "docs/manual/main.c"], + dataDir = ".", + extraSrcFiles = [ + "src/Test/C/constants.c", + "src/Test/C/constants.h", + "src/Test/C/main.c", + "src/Test/MakeTutor/Makefile", + "src/Test/MakeTutor/hellofunc.c", + "src/Test/MakeTutor/hellomake.c", + "src/Test/MakeTutor/hellomake.h", + "src/Test/Tar/list.txt", + "src/Test/Ninja/*.ninja", + "src/Test/Ninja/subdir/*.ninja", + "src/Test/Ninja/*.output", + "src/Test/Progress/*.prog", + "src/Test/Tup/hello.c", + "src/Test/Tup/root.cfg", + "src/Test/Tup/newmath/root.cfg", + "src/Test/Tup/newmath/square.c", + "src/Test/Tup/newmath/square.h", + "src/Paths.hs", + "docs/Manual.md", + "docs/shake-progress.png"], + extraTmpFiles = [], + extraDocFiles = [ + "CHANGES.txt", + "README.md"]}, + gpdScannedVersion = Nothing, + genPackageFlags = [ + MkPackageFlag { + flagName = FlagName "portable", + flagDescription = + "Obtain FileTime using portable functions", + flagDefault = False, + flagManual = True}], + condLibrary = Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName "Development.Shake", + ModuleName + "Development.Shake.Classes", + ModuleName + "Development.Shake.Command", + ModuleName + "Development.Shake.Config", + ModuleName + "Development.Shake.FilePath", + ModuleName + "Development.Shake.Forward", + ModuleName + "Development.Shake.Rule", + ModuleName + "Development.Shake.Util"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath ".", + SymbolicPath "src"], + otherModules = [ + ModuleName + "Development.Ninja.Env", + ModuleName + "Development.Ninja.Lexer", + ModuleName + "Development.Ninja.Parse", + ModuleName + "Development.Ninja.Type", + ModuleName + "Development.Shake.Args", + ModuleName + "Development.Shake.ByteString", + ModuleName + "Development.Shake.Core", + ModuleName + "Development.Shake.CmdOption", + ModuleName + "Development.Shake.Database", + ModuleName + "Development.Shake.Demo", + ModuleName + "Development.Shake.Derived", + ModuleName + "Development.Shake.Errors", + ModuleName + "Development.Shake.FileInfo", + ModuleName + "Development.Shake.FilePattern", + ModuleName + "Development.Shake.Monad", + ModuleName + "Development.Shake.Pool", + ModuleName + "Development.Shake.Profile", + ModuleName + "Development.Shake.Progress", + ModuleName + "Development.Shake.Resource", + ModuleName + "Development.Shake.Rules.Directory", + ModuleName + "Development.Shake.Rules.File", + ModuleName + "Development.Shake.Rules.Files", + ModuleName + "Development.Shake.Rules.Oracle", + ModuleName + "Development.Shake.Rules.OrderOnly", + ModuleName + "Development.Shake.Rules.Rerun", + ModuleName + "Development.Shake.Shake", + ModuleName + "Development.Shake.Special", + ModuleName + "Development.Shake.Storage", + ModuleName + "Development.Shake.Types", + ModuleName + "Development.Shake.Value", + ModuleName "General.Bilist", + ModuleName "General.Binary", + ModuleName "General.Cleanup", + ModuleName "General.Concurrent", + ModuleName "General.Extra", + ModuleName "General.FileLock", + ModuleName "General.Intern", + ModuleName "General.Process", + ModuleName "General.String", + ModuleName "General.Template", + ModuleName "General.Timing", + ModuleName "Paths_shake"], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (OrLaterVersion + (mkVersion [4, 5])) + mainLibSet, + Dependency + (PackageName "directory") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "hashable") + (OrLaterVersion + (mkVersion [1, 1, 2, 3])) + mainLibSet, + Dependency + (PackageName "binary") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "filepath") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "process") + (OrLaterVersion + (mkVersion [1, 1])) + mainLibSet, + Dependency + (PackageName + "unordered-containers") + (OrLaterVersion + (mkVersion [0, 2, 1])) + mainLibSet, + Dependency + (PackageName "bytestring") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "utf8-string") + (OrLaterVersion + (mkVersion [0, 3])) + mainLibSet, + Dependency + (PackageName "time") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "random") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "js-jquery") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "js-flot") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "transformers") + (OrLaterVersion + (mkVersion [0, 2])) + mainLibSet, + Dependency + (PackageName "extra") + (OrLaterVersion + (mkVersion [1, 4, 8])) + mainLibSet, + Dependency + (PackageName "deepseq") + (OrLaterVersion + (mkVersion [1, 1])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (OrLaterVersion + (mkVersion [4, 5])) + mainLibSet, + Dependency + (PackageName "directory") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "hashable") + (OrLaterVersion + (mkVersion [1, 1, 2, 3])) + mainLibSet, + Dependency + (PackageName "binary") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "filepath") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "process") + (OrLaterVersion + (mkVersion [1, 1])) + mainLibSet, + Dependency + (PackageName + "unordered-containers") + (OrLaterVersion + (mkVersion [0, 2, 1])) + mainLibSet, + Dependency + (PackageName "bytestring") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "utf8-string") + (OrLaterVersion + (mkVersion [0, 3])) + mainLibSet, + Dependency + (PackageName "time") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "random") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "js-jquery") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "js-flot") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "transformers") + (OrLaterVersion + (mkVersion [0, 2])) + mainLibSet, + Dependency + (PackageName "extra") + (OrLaterVersion + (mkVersion [1, 4, 8])) + mainLibSet, + Dependency + (PackageName "deepseq") + (OrLaterVersion + (mkVersion [1, 1])) + mainLibSet], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `Var (PackageFlag (FlagName "portable"))`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = ["-DPORTABLE"], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `Var (Impl GHC (EarlierVersion (mkVersion [7,6])))`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "old-time") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "old-time") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}, + condBranchIfFalse = Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `CNot (Var (OS Windows))`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "unix") + (OrLaterVersion + (mkVersion [2, 5, 1])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "unix") + (OrLaterVersion + (mkVersion [2, 5, 1])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}}, + CondBranch { + condBranchCondition = + `CNot (Var (OS Windows))`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "unix") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "unix") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}, + condSubLibraries = [], + condForeignLibs = [], + condExecutables = [ + _×_ + (UnqualComponentName "shake") + CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "shake", + modulePath = "Run.hs", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "src"], + otherModules = [ + ModuleName + "Development.Make.All", + ModuleName + "Development.Make.Env", + ModuleName + "Development.Make.Parse", + ModuleName + "Development.Make.Rules", + ModuleName + "Development.Make.Type", + ModuleName + "Development.Ninja.All", + ModuleName + "Development.Ninja.Env", + ModuleName + "Development.Ninja.Lexer", + ModuleName + "Development.Ninja.Parse", + ModuleName + "Development.Ninja.Type", + ModuleName "Development.Shake", + ModuleName + "Development.Shake.Args", + ModuleName + "Development.Shake.ByteString", + ModuleName + "Development.Shake.Classes", + ModuleName + "Development.Shake.CmdOption", + ModuleName + "Development.Shake.Command", + ModuleName + "Development.Shake.Core", + ModuleName + "Development.Shake.Database", + ModuleName + "Development.Shake.Demo", + ModuleName + "Development.Shake.Derived", + ModuleName + "Development.Shake.Errors", + ModuleName + "Development.Shake.FileInfo", + ModuleName + "Development.Shake.FilePath", + ModuleName + "Development.Shake.FilePattern", + ModuleName + "Development.Shake.Forward", + ModuleName + "Development.Shake.Monad", + ModuleName + "Development.Shake.Pool", + ModuleName + "Development.Shake.Profile", + ModuleName + "Development.Shake.Progress", + ModuleName + "Development.Shake.Resource", + ModuleName + "Development.Shake.Rule", + ModuleName + "Development.Shake.Rules.Directory", + ModuleName + "Development.Shake.Rules.File", + ModuleName + "Development.Shake.Rules.Files", + ModuleName + "Development.Shake.Rules.Oracle", + ModuleName + "Development.Shake.Rules.OrderOnly", + ModuleName + "Development.Shake.Rules.Rerun", + ModuleName + "Development.Shake.Shake", + ModuleName + "Development.Shake.Special", + ModuleName + "Development.Shake.Storage", + ModuleName + "Development.Shake.Types", + ModuleName + "Development.Shake.Value", + ModuleName "General.Bilist", + ModuleName "General.Binary", + ModuleName "General.Cleanup", + ModuleName "General.Concurrent", + ModuleName "General.Extra", + ModuleName "General.FileLock", + ModuleName "General.Intern", + ModuleName "General.Process", + ModuleName "General.String", + ModuleName "General.Template", + ModuleName "General.Timing", + ModuleName "Paths_shake", + ModuleName "Run"], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [ + "-main-is", + "Run.main", + "-rtsopts"] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion (mkVersion [4])) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "directory") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "hashable") + (OrLaterVersion + (mkVersion [1, 1, 2, 3])) + mainLibSet, + Dependency + (PackageName "binary") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "filepath") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "process") + (OrLaterVersion + (mkVersion [1, 1])) + mainLibSet, + Dependency + (PackageName + "unordered-containers") + (OrLaterVersion + (mkVersion [0, 2, 1])) + mainLibSet, + Dependency + (PackageName "bytestring") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "utf8-string") + (OrLaterVersion + (mkVersion [0, 3])) + mainLibSet, + Dependency + (PackageName "time") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "random") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "js-jquery") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "js-flot") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "transformers") + (OrLaterVersion + (mkVersion [0, 2])) + mainLibSet, + Dependency + (PackageName "extra") + (OrLaterVersion + (mkVersion [1, 4, 8])) + mainLibSet, + Dependency + (PackageName "deepseq") + (OrLaterVersion + (mkVersion [1, 1])) + mainLibSet, + Dependency + (PackageName "primitive") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion (mkVersion [4])) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "directory") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "hashable") + (OrLaterVersion + (mkVersion [1, 1, 2, 3])) + mainLibSet, + Dependency + (PackageName "binary") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "filepath") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "process") + (OrLaterVersion + (mkVersion [1, 1])) + mainLibSet, + Dependency + (PackageName + "unordered-containers") + (OrLaterVersion + (mkVersion [0, 2, 1])) + mainLibSet, + Dependency + (PackageName "bytestring") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "utf8-string") + (OrLaterVersion + (mkVersion [0, 3])) + mainLibSet, + Dependency + (PackageName "time") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "random") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "js-jquery") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "js-flot") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "transformers") + (OrLaterVersion + (mkVersion [0, 2])) + mainLibSet, + Dependency + (PackageName "extra") + (OrLaterVersion + (mkVersion [1, 4, 8])) + mainLibSet, + Dependency + (PackageName "deepseq") + (OrLaterVersion + (mkVersion [1, 1])) + mainLibSet, + Dependency + (PackageName "primitive") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `Var (Impl GHC (OrLaterVersion (mkVersion [7,8])))`, + condBranchIfTrue = CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "shake", + modulePath = "", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [ + "-threaded", + "-with-rtsopts=-I0 -qg -qb"] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = Nothing}, + CondBranch { + condBranchCondition = + `Var (PackageFlag (FlagName "portable"))`, + condBranchIfTrue = CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "shake", + modulePath = "", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = ["-DPORTABLE"], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `Var (Impl GHC (EarlierVersion (mkVersion [7,6])))`, + condBranchIfTrue = CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "shake", + modulePath = "", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "old-time") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "old-time") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}, + condBranchIfFalse = Just + CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "shake", + modulePath = "", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `CNot (Var (OS Windows))`, + condBranchIfTrue = CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "shake", + modulePath = "", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "unix") + (OrLaterVersion + (mkVersion [2, 5, 1])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "unix") + (OrLaterVersion + (mkVersion [2, 5, 1])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}}, + CondBranch { + condBranchCondition = + `CNot (Var (OS Windows))`, + condBranchIfTrue = CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "shake", + modulePath = "", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "unix") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "unix") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}], + condTestSuites = [ + _×_ + (UnqualComponentName + "shake-test") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + "Test.hs", + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "src"], + otherModules = [ + ModuleName + "Development.Make.All", + ModuleName + "Development.Make.Env", + ModuleName + "Development.Make.Parse", + ModuleName + "Development.Make.Rules", + ModuleName + "Development.Make.Type", + ModuleName + "Development.Ninja.All", + ModuleName + "Development.Ninja.Env", + ModuleName + "Development.Ninja.Lexer", + ModuleName + "Development.Ninja.Parse", + ModuleName + "Development.Ninja.Type", + ModuleName "Development.Shake", + ModuleName + "Development.Shake.Args", + ModuleName + "Development.Shake.ByteString", + ModuleName + "Development.Shake.Classes", + ModuleName + "Development.Shake.CmdOption", + ModuleName + "Development.Shake.Command", + ModuleName + "Development.Shake.Config", + ModuleName + "Development.Shake.Core", + ModuleName + "Development.Shake.Database", + ModuleName + "Development.Shake.Demo", + ModuleName + "Development.Shake.Derived", + ModuleName + "Development.Shake.Errors", + ModuleName + "Development.Shake.FileInfo", + ModuleName + "Development.Shake.FilePath", + ModuleName + "Development.Shake.FilePattern", + ModuleName + "Development.Shake.Forward", + ModuleName + "Development.Shake.Monad", + ModuleName + "Development.Shake.Pool", + ModuleName + "Development.Shake.Profile", + ModuleName + "Development.Shake.Progress", + ModuleName + "Development.Shake.Resource", + ModuleName + "Development.Shake.Rule", + ModuleName + "Development.Shake.Rules.Directory", + ModuleName + "Development.Shake.Rules.File", + ModuleName + "Development.Shake.Rules.Files", + ModuleName + "Development.Shake.Rules.Oracle", + ModuleName + "Development.Shake.Rules.OrderOnly", + ModuleName + "Development.Shake.Rules.Rerun", + ModuleName + "Development.Shake.Shake", + ModuleName + "Development.Shake.Special", + ModuleName + "Development.Shake.Storage", + ModuleName + "Development.Shake.Types", + ModuleName + "Development.Shake.Util", + ModuleName + "Development.Shake.Value", + ModuleName "General.Bilist", + ModuleName "General.Binary", + ModuleName "General.Cleanup", + ModuleName "General.Concurrent", + ModuleName "General.Extra", + ModuleName "General.FileLock", + ModuleName "General.Intern", + ModuleName "General.Process", + ModuleName "General.String", + ModuleName "General.Template", + ModuleName "General.Timing", + ModuleName "Paths_shake", + ModuleName "Run", + ModuleName "Test.Assume", + ModuleName "Test.Basic", + ModuleName "Test.Benchmark", + ModuleName "Test.C", + ModuleName "Test.Cache", + ModuleName "Test.Command", + ModuleName "Test.Config", + ModuleName "Test.Digest", + ModuleName "Test.Directory", + ModuleName "Test.Docs", + ModuleName "Test.Errors", + ModuleName "Test.FileLock", + ModuleName "Test.FilePath", + ModuleName "Test.FilePattern", + ModuleName "Test.Files", + ModuleName "Test.Forward", + ModuleName "Test.Journal", + ModuleName "Test.Lint", + ModuleName "Test.Live", + ModuleName "Test.Makefile", + ModuleName "Test.Manual", + ModuleName "Test.Match", + ModuleName "Test.Monad", + ModuleName "Test.Ninja", + ModuleName "Test.Oracle", + ModuleName "Test.OrderOnly", + ModuleName "Test.Parallel", + ModuleName "Test.Pool", + ModuleName "Test.Progress", + ModuleName "Test.Random", + ModuleName "Test.Resources", + ModuleName "Test.Self", + ModuleName "Test.Tar", + ModuleName "Test.Tup", + ModuleName "Test.Type", + ModuleName "Test.Unicode", + ModuleName "Test.Util", + ModuleName "Test.Verbosity", + ModuleName "Test.Version"], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [ + "-main-is", + "Test.main", + "-rtsopts"] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion (mkVersion [4])) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "directory") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "hashable") + (OrLaterVersion + (mkVersion [1, 1, 2, 3])) + mainLibSet, + Dependency + (PackageName "binary") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "filepath") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "process") + (OrLaterVersion + (mkVersion [1, 1])) + mainLibSet, + Dependency + (PackageName + "unordered-containers") + (OrLaterVersion + (mkVersion [0, 2, 1])) + mainLibSet, + Dependency + (PackageName "bytestring") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "utf8-string") + (OrLaterVersion + (mkVersion [0, 3])) + mainLibSet, + Dependency + (PackageName "time") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "random") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "js-jquery") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "js-flot") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "transformers") + (OrLaterVersion + (mkVersion [0, 2])) + mainLibSet, + Dependency + (PackageName "deepseq") + (OrLaterVersion + (mkVersion [1, 1])) + mainLibSet, + Dependency + (PackageName "extra") + (OrLaterVersion + (mkVersion [1, 4, 8])) + mainLibSet, + Dependency + (PackageName "QuickCheck") + (OrLaterVersion + (mkVersion [2, 0])) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion (mkVersion [4])) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "directory") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "hashable") + (OrLaterVersion + (mkVersion [1, 1, 2, 3])) + mainLibSet, + Dependency + (PackageName "binary") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "filepath") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "process") + (OrLaterVersion + (mkVersion [1, 1])) + mainLibSet, + Dependency + (PackageName + "unordered-containers") + (OrLaterVersion + (mkVersion [0, 2, 1])) + mainLibSet, + Dependency + (PackageName "bytestring") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "utf8-string") + (OrLaterVersion + (mkVersion [0, 3])) + mainLibSet, + Dependency + (PackageName "time") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "random") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "js-jquery") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "js-flot") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "transformers") + (OrLaterVersion + (mkVersion [0, 2])) + mainLibSet, + Dependency + (PackageName "deepseq") + (OrLaterVersion + (mkVersion [1, 1])) + mainLibSet, + Dependency + (PackageName "extra") + (OrLaterVersion + (mkVersion [1, 4, 8])) + mainLibSet, + Dependency + (PackageName "QuickCheck") + (OrLaterVersion + (mkVersion [2, 0])) + mainLibSet], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `Var (Impl GHC (OrLaterVersion (mkVersion [7,6])))`, + condBranchIfTrue = CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = + TestSuiteUnsupported + (TestTypeUnknown + "" + (mkVersion [])), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + ["-with-rtsopts=-K1K"] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = Nothing}, + CondBranch { + condBranchCondition = + `Var (Impl GHC (OrLaterVersion (mkVersion [7,8])))`, + condBranchIfTrue = CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = + TestSuiteUnsupported + (TestTypeUnknown + "" + (mkVersion [])), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + ["-threaded"] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = Nothing}, + CondBranch { + condBranchCondition = + `Var (PackageFlag (FlagName "portable"))`, + condBranchIfTrue = CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = + TestSuiteUnsupported + (TestTypeUnknown + "" + (mkVersion [])), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = ["-DPORTABLE"], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `Var (Impl GHC (EarlierVersion (mkVersion [7,6])))`, + condBranchIfTrue = CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = + TestSuiteUnsupported + (TestTypeUnknown + "" + (mkVersion [])), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "old-time") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "old-time") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}, + condBranchIfFalse = Just + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = + TestSuiteUnsupported + (TestTypeUnknown + "" + (mkVersion [])), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `CNot (Var (OS Windows))`, + condBranchIfTrue = CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = + TestSuiteUnsupported + (TestTypeUnknown + "" + (mkVersion [])), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "unix") + (OrLaterVersion + (mkVersion [2, 5, 1])) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "unix") + (OrLaterVersion + (mkVersion [2, 5, 1])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}}, + CondBranch { + condBranchCondition = + `CNot (Var (OS Windows))`, + condBranchIfTrue = CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = + TestSuiteUnsupported + (TestTypeUnknown + "" + (mkVersion [])), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "unix") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "unix") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}], + condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.expr b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.expr index 5d8fb72de8899fab6ad0c45a21a653e89c3fb342..f714c7a0fe4572145392a8e2b53cf9d58f4c3c5e 100644 --- a/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.expr +++ b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.expr @@ -1,584 +1,589 @@ -GenericPackageDescription - {condBenchmarks = [], - condExecutables = [], - condForeignLibs = [], - condLibrary = Just - CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName "base") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [4, 4])) - (EarlierVersion (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "template-haskell") - (EarlierVersion (mkVersion [2, 10])) - mainLibSet, - Dependency - (PackageName "th-lift") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "containers") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [0, 4])) - (EarlierVersion (mkVersion [0, 6]))) - mainLibSet, - Dependency - (PackageName "vector") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [0, 9])) - (EarlierVersion (mkVersion [0, 11]))) - mainLibSet, - Dependency - (PackageName "text") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [0, 11])) - (EarlierVersion (mkVersion [1, 3]))) - mainLibSet, - Dependency - (PackageName "bytestring") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [0, 9])) - (EarlierVersion (mkVersion [0, 11]))) - mainLibSet], - condTreeData = Library - {exposedModules = [ModuleName "Instances.TH.Lift"], - libBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Just Haskell2010, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [SymbolicPath "src"], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - ["-Wall", "-fwarn-tabs"] [], - otherExtensions = [EnableExtension - TemplateHaskell], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor [] [], - sharedOptions = PerCompilerFlavor [] [], - staticOptions = PerCompilerFlavor [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [4, 4])) - (EarlierVersion - (mkVersion - [5]))) - mainLibSet, - Dependency - (PackageName - "template-haskell") - (EarlierVersion - (mkVersion - [2, 10])) - mainLibSet, - Dependency - (PackageName - "th-lift") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "containers") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [0, 4])) - (EarlierVersion - (mkVersion - [0, 6]))) - mainLibSet, - Dependency - (PackageName - "vector") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [0, 9])) - (EarlierVersion - (mkVersion - [0, - 11]))) - mainLibSet, - Dependency - (PackageName - "text") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [0, 11])) - (EarlierVersion - (mkVersion - [1, 3]))) - mainLibSet, - Dependency - (PackageName - "bytestring") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [0, 9])) - (EarlierVersion - (mkVersion - [0, - 11]))) - mainLibSet], - virtualModules = []}, - libExposed = True, - libName = LMainLibName, - libVisibility = LibraryVisibilityPublic, - reexportedModules = [], - signatures = []}}, - condSubLibraries = [], - condTestSuites = [_×_ - (UnqualComponentName "tests") - CondNode - {condTreeComponents = [], - condTreeConstraints = [Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "template-haskell") - (EarlierVersion (mkVersion [2, 10])) - mainLibSet, - Dependency - (PackageName "containers") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [0, 4])) - (EarlierVersion (mkVersion [0, 6]))) - mainLibSet, - Dependency - (PackageName "vector") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [0, 9])) - (EarlierVersion (mkVersion [0, 11]))) - mainLibSet, - Dependency - (PackageName "text") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [0, 11])) - (EarlierVersion (mkVersion [1, 2]))) - mainLibSet, - Dependency - (PackageName "bytestring") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [0, 9])) - (EarlierVersion (mkVersion [0, 11]))) - mainLibSet, - Dependency - (PackageName "th-lift-instances") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "QuickCheck") - (IntersectVersionRanges - (OrLaterVersion (mkVersion [2, 6])) - (EarlierVersion (mkVersion [2, 8]))) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Just Haskell2010, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [SymbolicPath - "tests"], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor [] [], - otherExtensions = [EnableExtension - TemplateHaskell], - otherLanguages = [], - otherModules = [ModuleName "Data"], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] [], - sharedOptions = PerCompilerFlavor - [] [], - staticOptions = PerCompilerFlavor - [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "template-haskell") - (EarlierVersion - (mkVersion - [2, - 10])) - mainLibSet, - Dependency - (PackageName - "containers") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [0, - 4])) - (EarlierVersion - (mkVersion - [0, - 6]))) - mainLibSet, - Dependency - (PackageName - "vector") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [0, - 9])) - (EarlierVersion - (mkVersion - [0, - 11]))) - mainLibSet, - Dependency - (PackageName - "text") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [0, - 11])) - (EarlierVersion - (mkVersion - [1, - 2]))) - mainLibSet, - Dependency - (PackageName - "bytestring") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [0, - 9])) - (EarlierVersion - (mkVersion - [0, - 11]))) - mainLibSet, - Dependency - (PackageName - "th-lift-instances") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "QuickCheck") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion - [2, - 6])) - (EarlierVersion - (mkVersion - [2, - 8]))) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteExeV10 - (mkVersion [1, 0]) "Main.hs", - testName = UnqualComponentName ""}}, - _×_ - (UnqualComponentName "doctests") - CondNode - {condTreeComponents = [CondBranch - {condBranchCondition = `Var (Impl GHC (EarlierVersion (mkVersion [7,6,1])))`, - condBranchIfFalse = Nothing, - condBranchIfTrue = CondNode - {condTreeComponents = [], - condTreeConstraints = [], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Nothing, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - ["-Werror"] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = PerCompilerFlavor - [] - [], - staticOptions = PerCompilerFlavor - [] - [], - targetBuildDepends = [], - virtualModules = []}, - testInterface = TestSuiteUnsupported - (TestTypeUnknown - "" - (mkVersion - [])), - testName = UnqualComponentName - ""}}}], - condTreeConstraints = [Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "directory") - (OrLaterVersion (mkVersion [1, 0])) - mainLibSet, - Dependency - (PackageName "doctest") - (OrLaterVersion (mkVersion [0, 9, 1])) - mainLibSet, - Dependency - (PackageName "filepath") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeData = TestSuite - {testBuildInfo = BuildInfo - {asmOptions = [], - asmSources = [], - autogenIncludes = [], - autogenModules = [], - buildToolDepends = [], - buildTools = [], - buildable = True, - cSources = [], - ccOptions = [], - cmmOptions = [], - cmmSources = [], - cppOptions = [], - customFieldsBI = [], - cxxOptions = [], - cxxSources = [], - defaultExtensions = [], - defaultLanguage = Just Haskell2010, - extraBundledLibs = [], - extraDynLibFlavours = [], - extraFrameworkDirs = [], - extraGHCiLibs = [], - extraLibDirs = [], - extraLibDirsStatic = [], - extraLibFlavours = [], - extraLibs = [], - extraLibsStatic = [], - frameworks = [], - hsSourceDirs = [SymbolicPath - "tests"], - hsc2hsOptions = [], - includeDirs = [], - includes = [], - installIncludes = [], - jsSources = [], - ldOptions = [], - mixins = [], - oldExtensions = [], - options = PerCompilerFlavor - ["-Wall", "-threaded"] - [], - otherExtensions = [], - otherLanguages = [], - otherModules = [], - pkgconfigDepends = [], - profOptions = PerCompilerFlavor - [] [], - sharedOptions = PerCompilerFlavor - [] [], - staticOptions = PerCompilerFlavor - [] [], - targetBuildDepends = [Dependency - (PackageName - "base") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet, - Dependency - (PackageName - "directory") - (OrLaterVersion - (mkVersion - [1, - 0])) - mainLibSet, - Dependency - (PackageName - "doctest") - (OrLaterVersion - (mkVersion - [0, - 9, - 1])) - mainLibSet, - Dependency - (PackageName - "filepath") - (OrLaterVersion - (mkVersion - [0])) - mainLibSet], - virtualModules = []}, - testInterface = TestSuiteExeV10 - (mkVersion [1, 0]) "doctests.hs", - testName = UnqualComponentName ""}}], - genPackageFlags = [], - gpdScannedVersion = Nothing, - packageDescription = PackageDescription - {author = "Benno F\252nfst\252ck", - benchmarks = [], - bugReports = "http://github.com/bennofs/th-lift-instances/issues", - buildTypeRaw = Just Custom, - category = "Template Haskell", - copyright = "Copyright (C) 2013-2014 Benno F\252nfst\252ck", - customFieldsPD = [_×_ "x-revision" "1"], - dataDir = ".", - dataFiles = [], - description = concat - ["Most data types in haskell platform do not have Lift instances. This package provides orphan instances\n", - "for containers, text, bytestring and vector."], - executables = [], - extraDocFiles = [], - extraSrcFiles = [".ghci", - ".gitignore", - ".travis.yml", - ".vim.custom", - "README.md"], - extraTmpFiles = [], - foreignLibs = [], - homepage = "http://github.com/bennofs/th-lift-instances/", - library = Nothing, - licenseFiles = [SymbolicPath "LICENSE"], - licenseRaw = Right BSD3, - maintainer = "Benno F\252nfst\252ck <benno.fuenfstueck@gmail.com>", - package = PackageIdentifier - {pkgName = PackageName "th-lift-instances", - pkgVersion = mkVersion [0, 1, 4]}, - pkgUrl = "", - setupBuildInfo = Nothing, - sourceRepos = [SourceRepo - {repoBranch = Nothing, - repoKind = RepoHead, - repoLocation = Just - "https://github.com/bennofs/th-lift-instances.git", - repoModule = Nothing, - repoSubdir = Nothing, - repoTag = Nothing, - repoType = Just (KnownRepoType Git)}], - specVersion = CabalSpecV1_10, - stability = "experimental", - subLibraries = [], - synopsis = "Lift instances for template-haskell for common data types.", - testSuites = [], - testedWith = []}} +GenericPackageDescription { + packageDescription = + PackageDescription { + specVersion = CabalSpecV1_10, + package = PackageIdentifier { + pkgName = PackageName + "th-lift-instances", + pkgVersion = mkVersion + [0, 1, 4]}, + licenseRaw = Right BSD3, + licenseFiles = [ + SymbolicPath "LICENSE"], + copyright = + "Copyright (C) 2013-2014 Benno F\252nfst\252ck", + maintainer = + "Benno F\252nfst\252ck <benno.fuenfstueck@gmail.com>", + author = + "Benno F\252nfst\252ck", + stability = "experimental", + testedWith = [], + homepage = + "http://github.com/bennofs/th-lift-instances/", + pkgUrl = "", + bugReports = + "http://github.com/bennofs/th-lift-instances/issues", + sourceRepos = [ + SourceRepo { + repoKind = RepoHead, + repoType = Just + (KnownRepoType Git), + repoLocation = Just + "https://github.com/bennofs/th-lift-instances.git", + repoModule = Nothing, + repoBranch = Nothing, + repoTag = Nothing, + repoSubdir = Nothing}], + synopsis = + "Lift instances for template-haskell for common data types.", + description = + concat + [ + "Most data types in haskell platform do not have Lift instances. This package provides orphan instances\n", + "for containers, text, bytestring and vector."], + category = "Template Haskell", + customFieldsPD = [ + _×_ "x-revision" "1"], + buildTypeRaw = Just Custom, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = ".", + extraSrcFiles = [ + ".ghci", + ".gitignore", + ".travis.yml", + ".vim.custom", + "README.md"], + extraTmpFiles = [], + extraDocFiles = []}, + gpdScannedVersion = Nothing, + genPackageFlags = [], + condLibrary = Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName "Instances.TH.Lift"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "src"], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [ + EnableExtension + TemplateHaskell], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + ["-Wall", "-fwarn-tabs"] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 4])) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "template-haskell") + (EarlierVersion + (mkVersion [2, 10])) + mainLibSet, + Dependency + (PackageName "th-lift") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "containers") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 4])) + (EarlierVersion + (mkVersion [0, 6]))) + mainLibSet, + Dependency + (PackageName "vector") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 9])) + (EarlierVersion + (mkVersion [0, 11]))) + mainLibSet, + Dependency + (PackageName "text") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 11])) + (EarlierVersion + (mkVersion [1, 3]))) + mainLibSet, + Dependency + (PackageName "bytestring") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 9])) + (EarlierVersion + (mkVersion [0, 11]))) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 4])) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "template-haskell") + (EarlierVersion + (mkVersion [2, 10])) + mainLibSet, + Dependency + (PackageName "th-lift") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "containers") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 4])) + (EarlierVersion + (mkVersion [0, 6]))) + mainLibSet, + Dependency + (PackageName "vector") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 9])) + (EarlierVersion + (mkVersion [0, 11]))) + mainLibSet, + Dependency + (PackageName "text") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 11])) + (EarlierVersion + (mkVersion [1, 3]))) + mainLibSet, + Dependency + (PackageName "bytestring") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 9])) + (EarlierVersion + (mkVersion [0, 11]))) + mainLibSet], + condTreeComponents = []}, + condSubLibraries = [], + condForeignLibs = [], + condExecutables = [], + condTestSuites = [ + _×_ + (UnqualComponentName "tests") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + "Main.hs", + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "tests"], + otherModules = [ + ModuleName "Data"], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [ + EnableExtension + TemplateHaskell], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "template-haskell") + (EarlierVersion + (mkVersion [2, 10])) + mainLibSet, + Dependency + (PackageName "containers") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 4])) + (EarlierVersion + (mkVersion [0, 6]))) + mainLibSet, + Dependency + (PackageName "vector") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 9])) + (EarlierVersion + (mkVersion [0, 11]))) + mainLibSet, + Dependency + (PackageName "text") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 11])) + (EarlierVersion + (mkVersion [1, 2]))) + mainLibSet, + Dependency + (PackageName "bytestring") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 9])) + (EarlierVersion + (mkVersion [0, 11]))) + mainLibSet, + Dependency + (PackageName + "th-lift-instances") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "QuickCheck") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [2, 6])) + (EarlierVersion + (mkVersion [2, 8]))) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "template-haskell") + (EarlierVersion + (mkVersion [2, 10])) + mainLibSet, + Dependency + (PackageName "containers") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 4])) + (EarlierVersion + (mkVersion [0, 6]))) + mainLibSet, + Dependency + (PackageName "vector") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 9])) + (EarlierVersion + (mkVersion [0, 11]))) + mainLibSet, + Dependency + (PackageName "text") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 11])) + (EarlierVersion + (mkVersion [1, 2]))) + mainLibSet, + Dependency + (PackageName "bytestring") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 9])) + (EarlierVersion + (mkVersion [0, 11]))) + mainLibSet, + Dependency + (PackageName + "th-lift-instances") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "QuickCheck") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [2, 6])) + (EarlierVersion + (mkVersion [2, 8]))) + mainLibSet], + condTreeComponents = []}, + _×_ + (UnqualComponentName "doctests") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + "doctests.hs", + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "tests"], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + ["-Wall", "-threaded"] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "directory") + (OrLaterVersion + (mkVersion [1, 0])) + mainLibSet, + Dependency + (PackageName "doctest") + (OrLaterVersion + (mkVersion [0, 9, 1])) + mainLibSet, + Dependency + (PackageName "filepath") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "directory") + (OrLaterVersion + (mkVersion [1, 0])) + mainLibSet, + Dependency + (PackageName "doctest") + (OrLaterVersion + (mkVersion [0, 9, 1])) + mainLibSet, + Dependency + (PackageName "filepath") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `Var (Impl GHC (EarlierVersion (mkVersion [7,6,1])))`, + condBranchIfTrue = CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = + TestSuiteUnsupported + (TestTypeUnknown + "" + (mkVersion [])), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + ["-Werror"] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}], + condBenchmarks = []} diff --git a/Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs b/Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs index 9ad401b4b17007d913f610948159235a5ea38720..ea4bf7602c8adbcfe509d0f8037b8dfc484a1b69 100644 --- a/Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs +++ b/Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs @@ -27,9 +27,9 @@ tests = testGroup "Distribution.Utils.Structured" -- The difference is in encoding of newtypes #if MIN_VERSION_base(4,7,0) , testCase "GenericPackageDescription" $ - md5Check (Proxy :: Proxy GenericPackageDescription) 0xa164cbe5092a1cd31da1f15358d1537a + md5Check (Proxy :: Proxy GenericPackageDescription) 0xafbf1cfb39ece402a2008d07f5e5ffd8 , testCase "LocalBuildInfo" $ - md5Check (Proxy :: Proxy LocalBuildInfo) 0x9ce83e4aec3b2fa6d7f999dbc32c2a33 + md5Check (Proxy :: Proxy LocalBuildInfo) 0xd8b4c7f04e75345f0303fe2c3093bc29 #endif ] diff --git a/Cabal/src/Distribution/Simple/Build.hs b/Cabal/src/Distribution/Simple/Build.hs index 8a4beecfce43b96777b0a49d71892331278ab06f..4fe8a48c134a68656383baf9827aab6d53a55345 100644 --- a/Cabal/src/Distribution/Simple/Build.hs +++ b/Cabal/src/Distribution/Simple/Build.hs @@ -69,9 +69,10 @@ import Distribution.Simple.BuildTarget import Distribution.Simple.BuildToolDepends import Distribution.Simple.PreProcess import Distribution.Simple.LocalBuildInfo -import Distribution.Simple.Program.Builtin (ghcProgram, ghcjsProgram, uhcProgram, jhcProgram, haskellSuiteProgram) +import Distribution.Simple.Program +import Distribution.Simple.Program.Builtin (haskellSuiteProgram) +import qualified Distribution.Simple.Program.GHC as GHC import Distribution.Simple.Program.Types -import Distribution.Simple.Program.Db import Distribution.Simple.ShowBuildInfo import Distribution.Simple.BuildPaths import Distribution.Simple.Configure @@ -332,14 +333,14 @@ buildComponent verbosity numJobs pkg_descr lbi suffixes let exe = testSuiteExeV10AsExe test preprocessComponent pkg_descr comp lbi clbi False verbosity suffixes extras <- preprocessExtras verbosity comp lbi + (genDir, generatedExtras) <- generateCode (testCodeGenerators test) (testName test) pkg_descr (testBuildInfo test) lbi clbi verbosity setupMessage' verbosity "Building" (packageId pkg_descr) (componentLocalName clbi) (maybeComponentInstantiatedWith clbi) let ebi = buildInfo exe - exe' = exe { buildInfo = addExtraCSources ebi extras } + exe' = exe { buildInfo = addSrcDir (addExtraOtherModules (addExtraCSources ebi extras) generatedExtras) genDir } -- todo extend hssrcdirs buildExe verbosity numJobs pkg_descr lbi exe' clbi return Nothing - buildComponent verbosity numJobs pkg_descr lbi0 suffixes comp@(CTest test@TestSuite { testInterface = TestSuiteLibV09{} }) @@ -353,10 +354,13 @@ buildComponent verbosity numJobs pkg_descr lbi0 suffixes let (pkg, lib, libClbi, lbi, ipi, exe, exeClbi) = testSuiteLibV09AsLibAndExe pkg_descr test clbi lbi0 distPref pwd preprocessComponent pkg_descr comp lbi clbi False verbosity suffixes - extras <- preprocessExtras verbosity comp lbi + extras <- preprocessExtras verbosity comp lbi -- TODO find cpphs processed files + (genDir, generatedExtras) <- generateCode (testCodeGenerators test) (testName test) pkg_descr (testBuildInfo test) lbi clbi verbosity setupMessage' verbosity "Building" (packageId pkg_descr) (componentLocalName clbi) (maybeComponentInstantiatedWith clbi) - buildLib verbosity numJobs pkg lbi lib libClbi + let libbi = libBuildInfo lib + lib' = lib { libBuildInfo = addSrcDir (addExtraOtherModules libbi generatedExtras) genDir } + buildLib verbosity numJobs pkg lbi lib' libClbi -- NB: need to enable multiple instances here, because on 7.10+ -- the package name is the same as the library, and we still -- want the registration to go through. @@ -400,6 +404,32 @@ buildComponent verbosity _ _ _ _ die' verbosity $ "No support for building benchmark type " ++ prettyShow tt + +generateCode + :: [String] + -> UnqualComponentName + -> PackageDescription + -> BuildInfo + -> LocalBuildInfo + -> ComponentLocalBuildInfo + -> Verbosity + -> IO (FilePath, [ModuleName.ModuleName]) +generateCode codeGens nm pdesc bi lbi clbi verbosity = do + when (not . null $ codeGens) $ createDirectoryIfMissingVerbose verbosity True tgtDir + (\x -> (tgtDir,x)) . concat <$> mapM go codeGens + where + allLibs = (maybe id (:) $ library pdesc) (subLibraries pdesc) + dependencyLibs = filter (const True) allLibs -- intersect with componentPackageDeps of clbi + srcDirs = concatMap (hsSourceDirs . libBuildInfo) dependencyLibs + nm' = unUnqualComponentName nm + tgtDir = buildDir lbi </> nm' </> nm' ++ "-gen" + go :: String -> IO [ModuleName.ModuleName] + go codeGenProg = fmap fromString . lines <$> getDbProgramOutput verbosity (simpleProgram codeGenProg) (withPrograms lbi) + ((tgtDir : map getSymbolicPath srcDirs) ++ + ("--" : + GHC.renderGhcOptions (compiler lbi) (hostPlatform lbi) (GHC.componentGhcOptions verbosity lbi bi clbi tgtDir))) + + -- | Add extra C sources generated by preprocessing to build -- information. addExtraCSources :: BuildInfo -> [FilePath] -> BuildInfo @@ -435,6 +465,21 @@ addExtraAsmSources bi extras = bi { asmSources = new } old = Set.fromList $ asmSources bi exs = Set.fromList extras +-- | Add extra HS modules generated by preprocessing to build +-- information. +addExtraOtherModules :: BuildInfo -> [ModuleName.ModuleName] -> BuildInfo +addExtraOtherModules bi extras = bi { otherModules = new } + where new = Set.toList $ old `Set.union` exs + old = Set.fromList $ otherModules bi + exs = Set.fromList extras + +-- | Add extra source dir for generated modules. +addSrcDir :: BuildInfo -> FilePath -> BuildInfo +addSrcDir bi extra = bi { hsSourceDirs = new } + where new = Set.toList $ old `Set.union` ex + old = Set.fromList $ hsSourceDirs bi + ex = Set.fromList [unsafeMakeSymbolicPath extra] -- TODO + replComponent :: ReplOptions -> Verbosity diff --git a/Cabal/src/Distribution/Simple/PreProcess.hs b/Cabal/src/Distribution/Simple/PreProcess.hs index 5290012299f6179ef2f2f9b14a55e6410436a611..04f92dd58fa7e616130ddbabc5ca106a8e441325 100644 --- a/Cabal/src/Distribution/Simple/PreProcess.hs +++ b/Cabal/src/Distribution/Simple/PreProcess.hs @@ -57,7 +57,7 @@ import Distribution.Version import Distribution.Verbosity import Distribution.Utils.Path -import System.Directory (doesFileExist) +import System.Directory (doesFileExist, doesDirectoryExist) import System.Info (os, arch) import System.FilePath (splitExtension, dropExtensions, (</>), (<.>), takeDirectory, normalise, replaceExtension, @@ -237,7 +237,7 @@ preprocessComponent pd comp lbi clbi isSrcDist verbosity handlers = builtinSuffixes = builtinHaskellSuffixes ++ builtinCSuffixes localHandlers bi = [(ext, h bi lbi clbi) | (ext, h) <- handlers] pre dirs dir lhndlrs fp = - preprocessFile (map unsafeMakeSymbolicPath dirs) dir isSrcDist fp verbosity builtinSuffixes lhndlrs + preprocessFile (map unsafeMakeSymbolicPath dirs) dir isSrcDist fp verbosity builtinSuffixes lhndlrs True preProcessTest test = preProcessComponent (testBuildInfo test) (testModules test) preProcessBench bm = preProcessComponent (benchmarkBuildInfo bm) @@ -255,20 +255,20 @@ preprocessComponent pd comp lbi clbi isSrcDist verbosity handlers = , autogenPackageModulesDir lbi ] sequence_ [ preprocessFile (map unsafeMakeSymbolicPath sourceDirs) dir isSrcDist (ModuleName.toFilePath modu) verbosity builtinSuffixes - biHandlers + biHandlers False | modu <- modules ] - -- XXX: what we do here (re SymbolicPath dir) -- XXX: 2020-10-15 do we rely here on CWD being the PackageDir? + -- Note we don't fail on missing in this case, because the main file may be generated later (i.e. by a test code generator) preprocessFile (unsafeMakeSymbolicPath dir : hsSourceDirs bi) dir isSrcDist (dropExtensions $ exePath) verbosity - builtinSuffixes biHandlers + builtinSuffixes biHandlers False --TODO: try to list all the modules that could not be found -- not just the first one. It's annoying and slow due to the need -- to reconfigure after editing the .cabal file each time. --- |Find the first extension of the file that exists, and preprocess it +-- | Find the first extension of the file that exists, and preprocess it -- if required. preprocessFile :: [SymbolicPath PackageDir SourceDir] -- ^ source directories @@ -279,8 +279,9 @@ preprocessFile -> Verbosity -- ^verbosity -> [String] -- ^builtin suffixes -> [(String, PreProcessor)] -- ^possible preprocessors + -> Bool -- ^fail on missing file -> IO () -preprocessFile searchLoc buildLoc forSDist baseFile verbosity builtinSuffixes handlers = do +preprocessFile searchLoc buildLoc forSDist baseFile verbosity builtinSuffixes handlers failOnMissing = do -- look for files in the various source dirs with this module name -- and a file extension of a known preprocessor psrcFiles <- findFileWithExtension' (map fst handlers) (map getSymbolicPath searchLoc) baseFile @@ -294,8 +295,8 @@ preprocessFile searchLoc buildLoc forSDist baseFile verbosity builtinSuffixes ha -- the rest of the build system being aware of it (somewhat dodgy) Nothing -> do bsrcFiles <- findFileWithExtension builtinSuffixes (buildLoc : map getSymbolicPath searchLoc) baseFile - case bsrcFiles of - Nothing -> + case (bsrcFiles, failOnMissing) of + (Nothing, True) -> die' verbosity $ "can't find source for " ++ baseFile ++ " in " ++ intercalate ", " (map getSymbolicPath searchLoc) _ -> return () @@ -809,9 +810,13 @@ preprocessExtras verbosity comp lbi = case comp of ++ "type " ++ prettyShow tt where pp :: FilePath -> IO [FilePath] - pp dir = (map (dir </>) . filter not_sub . concat) - <$> for knownExtrasHandlers - (withLexicalCallStack (\f -> f dir)) + pp dir = do + b <- doesDirectoryExist dir + if b + then (map (dir </>) . filter not_sub . concat) + <$> for knownExtrasHandlers + (withLexicalCallStack (\f -> f dir)) + else pure [] -- TODO: This is a terrible hack to work around #3545 while we don't -- reorganize the directory layout. Basically, for the main -- library, we might accidentally pick up autogenerated sources for diff --git a/cabal-testsuite/PackageTests/TestCodeGenerator/Foo.hs b/cabal-testsuite/PackageTests/TestCodeGenerator/Foo.hs new file mode 100644 index 0000000000000000000000000000000000000000..2d3e705b0cbae2308bfdf23b3e01b71ab32bb27b --- /dev/null +++ b/cabal-testsuite/PackageTests/TestCodeGenerator/Foo.hs @@ -0,0 +1,4 @@ +module Foo where + +fooTest :: [String] -> Bool +fooTest _ = True diff --git a/cabal-testsuite/PackageTests/TestCodeGenerator/cabal.out b/cabal-testsuite/PackageTests/TestCodeGenerator/cabal.out new file mode 100644 index 0000000000000000000000000000000000000000..0403dcaa4f54296ed7d947fbf1ea055757ef1ce6 --- /dev/null +++ b/cabal-testsuite/PackageTests/TestCodeGenerator/cabal.out @@ -0,0 +1,21 @@ +# cabal v2-test +Resolving dependencies... +Build profile: -w ghc-<GHCVER> -O1 +In order, the following will be built: + - my-0.1 (lib) (first run) + - test-code-gen-0.1.0.0 (exe:test-code-gen) (first run) + - my-0.1 (test:test-Foo) (first run) +Configuring library for my-0.1.. +Preprocessing library for my-0.1.. +Building library for my-0.1.. +Configuring executable 'test-code-gen' for test-code-gen-0.1.0.0.. +Preprocessing executable 'test-code-gen' for test-code-gen-0.1.0.0.. +Building executable 'test-code-gen' for test-code-gen-0.1.0.0.. +Configuring test suite 'test-Foo' for my-0.1.. +Preprocessing test suite 'test-Foo' for my-0.1.. +Building test suite 'test-Foo' for my-0.1.. +Running 1 test suites... +Test suite test-Foo: RUNNING... +Test suite test-Foo: PASS +Test suite logged to: <ROOT>/cabal.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/my-0.1/t/test-Foo/test/my-0.1-test-Foo.log +1 of 1 test suites (1 of 1 test cases) passed. diff --git a/cabal-testsuite/PackageTests/TestCodeGenerator/cabal.project b/cabal-testsuite/PackageTests/TestCodeGenerator/cabal.project new file mode 100644 index 0000000000000000000000000000000000000000..1b2cd5ab5dfeefea33a35ce477029a8ff9c0acdf --- /dev/null +++ b/cabal-testsuite/PackageTests/TestCodeGenerator/cabal.project @@ -0,0 +1 @@ +packages: . test-code-gen/test-code-gen.cabal diff --git a/cabal-testsuite/PackageTests/TestCodeGenerator/cabal.test.hs b/cabal-testsuite/PackageTests/TestCodeGenerator/cabal.test.hs new file mode 100644 index 0000000000000000000000000000000000000000..94d4db92de8cb7e5865393facba4d257db0d8e4a --- /dev/null +++ b/cabal-testsuite/PackageTests/TestCodeGenerator/cabal.test.hs @@ -0,0 +1,4 @@ +import Test.Cabal.Prelude + +main = cabalTest $ do + cabal "v2-test" [] diff --git a/cabal-testsuite/PackageTests/TestCodeGenerator/my.cabal b/cabal-testsuite/PackageTests/TestCodeGenerator/my.cabal new file mode 100644 index 0000000000000000000000000000000000000000..fe74eaf7af246750435964d13aee710797823a63 --- /dev/null +++ b/cabal-testsuite/PackageTests/TestCodeGenerator/my.cabal @@ -0,0 +1,19 @@ +cabal-version: 3.6 +name: my +version: 0.1 +license: BSD-3-Clause +build-type: Simple + +library + default-language: Haskell2010 + exposed-modules: Foo + build-depends: base + +test-suite test-Foo + default-language: Haskell2010 + type: exitcode-stdio-1.0 + hs-source-dirs: tests + main-is: Main.hs + build-tool-depends: test-code-gen:test-code-gen + code-generators: test-code-gen + build-depends: base, my diff --git a/cabal-testsuite/PackageTests/TestCodeGenerator/test-code-gen/CHANGELOG.md b/cabal-testsuite/PackageTests/TestCodeGenerator/test-code-gen/CHANGELOG.md new file mode 100644 index 0000000000000000000000000000000000000000..984580fad3475b0ed952c06ad05ebfc9bbc6d9a5 --- /dev/null +++ b/cabal-testsuite/PackageTests/TestCodeGenerator/test-code-gen/CHANGELOG.md @@ -0,0 +1,5 @@ +# Revision history for test-code-gen + +## 0.1.0.0 -- YYYY-mm-dd + +* First version. Released on an unsuspecting world. diff --git a/cabal-testsuite/PackageTests/TestCodeGenerator/test-code-gen/LICENSE b/cabal-testsuite/PackageTests/TestCodeGenerator/test-code-gen/LICENSE new file mode 100644 index 0000000000000000000000000000000000000000..b28929f30d7324a708d085ad489481542f7e513f --- /dev/null +++ b/cabal-testsuite/PackageTests/TestCodeGenerator/test-code-gen/LICENSE @@ -0,0 +1,30 @@ +Copyright (c) 2022, + +All rights reserved. + +Redistribution and use in source and binary forms, with or without +modification, are permitted provided that the following conditions are met: + + * Redistributions of source code must retain the above copyright + notice, this list of conditions and the following disclaimer. + + * Redistributions in binary form must reproduce the above + copyright notice, this list of conditions and the following + disclaimer in the documentation and/or other materials provided + with the distribution. + + * Neither the name of nor the names of other + contributors may be used to endorse or promote products derived + from this software without specific prior written permission. + +THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS +"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT +LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR +A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT +OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, +SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT +LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, +DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY +THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT +(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE +OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. diff --git a/cabal-testsuite/PackageTests/TestCodeGenerator/test-code-gen/app/Main.hs b/cabal-testsuite/PackageTests/TestCodeGenerator/test-code-gen/app/Main.hs new file mode 100644 index 0000000000000000000000000000000000000000..a7b90b232c7fce7e4b5a00253da02c52ffcebfa9 --- /dev/null +++ b/cabal-testsuite/PackageTests/TestCodeGenerator/test-code-gen/app/Main.hs @@ -0,0 +1,18 @@ +module Main where +import System.FilePath +import System.Environment + +main :: IO () +main = do + (tgt:rest) <- getArgs + let (srcDirs, ghcArgs) = splitArgs rest + let isGood = srcDirs == ["."] && "-outputdir" `elem` ghcArgs + if isGood + then writeFile (tgt </> "Main.hs") $ "module Main where main = pure ()" + else writeFile (tgt </> "Main.hs") $ "module Main where main = error \"failure\"" + +splitArgs = go [] + where + go r ("--":xs) = (reverse r, xs) + go r (x:xs) = go (x:r) xs + go r [] = (reverse r, []) diff --git a/cabal-testsuite/PackageTests/TestCodeGenerator/test-code-gen/test-code-gen.cabal b/cabal-testsuite/PackageTests/TestCodeGenerator/test-code-gen/test-code-gen.cabal new file mode 100644 index 0000000000000000000000000000000000000000..a2c7d8a6823fb2e1547a4ae7953988c562f114b5 --- /dev/null +++ b/cabal-testsuite/PackageTests/TestCodeGenerator/test-code-gen/test-code-gen.cabal @@ -0,0 +1,15 @@ +cabal-version: 3.0 +name: test-code-gen +version: 0.1.0.0 +license: BSD-3-Clause +license-file: LICENSE +build-type: Simple +extra-doc-files: CHANGELOG.md + + +executable test-code-gen + main-is: Main.hs + build-depends: base, filepath + hs-source-dirs: app + default-language: Haskell2010 + diff --git a/cabal-testsuite/PackageTests/TestCodeGenerator/tests/blank b/cabal-testsuite/PackageTests/TestCodeGenerator/tests/blank new file mode 100644 index 0000000000000000000000000000000000000000..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391 diff --git a/changelog.d/pr-7688 b/changelog.d/pr-7688 new file mode 100644 index 0000000000000000000000000000000000000000..7cf1dad5c28d6ea5f1197ce5e433156aba74c7dd --- /dev/null +++ b/changelog.d/pr-7688 @@ -0,0 +1,11 @@ +synopsis: Add code-generators field to test-suite stanza +packages: Cabal +prs: #7688 +issues: #4500 + +description: { + +Test-suite stanzas now may contain a `code-generators:` field that can be used to run executables as preprocessors which take existing locations of library code and cabal-generated ghc build flags, and output new modules for use in the test stanza. This can be used to automatically generate drivers for "discover" style tests, including doctests. + + +} diff --git a/doc/cabal-package.rst b/doc/cabal-package.rst index 4541d12f61b5c11d8aeed844c30286a59226f7e2..819d146dc11b478cec3562e6de108691c4f94de1 100644 --- a/doc/cabal-package.rst +++ b/doc/cabal-package.rst @@ -1245,6 +1245,24 @@ the :pkg-field:`test-module` field. The module exporting the ``tests`` symbol. +.. pkg-field:: code-generators + + An optional list of preprocessors which can generate new modules + for use in the test-suite. + + A list of executabes (possibly brought into scope by :pkg-field:`build-tool-depends`) that are run after all other + preprocessors. These executables are invoked as so: ``exe-name + TARGETDIR [SOURCEDIRS] -- [GHCOPTIONS]``. The arguments are, in order a target dir for + output, a sequence of all source directories with source files of + local lib components that the given test stanza dependens on, and + following a double dash, all options cabal would pass to ghc for a + build. They are expected to output a newline-seperated list of + generated modules which have been written to the targetdir + (excepting, if written, the main module). This can + be used for driving doctests and other discover-style tests generated + from source code. + + Example: Package using ``exitcode-stdio-1.0`` interface """"""""""""""""""""""""""""""""""""""""""""""""""""""" diff --git a/doc/file-format-changelog.rst b/doc/file-format-changelog.rst index cffa4edd578623a1f31dc99dbd73ed220ea6854f..566d7a79ce5158564607b2bcc6433f82b193ee44 100644 --- a/doc/file-format-changelog.rst +++ b/doc/file-format-changelog.rst @@ -22,6 +22,17 @@ relative to the respective preceding *published* version. ``cabal-version: 3.x`` ---------------------- +* Added field ``code-generators`` to :pkg-section:`test-suite` stanzas. This + enumerates executabes (possibly brought into scope by :pkg-field:`build-tool-depends`) that are run after all other + preprocessors. These executables are invoked with a target dir for + output, a sequence of all source directories with source files of + local lib components that the given test stanza dependens on, and + following a double dash, all options cabal would pass to ghc for a + build. They are expected to output a newline-seperated list of + generated modules which have been written to the targetdir. This can + be used for driving doctests and other discover-style tests generated + from source code. + * Added fields :pkg-field:`extra-libraries-static` and :pkg-field:`extra-lib-dirs-static` to allow Haskell libraries to remember linker flags needed for fully static linking of system libraries into