diff --git a/Cabal-syntax/Cabal-syntax.cabal b/Cabal-syntax/Cabal-syntax.cabal index 85137dc147c..09edee0eced 100644 --- a/Cabal-syntax/Cabal-syntax.cabal +++ b/Cabal-syntax/Cabal-syntax.cabal @@ -121,6 +121,7 @@ library Distribution.Types.AbiDependency Distribution.Types.AbiHash Distribution.Types.Benchmark + Distribution.Types.BenchmarkStanza Distribution.Types.Benchmark.Lens Distribution.Types.BenchmarkInterface Distribution.Types.BenchmarkType @@ -160,6 +161,8 @@ library Distribution.Types.Library.Lens Distribution.Types.LibraryName Distribution.Types.LibraryVisibility + Distribution.Types.Imports + Distribution.Types.Imports.Lens Distribution.Types.MissingDependency Distribution.Types.MissingDependencyReason Distribution.Types.Mixin @@ -183,6 +186,7 @@ library Distribution.Types.SourceRepo Distribution.Types.SourceRepo.Lens Distribution.Types.TestSuite + Distribution.Types.TestSuiteStanza Distribution.Types.TestSuite.Lens Distribution.Types.TestSuiteInterface Distribution.Types.TestType diff --git a/Cabal-syntax/src/Distribution/PackageDescription.hs b/Cabal-syntax/src/Distribution/PackageDescription.hs index 47d46673e5f..bda173bd969 100644 --- a/Cabal-syntax/src/Distribution/PackageDescription.hs +++ b/Cabal-syntax/src/Distribution/PackageDescription.hs @@ -15,6 +15,9 @@ module Distribution.PackageDescription module Distribution.Types.PackageDescription , module Distribution.Types.GenericPackageDescription + -- * Working with Imports + , module Distribution.Types.Imports + -- * Components , module Distribution.Types.ComponentName @@ -29,11 +32,13 @@ module Distribution.PackageDescription -- ** TestSuite , module Distribution.Types.TestSuite + , module Distribution.Types.TestSuiteStanza , module Distribution.Types.TestType , module Distribution.Types.TestSuiteInterface -- ** Benchmark , module Distribution.Types.Benchmark + , module Distribution.Types.BenchmarkStanza , module Distribution.Types.BenchmarkType , module Distribution.Types.BenchmarkInterface @@ -88,6 +93,7 @@ import Prelude () import Distribution.Types.Benchmark import Distribution.Types.BenchmarkInterface +import Distribution.Types.BenchmarkStanza import Distribution.Types.BenchmarkType import Distribution.Types.BuildInfo import Distribution.Types.BuildType @@ -105,6 +111,7 @@ import Distribution.Types.ForeignLibOption import Distribution.Types.ForeignLibType import Distribution.Types.GenericPackageDescription import Distribution.Types.HookedBuildInfo +import Distribution.Types.Imports import Distribution.Types.IncludeRenaming import Distribution.Types.LegacyExeDependency import Distribution.Types.Library @@ -124,5 +131,6 @@ import Distribution.Types.SetupBuildInfo import Distribution.Types.SourceRepo import Distribution.Types.TestSuite import Distribution.Types.TestSuiteInterface +import Distribution.Types.TestSuiteStanza import Distribution.Types.TestType import Distribution.Types.UnqualComponentName diff --git a/Cabal-syntax/src/Distribution/PackageDescription/FieldGrammar.hs b/Cabal-syntax/src/Distribution/PackageDescription/FieldGrammar.hs index 24861389b8f..f08db2bc58f 100644 --- a/Cabal-syntax/src/Distribution/PackageDescription/FieldGrammar.hs +++ b/Cabal-syntax/src/Distribution/PackageDescription/FieldGrammar.hs @@ -22,22 +22,10 @@ module Distribution.PackageDescription.FieldGrammar , executableFieldGrammar -- * Test suite - , TestSuiteStanza (..) , testSuiteFieldGrammar - , validateTestSuite - , unvalidateTestSuite - - -- ** Lenses - , testStanzaTestType - , testStanzaMainIs - , testStanzaTestModule - , testStanzaBuildInfo -- * Benchmark - , BenchmarkStanza (..) , benchmarkFieldGrammar - , validateBenchmark - , unvalidateBenchmark -- * Field grammars , formatDependencyList @@ -48,12 +36,6 @@ module Distribution.PackageDescription.FieldGrammar , formatOtherExtensions , formatOtherModules - -- ** Lenses - , benchmarkStanzaBenchmarkType - , benchmarkStanzaMainIs - , benchmarkStanzaBenchmarkModule - , benchmarkStanzaBuildInfo - -- * Flag , flagFieldGrammar @@ -290,43 +272,6 @@ executableFieldGrammar n = {-# SPECIALIZE executableFieldGrammar :: UnqualComponentName -> ParsecFieldGrammar' Executable #-} {-# SPECIALIZE executableFieldGrammar :: UnqualComponentName -> PrettyFieldGrammar' Executable #-} -------------------------------------------------------------------------------- --- TestSuite -------------------------------------------------------------------------------- - --- | An intermediate type just used for parsing the test-suite stanza. --- After validation it is converted into the proper 'TestSuite' type. -data TestSuiteStanza = TestSuiteStanza - { _testStanzaTestType :: Maybe TestType - , _testStanzaMainIs :: Maybe (RelativePath Source File) - , _testStanzaTestModule :: Maybe ModuleName - , _testStanzaBuildInfo :: BuildInfo - , _testStanzaCodeGenerators :: [String] - } - -instance L.HasBuildInfo TestSuiteStanza where - buildInfo = testStanzaBuildInfo - -testStanzaTestType :: Lens' TestSuiteStanza (Maybe TestType) -testStanzaTestType f s = fmap (\x -> s{_testStanzaTestType = x}) (f (_testStanzaTestType s)) -{-# INLINE testStanzaTestType #-} - -testStanzaMainIs :: Lens' TestSuiteStanza (Maybe (RelativePath Source File)) -testStanzaMainIs f s = fmap (\x -> s{_testStanzaMainIs = x}) (f (_testStanzaMainIs s)) -{-# INLINE testStanzaMainIs #-} - -testStanzaTestModule :: Lens' TestSuiteStanza (Maybe ModuleName) -testStanzaTestModule f s = fmap (\x -> s{_testStanzaTestModule = x}) (f (_testStanzaTestModule s)) -{-# INLINE testStanzaTestModule #-} - -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) @@ -361,117 +306,10 @@ testSuiteFieldGrammar = <*> monoidalFieldAla "code-generators" (alaList' CommaFSep Token) testStanzaCodeGenerators ^^^ availableSince CabalSpecV3_8 [] -validateTestSuite :: CabalSpecVersion -> Position -> TestSuiteStanza -> ParseResult src TestSuite -validateTestSuite cabalSpecVersion pos stanza = case testSuiteType of - Nothing -> pure basicTestSuite - Just tt@(TestTypeUnknown _ _) -> - pure - basicTestSuite - { testInterface = TestSuiteUnsupported tt - } - Just tt - | tt `notElem` knownTestTypes -> - pure - basicTestSuite - { testInterface = TestSuiteUnsupported tt - } - Just tt@(TestTypeExe ver) -> case _testStanzaMainIs stanza of - Nothing -> do - parseFailure pos (missingField "main-is" tt) - pure emptyTestSuite - Just file -> do - when (isJust (_testStanzaTestModule stanza)) $ - parseWarning pos PWTExtraBenchmarkModule (extraField "test-module" tt) - pure - basicTestSuite - { testInterface = TestSuiteExeV10 ver file - } - Just tt@(TestTypeLib ver) -> case _testStanzaTestModule stanza of - Nothing -> do - parseFailure pos (missingField "test-module" tt) - pure emptyTestSuite - Just module_ -> do - when (isJust (_testStanzaMainIs stanza)) $ - parseWarning pos PWTExtraMainIs (extraField "main-is" tt) - pure - basicTestSuite - { testInterface = TestSuiteLibV09 ver module_ - } - where - testSuiteType = - _testStanzaTestType stanza - <|> do - guard (cabalSpecVersion >= CabalSpecV3_8) - - testTypeExe <$ _testStanzaMainIs stanza - <|> testTypeLib <$ _testStanzaTestModule stanza - - missingField name tt = - "The '" - ++ name - ++ "' field is required for the " - ++ prettyShow tt - ++ " test suite type." - - 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 - { _testStanzaTestType = ty - , _testStanzaMainIs = ma - , _testStanzaTestModule = mo - , _testStanzaBuildInfo = testBuildInfo t - , _testStanzaCodeGenerators = testCodeGenerators t - } - where - (ty, ma, mo) = case testInterface t of - TestSuiteExeV10 ver file -> (Just $ TestTypeExe ver, Just file, Nothing) - TestSuiteLibV09 ver modu -> (Just $ TestTypeLib ver, Nothing, Just modu) - _ -> (Nothing, Nothing, Nothing) - ------------------------------------------------------------------------------- -- Benchmark ------------------------------------------------------------------------------- --- | An intermediate type just used for parsing the benchmark stanza. --- After validation it is converted into the proper 'Benchmark' type. -data BenchmarkStanza = BenchmarkStanza - { _benchmarkStanzaBenchmarkType :: Maybe BenchmarkType - , _benchmarkStanzaMainIs :: Maybe (RelativePath Source File) - , _benchmarkStanzaBenchmarkModule :: Maybe ModuleName - , _benchmarkStanzaBuildInfo :: BuildInfo - } - -instance L.HasBuildInfo BenchmarkStanza where - buildInfo = benchmarkStanzaBuildInfo - -benchmarkStanzaBenchmarkType :: Lens' BenchmarkStanza (Maybe BenchmarkType) -benchmarkStanzaBenchmarkType f s = fmap (\x -> s{_benchmarkStanzaBenchmarkType = x}) (f (_benchmarkStanzaBenchmarkType s)) -{-# INLINE benchmarkStanzaBenchmarkType #-} - -benchmarkStanzaMainIs :: Lens' BenchmarkStanza (Maybe (RelativePath Source File)) -benchmarkStanzaMainIs f s = fmap (\x -> s{_benchmarkStanzaMainIs = x}) (f (_benchmarkStanzaMainIs s)) -{-# INLINE benchmarkStanzaMainIs #-} - -benchmarkStanzaBenchmarkModule :: Lens' BenchmarkStanza (Maybe ModuleName) -benchmarkStanzaBenchmarkModule f s = fmap (\x -> s{_benchmarkStanzaBenchmarkModule = x}) (f (_benchmarkStanzaBenchmarkModule s)) -{-# INLINE benchmarkStanzaBenchmarkModule #-} - -benchmarkStanzaBuildInfo :: Lens' BenchmarkStanza BuildInfo -benchmarkStanzaBuildInfo f s = fmap (\x -> s{_benchmarkStanzaBuildInfo = x}) (f (_benchmarkStanzaBuildInfo s)) -{-# INLINE benchmarkStanzaBuildInfo #-} - benchmarkFieldGrammar :: ( FieldGrammar c g , Applicative (g BenchmarkStanza) @@ -503,76 +341,6 @@ benchmarkFieldGrammar = <*> optionalField "benchmark-module" benchmarkStanzaBenchmarkModule <*> blurFieldGrammar benchmarkStanzaBuildInfo buildInfoFieldGrammar -validateBenchmark :: CabalSpecVersion -> Position -> BenchmarkStanza -> ParseResult src Benchmark -validateBenchmark cabalSpecVersion pos stanza = case benchmarkStanzaType of - Nothing -> - pure - emptyBenchmark - { benchmarkBuildInfo = _benchmarkStanzaBuildInfo stanza - } - Just tt@(BenchmarkTypeUnknown _ _) -> - pure - emptyBenchmark - { benchmarkInterface = BenchmarkUnsupported tt - , benchmarkBuildInfo = _benchmarkStanzaBuildInfo stanza - } - Just tt - | tt `notElem` knownBenchmarkTypes -> - pure - emptyBenchmark - { benchmarkInterface = BenchmarkUnsupported tt - , benchmarkBuildInfo = _benchmarkStanzaBuildInfo stanza - } - Just tt@(BenchmarkTypeExe ver) -> case _benchmarkStanzaMainIs stanza of - Nothing -> do - parseFailure pos (missingField "main-is" tt) - pure emptyBenchmark - Just file -> do - when (isJust (_benchmarkStanzaBenchmarkModule stanza)) $ - parseWarning pos PWTExtraBenchmarkModule (extraField "benchmark-module" tt) - pure - emptyBenchmark - { benchmarkInterface = BenchmarkExeV10 ver file - , benchmarkBuildInfo = _benchmarkStanzaBuildInfo stanza - } - where - benchmarkStanzaType = - _benchmarkStanzaBenchmarkType stanza <|> do - guard (cabalSpecVersion >= CabalSpecV3_8) - - benchmarkTypeExe <$ _benchmarkStanzaMainIs stanza - - missingField name tt = - "The '" - ++ name - ++ "' field is required for the " - ++ prettyShow tt - ++ " benchmark type." - - extraField name tt = - "The '" - ++ name - ++ "' field is not used for the '" - ++ prettyShow tt - ++ "' benchmark type." - -unvalidateBenchmark :: Benchmark -> BenchmarkStanza -unvalidateBenchmark b = - BenchmarkStanza - { _benchmarkStanzaBenchmarkType = ty - , _benchmarkStanzaMainIs = ma - , _benchmarkStanzaBenchmarkModule = mo - , _benchmarkStanzaBuildInfo = benchmarkBuildInfo b - } - where - (ty, ma, mo) = case benchmarkInterface b of - BenchmarkExeV10 ver ma' - | getSymbolicPath ma' == "" -> - (Just $ BenchmarkTypeExe ver, Nothing, Nothing) - | otherwise -> - (Just $ BenchmarkTypeExe ver, Just ma', Nothing) - _ -> (Nothing, Nothing, Nothing) - ------------------------------------------------------------------------------- -- Build info ------------------------------------------------------------------------------- diff --git a/Cabal-syntax/src/Distribution/PackageDescription/Parsec.hs b/Cabal-syntax/src/Distribution/PackageDescription/Parsec.hs index c7e327ddb7f..4b605c93268 100644 --- a/Cabal-syntax/src/Distribution/PackageDescription/Parsec.hs +++ b/Cabal-syntax/src/Distribution/PackageDescription/Parsec.hs @@ -63,8 +63,6 @@ import qualified Data.Set as Set import qualified Distribution.Compat.Newtype as Newtype import qualified Distribution.Compat.NonEmptySet as NES import qualified Distribution.Types.BuildInfo.Lens as L -import qualified Distribution.Types.Executable.Lens as L -import qualified Distribution.Types.ForeignLib.Lens as L import qualified Distribution.Types.GenericPackageDescription.Lens as L import qualified Distribution.Types.PackageDescription.Lens as L import qualified Distribution.Types.SetupBuildInfo.Lens as L @@ -129,14 +127,14 @@ type SectionParser src = StateT SectionS (ParseResult src) -- | State of section parser data SectionS = SectionS { _stateGpd :: !GenericPackageDescription - , _stateCommonStanzas :: !(Map String CondTreeBuildInfo) + , _stateCommonStanzas :: !(Map String CondTreeBuildInfoWithImports) } stateGpd :: Lens' SectionS GenericPackageDescription stateGpd f (SectionS gpd cs) = (\x -> SectionS x cs) <$> f gpd {-# INLINE stateGpd #-} -stateCommonStanzas :: Lens' SectionS (Map String CondTreeBuildInfo) +stateCommonStanzas :: Lens' SectionS (Map String CondTreeBuildInfoWithImports) stateCommonStanzas f (SectionS gpd cs) = SectionS gpd <$> f cs {-# INLINE stateCommonStanzas #-} @@ -240,9 +238,15 @@ parseGenericPackageDescription' scannedVer lexWarnings utf8WarnPos fs = do cabalFormatVersionsDesc :: String cabalFormatVersionsDesc = "Current cabal-version values are listed at https://cabal.readthedocs.io/en/stable/file-format-changelog.html." -goSections :: CabalSpecVersion -> [Field Position] -> SectionParser src () -goSections specVer = traverse_ process +goSections :: forall src. CabalSpecVersion -> [Field Position] -> SectionParser src () +goSections specVer fieldPositions = do + traverse_ process fieldPositions + + -- Retain commen stanzas after parsing sections + commonStanzas <- use stateCommonStanzas + (stateGpd . L.gpdCommonStanzas) .= commonStanzas where + process :: Field Position -> SectionParser src () process (Field (Name pos name) _) = lift $ parseWarning pos PWTTrailingFields $ @@ -259,11 +263,10 @@ goSections specVer = traverse_ process :: L.HasBuildInfo a => ParsecFieldGrammar' a -- \^ grammar - -> (BuildInfo -> a) - -> Map String CondTreeBuildInfo + -> Map String CondTreeBuildInfoWithImports -- \^ common stanzas -> [Field Position] - -> ParseResult src (CondTree ConfVar [Dependency] a) + -> ParseResult src (CondTree ConfVar [Dependency] (WithImports a)) parseCondTree' = parseCondTreeWithCommonStanzas specVer parseSection :: Name Position -> [SectionArg Position] -> [Field Position] -> SectionParser src () @@ -274,8 +277,7 @@ goSections specVer = traverse_ process | name == "common" = do commonStanzas <- use stateCommonStanzas name' <- lift $ parseCommonName pos args - biTree <- lift $ parseCondTree' buildInfoFieldGrammar id commonStanzas fields - + biTree <- lift $ parseCondTree' buildInfoFieldGrammar commonStanzas fields case Map.lookup name' commonStanzas of Nothing -> stateCommonStanzas .= Map.insert name' biTree commonStanzas Just _ -> @@ -283,18 +285,18 @@ goSections specVer = traverse_ process parseFailure pos $ "Duplicate common stanza: " ++ name' | name == "library" && null args = do - prev <- use $ stateGpd . L.condLibrary + prev <- use $ stateGpd . L.condLibraryUnmerged when (isJust prev) $ lift $ parseFailure pos $ "Multiple main libraries; have you forgotten to specify a name for an internal library?" commonStanzas <- use stateCommonStanzas - let name'' = LMainLibName - lib <- lift $ parseCondTree' (libraryFieldGrammar name'') (libraryFromBuildInfo name'') commonStanzas fields + let name' = LMainLibName + lib <- lift $ parseCondTree' (libraryFieldGrammar name') commonStanzas fields -- -- TODO check that not set - stateGpd . L.condLibrary ?= lib + stateGpd . L.condLibraryUnmerged ?= lib -- Sublibraries -- TODO: check cabal-version @@ -302,18 +304,18 @@ goSections specVer = traverse_ process commonStanzas <- use stateCommonStanzas name' <- parseUnqualComponentName pos args let name'' = LSubLibName name' - lib <- lift $ parseCondTree' (libraryFieldGrammar name'') (libraryFromBuildInfo name'') commonStanzas fields + lib <- lift $ parseCondTree' (libraryFieldGrammar name'') commonStanzas fields -- TODO check duplicate name here? - stateGpd . L.condSubLibraries %= snoc (name', lib) + stateGpd . L.condSubLibrariesUnmerged %= snoc (name', lib) -- TODO: check cabal-version | name == "foreign-library" = do commonStanzas <- use stateCommonStanzas name' <- parseUnqualComponentName pos args - flib <- lift $ parseCondTree' (foreignLibFieldGrammar name') (fromBuildInfo' name') commonStanzas fields + flib <- lift $ parseCondTree' (foreignLibFieldGrammar name') commonStanzas fields let hasType ts = foreignLibType ts /= foreignLibType mempty - unless (onAllBranches hasType flib) $ + unless (onAllBranches hasType (mapTreeData unImportNames flib)) $ lift $ parseFailure pos $ concat @@ -325,21 +327,28 @@ goSections specVer = traverse_ process ] -- TODO check duplicate name here? - stateGpd . L.condForeignLibs %= snoc (name', flib) + stateGpd . L.condForeignLibsUnmerged %= snoc (name', flib) | name == "executable" = do commonStanzas <- use stateCommonStanzas name' <- parseUnqualComponentName pos args - exe <- lift $ parseCondTree' (executableFieldGrammar name') (fromBuildInfo' name') commonStanzas fields + exe <- lift $ parseCondTree' (executableFieldGrammar name') commonStanzas fields -- TODO check duplicate name here? - stateGpd . L.condExecutables %= snoc (name', exe) + stateGpd . L.condExecutablesUnmerged %= snoc (name', exe) | name == "test-suite" = do commonStanzas <- use stateCommonStanzas name' <- parseUnqualComponentName pos args - testStanza <- lift $ parseCondTree' testSuiteFieldGrammar (fromBuildInfo' name') commonStanzas fields - testSuite <- lift $ traverse (validateTestSuite specVer pos) testStanza + testStanza <- lift $ parseCondTree' testSuiteFieldGrammar commonStanzas fields + + -- Patching depends on merging, validation depends on patching + let testStanza' :: CondTree ConfVar [Dependency] TestSuiteStanza + testStanza' = + mergeTestSuiteStanza commonStanzas testStanza + & fmap (patchTestSuiteType specVer) + _ok <- lift $ traverse (validateTestSuite pos) testStanza' + let validated = mapTreeData convertTestSuite testStanza' let hasType ts = testInterface ts /= testInterface mempty - unless (onAllBranches hasType testSuite) $ + unless (onAllBranches hasType validated) $ lift $ parseFailure pos $ concat @@ -359,15 +368,23 @@ goSections specVer = traverse_ process ] -- TODO check duplicate name here? - stateGpd . L.condTestSuites %= snoc (name', testSuite) + -- Store the unmerged unvalidated version + stateGpd . L.condTestSuitesUnmerged %= snoc (name', testStanza) | name == "benchmark" = do commonStanzas <- use stateCommonStanzas name' <- parseUnqualComponentName pos args - benchStanza <- lift $ parseCondTree' benchmarkFieldGrammar (fromBuildInfo' name') commonStanzas fields - bench <- lift $ traverse (validateBenchmark specVer pos) benchStanza + benchStanza <- lift $ parseCondTree' benchmarkFieldGrammar commonStanzas fields + + -- Patching depends on merging, validation depends on patching + let benchStanza' :: CondTree ConfVar [Dependency] BenchmarkStanza + benchStanza' = + mergeBenchmarkStanza commonStanzas benchStanza + & fmap (patchBenchmarkType specVer) + _ok <- lift $ traverse (validateBenchmark pos . unImportNames) benchStanza + let validated = mapTreeData convertBenchmark benchStanza' let hasType ts = benchmarkInterface ts /= benchmarkInterface mempty - unless (onAllBranches hasType bench) $ + unless (onAllBranches hasType validated) $ lift $ parseFailure pos $ concat @@ -387,7 +404,7 @@ goSections specVer = traverse_ process ] -- TODO check duplicate name here? - stateGpd . L.condBenchmarks %= snoc (name', bench) + stateGpd . L.condBenchmarksUnmerged %= snoc (name', benchStanza) | name == "flag" = do name' <- parseNameBS pos args name'' <- lift $ runFieldParser' [pos] parsec specVer (fieldLineStreamFromBS name') `recoverWith` mkFlagName "" @@ -469,34 +486,32 @@ warnInvalidSubsection (MkSection (Name pos name) _ _) = parseCondTree :: forall src a - . L.HasBuildInfo a - => CabalSpecVersion + . CabalSpecVersion -> HasElif -- ^ accept @elif@ -> ParsecFieldGrammar' a -- ^ grammar - -> Map String CondTreeBuildInfo + -> Map String CondTreeBuildInfoWithImports -- ^ common stanzas - -> (BuildInfo -> a) - -- ^ constructor from buildInfo -> (a -> [Dependency]) -- ^ condition extractor -> [Field Position] - -> ParseResult src (CondTree ConfVar [Dependency] a) -parseCondTree v hasElif grammar commonStanzas fromBuildInfo cond = go + -> ParseResult src (CondTree ConfVar [Dependency] (WithImports a)) +parseCondTree v hasElif grammar commonStanzas cond = go where + go :: [Field Position] -> ParseResult src (CondTree ConfVar [Dependency] (WithImports a)) go fields0 = do - (fields, endo) <- + (fields, imports) <- if v >= CabalSpecV3_0 - then processImports v fromBuildInfo commonStanzas fields0 - else traverse (warnImport v) fields0 >>= \fields1 -> return (catMaybes fields1, id) + then processImports v commonStanzas fields0 + else traverse (warnImport v) fields0 >>= \fields1 -> return (catMaybes fields1, mempty) let (fs, ss) = partitionFields fields x <- parseFieldGrammar v fs grammar branches <- concat <$> traverse parseIfs ss - return $ endo $ CondNode x (cond x) branches + return $ CondNode (WithImports imports x) (cond x) branches - parseIfs :: [Section Position] -> ParseResult src [CondBranch ConfVar [Dependency] a] + parseIfs :: [Section Position] -> ParseResult src [CondBranch ConfVar [Dependency] (WithImports a)] parseIfs [] = return [] parseIfs (MkSection (Name pos name) test fields : sections) | name == "if" = do test' <- parseConditionConfVar (startOfSection (incPos 2 pos) test) test @@ -509,7 +524,7 @@ parseCondTree v hasElif grammar commonStanzas fromBuildInfo cond = go parseElseIfs :: [Section Position] - -> ParseResult src (Maybe (CondTree ConfVar [Dependency] a), [CondBranch ConfVar [Dependency] a]) + -> ParseResult src (Maybe (CondTree ConfVar [Dependency] (WithImports a)), [CondBranch ConfVar [Dependency] (WithImports a)]) parseElseIfs [] = return (Nothing, []) parseElseIfs (MkSection (Name pos name) args fields : sections) | name == "else" = do unless (null args) $ @@ -526,7 +541,7 @@ parseCondTree v hasElif grammar commonStanzas fromBuildInfo cond = go (elseFields, sections') <- parseElseIfs sections -- we parse an empty 'Fields', to get empty value for a node a <- parseFieldGrammar v mempty grammar - return (Just $ CondNode a (cond a) [CondBranch test' fields' elseFields], sections') + return (Just $ CondNode (noImports a) (cond a) [CondBranch test' fields' elseFields], sections') parseElseIfs (MkSection (Name pos name) _ _ : sections) | name == "elif" = do parseWarning pos PWTInvalidSubsection $ "invalid subsection \"elif\". You should set cabal-version: 2.2 or larger to use elif-conditionals." (,) Nothing <$> parseIfs sections @@ -594,36 +609,7 @@ with new AST, this all need to be rewritten. -- The approach is simple, and have good properties: -- -- * Common stanzas are parsed exactly once, even if not-used. Thus we report errors in them. -type CondTreeBuildInfo = CondTree ConfVar [Dependency] BuildInfo - --- | Create @a@ from 'BuildInfo'. --- This class is used to implement common stanza parsing. --- --- Law: @view buildInfo . fromBuildInfo = id@ --- --- This takes name, as 'FieldGrammar's take names too. -class L.HasBuildInfo a => FromBuildInfo a where - fromBuildInfo' :: UnqualComponentName -> BuildInfo -> a - -libraryFromBuildInfo :: LibraryName -> BuildInfo -> Library -libraryFromBuildInfo n bi = - emptyLibrary - { libName = n - , libVisibility = case n of - LMainLibName -> LibraryVisibilityPublic - LSubLibName _ -> LibraryVisibilityPrivate - , libBuildInfo = bi - } - -instance FromBuildInfo BuildInfo where fromBuildInfo' _ = id -instance FromBuildInfo ForeignLib where fromBuildInfo' n bi = set L.foreignLibName n $ set L.buildInfo bi emptyForeignLib -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 [] - -instance FromBuildInfo BenchmarkStanza where - fromBuildInfo' _ bi = BenchmarkStanza Nothing Nothing Nothing bi +type CondTreeBuildInfoWithImports = CondTree ConfVar [Dependency] (WithImports BuildInfo) parseCondTreeWithCommonStanzas :: forall src a @@ -631,36 +617,44 @@ parseCondTreeWithCommonStanzas => CabalSpecVersion -> ParsecFieldGrammar' a -- ^ grammar - -> (BuildInfo -> a) - -- ^ construct fromBuildInfo - -> Map String CondTreeBuildInfo + -> Map String CondTreeBuildInfoWithImports -- ^ common stanzas -> [Field Position] - -> ParseResult src (CondTree ConfVar [Dependency] a) -parseCondTreeWithCommonStanzas v grammar fromBuildInfo commonStanzas fields = do - (fields', endo) <- processImports v fromBuildInfo commonStanzas fields - x <- parseCondTree v hasElif grammar commonStanzas fromBuildInfo (view L.targetBuildDepends) fields' - return (endo x) + -> ParseResult src (CondTree ConfVar [Dependency] (WithImports a)) +parseCondTreeWithCommonStanzas v grammar commonStanzas fields = do + (fields', imports) <- processImports v commonStanzas fields + x <- parseCondTree v hasElif grammar commonStanzas (view L.targetBuildDepends) fields' + -- We replace the imports from parseCondTree, because it comes right after + -- the import processing and hence is always empty, if such imports should + -- exist in the grammar, that is >= cabal 3.0. + return (replaceImportsOnRoot imports x) where hasElif = specHasElif v +-- | only attach import annotation on root +replaceImportsOnRoot + :: [ImportName] + -> CondTree v c (WithImports a) + -> CondTree v c (WithImports a) +replaceImportsOnRoot imports = mapTreeData' (WithImports imports . unImportNames) id + processImports - :: forall src a - . L.HasBuildInfo a - => CabalSpecVersion - -> (BuildInfo -> a) - -- ^ construct fromBuildInfo - -> Map String CondTreeBuildInfo + :: CabalSpecVersion + -> Map String CondTreeBuildInfoWithImports -- ^ common stanzas -> [Field Position] - -> ParseResult src ([Field Position], CondTree ConfVar [Dependency] a -> CondTree ConfVar [Dependency] a) -processImports v fromBuildInfo commonStanzas = go [] + -> ParseResult src ([Field Position], [ImportName]) +processImports v commonStanzas = go [] where hasCommonStanzas = specHasCommonStanzas v getList' :: List CommaFSep Token String -> [String] getList' = Newtype.unpack + go + :: [ImportName] + -> [Field Position] + -> ParseResult src ([Field Position], [ImportName]) go acc (Field (Name pos name) _ : fields) | name == "import" , hasCommonStanzas == NoCommonStanzas = do @@ -669,20 +663,19 @@ processImports v fromBuildInfo commonStanzas = go [] -- supported: go acc (Field (Name pos name) fls : fields) | name == "import" = do names <- getList' <$> runFieldParser pos parsec v fls - names' <- for names $ \commonName -> - case Map.lookup commonName commonStanzas of - Nothing -> do + validNames <- for names $ \commonName -> + if Map.member commonName commonStanzas + then pure (Just commonName) + else do parseFailure pos $ "Undefined common stanza imported: " ++ commonName pure Nothing - Just commonTree -> - pure (Just commonTree) - go (acc ++ catMaybes names') fields + go (acc ++ catMaybes validNames) fields -- parse actual CondTree - go acc fields = do + go names fields = do fields' <- catMaybes <$> traverse (warnImport v) fields - pure $ (fields', \x -> foldr (mergeCommonStanza fromBuildInfo) x acc) + pure (fields', names) -- | Warn on "import" fields, also map to Maybe, so erroneous fields can be filtered warnImport :: CabalSpecVersion -> Field Position -> ParseResult src (Maybe (Field Position)) @@ -693,21 +686,6 @@ warnImport v (Field (Name pos name) _) | name == "import" = do return Nothing warnImport _ f = pure (Just f) -mergeCommonStanza - :: L.HasBuildInfo a - => (BuildInfo -> a) - -> CondTree ConfVar [Dependency] BuildInfo - -> CondTree ConfVar [Dependency] a - -> CondTree ConfVar [Dependency] a -mergeCommonStanza fromBuildInfo (CondNode bi _ bis) (CondNode x _ cs) = - CondNode x' (x' ^. L.targetBuildDepends) cs' - where - -- new value is old value with buildInfo field _prepended_. - x' = x & L.buildInfo %~ (bi <>) - - -- tree components are appended together. - cs' = map (fmap fromBuildInfo) bis ++ cs - ------------------------------------------------------------------------------- -- Branches ------------------------------------------------------------------------------- diff --git a/Cabal-syntax/src/Distribution/PackageDescription/PrettyPrint.hs b/Cabal-syntax/src/Distribution/PackageDescription/PrettyPrint.hs index 15c2c15fe09..7998a477a16 100644 --- a/Cabal-syntax/src/Distribution/PackageDescription/PrettyPrint.hs +++ b/Cabal-syntax/src/Distribution/PackageDescription/PrettyPrint.hs @@ -53,7 +53,6 @@ import Distribution.PackageDescription.FieldGrammar import Distribution.Pretty import Distribution.Utils.Generic (writeFileAtomic, writeUTF8File) -import qualified Distribution.PackageDescription.FieldGrammar as FG import qualified Distribution.Types.BuildInfo.Lens as L import qualified Distribution.Types.SetupBuildInfo.Lens as L @@ -171,14 +170,14 @@ ppCondExecutables v exes = ppCondTestSuites :: CabalSpecVersion -> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)] -> [PrettyField ()] ppCondTestSuites v suites = [ PrettySection () "test-suite" [pretty n] $ - ppCondTree2 v testSuiteFieldGrammar (fmap FG.unvalidateTestSuite condTree) + ppCondTree2 v testSuiteFieldGrammar (fmap unvalidateTestSuite condTree) | (n, condTree) <- suites ] ppCondBenchmarks :: CabalSpecVersion -> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)] -> [PrettyField ()] ppCondBenchmarks v suites = [ PrettySection () "benchmark" [pretty n] $ - ppCondTree2 v benchmarkFieldGrammar (fmap FG.unvalidateBenchmark condTree) + ppCondTree2 v benchmarkFieldGrammar (fmap unvalidateBenchmark condTree) | (n, condTree) <- suites ] diff --git a/Cabal-syntax/src/Distribution/Types/BenchmarkStanza.hs b/Cabal-syntax/src/Distribution/Types/BenchmarkStanza.hs new file mode 100644 index 00000000000..b57610a2c35 --- /dev/null +++ b/Cabal-syntax/src/Distribution/Types/BenchmarkStanza.hs @@ -0,0 +1,135 @@ +{-# LANGUAGE ConstraintKinds #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE QuantifiedConstraints #-} + +module Distribution.Types.BenchmarkStanza where + +import Distribution.Compat.Lens +import Distribution.Compat.Prelude +import Prelude () + +import Distribution.CabalSpecVersion +import Distribution.Fields +import Distribution.ModuleName (ModuleName) +import Distribution.Parsec +import Distribution.Pretty (prettyShow) +import Distribution.Types.Benchmark +import Distribution.Types.BenchmarkInterface +import Distribution.Types.BenchmarkType +import Distribution.Types.BuildInfo +import qualified Distribution.Types.BuildInfo.Lens as L +import Distribution.Utils.Path + +-- | An intermediate type just used for parsing the benchmark stanza. +-- After validation it is converted into the proper 'Benchmark' type. +data BenchmarkStanza = BenchmarkStanza + { _benchmarkStanzaBenchmarkType :: Maybe BenchmarkType + , _benchmarkStanzaMainIs :: Maybe (RelativePath Source File) + , _benchmarkStanzaBenchmarkModule :: Maybe ModuleName + , _benchmarkStanzaBuildInfo :: BuildInfo + } + deriving (Show, Eq, Data, Generic) + +instance Binary BenchmarkStanza +instance Structured BenchmarkStanza +instance NFData BenchmarkStanza where rnf = genericRnf + +validateBenchmark :: Position -> BenchmarkStanza -> ParseResult src () +validateBenchmark pos stanza = case _benchmarkStanzaBenchmarkType stanza of + Nothing -> pure () + Just (BenchmarkTypeUnknown _ _) -> pure () + Just tt | tt `notElem` knownBenchmarkTypes -> pure () + Just tt@(BenchmarkTypeExe _ver) -> case _benchmarkStanzaMainIs stanza of + Nothing -> parseFailure pos (missingField "main-is" tt) + Just _file -> + when (isJust (_benchmarkStanzaBenchmarkModule stanza)) $ + parseWarning pos PWTExtraBenchmarkModule (extraField "benchmark-module" tt) + where + missingField name tt = + "The '" + ++ name + ++ "' field is required for the " + ++ prettyShow tt + ++ " benchmark type." + + extraField name tt = + "The '" + ++ name + ++ "' field is not used for the '" + ++ prettyShow tt + ++ "' benchmark type." + +convertBenchmark :: BenchmarkStanza -> Benchmark +convertBenchmark stanza = case _benchmarkStanzaBenchmarkType stanza of + Nothing -> + emptyBenchmark + { benchmarkBuildInfo = _benchmarkStanzaBuildInfo stanza + } + Just tt@(BenchmarkTypeUnknown _ _) -> + emptyBenchmark + { benchmarkInterface = BenchmarkUnsupported tt + , benchmarkBuildInfo = _benchmarkStanzaBuildInfo stanza + } + Just tt + | tt `notElem` knownBenchmarkTypes -> + emptyBenchmark + { benchmarkInterface = BenchmarkUnsupported tt + , benchmarkBuildInfo = _benchmarkStanzaBuildInfo stanza + } + Just (BenchmarkTypeExe ver) -> case _benchmarkStanzaMainIs stanza of + Nothing -> emptyBenchmark + Just file -> + emptyBenchmark + { benchmarkInterface = BenchmarkExeV10 ver file + , benchmarkBuildInfo = _benchmarkStanzaBuildInfo stanza + } + +unvalidateBenchmark :: Benchmark -> BenchmarkStanza +unvalidateBenchmark b = + BenchmarkStanza + { _benchmarkStanzaBenchmarkType = ty + , _benchmarkStanzaMainIs = ma + , _benchmarkStanzaBenchmarkModule = mo + , _benchmarkStanzaBuildInfo = benchmarkBuildInfo b + } + where + (ty, ma, mo) = case benchmarkInterface b of + BenchmarkExeV10 ver ma' + | getSymbolicPath ma' == "" -> + (Just $ BenchmarkTypeExe ver, Nothing, Nothing) + | otherwise -> + (Just $ BenchmarkTypeExe ver, Just ma', Nothing) + _ -> (Nothing, Nothing, Nothing) + +patchBenchmarkType :: CabalSpecVersion -> BenchmarkStanza -> BenchmarkStanza +patchBenchmarkType cabalSpecVersion stanza = + stanza + { _benchmarkStanzaBenchmarkType = + _benchmarkStanzaBenchmarkType stanza <|> do + guard (cabalSpecVersion >= CabalSpecV3_8) + benchmarkTypeExe <$ _benchmarkStanzaMainIs stanza + } + +instance L.HasBuildInfo BenchmarkStanza where + buildInfo = benchmarkStanzaBuildInfo + +benchmarkStanzaBenchmarkType :: Lens' BenchmarkStanza (Maybe BenchmarkType) +benchmarkStanzaBenchmarkType f s = fmap (\x -> s{_benchmarkStanzaBenchmarkType = x}) (f (_benchmarkStanzaBenchmarkType s)) +{-# INLINE benchmarkStanzaBenchmarkType #-} + +benchmarkStanzaMainIs :: Lens' BenchmarkStanza (Maybe (RelativePath Source File)) +benchmarkStanzaMainIs f s = fmap (\x -> s{_benchmarkStanzaMainIs = x}) (f (_benchmarkStanzaMainIs s)) +{-# INLINE benchmarkStanzaMainIs #-} + +benchmarkStanzaBenchmarkModule :: Lens' BenchmarkStanza (Maybe ModuleName) +benchmarkStanzaBenchmarkModule f s = fmap (\x -> s{_benchmarkStanzaBenchmarkModule = x}) (f (_benchmarkStanzaBenchmarkModule s)) +{-# INLINE benchmarkStanzaBenchmarkModule #-} + +benchmarkStanzaBuildInfo :: Lens' BenchmarkStanza BuildInfo +benchmarkStanzaBuildInfo f s = fmap (\x -> s{_benchmarkStanzaBuildInfo = x}) (f (_benchmarkStanzaBuildInfo s)) +{-# INLINE benchmarkStanzaBuildInfo #-} diff --git a/Cabal-syntax/src/Distribution/Types/CondTree.hs b/Cabal-syntax/src/Distribution/Types/CondTree.hs index c74ffdf6395..0fb035fadae 100644 --- a/Cabal-syntax/src/Distribution/Types/CondTree.hs +++ b/Cabal-syntax/src/Distribution/Types/CondTree.hs @@ -13,6 +13,7 @@ module Distribution.Types.CondTree , mapTreeConstrs , mapTreeConds , mapTreeData + , mapTreeData' , traverseCondTreeV , traverseCondBranchV , traverseCondTreeC @@ -123,6 +124,26 @@ mapTreeConds f = mapCondTree id id f mapTreeData :: (a -> b) -> CondTree v c a -> CondTree v c b mapTreeData f = mapCondTree f id id +-- | Transform data and branches differently +mapTreeData' + :: (a -> b) + -- ^ transform root + -> (a -> b) + -- ^ transform subtrees + -> CondTree v c a + -> CondTree v c b +mapTreeData' f g n = + n + { condTreeData = f (condTreeData n) + , condTreeComponents = map g' (condTreeComponents n) + } + where + g' (CondBranch cond ifTrue ifFalse) = + CondBranch + (cond) + (mapTreeData' g g $ ifTrue) + (mapTreeData' g g <$> ifFalse) + -- | @@Traversal@@ for the variables traverseCondTreeV :: L.Traversal (CondTree v c a) (CondTree w c a) v w traverseCondTreeV f (CondNode a c ifs) = diff --git a/Cabal-syntax/src/Distribution/Types/GenericPackageDescription.hs b/Cabal-syntax/src/Distribution/Types/GenericPackageDescription.hs index 97f4ed8cccb..910e127078b 100644 --- a/Cabal-syntax/src/Distribution/Types/GenericPackageDescription.hs +++ b/Cabal-syntax/src/Distribution/Types/GenericPackageDescription.hs @@ -1,11 +1,42 @@ +{-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE ViewPatterns #-} +#if __GLASGOW_HASKELL__ >= 914 +{-# LANGUAGE ExplicitNamespaces #-} +#endif module Distribution.Types.GenericPackageDescription ( GenericPackageDescription (..) +#if __GLASGOW_HASKELL__ >= 914 + , data GenericPackageDescription +#else + , pattern GenericPackageDescription +#endif , emptyGenericPackageDescription + , mergeImports + + -- * Accessors from 'PatternSynonyms'\'s record syntax + , packageDescription + , gpdScannedVersion + , genPackageFlags + , condLibrary + , condSubLibraries + , condForeignLibs + , condExecutables + , condTestSuites + , condBenchmarks + + -- * Merging helpers + , mergeCondLibrary + , mergeCondSubLibraries + , mergeCondForeignLibs + , mergeCondExecutables + , mergeTestSuiteStanza + , mergeBenchmarkStanza ) where import Distribution.Compat.Prelude @@ -15,26 +46,42 @@ import Prelude () import Distribution.Compat.Lens as L import qualified Distribution.Types.BuildInfo.Lens as L +-- TODO(leana8959): fix it this orphan +import qualified Distribution.Types.Imports.Lens as L () + import Distribution.Types.PackageDescription +import Distribution.CabalSpecVersion import Distribution.Package import Distribution.Types.Benchmark +import Distribution.Types.BenchmarkStanza +import Distribution.Types.BuildInfo import Distribution.Types.CondTree import Distribution.Types.ConfVar import Distribution.Types.Executable import Distribution.Types.Flag import Distribution.Types.ForeignLib +import Distribution.Types.Imports import Distribution.Types.Library +import Distribution.Types.LibraryName +import Distribution.Types.LibraryVisibility import Distribution.Types.TestSuite +import Distribution.Types.TestSuiteStanza import Distribution.Types.UnqualComponentName import Distribution.Version +import qualified Data.Map as Map + -- --------------------------------------------------------------------------- -- The 'GenericPackageDescription' type -data GenericPackageDescription = GenericPackageDescription - { packageDescription :: PackageDescription - , gpdScannedVersion :: Maybe Version +type DependencyTree a = CondTree ConfVar [Dependency] a + +-- | The internal representation of 'GenericPackageDescription', containing the unmerged stanzas +-- We provide a pattern below for backward compatibility, as well for hiding the internals of wiring the imports +data GenericPackageDescription = GenericPackageDescription' + { packageDescriptionInternal :: PackageDescription + , gpdScannedVersionInternal :: Maybe Version -- ^ This is a version as specified in source. -- We populate this field in index reading for dummy GPDs, -- only when GPD reading failed, but scanning haven't. @@ -43,35 +90,283 @@ data GenericPackageDescription = GenericPackageDescription -- -- Perfectly, PackageIndex should have sum type, so we don't need to -- have dummy GPDs. - , genPackageFlags :: [PackageFlag] - , condLibrary :: Maybe (CondTree ConfVar [Dependency] Library) + , genPackageFlagsInternal :: [PackageFlag] + , gpdCommonStanzas :: Map ImportName (DependencyTree (WithImports BuildInfo)) + , condLibraryUnmerged :: Maybe (DependencyTree (WithImports Library)) + , condSubLibrariesUnmerged :: [(UnqualComponentName, DependencyTree (WithImports Library))] + , condForeignLibsUnmerged :: [(UnqualComponentName, DependencyTree (WithImports ForeignLib))] + , condExecutablesUnmerged :: [(UnqualComponentName, DependencyTree (WithImports Executable))] + , condTestSuitesUnmerged :: [(UnqualComponentName, DependencyTree (WithImports TestSuiteStanza))] + , condBenchmarksUnmerged :: [(UnqualComponentName, DependencyTree (WithImports BenchmarkStanza))] + } + deriving (Show, Eq, Data, Generic) + +pattern GenericPackageDescription + :: PackageDescription + -> Maybe Version + -> [PackageFlag] + -> Maybe (DependencyTree Library) + -> [(UnqualComponentName, DependencyTree Library)] + -> [(UnqualComponentName, DependencyTree ForeignLib)] + -> [(UnqualComponentName, DependencyTree Executable)] + -> [(UnqualComponentName, DependencyTree TestSuite)] + -> [(UnqualComponentName, DependencyTree Benchmark)] + -> GenericPackageDescription +pattern GenericPackageDescription + { packageDescription + , gpdScannedVersion + , genPackageFlags + , condLibrary , condSubLibraries - :: [ ( UnqualComponentName - , CondTree ConfVar [Dependency] Library - ) - ] , condForeignLibs - :: [ ( UnqualComponentName - , CondTree ConfVar [Dependency] ForeignLib - ) - ] , condExecutables - :: [ ( UnqualComponentName - , CondTree ConfVar [Dependency] Executable - ) - ] , condTestSuites - :: [ ( UnqualComponentName - , CondTree ConfVar [Dependency] TestSuite - ) - ] , condBenchmarks - :: [ ( UnqualComponentName - , CondTree ConfVar [Dependency] Benchmark - ) - ] - } - deriving (Show, Eq, Data, Generic) + } <- + ( viewGenericPackageDescription -> + ( packageDescription + , gpdScannedVersion + , genPackageFlags + , condLibrary + , condSubLibraries + , condForeignLibs + , condExecutables + , condTestSuites + , condBenchmarks + ) + ) + where + GenericPackageDescription + pd + scannedVersion + packageFlags + lib + sublibs + flibs + exes + tests + bms = + GenericPackageDescription' + pd + scannedVersion + packageFlags + mempty + ((fmap . fmap) noImports lib) + ((fmap . fmap . fmap) noImports sublibs) + ((fmap . fmap . fmap) noImports flibs) + ((fmap . fmap . fmap) noImports exes) + ((fmap . fmap . fmap) (noImports . unvalidateTestSuite) tests) + ((fmap . fmap . fmap) (noImports . unvalidateBenchmark) bms) + +{-# COMPLETE GenericPackageDescription #-} + +viewGenericPackageDescription + :: GenericPackageDescription + -> ( PackageDescription + , Maybe Version + , [PackageFlag] + , Maybe (DependencyTree Library) + , [(UnqualComponentName, DependencyTree Library)] + , [(UnqualComponentName, DependencyTree ForeignLib)] + , [(UnqualComponentName, DependencyTree Executable)] + , [(UnqualComponentName, DependencyTree TestSuite)] + , [(UnqualComponentName, DependencyTree Benchmark)] + ) +viewGenericPackageDescription gpd = + ( packageDescriptionInternal gpd + , gpdScannedVersionInternal gpd + , genPackageFlagsInternal gpd + , condLibrary' gpd + , condSubLibraries' gpd + , condForeignLibs' gpd + , condExecutables' gpd + , condTestSuites' gpd + , condBenchmarks' gpd + ) + +libraryFromBuildInfo :: LibraryName -> BuildInfo -> Library +libraryFromBuildInfo n bi = + emptyLibrary + { libName = n + , libVisibility = case n of + LMainLibName -> LibraryVisibilityPublic + LSubLibName _ -> LibraryVisibilityPrivate + , libBuildInfo = bi + } + +foreignLibFromBuildInfo :: UnqualComponentName -> BuildInfo -> ForeignLib +foreignLibFromBuildInfo n bi = emptyForeignLib{foreignLibName = n, foreignLibBuildInfo = bi} + +executableFromBuildInfo :: UnqualComponentName -> BuildInfo -> Executable +executableFromBuildInfo n bi = emptyExecutable{exeName = n, buildInfo = bi} + +testSuiteStanzaFromBuildInfo :: BuildInfo -> TestSuiteStanza +testSuiteStanzaFromBuildInfo bi = TestSuiteStanza Nothing Nothing Nothing bi [] + +benchmarkStanzaFromBuildInfo :: BuildInfo -> BenchmarkStanza +benchmarkStanzaFromBuildInfo bi = BenchmarkStanza Nothing Nothing Nothing bi + +condLibrary' + :: GenericPackageDescription + -> Maybe (DependencyTree Library) +condLibrary' gpd = mergeCondLibrary (gpdCommonStanzas gpd) <$> (condLibraryUnmerged gpd) + +mergeCondLibrary + :: Map ImportName (DependencyTree (WithImports BuildInfo)) + -> DependencyTree (WithImports Library) + -> DependencyTree Library +mergeCondLibrary = flip mergeImports fromBuildInfo + where + fromBuildInfo = libraryFromBuildInfo . libName + +condSubLibraries' + :: GenericPackageDescription + -> [(UnqualComponentName, DependencyTree Library)] +condSubLibraries' gpd = mergeCondSubLibraries (gpdCommonStanzas gpd) (condSubLibrariesUnmerged gpd) + +mergeCondSubLibraries + :: Map ImportName (DependencyTree (WithImports BuildInfo)) + -> [(UnqualComponentName, DependencyTree (WithImports Library))] + -> [(UnqualComponentName, DependencyTree Library)] +mergeCondSubLibraries commonStanzas = map (mergeCondLibrary commonStanzas <$>) + +condForeignLibs' + :: GenericPackageDescription + -> [(UnqualComponentName, DependencyTree ForeignLib)] +condForeignLibs' gpd = mergeCondForeignLibs (gpdCommonStanzas gpd) (condForeignLibsUnmerged gpd) + +mergeCondForeignLibs + :: Map ImportName (DependencyTree (WithImports BuildInfo)) + -> [(UnqualComponentName, DependencyTree (WithImports ForeignLib))] + -> [(UnqualComponentName, DependencyTree ForeignLib)] +mergeCondForeignLibs commonStanzas = map $ \(name, tree) -> + -- TODO(leana8959): is the name within the foreignlib important or we should use the name in the tuple? + (name, mergeImports commonStanzas (const $ foreignLibFromBuildInfo name) tree) + +condExecutables' + :: GenericPackageDescription + -> [(UnqualComponentName, DependencyTree Executable)] +condExecutables' gpd = mergeCondExecutables (gpdCommonStanzas gpd) (condExecutablesUnmerged gpd) + +mergeCondExecutables + :: Map ImportName (DependencyTree (WithImports BuildInfo)) + -> [(UnqualComponentName, DependencyTree (WithImports Executable))] + -> [(UnqualComponentName, DependencyTree Executable)] +mergeCondExecutables commonStanzas = map $ \(name, tree) -> + (name, mergeImports commonStanzas (const $ executableFromBuildInfo name) tree) + +mergeTestSuiteStanza + :: Map ImportName (DependencyTree (WithImports BuildInfo)) + -> DependencyTree (WithImports TestSuiteStanza) + -> DependencyTree TestSuiteStanza +mergeTestSuiteStanza commonStanza = + mergeImports commonStanza (const $ testSuiteStanzaFromBuildInfo) + +mergeBenchmarkStanza + :: Map ImportName (DependencyTree (WithImports BuildInfo)) + -> DependencyTree (WithImports BenchmarkStanza) + -> DependencyTree BenchmarkStanza +mergeBenchmarkStanza commonStanza = + mergeImports commonStanza (const $ benchmarkStanzaFromBuildInfo) + +condTestSuites' + :: GenericPackageDescription + -> [(UnqualComponentName, DependencyTree TestSuite)] +condTestSuites' gpd = + mergeTestSuiteStanza' (gpdCommonStanzas gpd) (condTestSuitesUnmerged gpd) + & (map . fmap . mapTreeData) (convertTestSuite . patchTestSuiteType specVer) + where + specVer :: CabalSpecVersion + specVer = specVersion . packageDescriptionInternal $ gpd + +mergeTestSuiteStanza' + :: Map ImportName (DependencyTree (WithImports BuildInfo)) + -> [(UnqualComponentName, DependencyTree (WithImports TestSuiteStanza))] + -> [(UnqualComponentName, DependencyTree TestSuiteStanza)] +mergeTestSuiteStanza' commonStanza = + map $ + fmap $ + mergeImports commonStanza (const $ testSuiteStanzaFromBuildInfo) + +condBenchmarks' + :: GenericPackageDescription + -> [(UnqualComponentName, DependencyTree Benchmark)] +condBenchmarks' gpd = + mergeBenchmarkStanza' (gpdCommonStanzas gpd) (condBenchmarksUnmerged gpd) + & (map . fmap . mapTreeData) (convertBenchmark . patchBenchmarkType specVer) + where + specVer :: CabalSpecVersion + specVer = specVersion . packageDescriptionInternal $ gpd + +mergeBenchmarkStanza' + :: Map ImportName (DependencyTree (WithImports BuildInfo)) + -> [(UnqualComponentName, DependencyTree (WithImports BenchmarkStanza))] + -> [(UnqualComponentName, DependencyTree BenchmarkStanza)] +mergeBenchmarkStanza' commonStanza = + map $ + fmap $ + mergeImports commonStanza (const $ benchmarkStanzaFromBuildInfo) + +mergeImports + :: forall a + . L.HasBuildInfo a + => Map ImportName (DependencyTree (WithImports BuildInfo)) + -> (a -> (BuildInfo -> a)) + -- ^ We need the information regarding the root node to be able to build such a constructor function + -> DependencyTree (WithImports a) + -> DependencyTree a +mergeImports commonStanzas fromBuildInfo (CondNode root c zs) = + let endo :: DependencyTree a -> DependencyTree a + endo = resolveImports (getImportNames root) + + tree :: DependencyTree a + tree = CondNode (unImportNames root) c (map goBranch zs) + in endo tree + where + goBranch + :: L.HasBuildInfo a + => CondBranch ConfVar [Dependency] (WithImports a) + -> CondBranch ConfVar [Dependency] a + goBranch (CondBranch cond ifTrue ifFalse) = CondBranch cond (goNode ifTrue) (goNode <$> ifFalse) + where + goNode = mergeImports commonStanzas fromBuildInfo + + resolveImports + :: L.HasBuildInfo a + => [ImportName] + -> (DependencyTree a -> DependencyTree a) + resolveImports importNames = + let commonTrees :: [DependencyTree (WithImports BuildInfo)] + commonTrees = + map + ( fromMaybe (error "failed to merge imports, did you mess with GenericPackageDescription?") + . flip Map.lookup commonStanzas + ) + importNames + + commonTrees' :: [DependencyTree BuildInfo] + commonTrees' = map goNode commonTrees + in \x -> foldr mergeCondTree x commonTrees' + where + goNode = mergeImports commonStanzas (const id) + + mergeCondTree + :: L.HasBuildInfo a + => DependencyTree BuildInfo + -> DependencyTree a + -> DependencyTree a + mergeCondTree (CondNode bi _ bis) (CondNode x _ cs) = CondNode x' (x' ^. L.targetBuildDepends) cs' + where + fromBuildInfo' :: (BuildInfo -> a) + fromBuildInfo' = fromBuildInfo (unImportNames root) + + -- new value is old value with buildInfo field _prepended_. + x' :: a + x' = x & L.buildInfo %~ (bi <>) + + -- tree components are appended together. + cs' :: [CondBranch ConfVar [Dependency] a] + cs' = map (fromBuildInfo' <$>) bis ++ cs instance Package GenericPackageDescription where packageId = packageId . packageDescription @@ -81,17 +376,29 @@ instance Structured GenericPackageDescription instance NFData GenericPackageDescription where rnf = genericRnf emptyGenericPackageDescription :: GenericPackageDescription -emptyGenericPackageDescription = GenericPackageDescription emptyPackageDescription Nothing [] Nothing [] [] [] [] [] +emptyGenericPackageDescription = + GenericPackageDescription + { packageDescription = emptyPackageDescription + , gpdScannedVersion = Nothing + , genPackageFlags = [] + , condLibrary = Nothing + , condSubLibraries = [] + , condForeignLibs = [] + , condExecutables = [] + , condTestSuites = [] + , condBenchmarks = [] + } -- ----------------------------------------------------------------------------- -- Traversal Instances instance L.HasBuildInfos GenericPackageDescription where - traverseBuildInfos f (GenericPackageDescription p v a1 x1 x2 x3 x4 x5 x6) = - GenericPackageDescription + traverseBuildInfos f (GenericPackageDescription' p v a1 commonStanzas x1 x2 x3 x4 x5 x6) = + GenericPackageDescription' <$> L.traverseBuildInfos f p <*> pure v <*> pure a1 + <*> (traverse . traverseCondTreeBuildInfo) f commonStanzas <*> (traverse . traverseCondTreeBuildInfo) f x1 <*> (traverse . L._2 . traverseCondTreeBuildInfo) f x2 <*> (traverse . L._2 . traverseCondTreeBuildInfo) f x3 diff --git a/Cabal-syntax/src/Distribution/Types/GenericPackageDescription/Lens.hs b/Cabal-syntax/src/Distribution/Types/GenericPackageDescription/Lens.hs index 213c97128f9..9a9593790e8 100644 --- a/Cabal-syntax/src/Distribution/Types/GenericPackageDescription/Lens.hs +++ b/Cabal-syntax/src/Distribution/Types/GenericPackageDescription/Lens.hs @@ -13,6 +13,7 @@ import Distribution.Compat.Prelude import Prelude () import qualified Distribution.Types.GenericPackageDescription as T +import qualified Distribution.Types.Imports as T -- We import types from their packages, so we can remove unused imports -- and have wider inter-module dependency graph @@ -20,16 +21,20 @@ import qualified Distribution.Types.GenericPackageDescription as T import Distribution.Compiler (CompilerFlavor) import Distribution.System (Arch, OS) import Distribution.Types.Benchmark (Benchmark) +import Distribution.Types.BenchmarkStanza (BenchmarkStanza) +import Distribution.Types.BuildInfo (BuildInfo) import Distribution.Types.CondTree (CondTree) import Distribution.Types.ConfVar (ConfVar (..)) import Distribution.Types.Dependency (Dependency) import Distribution.Types.Executable (Executable) import Distribution.Types.Flag (FlagName, PackageFlag (MkPackageFlag)) import Distribution.Types.ForeignLib (ForeignLib) -import Distribution.Types.GenericPackageDescription (GenericPackageDescription (GenericPackageDescription)) +import Distribution.Types.GenericPackageDescription +import Distribution.Types.Imports (ImportName) import Distribution.Types.Library (Library) import Distribution.Types.PackageDescription (PackageDescription) import Distribution.Types.TestSuite (TestSuite) +import Distribution.Types.TestSuiteStanza (TestSuiteStanza) import Distribution.Types.UnqualComponentName (UnqualComponentName) import Distribution.Version (Version, VersionRange) @@ -37,55 +42,99 @@ import Distribution.Version (Version, VersionRange) -- GenericPackageDescription ------------------------------------------------------------------------------- +type DependencyTree a = CondTree ConfVar [Dependency] a + +-- Merging drops commonStanzas! +-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +-- +-- When using an the bidirectional PatternSynonym 'GenericPackageDescription' and its accessors, +-- commonStanzas is filled with mempty. +-- +-- When there's no specific reason to use merging pattern accessors, use the internal one! + packageDescription :: Lens' GenericPackageDescription PackageDescription -packageDescription f s = fmap (\x -> s{T.packageDescription = x}) (f (T.packageDescription s)) +packageDescription f s = fmap (\x -> s{T.packageDescriptionInternal = x}) (f (T.packageDescriptionInternal s)) {-# INLINE packageDescription #-} gpdScannedVersion :: Lens' GenericPackageDescription (Maybe Version) -gpdScannedVersion f s = fmap (\x -> s{T.gpdScannedVersion = x}) (f (T.gpdScannedVersion s)) +gpdScannedVersion f s = fmap (\x -> s{T.gpdScannedVersionInternal = x}) (f (T.gpdScannedVersionInternal s)) {-# INLINE gpdScannedVersion #-} genPackageFlags :: Lens' GenericPackageDescription [PackageFlag] -genPackageFlags f s = fmap (\x -> s{T.genPackageFlags = x}) (f (T.genPackageFlags s)) +genPackageFlags f s = fmap (\x -> s{T.genPackageFlagsInternal = x}) (f (T.genPackageFlagsInternal s)) {-# INLINE genPackageFlags #-} -condLibrary :: Lens' GenericPackageDescription (Maybe (CondTree ConfVar [Dependency] Library)) +gpdCommonStanzas :: Lens' GenericPackageDescription (Map ImportName (DependencyTree (T.WithImports BuildInfo))) +gpdCommonStanzas f s = fmap (\x -> s{T.gpdCommonStanzas = x}) (f (T.gpdCommonStanzas s)) +{-# INLINE gpdCommonStanzas #-} + +condLibraryUnmerged :: Lens' GenericPackageDescription (Maybe (DependencyTree (T.WithImports Library))) +condLibraryUnmerged f s = fmap (\x -> s{T.condLibraryUnmerged = x}) (f (T.condLibraryUnmerged s)) +{-# INLINE condLibraryUnmerged #-} + +condSubLibrariesUnmerged :: Lens' GenericPackageDescription [(UnqualComponentName, (DependencyTree (T.WithImports Library)))] +condSubLibrariesUnmerged f s = fmap (\x -> s{T.condSubLibrariesUnmerged = x}) (f (T.condSubLibrariesUnmerged s)) +{-# INLINE condSubLibrariesUnmerged #-} + +condForeignLibsUnmerged :: Lens' GenericPackageDescription [(UnqualComponentName, (DependencyTree (T.WithImports ForeignLib)))] +condForeignLibsUnmerged f s = fmap (\x -> s{T.condForeignLibsUnmerged = x}) (f (T.condForeignLibsUnmerged s)) +{-# INLINE condForeignLibsUnmerged #-} + +condExecutablesUnmerged :: Lens' GenericPackageDescription [(UnqualComponentName, (DependencyTree (T.WithImports Executable)))] +condExecutablesUnmerged f s = fmap (\x -> s{T.condExecutablesUnmerged = x}) (f (T.condExecutablesUnmerged s)) +{-# INLINE condExecutablesUnmerged #-} + +condTestSuitesUnmerged :: Lens' GenericPackageDescription [(UnqualComponentName, (DependencyTree (T.WithImports TestSuiteStanza)))] +condTestSuitesUnmerged f s = fmap (\x -> s{T.condTestSuitesUnmerged = x}) (f (T.condTestSuitesUnmerged s)) +{-# INLINE condTestSuitesUnmerged #-} + +condBenchmarksUnmerged :: Lens' GenericPackageDescription [(UnqualComponentName, (DependencyTree (T.WithImports BenchmarkStanza)))] +condBenchmarksUnmerged f s = fmap (\x -> s{T.condBenchmarksUnmerged = x}) (f (T.condBenchmarksUnmerged s)) +{-# INLINE condBenchmarksUnmerged #-} + +-- TODO(leana8959): These accessor will merge the imports, apply f, and then put them back as if the imports weren't there +-- This is a good way to mask the import behaviour. +-- However, I do not know when this might be surprising +-- +-- If this is used in the parser for example, it would be a massive footgun because it would essentially "erase" all the imports and put the merged one back +condLibrary :: Lens' GenericPackageDescription (Maybe (DependencyTree (Library))) condLibrary f s = fmap (\x -> s{T.condLibrary = x}) (f (T.condLibrary s)) {-# INLINE condLibrary #-} -condSubLibraries :: Lens' GenericPackageDescription [(UnqualComponentName, (CondTree ConfVar [Dependency] Library))] +condSubLibraries :: Lens' GenericPackageDescription [(UnqualComponentName, (DependencyTree Library))] condSubLibraries f s = fmap (\x -> s{T.condSubLibraries = x}) (f (T.condSubLibraries s)) {-# INLINE condSubLibraries #-} -condForeignLibs :: Lens' GenericPackageDescription [(UnqualComponentName, (CondTree ConfVar [Dependency] ForeignLib))] +condForeignLibs :: Lens' GenericPackageDescription [(UnqualComponentName, (DependencyTree ForeignLib))] condForeignLibs f s = fmap (\x -> s{T.condForeignLibs = x}) (f (T.condForeignLibs s)) {-# INLINE condForeignLibs #-} -condExecutables :: Lens' GenericPackageDescription [(UnqualComponentName, (CondTree ConfVar [Dependency] Executable))] +condExecutables :: Lens' GenericPackageDescription [(UnqualComponentName, (DependencyTree Executable))] condExecutables f s = fmap (\x -> s{T.condExecutables = x}) (f (T.condExecutables s)) {-# INLINE condExecutables #-} -condTestSuites :: Lens' GenericPackageDescription [(UnqualComponentName, (CondTree ConfVar [Dependency] TestSuite))] +condTestSuites :: Lens' GenericPackageDescription [(UnqualComponentName, (DependencyTree TestSuite))] condTestSuites f s = fmap (\x -> s{T.condTestSuites = x}) (f (T.condTestSuites s)) {-# INLINE condTestSuites #-} -condBenchmarks :: Lens' GenericPackageDescription [(UnqualComponentName, (CondTree ConfVar [Dependency] Benchmark))] +condBenchmarks :: Lens' GenericPackageDescription [(UnqualComponentName, (DependencyTree Benchmark))] condBenchmarks f s = fmap (\x -> s{T.condBenchmarks = x}) (f (T.condBenchmarks s)) {-# INLINE condBenchmarks #-} allCondTrees :: Applicative f => ( forall a - . CondTree ConfVar [Dependency] a - -> f (CondTree ConfVar [Dependency] a) + . DependencyTree a + -> f (DependencyTree a) ) -> GenericPackageDescription -> f GenericPackageDescription -allCondTrees f (GenericPackageDescription p v a1 x1 x2 x3 x4 x5 x6) = - GenericPackageDescription +allCondTrees f (GenericPackageDescription' p v a1 commonStanzas x1 x2 x3 x4 x5 x6) = + GenericPackageDescription' <$> pure p <*> pure v <*> pure a1 + <*> traverse f commonStanzas <*> traverse f x1 <*> (traverse . _2) f x2 <*> (traverse . _2) f x3 diff --git a/Cabal-syntax/src/Distribution/Types/Imports.hs b/Cabal-syntax/src/Distribution/Types/Imports.hs new file mode 100644 index 00000000000..732322fe79d --- /dev/null +++ b/Cabal-syntax/src/Distribution/Types/Imports.hs @@ -0,0 +1,25 @@ +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DeriveGeneric #-} + +module Distribution.Types.Imports where + +import Distribution.Compat.Prelude + +data WithImports a = WithImports + { getImportNames :: ![ImportName] + , unImportNames :: !a + } + deriving (Show, Functor, Eq, Ord, Read, Data, Generic) + +instance Binary a => Binary (WithImports a) +instance Structured a => Structured (WithImports a) +instance NFData a => NFData (WithImports a) where rnf = genericRnf + +type ImportName = String + +mapImports :: ([ImportName] -> [ImportName]) -> WithImports a -> WithImports a +mapImports f (WithImports imports x) = WithImports (f imports) x + +noImports :: a -> WithImports a +noImports = WithImports mempty diff --git a/Cabal-syntax/src/Distribution/Types/Imports/Lens.hs b/Cabal-syntax/src/Distribution/Types/Imports/Lens.hs new file mode 100644 index 00000000000..955163acce1 --- /dev/null +++ b/Cabal-syntax/src/Distribution/Types/Imports/Lens.hs @@ -0,0 +1,21 @@ +{-# OPTIONS_GHC "-Wno-orphans" #-} + +-- TODO(leana8959): how can I put HasBuildInfo elsewhere + +module Distribution.Types.Imports.Lens where + +import Distribution.Compat.Lens + +import qualified Distribution.Types.BuildInfo.Lens as L +import qualified Distribution.Types.Imports as T + +getImportNames :: Lens (T.WithImports a) (T.WithImports b) a b +getImportNames f (T.WithImports is x) = fmap (\y -> T.WithImports is y) (f x) +{-# INLINE getImportNames #-} + +unImportNames :: Lens' (T.WithImports a) [T.ImportName] +unImportNames f (T.WithImports is x) = fmap (\is' -> T.WithImports is' x) (f is) +{-# INLINE unImportNames #-} + +instance L.HasBuildInfo a => L.HasBuildInfo (T.WithImports a) where + buildInfo f (T.WithImports is x) = T.WithImports is <$> L.buildInfo f x diff --git a/Cabal-syntax/src/Distribution/Types/TestSuiteStanza.hs b/Cabal-syntax/src/Distribution/Types/TestSuiteStanza.hs new file mode 100644 index 00000000000..9e47a409b03 --- /dev/null +++ b/Cabal-syntax/src/Distribution/Types/TestSuiteStanza.hs @@ -0,0 +1,162 @@ +{-# LANGUAGE ConstraintKinds #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE QuantifiedConstraints #-} + +module Distribution.Types.TestSuiteStanza where + +import Distribution.Compat.Lens +import Distribution.Compat.Prelude +import Prelude () + +import Distribution.CabalSpecVersion +import Distribution.Fields.ParseResult +import Distribution.ModuleName (ModuleName) +import Distribution.Parsec +import Distribution.Pretty (prettyShow) +import Distribution.Types.BuildInfo +import qualified Distribution.Types.BuildInfo.Lens as L +import Distribution.Types.TestSuite +import Distribution.Types.TestSuiteInterface +import Distribution.Types.TestType +import Distribution.Utils.Path + +-- | An intermediate type just used for parsing the test-suite stanza. +-- After validation it is converted into the proper 'TestSuite' type. +data TestSuiteStanza = TestSuiteStanza + { _testStanzaTestType :: Maybe TestType + , _testStanzaMainIs :: Maybe (RelativePath Source File) + , _testStanzaTestModule :: Maybe ModuleName + , _testStanzaBuildInfo :: BuildInfo + , _testStanzaCodeGenerators :: [String] + } + deriving (Show, Eq, Data, Generic) + +instance Binary TestSuiteStanza +instance Structured TestSuiteStanza +instance NFData TestSuiteStanza where rnf = genericRnf + +instance L.HasBuildInfo TestSuiteStanza where + buildInfo = testStanzaBuildInfo + +validateTestSuite :: Position -> TestSuiteStanza -> ParseResult src () +validateTestSuite pos stanza = case _testStanzaTestType stanza of + Nothing -> pure () + Just (TestTypeUnknown _ _) -> pure () + Just tt | tt `notElem` knownTestTypes -> pure () + Just tt@(TestTypeExe _ver) -> case _testStanzaMainIs stanza of + Nothing -> parseFailure pos (missingField "main-is" tt) + Just _file -> + when (isJust (_testStanzaTestModule stanza)) $ + parseWarning pos PWTExtraBenchmarkModule (extraField "test-module" tt) + Just tt@(TestTypeLib _ver) -> case _testStanzaTestModule stanza of + Nothing -> + parseFailure pos (missingField "test-module" tt) + Just _module -> + when (isJust (_testStanzaMainIs stanza)) $ + parseWarning pos PWTExtraMainIs (extraField "main-is" tt) + where + missingField name tt = + "The '" + ++ name + ++ "' field is required for the " + ++ prettyShow tt + ++ " test suite type." + + extraField name tt = + "The '" + ++ name + ++ "' field is not used for the '" + ++ prettyShow tt + ++ "' test suite type." + +-- | Convert a previously validated 'TestSuiteStanza' to 'GenericPackageDescription''s 'TestSuite' type +-- We do not check the validity here +convertTestSuite :: TestSuiteStanza -> TestSuite +convertTestSuite stanza = case _testStanzaTestType stanza of + Nothing -> basicTestSuite + Just tt@(TestTypeUnknown _ _) -> + basicTestSuite + { testInterface = TestSuiteUnsupported tt + } + Just tt + | tt `notElem` knownTestTypes -> + basicTestSuite + { testInterface = TestSuiteUnsupported tt + } + Just (TestTypeExe ver) -> case _testStanzaMainIs stanza of + Nothing -> failedToConvert + Just file -> + basicTestSuite + { testInterface = TestSuiteExeV10 ver file + } + Just (TestTypeLib ver) -> case _testStanzaTestModule stanza of + Nothing -> failedToConvert + Just module_ -> + basicTestSuite + { testInterface = TestSuiteLibV09 ver module_ + } + where + failedToConvert = + error $ + "Unexpected: the conversion from TestSuiteStanza to TestSuite failed\n" + <> "Did you mess with `GenericPackageDescription`?" + + basicTestSuite = + emptyTestSuite + { testBuildInfo = _testStanzaBuildInfo stanza + , testCodeGenerators = _testStanzaCodeGenerators stanza + } + +unvalidateTestSuite :: TestSuite -> TestSuiteStanza +unvalidateTestSuite t = + TestSuiteStanza + { _testStanzaTestType = ty + , _testStanzaMainIs = ma + , _testStanzaTestModule = mo + , _testStanzaBuildInfo = testBuildInfo t + , _testStanzaCodeGenerators = testCodeGenerators t + } + where + (ty, ma, mo) = case testInterface t of + TestSuiteExeV10 ver file -> (Just $ TestTypeExe ver, Just file, Nothing) + TestSuiteLibV09 ver modu -> (Just $ TestTypeLib ver, Nothing, Just modu) + _ -> (Nothing, Nothing, Nothing) + +-- TODO(leana8959): we need to keep a cabal spec version around, and then interpret this after the merging + +-- | We try to guess the TestSuiteType if it's not specified +patchTestSuiteType :: CabalSpecVersion -> TestSuiteStanza -> TestSuiteStanza +patchTestSuiteType cabalSpecVersion stanza = + stanza + { _testStanzaTestType = + _testStanzaTestType stanza + <|> do + guard (cabalSpecVersion >= CabalSpecV3_8) + testTypeExe <$ _testStanzaMainIs stanza + <|> testTypeLib <$ _testStanzaTestModule stanza + } + +testStanzaTestType :: Lens' TestSuiteStanza (Maybe TestType) +testStanzaTestType f s = fmap (\x -> s{_testStanzaTestType = x}) (f (_testStanzaTestType s)) +{-# INLINE testStanzaTestType #-} + +testStanzaMainIs :: Lens' TestSuiteStanza (Maybe (RelativePath Source File)) +testStanzaMainIs f s = fmap (\x -> s{_testStanzaMainIs = x}) (f (_testStanzaMainIs s)) +{-# INLINE testStanzaMainIs #-} + +testStanzaTestModule :: Lens' TestSuiteStanza (Maybe ModuleName) +testStanzaTestModule f s = fmap (\x -> s{_testStanzaTestModule = x}) (f (_testStanzaTestModule s)) +{-# INLINE testStanzaTestModule #-} + +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 #-} diff --git a/Cabal-tests/tests/HackageTests.hs b/Cabal-tests/tests/HackageTests.hs index 1265c6cb13e..ddc35545014 100644 --- a/Cabal-tests/tests/HackageTests.hs +++ b/Cabal-tests/tests/HackageTests.hs @@ -23,6 +23,17 @@ import Data.Monoid (Sum (..)) import Distribution.PackageDescription.Check (PackageCheck (..), checkPackage) import Distribution.PackageDescription.PrettyPrint (showGenericPackageDescription) import Distribution.PackageDescription.Quirks (patchQuirks) +import Distribution.PackageDescription + ( packageDescription + , gpdScannedVersion + , genPackageFlags + , condLibrary + , condSubLibraries + , condForeignLibs + , condExecutables + , condTestSuites + , condBenchmarks + ) import Distribution.Simple.Utils (fromUTF8BS, toUTF8BS) import Distribution.Fields.ParseResult import Distribution.Parsec.Source @@ -257,7 +268,20 @@ roundtripTest testFieldsTransform fpath bs = do let y = y0 & L.packageDescription . L.description .~ mempty let x = x0 & L.packageDescription . L.description .~ mempty - assertEqual' bs' x y + -- Due to the imports being merged, the structural comparison will fail + -- Instead, we check the equality after merging + let checkField field = assertEqual' bs' (field x) (field y) + sequence_ + [ checkField packageDescription + , checkField gpdScannedVersion + , checkField genPackageFlags + , checkField condLibrary + , checkField condSubLibraries + , checkField condForeignLibs + , checkField condExecutables + , checkField condTestSuites + , checkField condBenchmarks + ] -- fromParsecField, "shallow" parser/pretty roundtrip when testFieldsTransform $ diff --git a/Cabal-tests/tests/NoThunks.hs b/Cabal-tests/tests/NoThunks.hs index a53d404dd1e..5f461447cfa 100644 --- a/Cabal-tests/tests/NoThunks.hs +++ b/Cabal-tests/tests/NoThunks.hs @@ -61,8 +61,11 @@ noThunksParse = do -- NoThunks instances ------------------------------------------------------------------------------- +instance NoThunks a => NoThunks (WithImports a) + instance NoThunks Arch instance NoThunks Benchmark +instance NoThunks BenchmarkStanza instance NoThunks BenchmarkInterface instance NoThunks BenchmarkType instance NoThunks BuildInfo @@ -112,6 +115,7 @@ instance NoThunks SourceRepo instance NoThunks IncludeRenaming instance NoThunks ModuleRenaming instance NoThunks TestSuite +instance NoThunks TestSuiteStanza instance NoThunks TestSuiteInterface instance NoThunks TestType instance NoThunks UnqualComponentName diff --git a/Cabal-tests/tests/ParserTests.hs b/Cabal-tests/tests/ParserTests.hs index 8368ed19451..00b11872a3b 100644 --- a/Cabal-tests/tests/ParserTests.hs +++ b/Cabal-tests/tests/ParserTests.hs @@ -10,11 +10,29 @@ import Test.Tasty import Test.Tasty.Golden.Advanced (goldenTest) import Test.Tasty.HUnit -import Control.Monad (unless, void) +import Control.Monad (void) import Data.Algorithm.Diff (PolyDiff (..), getGroupedDiff) import Data.Maybe (isNothing) import Distribution.Fields (pwarning) -import Distribution.PackageDescription (GenericPackageDescription) +import Distribution.PackageDescription + ( GenericPackageDescription + , packageDescription + , gpdScannedVersion + , genPackageFlags + , gpdCommonStanzas + , condLibrary + , condSubLibraries + , condForeignLibs + , condExecutables + , condTestSuites + , condBenchmarks + , condLibraryUnmerged + , condSubLibrariesUnmerged + , condForeignLibsUnmerged + , condExecutablesUnmerged + , condTestSuitesUnmerged + , condBenchmarksUnmerged + ) import Distribution.PackageDescription.Parsec (parseGenericPackageDescription) import Distribution.PackageDescription.PrettyPrint (showGenericPackageDescription) import Distribution.Parsec (PWarnType (..), PWarning (..), showPErrorWithSource, showPWarningWithSource) @@ -41,6 +59,7 @@ import Data.TreeDiff.Instances.Cabal () tests :: TestTree tests = testGroup "parsec tests" [ regressionTests + , accessorsTests , warningTests , errorTests , ipiTests @@ -150,13 +169,50 @@ errorTest fp = cabalGoldenTest fp correct $ do input = "tests" "ParserTests" "errors" fp correct = replaceExtension input "errors" +------------------------------------------------------------------------------- +-- Internal accessors tests +------------------------------------------------------------------------------- + +accessorsTests :: TestTree +accessorsTests = testGroup "accessors" + [ +#ifdef MIN_VERSION_tree_diff + accessorsGoldenTest "library-merging.cabal" +#endif + ] + +#ifdef MIN_VERSION_tree_diff +accessorsGoldenTest :: FilePath -> TestTree +accessorsGoldenTest fp = + let go label f = ediffGolden goldenTest label exprFile $ do + contents <- BS.readFile input + let res = withSource (PCabalFile (fp, contents)) $ parseGenericPackageDescription contents + let (_, x) = runParseResult res + case x of + Right gpd -> pure (toExpr $ f gpd) + Left (_, errs) -> fail $ unlines $ "ERROR" : map (showPErrorWithSource . fmap renderCabalFileSource) (NE.toList errs) + where + input = "tests" "ParserTests" "accessors" fp + exprFile = replaceExtension input (label <> ".expr") + in testGroup "accessors" + [ go "gpdCommonStanzas" gpdCommonStanzas + , go "condLibraryUnmerged" condLibraryUnmerged + , go "condSubLibrariesUnmerged" condSubLibrariesUnmerged + , go "condForeignLibsUnmerged" condForeignLibsUnmerged + , go "condExecutablesUnmerged" condExecutablesUnmerged + , go "condTestSuitesUnmerged" condTestSuitesUnmerged + , go "condBenchmarksUnmerged" condBenchmarksUnmerged + ] +#endif + ------------------------------------------------------------------------------- -- Regressions ------------------------------------------------------------------------------- regressionTests :: TestTree regressionTests = testGroup "regressions" - [ regressionTest "encoding-0.8.cabal" + [ regressionTest "supervisors-0.1.cabal" + , regressionTest "encoding-0.8.cabal" , regressionTest "Octree-0.5.cabal" , regressionTest "nothing-unicode.cabal" , regressionTest "multiple-libs-2.cabal" @@ -232,16 +288,29 @@ formatGoldenTest fp = cabalGoldenTest "format" correct $ do #ifdef MIN_VERSION_tree_diff treeDiffGoldenTest :: FilePath -> TestTree -treeDiffGoldenTest fp = ediffGolden goldenTest "expr" exprFile $ do - contents <- BS.readFile input - let res = withSource (PCabalFile (fp, contents)) $ parseGenericPackageDescription contents - let (_, x) = runParseResult res - case x of - Right gpd -> pure (toExpr gpd) - Left (_, errs) -> fail $ unlines $ "ERROR" : map (showPErrorWithSource . fmap renderCabalFileSource) (NE.toList errs) - where - input = "tests" "ParserTests" "regressions" fp - exprFile = replaceExtension input "expr" +treeDiffGoldenTest fp = + let go label f = ediffGolden goldenTest label exprFile $ do + contents <- BS.readFile input + let res = withSource (PCabalFile (fp, contents)) $ parseGenericPackageDescription contents + let (_, x) = runParseResult res + case x of + Right gpd -> pure (toExpr $ f gpd) + Left (_, errs) -> fail $ unlines $ "ERROR" : map (showPErrorWithSource . fmap renderCabalFileSource) (NE.toList errs) + where + input = "tests" "ParserTests" "regressions" fp + exprFile = replaceExtension input (label <> ".expr") + in testGroup "expr" + [ go "packageDescription" packageDescription + , go "gpdScannedVersion" gpdScannedVersion + , go "genPackageFlags" genPackageFlags + -- Test accessors because they encapsulate the merging behaviour + , go "condLibrary" condLibrary + , go "condSubLibraries" condSubLibraries + , go "condForeignLibs" condForeignLibs + , go "condExecutables" condExecutables + , go "condTestSuites" condTestSuites + , go "condBenchmarks" condBenchmarks + ] #endif formatRoundTripTest :: FilePath -> TestTree @@ -250,24 +319,38 @@ formatRoundTripTest fp = testCase "roundtrip" $ do x <- parse contents let contents' = showGenericPackageDescription x y <- parse (toUTF8BS contents') - -- previously we mangled licenses a bit - let y' = y + + let checkField field = + field x == field y @? {- FOURMOLU_DISABLE -} - unless (x == y') $ #ifdef MIN_VERSION_tree_diff - assertFailure $ unlines - [ "re-parsed doesn't match" - , show $ ansiWlEditExpr $ ediff x y - ] + unlines + [ "re-parsed doesn't match" + , show $ ansiWlEditExpr $ ediff x y + ] #else - assertFailure $ unlines - [ "re-parsed doesn't match" - , "expected" - , show x - , "actual" - , show y - ] + unlines + [ "re-parsed doesn't match" + , "expected" + , show x + , "actual" + , show y + ] #endif + -- Due to the imports being merged, the structural comparison will fail + -- Instead, we check the equality after merging + sequence_ + [ checkField packageDescription + , checkField gpdScannedVersion + , checkField genPackageFlags + , checkField condLibrary + , checkField condSubLibraries + , checkField condForeignLibs + , checkField condExecutables + , checkField condTestSuites + , checkField condBenchmarks + ] + where parse :: BS.ByteString -> IO GenericPackageDescription parse c = do diff --git a/Cabal-tests/tests/ParserTests/accessors/library-merging.cabal b/Cabal-tests/tests/ParserTests/accessors/library-merging.cabal new file mode 100644 index 00000000000..6f8ed6ad6c0 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/accessors/library-merging.cabal @@ -0,0 +1,30 @@ +cabal-version: 3.0 +name: Library-merging +version: 0 +synopsis: Tests the correctness of deferred merging in imports +build-type: Simple + +flag foo + manual: True + default: True + +common windows + if os(windows) + build-depends: Win32 + +common deps + import: windows + buildable: True + build-depends: + base >=4.10 && <4.11, + containers + +library + if flag(foo) + import: deps + + default-language: Haskell2010 + exposed-modules: ElseIf + + build-depends: + ghc-prim diff --git a/Cabal-tests/tests/ParserTests/accessors/library-merging.condBenchmarksUnmerged.expr b/Cabal-tests/tests/ParserTests/accessors/library-merging.condBenchmarksUnmerged.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/accessors/library-merging.condBenchmarksUnmerged.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/accessors/library-merging.condExecutablesUnmerged.expr b/Cabal-tests/tests/ParserTests/accessors/library-merging.condExecutablesUnmerged.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/accessors/library-merging.condExecutablesUnmerged.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/accessors/library-merging.condForeignLibsUnmerged.expr b/Cabal-tests/tests/ParserTests/accessors/library-merging.condForeignLibsUnmerged.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/accessors/library-merging.condForeignLibsUnmerged.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.expr b/Cabal-tests/tests/ParserTests/accessors/library-merging.condLibraryUnmerged.expr similarity index 65% rename from Cabal-tests/tests/ParserTests/regressions/nothing-unicode.expr rename to Cabal-tests/tests/ParserTests/accessors/library-merging.condLibraryUnmerged.expr index ccfe4421c7b..52e6ffc5359 100644 --- a/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.expr +++ b/Cabal-tests/tests/ParserTests/accessors/library-merging.condLibraryUnmerged.expr @@ -1,64 +1,11 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV1_10, - package = PackageIdentifier { - pkgName = PackageName "\28961", - 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 = - "The canonical non-package \28961", - description = "", - category = "", - customFieldsPD = [ - _×_ "x-\28961" "\28961"], - buildTypeRaw = Just Simple, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [ - MkPackageFlag { - flagName = FlagName "\28961", - flagDescription = "\28961", - flagDefault = True, - flagManual = False}], - condLibrary = Just - CondNode { - condTreeData = Library { +Just + CondNode { + condTreeData = WithImports { + getImportNames = [], + unImportNames = Library { libName = LMainLibName, exposedModules = [ - ModuleName "\937"], + ModuleName "ElseIf"], reexportedModules = [], signatures = [], libExposed = True, @@ -69,11 +16,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -119,15 +66,25 @@ GenericPackageDescription { staticOptions = PerCompilerFlavor [] [], customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = [ - CondBranch { - condBranchCondition = - `CNot (Var (PackageFlag (FlagName "\\28961")))`, - condBranchIfTrue = CondNode { - condTreeData = Library { + 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 = WithImports { + getImportNames = ["deps"], + unImportNames = Library { libName = LMainLibName, exposedModules = [], reexportedModules = [], @@ -136,15 +93,15 @@ GenericPackageDescription { libVisibility = LibraryVisibilityPublic, libBuildInfo = BuildInfo { - buildable = False, + buildable = True, buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -190,12 +147,7 @@ GenericPackageDescription { PerCompilerFlavor [] [], customFieldsBI = [], targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}, - condBranchIfFalse = Nothing}]}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} + mixins = []}}}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]} diff --git a/Cabal-tests/tests/ParserTests/accessors/library-merging.condSubLibrariesUnmerged.expr b/Cabal-tests/tests/ParserTests/accessors/library-merging.condSubLibrariesUnmerged.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/accessors/library-merging.condSubLibrariesUnmerged.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/accessors/library-merging.condTestSuitesUnmerged.expr b/Cabal-tests/tests/ParserTests/accessors/library-merging.condTestSuitesUnmerged.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/accessors/library-merging.condTestSuitesUnmerged.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5055.expr b/Cabal-tests/tests/ParserTests/accessors/library-merging.gpdCommonStanzas.expr similarity index 65% rename from Cabal-tests/tests/ParserTests/regressions/issue-5055.expr rename to Cabal-tests/tests/ParserTests/accessors/library-merging.gpdCommonStanzas.expr index 996fa26eece..2ba0b4c17fa 100644 --- a/Cabal-tests/tests/ParserTests/regressions/issue-5055.expr +++ b/Cabal-tests/tests/ParserTests/accessors/library-merging.gpdCommonStanzas.expr @@ -1,67 +1,20 @@ -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 = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Nothing, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [ +Map.fromList + [ _×_ - (UnqualComponentName - "flag-test-exe") + "deps" CondNode { - condTreeData = Executable { - exeName = UnqualComponentName - "flag-test-exe", - modulePath = SymbolicPath - "FirstMain.hs", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { + condTreeData = WithImports { + getImportNames = ["windows"], + unImportNames = BuildInfo { buildable = True, buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -76,8 +29,7 @@ GenericPackageDescription { otherModules = [], virtualModules = [], autogenModules = [], - defaultLanguage = Just - Haskell2010, + defaultLanguage = Nothing, otherLanguages = [], defaultExtensions = [], otherExtensions = [], @@ -112,9 +64,13 @@ GenericPackageDescription { (PackageName "base") (IntersectVersionRanges (OrLaterVersion - (mkVersion [4, 8])) + (mkVersion [4, 10])) (EarlierVersion - (mkVersion [5]))) + (mkVersion [4, 11]))) + mainLibSet, + Dependency + (PackageName "containers") + (OrLaterVersion (mkVersion [0])) mainLibSet], mixins = []}}, condTreeConstraints = [ @@ -122,32 +78,30 @@ GenericPackageDescription { (PackageName "base") (IntersectVersionRanges (OrLaterVersion - (mkVersion [4, 8])) + (mkVersion [4, 10])) (EarlierVersion - (mkVersion [5]))) + (mkVersion [4, 11]))) + mainLibSet, + Dependency + (PackageName "containers") + (OrLaterVersion (mkVersion [0])) mainLibSet], - condTreeComponents = []}], - condTestSuites = [ + condTreeComponents = []}, _×_ - (UnqualComponentName - "flag-cabal-test") + "windows" CondNode { - condTreeData = TestSuite { - testName = UnqualComponentName - "", - testInterface = TestSuiteExeV10 - (mkVersion [1, 0]) - (SymbolicPath "SecondMain.hs"), - testBuildInfo = BuildInfo { + condTreeData = WithImports { + getImportNames = [], + unImportNames = BuildInfo { buildable = True, buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -162,8 +116,7 @@ GenericPackageDescription { otherModules = [], virtualModules = [], autogenModules = [], - defaultLanguage = Just - Haskell2010, + defaultLanguage = Nothing, otherLanguages = [], defaultExtensions = [], otherExtensions = [], @@ -193,49 +146,26 @@ GenericPackageDescription { 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], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], condTreeComponents = [ CondBranch { condBranchCondition = `Var (OS Windows)`, condBranchIfTrue = CondNode { - condTreeData = TestSuite { - testName = UnqualComponentName - "", - testInterface = - TestSuiteUnsupported - (TestTypeUnknown - "" - (mkVersion [])), - testBuildInfo = BuildInfo { + condTreeData = WithImports { + getImportNames = [], + unImportNames = BuildInfo { buildable = True, buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -280,10 +210,16 @@ GenericPackageDescription { staticOptions = PerCompilerFlavor [] [], customFieldsBI = [], - targetBuildDepends = [], - mixins = []}, - testCodeGenerators = []}, - condTreeConstraints = [], + targetBuildDepends = [ + Dependency + (PackageName "Win32") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "Win32") + (OrLaterVersion (mkVersion [0])) + mainLibSet], condTreeComponents = []}, - condBranchIfFalse = Nothing}]}], - condBenchmarks = []} + condBranchIfFalse = Nothing}]}] diff --git a/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.condLibrary.expr new file mode 100644 index 00000000000..3238fef0f66 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.condLibrary.expr @@ -0,0 +1,109 @@ +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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.condTestSuites.expr new file mode 100644 index 00000000000..4acb3c74a80 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.condTestSuites.expr @@ -0,0 +1,219 @@ +[ + _×_ + (UnqualComponentName + "test_Octree") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + (SymbolicPath + "tests/test_Octree.hs"), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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]) + (SymbolicPath "README.lhs"), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.expr b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.expr deleted file mode 100644 index 634b27b8828..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.expr +++ /dev/null @@ -1,404 +0,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 = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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]) - (SymbolicPath - "tests/test_Octree.hs"), - testBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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]) - (SymbolicPath "README.lhs"), - testBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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/Octree-0.5.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.packageDescription.expr new file mode 100644 index 00000000000..1d3cf682eb0 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.packageDescription.expr @@ -0,0 +1,68 @@ +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 = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/anynone.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/anynone.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/anynone.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/anynone.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/anynone.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/anynone.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/anynone.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/anynone.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/anynone.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/anynone.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/anynone.condLibrary.expr new file mode 100644 index 00000000000..ddc7e748430 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/anynone.condLibrary.expr @@ -0,0 +1,78 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName "AnyNone"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/anynone.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/anynone.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/anynone.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/anynone.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/anynone.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/anynone.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/anynone.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/anynone.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/anynone.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/anynone.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/anynone.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/anynone.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/anynone.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/anynone.packageDescription.expr new file mode 100644 index 00000000000..9f37dbb5280 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/anynone.packageDescription.expr @@ -0,0 +1,34 @@ +PackageDescription { + specVersion = CabalSpecV3_0, + package = PackageIdentifier { + pkgName = PackageName "anynone", + pkgVersion = mkVersion [0]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = "The -any none demo", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/big-version.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/big-version.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/big-version.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/big-version.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/big-version.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/big-version.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/big-version.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/big-version.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/big-version.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/big-version.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/big-version.condLibrary.expr new file mode 100644 index 00000000000..acc4281010f --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/big-version.condLibrary.expr @@ -0,0 +1,69 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/big-version.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/big-version.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/big-version.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/big-version.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/big-version.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/big-version.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/big-version.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/big-version.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/big-version.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/big-version.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/big-version.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/big-version.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/big-version.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/big-version.packageDescription.expr new file mode 100644 index 00000000000..6b6f2eb5bd5 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/big-version.packageDescription.expr @@ -0,0 +1,36 @@ +PackageDescription { + specVersion = CabalSpecV3_0, + package = PackageIdentifier { + pkgName = PackageName + "big-version", + pkgVersion = mkVersion + [123456789]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = "", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Nothing, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/common-conditional.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/common-conditional.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common-conditional.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/common-conditional.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/common-conditional.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common-conditional.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/common-conditional.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/common-conditional.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common-conditional.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/common-conditional.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/common-conditional.condLibrary.expr new file mode 100644 index 00000000000..0e3d49ae740 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common-conditional.condLibrary.expr @@ -0,0 +1,252 @@ +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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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}]} diff --git a/Cabal-tests/tests/ParserTests/regressions/common-conditional.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/common-conditional.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common-conditional.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/common-conditional.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/common-conditional.condTestSuites.expr new file mode 100644 index 00000000000..f0110fa556a --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common-conditional.condTestSuites.expr @@ -0,0 +1,405 @@ +[ + _×_ + (UnqualComponentName "tests") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + (SymbolicPath "Tests.hs"), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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}]}] diff --git a/Cabal-tests/tests/ParserTests/regressions/common-conditional.expr b/Cabal-tests/tests/ParserTests/regressions/common-conditional.expr deleted file mode 100644 index 41e0fd5377a..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/common-conditional.expr +++ /dev/null @@ -1,716 +0,0 @@ -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 = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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]) - (SymbolicPath "Tests.hs"), - testBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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-conditional.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/common-conditional.genPackageFlags.expr new file mode 100644 index 00000000000..e28e3de5409 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common-conditional.genPackageFlags.expr @@ -0,0 +1,6 @@ +[ + MkPackageFlag { + flagName = FlagName "foo", + flagDescription = "", + flagDefault = True, + flagManual = True}] diff --git a/Cabal-tests/tests/ParserTests/regressions/common-conditional.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/common-conditional.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common-conditional.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/common-conditional.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/common-conditional.packageDescription.expr new file mode 100644 index 00000000000..f9bbedb99bb --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common-conditional.packageDescription.expr @@ -0,0 +1,46 @@ +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 = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/common.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/common.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/common.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/common.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/common.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/common.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/common.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/common.condLibrary.expr new file mode 100644 index 00000000000..d2670399e96 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common.condLibrary.expr @@ -0,0 +1,78 @@ +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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "ghc-prim") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "ghc-prim") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/common.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/common.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/common.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/common.condTestSuites.expr new file mode 100644 index 00000000000..3c9a50860f2 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common.condTestSuites.expr @@ -0,0 +1,77 @@ +[ + _×_ + (UnqualComponentName "tests") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + (SymbolicPath "Tests.hs"), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "HUnit") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "HUnit") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/common.expr b/Cabal-tests/tests/ParserTests/regressions/common.expr deleted file mode 100644 index e8c766460f2..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/common.expr +++ /dev/null @@ -1,212 +0,0 @@ -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 = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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]) - (SymbolicPath "Tests.hs"), - testBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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/common.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/common.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/common.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/common.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/common.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/common.packageDescription.expr new file mode 100644 index 00000000000..7fe8c58c01c --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common.packageDescription.expr @@ -0,0 +1,49 @@ +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 = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/common2.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/common2.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common2.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/common2.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/common2.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common2.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/common2.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/common2.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common2.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/common2.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/common2.condLibrary.expr new file mode 100644 index 00000000000..ab9d347d4e0 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common2.condLibrary.expr @@ -0,0 +1,181 @@ +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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "Win32") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "Win32") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]} diff --git a/Cabal-tests/tests/ParserTests/regressions/elif.expr b/Cabal-tests/tests/ParserTests/regressions/common2.condSubLibraries.expr similarity index 71% rename from Cabal-tests/tests/ParserTests/regressions/elif.expr rename to Cabal-tests/tests/ParserTests/regressions/common2.condSubLibraries.expr index e04821eaaef..b8f3d8fb865 100644 --- a/Cabal-tests/tests/ParserTests/regressions/elif.expr +++ b/Cabal-tests/tests/ParserTests/regressions/common2.condSubLibraries.expr @@ -1,72 +1,28 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV1_10, - package = PackageIdentifier { - pkgName = PackageName "elif", - 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 = "The elif demo", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Just Simple, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just +[ + _×_ + (UnqualComponentName "internal") CondNode { condTreeData = Library { - libName = LMainLibName, + libName = LSubLibName + (UnqualComponentName + "internal"), exposedModules = [ - ModuleName "ElseIf"], + ModuleName "ElseIf2"], reexportedModules = [], signatures = [], libExposed = True, libVisibility = - LibraryVisibilityPublic, + LibraryVisibilityPrivate, libBuildInfo = BuildInfo { buildable = True, buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -112,32 +68,66 @@ GenericPackageDescription { staticOptions = PerCompilerFlavor [] [], customFieldsBI = [], - targetBuildDepends = [], + 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 = [], + 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 Linux)`, + `Var (OS Windows)`, condBranchIfTrue = CondNode { condTreeData = Library { - libName = LMainLibName, + libName = LSubLibName + (UnqualComponentName + "internal"), exposedModules = [], reexportedModules = [], signatures = [], libExposed = True, libVisibility = - LibraryVisibilityPublic, + LibraryVisibilityPrivate, libBuildInfo = BuildInfo { buildable = True, buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -184,19 +174,14 @@ GenericPackageDescription { customFieldsBI = [], targetBuildDepends = [ Dependency - (PackageName "unix") + (PackageName "Win32") (OrLaterVersion (mkVersion [0])) mainLibSet], mixins = []}}, condTreeConstraints = [ Dependency - (PackageName "unix") + (PackageName "Win32") (OrLaterVersion (mkVersion [0])) mainLibSet], condTreeComponents = []}, - condBranchIfFalse = Nothing}]}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} + condBranchIfFalse = Nothing}]}] diff --git a/Cabal-tests/tests/ParserTests/regressions/common2.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/common2.condTestSuites.expr new file mode 100644 index 00000000000..0a139c37f93 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common2.condTestSuites.expr @@ -0,0 +1,333 @@ +[ + _×_ + (UnqualComponentName "tests") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + (SymbolicPath "Tests.hs"), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}] diff --git a/Cabal-tests/tests/ParserTests/regressions/common2.expr b/Cabal-tests/tests/ParserTests/regressions/common2.expr deleted file mode 100644 index af882207fc4..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/common2.expr +++ /dev/null @@ -1,753 +0,0 @@ -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 = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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]) - (SymbolicPath "Tests.hs"), - testBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}, - testCodeGenerators = []}, - condTreeConstraints = [], - condTreeComponents = []}, - condBranchIfFalse = Nothing}]}], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/common2.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/common2.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common2.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/common2.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/common2.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common2.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/common2.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/common2.packageDescription.expr new file mode 100644 index 00000000000..35b398ff00b --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common2.packageDescription.expr @@ -0,0 +1,45 @@ +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 = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/common3.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/common3.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common3.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/common3.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/common3.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common3.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/common3.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/common3.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common3.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/common3.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/common3.condLibrary.expr new file mode 100644 index 00000000000..d2670399e96 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common3.condLibrary.expr @@ -0,0 +1,78 @@ +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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "ghc-prim") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "ghc-prim") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/common3.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/common3.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common3.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.expr b/Cabal-tests/tests/ParserTests/regressions/common3.condTestSuites.expr similarity index 55% rename from Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.expr rename to Cabal-tests/tests/ParserTests/regressions/common3.condTestSuites.expr index ce7c453e697..f1841f497bf 100644 --- a/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.expr +++ b/Cabal-tests/tests/ParserTests/regressions/common3.condTestSuites.expr @@ -1,61 +1,23 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV3_0, - package = PackageIdentifier { - pkgName = PackageName "issue", - pkgVersion = mkVersion [6083]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = "", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Nothing, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just +[ + _×_ + (UnqualComponentName "tests") CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + (SymbolicPath "Tests.hs"), + testBuildInfo = BuildInfo { buildable = True, buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -70,8 +32,7 @@ GenericPackageDescription { otherModules = [], virtualModules = [], autogenModules = [], - defaultLanguage = Just - Haskell2010, + defaultLanguage = Nothing, otherLanguages = [], defaultExtensions = [], otherExtensions = [], @@ -103,26 +64,38 @@ GenericPackageDescription { customFieldsBI = [], targetBuildDepends = [ Dependency - (PackageName "freetype") + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 10])) + (EarlierVersion + (mkVersion [4, 11]))) + mainLibSet, + Dependency + (PackageName "containers") (OrLaterVersion (mkVersion [0])) mainLibSet, Dependency - (PackageName "freetype") + (PackageName "HUnit") (OrLaterVersion (mkVersion [0])) mainLibSet], - mixins = []}}, + mixins = []}, + testCodeGenerators = []}, condTreeConstraints = [ Dependency - (PackageName "freetype") + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 10])) + (EarlierVersion + (mkVersion [4, 11]))) + mainLibSet, + Dependency + (PackageName "containers") (OrLaterVersion (mkVersion [0])) mainLibSet, Dependency - (PackageName "freetype") + (PackageName "HUnit") (OrLaterVersion (mkVersion [0])) mainLibSet], - condTreeComponents = []}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} + condTreeComponents = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/common3.expr b/Cabal-tests/tests/ParserTests/regressions/common3.expr deleted file mode 100644 index be783c4cab6..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/common3.expr +++ /dev/null @@ -1,236 +0,0 @@ -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 = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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]) - (SymbolicPath "Tests.hs"), - testBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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/common3.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/common3.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common3.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/common3.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/common3.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common3.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/common3.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/common3.packageDescription.expr new file mode 100644 index 00000000000..a142753eef8 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/common3.packageDescription.expr @@ -0,0 +1,49 @@ +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 = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/elif.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/elif.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/elif.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/elif.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/elif.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/elif.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/elif.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/elif.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/elif.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/elif.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/elif.condLibrary.expr new file mode 100644 index 00000000000..1e463e8bded --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/elif.condLibrary.expr @@ -0,0 +1,149 @@ +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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `Var (OS Linux)`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "unix") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "unix") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]} diff --git a/Cabal-tests/tests/ParserTests/regressions/elif.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/elif.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/elif.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/elif.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/elif.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/elif.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/elif.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/elif.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/elif.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/elif.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/elif.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/elif.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/elif.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/elif.packageDescription.expr new file mode 100644 index 00000000000..ea2a00f7d2a --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/elif.packageDescription.expr @@ -0,0 +1,44 @@ +PackageDescription { + specVersion = CabalSpecV1_10, + package = PackageIdentifier { + pkgName = PackageName "elif", + 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 = "The elif demo", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/elif2.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/elif2.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/elif2.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/elif2.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/elif2.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/elif2.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/elif2.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/elif2.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/elif2.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/elif2.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/elif2.condLibrary.expr new file mode 100644 index 00000000000..4eb2a84e2f5 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/elif2.condLibrary.expr @@ -0,0 +1,362 @@ +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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `Var (OS Linux)`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "unix") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "unix") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "Win32") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "Win32") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = False, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []}}]}}]} diff --git a/Cabal-tests/tests/ParserTests/regressions/elif2.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/elif2.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/elif2.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/elif2.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/elif2.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/elif2.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/elif2.expr b/Cabal-tests/tests/ParserTests/regressions/elif2.expr deleted file mode 100644 index 88eb02d59d7..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/elif2.expr +++ /dev/null @@ -1,415 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV2_2, - package = PackageIdentifier { - pkgName = PackageName "elif", - 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 = "The elif demo", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Just Simple, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = [ - CondBranch { - condBranchCondition = - `Var (OS Linux)`, - condBranchIfTrue = CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "unix") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "unix") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeComponents = []}, - condBranchIfFalse = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "Win32") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "Win32") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeComponents = []}, - condBranchIfFalse = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = False, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}}]}}]}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/elif2.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/elif2.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/elif2.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/elif2.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/elif2.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/elif2.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/elif2.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/elif2.packageDescription.expr new file mode 100644 index 00000000000..0bd95cbf42d --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/elif2.packageDescription.expr @@ -0,0 +1,44 @@ +PackageDescription { + specVersion = CabalSpecV2_2, + package = PackageIdentifier { + pkgName = PackageName "elif", + 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 = "The elif demo", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.condLibrary.expr new file mode 100644 index 00000000000..353f9b25e8f --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.condLibrary.expr @@ -0,0 +1,90 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName "Data.Encoding"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 + [ + "-Wall", + "-O2", + "-threaded", + "-rtsopts", + "-with-rtsopts=-N1 -A64m"] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (UnionVersionRanges + (LaterVersion + (mkVersion [4, 4])) + (ThisVersion + (mkVersion [4, 4]))) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (UnionVersionRanges + (LaterVersion + (mkVersion [4, 4])) + (ThisVersion + (mkVersion [4, 4]))) + mainLibSet], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.expr b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.expr deleted file mode 100644 index 02c4a4222c7..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.expr +++ /dev/null @@ -1,148 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV1_12, - package = PackageIdentifier { - pkgName = PackageName - "encoding", - pkgVersion = mkVersion [0, 8]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = "", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Nothing, - setupBuildInfo = Just - SetupBuildInfo { - setupDepends = [ - Dependency - (PackageName "base") - (EarlierVersion (mkVersion [5])) - mainLibSet, - Dependency - (PackageName "ghc-prim") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - defaultSetupDepends = False}, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [ - SymbolicPath "README.md", - SymbolicPath "--", - SymbolicPath "--"], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [ - ModuleName "Data.Encoding"], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 - [ - "-Wall", - "-O2", - "-threaded", - "-rtsopts", - "-with-rtsopts=-N1 -A64m"] - [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = - PerCompilerFlavor [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (UnionVersionRanges - (LaterVersion - (mkVersion [4, 4])) - (ThisVersion - (mkVersion [4, 4]))) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (UnionVersionRanges - (LaterVersion - (mkVersion [4, 4])) - (ThisVersion - (mkVersion [4, 4]))) - mainLibSet], - condTreeComponents = []}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.packageDescription.expr new file mode 100644 index 00000000000..e979a3cf116 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.packageDescription.expr @@ -0,0 +1,49 @@ +PackageDescription { + specVersion = CabalSpecV1_12, + package = PackageIdentifier { + pkgName = PackageName + "encoding", + pkgVersion = mkVersion [0, 8]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = "", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Nothing, + setupBuildInfo = Just + SetupBuildInfo { + setupDepends = [ + Dependency + (PackageName "base") + (EarlierVersion (mkVersion [5])) + mainLibSet, + Dependency + (PackageName "ghc-prim") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + defaultSetupDepends = False}, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [ + SymbolicPath "README.md", + SymbolicPath "--", + SymbolicPath "--"], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/generics-sop.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/generics-sop.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/generics-sop.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/generics-sop.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/generics-sop.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/generics-sop.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/generics-sop.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/generics-sop.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/generics-sop.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/generics-sop.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/generics-sop.condLibrary.expr new file mode 100644 index 00000000000..76630720e45 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/generics-sop.condLibrary.expr @@ -0,0 +1,528 @@ +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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]} diff --git a/Cabal-tests/tests/ParserTests/regressions/generics-sop.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/generics-sop.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/generics-sop.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/generics-sop.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/generics-sop.condTestSuites.expr new file mode 100644 index 00000000000..7e22ac9c4a2 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/generics-sop.condTestSuites.expr @@ -0,0 +1,194 @@ +[ + _×_ + (UnqualComponentName "doctests") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + (SymbolicPath "doctests.hs"), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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]) + (SymbolicPath "Example.hs"), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/generics-sop.expr b/Cabal-tests/tests/ParserTests/regressions/generics-sop.expr deleted file mode 100644 index a7cdf1a4300..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/generics-sop.expr +++ /dev/null @@ -1,855 +0,0 @@ -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 , Andres L\246h ", - 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", - "* @@ basic examples,\n", - "\n", - "* @@ generic pretty printing,\n", - "\n", - "* @@ generically computed lenses,\n", - "\n", - "* @@ 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", - ".\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 = SymbolicPath ".", - extraSrcFiles = [ - SymbolicPath "CHANGELOG.md"], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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]) - (SymbolicPath "doctests.hs"), - testBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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]) - (SymbolicPath "Example.hs"), - testBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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/generics-sop.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/generics-sop.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/generics-sop.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/generics-sop.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/generics-sop.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/generics-sop.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/generics-sop.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/generics-sop.packageDescription.expr new file mode 100644 index 00000000000..8e3c834bea9 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/generics-sop.packageDescription.expr @@ -0,0 +1,125 @@ +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 , Andres L\246h ", + 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", + "* @@ basic examples,\n", + "\n", + "* @@ generic pretty printing,\n", + "\n", + "* @@ generically computed lenses,\n", + "\n", + "* @@ 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", + ".\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 = SymbolicPath ".", + extraSrcFiles = [ + SymbolicPath "CHANGELOG.md"], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/hasktorch.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/hasktorch.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/hasktorch.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/hasktorch.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/hasktorch.condExecutables.expr new file mode 100644 index 00000000000..61e9ad7f94d --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/hasktorch.condExecutables.expr @@ -0,0 +1,412 @@ +[ + _×_ + (UnqualComponentName + "isdefinite-cpu") + CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "isdefinite-cpu", + modulePath = SymbolicPath + "Noop.hs", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "hasktorch-cpu")]))], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "hasktorch-cpu")]))], + condTreeComponents = []}, + _×_ + (UnqualComponentName + "isdefinite-gpu") + CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "isdefinite-gpu", + modulePath = SymbolicPath + "Noop.hs", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "hasktorch-gpu")]))], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "hasktorch-gpu")]))], + condTreeComponents = []}, + _×_ + (UnqualComponentName + "isdefinite") + CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "isdefinite", + modulePath = SymbolicPath + "Noop.hs", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + _×_ + (UnqualComponentName "memcheck") + CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "memcheck", + modulePath = SymbolicPath + "Memcheck.hs", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/hasktorch.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/hasktorch.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/hasktorch.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/hasktorch.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/hasktorch.condLibrary.expr new file mode 100644 index 00000000000..5f4b337ad30 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/hasktorch.condLibrary.expr @@ -0,0 +1,1036 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName + "Torch.Core.Exceptions", + ModuleName "Torch.Core.Random", + ModuleName "Torch.Core.LogAdd"], + reexportedModules = [ + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Types.Numeric", + moduleReexportName = ModuleName + "Torch.Types.Numeric"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Long", + moduleReexportName = ModuleName + "Torch.Long"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Long.Dynamic", + moduleReexportName = ModuleName + "Torch.Long.Dynamic"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Long.Storage", + moduleReexportName = ModuleName + "Torch.Long.Storage"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Double", + moduleReexportName = ModuleName + "Torch.Double"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.Dynamic", + moduleReexportName = ModuleName + "Torch.Double.Dynamic"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.Storage", + moduleReexportName = ModuleName + "Torch.Double.Storage"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Double.NN", + moduleReexportName = ModuleName + "Torch.Double.NN"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Activation", + moduleReexportName = ModuleName + "Torch.Double.NN.Activation"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Backprop", + moduleReexportName = ModuleName + "Torch.Double.NN.Backprop"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Conv1d", + moduleReexportName = ModuleName + "Torch.Double.NN.Conv1d"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Conv2d", + moduleReexportName = ModuleName + "Torch.Double.NN.Conv2d"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Criterion", + moduleReexportName = ModuleName + "Torch.Double.NN.Criterion"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Layers", + moduleReexportName = ModuleName + "Torch.Double.NN.Layers"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Linear", + moduleReexportName = ModuleName + "Torch.Double.NN.Linear"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Math", + moduleReexportName = ModuleName + "Torch.Double.NN.Math"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Padding", + moduleReexportName = ModuleName + "Torch.Double.NN.Padding"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Pooling", + moduleReexportName = ModuleName + "Torch.Double.NN.Pooling"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Sampling", + moduleReexportName = ModuleName + "Torch.Double.NN.Sampling"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.Dynamic.NN", + moduleReexportName = ModuleName + "Torch.Double.Dynamic.NN"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.Dynamic.NN.Activation", + moduleReexportName = ModuleName + "Torch.Double.Dynamic.NN.Activation"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.Dynamic.NN.Pooling", + moduleReexportName = ModuleName + "Torch.Double.Dynamic.NN.Pooling"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.Dynamic.NN.Criterion", + moduleReexportName = ModuleName + "Torch.Double.Dynamic.NN.Criterion"}], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "utils"], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [ + EnableExtension LambdaCase, + EnableExtension DataKinds, + EnableExtension TypeFamilies, + EnableExtension + TypeSynonymInstances, + EnableExtension + ScopedTypeVariables, + EnableExtension + FlexibleContexts, + EnableExtension CPP], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "dimensions") + (UnionVersionRanges + (ThisVersion (mkVersion [1, 0])) + (LaterVersion + (mkVersion [1, 0]))) + mainLibSet, + Dependency + (PackageName "safe-exceptions") + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 1, 0])) + (LaterVersion + (mkVersion [0, 1, 0]))) + mainLibSet, + Dependency + (PackageName "singletons") + (UnionVersionRanges + (ThisVersion (mkVersion [2, 2])) + (LaterVersion + (mkVersion [2, 2]))) + mainLibSet, + Dependency + (PackageName "text") + (UnionVersionRanges + (ThisVersion + (mkVersion [1, 2, 2])) + (LaterVersion + (mkVersion [1, 2, 2]))) + mainLibSet, + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "hasktorch-cpu")])), + Dependency + (PackageName "hasktorch-ffi-th") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet, + Dependency + (PackageName + "hasktorch-types-th") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "dimensions") + (UnionVersionRanges + (ThisVersion (mkVersion [1, 0])) + (LaterVersion + (mkVersion [1, 0]))) + mainLibSet, + Dependency + (PackageName "safe-exceptions") + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 1, 0])) + (LaterVersion + (mkVersion [0, 1, 0]))) + mainLibSet, + Dependency + (PackageName "singletons") + (UnionVersionRanges + (ThisVersion (mkVersion [2, 2])) + (LaterVersion + (mkVersion [2, 2]))) + mainLibSet, + Dependency + (PackageName "text") + (UnionVersionRanges + (ThisVersion + (mkVersion [1, 2, 2])) + (LaterVersion + (mkVersion [1, 2, 2]))) + mainLibSet, + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "hasktorch-cpu")])), + Dependency + (PackageName "hasktorch-ffi-th") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet, + Dependency + (PackageName + "hasktorch-types-th") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `CNot (Var (PackageFlag (FlagName "lite")))`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [ + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Byte", + moduleReexportName = ModuleName + "Torch.Byte"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Byte.Dynamic", + moduleReexportName = ModuleName + "Torch.Byte.Dynamic"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Byte.Storage", + moduleReexportName = ModuleName + "Torch.Byte.Storage"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Char", + moduleReexportName = ModuleName + "Torch.Char"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Char.Dynamic", + moduleReexportName = ModuleName + "Torch.Char.Dynamic"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Char.Storage", + moduleReexportName = ModuleName + "Torch.Char.Storage"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Short", + moduleReexportName = ModuleName + "Torch.Short"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Short.Dynamic", + moduleReexportName = ModuleName + "Torch.Short.Dynamic"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Short.Storage", + moduleReexportName = ModuleName + "Torch.Short.Storage"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Int", + moduleReexportName = ModuleName + "Torch.Int"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Int.Dynamic", + moduleReexportName = ModuleName + "Torch.Int.Dynamic"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Int.Storage", + moduleReexportName = ModuleName + "Torch.Int.Storage"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Float", + moduleReexportName = ModuleName + "Torch.Float"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Float.Dynamic", + moduleReexportName = ModuleName + "Torch.Float.Dynamic"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Float.Storage", + moduleReexportName = ModuleName + "Torch.Float.Storage"}], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = Nothing}, + CondBranch { + condBranchCondition = + `Var (PackageFlag (FlagName "cuda"))`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [ + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Cuda.Long", + moduleReexportName = ModuleName + "Torch.Cuda.Long"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Long.Dynamic", + moduleReexportName = ModuleName + "Torch.Cuda.Long.Dynamic"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Long.Storage", + moduleReexportName = ModuleName + "Torch.Cuda.Long.Storage"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Cuda.Double", + moduleReexportName = ModuleName + "Torch.Cuda.Double"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.Dynamic", + moduleReexportName = ModuleName + "Torch.Cuda.Double.Dynamic"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.Storage", + moduleReexportName = ModuleName + "Torch.Cuda.Double.Storage"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Activation", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Activation"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Backprop", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Backprop"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Conv1d", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Conv1d"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Conv2d", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Conv2d"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Criterion", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Criterion"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Layers", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Layers"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Linear", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Linear"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Math", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Math"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Padding", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Padding"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Pooling", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Pooling"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Sampling", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Sampling"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.Dynamic.NN", + moduleReexportName = ModuleName + "Torch.Cuda.Double.Dynamic.NN"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.Dynamic.NN.Activation", + moduleReexportName = ModuleName + "Torch.Cuda.Double.Dynamic.NN.Activation"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.Dynamic.NN.Pooling", + moduleReexportName = ModuleName + "Torch.Cuda.Double.Dynamic.NN.Pooling"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.Dynamic.NN.Criterion", + moduleReexportName = ModuleName + "Torch.Cuda.Double.Dynamic.NN.Criterion"}], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "hasktorch-gpu")]))], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "hasktorch-gpu")]))], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `CNot (Var (PackageFlag (FlagName "lite")))`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [ + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Cuda.Byte", + moduleReexportName = ModuleName + "Torch.Cuda.Byte"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Byte.Dynamic", + moduleReexportName = ModuleName + "Torch.Cuda.Byte.Dynamic"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Byte.Storage", + moduleReexportName = ModuleName + "Torch.Cuda.Byte.Storage"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Cuda.Char", + moduleReexportName = ModuleName + "Torch.Cuda.Char"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Char.Dynamic", + moduleReexportName = ModuleName + "Torch.Cuda.Char.Dynamic"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Char.Storage", + moduleReexportName = ModuleName + "Torch.Cuda.Char.Storage"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Cuda.Short", + moduleReexportName = ModuleName + "Torch.Cuda.Short"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Short.Dynamic", + moduleReexportName = ModuleName + "Torch.Cuda.Short.Dynamic"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Short.Storage", + moduleReexportName = ModuleName + "Torch.Cuda.Short.Storage"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Cuda.Int", + moduleReexportName = ModuleName + "Torch.Cuda.Int"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Int.Dynamic", + moduleReexportName = ModuleName + "Torch.Cuda.Int.Dynamic"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Int.Storage", + moduleReexportName = ModuleName + "Torch.Cuda.Int.Storage"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Cuda.Float", + moduleReexportName = ModuleName + "Torch.Cuda.Float"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Float.Dynamic", + moduleReexportName = ModuleName + "Torch.Cuda.Float.Dynamic"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Float.Storage", + moduleReexportName = ModuleName + "Torch.Cuda.Float.Storage"}], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}, + condBranchIfFalse = Nothing}]} diff --git a/Cabal-tests/tests/ParserTests/regressions/hasktorch.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/hasktorch.condSubLibraries.expr new file mode 100644 index 00000000000..1df86b8ffb6 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/hasktorch.condSubLibraries.expr @@ -0,0 +1,8425 @@ +[ + _×_ + (UnqualComponentName + "hasktorch-cpu") + CondNode { + condTreeData = + Library { + libName = LSubLibName + (UnqualComponentName + "hasktorch-cpu"), + exposedModules = [ + ModuleName "Torch.Long", + ModuleName "Torch.Long.Dynamic", + ModuleName "Torch.Long.Storage", + ModuleName "Torch.Double", + ModuleName + "Torch.Double.Dynamic", + ModuleName + "Torch.Double.Storage"], + reexportedModules = [ + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Double.NN", + moduleReexportName = ModuleName + "Torch.Double.NN"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Activation", + moduleReexportName = ModuleName + "Torch.Double.NN.Activation"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Backprop", + moduleReexportName = ModuleName + "Torch.Double.NN.Backprop"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Conv1d", + moduleReexportName = ModuleName + "Torch.Double.NN.Conv1d"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Conv2d", + moduleReexportName = ModuleName + "Torch.Double.NN.Conv2d"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Criterion", + moduleReexportName = ModuleName + "Torch.Double.NN.Criterion"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Layers", + moduleReexportName = ModuleName + "Torch.Double.NN.Layers"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Linear", + moduleReexportName = ModuleName + "Torch.Double.NN.Linear"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Math", + moduleReexportName = ModuleName + "Torch.Double.NN.Math"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Padding", + moduleReexportName = ModuleName + "Torch.Double.NN.Padding"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Pooling", + moduleReexportName = ModuleName + "Torch.Double.NN.Pooling"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.NN.Sampling", + moduleReexportName = ModuleName + "Torch.Double.NN.Sampling"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.Dynamic.NN", + moduleReexportName = ModuleName + "Torch.Double.Dynamic.NN"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.Dynamic.NN.Activation", + moduleReexportName = ModuleName + "Torch.Double.Dynamic.NN.Activation"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.Dynamic.NN.Pooling", + moduleReexportName = ModuleName + "Torch.Double.Dynamic.NN.Pooling"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Double.Dynamic.NN.Criterion", + moduleReexportName = ModuleName + "Torch.Double.Dynamic.NN.Criterion"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Float.NN", + moduleReexportName = ModuleName + "Torch.Float.NN"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Float.NN.Activation", + moduleReexportName = ModuleName + "Torch.Float.NN.Activation"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Float.NN.Backprop", + moduleReexportName = ModuleName + "Torch.Float.NN.Backprop"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Float.NN.Conv1d", + moduleReexportName = ModuleName + "Torch.Float.NN.Conv1d"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Float.NN.Conv2d", + moduleReexportName = ModuleName + "Torch.Float.NN.Conv2d"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Float.NN.Criterion", + moduleReexportName = ModuleName + "Torch.Float.NN.Criterion"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Float.NN.Layers", + moduleReexportName = ModuleName + "Torch.Float.NN.Layers"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Float.NN.Linear", + moduleReexportName = ModuleName + "Torch.Float.NN.Linear"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Float.NN.Math", + moduleReexportName = ModuleName + "Torch.Float.NN.Math"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Float.NN.Padding", + moduleReexportName = ModuleName + "Torch.Float.NN.Padding"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Float.NN.Pooling", + moduleReexportName = ModuleName + "Torch.Float.NN.Pooling"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Float.NN.Sampling", + moduleReexportName = ModuleName + "Torch.Float.NN.Sampling"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Float.Dynamic.NN", + moduleReexportName = ModuleName + "Torch.Float.Dynamic.NN"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Float.Dynamic.NN.Activation", + moduleReexportName = ModuleName + "Torch.Float.Dynamic.NN.Activation"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Float.Dynamic.NN.Pooling", + moduleReexportName = ModuleName + "Torch.Float.Dynamic.NN.Pooling"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Float.Dynamic.NN.Criterion", + moduleReexportName = ModuleName + "Torch.Float.Dynamic.NN.Criterion"}], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPrivate, + libBuildInfo = + BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "utils", + SymbolicPath "src"], + otherModules = [ + ModuleName + "Torch.Core.Exceptions", + ModuleName "Torch.Core.Random", + ModuleName "Torch.Core.LogAdd"], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [ + EnableExtension LambdaCase, + EnableExtension DataKinds, + EnableExtension TypeFamilies, + EnableExtension + TypeSynonymInstances, + EnableExtension + ScopedTypeVariables, + EnableExtension + FlexibleContexts, + EnableExtension CPP], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName + "hasktorch-types-th") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet, + Dependency + (PackageName "dimensions") + (UnionVersionRanges + (ThisVersion (mkVersion [1, 0])) + (LaterVersion + (mkVersion [1, 0]))) + mainLibSet, + Dependency + (PackageName "hasktorch-ffi-th") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet, + Dependency + (PackageName + "hasktorch-types-th") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet, + Dependency + (PackageName "safe-exceptions") + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 1, 0])) + (LaterVersion + (mkVersion [0, 1, 0]))) + mainLibSet, + Dependency + (PackageName "singletons") + (UnionVersionRanges + (ThisVersion (mkVersion [2, 2])) + (LaterVersion + (mkVersion [2, 2]))) + mainLibSet, + Dependency + (PackageName "text") + (UnionVersionRanges + (ThisVersion + (mkVersion [1, 2, 2])) + (LaterVersion + (mkVersion [1, 2, 2]))) + mainLibSet, + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "hasktorch-indef-floating")])), + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "hasktorch-indef-signed")]))], + mixins = + [ + Mixin { + mixinPackageName = PackageName + "hasktorch", + mixinLibraryName = LSubLibName + (UnqualComponentName + "hasktorch-indef-signed"), + mixinIncludeRenaming = + IncludeRenaming { + includeProvidesRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Indef.Storage") + (ModuleName + "Torch.Indef.Long.Storage"), + _×_ + (ModuleName + "Torch.Indef.Storage.Copy") + (ModuleName + "Torch.Indef.Long.Storage.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor") + (ModuleName + "Torch.Indef.Long.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Copy") + (ModuleName + "Torch.Indef.Long.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Index") + (ModuleName + "Torch.Indef.Long.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Masked") + (ModuleName + "Torch.Indef.Long.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math") + (ModuleName + "Torch.Indef.Long.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Long.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Long.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Long.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Long.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Long.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Long.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Mode") + (ModuleName + "Torch.Indef.Long.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Long.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Sort") + (ModuleName + "Torch.Indef.Long.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.TopK") + (ModuleName + "Torch.Indef.Long.Tensor.TopK"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor") + (ModuleName + "Torch.Indef.Long.Dynamic.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Copy") + (ModuleName + "Torch.Indef.Long.Dynamic.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Index") + (ModuleName + "Torch.Indef.Long.Dynamic.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Masked") + (ModuleName + "Torch.Indef.Long.Dynamic.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math") + (ModuleName + "Torch.Indef.Long.Dynamic.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Long.Dynamic.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Long.Dynamic.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Long.Dynamic.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Long.Dynamic.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Long.Dynamic.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Long.Dynamic.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Mode") + (ModuleName + "Torch.Indef.Long.Dynamic.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Long.Dynamic.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Sort") + (ModuleName + "Torch.Indef.Long.Dynamic.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.TopK") + (ModuleName + "Torch.Indef.Long.Dynamic.Tensor.TopK"), + _×_ + (ModuleName "Torch.Indef.Types") + (ModuleName "Torch.Long.Types"), + _×_ + (ModuleName "Torch.Indef.Index") + (ModuleName "Torch.Long.Index"), + _×_ + (ModuleName "Torch.Indef.Mask") + (ModuleName "Torch.Long.Mask"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Long.Tensor.Math.Pointwise.Signed"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Long.Dynamic.Tensor.Math.Pointwise.Signed")], + includeRequiresRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Sig.Index.Tensor") + (ModuleName + "Torch.FFI.TH.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Index.TensorFree") + (ModuleName + "Torch.FFI.TH.Long.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.Tensor") + (ModuleName + "Torch.FFI.TH.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.TensorFree") + (ModuleName + "Torch.FFI.TH.Byte.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.MathReduce") + (ModuleName + "Torch.FFI.TH.Byte.TensorMath"), + _×_ + (ModuleName "Torch.Sig.State") + (ModuleName "Torch.Types.TH"), + _×_ + (ModuleName + "Torch.Sig.Types.Global") + (ModuleName "Torch.Types.TH"), + _×_ + (ModuleName "Torch.Sig.Types") + (ModuleName + "Torch.Types.TH.Long"), + _×_ + (ModuleName "Torch.Sig.Storage") + (ModuleName + "Torch.FFI.TH.Long.Storage"), + _×_ + (ModuleName + "Torch.Sig.Storage.Copy") + (ModuleName + "Torch.FFI.TH.Long.StorageCopy"), + _×_ + (ModuleName + "Torch.Sig.Storage.Memory") + (ModuleName + "Torch.FFI.TH.Long.FreeStorage"), + _×_ + (ModuleName "Torch.Sig.Tensor") + (ModuleName + "Torch.FFI.TH.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Copy") + (ModuleName + "Torch.FFI.TH.Long.TensorCopy"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Memory") + (ModuleName + "Torch.FFI.TH.Long.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Index") + (ModuleName + "Torch.FFI.TH.Long.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Masked") + (ModuleName + "Torch.FFI.TH.Long.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math") + (ModuleName + "Torch.FFI.TH.Long.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Compare") + (ModuleName + "Torch.FFI.TH.Long.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.CompareT") + (ModuleName + "Torch.FFI.TH.Long.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pairwise") + (ModuleName + "Torch.FFI.TH.Long.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise") + (ModuleName + "Torch.FFI.TH.Long.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Reduce") + (ModuleName + "Torch.FFI.TH.Long.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Scan") + (ModuleName + "Torch.FFI.TH.Long.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Mode") + (ModuleName + "Torch.FFI.TH.Long.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.ScatterGather") + (ModuleName + "Torch.FFI.TH.Long.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Sort") + (ModuleName + "Torch.FFI.TH.Long.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.TopK") + (ModuleName + "Torch.FFI.TH.Long.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.FFI.TH.Long.TensorMath")]}}, + Mixin { + mixinPackageName = PackageName + "hasktorch", + mixinLibraryName = LSubLibName + (UnqualComponentName + "hasktorch-indef-floating"), + mixinIncludeRenaming = + IncludeRenaming { + includeProvidesRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Indef.Storage") + (ModuleName + "Torch.Indef.Double.Storage"), + _×_ + (ModuleName + "Torch.Indef.Storage.Copy") + (ModuleName + "Torch.Indef.Double.Storage.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor") + (ModuleName + "Torch.Indef.Double.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Copy") + (ModuleName + "Torch.Indef.Double.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Index") + (ModuleName + "Torch.Indef.Double.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Masked") + (ModuleName + "Torch.Indef.Double.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math") + (ModuleName + "Torch.Indef.Double.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Double.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Double.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Double.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Double.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Double.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Double.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Mode") + (ModuleName + "Torch.Indef.Double.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Double.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Sort") + (ModuleName + "Torch.Indef.Double.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.TopK") + (ModuleName + "Torch.Indef.Double.Tensor.TopK"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Copy") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Index") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Masked") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Mode") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Sort") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.TopK") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.TopK"), + _×_ + (ModuleName "Torch.Indef.Types") + (ModuleName + "Torch.Double.Types"), + _×_ + (ModuleName "Torch.Indef.Index") + (ModuleName + "Torch.Double.Index"), + _×_ + (ModuleName "Torch.Indef.Mask") + (ModuleName + "Torch.Double.Mask"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Double.Tensor.Math.Pointwise.Signed"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math.Pointwise.Signed"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Blas") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math.Blas"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Lapack") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math.Lapack"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Floating") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math.Pointwise.Floating"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce.Floating") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math.Reduce.Floating"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Floating") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math.Floating"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Blas") + (ModuleName + "Torch.Indef.Double.Tensor.Math.Blas"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Lapack") + (ModuleName + "Torch.Indef.Double.Tensor.Math.Lapack"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Floating") + (ModuleName + "Torch.Indef.Double.Tensor.Math.Pointwise.Floating"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce.Floating") + (ModuleName + "Torch.Indef.Double.Tensor.Math.Reduce.Floating"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Floating") + (ModuleName + "Torch.Indef.Double.Tensor.Math.Floating"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Random.TH") + (ModuleName + "Torch.Indef.Double.Tensor.Random.TH"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Random.TH") + (ModuleName + "Torch.Indef.Double.Tensor.Math.Random.TH"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Random.TH") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Random.TH"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Random.TH") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math.Random.TH"), + _×_ + (ModuleName + "Torch.Undefined.Tensor.Random.THC") + (ModuleName + "Torch.Undefined.Double.Tensor.Random.THC"), + _×_ + (ModuleName + "Torch.Indef.Storage") + (ModuleName + "Torch.Indef.Double.Storage"), + _×_ + (ModuleName + "Torch.Indef.Storage.Copy") + (ModuleName + "Torch.Indef.Double.Storage.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor") + (ModuleName + "Torch.Indef.Double.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Copy") + (ModuleName + "Torch.Indef.Double.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Index") + (ModuleName + "Torch.Indef.Double.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Masked") + (ModuleName + "Torch.Indef.Double.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math") + (ModuleName + "Torch.Indef.Double.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Double.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Double.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Double.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Double.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Double.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Double.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Mode") + (ModuleName + "Torch.Indef.Double.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Double.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Sort") + (ModuleName + "Torch.Indef.Double.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.TopK") + (ModuleName + "Torch.Indef.Double.Tensor.TopK"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Copy") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Index") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Masked") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Mode") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Sort") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.TopK") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.TopK"), + _×_ + (ModuleName "Torch.Indef.Types") + (ModuleName + "Torch.Double.Types"), + _×_ + (ModuleName "Torch.Indef.Index") + (ModuleName + "Torch.Double.Index"), + _×_ + (ModuleName "Torch.Indef.Mask") + (ModuleName + "Torch.Double.Mask"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Double.Tensor.Math.Pointwise.Signed"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Double.Dynamic.Tensor.Math.Pointwise.Signed"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.NN") + (ModuleName + "Torch.Double.Dynamic.NN"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.NN.Activation") + (ModuleName + "Torch.Double.Dynamic.NN.Activation"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.NN.Pooling") + (ModuleName + "Torch.Double.Dynamic.NN.Pooling"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.NN.Criterion") + (ModuleName + "Torch.Double.Dynamic.NN.Criterion"), + _×_ + (ModuleName + "Torch.Indef.Static.NN") + (ModuleName "Torch.Double.NN"), + _×_ + (ModuleName + "Torch.Indef.Static.NN") + (ModuleName "Torch.Double.NN"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Activation") + (ModuleName + "Torch.Double.NN.Activation"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Backprop") + (ModuleName + "Torch.Double.NN.Backprop"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Conv1d") + (ModuleName + "Torch.Double.NN.Conv1d"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Conv2d") + (ModuleName + "Torch.Double.NN.Conv2d"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Criterion") + (ModuleName + "Torch.Double.NN.Criterion"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Layers") + (ModuleName + "Torch.Double.NN.Layers"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Linear") + (ModuleName + "Torch.Double.NN.Linear"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Math") + (ModuleName + "Torch.Double.NN.Math"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Padding") + (ModuleName + "Torch.Double.NN.Padding"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Pooling") + (ModuleName + "Torch.Double.NN.Pooling"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Sampling") + (ModuleName + "Torch.Double.NN.Sampling")], + includeRequiresRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Sig.Index.Tensor") + (ModuleName + "Torch.FFI.TH.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Index.TensorFree") + (ModuleName + "Torch.FFI.TH.Long.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.Tensor") + (ModuleName + "Torch.FFI.TH.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.TensorFree") + (ModuleName + "Torch.FFI.TH.Byte.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.MathReduce") + (ModuleName + "Torch.FFI.TH.Byte.TensorMath"), + _×_ + (ModuleName "Torch.Sig.State") + (ModuleName "Torch.Types.TH"), + _×_ + (ModuleName + "Torch.Sig.Types.Global") + (ModuleName "Torch.Types.TH"), + _×_ + (ModuleName "Torch.Sig.Types") + (ModuleName + "Torch.Types.TH.Double"), + _×_ + (ModuleName "Torch.Sig.Storage") + (ModuleName + "Torch.FFI.TH.Double.Storage"), + _×_ + (ModuleName + "Torch.Sig.Storage.Copy") + (ModuleName + "Torch.FFI.TH.Double.StorageCopy"), + _×_ + (ModuleName + "Torch.Sig.Storage.Memory") + (ModuleName + "Torch.FFI.TH.Double.FreeStorage"), + _×_ + (ModuleName "Torch.Sig.Tensor") + (ModuleName + "Torch.FFI.TH.Double.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Copy") + (ModuleName + "Torch.FFI.TH.Double.TensorCopy"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Memory") + (ModuleName + "Torch.FFI.TH.Double.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Index") + (ModuleName + "Torch.FFI.TH.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Masked") + (ModuleName + "Torch.FFI.TH.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math") + (ModuleName + "Torch.FFI.TH.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Compare") + (ModuleName + "Torch.FFI.TH.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.CompareT") + (ModuleName + "Torch.FFI.TH.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pairwise") + (ModuleName + "Torch.FFI.TH.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise") + (ModuleName + "Torch.FFI.TH.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Reduce") + (ModuleName + "Torch.FFI.TH.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Scan") + (ModuleName + "Torch.FFI.TH.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Mode") + (ModuleName + "Torch.FFI.TH.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.ScatterGather") + (ModuleName + "Torch.FFI.TH.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Sort") + (ModuleName + "Torch.FFI.TH.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.TopK") + (ModuleName + "Torch.FFI.TH.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.FFI.TH.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise.Floating") + (ModuleName + "Torch.FFI.TH.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Reduce.Floating") + (ModuleName + "Torch.FFI.TH.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Floating") + (ModuleName + "Torch.FFI.TH.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Blas") + (ModuleName + "Torch.FFI.TH.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Lapack") + (ModuleName + "Torch.FFI.TH.Double.TensorLapack"), + _×_ + (ModuleName "Torch.Sig.NN") + (ModuleName + "Torch.FFI.TH.NN.Double"), + _×_ + (ModuleName + "Torch.Sig.Types.NN") + (ModuleName "Torch.Types.TH"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Random.TH") + (ModuleName + "Torch.FFI.TH.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Random.TH") + (ModuleName + "Torch.FFI.TH.Double.TensorRandom"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Random.THC") + (ModuleName + "Torch.Undefined.Double.Tensor.Random.THC")]}}]}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName + "hasktorch-types-th") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet, + Dependency + (PackageName "dimensions") + (UnionVersionRanges + (ThisVersion (mkVersion [1, 0])) + (LaterVersion + (mkVersion [1, 0]))) + mainLibSet, + Dependency + (PackageName "hasktorch-ffi-th") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet, + Dependency + (PackageName + "hasktorch-types-th") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet, + Dependency + (PackageName "safe-exceptions") + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 1, 0])) + (LaterVersion + (mkVersion [0, 1, 0]))) + mainLibSet, + Dependency + (PackageName "singletons") + (UnionVersionRanges + (ThisVersion (mkVersion [2, 2])) + (LaterVersion + (mkVersion [2, 2]))) + mainLibSet, + Dependency + (PackageName "text") + (UnionVersionRanges + (ThisVersion + (mkVersion [1, 2, 2])) + (LaterVersion + (mkVersion [1, 2, 2]))) + mainLibSet, + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "hasktorch-indef-floating")])), + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "hasktorch-indef-signed")]))], + condTreeComponents = + [ + CondBranch { + condBranchCondition = + `Var (PackageFlag (FlagName "lite"))`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LSubLibName + (UnqualComponentName + "hasktorch-cpu"), + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPrivate, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = + Just + CondNode { + condTreeData = + Library { + libName = LSubLibName + (UnqualComponentName + "hasktorch-cpu"), + exposedModules = [ + ModuleName "Torch.Byte", + ModuleName "Torch.Byte.Dynamic", + ModuleName "Torch.Byte.Storage", + ModuleName "Torch.Char", + ModuleName "Torch.Char.Dynamic", + ModuleName "Torch.Char.Storage", + ModuleName "Torch.Short", + ModuleName + "Torch.Short.Dynamic", + ModuleName + "Torch.Short.Storage", + ModuleName "Torch.Int", + ModuleName "Torch.Int.Dynamic", + ModuleName "Torch.Int.Storage", + ModuleName "Torch.Float", + ModuleName + "Torch.Float.Dynamic", + ModuleName + "Torch.Float.Storage"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPrivate, + libBuildInfo = + BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "hasktorch-indef-unsigned")]))], + mixins = + [ + Mixin { + mixinPackageName = PackageName + "hasktorch", + mixinLibraryName = LSubLibName + (UnqualComponentName + "hasktorch-indef-unsigned"), + mixinIncludeRenaming = + IncludeRenaming { + includeProvidesRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Indef.Storage") + (ModuleName + "Torch.Indef.Byte.Storage"), + _×_ + (ModuleName + "Torch.Indef.Storage.Copy") + (ModuleName + "Torch.Indef.Byte.Storage.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor") + (ModuleName + "Torch.Indef.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Copy") + (ModuleName + "Torch.Indef.Byte.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Index") + (ModuleName + "Torch.Indef.Byte.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Masked") + (ModuleName + "Torch.Indef.Byte.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math") + (ModuleName + "Torch.Indef.Byte.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Byte.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Byte.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Byte.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Byte.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Byte.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Byte.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Mode") + (ModuleName + "Torch.Indef.Byte.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Byte.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Sort") + (ModuleName + "Torch.Indef.Byte.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.TopK") + (ModuleName + "Torch.Indef.Byte.Tensor.TopK"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor") + (ModuleName + "Torch.Indef.Byte.Dynamic.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Copy") + (ModuleName + "Torch.Indef.Byte.Dynamic.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Index") + (ModuleName + "Torch.Indef.Byte.Dynamic.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Masked") + (ModuleName + "Torch.Indef.Byte.Dynamic.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math") + (ModuleName + "Torch.Indef.Byte.Dynamic.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Byte.Dynamic.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Byte.Dynamic.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Byte.Dynamic.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Byte.Dynamic.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Byte.Dynamic.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Byte.Dynamic.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Mode") + (ModuleName + "Torch.Indef.Byte.Dynamic.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Byte.Dynamic.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Sort") + (ModuleName + "Torch.Indef.Byte.Dynamic.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.TopK") + (ModuleName + "Torch.Indef.Byte.Dynamic.Tensor.TopK"), + _×_ + (ModuleName "Torch.Indef.Types") + (ModuleName "Torch.Byte.Types"), + _×_ + (ModuleName "Torch.Indef.Index") + (ModuleName "Torch.Byte.Index"), + _×_ + (ModuleName "Torch.Indef.Mask") + (ModuleName "Torch.Byte.Mask")], + includeRequiresRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Sig.Index.Tensor") + (ModuleName + "Torch.FFI.TH.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Index.TensorFree") + (ModuleName + "Torch.FFI.TH.Long.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.Tensor") + (ModuleName + "Torch.FFI.TH.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.TensorFree") + (ModuleName + "Torch.FFI.TH.Byte.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.MathReduce") + (ModuleName + "Torch.FFI.TH.Byte.TensorMath"), + _×_ + (ModuleName "Torch.Sig.State") + (ModuleName "Torch.Types.TH"), + _×_ + (ModuleName + "Torch.Sig.Types.Global") + (ModuleName "Torch.Types.TH"), + _×_ + (ModuleName "Torch.Sig.Types") + (ModuleName + "Torch.Types.TH.Byte"), + _×_ + (ModuleName "Torch.Sig.Storage") + (ModuleName + "Torch.FFI.TH.Byte.Storage"), + _×_ + (ModuleName + "Torch.Sig.Storage.Copy") + (ModuleName + "Torch.FFI.TH.Byte.StorageCopy"), + _×_ + (ModuleName + "Torch.Sig.Storage.Memory") + (ModuleName + "Torch.FFI.TH.Byte.FreeStorage"), + _×_ + (ModuleName "Torch.Sig.Tensor") + (ModuleName + "Torch.FFI.TH.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Copy") + (ModuleName + "Torch.FFI.TH.Byte.TensorCopy"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Memory") + (ModuleName + "Torch.FFI.TH.Byte.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Index") + (ModuleName + "Torch.FFI.TH.Byte.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Masked") + (ModuleName + "Torch.FFI.TH.Byte.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math") + (ModuleName + "Torch.FFI.TH.Byte.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Compare") + (ModuleName + "Torch.FFI.TH.Byte.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.CompareT") + (ModuleName + "Torch.FFI.TH.Byte.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pairwise") + (ModuleName + "Torch.FFI.TH.Byte.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise") + (ModuleName + "Torch.FFI.TH.Byte.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Reduce") + (ModuleName + "Torch.FFI.TH.Byte.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Scan") + (ModuleName + "Torch.FFI.TH.Byte.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Mode") + (ModuleName + "Torch.FFI.TH.Byte.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.ScatterGather") + (ModuleName + "Torch.FFI.TH.Byte.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Sort") + (ModuleName + "Torch.FFI.TH.Byte.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.TopK") + (ModuleName + "Torch.FFI.TH.Byte.TensorMath")]}}, + Mixin { + mixinPackageName = PackageName + "hasktorch", + mixinLibraryName = LSubLibName + (UnqualComponentName + "hasktorch-indef-unsigned"), + mixinIncludeRenaming = + IncludeRenaming { + includeProvidesRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Indef.Storage") + (ModuleName + "Torch.Indef.Char.Storage"), + _×_ + (ModuleName + "Torch.Indef.Storage.Copy") + (ModuleName + "Torch.Indef.Char.Storage.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor") + (ModuleName + "Torch.Indef.Char.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Copy") + (ModuleName + "Torch.Indef.Char.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Index") + (ModuleName + "Torch.Indef.Char.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Masked") + (ModuleName + "Torch.Indef.Char.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math") + (ModuleName + "Torch.Indef.Char.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Char.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Char.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Char.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Char.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Char.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Char.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Mode") + (ModuleName + "Torch.Indef.Char.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Char.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Sort") + (ModuleName + "Torch.Indef.Char.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.TopK") + (ModuleName + "Torch.Indef.Char.Tensor.TopK"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor") + (ModuleName + "Torch.Indef.Char.Dynamic.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Copy") + (ModuleName + "Torch.Indef.Char.Dynamic.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Index") + (ModuleName + "Torch.Indef.Char.Dynamic.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Masked") + (ModuleName + "Torch.Indef.Char.Dynamic.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math") + (ModuleName + "Torch.Indef.Char.Dynamic.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Char.Dynamic.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Char.Dynamic.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Char.Dynamic.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Char.Dynamic.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Char.Dynamic.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Char.Dynamic.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Mode") + (ModuleName + "Torch.Indef.Char.Dynamic.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Char.Dynamic.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Sort") + (ModuleName + "Torch.Indef.Char.Dynamic.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.TopK") + (ModuleName + "Torch.Indef.Char.Dynamic.Tensor.TopK"), + _×_ + (ModuleName "Torch.Indef.Types") + (ModuleName "Torch.Char.Types"), + _×_ + (ModuleName "Torch.Indef.Index") + (ModuleName "Torch.Char.Index"), + _×_ + (ModuleName "Torch.Indef.Mask") + (ModuleName "Torch.Char.Mask")], + includeRequiresRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Sig.Index.Tensor") + (ModuleName + "Torch.FFI.TH.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Index.TensorFree") + (ModuleName + "Torch.FFI.TH.Long.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.Tensor") + (ModuleName + "Torch.FFI.TH.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.TensorFree") + (ModuleName + "Torch.FFI.TH.Byte.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.MathReduce") + (ModuleName + "Torch.FFI.TH.Byte.TensorMath"), + _×_ + (ModuleName "Torch.Sig.State") + (ModuleName "Torch.Types.TH"), + _×_ + (ModuleName + "Torch.Sig.Types.Global") + (ModuleName "Torch.Types.TH"), + _×_ + (ModuleName "Torch.Sig.Types") + (ModuleName + "Torch.Types.TH.Char"), + _×_ + (ModuleName "Torch.Sig.Storage") + (ModuleName + "Torch.FFI.TH.Char.Storage"), + _×_ + (ModuleName + "Torch.Sig.Storage.Copy") + (ModuleName + "Torch.FFI.TH.Char.StorageCopy"), + _×_ + (ModuleName + "Torch.Sig.Storage.Memory") + (ModuleName + "Torch.FFI.TH.Char.FreeStorage"), + _×_ + (ModuleName "Torch.Sig.Tensor") + (ModuleName + "Torch.FFI.TH.Char.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Copy") + (ModuleName + "Torch.FFI.TH.Char.TensorCopy"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Memory") + (ModuleName + "Torch.FFI.TH.Char.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Index") + (ModuleName + "Torch.FFI.TH.Char.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Masked") + (ModuleName + "Torch.FFI.TH.Char.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math") + (ModuleName + "Torch.FFI.TH.Char.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Compare") + (ModuleName + "Torch.FFI.TH.Char.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.CompareT") + (ModuleName + "Torch.FFI.TH.Char.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pairwise") + (ModuleName + "Torch.FFI.TH.Char.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise") + (ModuleName + "Torch.FFI.TH.Char.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Reduce") + (ModuleName + "Torch.FFI.TH.Char.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Scan") + (ModuleName + "Torch.FFI.TH.Char.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Mode") + (ModuleName + "Torch.FFI.TH.Char.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.ScatterGather") + (ModuleName + "Torch.FFI.TH.Char.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Sort") + (ModuleName + "Torch.FFI.TH.Char.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.TopK") + (ModuleName + "Torch.FFI.TH.Char.TensorMath")]}}, + Mixin { + mixinPackageName = PackageName + "hasktorch", + mixinLibraryName = LSubLibName + (UnqualComponentName + "hasktorch-indef-signed"), + mixinIncludeRenaming = + IncludeRenaming { + includeProvidesRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Indef.Storage") + (ModuleName + "Torch.Indef.Short.Storage"), + _×_ + (ModuleName + "Torch.Indef.Storage.Copy") + (ModuleName + "Torch.Indef.Short.Storage.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor") + (ModuleName + "Torch.Indef.Short.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Copy") + (ModuleName + "Torch.Indef.Short.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Index") + (ModuleName + "Torch.Indef.Short.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Masked") + (ModuleName + "Torch.Indef.Short.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math") + (ModuleName + "Torch.Indef.Short.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Short.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Short.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Short.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Short.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Short.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Short.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Mode") + (ModuleName + "Torch.Indef.Short.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Short.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Sort") + (ModuleName + "Torch.Indef.Short.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.TopK") + (ModuleName + "Torch.Indef.Short.Tensor.TopK"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor") + (ModuleName + "Torch.Indef.Short.Dynamic.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Copy") + (ModuleName + "Torch.Indef.Short.Dynamic.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Index") + (ModuleName + "Torch.Indef.Short.Dynamic.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Masked") + (ModuleName + "Torch.Indef.Short.Dynamic.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math") + (ModuleName + "Torch.Indef.Short.Dynamic.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Short.Dynamic.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Short.Dynamic.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Short.Dynamic.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Short.Dynamic.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Short.Dynamic.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Short.Dynamic.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Mode") + (ModuleName + "Torch.Indef.Short.Dynamic.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Short.Dynamic.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Sort") + (ModuleName + "Torch.Indef.Short.Dynamic.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.TopK") + (ModuleName + "Torch.Indef.Short.Dynamic.Tensor.TopK"), + _×_ + (ModuleName "Torch.Indef.Types") + (ModuleName + "Torch.Short.Types"), + _×_ + (ModuleName "Torch.Indef.Index") + (ModuleName + "Torch.Short.Index"), + _×_ + (ModuleName "Torch.Indef.Mask") + (ModuleName "Torch.Short.Mask"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Short.Tensor.Math.Pointwise.Signed"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Short.Dynamic.Tensor.Math.Pointwise.Signed")], + includeRequiresRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Sig.Index.Tensor") + (ModuleName + "Torch.FFI.TH.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Index.TensorFree") + (ModuleName + "Torch.FFI.TH.Long.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.Tensor") + (ModuleName + "Torch.FFI.TH.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.TensorFree") + (ModuleName + "Torch.FFI.TH.Byte.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.MathReduce") + (ModuleName + "Torch.FFI.TH.Byte.TensorMath"), + _×_ + (ModuleName "Torch.Sig.State") + (ModuleName "Torch.Types.TH"), + _×_ + (ModuleName + "Torch.Sig.Types.Global") + (ModuleName "Torch.Types.TH"), + _×_ + (ModuleName "Torch.Sig.Types") + (ModuleName + "Torch.Types.TH.Short"), + _×_ + (ModuleName "Torch.Sig.Storage") + (ModuleName + "Torch.FFI.TH.Short.Storage"), + _×_ + (ModuleName + "Torch.Sig.Storage.Copy") + (ModuleName + "Torch.FFI.TH.Short.StorageCopy"), + _×_ + (ModuleName + "Torch.Sig.Storage.Memory") + (ModuleName + "Torch.FFI.TH.Short.FreeStorage"), + _×_ + (ModuleName "Torch.Sig.Tensor") + (ModuleName + "Torch.FFI.TH.Short.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Copy") + (ModuleName + "Torch.FFI.TH.Short.TensorCopy"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Memory") + (ModuleName + "Torch.FFI.TH.Short.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Index") + (ModuleName + "Torch.FFI.TH.Short.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Masked") + (ModuleName + "Torch.FFI.TH.Short.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math") + (ModuleName + "Torch.FFI.TH.Short.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Compare") + (ModuleName + "Torch.FFI.TH.Short.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.CompareT") + (ModuleName + "Torch.FFI.TH.Short.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pairwise") + (ModuleName + "Torch.FFI.TH.Short.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise") + (ModuleName + "Torch.FFI.TH.Short.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Reduce") + (ModuleName + "Torch.FFI.TH.Short.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Scan") + (ModuleName + "Torch.FFI.TH.Short.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Mode") + (ModuleName + "Torch.FFI.TH.Short.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.ScatterGather") + (ModuleName + "Torch.FFI.TH.Short.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Sort") + (ModuleName + "Torch.FFI.TH.Short.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.TopK") + (ModuleName + "Torch.FFI.TH.Short.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.FFI.TH.Short.TensorMath")]}}, + Mixin { + mixinPackageName = PackageName + "hasktorch", + mixinLibraryName = LSubLibName + (UnqualComponentName + "hasktorch-indef-signed"), + mixinIncludeRenaming = + IncludeRenaming { + includeProvidesRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Indef.Storage") + (ModuleName + "Torch.Indef.Int.Storage"), + _×_ + (ModuleName + "Torch.Indef.Storage.Copy") + (ModuleName + "Torch.Indef.Int.Storage.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor") + (ModuleName + "Torch.Indef.Int.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Copy") + (ModuleName + "Torch.Indef.Int.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Index") + (ModuleName + "Torch.Indef.Int.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Masked") + (ModuleName + "Torch.Indef.Int.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math") + (ModuleName + "Torch.Indef.Int.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Int.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Int.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Int.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Int.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Int.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Int.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Mode") + (ModuleName + "Torch.Indef.Int.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Int.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Sort") + (ModuleName + "Torch.Indef.Int.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.TopK") + (ModuleName + "Torch.Indef.Int.Tensor.TopK"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor") + (ModuleName + "Torch.Indef.Int.Dynamic.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Copy") + (ModuleName + "Torch.Indef.Int.Dynamic.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Index") + (ModuleName + "Torch.Indef.Int.Dynamic.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Masked") + (ModuleName + "Torch.Indef.Int.Dynamic.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math") + (ModuleName + "Torch.Indef.Int.Dynamic.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Int.Dynamic.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Int.Dynamic.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Int.Dynamic.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Int.Dynamic.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Int.Dynamic.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Int.Dynamic.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Mode") + (ModuleName + "Torch.Indef.Int.Dynamic.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Int.Dynamic.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Sort") + (ModuleName + "Torch.Indef.Int.Dynamic.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.TopK") + (ModuleName + "Torch.Indef.Int.Dynamic.Tensor.TopK"), + _×_ + (ModuleName "Torch.Indef.Types") + (ModuleName "Torch.Int.Types"), + _×_ + (ModuleName "Torch.Indef.Index") + (ModuleName "Torch.Int.Index"), + _×_ + (ModuleName "Torch.Indef.Mask") + (ModuleName "Torch.Int.Mask"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Int.Tensor.Math.Pointwise.Signed"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Int.Dynamic.Tensor.Math.Pointwise.Signed")], + includeRequiresRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Sig.Index.Tensor") + (ModuleName + "Torch.FFI.TH.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Index.TensorFree") + (ModuleName + "Torch.FFI.TH.Long.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.Tensor") + (ModuleName + "Torch.FFI.TH.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.TensorFree") + (ModuleName + "Torch.FFI.TH.Byte.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.MathReduce") + (ModuleName + "Torch.FFI.TH.Byte.TensorMath"), + _×_ + (ModuleName "Torch.Sig.State") + (ModuleName "Torch.Types.TH"), + _×_ + (ModuleName + "Torch.Sig.Types.Global") + (ModuleName "Torch.Types.TH"), + _×_ + (ModuleName "Torch.Sig.Types") + (ModuleName + "Torch.Types.TH.Int"), + _×_ + (ModuleName "Torch.Sig.Storage") + (ModuleName + "Torch.FFI.TH.Int.Storage"), + _×_ + (ModuleName + "Torch.Sig.Storage.Copy") + (ModuleName + "Torch.FFI.TH.Int.StorageCopy"), + _×_ + (ModuleName + "Torch.Sig.Storage.Memory") + (ModuleName + "Torch.FFI.TH.Int.FreeStorage"), + _×_ + (ModuleName "Torch.Sig.Tensor") + (ModuleName + "Torch.FFI.TH.Int.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Copy") + (ModuleName + "Torch.FFI.TH.Int.TensorCopy"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Memory") + (ModuleName + "Torch.FFI.TH.Int.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Index") + (ModuleName + "Torch.FFI.TH.Int.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Masked") + (ModuleName + "Torch.FFI.TH.Int.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math") + (ModuleName + "Torch.FFI.TH.Int.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Compare") + (ModuleName + "Torch.FFI.TH.Int.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.CompareT") + (ModuleName + "Torch.FFI.TH.Int.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pairwise") + (ModuleName + "Torch.FFI.TH.Int.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise") + (ModuleName + "Torch.FFI.TH.Int.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Reduce") + (ModuleName + "Torch.FFI.TH.Int.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Scan") + (ModuleName + "Torch.FFI.TH.Int.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Mode") + (ModuleName + "Torch.FFI.TH.Int.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.ScatterGather") + (ModuleName + "Torch.FFI.TH.Int.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Sort") + (ModuleName + "Torch.FFI.TH.Int.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.TopK") + (ModuleName + "Torch.FFI.TH.Int.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.FFI.TH.Int.TensorMath")]}}, + Mixin { + mixinPackageName = PackageName + "hasktorch", + mixinLibraryName = LSubLibName + (UnqualComponentName + "hasktorch-indef-floating"), + mixinIncludeRenaming = + IncludeRenaming { + includeProvidesRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Indef.Storage") + (ModuleName + "Torch.Indef.Float.Storage"), + _×_ + (ModuleName + "Torch.Indef.Storage.Copy") + (ModuleName + "Torch.Indef.Float.Storage.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor") + (ModuleName + "Torch.Indef.Float.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Copy") + (ModuleName + "Torch.Indef.Float.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Index") + (ModuleName + "Torch.Indef.Float.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Masked") + (ModuleName + "Torch.Indef.Float.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math") + (ModuleName + "Torch.Indef.Float.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Float.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Float.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Float.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Float.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Float.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Float.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Mode") + (ModuleName + "Torch.Indef.Float.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Float.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Sort") + (ModuleName + "Torch.Indef.Float.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.TopK") + (ModuleName + "Torch.Indef.Float.Tensor.TopK"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Copy") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Index") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Masked") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Mode") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Sort") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.TopK") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.TopK"), + _×_ + (ModuleName "Torch.Indef.Types") + (ModuleName + "Torch.Float.Types"), + _×_ + (ModuleName "Torch.Indef.Index") + (ModuleName + "Torch.Float.Index"), + _×_ + (ModuleName "Torch.Indef.Mask") + (ModuleName "Torch.Float.Mask"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Float.Tensor.Math.Pointwise.Signed"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math.Pointwise.Signed"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Blas") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math.Blas"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Lapack") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math.Lapack"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Floating") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math.Pointwise.Floating"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce.Floating") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math.Reduce.Floating"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Floating") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math.Floating"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Blas") + (ModuleName + "Torch.Indef.Float.Tensor.Math.Blas"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Lapack") + (ModuleName + "Torch.Indef.Float.Tensor.Math.Lapack"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Floating") + (ModuleName + "Torch.Indef.Float.Tensor.Math.Pointwise.Floating"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce.Floating") + (ModuleName + "Torch.Indef.Float.Tensor.Math.Reduce.Floating"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Floating") + (ModuleName + "Torch.Indef.Float.Tensor.Math.Floating"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Random.TH") + (ModuleName + "Torch.Indef.Float.Tensor.Random.TH"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Random.TH") + (ModuleName + "Torch.Indef.Float.Tensor.Math.Random.TH"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Random.TH") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Random.TH"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Random.TH") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math.Random.TH"), + _×_ + (ModuleName + "Torch.Undefined.Tensor.Random.THC") + (ModuleName + "Torch.Undefined.Float.Tensor.Random.THC"), + _×_ + (ModuleName + "Torch.Indef.Storage") + (ModuleName + "Torch.Indef.Float.Storage"), + _×_ + (ModuleName + "Torch.Indef.Storage.Copy") + (ModuleName + "Torch.Indef.Float.Storage.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor") + (ModuleName + "Torch.Indef.Float.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Copy") + (ModuleName + "Torch.Indef.Float.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Index") + (ModuleName + "Torch.Indef.Float.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Masked") + (ModuleName + "Torch.Indef.Float.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math") + (ModuleName + "Torch.Indef.Float.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Float.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Float.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Float.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Float.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Float.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Float.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Mode") + (ModuleName + "Torch.Indef.Float.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Float.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Sort") + (ModuleName + "Torch.Indef.Float.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.TopK") + (ModuleName + "Torch.Indef.Float.Tensor.TopK"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Copy") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Index") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Masked") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Mode") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Sort") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.TopK") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.TopK"), + _×_ + (ModuleName "Torch.Indef.Types") + (ModuleName + "Torch.Float.Types"), + _×_ + (ModuleName "Torch.Indef.Index") + (ModuleName + "Torch.Float.Index"), + _×_ + (ModuleName "Torch.Indef.Mask") + (ModuleName "Torch.Float.Mask"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Float.Tensor.Math.Pointwise.Signed"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Float.Dynamic.Tensor.Math.Pointwise.Signed"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.NN") + (ModuleName + "Torch.Float.Dynamic.NN"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.NN.Activation") + (ModuleName + "Torch.Float.Dynamic.NN.Activation"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.NN.Pooling") + (ModuleName + "Torch.Float.Dynamic.NN.Pooling"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.NN.Criterion") + (ModuleName + "Torch.Float.Dynamic.NN.Criterion"), + _×_ + (ModuleName + "Torch.Indef.Static.NN") + (ModuleName "Torch.Float.NN"), + _×_ + (ModuleName + "Torch.Indef.Static.NN") + (ModuleName "Torch.Float.NN"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Activation") + (ModuleName + "Torch.Float.NN.Activation"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Backprop") + (ModuleName + "Torch.Float.NN.Backprop"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Conv1d") + (ModuleName + "Torch.Float.NN.Conv1d"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Conv2d") + (ModuleName + "Torch.Float.NN.Conv2d"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Criterion") + (ModuleName + "Torch.Float.NN.Criterion"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Layers") + (ModuleName + "Torch.Float.NN.Layers"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Linear") + (ModuleName + "Torch.Float.NN.Linear"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Math") + (ModuleName + "Torch.Float.NN.Math"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Padding") + (ModuleName + "Torch.Float.NN.Padding"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Pooling") + (ModuleName + "Torch.Float.NN.Pooling"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Sampling") + (ModuleName + "Torch.Float.NN.Sampling")], + includeRequiresRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Sig.Index.Tensor") + (ModuleName + "Torch.FFI.TH.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Index.TensorFree") + (ModuleName + "Torch.FFI.TH.Long.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.Tensor") + (ModuleName + "Torch.FFI.TH.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.TensorFree") + (ModuleName + "Torch.FFI.TH.Byte.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.MathReduce") + (ModuleName + "Torch.FFI.TH.Byte.TensorMath"), + _×_ + (ModuleName "Torch.Sig.State") + (ModuleName "Torch.Types.TH"), + _×_ + (ModuleName + "Torch.Sig.Types.Global") + (ModuleName "Torch.Types.TH"), + _×_ + (ModuleName "Torch.Sig.Types") + (ModuleName + "Torch.Types.TH.Float"), + _×_ + (ModuleName "Torch.Sig.Storage") + (ModuleName + "Torch.FFI.TH.Float.Storage"), + _×_ + (ModuleName + "Torch.Sig.Storage.Copy") + (ModuleName + "Torch.FFI.TH.Float.StorageCopy"), + _×_ + (ModuleName + "Torch.Sig.Storage.Memory") + (ModuleName + "Torch.FFI.TH.Float.FreeStorage"), + _×_ + (ModuleName "Torch.Sig.Tensor") + (ModuleName + "Torch.FFI.TH.Float.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Copy") + (ModuleName + "Torch.FFI.TH.Float.TensorCopy"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Memory") + (ModuleName + "Torch.FFI.TH.Float.FreeTensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Index") + (ModuleName + "Torch.FFI.TH.Float.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Masked") + (ModuleName + "Torch.FFI.TH.Float.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math") + (ModuleName + "Torch.FFI.TH.Float.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Compare") + (ModuleName + "Torch.FFI.TH.Float.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.CompareT") + (ModuleName + "Torch.FFI.TH.Float.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pairwise") + (ModuleName + "Torch.FFI.TH.Float.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise") + (ModuleName + "Torch.FFI.TH.Float.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Reduce") + (ModuleName + "Torch.FFI.TH.Float.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Scan") + (ModuleName + "Torch.FFI.TH.Float.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Mode") + (ModuleName + "Torch.FFI.TH.Float.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.ScatterGather") + (ModuleName + "Torch.FFI.TH.Float.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Sort") + (ModuleName + "Torch.FFI.TH.Float.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.TopK") + (ModuleName + "Torch.FFI.TH.Float.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.FFI.TH.Float.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise.Floating") + (ModuleName + "Torch.FFI.TH.Float.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Reduce.Floating") + (ModuleName + "Torch.FFI.TH.Float.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Floating") + (ModuleName + "Torch.FFI.TH.Float.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Blas") + (ModuleName + "Torch.FFI.TH.Float.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Lapack") + (ModuleName + "Torch.FFI.TH.Float.TensorLapack"), + _×_ + (ModuleName "Torch.Sig.NN") + (ModuleName + "Torch.FFI.TH.NN.Float"), + _×_ + (ModuleName + "Torch.Sig.Types.NN") + (ModuleName "Torch.Types.TH"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Random.TH") + (ModuleName + "Torch.FFI.TH.Float.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Random.TH") + (ModuleName + "Torch.FFI.TH.Float.TensorRandom"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Random.THC") + (ModuleName + "Torch.Undefined.Float.Tensor.Random.THC")]}}]}}, + condTreeConstraints = [ + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "hasktorch-indef-unsigned")]))], + condTreeComponents = []}}]}, + _×_ + (UnqualComponentName + "hasktorch-gpu") + CondNode { + condTreeData = + Library { + libName = LSubLibName + (UnqualComponentName + "hasktorch-gpu"), + exposedModules = [ + ModuleName "Torch.Cuda.Long", + ModuleName + "Torch.Cuda.Long.Dynamic", + ModuleName + "Torch.Cuda.Long.Storage", + ModuleName "Torch.Cuda.Double", + ModuleName + "Torch.Cuda.Double.Dynamic", + ModuleName + "Torch.Cuda.Double.Storage"], + reexportedModules = [ + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Activation", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Activation"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Backprop", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Backprop"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Conv1d", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Conv1d"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Conv2d", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Conv2d"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Criterion", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Criterion"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Layers", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Layers"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Linear", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Linear"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Math", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Math"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Padding", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Padding"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Pooling", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Pooling"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.NN.Sampling", + moduleReexportName = ModuleName + "Torch.Cuda.Double.NN.Sampling"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.Dynamic.NN", + moduleReexportName = ModuleName + "Torch.Cuda.Double.Dynamic.NN"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.Dynamic.NN.Activation", + moduleReexportName = ModuleName + "Torch.Cuda.Double.Dynamic.NN.Activation"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.Dynamic.NN.Pooling", + moduleReexportName = ModuleName + "Torch.Cuda.Double.Dynamic.NN.Pooling"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Cuda.Double.Dynamic.NN.Criterion", + moduleReexportName = ModuleName + "Torch.Cuda.Double.Dynamic.NN.Criterion"}], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPrivate, + libBuildInfo = + BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [ + "-DCUDA", + "-DHASKTORCH_INTERNAL_CUDA"], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "utils", + SymbolicPath "src"], + otherModules = [ + ModuleName + "Torch.Core.Exceptions", + ModuleName "Torch.Core.Random", + ModuleName "Torch.Core.LogAdd"], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [ + EnableExtension LambdaCase, + EnableExtension DataKinds, + EnableExtension TypeFamilies, + EnableExtension + TypeSynonymInstances, + EnableExtension + ScopedTypeVariables, + EnableExtension + FlexibleContexts, + EnableExtension CPP], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName + "hasktorch-types-th") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet, + Dependency + (PackageName "dimensions") + (UnionVersionRanges + (ThisVersion (mkVersion [1, 0])) + (LaterVersion + (mkVersion [1, 0]))) + mainLibSet, + Dependency + (PackageName "hasktorch-ffi-th") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet, + Dependency + (PackageName + "hasktorch-types-th") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet, + Dependency + (PackageName "safe-exceptions") + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 1, 0])) + (LaterVersion + (mkVersion [0, 1, 0]))) + mainLibSet, + Dependency + (PackageName "singletons") + (UnionVersionRanges + (ThisVersion (mkVersion [2, 2])) + (LaterVersion + (mkVersion [2, 2]))) + mainLibSet, + Dependency + (PackageName "text") + (UnionVersionRanges + (ThisVersion + (mkVersion [1, 2, 2])) + (LaterVersion + (mkVersion [1, 2, 2]))) + mainLibSet, + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "hasktorch-indef-floating")])), + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "hasktorch-indef-signed")])), + Dependency + (PackageName + "hasktorch-ffi-thc") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet, + Dependency + (PackageName + "hasktorch-types-thc") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet], + mixins = + [ + Mixin { + mixinPackageName = PackageName + "hasktorch", + mixinLibraryName = LSubLibName + (UnqualComponentName + "hasktorch-indef-signed"), + mixinIncludeRenaming = + IncludeRenaming { + includeProvidesRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Indef.Storage") + (ModuleName + "Torch.Indef.Cuda.Long.Storage"), + _×_ + (ModuleName + "Torch.Indef.Storage.Copy") + (ModuleName + "Torch.Indef.Cuda.Long.Storage.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor") + (ModuleName + "Torch.Indef.Cuda.Long.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Copy") + (ModuleName + "Torch.Indef.Cuda.Long.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Index") + (ModuleName + "Torch.Indef.Cuda.Long.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Masked") + (ModuleName + "Torch.Indef.Cuda.Long.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math") + (ModuleName + "Torch.Indef.Cuda.Long.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Cuda.Long.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Cuda.Long.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Cuda.Long.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Cuda.Long.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Cuda.Long.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Cuda.Long.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Mode") + (ModuleName + "Torch.Indef.Cuda.Long.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Cuda.Long.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Sort") + (ModuleName + "Torch.Indef.Cuda.Long.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.TopK") + (ModuleName + "Torch.Indef.Cuda.Long.Tensor.TopK"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor") + (ModuleName + "Torch.Indef.Cuda.Long.Dynamic.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Copy") + (ModuleName + "Torch.Indef.Cuda.Long.Dynamic.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Index") + (ModuleName + "Torch.Indef.Cuda.Long.Dynamic.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Masked") + (ModuleName + "Torch.Indef.Cuda.Long.Dynamic.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math") + (ModuleName + "Torch.Indef.Cuda.Long.Dynamic.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Mode") + (ModuleName + "Torch.Indef.Cuda.Long.Dynamic.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Cuda.Long.Dynamic.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Sort") + (ModuleName + "Torch.Indef.Cuda.Long.Dynamic.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.TopK") + (ModuleName + "Torch.Indef.Cuda.Long.Dynamic.Tensor.TopK"), + _×_ + (ModuleName "Torch.Indef.Types") + (ModuleName + "Torch.Cuda.Long.Types"), + _×_ + (ModuleName "Torch.Indef.Index") + (ModuleName + "Torch.Cuda.Long.Index"), + _×_ + (ModuleName "Torch.Indef.Mask") + (ModuleName + "Torch.Cuda.Long.Mask"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Cuda.Long.Tensor.Math.Pointwise.Signed"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Pointwise.Signed")], + includeRequiresRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Sig.Index.Tensor") + (ModuleName + "Torch.FFI.THC.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Index.TensorFree") + (ModuleName + "Torch.FFI.THC.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.Tensor") + (ModuleName + "Torch.FFI.THC.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.TensorFree") + (ModuleName + "Torch.FFI.THC.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.MathReduce") + (ModuleName + "Torch.FFI.THC.Byte.TensorMathReduce"), + _×_ + (ModuleName "Torch.Sig.State") + (ModuleName + "Torch.FFI.THC.State"), + _×_ + (ModuleName + "Torch.Sig.Types.Global") + (ModuleName "Torch.Types.THC"), + _×_ + (ModuleName "Torch.Sig.Types") + (ModuleName + "Torch.Types.THC.Long"), + _×_ + (ModuleName "Torch.Sig.Storage") + (ModuleName + "Torch.FFI.THC.Long.Storage"), + _×_ + (ModuleName + "Torch.Sig.Storage.Copy") + (ModuleName + "Torch.FFI.THC.Long.StorageCopy"), + _×_ + (ModuleName + "Torch.Sig.Storage.Memory") + (ModuleName + "Torch.FFI.THC.Long.Storage"), + _×_ + (ModuleName "Torch.Sig.Tensor") + (ModuleName + "Torch.FFI.THC.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Copy") + (ModuleName + "Torch.FFI.THC.Long.TensorCopy"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Memory") + (ModuleName + "Torch.FFI.THC.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Index") + (ModuleName + "Torch.FFI.THC.Long.TensorIndex"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Masked") + (ModuleName + "Torch.FFI.THC.Long.TensorMasked"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math") + (ModuleName + "Torch.FFI.THC.Long.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Compare") + (ModuleName + "Torch.FFI.THC.Long.TensorMathCompare"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.CompareT") + (ModuleName + "Torch.FFI.THC.Long.TensorMathCompareT"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pairwise") + (ModuleName + "Torch.FFI.THC.Long.TensorMathPairwise"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise") + (ModuleName + "Torch.FFI.THC.Long.TensorMathPointwise"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Reduce") + (ModuleName + "Torch.FFI.THC.Long.TensorMathReduce"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Scan") + (ModuleName + "Torch.FFI.THC.Long.TensorMathScan"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Mode") + (ModuleName + "Torch.FFI.THC.Long.TensorMode"), + _×_ + (ModuleName + "Torch.Sig.Tensor.ScatterGather") + (ModuleName + "Torch.FFI.THC.Long.TensorScatterGather"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Sort") + (ModuleName + "Torch.FFI.THC.Long.TensorSort"), + _×_ + (ModuleName + "Torch.Sig.Tensor.TopK") + (ModuleName + "Torch.FFI.THC.Long.TensorTopK"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.FFI.THC.Long.TensorMathPointwise")]}}, + Mixin { + mixinPackageName = PackageName + "hasktorch", + mixinLibraryName = LSubLibName + (UnqualComponentName + "hasktorch-indef-floating"), + mixinIncludeRenaming = + IncludeRenaming { + includeProvidesRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Indef.Storage") + (ModuleName + "Torch.Indef.Cuda.Double.Storage"), + _×_ + (ModuleName + "Torch.Indef.Storage.Copy") + (ModuleName + "Torch.Indef.Cuda.Double.Storage.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Copy") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Index") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Masked") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Mode") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Sort") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.TopK") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.TopK"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Copy") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Index") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Masked") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Mode") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Sort") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.TopK") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.TopK"), + _×_ + (ModuleName "Torch.Indef.Types") + (ModuleName + "Torch.Cuda.Double.Types"), + _×_ + (ModuleName "Torch.Indef.Index") + (ModuleName + "Torch.Cuda.Double.Index"), + _×_ + (ModuleName "Torch.Indef.Mask") + (ModuleName + "Torch.Cuda.Double.Mask"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math.Pointwise.Signed"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pointwise.Signed"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Blas") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Blas"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Lapack") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Lapack"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Floating") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pointwise.Floating"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce.Floating") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Reduce.Floating"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Floating") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Floating"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Blas") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math.Blas"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Lapack") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math.Lapack"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Floating") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math.Pointwise.Floating"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce.Floating") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math.Reduce.Floating"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Floating") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math.Floating"), + _×_ + (ModuleName + "Torch.Undefined.Tensor.Random.TH") + (ModuleName + "Torch.Undefined.Cuda.Double.Tensor.Random.TH"), + _×_ + (ModuleName + "Torch.Undefined.Tensor.Math.Random.TH") + (ModuleName + "Torch.Undefined.Cuda.Double.Tensor.Math.Random.TH"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Random.THC") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Random.THC"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Random.THC") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Random.THC"), + _×_ + (ModuleName + "Torch.Indef.Storage") + (ModuleName + "Torch.Indef.Cuda.Double.Storage"), + _×_ + (ModuleName + "Torch.Indef.Storage.Copy") + (ModuleName + "Torch.Indef.Cuda.Double.Storage.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Copy") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Index") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Masked") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Mode") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Sort") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.TopK") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.TopK"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Copy") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Index") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Masked") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Mode") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Sort") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.TopK") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.TopK"), + _×_ + (ModuleName "Torch.Indef.Types") + (ModuleName + "Torch.Cuda.Double.Types"), + _×_ + (ModuleName "Torch.Indef.Index") + (ModuleName + "Torch.Cuda.Double.Index"), + _×_ + (ModuleName "Torch.Indef.Mask") + (ModuleName + "Torch.Cuda.Double.Mask"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Cuda.Double.Tensor.Math.Pointwise.Signed"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pointwise.Signed"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.NN") + (ModuleName + "Torch.Cuda.Double.Dynamic.NN"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.NN.Activation") + (ModuleName + "Torch.Cuda.Double.Dynamic.NN.Activation"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.NN.Pooling") + (ModuleName + "Torch.Cuda.Double.Dynamic.NN.Pooling"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.NN.Criterion") + (ModuleName + "Torch.Cuda.Double.Dynamic.NN.Criterion"), + _×_ + (ModuleName + "Torch.Indef.Static.NN") + (ModuleName + "Torch.Cuda.Double.NN"), + _×_ + (ModuleName + "Torch.Indef.Static.NN") + (ModuleName + "Torch.Cuda.Double.NN"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Activation") + (ModuleName + "Torch.Cuda.Double.NN.Activation"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Backprop") + (ModuleName + "Torch.Cuda.Double.NN.Backprop"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Conv1d") + (ModuleName + "Torch.Cuda.Double.NN.Conv1d"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Conv2d") + (ModuleName + "Torch.Cuda.Double.NN.Conv2d"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Criterion") + (ModuleName + "Torch.Cuda.Double.NN.Criterion"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Layers") + (ModuleName + "Torch.Cuda.Double.NN.Layers"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Linear") + (ModuleName + "Torch.Cuda.Double.NN.Linear"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Math") + (ModuleName + "Torch.Cuda.Double.NN.Math"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Padding") + (ModuleName + "Torch.Cuda.Double.NN.Padding"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Pooling") + (ModuleName + "Torch.Cuda.Double.NN.Pooling"), + _×_ + (ModuleName + "Torch.Indef.Static.NN.Sampling") + (ModuleName + "Torch.Cuda.Double.NN.Sampling")], + includeRequiresRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Sig.Index.Tensor") + (ModuleName + "Torch.FFI.THC.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Index.TensorFree") + (ModuleName + "Torch.FFI.THC.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.Tensor") + (ModuleName + "Torch.FFI.THC.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.TensorFree") + (ModuleName + "Torch.FFI.THC.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.MathReduce") + (ModuleName + "Torch.FFI.THC.Byte.TensorMathReduce"), + _×_ + (ModuleName "Torch.Sig.State") + (ModuleName + "Torch.FFI.THC.State"), + _×_ + (ModuleName + "Torch.Sig.Types.Global") + (ModuleName "Torch.Types.THC"), + _×_ + (ModuleName "Torch.Sig.Types") + (ModuleName + "Torch.Types.THC.Double"), + _×_ + (ModuleName "Torch.Sig.Storage") + (ModuleName + "Torch.FFI.THC.Double.Storage"), + _×_ + (ModuleName + "Torch.Sig.Storage.Copy") + (ModuleName + "Torch.FFI.THC.Double.StorageCopy"), + _×_ + (ModuleName + "Torch.Sig.Storage.Memory") + (ModuleName + "Torch.FFI.THC.Double.Storage"), + _×_ + (ModuleName "Torch.Sig.Tensor") + (ModuleName + "Torch.FFI.THC.Double.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Copy") + (ModuleName + "Torch.FFI.THC.Double.TensorCopy"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Memory") + (ModuleName + "Torch.FFI.THC.Double.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Index") + (ModuleName + "Torch.FFI.THC.Double.TensorIndex"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Masked") + (ModuleName + "Torch.FFI.THC.Double.TensorMasked"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math") + (ModuleName + "Torch.FFI.THC.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Compare") + (ModuleName + "Torch.FFI.THC.Double.TensorMathCompare"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.CompareT") + (ModuleName + "Torch.FFI.THC.Double.TensorMathCompareT"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pairwise") + (ModuleName + "Torch.FFI.THC.Double.TensorMathPairwise"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise") + (ModuleName + "Torch.FFI.THC.Double.TensorMathPointwise"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Reduce") + (ModuleName + "Torch.FFI.THC.Double.TensorMathReduce"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Scan") + (ModuleName + "Torch.FFI.THC.Double.TensorMathScan"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Mode") + (ModuleName + "Torch.FFI.THC.Double.TensorMode"), + _×_ + (ModuleName + "Torch.Sig.Tensor.ScatterGather") + (ModuleName + "Torch.FFI.THC.Double.TensorScatterGather"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Sort") + (ModuleName + "Torch.FFI.THC.Double.TensorSort"), + _×_ + (ModuleName + "Torch.Sig.Tensor.TopK") + (ModuleName + "Torch.FFI.THC.Double.TensorTopK"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.FFI.THC.Double.TensorMathPointwise"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise.Floating") + (ModuleName + "Torch.FFI.THC.Double.TensorMathPointwise"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Reduce.Floating") + (ModuleName + "Torch.FFI.THC.Double.TensorMathReduce"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Floating") + (ModuleName + "Torch.FFI.THC.Double.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Blas") + (ModuleName + "Torch.FFI.THC.Double.TensorMathBlas"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Lapack") + (ModuleName + "Torch.FFI.THC.Double.TensorMathMagma"), + _×_ + (ModuleName "Torch.Sig.NN") + (ModuleName + "Torch.FFI.THC.NN.Double"), + _×_ + (ModuleName + "Torch.Sig.Types.NN") + (ModuleName "Torch.Types.THC"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Random.TH") + (ModuleName + "Torch.Undefined.Cuda.Double.Tensor.Math.Random.TH"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Random.TH") + (ModuleName + "Torch.Undefined.Cuda.Double.Tensor.Random.TH"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Random.THC") + (ModuleName + "Torch.FFI.THC.Double.TensorRandom")]}}]}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName + "hasktorch-types-th") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet, + Dependency + (PackageName "dimensions") + (UnionVersionRanges + (ThisVersion (mkVersion [1, 0])) + (LaterVersion + (mkVersion [1, 0]))) + mainLibSet, + Dependency + (PackageName "hasktorch-ffi-th") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet, + Dependency + (PackageName + "hasktorch-types-th") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet, + Dependency + (PackageName "safe-exceptions") + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 1, 0])) + (LaterVersion + (mkVersion [0, 1, 0]))) + mainLibSet, + Dependency + (PackageName "singletons") + (UnionVersionRanges + (ThisVersion (mkVersion [2, 2])) + (LaterVersion + (mkVersion [2, 2]))) + mainLibSet, + Dependency + (PackageName "text") + (UnionVersionRanges + (ThisVersion + (mkVersion [1, 2, 2])) + (LaterVersion + (mkVersion [1, 2, 2]))) + mainLibSet, + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "hasktorch-indef-floating")])), + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "hasktorch-indef-signed")])), + Dependency + (PackageName + "hasktorch-ffi-thc") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet, + Dependency + (PackageName + "hasktorch-types-thc") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet], + condTreeComponents = + [ + CondBranch { + condBranchCondition = + `Var (PackageFlag (FlagName "lite"))`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LSubLibName + (UnqualComponentName + "hasktorch-gpu"), + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPrivate, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = + Just + CondNode { + condTreeData = + Library { + libName = LSubLibName + (UnqualComponentName + "hasktorch-gpu"), + exposedModules = [ + ModuleName "Torch.Cuda.Byte", + ModuleName + "Torch.Cuda.Byte.Dynamic", + ModuleName + "Torch.Cuda.Byte.Storage", + ModuleName "Torch.Cuda.Char", + ModuleName + "Torch.Cuda.Char.Dynamic", + ModuleName + "Torch.Cuda.Char.Storage", + ModuleName "Torch.Cuda.Short", + ModuleName + "Torch.Cuda.Short.Dynamic", + ModuleName + "Torch.Cuda.Short.Storage", + ModuleName "Torch.Cuda.Int", + ModuleName + "Torch.Cuda.Int.Dynamic", + ModuleName + "Torch.Cuda.Int.Storage"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPrivate, + libBuildInfo = + BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "hasktorch-indef-unsigned")]))], + mixins = + [ + Mixin { + mixinPackageName = PackageName + "hasktorch", + mixinLibraryName = LSubLibName + (UnqualComponentName + "hasktorch-indef-unsigned"), + mixinIncludeRenaming = + IncludeRenaming { + includeProvidesRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Indef.Storage") + (ModuleName + "Torch.Indef.Cuda.Byte.Storage"), + _×_ + (ModuleName + "Torch.Indef.Storage.Copy") + (ModuleName + "Torch.Indef.Cuda.Byte.Storage.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor") + (ModuleName + "Torch.Indef.Cuda.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Copy") + (ModuleName + "Torch.Indef.Cuda.Byte.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Index") + (ModuleName + "Torch.Indef.Cuda.Byte.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Masked") + (ModuleName + "Torch.Indef.Cuda.Byte.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math") + (ModuleName + "Torch.Indef.Cuda.Byte.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Cuda.Byte.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Cuda.Byte.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Cuda.Byte.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Cuda.Byte.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Cuda.Byte.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Cuda.Byte.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Mode") + (ModuleName + "Torch.Indef.Cuda.Byte.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Cuda.Byte.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Sort") + (ModuleName + "Torch.Indef.Cuda.Byte.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.TopK") + (ModuleName + "Torch.Indef.Cuda.Byte.Tensor.TopK"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor") + (ModuleName + "Torch.Indef.Cuda.Byte.Dynamic.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Copy") + (ModuleName + "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Index") + (ModuleName + "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Masked") + (ModuleName + "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math") + (ModuleName + "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Mode") + (ModuleName + "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Cuda.Byte.Dynamic.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Sort") + (ModuleName + "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.TopK") + (ModuleName + "Torch.Indef.Cuda.Byte.Dynamic.Tensor.TopK"), + _×_ + (ModuleName "Torch.Indef.Types") + (ModuleName + "Torch.Cuda.Byte.Types"), + _×_ + (ModuleName "Torch.Indef.Index") + (ModuleName + "Torch.Cuda.Byte.Index"), + _×_ + (ModuleName "Torch.Indef.Mask") + (ModuleName + "Torch.Cuda.Byte.Mask")], + includeRequiresRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Sig.Index.Tensor") + (ModuleName + "Torch.FFI.THC.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Index.TensorFree") + (ModuleName + "Torch.FFI.THC.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.Tensor") + (ModuleName + "Torch.FFI.THC.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.TensorFree") + (ModuleName + "Torch.FFI.THC.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.MathReduce") + (ModuleName + "Torch.FFI.THC.Byte.TensorMathReduce"), + _×_ + (ModuleName "Torch.Sig.State") + (ModuleName + "Torch.FFI.THC.State"), + _×_ + (ModuleName + "Torch.Sig.Types.Global") + (ModuleName "Torch.Types.THC"), + _×_ + (ModuleName "Torch.Sig.Types") + (ModuleName + "Torch.Types.THC.Byte"), + _×_ + (ModuleName "Torch.Sig.Storage") + (ModuleName + "Torch.FFI.THC.Byte.Storage"), + _×_ + (ModuleName + "Torch.Sig.Storage.Copy") + (ModuleName + "Torch.FFI.THC.Byte.StorageCopy"), + _×_ + (ModuleName + "Torch.Sig.Storage.Memory") + (ModuleName + "Torch.FFI.THC.Byte.Storage"), + _×_ + (ModuleName "Torch.Sig.Tensor") + (ModuleName + "Torch.FFI.THC.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Copy") + (ModuleName + "Torch.FFI.THC.Byte.TensorCopy"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Memory") + (ModuleName + "Torch.FFI.THC.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Index") + (ModuleName + "Torch.FFI.THC.Byte.TensorIndex"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Masked") + (ModuleName + "Torch.FFI.THC.Byte.TensorMasked"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math") + (ModuleName + "Torch.FFI.THC.Byte.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Compare") + (ModuleName + "Torch.FFI.THC.Byte.TensorMathCompare"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.CompareT") + (ModuleName + "Torch.FFI.THC.Byte.TensorMathCompareT"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pairwise") + (ModuleName + "Torch.FFI.THC.Byte.TensorMathPairwise"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise") + (ModuleName + "Torch.FFI.THC.Byte.TensorMathPointwise"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Reduce") + (ModuleName + "Torch.FFI.THC.Byte.TensorMathReduce"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Scan") + (ModuleName + "Torch.FFI.THC.Byte.TensorMathScan"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Mode") + (ModuleName + "Torch.FFI.THC.Byte.TensorMode"), + _×_ + (ModuleName + "Torch.Sig.Tensor.ScatterGather") + (ModuleName + "Torch.FFI.THC.Byte.TensorScatterGather"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Sort") + (ModuleName + "Torch.FFI.THC.Byte.TensorSort"), + _×_ + (ModuleName + "Torch.Sig.Tensor.TopK") + (ModuleName + "Torch.FFI.THC.Byte.TensorTopK")]}}, + Mixin { + mixinPackageName = PackageName + "hasktorch", + mixinLibraryName = LSubLibName + (UnqualComponentName + "hasktorch-indef-unsigned"), + mixinIncludeRenaming = + IncludeRenaming { + includeProvidesRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Indef.Storage") + (ModuleName + "Torch.Indef.Cuda.Char.Storage"), + _×_ + (ModuleName + "Torch.Indef.Storage.Copy") + (ModuleName + "Torch.Indef.Cuda.Char.Storage.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor") + (ModuleName + "Torch.Indef.Cuda.Char.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Copy") + (ModuleName + "Torch.Indef.Cuda.Char.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Index") + (ModuleName + "Torch.Indef.Cuda.Char.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Masked") + (ModuleName + "Torch.Indef.Cuda.Char.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math") + (ModuleName + "Torch.Indef.Cuda.Char.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Cuda.Char.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Cuda.Char.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Cuda.Char.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Cuda.Char.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Cuda.Char.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Cuda.Char.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Mode") + (ModuleName + "Torch.Indef.Cuda.Char.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Cuda.Char.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Sort") + (ModuleName + "Torch.Indef.Cuda.Char.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.TopK") + (ModuleName + "Torch.Indef.Cuda.Char.Tensor.TopK"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor") + (ModuleName + "Torch.Indef.Cuda.Char.Dynamic.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Copy") + (ModuleName + "Torch.Indef.Cuda.Char.Dynamic.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Index") + (ModuleName + "Torch.Indef.Cuda.Char.Dynamic.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Masked") + (ModuleName + "Torch.Indef.Cuda.Char.Dynamic.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math") + (ModuleName + "Torch.Indef.Cuda.Char.Dynamic.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Mode") + (ModuleName + "Torch.Indef.Cuda.Char.Dynamic.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Cuda.Char.Dynamic.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Sort") + (ModuleName + "Torch.Indef.Cuda.Char.Dynamic.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.TopK") + (ModuleName + "Torch.Indef.Cuda.Char.Dynamic.Tensor.TopK"), + _×_ + (ModuleName "Torch.Indef.Types") + (ModuleName + "Torch.Cuda.Char.Types"), + _×_ + (ModuleName "Torch.Indef.Index") + (ModuleName + "Torch.Cuda.Char.Index"), + _×_ + (ModuleName "Torch.Indef.Mask") + (ModuleName + "Torch.Cuda.Char.Mask")], + includeRequiresRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Sig.Index.Tensor") + (ModuleName + "Torch.FFI.THC.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Index.TensorFree") + (ModuleName + "Torch.FFI.THC.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.Tensor") + (ModuleName + "Torch.FFI.THC.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.TensorFree") + (ModuleName + "Torch.FFI.THC.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.MathReduce") + (ModuleName + "Torch.FFI.THC.Byte.TensorMathReduce"), + _×_ + (ModuleName "Torch.Sig.State") + (ModuleName + "Torch.FFI.THC.State"), + _×_ + (ModuleName + "Torch.Sig.Types.Global") + (ModuleName "Torch.Types.THC"), + _×_ + (ModuleName "Torch.Sig.Types") + (ModuleName + "Torch.Types.THC.Char"), + _×_ + (ModuleName "Torch.Sig.Storage") + (ModuleName + "Torch.FFI.THC.Char.Storage"), + _×_ + (ModuleName + "Torch.Sig.Storage.Copy") + (ModuleName + "Torch.FFI.THC.Char.StorageCopy"), + _×_ + (ModuleName + "Torch.Sig.Storage.Memory") + (ModuleName + "Torch.FFI.THC.Char.Storage"), + _×_ + (ModuleName "Torch.Sig.Tensor") + (ModuleName + "Torch.FFI.THC.Char.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Copy") + (ModuleName + "Torch.FFI.THC.Char.TensorCopy"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Memory") + (ModuleName + "Torch.FFI.THC.Char.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Index") + (ModuleName + "Torch.FFI.THC.Char.TensorIndex"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Masked") + (ModuleName + "Torch.FFI.THC.Char.TensorMasked"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math") + (ModuleName + "Torch.FFI.THC.Char.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Compare") + (ModuleName + "Torch.FFI.THC.Char.TensorMathCompare"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.CompareT") + (ModuleName + "Torch.FFI.THC.Char.TensorMathCompareT"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pairwise") + (ModuleName + "Torch.FFI.THC.Char.TensorMathPairwise"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise") + (ModuleName + "Torch.FFI.THC.Char.TensorMathPointwise"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Reduce") + (ModuleName + "Torch.FFI.THC.Char.TensorMathReduce"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Scan") + (ModuleName + "Torch.FFI.THC.Char.TensorMathScan"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Mode") + (ModuleName + "Torch.FFI.THC.Char.TensorMode"), + _×_ + (ModuleName + "Torch.Sig.Tensor.ScatterGather") + (ModuleName + "Torch.FFI.THC.Char.TensorScatterGather"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Sort") + (ModuleName + "Torch.FFI.THC.Char.TensorSort"), + _×_ + (ModuleName + "Torch.Sig.Tensor.TopK") + (ModuleName + "Torch.FFI.THC.Char.TensorTopK")]}}, + Mixin { + mixinPackageName = PackageName + "hasktorch", + mixinLibraryName = LSubLibName + (UnqualComponentName + "hasktorch-indef-signed"), + mixinIncludeRenaming = + IncludeRenaming { + includeProvidesRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Indef.Storage") + (ModuleName + "Torch.Indef.Cuda.Short.Storage"), + _×_ + (ModuleName + "Torch.Indef.Storage.Copy") + (ModuleName + "Torch.Indef.Cuda.Short.Storage.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor") + (ModuleName + "Torch.Indef.Cuda.Short.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Copy") + (ModuleName + "Torch.Indef.Cuda.Short.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Index") + (ModuleName + "Torch.Indef.Cuda.Short.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Masked") + (ModuleName + "Torch.Indef.Cuda.Short.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math") + (ModuleName + "Torch.Indef.Cuda.Short.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Cuda.Short.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Cuda.Short.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Cuda.Short.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Cuda.Short.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Cuda.Short.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Cuda.Short.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Mode") + (ModuleName + "Torch.Indef.Cuda.Short.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Cuda.Short.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Sort") + (ModuleName + "Torch.Indef.Cuda.Short.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.TopK") + (ModuleName + "Torch.Indef.Cuda.Short.Tensor.TopK"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor") + (ModuleName + "Torch.Indef.Cuda.Short.Dynamic.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Copy") + (ModuleName + "Torch.Indef.Cuda.Short.Dynamic.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Index") + (ModuleName + "Torch.Indef.Cuda.Short.Dynamic.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Masked") + (ModuleName + "Torch.Indef.Cuda.Short.Dynamic.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math") + (ModuleName + "Torch.Indef.Cuda.Short.Dynamic.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Mode") + (ModuleName + "Torch.Indef.Cuda.Short.Dynamic.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Cuda.Short.Dynamic.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Sort") + (ModuleName + "Torch.Indef.Cuda.Short.Dynamic.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.TopK") + (ModuleName + "Torch.Indef.Cuda.Short.Dynamic.Tensor.TopK"), + _×_ + (ModuleName "Torch.Indef.Types") + (ModuleName + "Torch.Cuda.Short.Types"), + _×_ + (ModuleName "Torch.Indef.Index") + (ModuleName + "Torch.Cuda.Short.Index"), + _×_ + (ModuleName "Torch.Indef.Mask") + (ModuleName + "Torch.Cuda.Short.Mask"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Cuda.Short.Tensor.Math.Pointwise.Signed"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Pointwise.Signed")], + includeRequiresRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Sig.Index.Tensor") + (ModuleName + "Torch.FFI.THC.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Index.TensorFree") + (ModuleName + "Torch.FFI.THC.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.Tensor") + (ModuleName + "Torch.FFI.THC.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.TensorFree") + (ModuleName + "Torch.FFI.THC.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.MathReduce") + (ModuleName + "Torch.FFI.THC.Byte.TensorMathReduce"), + _×_ + (ModuleName "Torch.Sig.State") + (ModuleName + "Torch.FFI.THC.State"), + _×_ + (ModuleName + "Torch.Sig.Types.Global") + (ModuleName "Torch.Types.THC"), + _×_ + (ModuleName "Torch.Sig.Types") + (ModuleName + "Torch.Types.THC.Short"), + _×_ + (ModuleName "Torch.Sig.Storage") + (ModuleName + "Torch.FFI.THC.Short.Storage"), + _×_ + (ModuleName + "Torch.Sig.Storage.Copy") + (ModuleName + "Torch.FFI.THC.Short.StorageCopy"), + _×_ + (ModuleName + "Torch.Sig.Storage.Memory") + (ModuleName + "Torch.FFI.THC.Short.Storage"), + _×_ + (ModuleName "Torch.Sig.Tensor") + (ModuleName + "Torch.FFI.THC.Short.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Copy") + (ModuleName + "Torch.FFI.THC.Short.TensorCopy"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Memory") + (ModuleName + "Torch.FFI.THC.Short.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Index") + (ModuleName + "Torch.FFI.THC.Short.TensorIndex"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Masked") + (ModuleName + "Torch.FFI.THC.Short.TensorMasked"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math") + (ModuleName + "Torch.FFI.THC.Short.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Compare") + (ModuleName + "Torch.FFI.THC.Short.TensorMathCompare"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.CompareT") + (ModuleName + "Torch.FFI.THC.Short.TensorMathCompareT"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pairwise") + (ModuleName + "Torch.FFI.THC.Short.TensorMathPairwise"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise") + (ModuleName + "Torch.FFI.THC.Short.TensorMathPointwise"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Reduce") + (ModuleName + "Torch.FFI.THC.Short.TensorMathReduce"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Scan") + (ModuleName + "Torch.FFI.THC.Short.TensorMathScan"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Mode") + (ModuleName + "Torch.FFI.THC.Short.TensorMode"), + _×_ + (ModuleName + "Torch.Sig.Tensor.ScatterGather") + (ModuleName + "Torch.FFI.THC.Short.TensorScatterGather"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Sort") + (ModuleName + "Torch.FFI.THC.Short.TensorSort"), + _×_ + (ModuleName + "Torch.Sig.Tensor.TopK") + (ModuleName + "Torch.FFI.THC.Short.TensorTopK"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.FFI.THC.Short.TensorMathPointwise")]}}, + Mixin { + mixinPackageName = PackageName + "hasktorch", + mixinLibraryName = LSubLibName + (UnqualComponentName + "hasktorch-indef-signed"), + mixinIncludeRenaming = + IncludeRenaming { + includeProvidesRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Indef.Storage") + (ModuleName + "Torch.Indef.Cuda.Int.Storage"), + _×_ + (ModuleName + "Torch.Indef.Storage.Copy") + (ModuleName + "Torch.Indef.Cuda.Int.Storage.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor") + (ModuleName + "Torch.Indef.Cuda.Int.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Copy") + (ModuleName + "Torch.Indef.Cuda.Int.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Index") + (ModuleName + "Torch.Indef.Cuda.Int.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Masked") + (ModuleName + "Torch.Indef.Cuda.Int.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math") + (ModuleName + "Torch.Indef.Cuda.Int.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Cuda.Int.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Cuda.Int.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Cuda.Int.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Cuda.Int.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Cuda.Int.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Cuda.Int.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Mode") + (ModuleName + "Torch.Indef.Cuda.Int.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Cuda.Int.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Sort") + (ModuleName + "Torch.Indef.Cuda.Int.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.TopK") + (ModuleName + "Torch.Indef.Cuda.Int.Tensor.TopK"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor") + (ModuleName + "Torch.Indef.Cuda.Int.Dynamic.Tensor"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Copy") + (ModuleName + "Torch.Indef.Cuda.Int.Dynamic.Tensor.Copy"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Index") + (ModuleName + "Torch.Indef.Cuda.Int.Dynamic.Tensor.Index"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Masked") + (ModuleName + "Torch.Indef.Cuda.Int.Dynamic.Tensor.Masked"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math") + (ModuleName + "Torch.Indef.Cuda.Int.Dynamic.Tensor.Math"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare") + (ModuleName + "Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Compare"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT") + (ModuleName + "Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.CompareT"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise") + (ModuleName + "Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Pairwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise") + (ModuleName + "Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Pointwise"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce") + (ModuleName + "Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Reduce"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan") + (ModuleName + "Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Scan"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Mode") + (ModuleName + "Torch.Indef.Cuda.Int.Dynamic.Tensor.Mode"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather") + (ModuleName + "Torch.Indef.Cuda.Int.Dynamic.Tensor.ScatterGather"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Sort") + (ModuleName + "Torch.Indef.Cuda.Int.Dynamic.Tensor.Sort"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.TopK") + (ModuleName + "Torch.Indef.Cuda.Int.Dynamic.Tensor.TopK"), + _×_ + (ModuleName "Torch.Indef.Types") + (ModuleName + "Torch.Cuda.Int.Types"), + _×_ + (ModuleName "Torch.Indef.Index") + (ModuleName + "Torch.Cuda.Int.Index"), + _×_ + (ModuleName "Torch.Indef.Mask") + (ModuleName + "Torch.Cuda.Int.Mask"), + _×_ + (ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Cuda.Int.Tensor.Math.Pointwise.Signed"), + _×_ + (ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Pointwise.Signed")], + includeRequiresRn = + ModuleRenaming + [ + _×_ + (ModuleName + "Torch.Sig.Index.Tensor") + (ModuleName + "Torch.FFI.THC.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Index.TensorFree") + (ModuleName + "Torch.FFI.THC.Long.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.Tensor") + (ModuleName + "Torch.FFI.THC.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.TensorFree") + (ModuleName + "Torch.FFI.THC.Byte.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Mask.MathReduce") + (ModuleName + "Torch.FFI.THC.Byte.TensorMathReduce"), + _×_ + (ModuleName "Torch.Sig.State") + (ModuleName + "Torch.FFI.THC.State"), + _×_ + (ModuleName + "Torch.Sig.Types.Global") + (ModuleName "Torch.Types.THC"), + _×_ + (ModuleName "Torch.Sig.Types") + (ModuleName + "Torch.Types.THC.Int"), + _×_ + (ModuleName "Torch.Sig.Storage") + (ModuleName + "Torch.FFI.THC.Int.Storage"), + _×_ + (ModuleName + "Torch.Sig.Storage.Copy") + (ModuleName + "Torch.FFI.THC.Int.StorageCopy"), + _×_ + (ModuleName + "Torch.Sig.Storage.Memory") + (ModuleName + "Torch.FFI.THC.Int.Storage"), + _×_ + (ModuleName "Torch.Sig.Tensor") + (ModuleName + "Torch.FFI.THC.Int.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Copy") + (ModuleName + "Torch.FFI.THC.Int.TensorCopy"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Memory") + (ModuleName + "Torch.FFI.THC.Int.Tensor"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Index") + (ModuleName + "Torch.FFI.THC.Int.TensorIndex"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Masked") + (ModuleName + "Torch.FFI.THC.Int.TensorMasked"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math") + (ModuleName + "Torch.FFI.THC.Int.TensorMath"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Compare") + (ModuleName + "Torch.FFI.THC.Int.TensorMathCompare"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.CompareT") + (ModuleName + "Torch.FFI.THC.Int.TensorMathCompareT"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pairwise") + (ModuleName + "Torch.FFI.THC.Int.TensorMathPairwise"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise") + (ModuleName + "Torch.FFI.THC.Int.TensorMathPointwise"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Reduce") + (ModuleName + "Torch.FFI.THC.Int.TensorMathReduce"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Scan") + (ModuleName + "Torch.FFI.THC.Int.TensorMathScan"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Mode") + (ModuleName + "Torch.FFI.THC.Int.TensorMode"), + _×_ + (ModuleName + "Torch.Sig.Tensor.ScatterGather") + (ModuleName + "Torch.FFI.THC.Int.TensorScatterGather"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Sort") + (ModuleName + "Torch.FFI.THC.Int.TensorSort"), + _×_ + (ModuleName + "Torch.Sig.Tensor.TopK") + (ModuleName + "Torch.FFI.THC.Int.TensorTopK"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.FFI.THC.Int.TensorMathPointwise")]}}]}}, + condTreeConstraints = [ + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "hasktorch-indef-unsigned")]))], + condTreeComponents = []}}]}, + _×_ + (UnqualComponentName + "hasktorch-indef-unsigned") + CondNode { + condTreeData = Library { + libName = LSubLibName + (UnqualComponentName + "hasktorch-indef-unsigned"), + exposedModules = [], + reexportedModules = [ + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Indef.Index", + moduleReexportName = ModuleName + "Torch.Indef.Index"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Indef.Mask", + moduleReexportName = ModuleName + "Torch.Indef.Mask"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Indef.Types", + moduleReexportName = ModuleName + "Torch.Indef.Types"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Storage", + moduleReexportName = ModuleName + "Torch.Indef.Storage"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Storage.Copy", + moduleReexportName = ModuleName + "Torch.Indef.Storage.Copy"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Print", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Print"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Copy", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Copy"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Index", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Index"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Masked", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Masked"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Mode", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Mode"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Sort", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Sort"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.TopK", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.TopK"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Copy", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Copy"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Index", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Index"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Masked", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Masked"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Compare", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Compare"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Scan", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Scan"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Mode", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Mode"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.ScatterGather", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.ScatterGather"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Sort", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Sort"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.TopK", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.TopK"}], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPrivate, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName + "hasktorch-signatures-partial") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet, + Dependency + (PackageName "hasktorch-indef") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = [ + Mixin { + mixinPackageName = PackageName + "hasktorch-indef", + mixinLibraryName = LMainLibName, + mixinIncludeRenaming = + IncludeRenaming { + includeProvidesRn = + DefaultRenaming, + includeRequiresRn = + ModuleRenaming + [ + _×_ + (ModuleName "Torch.Sig.NN") + (ModuleName + "Torch.Undefined.NN"), + _×_ + (ModuleName + "Torch.Sig.Types.NN") + (ModuleName + "Torch.Undefined.Types.NN"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Blas") + (ModuleName + "Torch.Undefined.Tensor.Math.Blas"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Floating") + (ModuleName + "Torch.Undefined.Tensor.Math.Floating"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Lapack") + (ModuleName + "Torch.Undefined.Tensor.Math.Lapack"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise.Signed") + (ModuleName + "Torch.Undefined.Tensor.Math.Pointwise.Signed"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise.Floating") + (ModuleName + "Torch.Undefined.Tensor.Math.Pointwise.Floating"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Reduce.Floating") + (ModuleName + "Torch.Undefined.Tensor.Math.Reduce.Floating"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Random.TH") + (ModuleName + "Torch.Undefined.Tensor.Math.Random.TH"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Random.TH") + (ModuleName + "Torch.Undefined.Tensor.Random.TH"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Random.THC") + (ModuleName + "Torch.Undefined.Tensor.Random.THC")]}}]}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName + "hasktorch-signatures-partial") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet, + Dependency + (PackageName "hasktorch-indef") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + _×_ + (UnqualComponentName + "hasktorch-indef-signed") + CondNode { + condTreeData = Library { + libName = LSubLibName + (UnqualComponentName + "hasktorch-indef-signed"), + exposedModules = [], + reexportedModules = [ + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Indef.Index", + moduleReexportName = ModuleName + "Torch.Indef.Index"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Indef.Mask", + moduleReexportName = ModuleName + "Torch.Indef.Mask"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Indef.Types", + moduleReexportName = ModuleName + "Torch.Indef.Types"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Storage", + moduleReexportName = ModuleName + "Torch.Indef.Storage"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Storage.Copy", + moduleReexportName = ModuleName + "Torch.Indef.Storage.Copy"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Print", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Print"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Copy", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Copy"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Index", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Index"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Masked", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Masked"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Mode", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Mode"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Sort", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Sort"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.TopK", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.TopK"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Copy", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Copy"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Index", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Index"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Masked", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Masked"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Compare", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Compare"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Scan", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Scan"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Mode", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Mode"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.ScatterGather", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.ScatterGather"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Sort", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Sort"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.TopK", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.TopK"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Signed", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Signed"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed"}], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPrivate, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName + "hasktorch-signatures-partial") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet, + Dependency + (PackageName "hasktorch-indef") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = [ + Mixin { + mixinPackageName = PackageName + "hasktorch-indef", + mixinLibraryName = LMainLibName, + mixinIncludeRenaming = + IncludeRenaming { + includeProvidesRn = + DefaultRenaming, + includeRequiresRn = + ModuleRenaming + [ + _×_ + (ModuleName "Torch.Sig.NN") + (ModuleName + "Torch.Undefined.NN"), + _×_ + (ModuleName + "Torch.Sig.Types.NN") + (ModuleName + "Torch.Undefined.Types.NN"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Blas") + (ModuleName + "Torch.Undefined.Tensor.Math.Blas"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Floating") + (ModuleName + "Torch.Undefined.Tensor.Math.Floating"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Lapack") + (ModuleName + "Torch.Undefined.Tensor.Math.Lapack"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Pointwise.Floating") + (ModuleName + "Torch.Undefined.Tensor.Math.Pointwise.Floating"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Reduce.Floating") + (ModuleName + "Torch.Undefined.Tensor.Math.Reduce.Floating"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Math.Random.TH") + (ModuleName + "Torch.Undefined.Tensor.Math.Random.TH"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Random.TH") + (ModuleName + "Torch.Undefined.Tensor.Random.TH"), + _×_ + (ModuleName + "Torch.Sig.Tensor.Random.THC") + (ModuleName + "Torch.Undefined.Tensor.Random.THC")]}}]}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName + "hasktorch-signatures-partial") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet, + Dependency + (PackageName "hasktorch-indef") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + _×_ + (UnqualComponentName + "hasktorch-indef-floating") + CondNode { + condTreeData = Library { + libName = LSubLibName + (UnqualComponentName + "hasktorch-indef-floating"), + exposedModules = [], + reexportedModules = [ + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Indef.Index", + moduleReexportName = ModuleName + "Torch.Indef.Index"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Indef.Mask", + moduleReexportName = ModuleName + "Torch.Indef.Mask"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName "Torch.Indef.Types", + moduleReexportName = ModuleName + "Torch.Indef.Types"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Storage", + moduleReexportName = ModuleName + "Torch.Indef.Storage"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Storage.Copy", + moduleReexportName = ModuleName + "Torch.Indef.Storage.Copy"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Print", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Print"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Copy", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Copy"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Index", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Index"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Masked", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Masked"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Compare"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.CompareT"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pairwise"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Scan"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Mode", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Mode"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.ScatterGather"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Sort", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Sort"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.TopK", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.TopK"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Copy", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Copy"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Index", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Index"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Masked", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Masked"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Compare", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Compare"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.CompareT"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Pairwise"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Scan", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Scan"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Mode", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Mode"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.ScatterGather", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.ScatterGather"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Sort", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Sort"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.TopK", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.TopK"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Signed", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Signed"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Blas", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Blas"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Floating", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Floating"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Lapack", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Lapack"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Floating", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Floating"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce.Floating", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Reduce.Floating"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Random.TH", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Random.TH"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Random.THC", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Random.THC"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Random.TH", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.Tensor.Math.Random.TH"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Blas", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Blas"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Floating", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Floating"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Lapack", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Lapack"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Floating", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Pointwise.Floating"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce.Floating", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Reduce.Floating"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Random.TH", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Random.TH"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Random.THC", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Random.THC"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.Tensor.Math.Random.TH", + moduleReexportName = ModuleName + "Torch.Indef.Static.Tensor.Math.Random.TH"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.NN", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.NN"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.NN.Activation", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.NN.Activation"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.NN.Pooling", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.NN.Pooling"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Dynamic.NN.Criterion", + moduleReexportName = ModuleName + "Torch.Indef.Dynamic.NN.Criterion"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.NN", + moduleReexportName = ModuleName + "Torch.Indef.Static.NN"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.NN.Activation", + moduleReexportName = ModuleName + "Torch.Indef.Static.NN.Activation"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.NN.Backprop", + moduleReexportName = ModuleName + "Torch.Indef.Static.NN.Backprop"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.NN.Conv1d", + moduleReexportName = ModuleName + "Torch.Indef.Static.NN.Conv1d"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.NN.Conv2d", + moduleReexportName = ModuleName + "Torch.Indef.Static.NN.Conv2d"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.NN.Criterion", + moduleReexportName = ModuleName + "Torch.Indef.Static.NN.Criterion"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.NN.Layers", + moduleReexportName = ModuleName + "Torch.Indef.Static.NN.Layers"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.NN.Linear", + moduleReexportName = ModuleName + "Torch.Indef.Static.NN.Linear"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.NN.Math", + moduleReexportName = ModuleName + "Torch.Indef.Static.NN.Math"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.NN.Padding", + moduleReexportName = ModuleName + "Torch.Indef.Static.NN.Padding"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.NN.Pooling", + moduleReexportName = ModuleName + "Torch.Indef.Static.NN.Pooling"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Indef.Static.NN.Sampling", + moduleReexportName = ModuleName + "Torch.Indef.Static.NN.Sampling"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Undefined.Tensor.Math.Random.TH", + moduleReexportName = ModuleName + "Torch.Undefined.Tensor.Math.Random.TH"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Undefined.Tensor.Random.TH", + moduleReexportName = ModuleName + "Torch.Undefined.Tensor.Random.TH"}, + ModuleReexport { + moduleReexportOriginalPackage = + Nothing, + moduleReexportOriginalName = + ModuleName + "Torch.Undefined.Tensor.Random.THC", + moduleReexportName = ModuleName + "Torch.Undefined.Tensor.Random.THC"}], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPrivate, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "hasktorch-indef") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName + "hasktorch-signatures-partial") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "hasktorch-indef") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName + "hasktorch-signatures-partial") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 0, 1])) + (LaterVersion + (mkVersion [0, 0, 1]))) + (EarlierVersion + (mkVersion [0, 0, 2]))) + mainLibSet], + condTreeComponents = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/hasktorch.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/hasktorch.condTestSuites.expr new file mode 100644 index 00000000000..25cf09833a4 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/hasktorch.condTestSuites.expr @@ -0,0 +1,300 @@ +[ + _×_ + (UnqualComponentName "spec") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + (SymbolicPath "Spec.hs"), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "tests"], + otherModules = [ + ModuleName "Orphans", + ModuleName "MemorySpec", + ModuleName "RawLapackSVDSpec", + ModuleName + "GarbageCollectionSpec", + ModuleName + "Torch.Prelude.Extras", + ModuleName + "Torch.Core.LogAddSpec", + ModuleName + "Torch.Core.RandomSpec", + ModuleName + "Torch.Static.NN.AbsSpec", + ModuleName + "Torch.Static.NN.LinearSpec"], + virtualModules = [], + autogenModules = [], + defaultLanguage = Just + Haskell2010, + otherLanguages = [], + defaultExtensions = [ + EnableExtension LambdaCase, + EnableExtension DataKinds, + EnableExtension TypeFamilies, + EnableExtension + TypeSynonymInstances, + EnableExtension + ScopedTypeVariables, + EnableExtension + FlexibleContexts, + EnableExtension CPP], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "QuickCheck") + (UnionVersionRanges + (ThisVersion + (mkVersion [2, 11])) + (LaterVersion + (mkVersion [2, 11]))) + mainLibSet, + Dependency + (PackageName "backprop") + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 2, 5])) + (LaterVersion + (mkVersion [0, 2, 5]))) + mainLibSet, + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "dimensions") + (UnionVersionRanges + (ThisVersion (mkVersion [1, 0])) + (LaterVersion + (mkVersion [1, 0]))) + mainLibSet, + Dependency + (PackageName + "ghc-typelits-natnormalise") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "hspec") + (UnionVersionRanges + (ThisVersion + (mkVersion [2, 4, 4])) + (LaterVersion + (mkVersion [2, 4, 4]))) + mainLibSet, + Dependency + (PackageName "singletons") + (UnionVersionRanges + (ThisVersion (mkVersion [2, 2])) + (LaterVersion + (mkVersion [2, 2]))) + mainLibSet, + Dependency + (PackageName "mtl") + (UnionVersionRanges + (ThisVersion + (mkVersion [2, 2, 2])) + (LaterVersion + (mkVersion [2, 2, 2]))) + mainLibSet, + Dependency + (PackageName + "microlens-platform") + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 3, 10])) + (LaterVersion + (mkVersion [0, 3, 10]))) + mainLibSet, + Dependency + (PackageName "monad-loops") + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 4, 3])) + (LaterVersion + (mkVersion [0, 4, 3]))) + mainLibSet, + Dependency + (PackageName "time") + (UnionVersionRanges + (ThisVersion + (mkVersion [1, 8, 0])) + (LaterVersion + (mkVersion [1, 8, 0]))) + mainLibSet, + Dependency + (PackageName "transformers") + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 5, 5])) + (LaterVersion + (mkVersion [0, 5, 5]))) + mainLibSet, + Dependency + (PackageName "generic-lens") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [ + Dependency + (PackageName "QuickCheck") + (UnionVersionRanges + (ThisVersion + (mkVersion [2, 11])) + (LaterVersion + (mkVersion [2, 11]))) + mainLibSet, + Dependency + (PackageName "backprop") + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 2, 5])) + (LaterVersion + (mkVersion [0, 2, 5]))) + mainLibSet, + Dependency + (PackageName "base") + (IntersectVersionRanges + (UnionVersionRanges + (ThisVersion (mkVersion [4, 7])) + (LaterVersion + (mkVersion [4, 7]))) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "dimensions") + (UnionVersionRanges + (ThisVersion (mkVersion [1, 0])) + (LaterVersion + (mkVersion [1, 0]))) + mainLibSet, + Dependency + (PackageName + "ghc-typelits-natnormalise") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "hasktorch") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "hspec") + (UnionVersionRanges + (ThisVersion + (mkVersion [2, 4, 4])) + (LaterVersion + (mkVersion [2, 4, 4]))) + mainLibSet, + Dependency + (PackageName "singletons") + (UnionVersionRanges + (ThisVersion (mkVersion [2, 2])) + (LaterVersion + (mkVersion [2, 2]))) + mainLibSet, + Dependency + (PackageName "mtl") + (UnionVersionRanges + (ThisVersion + (mkVersion [2, 2, 2])) + (LaterVersion + (mkVersion [2, 2, 2]))) + mainLibSet, + Dependency + (PackageName + "microlens-platform") + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 3, 10])) + (LaterVersion + (mkVersion [0, 3, 10]))) + mainLibSet, + Dependency + (PackageName "monad-loops") + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 4, 3])) + (LaterVersion + (mkVersion [0, 4, 3]))) + mainLibSet, + Dependency + (PackageName "time") + (UnionVersionRanges + (ThisVersion + (mkVersion [1, 8, 0])) + (LaterVersion + (mkVersion [1, 8, 0]))) + mainLibSet, + Dependency + (PackageName "transformers") + (UnionVersionRanges + (ThisVersion + (mkVersion [0, 5, 5])) + (LaterVersion + (mkVersion [0, 5, 5]))) + mainLibSet, + Dependency + (PackageName "generic-lens") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/hasktorch.expr b/Cabal-tests/tests/ParserTests/regressions/hasktorch.expr deleted file mode 100644 index 9dfa089a3d5..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/hasktorch.expr +++ /dev/null @@ -1,10248 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV2_2, - package = PackageIdentifier { - pkgName = PackageName - "hasktorch", - pkgVersion = mkVersion - [0, 0, 1, 0]}, - licenseRaw = Left - (License - (ELicense - (ELicenseId BSD_3_Clause) - Nothing)), - licenseFiles = [], - copyright = "", - maintainer = - "Sam Stites , Austin Huang - cipher:ROT13", - author = "Hasktorch dev team", - stability = "", - testedWith = [], - homepage = - "https://github.com/hasktorch/hasktorch#readme", - pkgUrl = "", - bugReports = - "https://github.com/hasktorch/hasktorch/issues", - sourceRepos = [ - SourceRepo { - repoKind = RepoHead, - repoType = Just - (KnownRepoType Git), - repoLocation = Just - "https://github.com/hasktorch/hasktorch", - repoModule = Nothing, - repoBranch = Nothing, - repoTag = Nothing, - repoSubdir = Nothing}], - synopsis = - "Torch for tensors and neural networks in Haskell", - description = - "Hasktorch is a library for tensors and neural networks in Haskell. It is an independent open source community project which leverages the core C libraries shared by Torch and PyTorch. This library leverages @cabal v2-build@ and @backpack@. *Note that this project is in early development and should only be used by contributing developers. Expect substantial changes to the library API as it evolves. Contributions and PRs are welcome (see details on github).*", - category = - "Tensors, Machine Learning, AI", - customFieldsPD = [], - buildTypeRaw = Just Simple, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [ - MkPackageFlag { - flagName = FlagName "cuda", - flagDescription = - "build with THC support", - flagDefault = False, - flagManual = False}, - MkPackageFlag { - flagName = FlagName "lite", - flagDescription = - "only build with Double and Long support", - flagDefault = False, - flagManual = False}], - condLibrary = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [ - ModuleName - "Torch.Core.Exceptions", - ModuleName "Torch.Core.Random", - ModuleName "Torch.Core.LogAdd"], - reexportedModules = [ - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Types.Numeric", - moduleReexportName = ModuleName - "Torch.Types.Numeric"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Long", - moduleReexportName = ModuleName - "Torch.Long"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Long.Dynamic", - moduleReexportName = ModuleName - "Torch.Long.Dynamic"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Long.Storage", - moduleReexportName = ModuleName - "Torch.Long.Storage"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Double", - moduleReexportName = ModuleName - "Torch.Double"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.Dynamic", - moduleReexportName = ModuleName - "Torch.Double.Dynamic"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.Storage", - moduleReexportName = ModuleName - "Torch.Double.Storage"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Double.NN", - moduleReexportName = ModuleName - "Torch.Double.NN"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Activation", - moduleReexportName = ModuleName - "Torch.Double.NN.Activation"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Backprop", - moduleReexportName = ModuleName - "Torch.Double.NN.Backprop"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Conv1d", - moduleReexportName = ModuleName - "Torch.Double.NN.Conv1d"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Conv2d", - moduleReexportName = ModuleName - "Torch.Double.NN.Conv2d"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Criterion", - moduleReexportName = ModuleName - "Torch.Double.NN.Criterion"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Layers", - moduleReexportName = ModuleName - "Torch.Double.NN.Layers"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Linear", - moduleReexportName = ModuleName - "Torch.Double.NN.Linear"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Math", - moduleReexportName = ModuleName - "Torch.Double.NN.Math"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Padding", - moduleReexportName = ModuleName - "Torch.Double.NN.Padding"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Pooling", - moduleReexportName = ModuleName - "Torch.Double.NN.Pooling"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Sampling", - moduleReexportName = ModuleName - "Torch.Double.NN.Sampling"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.Dynamic.NN", - moduleReexportName = ModuleName - "Torch.Double.Dynamic.NN"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.Dynamic.NN.Activation", - moduleReexportName = ModuleName - "Torch.Double.Dynamic.NN.Activation"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.Dynamic.NN.Pooling", - moduleReexportName = ModuleName - "Torch.Double.Dynamic.NN.Pooling"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.Dynamic.NN.Criterion", - moduleReexportName = ModuleName - "Torch.Double.Dynamic.NN.Criterion"}], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - asmOptions = [], - cmmOptions = [], - ccOptions = [], - cxxOptions = [], - ldOptions = [], - hsc2hsOptions = [], - pkgconfigDepends = [], - frameworks = [], - extraFrameworkDirs = [], - asmSources = [], - cmmSources = [], - cSources = [], - cxxSources = [], - jsSources = [], - hsSourceDirs = [ - SymbolicPath "utils"], - otherModules = [], - virtualModules = [], - autogenModules = [], - defaultLanguage = Just - Haskell2010, - otherLanguages = [], - defaultExtensions = [ - EnableExtension LambdaCase, - EnableExtension DataKinds, - EnableExtension TypeFamilies, - EnableExtension - TypeSynonymInstances, - EnableExtension - ScopedTypeVariables, - EnableExtension - FlexibleContexts, - EnableExtension CPP], - otherExtensions = [], - oldExtensions = [], - extraLibs = [], - extraLibsStatic = [], - extraGHCiLibs = [], - extraBundledLibs = [], - extraLibFlavours = [], - extraDynLibFlavours = [], - extraLibDirs = [], - extraLibDirsStatic = [], - includeDirs = [], - includes = [], - autogenIncludes = [], - installIncludes = [], - options = PerCompilerFlavor - [] - [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = - PerCompilerFlavor [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "dimensions") - (UnionVersionRanges - (ThisVersion (mkVersion [1, 0])) - (LaterVersion - (mkVersion [1, 0]))) - mainLibSet, - Dependency - (PackageName "safe-exceptions") - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 1, 0])) - (LaterVersion - (mkVersion [0, 1, 0]))) - mainLibSet, - Dependency - (PackageName "singletons") - (UnionVersionRanges - (ThisVersion (mkVersion [2, 2])) - (LaterVersion - (mkVersion [2, 2]))) - mainLibSet, - Dependency - (PackageName "text") - (UnionVersionRanges - (ThisVersion - (mkVersion [1, 2, 2])) - (LaterVersion - (mkVersion [1, 2, 2]))) - mainLibSet, - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "hasktorch-cpu")])), - Dependency - (PackageName "hasktorch-ffi-th") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet, - Dependency - (PackageName - "hasktorch-types-th") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "dimensions") - (UnionVersionRanges - (ThisVersion (mkVersion [1, 0])) - (LaterVersion - (mkVersion [1, 0]))) - mainLibSet, - Dependency - (PackageName "safe-exceptions") - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 1, 0])) - (LaterVersion - (mkVersion [0, 1, 0]))) - mainLibSet, - Dependency - (PackageName "singletons") - (UnionVersionRanges - (ThisVersion (mkVersion [2, 2])) - (LaterVersion - (mkVersion [2, 2]))) - mainLibSet, - Dependency - (PackageName "text") - (UnionVersionRanges - (ThisVersion - (mkVersion [1, 2, 2])) - (LaterVersion - (mkVersion [1, 2, 2]))) - mainLibSet, - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "hasktorch-cpu")])), - Dependency - (PackageName "hasktorch-ffi-th") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet, - Dependency - (PackageName - "hasktorch-types-th") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet], - condTreeComponents = [ - CondBranch { - condBranchCondition = - `CNot (Var (PackageFlag (FlagName "lite")))`, - condBranchIfTrue = CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [ - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Byte", - moduleReexportName = ModuleName - "Torch.Byte"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Byte.Dynamic", - moduleReexportName = ModuleName - "Torch.Byte.Dynamic"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Byte.Storage", - moduleReexportName = ModuleName - "Torch.Byte.Storage"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Char", - moduleReexportName = ModuleName - "Torch.Char"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Char.Dynamic", - moduleReexportName = ModuleName - "Torch.Char.Dynamic"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Char.Storage", - moduleReexportName = ModuleName - "Torch.Char.Storage"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Short", - moduleReexportName = ModuleName - "Torch.Short"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Short.Dynamic", - moduleReexportName = ModuleName - "Torch.Short.Dynamic"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Short.Storage", - moduleReexportName = ModuleName - "Torch.Short.Storage"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Int", - moduleReexportName = ModuleName - "Torch.Int"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Int.Dynamic", - moduleReexportName = ModuleName - "Torch.Int.Dynamic"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Int.Storage", - moduleReexportName = ModuleName - "Torch.Int.Storage"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Float", - moduleReexportName = ModuleName - "Torch.Float"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Float.Dynamic", - moduleReexportName = ModuleName - "Torch.Float.Dynamic"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Float.Storage", - moduleReexportName = ModuleName - "Torch.Float.Storage"}], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}, - condBranchIfFalse = Nothing}, - CondBranch { - condBranchCondition = - `Var (PackageFlag (FlagName "cuda"))`, - condBranchIfTrue = CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [ - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Cuda.Long", - moduleReexportName = ModuleName - "Torch.Cuda.Long"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Long.Dynamic", - moduleReexportName = ModuleName - "Torch.Cuda.Long.Dynamic"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Long.Storage", - moduleReexportName = ModuleName - "Torch.Cuda.Long.Storage"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Cuda.Double", - moduleReexportName = ModuleName - "Torch.Cuda.Double"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.Dynamic", - moduleReexportName = ModuleName - "Torch.Cuda.Double.Dynamic"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.Storage", - moduleReexportName = ModuleName - "Torch.Cuda.Double.Storage"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Activation", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Activation"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Backprop", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Backprop"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Conv1d", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Conv1d"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Conv2d", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Conv2d"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Criterion", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Criterion"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Layers", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Layers"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Linear", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Linear"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Math", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Math"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Padding", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Padding"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Pooling", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Pooling"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Sampling", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Sampling"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.Dynamic.NN", - moduleReexportName = ModuleName - "Torch.Cuda.Double.Dynamic.NN"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.Dynamic.NN.Activation", - moduleReexportName = ModuleName - "Torch.Cuda.Double.Dynamic.NN.Activation"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.Dynamic.NN.Pooling", - moduleReexportName = ModuleName - "Torch.Cuda.Double.Dynamic.NN.Pooling"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.Dynamic.NN.Criterion", - moduleReexportName = ModuleName - "Torch.Cuda.Double.Dynamic.NN.Criterion"}], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "hasktorch-gpu")]))], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "hasktorch-gpu")]))], - condTreeComponents = [ - CondBranch { - condBranchCondition = - `CNot (Var (PackageFlag (FlagName "lite")))`, - condBranchIfTrue = CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [ - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Cuda.Byte", - moduleReexportName = ModuleName - "Torch.Cuda.Byte"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Byte.Dynamic", - moduleReexportName = ModuleName - "Torch.Cuda.Byte.Dynamic"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Byte.Storage", - moduleReexportName = ModuleName - "Torch.Cuda.Byte.Storage"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Cuda.Char", - moduleReexportName = ModuleName - "Torch.Cuda.Char"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Char.Dynamic", - moduleReexportName = ModuleName - "Torch.Cuda.Char.Dynamic"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Char.Storage", - moduleReexportName = ModuleName - "Torch.Cuda.Char.Storage"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Cuda.Short", - moduleReexportName = ModuleName - "Torch.Cuda.Short"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Short.Dynamic", - moduleReexportName = ModuleName - "Torch.Cuda.Short.Dynamic"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Short.Storage", - moduleReexportName = ModuleName - "Torch.Cuda.Short.Storage"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Cuda.Int", - moduleReexportName = ModuleName - "Torch.Cuda.Int"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Int.Dynamic", - moduleReexportName = ModuleName - "Torch.Cuda.Int.Dynamic"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Int.Storage", - moduleReexportName = ModuleName - "Torch.Cuda.Int.Storage"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Cuda.Float", - moduleReexportName = ModuleName - "Torch.Cuda.Float"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Float.Dynamic", - moduleReexportName = ModuleName - "Torch.Cuda.Float.Dynamic"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Float.Storage", - moduleReexportName = ModuleName - "Torch.Cuda.Float.Storage"}], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}, - condBranchIfFalse = Nothing}]}, - condBranchIfFalse = Nothing}]}, - condSubLibraries = - [ - _×_ - (UnqualComponentName - "hasktorch-cpu") - CondNode { - condTreeData = - Library { - libName = LSubLibName - (UnqualComponentName - "hasktorch-cpu"), - exposedModules = [ - ModuleName "Torch.Long", - ModuleName "Torch.Long.Dynamic", - ModuleName "Torch.Long.Storage", - ModuleName "Torch.Double", - ModuleName - "Torch.Double.Dynamic", - ModuleName - "Torch.Double.Storage"], - reexportedModules = [ - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Double.NN", - moduleReexportName = ModuleName - "Torch.Double.NN"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Activation", - moduleReexportName = ModuleName - "Torch.Double.NN.Activation"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Backprop", - moduleReexportName = ModuleName - "Torch.Double.NN.Backprop"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Conv1d", - moduleReexportName = ModuleName - "Torch.Double.NN.Conv1d"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Conv2d", - moduleReexportName = ModuleName - "Torch.Double.NN.Conv2d"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Criterion", - moduleReexportName = ModuleName - "Torch.Double.NN.Criterion"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Layers", - moduleReexportName = ModuleName - "Torch.Double.NN.Layers"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Linear", - moduleReexportName = ModuleName - "Torch.Double.NN.Linear"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Math", - moduleReexportName = ModuleName - "Torch.Double.NN.Math"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Padding", - moduleReexportName = ModuleName - "Torch.Double.NN.Padding"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Pooling", - moduleReexportName = ModuleName - "Torch.Double.NN.Pooling"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.NN.Sampling", - moduleReexportName = ModuleName - "Torch.Double.NN.Sampling"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.Dynamic.NN", - moduleReexportName = ModuleName - "Torch.Double.Dynamic.NN"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.Dynamic.NN.Activation", - moduleReexportName = ModuleName - "Torch.Double.Dynamic.NN.Activation"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.Dynamic.NN.Pooling", - moduleReexportName = ModuleName - "Torch.Double.Dynamic.NN.Pooling"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Double.Dynamic.NN.Criterion", - moduleReexportName = ModuleName - "Torch.Double.Dynamic.NN.Criterion"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Float.NN", - moduleReexportName = ModuleName - "Torch.Float.NN"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Float.NN.Activation", - moduleReexportName = ModuleName - "Torch.Float.NN.Activation"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Float.NN.Backprop", - moduleReexportName = ModuleName - "Torch.Float.NN.Backprop"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Float.NN.Conv1d", - moduleReexportName = ModuleName - "Torch.Float.NN.Conv1d"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Float.NN.Conv2d", - moduleReexportName = ModuleName - "Torch.Float.NN.Conv2d"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Float.NN.Criterion", - moduleReexportName = ModuleName - "Torch.Float.NN.Criterion"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Float.NN.Layers", - moduleReexportName = ModuleName - "Torch.Float.NN.Layers"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Float.NN.Linear", - moduleReexportName = ModuleName - "Torch.Float.NN.Linear"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Float.NN.Math", - moduleReexportName = ModuleName - "Torch.Float.NN.Math"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Float.NN.Padding", - moduleReexportName = ModuleName - "Torch.Float.NN.Padding"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Float.NN.Pooling", - moduleReexportName = ModuleName - "Torch.Float.NN.Pooling"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Float.NN.Sampling", - moduleReexportName = ModuleName - "Torch.Float.NN.Sampling"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Float.Dynamic.NN", - moduleReexportName = ModuleName - "Torch.Float.Dynamic.NN"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Float.Dynamic.NN.Activation", - moduleReexportName = ModuleName - "Torch.Float.Dynamic.NN.Activation"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Float.Dynamic.NN.Pooling", - moduleReexportName = ModuleName - "Torch.Float.Dynamic.NN.Pooling"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Float.Dynamic.NN.Criterion", - moduleReexportName = ModuleName - "Torch.Float.Dynamic.NN.Criterion"}], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPrivate, - libBuildInfo = - BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - asmOptions = [], - cmmOptions = [], - ccOptions = [], - cxxOptions = [], - ldOptions = [], - hsc2hsOptions = [], - pkgconfigDepends = [], - frameworks = [], - extraFrameworkDirs = [], - asmSources = [], - cmmSources = [], - cSources = [], - cxxSources = [], - jsSources = [], - hsSourceDirs = [ - SymbolicPath "utils", - SymbolicPath "src"], - otherModules = [ - ModuleName - "Torch.Core.Exceptions", - ModuleName "Torch.Core.Random", - ModuleName "Torch.Core.LogAdd"], - virtualModules = [], - autogenModules = [], - defaultLanguage = Just - Haskell2010, - otherLanguages = [], - defaultExtensions = [ - EnableExtension LambdaCase, - EnableExtension DataKinds, - EnableExtension TypeFamilies, - EnableExtension - TypeSynonymInstances, - EnableExtension - ScopedTypeVariables, - EnableExtension - FlexibleContexts, - EnableExtension CPP], - otherExtensions = [], - oldExtensions = [], - extraLibs = [], - extraLibsStatic = [], - extraGHCiLibs = [], - extraBundledLibs = [], - extraLibFlavours = [], - extraDynLibFlavours = [], - extraLibDirs = [], - extraLibDirsStatic = [], - includeDirs = [], - includes = [], - autogenIncludes = [], - installIncludes = [], - options = PerCompilerFlavor - [] - [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = - PerCompilerFlavor [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName - "hasktorch-types-th") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet, - Dependency - (PackageName "dimensions") - (UnionVersionRanges - (ThisVersion (mkVersion [1, 0])) - (LaterVersion - (mkVersion [1, 0]))) - mainLibSet, - Dependency - (PackageName "hasktorch-ffi-th") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet, - Dependency - (PackageName - "hasktorch-types-th") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet, - Dependency - (PackageName "safe-exceptions") - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 1, 0])) - (LaterVersion - (mkVersion [0, 1, 0]))) - mainLibSet, - Dependency - (PackageName "singletons") - (UnionVersionRanges - (ThisVersion (mkVersion [2, 2])) - (LaterVersion - (mkVersion [2, 2]))) - mainLibSet, - Dependency - (PackageName "text") - (UnionVersionRanges - (ThisVersion - (mkVersion [1, 2, 2])) - (LaterVersion - (mkVersion [1, 2, 2]))) - mainLibSet, - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "hasktorch-indef-floating")])), - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "hasktorch-indef-signed")]))], - mixins = - [ - Mixin { - mixinPackageName = PackageName - "hasktorch", - mixinLibraryName = LSubLibName - (UnqualComponentName - "hasktorch-indef-signed"), - mixinIncludeRenaming = - IncludeRenaming { - includeProvidesRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Indef.Storage") - (ModuleName - "Torch.Indef.Long.Storage"), - _×_ - (ModuleName - "Torch.Indef.Storage.Copy") - (ModuleName - "Torch.Indef.Long.Storage.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor") - (ModuleName - "Torch.Indef.Long.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Copy") - (ModuleName - "Torch.Indef.Long.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Index") - (ModuleName - "Torch.Indef.Long.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Masked") - (ModuleName - "Torch.Indef.Long.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math") - (ModuleName - "Torch.Indef.Long.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Long.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Long.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Long.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Long.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Long.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Long.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Mode") - (ModuleName - "Torch.Indef.Long.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Long.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Sort") - (ModuleName - "Torch.Indef.Long.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.TopK") - (ModuleName - "Torch.Indef.Long.Tensor.TopK"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor") - (ModuleName - "Torch.Indef.Long.Dynamic.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Copy") - (ModuleName - "Torch.Indef.Long.Dynamic.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Index") - (ModuleName - "Torch.Indef.Long.Dynamic.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Masked") - (ModuleName - "Torch.Indef.Long.Dynamic.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math") - (ModuleName - "Torch.Indef.Long.Dynamic.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Long.Dynamic.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Long.Dynamic.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Long.Dynamic.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Long.Dynamic.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Long.Dynamic.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Long.Dynamic.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Mode") - (ModuleName - "Torch.Indef.Long.Dynamic.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Long.Dynamic.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Sort") - (ModuleName - "Torch.Indef.Long.Dynamic.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.TopK") - (ModuleName - "Torch.Indef.Long.Dynamic.Tensor.TopK"), - _×_ - (ModuleName "Torch.Indef.Types") - (ModuleName "Torch.Long.Types"), - _×_ - (ModuleName "Torch.Indef.Index") - (ModuleName "Torch.Long.Index"), - _×_ - (ModuleName "Torch.Indef.Mask") - (ModuleName "Torch.Long.Mask"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Long.Tensor.Math.Pointwise.Signed"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Long.Dynamic.Tensor.Math.Pointwise.Signed")], - includeRequiresRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Sig.Index.Tensor") - (ModuleName - "Torch.FFI.TH.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Index.TensorFree") - (ModuleName - "Torch.FFI.TH.Long.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.Tensor") - (ModuleName - "Torch.FFI.TH.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.TensorFree") - (ModuleName - "Torch.FFI.TH.Byte.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.MathReduce") - (ModuleName - "Torch.FFI.TH.Byte.TensorMath"), - _×_ - (ModuleName "Torch.Sig.State") - (ModuleName "Torch.Types.TH"), - _×_ - (ModuleName - "Torch.Sig.Types.Global") - (ModuleName "Torch.Types.TH"), - _×_ - (ModuleName "Torch.Sig.Types") - (ModuleName - "Torch.Types.TH.Long"), - _×_ - (ModuleName "Torch.Sig.Storage") - (ModuleName - "Torch.FFI.TH.Long.Storage"), - _×_ - (ModuleName - "Torch.Sig.Storage.Copy") - (ModuleName - "Torch.FFI.TH.Long.StorageCopy"), - _×_ - (ModuleName - "Torch.Sig.Storage.Memory") - (ModuleName - "Torch.FFI.TH.Long.FreeStorage"), - _×_ - (ModuleName "Torch.Sig.Tensor") - (ModuleName - "Torch.FFI.TH.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Copy") - (ModuleName - "Torch.FFI.TH.Long.TensorCopy"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Memory") - (ModuleName - "Torch.FFI.TH.Long.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Index") - (ModuleName - "Torch.FFI.TH.Long.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Masked") - (ModuleName - "Torch.FFI.TH.Long.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math") - (ModuleName - "Torch.FFI.TH.Long.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Compare") - (ModuleName - "Torch.FFI.TH.Long.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.CompareT") - (ModuleName - "Torch.FFI.TH.Long.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pairwise") - (ModuleName - "Torch.FFI.TH.Long.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise") - (ModuleName - "Torch.FFI.TH.Long.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Reduce") - (ModuleName - "Torch.FFI.TH.Long.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Scan") - (ModuleName - "Torch.FFI.TH.Long.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Mode") - (ModuleName - "Torch.FFI.TH.Long.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.ScatterGather") - (ModuleName - "Torch.FFI.TH.Long.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Sort") - (ModuleName - "Torch.FFI.TH.Long.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.TopK") - (ModuleName - "Torch.FFI.TH.Long.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.FFI.TH.Long.TensorMath")]}}, - Mixin { - mixinPackageName = PackageName - "hasktorch", - mixinLibraryName = LSubLibName - (UnqualComponentName - "hasktorch-indef-floating"), - mixinIncludeRenaming = - IncludeRenaming { - includeProvidesRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Indef.Storage") - (ModuleName - "Torch.Indef.Double.Storage"), - _×_ - (ModuleName - "Torch.Indef.Storage.Copy") - (ModuleName - "Torch.Indef.Double.Storage.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor") - (ModuleName - "Torch.Indef.Double.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Copy") - (ModuleName - "Torch.Indef.Double.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Index") - (ModuleName - "Torch.Indef.Double.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Masked") - (ModuleName - "Torch.Indef.Double.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math") - (ModuleName - "Torch.Indef.Double.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Double.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Double.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Double.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Double.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Double.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Double.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Mode") - (ModuleName - "Torch.Indef.Double.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Double.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Sort") - (ModuleName - "Torch.Indef.Double.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.TopK") - (ModuleName - "Torch.Indef.Double.Tensor.TopK"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Copy") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Index") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Masked") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Mode") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Sort") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.TopK") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.TopK"), - _×_ - (ModuleName "Torch.Indef.Types") - (ModuleName - "Torch.Double.Types"), - _×_ - (ModuleName "Torch.Indef.Index") - (ModuleName - "Torch.Double.Index"), - _×_ - (ModuleName "Torch.Indef.Mask") - (ModuleName - "Torch.Double.Mask"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Double.Tensor.Math.Pointwise.Signed"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math.Pointwise.Signed"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Blas") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math.Blas"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Lapack") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math.Lapack"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Floating") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math.Pointwise.Floating"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce.Floating") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math.Reduce.Floating"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Floating") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math.Floating"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Blas") - (ModuleName - "Torch.Indef.Double.Tensor.Math.Blas"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Lapack") - (ModuleName - "Torch.Indef.Double.Tensor.Math.Lapack"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Floating") - (ModuleName - "Torch.Indef.Double.Tensor.Math.Pointwise.Floating"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce.Floating") - (ModuleName - "Torch.Indef.Double.Tensor.Math.Reduce.Floating"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Floating") - (ModuleName - "Torch.Indef.Double.Tensor.Math.Floating"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Random.TH") - (ModuleName - "Torch.Indef.Double.Tensor.Random.TH"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Random.TH") - (ModuleName - "Torch.Indef.Double.Tensor.Math.Random.TH"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Random.TH") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Random.TH"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Random.TH") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math.Random.TH"), - _×_ - (ModuleName - "Torch.Undefined.Tensor.Random.THC") - (ModuleName - "Torch.Undefined.Double.Tensor.Random.THC"), - _×_ - (ModuleName - "Torch.Indef.Storage") - (ModuleName - "Torch.Indef.Double.Storage"), - _×_ - (ModuleName - "Torch.Indef.Storage.Copy") - (ModuleName - "Torch.Indef.Double.Storage.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor") - (ModuleName - "Torch.Indef.Double.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Copy") - (ModuleName - "Torch.Indef.Double.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Index") - (ModuleName - "Torch.Indef.Double.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Masked") - (ModuleName - "Torch.Indef.Double.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math") - (ModuleName - "Torch.Indef.Double.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Double.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Double.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Double.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Double.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Double.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Double.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Mode") - (ModuleName - "Torch.Indef.Double.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Double.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Sort") - (ModuleName - "Torch.Indef.Double.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.TopK") - (ModuleName - "Torch.Indef.Double.Tensor.TopK"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Copy") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Index") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Masked") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Mode") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Sort") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.TopK") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.TopK"), - _×_ - (ModuleName "Torch.Indef.Types") - (ModuleName - "Torch.Double.Types"), - _×_ - (ModuleName "Torch.Indef.Index") - (ModuleName - "Torch.Double.Index"), - _×_ - (ModuleName "Torch.Indef.Mask") - (ModuleName - "Torch.Double.Mask"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Double.Tensor.Math.Pointwise.Signed"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Double.Dynamic.Tensor.Math.Pointwise.Signed"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.NN") - (ModuleName - "Torch.Double.Dynamic.NN"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.NN.Activation") - (ModuleName - "Torch.Double.Dynamic.NN.Activation"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.NN.Pooling") - (ModuleName - "Torch.Double.Dynamic.NN.Pooling"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.NN.Criterion") - (ModuleName - "Torch.Double.Dynamic.NN.Criterion"), - _×_ - (ModuleName - "Torch.Indef.Static.NN") - (ModuleName "Torch.Double.NN"), - _×_ - (ModuleName - "Torch.Indef.Static.NN") - (ModuleName "Torch.Double.NN"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Activation") - (ModuleName - "Torch.Double.NN.Activation"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Backprop") - (ModuleName - "Torch.Double.NN.Backprop"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Conv1d") - (ModuleName - "Torch.Double.NN.Conv1d"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Conv2d") - (ModuleName - "Torch.Double.NN.Conv2d"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Criterion") - (ModuleName - "Torch.Double.NN.Criterion"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Layers") - (ModuleName - "Torch.Double.NN.Layers"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Linear") - (ModuleName - "Torch.Double.NN.Linear"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Math") - (ModuleName - "Torch.Double.NN.Math"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Padding") - (ModuleName - "Torch.Double.NN.Padding"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Pooling") - (ModuleName - "Torch.Double.NN.Pooling"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Sampling") - (ModuleName - "Torch.Double.NN.Sampling")], - includeRequiresRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Sig.Index.Tensor") - (ModuleName - "Torch.FFI.TH.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Index.TensorFree") - (ModuleName - "Torch.FFI.TH.Long.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.Tensor") - (ModuleName - "Torch.FFI.TH.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.TensorFree") - (ModuleName - "Torch.FFI.TH.Byte.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.MathReduce") - (ModuleName - "Torch.FFI.TH.Byte.TensorMath"), - _×_ - (ModuleName "Torch.Sig.State") - (ModuleName "Torch.Types.TH"), - _×_ - (ModuleName - "Torch.Sig.Types.Global") - (ModuleName "Torch.Types.TH"), - _×_ - (ModuleName "Torch.Sig.Types") - (ModuleName - "Torch.Types.TH.Double"), - _×_ - (ModuleName "Torch.Sig.Storage") - (ModuleName - "Torch.FFI.TH.Double.Storage"), - _×_ - (ModuleName - "Torch.Sig.Storage.Copy") - (ModuleName - "Torch.FFI.TH.Double.StorageCopy"), - _×_ - (ModuleName - "Torch.Sig.Storage.Memory") - (ModuleName - "Torch.FFI.TH.Double.FreeStorage"), - _×_ - (ModuleName "Torch.Sig.Tensor") - (ModuleName - "Torch.FFI.TH.Double.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Copy") - (ModuleName - "Torch.FFI.TH.Double.TensorCopy"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Memory") - (ModuleName - "Torch.FFI.TH.Double.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Index") - (ModuleName - "Torch.FFI.TH.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Masked") - (ModuleName - "Torch.FFI.TH.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math") - (ModuleName - "Torch.FFI.TH.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Compare") - (ModuleName - "Torch.FFI.TH.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.CompareT") - (ModuleName - "Torch.FFI.TH.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pairwise") - (ModuleName - "Torch.FFI.TH.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise") - (ModuleName - "Torch.FFI.TH.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Reduce") - (ModuleName - "Torch.FFI.TH.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Scan") - (ModuleName - "Torch.FFI.TH.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Mode") - (ModuleName - "Torch.FFI.TH.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.ScatterGather") - (ModuleName - "Torch.FFI.TH.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Sort") - (ModuleName - "Torch.FFI.TH.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.TopK") - (ModuleName - "Torch.FFI.TH.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.FFI.TH.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise.Floating") - (ModuleName - "Torch.FFI.TH.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Reduce.Floating") - (ModuleName - "Torch.FFI.TH.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Floating") - (ModuleName - "Torch.FFI.TH.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Blas") - (ModuleName - "Torch.FFI.TH.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Lapack") - (ModuleName - "Torch.FFI.TH.Double.TensorLapack"), - _×_ - (ModuleName "Torch.Sig.NN") - (ModuleName - "Torch.FFI.TH.NN.Double"), - _×_ - (ModuleName - "Torch.Sig.Types.NN") - (ModuleName "Torch.Types.TH"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Random.TH") - (ModuleName - "Torch.FFI.TH.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Random.TH") - (ModuleName - "Torch.FFI.TH.Double.TensorRandom"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Random.THC") - (ModuleName - "Torch.Undefined.Double.Tensor.Random.THC")]}}]}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName - "hasktorch-types-th") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet, - Dependency - (PackageName "dimensions") - (UnionVersionRanges - (ThisVersion (mkVersion [1, 0])) - (LaterVersion - (mkVersion [1, 0]))) - mainLibSet, - Dependency - (PackageName "hasktorch-ffi-th") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet, - Dependency - (PackageName - "hasktorch-types-th") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet, - Dependency - (PackageName "safe-exceptions") - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 1, 0])) - (LaterVersion - (mkVersion [0, 1, 0]))) - mainLibSet, - Dependency - (PackageName "singletons") - (UnionVersionRanges - (ThisVersion (mkVersion [2, 2])) - (LaterVersion - (mkVersion [2, 2]))) - mainLibSet, - Dependency - (PackageName "text") - (UnionVersionRanges - (ThisVersion - (mkVersion [1, 2, 2])) - (LaterVersion - (mkVersion [1, 2, 2]))) - mainLibSet, - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "hasktorch-indef-floating")])), - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "hasktorch-indef-signed")]))], - condTreeComponents = - [ - CondBranch { - condBranchCondition = - `Var (PackageFlag (FlagName "lite"))`, - condBranchIfTrue = CondNode { - condTreeData = Library { - libName = LSubLibName - (UnqualComponentName - "hasktorch-cpu"), - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPrivate, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}, - condBranchIfFalse = - Just - CondNode { - condTreeData = - Library { - libName = LSubLibName - (UnqualComponentName - "hasktorch-cpu"), - exposedModules = [ - ModuleName "Torch.Byte", - ModuleName "Torch.Byte.Dynamic", - ModuleName "Torch.Byte.Storage", - ModuleName "Torch.Char", - ModuleName "Torch.Char.Dynamic", - ModuleName "Torch.Char.Storage", - ModuleName "Torch.Short", - ModuleName - "Torch.Short.Dynamic", - ModuleName - "Torch.Short.Storage", - ModuleName "Torch.Int", - ModuleName "Torch.Int.Dynamic", - ModuleName "Torch.Int.Storage", - ModuleName "Torch.Float", - ModuleName - "Torch.Float.Dynamic", - ModuleName - "Torch.Float.Storage"], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPrivate, - libBuildInfo = - BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "hasktorch-indef-unsigned")]))], - mixins = - [ - Mixin { - mixinPackageName = PackageName - "hasktorch", - mixinLibraryName = LSubLibName - (UnqualComponentName - "hasktorch-indef-unsigned"), - mixinIncludeRenaming = - IncludeRenaming { - includeProvidesRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Indef.Storage") - (ModuleName - "Torch.Indef.Byte.Storage"), - _×_ - (ModuleName - "Torch.Indef.Storage.Copy") - (ModuleName - "Torch.Indef.Byte.Storage.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor") - (ModuleName - "Torch.Indef.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Copy") - (ModuleName - "Torch.Indef.Byte.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Index") - (ModuleName - "Torch.Indef.Byte.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Masked") - (ModuleName - "Torch.Indef.Byte.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math") - (ModuleName - "Torch.Indef.Byte.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Byte.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Byte.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Byte.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Byte.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Byte.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Byte.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Mode") - (ModuleName - "Torch.Indef.Byte.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Byte.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Sort") - (ModuleName - "Torch.Indef.Byte.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.TopK") - (ModuleName - "Torch.Indef.Byte.Tensor.TopK"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor") - (ModuleName - "Torch.Indef.Byte.Dynamic.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Copy") - (ModuleName - "Torch.Indef.Byte.Dynamic.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Index") - (ModuleName - "Torch.Indef.Byte.Dynamic.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Masked") - (ModuleName - "Torch.Indef.Byte.Dynamic.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math") - (ModuleName - "Torch.Indef.Byte.Dynamic.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Byte.Dynamic.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Byte.Dynamic.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Byte.Dynamic.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Byte.Dynamic.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Byte.Dynamic.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Byte.Dynamic.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Mode") - (ModuleName - "Torch.Indef.Byte.Dynamic.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Byte.Dynamic.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Sort") - (ModuleName - "Torch.Indef.Byte.Dynamic.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.TopK") - (ModuleName - "Torch.Indef.Byte.Dynamic.Tensor.TopK"), - _×_ - (ModuleName "Torch.Indef.Types") - (ModuleName "Torch.Byte.Types"), - _×_ - (ModuleName "Torch.Indef.Index") - (ModuleName "Torch.Byte.Index"), - _×_ - (ModuleName "Torch.Indef.Mask") - (ModuleName "Torch.Byte.Mask")], - includeRequiresRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Sig.Index.Tensor") - (ModuleName - "Torch.FFI.TH.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Index.TensorFree") - (ModuleName - "Torch.FFI.TH.Long.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.Tensor") - (ModuleName - "Torch.FFI.TH.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.TensorFree") - (ModuleName - "Torch.FFI.TH.Byte.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.MathReduce") - (ModuleName - "Torch.FFI.TH.Byte.TensorMath"), - _×_ - (ModuleName "Torch.Sig.State") - (ModuleName "Torch.Types.TH"), - _×_ - (ModuleName - "Torch.Sig.Types.Global") - (ModuleName "Torch.Types.TH"), - _×_ - (ModuleName "Torch.Sig.Types") - (ModuleName - "Torch.Types.TH.Byte"), - _×_ - (ModuleName "Torch.Sig.Storage") - (ModuleName - "Torch.FFI.TH.Byte.Storage"), - _×_ - (ModuleName - "Torch.Sig.Storage.Copy") - (ModuleName - "Torch.FFI.TH.Byte.StorageCopy"), - _×_ - (ModuleName - "Torch.Sig.Storage.Memory") - (ModuleName - "Torch.FFI.TH.Byte.FreeStorage"), - _×_ - (ModuleName "Torch.Sig.Tensor") - (ModuleName - "Torch.FFI.TH.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Copy") - (ModuleName - "Torch.FFI.TH.Byte.TensorCopy"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Memory") - (ModuleName - "Torch.FFI.TH.Byte.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Index") - (ModuleName - "Torch.FFI.TH.Byte.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Masked") - (ModuleName - "Torch.FFI.TH.Byte.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math") - (ModuleName - "Torch.FFI.TH.Byte.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Compare") - (ModuleName - "Torch.FFI.TH.Byte.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.CompareT") - (ModuleName - "Torch.FFI.TH.Byte.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pairwise") - (ModuleName - "Torch.FFI.TH.Byte.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise") - (ModuleName - "Torch.FFI.TH.Byte.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Reduce") - (ModuleName - "Torch.FFI.TH.Byte.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Scan") - (ModuleName - "Torch.FFI.TH.Byte.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Mode") - (ModuleName - "Torch.FFI.TH.Byte.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.ScatterGather") - (ModuleName - "Torch.FFI.TH.Byte.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Sort") - (ModuleName - "Torch.FFI.TH.Byte.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.TopK") - (ModuleName - "Torch.FFI.TH.Byte.TensorMath")]}}, - Mixin { - mixinPackageName = PackageName - "hasktorch", - mixinLibraryName = LSubLibName - (UnqualComponentName - "hasktorch-indef-unsigned"), - mixinIncludeRenaming = - IncludeRenaming { - includeProvidesRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Indef.Storage") - (ModuleName - "Torch.Indef.Char.Storage"), - _×_ - (ModuleName - "Torch.Indef.Storage.Copy") - (ModuleName - "Torch.Indef.Char.Storage.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor") - (ModuleName - "Torch.Indef.Char.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Copy") - (ModuleName - "Torch.Indef.Char.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Index") - (ModuleName - "Torch.Indef.Char.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Masked") - (ModuleName - "Torch.Indef.Char.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math") - (ModuleName - "Torch.Indef.Char.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Char.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Char.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Char.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Char.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Char.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Char.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Mode") - (ModuleName - "Torch.Indef.Char.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Char.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Sort") - (ModuleName - "Torch.Indef.Char.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.TopK") - (ModuleName - "Torch.Indef.Char.Tensor.TopK"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor") - (ModuleName - "Torch.Indef.Char.Dynamic.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Copy") - (ModuleName - "Torch.Indef.Char.Dynamic.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Index") - (ModuleName - "Torch.Indef.Char.Dynamic.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Masked") - (ModuleName - "Torch.Indef.Char.Dynamic.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math") - (ModuleName - "Torch.Indef.Char.Dynamic.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Char.Dynamic.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Char.Dynamic.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Char.Dynamic.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Char.Dynamic.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Char.Dynamic.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Char.Dynamic.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Mode") - (ModuleName - "Torch.Indef.Char.Dynamic.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Char.Dynamic.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Sort") - (ModuleName - "Torch.Indef.Char.Dynamic.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.TopK") - (ModuleName - "Torch.Indef.Char.Dynamic.Tensor.TopK"), - _×_ - (ModuleName "Torch.Indef.Types") - (ModuleName "Torch.Char.Types"), - _×_ - (ModuleName "Torch.Indef.Index") - (ModuleName "Torch.Char.Index"), - _×_ - (ModuleName "Torch.Indef.Mask") - (ModuleName "Torch.Char.Mask")], - includeRequiresRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Sig.Index.Tensor") - (ModuleName - "Torch.FFI.TH.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Index.TensorFree") - (ModuleName - "Torch.FFI.TH.Long.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.Tensor") - (ModuleName - "Torch.FFI.TH.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.TensorFree") - (ModuleName - "Torch.FFI.TH.Byte.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.MathReduce") - (ModuleName - "Torch.FFI.TH.Byte.TensorMath"), - _×_ - (ModuleName "Torch.Sig.State") - (ModuleName "Torch.Types.TH"), - _×_ - (ModuleName - "Torch.Sig.Types.Global") - (ModuleName "Torch.Types.TH"), - _×_ - (ModuleName "Torch.Sig.Types") - (ModuleName - "Torch.Types.TH.Char"), - _×_ - (ModuleName "Torch.Sig.Storage") - (ModuleName - "Torch.FFI.TH.Char.Storage"), - _×_ - (ModuleName - "Torch.Sig.Storage.Copy") - (ModuleName - "Torch.FFI.TH.Char.StorageCopy"), - _×_ - (ModuleName - "Torch.Sig.Storage.Memory") - (ModuleName - "Torch.FFI.TH.Char.FreeStorage"), - _×_ - (ModuleName "Torch.Sig.Tensor") - (ModuleName - "Torch.FFI.TH.Char.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Copy") - (ModuleName - "Torch.FFI.TH.Char.TensorCopy"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Memory") - (ModuleName - "Torch.FFI.TH.Char.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Index") - (ModuleName - "Torch.FFI.TH.Char.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Masked") - (ModuleName - "Torch.FFI.TH.Char.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math") - (ModuleName - "Torch.FFI.TH.Char.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Compare") - (ModuleName - "Torch.FFI.TH.Char.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.CompareT") - (ModuleName - "Torch.FFI.TH.Char.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pairwise") - (ModuleName - "Torch.FFI.TH.Char.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise") - (ModuleName - "Torch.FFI.TH.Char.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Reduce") - (ModuleName - "Torch.FFI.TH.Char.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Scan") - (ModuleName - "Torch.FFI.TH.Char.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Mode") - (ModuleName - "Torch.FFI.TH.Char.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.ScatterGather") - (ModuleName - "Torch.FFI.TH.Char.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Sort") - (ModuleName - "Torch.FFI.TH.Char.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.TopK") - (ModuleName - "Torch.FFI.TH.Char.TensorMath")]}}, - Mixin { - mixinPackageName = PackageName - "hasktorch", - mixinLibraryName = LSubLibName - (UnqualComponentName - "hasktorch-indef-signed"), - mixinIncludeRenaming = - IncludeRenaming { - includeProvidesRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Indef.Storage") - (ModuleName - "Torch.Indef.Short.Storage"), - _×_ - (ModuleName - "Torch.Indef.Storage.Copy") - (ModuleName - "Torch.Indef.Short.Storage.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor") - (ModuleName - "Torch.Indef.Short.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Copy") - (ModuleName - "Torch.Indef.Short.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Index") - (ModuleName - "Torch.Indef.Short.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Masked") - (ModuleName - "Torch.Indef.Short.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math") - (ModuleName - "Torch.Indef.Short.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Short.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Short.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Short.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Short.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Short.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Short.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Mode") - (ModuleName - "Torch.Indef.Short.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Short.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Sort") - (ModuleName - "Torch.Indef.Short.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.TopK") - (ModuleName - "Torch.Indef.Short.Tensor.TopK"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor") - (ModuleName - "Torch.Indef.Short.Dynamic.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Copy") - (ModuleName - "Torch.Indef.Short.Dynamic.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Index") - (ModuleName - "Torch.Indef.Short.Dynamic.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Masked") - (ModuleName - "Torch.Indef.Short.Dynamic.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math") - (ModuleName - "Torch.Indef.Short.Dynamic.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Short.Dynamic.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Short.Dynamic.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Short.Dynamic.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Short.Dynamic.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Short.Dynamic.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Short.Dynamic.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Mode") - (ModuleName - "Torch.Indef.Short.Dynamic.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Short.Dynamic.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Sort") - (ModuleName - "Torch.Indef.Short.Dynamic.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.TopK") - (ModuleName - "Torch.Indef.Short.Dynamic.Tensor.TopK"), - _×_ - (ModuleName "Torch.Indef.Types") - (ModuleName - "Torch.Short.Types"), - _×_ - (ModuleName "Torch.Indef.Index") - (ModuleName - "Torch.Short.Index"), - _×_ - (ModuleName "Torch.Indef.Mask") - (ModuleName "Torch.Short.Mask"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Short.Tensor.Math.Pointwise.Signed"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Short.Dynamic.Tensor.Math.Pointwise.Signed")], - includeRequiresRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Sig.Index.Tensor") - (ModuleName - "Torch.FFI.TH.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Index.TensorFree") - (ModuleName - "Torch.FFI.TH.Long.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.Tensor") - (ModuleName - "Torch.FFI.TH.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.TensorFree") - (ModuleName - "Torch.FFI.TH.Byte.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.MathReduce") - (ModuleName - "Torch.FFI.TH.Byte.TensorMath"), - _×_ - (ModuleName "Torch.Sig.State") - (ModuleName "Torch.Types.TH"), - _×_ - (ModuleName - "Torch.Sig.Types.Global") - (ModuleName "Torch.Types.TH"), - _×_ - (ModuleName "Torch.Sig.Types") - (ModuleName - "Torch.Types.TH.Short"), - _×_ - (ModuleName "Torch.Sig.Storage") - (ModuleName - "Torch.FFI.TH.Short.Storage"), - _×_ - (ModuleName - "Torch.Sig.Storage.Copy") - (ModuleName - "Torch.FFI.TH.Short.StorageCopy"), - _×_ - (ModuleName - "Torch.Sig.Storage.Memory") - (ModuleName - "Torch.FFI.TH.Short.FreeStorage"), - _×_ - (ModuleName "Torch.Sig.Tensor") - (ModuleName - "Torch.FFI.TH.Short.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Copy") - (ModuleName - "Torch.FFI.TH.Short.TensorCopy"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Memory") - (ModuleName - "Torch.FFI.TH.Short.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Index") - (ModuleName - "Torch.FFI.TH.Short.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Masked") - (ModuleName - "Torch.FFI.TH.Short.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math") - (ModuleName - "Torch.FFI.TH.Short.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Compare") - (ModuleName - "Torch.FFI.TH.Short.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.CompareT") - (ModuleName - "Torch.FFI.TH.Short.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pairwise") - (ModuleName - "Torch.FFI.TH.Short.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise") - (ModuleName - "Torch.FFI.TH.Short.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Reduce") - (ModuleName - "Torch.FFI.TH.Short.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Scan") - (ModuleName - "Torch.FFI.TH.Short.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Mode") - (ModuleName - "Torch.FFI.TH.Short.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.ScatterGather") - (ModuleName - "Torch.FFI.TH.Short.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Sort") - (ModuleName - "Torch.FFI.TH.Short.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.TopK") - (ModuleName - "Torch.FFI.TH.Short.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.FFI.TH.Short.TensorMath")]}}, - Mixin { - mixinPackageName = PackageName - "hasktorch", - mixinLibraryName = LSubLibName - (UnqualComponentName - "hasktorch-indef-signed"), - mixinIncludeRenaming = - IncludeRenaming { - includeProvidesRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Indef.Storage") - (ModuleName - "Torch.Indef.Int.Storage"), - _×_ - (ModuleName - "Torch.Indef.Storage.Copy") - (ModuleName - "Torch.Indef.Int.Storage.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor") - (ModuleName - "Torch.Indef.Int.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Copy") - (ModuleName - "Torch.Indef.Int.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Index") - (ModuleName - "Torch.Indef.Int.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Masked") - (ModuleName - "Torch.Indef.Int.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math") - (ModuleName - "Torch.Indef.Int.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Int.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Int.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Int.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Int.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Int.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Int.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Mode") - (ModuleName - "Torch.Indef.Int.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Int.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Sort") - (ModuleName - "Torch.Indef.Int.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.TopK") - (ModuleName - "Torch.Indef.Int.Tensor.TopK"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor") - (ModuleName - "Torch.Indef.Int.Dynamic.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Copy") - (ModuleName - "Torch.Indef.Int.Dynamic.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Index") - (ModuleName - "Torch.Indef.Int.Dynamic.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Masked") - (ModuleName - "Torch.Indef.Int.Dynamic.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math") - (ModuleName - "Torch.Indef.Int.Dynamic.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Int.Dynamic.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Int.Dynamic.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Int.Dynamic.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Int.Dynamic.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Int.Dynamic.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Int.Dynamic.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Mode") - (ModuleName - "Torch.Indef.Int.Dynamic.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Int.Dynamic.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Sort") - (ModuleName - "Torch.Indef.Int.Dynamic.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.TopK") - (ModuleName - "Torch.Indef.Int.Dynamic.Tensor.TopK"), - _×_ - (ModuleName "Torch.Indef.Types") - (ModuleName "Torch.Int.Types"), - _×_ - (ModuleName "Torch.Indef.Index") - (ModuleName "Torch.Int.Index"), - _×_ - (ModuleName "Torch.Indef.Mask") - (ModuleName "Torch.Int.Mask"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Int.Tensor.Math.Pointwise.Signed"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Int.Dynamic.Tensor.Math.Pointwise.Signed")], - includeRequiresRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Sig.Index.Tensor") - (ModuleName - "Torch.FFI.TH.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Index.TensorFree") - (ModuleName - "Torch.FFI.TH.Long.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.Tensor") - (ModuleName - "Torch.FFI.TH.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.TensorFree") - (ModuleName - "Torch.FFI.TH.Byte.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.MathReduce") - (ModuleName - "Torch.FFI.TH.Byte.TensorMath"), - _×_ - (ModuleName "Torch.Sig.State") - (ModuleName "Torch.Types.TH"), - _×_ - (ModuleName - "Torch.Sig.Types.Global") - (ModuleName "Torch.Types.TH"), - _×_ - (ModuleName "Torch.Sig.Types") - (ModuleName - "Torch.Types.TH.Int"), - _×_ - (ModuleName "Torch.Sig.Storage") - (ModuleName - "Torch.FFI.TH.Int.Storage"), - _×_ - (ModuleName - "Torch.Sig.Storage.Copy") - (ModuleName - "Torch.FFI.TH.Int.StorageCopy"), - _×_ - (ModuleName - "Torch.Sig.Storage.Memory") - (ModuleName - "Torch.FFI.TH.Int.FreeStorage"), - _×_ - (ModuleName "Torch.Sig.Tensor") - (ModuleName - "Torch.FFI.TH.Int.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Copy") - (ModuleName - "Torch.FFI.TH.Int.TensorCopy"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Memory") - (ModuleName - "Torch.FFI.TH.Int.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Index") - (ModuleName - "Torch.FFI.TH.Int.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Masked") - (ModuleName - "Torch.FFI.TH.Int.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math") - (ModuleName - "Torch.FFI.TH.Int.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Compare") - (ModuleName - "Torch.FFI.TH.Int.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.CompareT") - (ModuleName - "Torch.FFI.TH.Int.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pairwise") - (ModuleName - "Torch.FFI.TH.Int.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise") - (ModuleName - "Torch.FFI.TH.Int.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Reduce") - (ModuleName - "Torch.FFI.TH.Int.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Scan") - (ModuleName - "Torch.FFI.TH.Int.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Mode") - (ModuleName - "Torch.FFI.TH.Int.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.ScatterGather") - (ModuleName - "Torch.FFI.TH.Int.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Sort") - (ModuleName - "Torch.FFI.TH.Int.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.TopK") - (ModuleName - "Torch.FFI.TH.Int.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.FFI.TH.Int.TensorMath")]}}, - Mixin { - mixinPackageName = PackageName - "hasktorch", - mixinLibraryName = LSubLibName - (UnqualComponentName - "hasktorch-indef-floating"), - mixinIncludeRenaming = - IncludeRenaming { - includeProvidesRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Indef.Storage") - (ModuleName - "Torch.Indef.Float.Storage"), - _×_ - (ModuleName - "Torch.Indef.Storage.Copy") - (ModuleName - "Torch.Indef.Float.Storage.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor") - (ModuleName - "Torch.Indef.Float.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Copy") - (ModuleName - "Torch.Indef.Float.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Index") - (ModuleName - "Torch.Indef.Float.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Masked") - (ModuleName - "Torch.Indef.Float.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math") - (ModuleName - "Torch.Indef.Float.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Float.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Float.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Float.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Float.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Float.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Float.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Mode") - (ModuleName - "Torch.Indef.Float.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Float.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Sort") - (ModuleName - "Torch.Indef.Float.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.TopK") - (ModuleName - "Torch.Indef.Float.Tensor.TopK"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Copy") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Index") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Masked") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Mode") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Sort") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.TopK") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.TopK"), - _×_ - (ModuleName "Torch.Indef.Types") - (ModuleName - "Torch.Float.Types"), - _×_ - (ModuleName "Torch.Indef.Index") - (ModuleName - "Torch.Float.Index"), - _×_ - (ModuleName "Torch.Indef.Mask") - (ModuleName "Torch.Float.Mask"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Float.Tensor.Math.Pointwise.Signed"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math.Pointwise.Signed"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Blas") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math.Blas"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Lapack") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math.Lapack"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Floating") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math.Pointwise.Floating"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce.Floating") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math.Reduce.Floating"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Floating") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math.Floating"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Blas") - (ModuleName - "Torch.Indef.Float.Tensor.Math.Blas"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Lapack") - (ModuleName - "Torch.Indef.Float.Tensor.Math.Lapack"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Floating") - (ModuleName - "Torch.Indef.Float.Tensor.Math.Pointwise.Floating"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce.Floating") - (ModuleName - "Torch.Indef.Float.Tensor.Math.Reduce.Floating"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Floating") - (ModuleName - "Torch.Indef.Float.Tensor.Math.Floating"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Random.TH") - (ModuleName - "Torch.Indef.Float.Tensor.Random.TH"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Random.TH") - (ModuleName - "Torch.Indef.Float.Tensor.Math.Random.TH"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Random.TH") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Random.TH"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Random.TH") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math.Random.TH"), - _×_ - (ModuleName - "Torch.Undefined.Tensor.Random.THC") - (ModuleName - "Torch.Undefined.Float.Tensor.Random.THC"), - _×_ - (ModuleName - "Torch.Indef.Storage") - (ModuleName - "Torch.Indef.Float.Storage"), - _×_ - (ModuleName - "Torch.Indef.Storage.Copy") - (ModuleName - "Torch.Indef.Float.Storage.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor") - (ModuleName - "Torch.Indef.Float.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Copy") - (ModuleName - "Torch.Indef.Float.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Index") - (ModuleName - "Torch.Indef.Float.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Masked") - (ModuleName - "Torch.Indef.Float.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math") - (ModuleName - "Torch.Indef.Float.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Float.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Float.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Float.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Float.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Float.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Float.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Mode") - (ModuleName - "Torch.Indef.Float.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Float.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Sort") - (ModuleName - "Torch.Indef.Float.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.TopK") - (ModuleName - "Torch.Indef.Float.Tensor.TopK"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Copy") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Index") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Masked") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Mode") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Sort") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.TopK") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.TopK"), - _×_ - (ModuleName "Torch.Indef.Types") - (ModuleName - "Torch.Float.Types"), - _×_ - (ModuleName "Torch.Indef.Index") - (ModuleName - "Torch.Float.Index"), - _×_ - (ModuleName "Torch.Indef.Mask") - (ModuleName "Torch.Float.Mask"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Float.Tensor.Math.Pointwise.Signed"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Float.Dynamic.Tensor.Math.Pointwise.Signed"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.NN") - (ModuleName - "Torch.Float.Dynamic.NN"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.NN.Activation") - (ModuleName - "Torch.Float.Dynamic.NN.Activation"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.NN.Pooling") - (ModuleName - "Torch.Float.Dynamic.NN.Pooling"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.NN.Criterion") - (ModuleName - "Torch.Float.Dynamic.NN.Criterion"), - _×_ - (ModuleName - "Torch.Indef.Static.NN") - (ModuleName "Torch.Float.NN"), - _×_ - (ModuleName - "Torch.Indef.Static.NN") - (ModuleName "Torch.Float.NN"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Activation") - (ModuleName - "Torch.Float.NN.Activation"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Backprop") - (ModuleName - "Torch.Float.NN.Backprop"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Conv1d") - (ModuleName - "Torch.Float.NN.Conv1d"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Conv2d") - (ModuleName - "Torch.Float.NN.Conv2d"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Criterion") - (ModuleName - "Torch.Float.NN.Criterion"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Layers") - (ModuleName - "Torch.Float.NN.Layers"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Linear") - (ModuleName - "Torch.Float.NN.Linear"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Math") - (ModuleName - "Torch.Float.NN.Math"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Padding") - (ModuleName - "Torch.Float.NN.Padding"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Pooling") - (ModuleName - "Torch.Float.NN.Pooling"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Sampling") - (ModuleName - "Torch.Float.NN.Sampling")], - includeRequiresRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Sig.Index.Tensor") - (ModuleName - "Torch.FFI.TH.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Index.TensorFree") - (ModuleName - "Torch.FFI.TH.Long.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.Tensor") - (ModuleName - "Torch.FFI.TH.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.TensorFree") - (ModuleName - "Torch.FFI.TH.Byte.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.MathReduce") - (ModuleName - "Torch.FFI.TH.Byte.TensorMath"), - _×_ - (ModuleName "Torch.Sig.State") - (ModuleName "Torch.Types.TH"), - _×_ - (ModuleName - "Torch.Sig.Types.Global") - (ModuleName "Torch.Types.TH"), - _×_ - (ModuleName "Torch.Sig.Types") - (ModuleName - "Torch.Types.TH.Float"), - _×_ - (ModuleName "Torch.Sig.Storage") - (ModuleName - "Torch.FFI.TH.Float.Storage"), - _×_ - (ModuleName - "Torch.Sig.Storage.Copy") - (ModuleName - "Torch.FFI.TH.Float.StorageCopy"), - _×_ - (ModuleName - "Torch.Sig.Storage.Memory") - (ModuleName - "Torch.FFI.TH.Float.FreeStorage"), - _×_ - (ModuleName "Torch.Sig.Tensor") - (ModuleName - "Torch.FFI.TH.Float.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Copy") - (ModuleName - "Torch.FFI.TH.Float.TensorCopy"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Memory") - (ModuleName - "Torch.FFI.TH.Float.FreeTensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Index") - (ModuleName - "Torch.FFI.TH.Float.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Masked") - (ModuleName - "Torch.FFI.TH.Float.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math") - (ModuleName - "Torch.FFI.TH.Float.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Compare") - (ModuleName - "Torch.FFI.TH.Float.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.CompareT") - (ModuleName - "Torch.FFI.TH.Float.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pairwise") - (ModuleName - "Torch.FFI.TH.Float.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise") - (ModuleName - "Torch.FFI.TH.Float.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Reduce") - (ModuleName - "Torch.FFI.TH.Float.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Scan") - (ModuleName - "Torch.FFI.TH.Float.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Mode") - (ModuleName - "Torch.FFI.TH.Float.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.ScatterGather") - (ModuleName - "Torch.FFI.TH.Float.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Sort") - (ModuleName - "Torch.FFI.TH.Float.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.TopK") - (ModuleName - "Torch.FFI.TH.Float.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.FFI.TH.Float.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise.Floating") - (ModuleName - "Torch.FFI.TH.Float.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Reduce.Floating") - (ModuleName - "Torch.FFI.TH.Float.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Floating") - (ModuleName - "Torch.FFI.TH.Float.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Blas") - (ModuleName - "Torch.FFI.TH.Float.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Lapack") - (ModuleName - "Torch.FFI.TH.Float.TensorLapack"), - _×_ - (ModuleName "Torch.Sig.NN") - (ModuleName - "Torch.FFI.TH.NN.Float"), - _×_ - (ModuleName - "Torch.Sig.Types.NN") - (ModuleName "Torch.Types.TH"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Random.TH") - (ModuleName - "Torch.FFI.TH.Float.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Random.TH") - (ModuleName - "Torch.FFI.TH.Float.TensorRandom"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Random.THC") - (ModuleName - "Torch.Undefined.Float.Tensor.Random.THC")]}}]}}, - condTreeConstraints = [ - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "hasktorch-indef-unsigned")]))], - condTreeComponents = []}}]}, - _×_ - (UnqualComponentName - "hasktorch-gpu") - CondNode { - condTreeData = - Library { - libName = LSubLibName - (UnqualComponentName - "hasktorch-gpu"), - exposedModules = [ - ModuleName "Torch.Cuda.Long", - ModuleName - "Torch.Cuda.Long.Dynamic", - ModuleName - "Torch.Cuda.Long.Storage", - ModuleName "Torch.Cuda.Double", - ModuleName - "Torch.Cuda.Double.Dynamic", - ModuleName - "Torch.Cuda.Double.Storage"], - reexportedModules = [ - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Activation", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Activation"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Backprop", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Backprop"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Conv1d", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Conv1d"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Conv2d", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Conv2d"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Criterion", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Criterion"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Layers", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Layers"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Linear", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Linear"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Math", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Math"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Padding", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Padding"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Pooling", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Pooling"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.NN.Sampling", - moduleReexportName = ModuleName - "Torch.Cuda.Double.NN.Sampling"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.Dynamic.NN", - moduleReexportName = ModuleName - "Torch.Cuda.Double.Dynamic.NN"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.Dynamic.NN.Activation", - moduleReexportName = ModuleName - "Torch.Cuda.Double.Dynamic.NN.Activation"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.Dynamic.NN.Pooling", - moduleReexportName = ModuleName - "Torch.Cuda.Double.Dynamic.NN.Pooling"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Cuda.Double.Dynamic.NN.Criterion", - moduleReexportName = ModuleName - "Torch.Cuda.Double.Dynamic.NN.Criterion"}], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPrivate, - libBuildInfo = - BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [ - "-DCUDA", - "-DHASKTORCH_INTERNAL_CUDA"], - jsppOptions = [], - asmOptions = [], - cmmOptions = [], - ccOptions = [], - cxxOptions = [], - ldOptions = [], - hsc2hsOptions = [], - pkgconfigDepends = [], - frameworks = [], - extraFrameworkDirs = [], - asmSources = [], - cmmSources = [], - cSources = [], - cxxSources = [], - jsSources = [], - hsSourceDirs = [ - SymbolicPath "utils", - SymbolicPath "src"], - otherModules = [ - ModuleName - "Torch.Core.Exceptions", - ModuleName "Torch.Core.Random", - ModuleName "Torch.Core.LogAdd"], - virtualModules = [], - autogenModules = [], - defaultLanguage = Just - Haskell2010, - otherLanguages = [], - defaultExtensions = [ - EnableExtension LambdaCase, - EnableExtension DataKinds, - EnableExtension TypeFamilies, - EnableExtension - TypeSynonymInstances, - EnableExtension - ScopedTypeVariables, - EnableExtension - FlexibleContexts, - EnableExtension CPP], - otherExtensions = [], - oldExtensions = [], - extraLibs = [], - extraLibsStatic = [], - extraGHCiLibs = [], - extraBundledLibs = [], - extraLibFlavours = [], - extraDynLibFlavours = [], - extraLibDirs = [], - extraLibDirsStatic = [], - includeDirs = [], - includes = [], - autogenIncludes = [], - installIncludes = [], - options = PerCompilerFlavor - [] - [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = - PerCompilerFlavor [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName - "hasktorch-types-th") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet, - Dependency - (PackageName "dimensions") - (UnionVersionRanges - (ThisVersion (mkVersion [1, 0])) - (LaterVersion - (mkVersion [1, 0]))) - mainLibSet, - Dependency - (PackageName "hasktorch-ffi-th") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet, - Dependency - (PackageName - "hasktorch-types-th") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet, - Dependency - (PackageName "safe-exceptions") - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 1, 0])) - (LaterVersion - (mkVersion [0, 1, 0]))) - mainLibSet, - Dependency - (PackageName "singletons") - (UnionVersionRanges - (ThisVersion (mkVersion [2, 2])) - (LaterVersion - (mkVersion [2, 2]))) - mainLibSet, - Dependency - (PackageName "text") - (UnionVersionRanges - (ThisVersion - (mkVersion [1, 2, 2])) - (LaterVersion - (mkVersion [1, 2, 2]))) - mainLibSet, - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "hasktorch-indef-floating")])), - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "hasktorch-indef-signed")])), - Dependency - (PackageName - "hasktorch-ffi-thc") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet, - Dependency - (PackageName - "hasktorch-types-thc") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet], - mixins = - [ - Mixin { - mixinPackageName = PackageName - "hasktorch", - mixinLibraryName = LSubLibName - (UnqualComponentName - "hasktorch-indef-signed"), - mixinIncludeRenaming = - IncludeRenaming { - includeProvidesRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Indef.Storage") - (ModuleName - "Torch.Indef.Cuda.Long.Storage"), - _×_ - (ModuleName - "Torch.Indef.Storage.Copy") - (ModuleName - "Torch.Indef.Cuda.Long.Storage.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor") - (ModuleName - "Torch.Indef.Cuda.Long.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Copy") - (ModuleName - "Torch.Indef.Cuda.Long.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Index") - (ModuleName - "Torch.Indef.Cuda.Long.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Masked") - (ModuleName - "Torch.Indef.Cuda.Long.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math") - (ModuleName - "Torch.Indef.Cuda.Long.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Cuda.Long.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Cuda.Long.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Cuda.Long.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Cuda.Long.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Cuda.Long.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Cuda.Long.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Mode") - (ModuleName - "Torch.Indef.Cuda.Long.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Cuda.Long.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Sort") - (ModuleName - "Torch.Indef.Cuda.Long.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.TopK") - (ModuleName - "Torch.Indef.Cuda.Long.Tensor.TopK"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor") - (ModuleName - "Torch.Indef.Cuda.Long.Dynamic.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Copy") - (ModuleName - "Torch.Indef.Cuda.Long.Dynamic.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Index") - (ModuleName - "Torch.Indef.Cuda.Long.Dynamic.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Masked") - (ModuleName - "Torch.Indef.Cuda.Long.Dynamic.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math") - (ModuleName - "Torch.Indef.Cuda.Long.Dynamic.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Mode") - (ModuleName - "Torch.Indef.Cuda.Long.Dynamic.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Cuda.Long.Dynamic.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Sort") - (ModuleName - "Torch.Indef.Cuda.Long.Dynamic.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.TopK") - (ModuleName - "Torch.Indef.Cuda.Long.Dynamic.Tensor.TopK"), - _×_ - (ModuleName "Torch.Indef.Types") - (ModuleName - "Torch.Cuda.Long.Types"), - _×_ - (ModuleName "Torch.Indef.Index") - (ModuleName - "Torch.Cuda.Long.Index"), - _×_ - (ModuleName "Torch.Indef.Mask") - (ModuleName - "Torch.Cuda.Long.Mask"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Cuda.Long.Tensor.Math.Pointwise.Signed"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Pointwise.Signed")], - includeRequiresRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Sig.Index.Tensor") - (ModuleName - "Torch.FFI.THC.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Index.TensorFree") - (ModuleName - "Torch.FFI.THC.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.Tensor") - (ModuleName - "Torch.FFI.THC.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.TensorFree") - (ModuleName - "Torch.FFI.THC.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.MathReduce") - (ModuleName - "Torch.FFI.THC.Byte.TensorMathReduce"), - _×_ - (ModuleName "Torch.Sig.State") - (ModuleName - "Torch.FFI.THC.State"), - _×_ - (ModuleName - "Torch.Sig.Types.Global") - (ModuleName "Torch.Types.THC"), - _×_ - (ModuleName "Torch.Sig.Types") - (ModuleName - "Torch.Types.THC.Long"), - _×_ - (ModuleName "Torch.Sig.Storage") - (ModuleName - "Torch.FFI.THC.Long.Storage"), - _×_ - (ModuleName - "Torch.Sig.Storage.Copy") - (ModuleName - "Torch.FFI.THC.Long.StorageCopy"), - _×_ - (ModuleName - "Torch.Sig.Storage.Memory") - (ModuleName - "Torch.FFI.THC.Long.Storage"), - _×_ - (ModuleName "Torch.Sig.Tensor") - (ModuleName - "Torch.FFI.THC.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Copy") - (ModuleName - "Torch.FFI.THC.Long.TensorCopy"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Memory") - (ModuleName - "Torch.FFI.THC.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Index") - (ModuleName - "Torch.FFI.THC.Long.TensorIndex"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Masked") - (ModuleName - "Torch.FFI.THC.Long.TensorMasked"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math") - (ModuleName - "Torch.FFI.THC.Long.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Compare") - (ModuleName - "Torch.FFI.THC.Long.TensorMathCompare"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.CompareT") - (ModuleName - "Torch.FFI.THC.Long.TensorMathCompareT"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pairwise") - (ModuleName - "Torch.FFI.THC.Long.TensorMathPairwise"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise") - (ModuleName - "Torch.FFI.THC.Long.TensorMathPointwise"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Reduce") - (ModuleName - "Torch.FFI.THC.Long.TensorMathReduce"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Scan") - (ModuleName - "Torch.FFI.THC.Long.TensorMathScan"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Mode") - (ModuleName - "Torch.FFI.THC.Long.TensorMode"), - _×_ - (ModuleName - "Torch.Sig.Tensor.ScatterGather") - (ModuleName - "Torch.FFI.THC.Long.TensorScatterGather"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Sort") - (ModuleName - "Torch.FFI.THC.Long.TensorSort"), - _×_ - (ModuleName - "Torch.Sig.Tensor.TopK") - (ModuleName - "Torch.FFI.THC.Long.TensorTopK"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.FFI.THC.Long.TensorMathPointwise")]}}, - Mixin { - mixinPackageName = PackageName - "hasktorch", - mixinLibraryName = LSubLibName - (UnqualComponentName - "hasktorch-indef-floating"), - mixinIncludeRenaming = - IncludeRenaming { - includeProvidesRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Indef.Storage") - (ModuleName - "Torch.Indef.Cuda.Double.Storage"), - _×_ - (ModuleName - "Torch.Indef.Storage.Copy") - (ModuleName - "Torch.Indef.Cuda.Double.Storage.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Copy") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Index") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Masked") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Mode") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Sort") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.TopK") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.TopK"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Copy") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Index") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Masked") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Mode") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Sort") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.TopK") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.TopK"), - _×_ - (ModuleName "Torch.Indef.Types") - (ModuleName - "Torch.Cuda.Double.Types"), - _×_ - (ModuleName "Torch.Indef.Index") - (ModuleName - "Torch.Cuda.Double.Index"), - _×_ - (ModuleName "Torch.Indef.Mask") - (ModuleName - "Torch.Cuda.Double.Mask"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math.Pointwise.Signed"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pointwise.Signed"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Blas") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Blas"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Lapack") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Lapack"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Floating") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pointwise.Floating"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce.Floating") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Reduce.Floating"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Floating") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Floating"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Blas") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math.Blas"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Lapack") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math.Lapack"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Floating") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math.Pointwise.Floating"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce.Floating") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math.Reduce.Floating"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Floating") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math.Floating"), - _×_ - (ModuleName - "Torch.Undefined.Tensor.Random.TH") - (ModuleName - "Torch.Undefined.Cuda.Double.Tensor.Random.TH"), - _×_ - (ModuleName - "Torch.Undefined.Tensor.Math.Random.TH") - (ModuleName - "Torch.Undefined.Cuda.Double.Tensor.Math.Random.TH"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Random.THC") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Random.THC"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Random.THC") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Random.THC"), - _×_ - (ModuleName - "Torch.Indef.Storage") - (ModuleName - "Torch.Indef.Cuda.Double.Storage"), - _×_ - (ModuleName - "Torch.Indef.Storage.Copy") - (ModuleName - "Torch.Indef.Cuda.Double.Storage.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Copy") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Index") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Masked") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Mode") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Sort") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.TopK") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.TopK"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Copy") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Index") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Masked") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Mode") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Sort") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.TopK") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.TopK"), - _×_ - (ModuleName "Torch.Indef.Types") - (ModuleName - "Torch.Cuda.Double.Types"), - _×_ - (ModuleName "Torch.Indef.Index") - (ModuleName - "Torch.Cuda.Double.Index"), - _×_ - (ModuleName "Torch.Indef.Mask") - (ModuleName - "Torch.Cuda.Double.Mask"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Cuda.Double.Tensor.Math.Pointwise.Signed"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pointwise.Signed"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.NN") - (ModuleName - "Torch.Cuda.Double.Dynamic.NN"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.NN.Activation") - (ModuleName - "Torch.Cuda.Double.Dynamic.NN.Activation"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.NN.Pooling") - (ModuleName - "Torch.Cuda.Double.Dynamic.NN.Pooling"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.NN.Criterion") - (ModuleName - "Torch.Cuda.Double.Dynamic.NN.Criterion"), - _×_ - (ModuleName - "Torch.Indef.Static.NN") - (ModuleName - "Torch.Cuda.Double.NN"), - _×_ - (ModuleName - "Torch.Indef.Static.NN") - (ModuleName - "Torch.Cuda.Double.NN"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Activation") - (ModuleName - "Torch.Cuda.Double.NN.Activation"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Backprop") - (ModuleName - "Torch.Cuda.Double.NN.Backprop"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Conv1d") - (ModuleName - "Torch.Cuda.Double.NN.Conv1d"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Conv2d") - (ModuleName - "Torch.Cuda.Double.NN.Conv2d"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Criterion") - (ModuleName - "Torch.Cuda.Double.NN.Criterion"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Layers") - (ModuleName - "Torch.Cuda.Double.NN.Layers"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Linear") - (ModuleName - "Torch.Cuda.Double.NN.Linear"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Math") - (ModuleName - "Torch.Cuda.Double.NN.Math"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Padding") - (ModuleName - "Torch.Cuda.Double.NN.Padding"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Pooling") - (ModuleName - "Torch.Cuda.Double.NN.Pooling"), - _×_ - (ModuleName - "Torch.Indef.Static.NN.Sampling") - (ModuleName - "Torch.Cuda.Double.NN.Sampling")], - includeRequiresRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Sig.Index.Tensor") - (ModuleName - "Torch.FFI.THC.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Index.TensorFree") - (ModuleName - "Torch.FFI.THC.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.Tensor") - (ModuleName - "Torch.FFI.THC.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.TensorFree") - (ModuleName - "Torch.FFI.THC.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.MathReduce") - (ModuleName - "Torch.FFI.THC.Byte.TensorMathReduce"), - _×_ - (ModuleName "Torch.Sig.State") - (ModuleName - "Torch.FFI.THC.State"), - _×_ - (ModuleName - "Torch.Sig.Types.Global") - (ModuleName "Torch.Types.THC"), - _×_ - (ModuleName "Torch.Sig.Types") - (ModuleName - "Torch.Types.THC.Double"), - _×_ - (ModuleName "Torch.Sig.Storage") - (ModuleName - "Torch.FFI.THC.Double.Storage"), - _×_ - (ModuleName - "Torch.Sig.Storage.Copy") - (ModuleName - "Torch.FFI.THC.Double.StorageCopy"), - _×_ - (ModuleName - "Torch.Sig.Storage.Memory") - (ModuleName - "Torch.FFI.THC.Double.Storage"), - _×_ - (ModuleName "Torch.Sig.Tensor") - (ModuleName - "Torch.FFI.THC.Double.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Copy") - (ModuleName - "Torch.FFI.THC.Double.TensorCopy"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Memory") - (ModuleName - "Torch.FFI.THC.Double.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Index") - (ModuleName - "Torch.FFI.THC.Double.TensorIndex"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Masked") - (ModuleName - "Torch.FFI.THC.Double.TensorMasked"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math") - (ModuleName - "Torch.FFI.THC.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Compare") - (ModuleName - "Torch.FFI.THC.Double.TensorMathCompare"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.CompareT") - (ModuleName - "Torch.FFI.THC.Double.TensorMathCompareT"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pairwise") - (ModuleName - "Torch.FFI.THC.Double.TensorMathPairwise"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise") - (ModuleName - "Torch.FFI.THC.Double.TensorMathPointwise"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Reduce") - (ModuleName - "Torch.FFI.THC.Double.TensorMathReduce"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Scan") - (ModuleName - "Torch.FFI.THC.Double.TensorMathScan"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Mode") - (ModuleName - "Torch.FFI.THC.Double.TensorMode"), - _×_ - (ModuleName - "Torch.Sig.Tensor.ScatterGather") - (ModuleName - "Torch.FFI.THC.Double.TensorScatterGather"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Sort") - (ModuleName - "Torch.FFI.THC.Double.TensorSort"), - _×_ - (ModuleName - "Torch.Sig.Tensor.TopK") - (ModuleName - "Torch.FFI.THC.Double.TensorTopK"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.FFI.THC.Double.TensorMathPointwise"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise.Floating") - (ModuleName - "Torch.FFI.THC.Double.TensorMathPointwise"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Reduce.Floating") - (ModuleName - "Torch.FFI.THC.Double.TensorMathReduce"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Floating") - (ModuleName - "Torch.FFI.THC.Double.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Blas") - (ModuleName - "Torch.FFI.THC.Double.TensorMathBlas"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Lapack") - (ModuleName - "Torch.FFI.THC.Double.TensorMathMagma"), - _×_ - (ModuleName "Torch.Sig.NN") - (ModuleName - "Torch.FFI.THC.NN.Double"), - _×_ - (ModuleName - "Torch.Sig.Types.NN") - (ModuleName "Torch.Types.THC"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Random.TH") - (ModuleName - "Torch.Undefined.Cuda.Double.Tensor.Math.Random.TH"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Random.TH") - (ModuleName - "Torch.Undefined.Cuda.Double.Tensor.Random.TH"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Random.THC") - (ModuleName - "Torch.FFI.THC.Double.TensorRandom")]}}]}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName - "hasktorch-types-th") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet, - Dependency - (PackageName "dimensions") - (UnionVersionRanges - (ThisVersion (mkVersion [1, 0])) - (LaterVersion - (mkVersion [1, 0]))) - mainLibSet, - Dependency - (PackageName "hasktorch-ffi-th") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet, - Dependency - (PackageName - "hasktorch-types-th") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet, - Dependency - (PackageName "safe-exceptions") - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 1, 0])) - (LaterVersion - (mkVersion [0, 1, 0]))) - mainLibSet, - Dependency - (PackageName "singletons") - (UnionVersionRanges - (ThisVersion (mkVersion [2, 2])) - (LaterVersion - (mkVersion [2, 2]))) - mainLibSet, - Dependency - (PackageName "text") - (UnionVersionRanges - (ThisVersion - (mkVersion [1, 2, 2])) - (LaterVersion - (mkVersion [1, 2, 2]))) - mainLibSet, - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "hasktorch-indef-floating")])), - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "hasktorch-indef-signed")])), - Dependency - (PackageName - "hasktorch-ffi-thc") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet, - Dependency - (PackageName - "hasktorch-types-thc") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet], - condTreeComponents = - [ - CondBranch { - condBranchCondition = - `Var (PackageFlag (FlagName "lite"))`, - condBranchIfTrue = CondNode { - condTreeData = Library { - libName = LSubLibName - (UnqualComponentName - "hasktorch-gpu"), - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPrivate, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}, - condBranchIfFalse = - Just - CondNode { - condTreeData = - Library { - libName = LSubLibName - (UnqualComponentName - "hasktorch-gpu"), - exposedModules = [ - ModuleName "Torch.Cuda.Byte", - ModuleName - "Torch.Cuda.Byte.Dynamic", - ModuleName - "Torch.Cuda.Byte.Storage", - ModuleName "Torch.Cuda.Char", - ModuleName - "Torch.Cuda.Char.Dynamic", - ModuleName - "Torch.Cuda.Char.Storage", - ModuleName "Torch.Cuda.Short", - ModuleName - "Torch.Cuda.Short.Dynamic", - ModuleName - "Torch.Cuda.Short.Storage", - ModuleName "Torch.Cuda.Int", - ModuleName - "Torch.Cuda.Int.Dynamic", - ModuleName - "Torch.Cuda.Int.Storage"], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPrivate, - libBuildInfo = - BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "hasktorch-indef-unsigned")]))], - mixins = - [ - Mixin { - mixinPackageName = PackageName - "hasktorch", - mixinLibraryName = LSubLibName - (UnqualComponentName - "hasktorch-indef-unsigned"), - mixinIncludeRenaming = - IncludeRenaming { - includeProvidesRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Indef.Storage") - (ModuleName - "Torch.Indef.Cuda.Byte.Storage"), - _×_ - (ModuleName - "Torch.Indef.Storage.Copy") - (ModuleName - "Torch.Indef.Cuda.Byte.Storage.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor") - (ModuleName - "Torch.Indef.Cuda.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Copy") - (ModuleName - "Torch.Indef.Cuda.Byte.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Index") - (ModuleName - "Torch.Indef.Cuda.Byte.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Masked") - (ModuleName - "Torch.Indef.Cuda.Byte.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math") - (ModuleName - "Torch.Indef.Cuda.Byte.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Cuda.Byte.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Cuda.Byte.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Cuda.Byte.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Cuda.Byte.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Cuda.Byte.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Cuda.Byte.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Mode") - (ModuleName - "Torch.Indef.Cuda.Byte.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Cuda.Byte.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Sort") - (ModuleName - "Torch.Indef.Cuda.Byte.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.TopK") - (ModuleName - "Torch.Indef.Cuda.Byte.Tensor.TopK"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor") - (ModuleName - "Torch.Indef.Cuda.Byte.Dynamic.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Copy") - (ModuleName - "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Index") - (ModuleName - "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Masked") - (ModuleName - "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math") - (ModuleName - "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Mode") - (ModuleName - "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Cuda.Byte.Dynamic.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Sort") - (ModuleName - "Torch.Indef.Cuda.Byte.Dynamic.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.TopK") - (ModuleName - "Torch.Indef.Cuda.Byte.Dynamic.Tensor.TopK"), - _×_ - (ModuleName "Torch.Indef.Types") - (ModuleName - "Torch.Cuda.Byte.Types"), - _×_ - (ModuleName "Torch.Indef.Index") - (ModuleName - "Torch.Cuda.Byte.Index"), - _×_ - (ModuleName "Torch.Indef.Mask") - (ModuleName - "Torch.Cuda.Byte.Mask")], - includeRequiresRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Sig.Index.Tensor") - (ModuleName - "Torch.FFI.THC.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Index.TensorFree") - (ModuleName - "Torch.FFI.THC.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.Tensor") - (ModuleName - "Torch.FFI.THC.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.TensorFree") - (ModuleName - "Torch.FFI.THC.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.MathReduce") - (ModuleName - "Torch.FFI.THC.Byte.TensorMathReduce"), - _×_ - (ModuleName "Torch.Sig.State") - (ModuleName - "Torch.FFI.THC.State"), - _×_ - (ModuleName - "Torch.Sig.Types.Global") - (ModuleName "Torch.Types.THC"), - _×_ - (ModuleName "Torch.Sig.Types") - (ModuleName - "Torch.Types.THC.Byte"), - _×_ - (ModuleName "Torch.Sig.Storage") - (ModuleName - "Torch.FFI.THC.Byte.Storage"), - _×_ - (ModuleName - "Torch.Sig.Storage.Copy") - (ModuleName - "Torch.FFI.THC.Byte.StorageCopy"), - _×_ - (ModuleName - "Torch.Sig.Storage.Memory") - (ModuleName - "Torch.FFI.THC.Byte.Storage"), - _×_ - (ModuleName "Torch.Sig.Tensor") - (ModuleName - "Torch.FFI.THC.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Copy") - (ModuleName - "Torch.FFI.THC.Byte.TensorCopy"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Memory") - (ModuleName - "Torch.FFI.THC.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Index") - (ModuleName - "Torch.FFI.THC.Byte.TensorIndex"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Masked") - (ModuleName - "Torch.FFI.THC.Byte.TensorMasked"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math") - (ModuleName - "Torch.FFI.THC.Byte.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Compare") - (ModuleName - "Torch.FFI.THC.Byte.TensorMathCompare"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.CompareT") - (ModuleName - "Torch.FFI.THC.Byte.TensorMathCompareT"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pairwise") - (ModuleName - "Torch.FFI.THC.Byte.TensorMathPairwise"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise") - (ModuleName - "Torch.FFI.THC.Byte.TensorMathPointwise"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Reduce") - (ModuleName - "Torch.FFI.THC.Byte.TensorMathReduce"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Scan") - (ModuleName - "Torch.FFI.THC.Byte.TensorMathScan"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Mode") - (ModuleName - "Torch.FFI.THC.Byte.TensorMode"), - _×_ - (ModuleName - "Torch.Sig.Tensor.ScatterGather") - (ModuleName - "Torch.FFI.THC.Byte.TensorScatterGather"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Sort") - (ModuleName - "Torch.FFI.THC.Byte.TensorSort"), - _×_ - (ModuleName - "Torch.Sig.Tensor.TopK") - (ModuleName - "Torch.FFI.THC.Byte.TensorTopK")]}}, - Mixin { - mixinPackageName = PackageName - "hasktorch", - mixinLibraryName = LSubLibName - (UnqualComponentName - "hasktorch-indef-unsigned"), - mixinIncludeRenaming = - IncludeRenaming { - includeProvidesRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Indef.Storage") - (ModuleName - "Torch.Indef.Cuda.Char.Storage"), - _×_ - (ModuleName - "Torch.Indef.Storage.Copy") - (ModuleName - "Torch.Indef.Cuda.Char.Storage.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor") - (ModuleName - "Torch.Indef.Cuda.Char.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Copy") - (ModuleName - "Torch.Indef.Cuda.Char.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Index") - (ModuleName - "Torch.Indef.Cuda.Char.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Masked") - (ModuleName - "Torch.Indef.Cuda.Char.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math") - (ModuleName - "Torch.Indef.Cuda.Char.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Cuda.Char.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Cuda.Char.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Cuda.Char.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Cuda.Char.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Cuda.Char.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Cuda.Char.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Mode") - (ModuleName - "Torch.Indef.Cuda.Char.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Cuda.Char.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Sort") - (ModuleName - "Torch.Indef.Cuda.Char.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.TopK") - (ModuleName - "Torch.Indef.Cuda.Char.Tensor.TopK"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor") - (ModuleName - "Torch.Indef.Cuda.Char.Dynamic.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Copy") - (ModuleName - "Torch.Indef.Cuda.Char.Dynamic.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Index") - (ModuleName - "Torch.Indef.Cuda.Char.Dynamic.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Masked") - (ModuleName - "Torch.Indef.Cuda.Char.Dynamic.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math") - (ModuleName - "Torch.Indef.Cuda.Char.Dynamic.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Mode") - (ModuleName - "Torch.Indef.Cuda.Char.Dynamic.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Cuda.Char.Dynamic.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Sort") - (ModuleName - "Torch.Indef.Cuda.Char.Dynamic.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.TopK") - (ModuleName - "Torch.Indef.Cuda.Char.Dynamic.Tensor.TopK"), - _×_ - (ModuleName "Torch.Indef.Types") - (ModuleName - "Torch.Cuda.Char.Types"), - _×_ - (ModuleName "Torch.Indef.Index") - (ModuleName - "Torch.Cuda.Char.Index"), - _×_ - (ModuleName "Torch.Indef.Mask") - (ModuleName - "Torch.Cuda.Char.Mask")], - includeRequiresRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Sig.Index.Tensor") - (ModuleName - "Torch.FFI.THC.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Index.TensorFree") - (ModuleName - "Torch.FFI.THC.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.Tensor") - (ModuleName - "Torch.FFI.THC.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.TensorFree") - (ModuleName - "Torch.FFI.THC.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.MathReduce") - (ModuleName - "Torch.FFI.THC.Byte.TensorMathReduce"), - _×_ - (ModuleName "Torch.Sig.State") - (ModuleName - "Torch.FFI.THC.State"), - _×_ - (ModuleName - "Torch.Sig.Types.Global") - (ModuleName "Torch.Types.THC"), - _×_ - (ModuleName "Torch.Sig.Types") - (ModuleName - "Torch.Types.THC.Char"), - _×_ - (ModuleName "Torch.Sig.Storage") - (ModuleName - "Torch.FFI.THC.Char.Storage"), - _×_ - (ModuleName - "Torch.Sig.Storage.Copy") - (ModuleName - "Torch.FFI.THC.Char.StorageCopy"), - _×_ - (ModuleName - "Torch.Sig.Storage.Memory") - (ModuleName - "Torch.FFI.THC.Char.Storage"), - _×_ - (ModuleName "Torch.Sig.Tensor") - (ModuleName - "Torch.FFI.THC.Char.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Copy") - (ModuleName - "Torch.FFI.THC.Char.TensorCopy"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Memory") - (ModuleName - "Torch.FFI.THC.Char.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Index") - (ModuleName - "Torch.FFI.THC.Char.TensorIndex"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Masked") - (ModuleName - "Torch.FFI.THC.Char.TensorMasked"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math") - (ModuleName - "Torch.FFI.THC.Char.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Compare") - (ModuleName - "Torch.FFI.THC.Char.TensorMathCompare"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.CompareT") - (ModuleName - "Torch.FFI.THC.Char.TensorMathCompareT"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pairwise") - (ModuleName - "Torch.FFI.THC.Char.TensorMathPairwise"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise") - (ModuleName - "Torch.FFI.THC.Char.TensorMathPointwise"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Reduce") - (ModuleName - "Torch.FFI.THC.Char.TensorMathReduce"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Scan") - (ModuleName - "Torch.FFI.THC.Char.TensorMathScan"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Mode") - (ModuleName - "Torch.FFI.THC.Char.TensorMode"), - _×_ - (ModuleName - "Torch.Sig.Tensor.ScatterGather") - (ModuleName - "Torch.FFI.THC.Char.TensorScatterGather"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Sort") - (ModuleName - "Torch.FFI.THC.Char.TensorSort"), - _×_ - (ModuleName - "Torch.Sig.Tensor.TopK") - (ModuleName - "Torch.FFI.THC.Char.TensorTopK")]}}, - Mixin { - mixinPackageName = PackageName - "hasktorch", - mixinLibraryName = LSubLibName - (UnqualComponentName - "hasktorch-indef-signed"), - mixinIncludeRenaming = - IncludeRenaming { - includeProvidesRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Indef.Storage") - (ModuleName - "Torch.Indef.Cuda.Short.Storage"), - _×_ - (ModuleName - "Torch.Indef.Storage.Copy") - (ModuleName - "Torch.Indef.Cuda.Short.Storage.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor") - (ModuleName - "Torch.Indef.Cuda.Short.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Copy") - (ModuleName - "Torch.Indef.Cuda.Short.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Index") - (ModuleName - "Torch.Indef.Cuda.Short.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Masked") - (ModuleName - "Torch.Indef.Cuda.Short.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math") - (ModuleName - "Torch.Indef.Cuda.Short.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Cuda.Short.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Cuda.Short.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Cuda.Short.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Cuda.Short.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Cuda.Short.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Cuda.Short.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Mode") - (ModuleName - "Torch.Indef.Cuda.Short.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Cuda.Short.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Sort") - (ModuleName - "Torch.Indef.Cuda.Short.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.TopK") - (ModuleName - "Torch.Indef.Cuda.Short.Tensor.TopK"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor") - (ModuleName - "Torch.Indef.Cuda.Short.Dynamic.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Copy") - (ModuleName - "Torch.Indef.Cuda.Short.Dynamic.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Index") - (ModuleName - "Torch.Indef.Cuda.Short.Dynamic.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Masked") - (ModuleName - "Torch.Indef.Cuda.Short.Dynamic.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math") - (ModuleName - "Torch.Indef.Cuda.Short.Dynamic.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Mode") - (ModuleName - "Torch.Indef.Cuda.Short.Dynamic.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Cuda.Short.Dynamic.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Sort") - (ModuleName - "Torch.Indef.Cuda.Short.Dynamic.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.TopK") - (ModuleName - "Torch.Indef.Cuda.Short.Dynamic.Tensor.TopK"), - _×_ - (ModuleName "Torch.Indef.Types") - (ModuleName - "Torch.Cuda.Short.Types"), - _×_ - (ModuleName "Torch.Indef.Index") - (ModuleName - "Torch.Cuda.Short.Index"), - _×_ - (ModuleName "Torch.Indef.Mask") - (ModuleName - "Torch.Cuda.Short.Mask"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Cuda.Short.Tensor.Math.Pointwise.Signed"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Pointwise.Signed")], - includeRequiresRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Sig.Index.Tensor") - (ModuleName - "Torch.FFI.THC.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Index.TensorFree") - (ModuleName - "Torch.FFI.THC.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.Tensor") - (ModuleName - "Torch.FFI.THC.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.TensorFree") - (ModuleName - "Torch.FFI.THC.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.MathReduce") - (ModuleName - "Torch.FFI.THC.Byte.TensorMathReduce"), - _×_ - (ModuleName "Torch.Sig.State") - (ModuleName - "Torch.FFI.THC.State"), - _×_ - (ModuleName - "Torch.Sig.Types.Global") - (ModuleName "Torch.Types.THC"), - _×_ - (ModuleName "Torch.Sig.Types") - (ModuleName - "Torch.Types.THC.Short"), - _×_ - (ModuleName "Torch.Sig.Storage") - (ModuleName - "Torch.FFI.THC.Short.Storage"), - _×_ - (ModuleName - "Torch.Sig.Storage.Copy") - (ModuleName - "Torch.FFI.THC.Short.StorageCopy"), - _×_ - (ModuleName - "Torch.Sig.Storage.Memory") - (ModuleName - "Torch.FFI.THC.Short.Storage"), - _×_ - (ModuleName "Torch.Sig.Tensor") - (ModuleName - "Torch.FFI.THC.Short.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Copy") - (ModuleName - "Torch.FFI.THC.Short.TensorCopy"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Memory") - (ModuleName - "Torch.FFI.THC.Short.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Index") - (ModuleName - "Torch.FFI.THC.Short.TensorIndex"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Masked") - (ModuleName - "Torch.FFI.THC.Short.TensorMasked"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math") - (ModuleName - "Torch.FFI.THC.Short.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Compare") - (ModuleName - "Torch.FFI.THC.Short.TensorMathCompare"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.CompareT") - (ModuleName - "Torch.FFI.THC.Short.TensorMathCompareT"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pairwise") - (ModuleName - "Torch.FFI.THC.Short.TensorMathPairwise"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise") - (ModuleName - "Torch.FFI.THC.Short.TensorMathPointwise"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Reduce") - (ModuleName - "Torch.FFI.THC.Short.TensorMathReduce"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Scan") - (ModuleName - "Torch.FFI.THC.Short.TensorMathScan"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Mode") - (ModuleName - "Torch.FFI.THC.Short.TensorMode"), - _×_ - (ModuleName - "Torch.Sig.Tensor.ScatterGather") - (ModuleName - "Torch.FFI.THC.Short.TensorScatterGather"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Sort") - (ModuleName - "Torch.FFI.THC.Short.TensorSort"), - _×_ - (ModuleName - "Torch.Sig.Tensor.TopK") - (ModuleName - "Torch.FFI.THC.Short.TensorTopK"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.FFI.THC.Short.TensorMathPointwise")]}}, - Mixin { - mixinPackageName = PackageName - "hasktorch", - mixinLibraryName = LSubLibName - (UnqualComponentName - "hasktorch-indef-signed"), - mixinIncludeRenaming = - IncludeRenaming { - includeProvidesRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Indef.Storage") - (ModuleName - "Torch.Indef.Cuda.Int.Storage"), - _×_ - (ModuleName - "Torch.Indef.Storage.Copy") - (ModuleName - "Torch.Indef.Cuda.Int.Storage.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor") - (ModuleName - "Torch.Indef.Cuda.Int.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Copy") - (ModuleName - "Torch.Indef.Cuda.Int.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Index") - (ModuleName - "Torch.Indef.Cuda.Int.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Masked") - (ModuleName - "Torch.Indef.Cuda.Int.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math") - (ModuleName - "Torch.Indef.Cuda.Int.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Cuda.Int.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Cuda.Int.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Cuda.Int.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Cuda.Int.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Cuda.Int.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Cuda.Int.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Mode") - (ModuleName - "Torch.Indef.Cuda.Int.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Cuda.Int.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Sort") - (ModuleName - "Torch.Indef.Cuda.Int.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.TopK") - (ModuleName - "Torch.Indef.Cuda.Int.Tensor.TopK"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor") - (ModuleName - "Torch.Indef.Cuda.Int.Dynamic.Tensor"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Copy") - (ModuleName - "Torch.Indef.Cuda.Int.Dynamic.Tensor.Copy"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Index") - (ModuleName - "Torch.Indef.Cuda.Int.Dynamic.Tensor.Index"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Masked") - (ModuleName - "Torch.Indef.Cuda.Int.Dynamic.Tensor.Masked"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math") - (ModuleName - "Torch.Indef.Cuda.Int.Dynamic.Tensor.Math"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare") - (ModuleName - "Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Compare"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT") - (ModuleName - "Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.CompareT"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise") - (ModuleName - "Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Pairwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise") - (ModuleName - "Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Pointwise"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce") - (ModuleName - "Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Reduce"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan") - (ModuleName - "Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Scan"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Mode") - (ModuleName - "Torch.Indef.Cuda.Int.Dynamic.Tensor.Mode"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather") - (ModuleName - "Torch.Indef.Cuda.Int.Dynamic.Tensor.ScatterGather"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Sort") - (ModuleName - "Torch.Indef.Cuda.Int.Dynamic.Tensor.Sort"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.TopK") - (ModuleName - "Torch.Indef.Cuda.Int.Dynamic.Tensor.TopK"), - _×_ - (ModuleName "Torch.Indef.Types") - (ModuleName - "Torch.Cuda.Int.Types"), - _×_ - (ModuleName "Torch.Indef.Index") - (ModuleName - "Torch.Cuda.Int.Index"), - _×_ - (ModuleName "Torch.Indef.Mask") - (ModuleName - "Torch.Cuda.Int.Mask"), - _×_ - (ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Cuda.Int.Tensor.Math.Pointwise.Signed"), - _×_ - (ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Pointwise.Signed")], - includeRequiresRn = - ModuleRenaming - [ - _×_ - (ModuleName - "Torch.Sig.Index.Tensor") - (ModuleName - "Torch.FFI.THC.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Index.TensorFree") - (ModuleName - "Torch.FFI.THC.Long.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.Tensor") - (ModuleName - "Torch.FFI.THC.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.TensorFree") - (ModuleName - "Torch.FFI.THC.Byte.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Mask.MathReduce") - (ModuleName - "Torch.FFI.THC.Byte.TensorMathReduce"), - _×_ - (ModuleName "Torch.Sig.State") - (ModuleName - "Torch.FFI.THC.State"), - _×_ - (ModuleName - "Torch.Sig.Types.Global") - (ModuleName "Torch.Types.THC"), - _×_ - (ModuleName "Torch.Sig.Types") - (ModuleName - "Torch.Types.THC.Int"), - _×_ - (ModuleName "Torch.Sig.Storage") - (ModuleName - "Torch.FFI.THC.Int.Storage"), - _×_ - (ModuleName - "Torch.Sig.Storage.Copy") - (ModuleName - "Torch.FFI.THC.Int.StorageCopy"), - _×_ - (ModuleName - "Torch.Sig.Storage.Memory") - (ModuleName - "Torch.FFI.THC.Int.Storage"), - _×_ - (ModuleName "Torch.Sig.Tensor") - (ModuleName - "Torch.FFI.THC.Int.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Copy") - (ModuleName - "Torch.FFI.THC.Int.TensorCopy"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Memory") - (ModuleName - "Torch.FFI.THC.Int.Tensor"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Index") - (ModuleName - "Torch.FFI.THC.Int.TensorIndex"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Masked") - (ModuleName - "Torch.FFI.THC.Int.TensorMasked"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math") - (ModuleName - "Torch.FFI.THC.Int.TensorMath"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Compare") - (ModuleName - "Torch.FFI.THC.Int.TensorMathCompare"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.CompareT") - (ModuleName - "Torch.FFI.THC.Int.TensorMathCompareT"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pairwise") - (ModuleName - "Torch.FFI.THC.Int.TensorMathPairwise"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise") - (ModuleName - "Torch.FFI.THC.Int.TensorMathPointwise"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Reduce") - (ModuleName - "Torch.FFI.THC.Int.TensorMathReduce"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Scan") - (ModuleName - "Torch.FFI.THC.Int.TensorMathScan"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Mode") - (ModuleName - "Torch.FFI.THC.Int.TensorMode"), - _×_ - (ModuleName - "Torch.Sig.Tensor.ScatterGather") - (ModuleName - "Torch.FFI.THC.Int.TensorScatterGather"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Sort") - (ModuleName - "Torch.FFI.THC.Int.TensorSort"), - _×_ - (ModuleName - "Torch.Sig.Tensor.TopK") - (ModuleName - "Torch.FFI.THC.Int.TensorTopK"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.FFI.THC.Int.TensorMathPointwise")]}}]}}, - condTreeConstraints = [ - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "hasktorch-indef-unsigned")]))], - condTreeComponents = []}}]}, - _×_ - (UnqualComponentName - "hasktorch-indef-unsigned") - CondNode { - condTreeData = Library { - libName = LSubLibName - (UnqualComponentName - "hasktorch-indef-unsigned"), - exposedModules = [], - reexportedModules = [ - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Indef.Index", - moduleReexportName = ModuleName - "Torch.Indef.Index"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Indef.Mask", - moduleReexportName = ModuleName - "Torch.Indef.Mask"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Indef.Types", - moduleReexportName = ModuleName - "Torch.Indef.Types"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Storage", - moduleReexportName = ModuleName - "Torch.Indef.Storage"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Storage.Copy", - moduleReexportName = ModuleName - "Torch.Indef.Storage.Copy"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Print", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Print"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Copy", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Copy"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Index", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Index"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Masked", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Masked"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Mode", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Mode"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Sort", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Sort"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.TopK", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.TopK"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Copy", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Copy"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Index", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Index"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Masked", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Masked"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Compare", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Compare"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Scan", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Scan"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Mode", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Mode"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.ScatterGather", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.ScatterGather"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Sort", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Sort"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.TopK", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.TopK"}], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPrivate, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName - "hasktorch-signatures-partial") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet, - Dependency - (PackageName "hasktorch-indef") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - mixins = [ - Mixin { - mixinPackageName = PackageName - "hasktorch-indef", - mixinLibraryName = LMainLibName, - mixinIncludeRenaming = - IncludeRenaming { - includeProvidesRn = - DefaultRenaming, - includeRequiresRn = - ModuleRenaming - [ - _×_ - (ModuleName "Torch.Sig.NN") - (ModuleName - "Torch.Undefined.NN"), - _×_ - (ModuleName - "Torch.Sig.Types.NN") - (ModuleName - "Torch.Undefined.Types.NN"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Blas") - (ModuleName - "Torch.Undefined.Tensor.Math.Blas"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Floating") - (ModuleName - "Torch.Undefined.Tensor.Math.Floating"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Lapack") - (ModuleName - "Torch.Undefined.Tensor.Math.Lapack"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise.Signed") - (ModuleName - "Torch.Undefined.Tensor.Math.Pointwise.Signed"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise.Floating") - (ModuleName - "Torch.Undefined.Tensor.Math.Pointwise.Floating"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Reduce.Floating") - (ModuleName - "Torch.Undefined.Tensor.Math.Reduce.Floating"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Random.TH") - (ModuleName - "Torch.Undefined.Tensor.Math.Random.TH"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Random.TH") - (ModuleName - "Torch.Undefined.Tensor.Random.TH"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Random.THC") - (ModuleName - "Torch.Undefined.Tensor.Random.THC")]}}]}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName - "hasktorch-signatures-partial") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet, - Dependency - (PackageName "hasktorch-indef") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeComponents = []}, - _×_ - (UnqualComponentName - "hasktorch-indef-signed") - CondNode { - condTreeData = Library { - libName = LSubLibName - (UnqualComponentName - "hasktorch-indef-signed"), - exposedModules = [], - reexportedModules = [ - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Indef.Index", - moduleReexportName = ModuleName - "Torch.Indef.Index"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Indef.Mask", - moduleReexportName = ModuleName - "Torch.Indef.Mask"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Indef.Types", - moduleReexportName = ModuleName - "Torch.Indef.Types"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Storage", - moduleReexportName = ModuleName - "Torch.Indef.Storage"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Storage.Copy", - moduleReexportName = ModuleName - "Torch.Indef.Storage.Copy"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Print", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Print"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Copy", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Copy"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Index", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Index"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Masked", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Masked"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Mode", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Mode"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Sort", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Sort"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.TopK", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.TopK"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Copy", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Copy"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Index", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Index"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Masked", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Masked"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Compare", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Compare"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Scan", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Scan"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Mode", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Mode"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.ScatterGather", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.ScatterGather"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Sort", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Sort"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.TopK", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.TopK"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Signed", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Signed"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed"}], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPrivate, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName - "hasktorch-signatures-partial") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet, - Dependency - (PackageName "hasktorch-indef") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - mixins = [ - Mixin { - mixinPackageName = PackageName - "hasktorch-indef", - mixinLibraryName = LMainLibName, - mixinIncludeRenaming = - IncludeRenaming { - includeProvidesRn = - DefaultRenaming, - includeRequiresRn = - ModuleRenaming - [ - _×_ - (ModuleName "Torch.Sig.NN") - (ModuleName - "Torch.Undefined.NN"), - _×_ - (ModuleName - "Torch.Sig.Types.NN") - (ModuleName - "Torch.Undefined.Types.NN"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Blas") - (ModuleName - "Torch.Undefined.Tensor.Math.Blas"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Floating") - (ModuleName - "Torch.Undefined.Tensor.Math.Floating"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Lapack") - (ModuleName - "Torch.Undefined.Tensor.Math.Lapack"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Pointwise.Floating") - (ModuleName - "Torch.Undefined.Tensor.Math.Pointwise.Floating"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Reduce.Floating") - (ModuleName - "Torch.Undefined.Tensor.Math.Reduce.Floating"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Math.Random.TH") - (ModuleName - "Torch.Undefined.Tensor.Math.Random.TH"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Random.TH") - (ModuleName - "Torch.Undefined.Tensor.Random.TH"), - _×_ - (ModuleName - "Torch.Sig.Tensor.Random.THC") - (ModuleName - "Torch.Undefined.Tensor.Random.THC")]}}]}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName - "hasktorch-signatures-partial") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet, - Dependency - (PackageName "hasktorch-indef") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeComponents = []}, - _×_ - (UnqualComponentName - "hasktorch-indef-floating") - CondNode { - condTreeData = Library { - libName = LSubLibName - (UnqualComponentName - "hasktorch-indef-floating"), - exposedModules = [], - reexportedModules = [ - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Indef.Index", - moduleReexportName = ModuleName - "Torch.Indef.Index"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Indef.Mask", - moduleReexportName = ModuleName - "Torch.Indef.Mask"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName "Torch.Indef.Types", - moduleReexportName = ModuleName - "Torch.Indef.Types"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Storage", - moduleReexportName = ModuleName - "Torch.Indef.Storage"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Storage.Copy", - moduleReexportName = ModuleName - "Torch.Indef.Storage.Copy"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Print", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Print"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Copy", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Copy"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Index", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Index"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Masked", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Masked"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Compare"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.CompareT"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pairwise"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Scan"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Mode", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Mode"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.ScatterGather"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Sort", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Sort"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.TopK", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.TopK"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Copy", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Copy"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Index", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Index"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Masked", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Masked"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Compare", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Compare"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.CompareT"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Pairwise"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Scan", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Scan"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Mode", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Mode"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.ScatterGather", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.ScatterGather"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Sort", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Sort"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.TopK", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.TopK"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Signed", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Signed"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Blas", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Blas"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Floating", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Floating"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Lapack", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Lapack"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Floating", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Floating"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce.Floating", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Reduce.Floating"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Random.TH", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Random.TH"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Random.THC", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Random.THC"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Random.TH", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.Tensor.Math.Random.TH"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Blas", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Blas"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Floating", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Floating"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Lapack", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Lapack"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Floating", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Pointwise.Floating"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce.Floating", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Reduce.Floating"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Random.TH", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Random.TH"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Random.THC", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Random.THC"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.Tensor.Math.Random.TH", - moduleReexportName = ModuleName - "Torch.Indef.Static.Tensor.Math.Random.TH"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.NN", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.NN"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.NN.Activation", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.NN.Activation"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.NN.Pooling", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.NN.Pooling"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Dynamic.NN.Criterion", - moduleReexportName = ModuleName - "Torch.Indef.Dynamic.NN.Criterion"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.NN", - moduleReexportName = ModuleName - "Torch.Indef.Static.NN"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.NN.Activation", - moduleReexportName = ModuleName - "Torch.Indef.Static.NN.Activation"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.NN.Backprop", - moduleReexportName = ModuleName - "Torch.Indef.Static.NN.Backprop"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.NN.Conv1d", - moduleReexportName = ModuleName - "Torch.Indef.Static.NN.Conv1d"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.NN.Conv2d", - moduleReexportName = ModuleName - "Torch.Indef.Static.NN.Conv2d"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.NN.Criterion", - moduleReexportName = ModuleName - "Torch.Indef.Static.NN.Criterion"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.NN.Layers", - moduleReexportName = ModuleName - "Torch.Indef.Static.NN.Layers"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.NN.Linear", - moduleReexportName = ModuleName - "Torch.Indef.Static.NN.Linear"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.NN.Math", - moduleReexportName = ModuleName - "Torch.Indef.Static.NN.Math"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.NN.Padding", - moduleReexportName = ModuleName - "Torch.Indef.Static.NN.Padding"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.NN.Pooling", - moduleReexportName = ModuleName - "Torch.Indef.Static.NN.Pooling"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Indef.Static.NN.Sampling", - moduleReexportName = ModuleName - "Torch.Indef.Static.NN.Sampling"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Undefined.Tensor.Math.Random.TH", - moduleReexportName = ModuleName - "Torch.Undefined.Tensor.Math.Random.TH"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Undefined.Tensor.Random.TH", - moduleReexportName = ModuleName - "Torch.Undefined.Tensor.Random.TH"}, - ModuleReexport { - moduleReexportOriginalPackage = - Nothing, - moduleReexportOriginalName = - ModuleName - "Torch.Undefined.Tensor.Random.THC", - moduleReexportName = ModuleName - "Torch.Undefined.Tensor.Random.THC"}], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPrivate, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "hasktorch-indef") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName - "hasktorch-signatures-partial") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "hasktorch-indef") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName - "hasktorch-signatures-partial") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 0, 1])) - (LaterVersion - (mkVersion [0, 0, 1]))) - (EarlierVersion - (mkVersion [0, 0, 2]))) - mainLibSet], - condTreeComponents = []}], - condForeignLibs = [], - condExecutables = [ - _×_ - (UnqualComponentName - "isdefinite-cpu") - CondNode { - condTreeData = Executable { - exeName = UnqualComponentName - "isdefinite-cpu", - modulePath = SymbolicPath - "Noop.hs", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 - [] - [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = - PerCompilerFlavor [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "hasktorch-cpu")]))], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "hasktorch-cpu")]))], - condTreeComponents = []}, - _×_ - (UnqualComponentName - "isdefinite-gpu") - CondNode { - condTreeData = Executable { - exeName = UnqualComponentName - "isdefinite-gpu", - modulePath = SymbolicPath - "Noop.hs", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 - [] - [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = - PerCompilerFlavor [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "hasktorch-gpu")]))], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "hasktorch-gpu")]))], - condTreeComponents = []}, - _×_ - (UnqualComponentName - "isdefinite") - CondNode { - condTreeData = Executable { - exeName = UnqualComponentName - "isdefinite", - modulePath = SymbolicPath - "Noop.hs", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 - [] - [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = - PerCompilerFlavor [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeComponents = []}, - _×_ - (UnqualComponentName "memcheck") - CondNode { - condTreeData = Executable { - exeName = UnqualComponentName - "memcheck", - modulePath = SymbolicPath - "Memcheck.hs", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 - [] - [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = - PerCompilerFlavor [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeComponents = []}], - condTestSuites = [ - _×_ - (UnqualComponentName "spec") - CondNode { - condTreeData = TestSuite { - testName = UnqualComponentName - "", - testInterface = TestSuiteExeV10 - (mkVersion [1, 0]) - (SymbolicPath "Spec.hs"), - testBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - asmOptions = [], - cmmOptions = [], - ccOptions = [], - cxxOptions = [], - ldOptions = [], - hsc2hsOptions = [], - pkgconfigDepends = [], - frameworks = [], - extraFrameworkDirs = [], - asmSources = [], - cmmSources = [], - cSources = [], - cxxSources = [], - jsSources = [], - hsSourceDirs = [ - SymbolicPath "tests"], - otherModules = [ - ModuleName "Orphans", - ModuleName "MemorySpec", - ModuleName "RawLapackSVDSpec", - ModuleName - "GarbageCollectionSpec", - ModuleName - "Torch.Prelude.Extras", - ModuleName - "Torch.Core.LogAddSpec", - ModuleName - "Torch.Core.RandomSpec", - ModuleName - "Torch.Static.NN.AbsSpec", - ModuleName - "Torch.Static.NN.LinearSpec"], - virtualModules = [], - autogenModules = [], - defaultLanguage = Just - Haskell2010, - otherLanguages = [], - defaultExtensions = [ - EnableExtension LambdaCase, - EnableExtension DataKinds, - EnableExtension TypeFamilies, - EnableExtension - TypeSynonymInstances, - EnableExtension - ScopedTypeVariables, - EnableExtension - FlexibleContexts, - EnableExtension CPP], - otherExtensions = [], - oldExtensions = [], - extraLibs = [], - extraLibsStatic = [], - extraGHCiLibs = [], - extraBundledLibs = [], - extraLibFlavours = [], - extraDynLibFlavours = [], - extraLibDirs = [], - extraLibDirsStatic = [], - includeDirs = [], - includes = [], - autogenIncludes = [], - installIncludes = [], - options = PerCompilerFlavor - [] - [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = - PerCompilerFlavor [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "QuickCheck") - (UnionVersionRanges - (ThisVersion - (mkVersion [2, 11])) - (LaterVersion - (mkVersion [2, 11]))) - mainLibSet, - Dependency - (PackageName "backprop") - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 2, 5])) - (LaterVersion - (mkVersion [0, 2, 5]))) - mainLibSet, - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "dimensions") - (UnionVersionRanges - (ThisVersion (mkVersion [1, 0])) - (LaterVersion - (mkVersion [1, 0]))) - mainLibSet, - Dependency - (PackageName - "ghc-typelits-natnormalise") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "hspec") - (UnionVersionRanges - (ThisVersion - (mkVersion [2, 4, 4])) - (LaterVersion - (mkVersion [2, 4, 4]))) - mainLibSet, - Dependency - (PackageName "singletons") - (UnionVersionRanges - (ThisVersion (mkVersion [2, 2])) - (LaterVersion - (mkVersion [2, 2]))) - mainLibSet, - Dependency - (PackageName "mtl") - (UnionVersionRanges - (ThisVersion - (mkVersion [2, 2, 2])) - (LaterVersion - (mkVersion [2, 2, 2]))) - mainLibSet, - Dependency - (PackageName - "microlens-platform") - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 3, 10])) - (LaterVersion - (mkVersion [0, 3, 10]))) - mainLibSet, - Dependency - (PackageName "monad-loops") - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 4, 3])) - (LaterVersion - (mkVersion [0, 4, 3]))) - mainLibSet, - Dependency - (PackageName "time") - (UnionVersionRanges - (ThisVersion - (mkVersion [1, 8, 0])) - (LaterVersion - (mkVersion [1, 8, 0]))) - mainLibSet, - Dependency - (PackageName "transformers") - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 5, 5])) - (LaterVersion - (mkVersion [0, 5, 5]))) - mainLibSet, - Dependency - (PackageName "generic-lens") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - mixins = []}, - testCodeGenerators = []}, - condTreeConstraints = [ - Dependency - (PackageName "QuickCheck") - (UnionVersionRanges - (ThisVersion - (mkVersion [2, 11])) - (LaterVersion - (mkVersion [2, 11]))) - mainLibSet, - Dependency - (PackageName "backprop") - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 2, 5])) - (LaterVersion - (mkVersion [0, 2, 5]))) - mainLibSet, - Dependency - (PackageName "base") - (IntersectVersionRanges - (UnionVersionRanges - (ThisVersion (mkVersion [4, 7])) - (LaterVersion - (mkVersion [4, 7]))) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "dimensions") - (UnionVersionRanges - (ThisVersion (mkVersion [1, 0])) - (LaterVersion - (mkVersion [1, 0]))) - mainLibSet, - Dependency - (PackageName - "ghc-typelits-natnormalise") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "hasktorch") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "hspec") - (UnionVersionRanges - (ThisVersion - (mkVersion [2, 4, 4])) - (LaterVersion - (mkVersion [2, 4, 4]))) - mainLibSet, - Dependency - (PackageName "singletons") - (UnionVersionRanges - (ThisVersion (mkVersion [2, 2])) - (LaterVersion - (mkVersion [2, 2]))) - mainLibSet, - Dependency - (PackageName "mtl") - (UnionVersionRanges - (ThisVersion - (mkVersion [2, 2, 2])) - (LaterVersion - (mkVersion [2, 2, 2]))) - mainLibSet, - Dependency - (PackageName - "microlens-platform") - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 3, 10])) - (LaterVersion - (mkVersion [0, 3, 10]))) - mainLibSet, - Dependency - (PackageName "monad-loops") - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 4, 3])) - (LaterVersion - (mkVersion [0, 4, 3]))) - mainLibSet, - Dependency - (PackageName "time") - (UnionVersionRanges - (ThisVersion - (mkVersion [1, 8, 0])) - (LaterVersion - (mkVersion [1, 8, 0]))) - mainLibSet, - Dependency - (PackageName "transformers") - (UnionVersionRanges - (ThisVersion - (mkVersion [0, 5, 5])) - (LaterVersion - (mkVersion [0, 5, 5]))) - mainLibSet, - Dependency - (PackageName "generic-lens") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeComponents = []}], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/hasktorch.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/hasktorch.genPackageFlags.expr new file mode 100644 index 00000000000..b9b52ac0345 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/hasktorch.genPackageFlags.expr @@ -0,0 +1,13 @@ +[ + MkPackageFlag { + flagName = FlagName "cuda", + flagDescription = + "build with THC support", + flagDefault = False, + flagManual = False}, + MkPackageFlag { + flagName = FlagName "lite", + flagDescription = + "only build with Double and Long support", + flagDefault = False, + flagManual = False}] diff --git a/Cabal-tests/tests/ParserTests/regressions/hasktorch.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/hasktorch.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/hasktorch.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/hasktorch.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/hasktorch.packageDescription.expr new file mode 100644 index 00000000000..aa61f8bf394 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/hasktorch.packageDescription.expr @@ -0,0 +1,56 @@ +PackageDescription { + specVersion = CabalSpecV2_2, + package = PackageIdentifier { + pkgName = PackageName + "hasktorch", + pkgVersion = mkVersion + [0, 0, 1, 0]}, + licenseRaw = Left + (License + (ELicense + (ELicenseId BSD_3_Clause) + Nothing)), + licenseFiles = [], + copyright = "", + maintainer = + "Sam Stites , Austin Huang - cipher:ROT13", + author = "Hasktorch dev team", + stability = "", + testedWith = [], + homepage = + "https://github.com/hasktorch/hasktorch#readme", + pkgUrl = "", + bugReports = + "https://github.com/hasktorch/hasktorch/issues", + sourceRepos = [ + SourceRepo { + repoKind = RepoHead, + repoType = Just + (KnownRepoType Git), + repoLocation = Just + "https://github.com/hasktorch/hasktorch", + repoModule = Nothing, + repoBranch = Nothing, + repoTag = Nothing, + repoSubdir = Nothing}], + synopsis = + "Torch for tensors and neural networks in Haskell", + description = + "Hasktorch is a library for tensors and neural networks in Haskell. It is an independent open source community project which leverages the core C libraries shared by Torch and PyTorch. This library leverages @cabal v2-build@ and @backpack@. *Note that this project is in early development and should only be used by contributing developers. Expect substantial changes to the library API as it evolves. Contributions and PRs are welcome (see details on github).*", + category = + "Tensors, Machine Learning, AI", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.condLibrary.expr new file mode 100644 index 00000000000..1b03802a873 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.condLibrary.expr @@ -0,0 +1,78 @@ +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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.packageDescription.expr new file mode 100644 index 00000000000..9d4eb147c16 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.packageDescription.expr @@ -0,0 +1,36 @@ +PackageDescription { + specVersion = CabalSpecV3_0, + package = PackageIdentifier { + pkgName = PackageName + "hidden-main-lib", + pkgVersion = mkVersion [0]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = + "main lib have to be visible", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/indentation.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/indentation.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/indentation.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/indentation.condLibrary.expr new file mode 100644 index 00000000000..acc4281010f --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation.condLibrary.expr @@ -0,0 +1,69 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/indentation.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/indentation.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation.expr b/Cabal-tests/tests/ParserTests/regressions/indentation.expr deleted file mode 100644 index f36a8997717..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/indentation.expr +++ /dev/null @@ -1,124 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV3_0, - package = PackageIdentifier { - pkgName = PackageName - "indentation", - pkgVersion = mkVersion [0]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = "", - description = concat - [ - "* foo\n", - "\n", - " * foo-bar\n", - "\n", - " * foo-baz\n", - "\n", - ".\n", - ".\n", - ".\n", - "some dots"], - category = "", - customFieldsPD = [], - buildTypeRaw = Nothing, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/indentation.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/indentation.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/indentation.packageDescription.expr new file mode 100644 index 00000000000..ce48c84b316 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation.packageDescription.expr @@ -0,0 +1,46 @@ +PackageDescription { + specVersion = CabalSpecV3_0, + package = PackageIdentifier { + pkgName = PackageName + "indentation", + pkgVersion = mkVersion [0]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = "", + description = concat + [ + "* foo\n", + "\n", + " * foo-bar\n", + "\n", + " * foo-baz\n", + "\n", + ".\n", + ".\n", + ".\n", + "some dots"], + category = "", + customFieldsPD = [], + buildTypeRaw = Nothing, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation2.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/indentation2.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation2.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation2.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/indentation2.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation2.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation2.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/indentation2.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation2.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation2.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/indentation2.condLibrary.expr new file mode 100644 index 00000000000..acc4281010f --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation2.condLibrary.expr @@ -0,0 +1,69 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation2.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/indentation2.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation2.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation2.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/indentation2.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation2.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation2.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/indentation2.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation2.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation2.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/indentation2.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation2.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation2.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/indentation2.packageDescription.expr new file mode 100644 index 00000000000..7078d47db01 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation2.packageDescription.expr @@ -0,0 +1,39 @@ +PackageDescription { + specVersion = CabalSpecV3_0, + package = PackageIdentifier { + pkgName = PackageName + "indentation", + pkgVersion = mkVersion [0]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = "", + description = concat + [ + "foo\n", + " indent2\n", + " indent4"], + category = "", + customFieldsPD = [], + buildTypeRaw = Nothing, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation3.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/indentation3.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation3.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation3.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/indentation3.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation3.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation3.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/indentation3.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation3.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation3.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/indentation3.condLibrary.expr new file mode 100644 index 00000000000..acc4281010f --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation3.condLibrary.expr @@ -0,0 +1,69 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation3.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/indentation3.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation3.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation3.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/indentation3.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation3.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation3.expr b/Cabal-tests/tests/ParserTests/regressions/indentation3.expr deleted file mode 100644 index 964bad3f924..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/indentation3.expr +++ /dev/null @@ -1,119 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV3_0, - package = PackageIdentifier { - pkgName = PackageName - "indentation", - pkgVersion = mkVersion [0]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = "", - description = concat - [ - "indent0\n", - "\n", - " indent2\n", - "indent0\n", - " indent2"], - category = "", - customFieldsPD = [], - buildTypeRaw = Nothing, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation3.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/indentation3.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation3.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation3.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/indentation3.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation3.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation3.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/indentation3.packageDescription.expr new file mode 100644 index 00000000000..d45c69b7b6d --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/indentation3.packageDescription.expr @@ -0,0 +1,41 @@ +PackageDescription { + specVersion = CabalSpecV3_0, + package = PackageIdentifier { + pkgName = PackageName + "indentation", + pkgVersion = mkVersion [0]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = "", + description = concat + [ + "indent0\n", + "\n", + " indent2\n", + "indent0\n", + " indent2"], + category = "", + customFieldsPD = [], + buildTypeRaw = Nothing, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5055.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5055.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5055.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/noVersion.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5055.condExecutables.expr similarity index 52% rename from Cabal-tests/tests/ParserTests/regressions/noVersion.expr rename to Cabal-tests/tests/ParserTests/regressions/issue-5055.condExecutables.expr index 838f87733eb..e5d3ff28be8 100644 --- a/Cabal-tests/tests/ParserTests/regressions/noVersion.expr +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5055.condExecutables.expr @@ -1,64 +1,24 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV1_22, - package = PackageIdentifier { - pkgName = PackageName - "noVersion", - pkgVersion = mkVersion [0]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = - "-none in build-depends", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Just Simple, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just +[ + _×_ + (UnqualComponentName + "flag-test-exe") CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [ - ModuleName "ElseIf"], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { + condTreeData = Executable { + exeName = UnqualComponentName + "flag-test-exe", + modulePath = SymbolicPath + "FirstMain.hs", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { buildable = True, buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -106,18 +66,21 @@ GenericPackageDescription { customFieldsBI = [], targetBuildDepends = [ Dependency - (PackageName "bad-package") - (EarlierVersion (mkVersion [0])) + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 8])) + (EarlierVersion + (mkVersion [5]))) mainLibSet], mixins = []}}, condTreeConstraints = [ Dependency - (PackageName "bad-package") - (EarlierVersion (mkVersion [0])) + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 8])) + (EarlierVersion + (mkVersion [5]))) mainLibSet], - condTreeComponents = []}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} + condTreeComponents = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5055.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5055.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5055.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5055.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5055.condLibrary.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5055.condLibrary.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5055.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5055.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5055.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5055.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5055.condTestSuites.expr new file mode 100644 index 00000000000..ce285aa1d22 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5055.condTestSuites.expr @@ -0,0 +1,159 @@ +[ + _×_ + (UnqualComponentName + "flag-cabal-test") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + (SymbolicPath "SecondMain.hs"), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5055.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5055.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5055.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5055.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5055.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5055.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5055.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5055.packageDescription.expr new file mode 100644 index 00000000000..bdd807fb337 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5055.packageDescription.expr @@ -0,0 +1,36 @@ +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 = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5846.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5846.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5846.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5846.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5846.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5846.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5846.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5846.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5846.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5846.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5846.condLibrary.expr new file mode 100644 index 00000000000..f8e88eb982a --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5846.condLibrary.expr @@ -0,0 +1,141 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "lib1") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName "a"), + LSubLibName + (UnqualComponentName "b")])), + Dependency + (PackageName "lib2") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName "c")])), + Dependency + (PackageName "lib3") + (OrLaterVersion (mkVersion [1])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName "d")])), + Dependency + (PackageName "lib4") + (OrLaterVersion (mkVersion [1])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName "a"), + LSubLibName + (UnqualComponentName "b")]))], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "lib1") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName "a"), + LSubLibName + (UnqualComponentName "b")])), + Dependency + (PackageName "lib2") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName "c")])), + Dependency + (PackageName "lib3") + (OrLaterVersion (mkVersion [1])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName "d")])), + Dependency + (PackageName "lib4") + (OrLaterVersion (mkVersion [1])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName "a"), + LSubLibName + (UnqualComponentName "b")]))], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5846.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5846.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5846.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5846.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5846.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5846.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5846.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5846.expr deleted file mode 100644 index c3e08359046..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/issue-5846.expr +++ /dev/null @@ -1,184 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV3_0, - package = PackageIdentifier { - pkgName = PackageName "issue", - pkgVersion = mkVersion [5846]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = "", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Nothing, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "lib1") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName "a"), - LSubLibName - (UnqualComponentName "b")])), - Dependency - (PackageName "lib2") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName "c")])), - Dependency - (PackageName "lib3") - (OrLaterVersion (mkVersion [1])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName "d")])), - Dependency - (PackageName "lib4") - (OrLaterVersion (mkVersion [1])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName "a"), - LSubLibName - (UnqualComponentName "b")]))], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "lib1") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName "a"), - LSubLibName - (UnqualComponentName "b")])), - Dependency - (PackageName "lib2") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName "c")])), - Dependency - (PackageName "lib3") - (OrLaterVersion (mkVersion [1])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName "d")])), - Dependency - (PackageName "lib4") - (OrLaterVersion (mkVersion [1])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName "a"), - LSubLibName - (UnqualComponentName "b")]))], - condTreeComponents = []}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5846.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5846.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5846.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5846.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5846.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5846.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5846.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5846.packageDescription.expr new file mode 100644 index 00000000000..2ece144e2cb --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5846.packageDescription.expr @@ -0,0 +1,34 @@ +PackageDescription { + specVersion = CabalSpecV3_0, + package = PackageIdentifier { + pkgName = PackageName "issue", + pkgVersion = mkVersion [5846]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = "", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Nothing, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.condExecutables.expr new file mode 100644 index 00000000000..7145f97f84a --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.condExecutables.expr @@ -0,0 +1,177 @@ +[ + _×_ + (UnqualComponentName "demo-a") + CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "demo-a", + modulePath = SymbolicPath + "Main.hs", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "issue") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "sublib") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "issue") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "sublib") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + _×_ + (UnqualComponentName "demo-b") + CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "demo-b", + modulePath = SymbolicPath + "Main.hs", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "issue") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "issue") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "sublib")]))], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "issue") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "issue") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "sublib")]))], + condTreeComponents = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.condLibrary.expr new file mode 100644 index 00000000000..9352f80235b --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.condLibrary.expr @@ -0,0 +1,95 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "issue") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "sublib")]))], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "issue") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "sublib")]))], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/big-version.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.condSubLibraries.expr similarity index 61% rename from Cabal-tests/tests/ParserTests/regressions/big-version.expr rename to Cabal-tests/tests/ParserTests/regressions/issue-6083-a.condSubLibraries.expr index 4d3659e4592..683d108f25c 100644 --- a/Cabal-tests/tests/ParserTests/regressions/big-version.expr +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.condSubLibraries.expr @@ -1,63 +1,26 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV3_0, - package = PackageIdentifier { - pkgName = PackageName - "big-version", - pkgVersion = mkVersion - [123456789]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = "", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Nothing, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just +[ + _×_ + (UnqualComponentName "sublib") CondNode { condTreeData = Library { - libName = LMainLibName, + libName = LSubLibName + (UnqualComponentName "sublib"), exposedModules = [], reexportedModules = [], signatures = [], libExposed = True, libVisibility = - LibraryVisibilityPublic, + LibraryVisibilityPrivate, libBuildInfo = BuildInfo { buildable = True, buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -106,9 +69,4 @@ GenericPackageDescription { targetBuildDepends = [], mixins = []}}, condTreeConstraints = [], - condTreeComponents = []}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} + condTreeComponents = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.expr deleted file mode 100644 index 001d3c86515..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.expr +++ /dev/null @@ -1,385 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV3_4, - package = PackageIdentifier { - pkgName = PackageName "issue", - pkgVersion = mkVersion [6083]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = "", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Nothing, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "issue") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "sublib")]))], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "issue") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "sublib")]))], - condTreeComponents = []}, - condSubLibraries = [ - _×_ - (UnqualComponentName "sublib") - CondNode { - condTreeData = Library { - libName = LSubLibName - (UnqualComponentName "sublib"), - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPrivate, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}], - condForeignLibs = [], - condExecutables = [ - _×_ - (UnqualComponentName "demo-a") - CondNode { - condTreeData = Executable { - exeName = UnqualComponentName - "demo-a", - modulePath = SymbolicPath - "Main.hs", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "issue") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "sublib") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "issue") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "sublib") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeComponents = []}, - _×_ - (UnqualComponentName "demo-b") - CondNode { - condTreeData = Executable { - exeName = UnqualComponentName - "demo-b", - modulePath = SymbolicPath - "Main.hs", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "issue") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "issue") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "sublib")]))], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "issue") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "issue") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "sublib")]))], - condTreeComponents = []}], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.packageDescription.expr new file mode 100644 index 00000000000..79deb33cd0d --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.packageDescription.expr @@ -0,0 +1,34 @@ +PackageDescription { + specVersion = CabalSpecV3_4, + package = PackageIdentifier { + pkgName = PackageName "issue", + pkgVersion = mkVersion [6083]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = "", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Nothing, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.condExecutables.expr new file mode 100644 index 00000000000..bc6b77953f5 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.condExecutables.expr @@ -0,0 +1,187 @@ +[ + _×_ + (UnqualComponentName "demo-a") + CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "demo-a", + modulePath = SymbolicPath + "Main.hs", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "issue") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "issue") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "sublib")]))], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "issue") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "issue") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "sublib")]))], + condTreeComponents = []}, + _×_ + (UnqualComponentName "demo-b") + CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "demo-b", + modulePath = SymbolicPath + "Main.hs", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "issue") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "issue") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "sublib")]))], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "issue") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "issue") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "sublib")]))], + condTreeComponents = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.condLibrary.expr new file mode 100644 index 00000000000..9352f80235b --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.condLibrary.expr @@ -0,0 +1,95 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "issue") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "sublib")]))], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "issue") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "sublib")]))], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-1.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.condSubLibraries.expr similarity index 60% rename from Cabal-tests/tests/ParserTests/regressions/spdx-1.expr rename to Cabal-tests/tests/ParserTests/regressions/issue-6083-b.condSubLibraries.expr index 88500d2d365..683d108f25c 100644 --- a/Cabal-tests/tests/ParserTests/regressions/spdx-1.expr +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.condSubLibraries.expr @@ -1,62 +1,26 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV2_0, - package = PackageIdentifier { - pkgName = PackageName "spdx", - pkgVersion = mkVersion [0]}, - licenseRaw = Right BSD3, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = - "testing positive parsing of spdx identifiers", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Just Simple, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just +[ + _×_ + (UnqualComponentName "sublib") CondNode { condTreeData = Library { - libName = LMainLibName, + libName = LSubLibName + (UnqualComponentName "sublib"), exposedModules = [], reexportedModules = [], signatures = [], libExposed = True, libVisibility = - LibraryVisibilityPublic, + LibraryVisibilityPrivate, libBuildInfo = BuildInfo { buildable = True, buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -105,9 +69,4 @@ GenericPackageDescription { targetBuildDepends = [], mixins = []}}, condTreeConstraints = [], - condTreeComponents = []}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} + condTreeComponents = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.expr deleted file mode 100644 index ca99e3d554f..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.expr +++ /dev/null @@ -1,395 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV3_0, - package = PackageIdentifier { - pkgName = PackageName "issue", - pkgVersion = mkVersion [6083]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = "", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Nothing, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "issue") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "sublib")]))], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "issue") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "sublib")]))], - condTreeComponents = []}, - condSubLibraries = [ - _×_ - (UnqualComponentName "sublib") - CondNode { - condTreeData = Library { - libName = LSubLibName - (UnqualComponentName "sublib"), - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPrivate, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}], - condForeignLibs = [], - condExecutables = [ - _×_ - (UnqualComponentName "demo-a") - CondNode { - condTreeData = Executable { - exeName = UnqualComponentName - "demo-a", - modulePath = SymbolicPath - "Main.hs", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "issue") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "issue") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "sublib")]))], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "issue") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "issue") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "sublib")]))], - condTreeComponents = []}, - _×_ - (UnqualComponentName "demo-b") - CondNode { - condTreeData = Executable { - exeName = UnqualComponentName - "demo-b", - modulePath = SymbolicPath - "Main.hs", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "issue") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "issue") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "sublib")]))], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "issue") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "issue") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "sublib")]))], - condTreeComponents = []}], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.packageDescription.expr new file mode 100644 index 00000000000..49cc3c9294e --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.packageDescription.expr @@ -0,0 +1,34 @@ +PackageDescription { + specVersion = CabalSpecV3_0, + package = PackageIdentifier { + pkgName = PackageName "issue", + pkgVersion = mkVersion [6083]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = "", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Nothing, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.condLibrary.expr new file mode 100644 index 00000000000..9352f80235b --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.condLibrary.expr @@ -0,0 +1,95 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "issue") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "sublib")]))], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "issue") + (OrLaterVersion (mkVersion [0])) + (NonEmptySet.fromNonEmpty + (NE.fromList + [ + LSubLibName + (UnqualComponentName + "sublib")]))], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation2.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.condSubLibraries.expr similarity index 60% rename from Cabal-tests/tests/ParserTests/regressions/indentation2.expr rename to Cabal-tests/tests/ParserTests/regressions/issue-6083-c.condSubLibraries.expr index 11afbcfd5d3..683d108f25c 100644 --- a/Cabal-tests/tests/ParserTests/regressions/indentation2.expr +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.condSubLibraries.expr @@ -1,66 +1,26 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV3_0, - package = PackageIdentifier { - pkgName = PackageName - "indentation", - pkgVersion = mkVersion [0]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = "", - description = concat - [ - "foo\n", - " indent2\n", - " indent4"], - category = "", - customFieldsPD = [], - buildTypeRaw = Nothing, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just +[ + _×_ + (UnqualComponentName "sublib") CondNode { condTreeData = Library { - libName = LMainLibName, + libName = LSubLibName + (UnqualComponentName "sublib"), exposedModules = [], reexportedModules = [], signatures = [], libExposed = True, libVisibility = - LibraryVisibilityPublic, + LibraryVisibilityPrivate, libBuildInfo = BuildInfo { buildable = True, buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -109,9 +69,4 @@ GenericPackageDescription { targetBuildDepends = [], mixins = []}}, condTreeConstraints = [], - condTreeComponents = []}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} + condTreeComponents = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.expr deleted file mode 100644 index b2f47a1a938..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.expr +++ /dev/null @@ -1,209 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV2_4, - package = PackageIdentifier { - pkgName = PackageName "issue", - pkgVersion = mkVersion [6083]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = "", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Nothing, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "issue") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "sublib")]))], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "issue") - (OrLaterVersion (mkVersion [0])) - (NonEmptySet.fromNonEmpty - (NE.fromList - [ - LSubLibName - (UnqualComponentName - "sublib")]))], - condTreeComponents = []}, - condSubLibraries = [ - _×_ - (UnqualComponentName "sublib") - CondNode { - condTreeData = Library { - libName = LSubLibName - (UnqualComponentName "sublib"), - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPrivate, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.packageDescription.expr new file mode 100644 index 00000000000..b8924725b32 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.packageDescription.expr @@ -0,0 +1,34 @@ +PackageDescription { + specVersion = CabalSpecV2_4, + package = PackageIdentifier { + pkgName = PackageName "issue", + pkgVersion = mkVersion [6083]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = "", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Nothing, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.condLibrary.expr new file mode 100644 index 00000000000..a7a2b77605a --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.condLibrary.expr @@ -0,0 +1,85 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "freetype") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "freetype") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "freetype") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "freetype") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.packageDescription.expr new file mode 100644 index 00000000000..49cc3c9294e --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.packageDescription.expr @@ -0,0 +1,34 @@ +PackageDescription { + specVersion = CabalSpecV3_0, + package = PackageIdentifier { + pkgName = PackageName "issue", + pkgVersion = mkVersion [6083]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = "", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Nothing, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-774.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/issue-774.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-774.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-774.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/issue-774.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-774.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-774.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/issue-774.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-774.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-774.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/issue-774.condLibrary.expr new file mode 100644 index 00000000000..0f7e3c6c197 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-774.condLibrary.expr @@ -0,0 +1,74 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName "Issue"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 + [ + "-Wall", + "-threaded", + "-with-rtsopts=-N -s -M1G -c", + "-rtsopts"] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-774.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/issue-774.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-774.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-774.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/issue-774.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-774.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-774.expr b/Cabal-tests/tests/ParserTests/regressions/issue-774.expr deleted file mode 100644 index 4aeb65cb960..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/issue-774.expr +++ /dev/null @@ -1,126 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV1_12, - package = PackageIdentifier { - pkgName = PackageName "issue", - pkgVersion = mkVersion [744]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = - "Package description parser interprets curly braces in the description field", - description = concat - [ - "Here is some C code:\n", - "\n", - "> for(i = 0; i < 100; i++) {\n", - "> printf(\"%d\\n\",i);\n", - "> }\n", - "\n", - "What does it look like?"], - category = "", - customFieldsPD = [], - buildTypeRaw = Just Simple, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [ - ModuleName "Issue"], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 - [ - "-Wall", - "-threaded", - "-with-rtsopts=-N -s -M1G -c", - "-rtsopts"] - [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = - PerCompilerFlavor [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-774.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/issue-774.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-774.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-774.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/issue-774.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-774.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-774.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/issue-774.packageDescription.expr new file mode 100644 index 00000000000..c1c38cabb20 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/issue-774.packageDescription.expr @@ -0,0 +1,43 @@ +PackageDescription { + specVersion = CabalSpecV1_12, + package = PackageIdentifier { + pkgName = PackageName "issue", + pkgVersion = mkVersion [744]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = + "Package description parser interprets curly braces in the description field", + description = concat + [ + "Here is some C code:\n", + "\n", + "> for(i = 0; i < 100; i++) {\n", + "> printf(\"%d\\n\",i);\n", + "> }\n", + "\n", + "What does it look like?"], + category = "", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.condExecutables.expr new file mode 100644 index 00000000000..898e1a70cc5 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.condExecutables.expr @@ -0,0 +1,162 @@ +[ + _×_ + (UnqualComponentName + "jaeger-flamegraph") + CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "jaeger-flamegraph", + modulePath = SymbolicPath + "Main.hs", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.condLibrary.expr new file mode 100644 index 00000000000..ab02aceb7eb --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.condLibrary.expr @@ -0,0 +1,99 @@ +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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.condTestSuites.expr new file mode 100644 index 00000000000..f209c1cfd6b --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.condTestSuites.expr @@ -0,0 +1,137 @@ +[ + _×_ + (UnqualComponentName "tests") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + (SymbolicPath "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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.expr b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.expr deleted file mode 100644 index b6dc81fee1b..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.expr +++ /dev/null @@ -1,480 +0,0 @@ -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 () 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 = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = SymbolicPath - "Main.hs", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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]) - (SymbolicPath "Driver.hs"), - testBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [ - ExeDependency - (PackageName "tasty-discover") - (UnqualComponentName - "tasty-discover") - (MajorBoundVersion - (mkVersion [4, 2, 1]))], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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/jaeger-flamegraph.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.packageDescription.expr new file mode 100644 index 00000000000..0c99139282a --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.packageDescription.expr @@ -0,0 +1,75 @@ +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 () 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 = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.condLibrary.expr new file mode 100644 index 00000000000..e30c14b8e37 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.condLibrary.expr @@ -0,0 +1,125 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName "LeadingComma", + ModuleName "LeadingComma2", + ModuleName "TrailingComma", + ModuleName "TrailingComma", + ModuleName "Comma", + ModuleName "InBetween", + ModuleName "NoCommas", + ModuleName "NoCommas"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "containers") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "deepseq") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "transformers") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "filepath") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "directory") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "containers") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "deepseq") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "transformers") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "filepath") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "directory") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.expr deleted file mode 100644 index 3a1d7d5f075..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.expr +++ /dev/null @@ -1,170 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV3_0, - package = PackageIdentifier { - pkgName = PackageName - "leading-comma", - pkgVersion = mkVersion [0]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = - "leading comma, trailing comma, or ordinary", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Just Simple, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [ - ModuleName "LeadingComma", - ModuleName "LeadingComma2", - ModuleName "TrailingComma", - ModuleName "TrailingComma", - ModuleName "Comma", - ModuleName "InBetween", - ModuleName "NoCommas", - ModuleName "NoCommas"], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "containers") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "deepseq") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "transformers") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "filepath") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "directory") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "containers") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "deepseq") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "transformers") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "filepath") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "directory") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeComponents = []}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.packageDescription.expr new file mode 100644 index 00000000000..172607af223 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.packageDescription.expr @@ -0,0 +1,36 @@ +PackageDescription { + specVersion = CabalSpecV3_0, + package = PackageIdentifier { + pkgName = PackageName + "leading-comma", + pkgVersion = mkVersion [0]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = + "leading comma, trailing comma, or ordinary", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/leading-comma.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/leading-comma.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/leading-comma.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma.condLibrary.expr new file mode 100644 index 00000000000..a77d7534266 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/leading-comma.condLibrary.expr @@ -0,0 +1,118 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName "LeadingComma"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "containers") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "deepseq") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "transformers") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "filepath") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "directory") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "containers") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "deepseq") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "transformers") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "filepath") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "directory") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/leading-comma.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/leading-comma.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma.expr deleted file mode 100644 index 230ebf53136..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/leading-comma.expr +++ /dev/null @@ -1,163 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV2_2, - package = PackageIdentifier { - pkgName = PackageName - "leading-comma", - pkgVersion = mkVersion [0]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = - "leading comma, trailing comma, or ordinary", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Just Simple, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [ - ModuleName "LeadingComma"], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "containers") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "deepseq") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "transformers") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "filepath") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "directory") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "containers") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "deepseq") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "transformers") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "filepath") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "directory") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeComponents = []}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/leading-comma.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/leading-comma.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma.packageDescription.expr new file mode 100644 index 00000000000..e4fa9e2e1f3 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/leading-comma.packageDescription.expr @@ -0,0 +1,36 @@ +PackageDescription { + specVersion = CabalSpecV2_2, + package = PackageIdentifier { + pkgName = PackageName + "leading-comma", + pkgVersion = mkVersion [0]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = + "leading comma, trailing comma, or ordinary", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq1.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/libpq1.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/libpq1.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq1.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/libpq1.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/libpq1.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq1.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/libpq1.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/libpq1.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq1.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/libpq1.condLibrary.expr new file mode 100644 index 00000000000..d8678f30f5e --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/libpq1.condLibrary.expr @@ -0,0 +1,641 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName + "Database.PostgreSQL.LibPQ", + ModuleName + "Database.PostgreSQL.LibPQ.Internal"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [ + LegacyExeDependency + "hsc2hs" + (OrLaterVersion + (mkVersion [0]))], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [ + SymbolicPath + "cbits/noticehandlers.c"], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "src"], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [ + SymbolicPath "cbits"], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + ["-Wall"] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 3])) + (EarlierVersion + (mkVersion [4, 13]))) + mainLibSet, + Dependency + (PackageName "bytestring") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 9, 1, 0])) + (EarlierVersion + (mkVersion [0, 11]))) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 3])) + (EarlierVersion + (mkVersion [4, 13]))) + mainLibSet, + Dependency + (PackageName "bytestring") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 9, 1, 0])) + (EarlierVersion + (mkVersion [0, 11]))) + mainLibSet], + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "unix") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [2, 4, 2, 0])) + (EarlierVersion + (mkVersion [2, 8]))) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "unix") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [2, 4, 2, 0])) + (EarlierVersion + (mkVersion [2, 8]))) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}, + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "Win32") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [2, 2, 0, 2])) + (EarlierVersion + (mkVersion [2, 7]))) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "Win32") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [2, 2, 0, 2])) + (EarlierVersion + (mkVersion [2, 7]))) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}, + CondBranch { + condBranchCondition = + `Var (PackageFlag (FlagName "use-pkg-config"))`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [ + PkgconfigDependency + (PkgconfigName "libpq") + (PcIntersectVersionRanges + (PcOrLaterVersion + (PkgconfigVersion "9")) + (PcEarlierVersion + (PkgconfigVersion "10")))], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []}, + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + 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 = [], + jsppOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = ["libpq"], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []}, + 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 = [], + jsppOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = ["pq"], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `Var (OS OpenBSD)`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = ["crypto", "ssl"], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = + Nothing}]}}]}}]} diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq1.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/libpq1.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/libpq1.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq1.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/libpq1.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/libpq1.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq1.expr b/Cabal-tests/tests/ParserTests/regressions/libpq1.expr deleted file mode 100644 index b331abffcca..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/libpq1.expr +++ /dev/null @@ -1,769 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV1_8, - package = PackageIdentifier { - pkgName = PackageName - "postgresql-libpq", - pkgVersion = mkVersion - [0, 9, 4, 2]}, - licenseRaw = Right BSD3, - licenseFiles = [ - SymbolicPath "LICENSE"], - copyright = concat - [ - "(c) 2010 Grant Monroe\n", - "(c) 2011 Leon P Smith"], - maintainer = - "Oleg Grenrus ", - author = - "Grant Monroe, Leon P Smith, Joey Adams", - stability = "", - testedWith = [ - _×_ - GHC - (ThisVersion - (mkVersion [7, 0, 4])), - _×_ - GHC - (ThisVersion - (mkVersion [7, 2, 2])), - _×_ - GHC - (ThisVersion - (mkVersion [7, 4, 2])), - _×_ - GHC - (ThisVersion - (mkVersion [7, 6, 3])), - _×_ - GHC - (ThisVersion - (mkVersion [7, 8, 4])), - _×_ - GHC - (ThisVersion - (mkVersion [7, 10, 3])), - _×_ - GHC - (ThisVersion - (mkVersion [8, 0, 2])), - _×_ - GHC - (ThisVersion - (mkVersion [8, 2, 2])), - _×_ - GHC - (ThisVersion - (mkVersion [8, 4, 3])), - _×_ - GHC - (ThisVersion - (mkVersion [8, 6, 1]))], - homepage = - "https://github.com/phadej/postgresql-libpq", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = - "low-level binding to libpq", - description = concat - [ - "This is a binding to libpq: the C application\n", - "programmer's interface to PostgreSQL. libpq is a\n", - "set of library functions that allow client\n", - "programs to pass queries to the PostgreSQL\n", - "backend server and to receive the results of\n", - "these queries."], - category = "Database", - customFieldsPD = [], - buildTypeRaw = Just Custom, - setupBuildInfo = Just - SetupBuildInfo { - setupDepends = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [4, 3])) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "Cabal") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [1, 10])) - (EarlierVersion - (mkVersion [2, 5]))) - mainLibSet], - defaultSetupDepends = False}, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [ - SymbolicPath - "cbits/noticehandlers.h", - SymbolicPath "CHANGELOG.md"], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [ - MkPackageFlag { - flagName = FlagName - "use-pkg-config", - flagDescription = "", - flagDefault = False, - flagManual = True}], - condLibrary = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [ - ModuleName - "Database.PostgreSQL.LibPQ", - ModuleName - "Database.PostgreSQL.LibPQ.Internal"], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [ - LegacyExeDependency - "hsc2hs" - (OrLaterVersion - (mkVersion [0]))], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - asmOptions = [], - cmmOptions = [], - ccOptions = [], - cxxOptions = [], - ldOptions = [], - hsc2hsOptions = [], - pkgconfigDepends = [], - frameworks = [], - extraFrameworkDirs = [], - asmSources = [], - cmmSources = [], - cSources = [ - SymbolicPath - "cbits/noticehandlers.c"], - cxxSources = [], - jsSources = [], - hsSourceDirs = [ - SymbolicPath "src"], - otherModules = [], - virtualModules = [], - autogenModules = [], - defaultLanguage = Nothing, - otherLanguages = [], - defaultExtensions = [], - otherExtensions = [], - oldExtensions = [], - extraLibs = [], - extraLibsStatic = [], - extraGHCiLibs = [], - extraBundledLibs = [], - extraLibFlavours = [], - extraDynLibFlavours = [], - extraLibDirs = [], - extraLibDirsStatic = [], - includeDirs = [ - SymbolicPath "cbits"], - includes = [], - autogenIncludes = [], - installIncludes = [], - options = PerCompilerFlavor - ["-Wall"] - [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = - PerCompilerFlavor [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [4, 3])) - (EarlierVersion - (mkVersion [4, 13]))) - mainLibSet, - Dependency - (PackageName "bytestring") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [0, 9, 1, 0])) - (EarlierVersion - (mkVersion [0, 11]))) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [4, 3])) - (EarlierVersion - (mkVersion [4, 13]))) - mainLibSet, - Dependency - (PackageName "bytestring") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [0, 9, 1, 0])) - (EarlierVersion - (mkVersion [0, 11]))) - mainLibSet], - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "unix") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [2, 4, 2, 0])) - (EarlierVersion - (mkVersion [2, 8]))) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "unix") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [2, 4, 2, 0])) - (EarlierVersion - (mkVersion [2, 8]))) - mainLibSet], - condTreeComponents = []}, - condBranchIfFalse = Nothing}, - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "Win32") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [2, 2, 0, 2])) - (EarlierVersion - (mkVersion [2, 7]))) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "Win32") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [2, 2, 0, 2])) - (EarlierVersion - (mkVersion [2, 7]))) - mainLibSet], - condTreeComponents = []}, - condBranchIfFalse = Nothing}, - CondBranch { - condBranchCondition = - `Var (PackageFlag (FlagName "use-pkg-config"))`, - condBranchIfTrue = CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - asmOptions = [], - cmmOptions = [], - ccOptions = [], - cxxOptions = [], - ldOptions = [], - hsc2hsOptions = [], - pkgconfigDepends = [ - PkgconfigDependency - (PkgconfigName "libpq") - (PcIntersectVersionRanges - (PcOrLaterVersion - (PkgconfigVersion "9")) - (PcEarlierVersion - (PkgconfigVersion "10")))], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}, - condBranchIfFalse = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - 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 = [], - jsppOptions = [], - 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 = ["libpq"], - extraLibsStatic = [], - extraGHCiLibs = [], - extraBundledLibs = [], - extraLibFlavours = [], - extraDynLibFlavours = [], - extraLibDirs = [], - extraLibDirsStatic = [], - includeDirs = [], - includes = [], - autogenIncludes = [], - installIncludes = [], - options = PerCompilerFlavor - [] - [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = - PerCompilerFlavor [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}, - condBranchIfFalse = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 = ["pq"], - extraLibsStatic = [], - extraGHCiLibs = [], - extraBundledLibs = [], - extraLibFlavours = [], - extraDynLibFlavours = [], - extraLibDirs = [], - extraLibDirsStatic = [], - includeDirs = [], - includes = [], - autogenIncludes = [], - installIncludes = [], - options = PerCompilerFlavor - [] - [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = - PerCompilerFlavor [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = [ - CondBranch { - condBranchCondition = - `Var (OS OpenBSD)`, - condBranchIfTrue = CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 = ["crypto", "ssl"], - extraLibsStatic = [], - extraGHCiLibs = [], - extraBundledLibs = [], - extraLibFlavours = [], - extraDynLibFlavours = [], - extraLibDirs = [], - extraLibDirsStatic = [], - includeDirs = [], - includes = [], - autogenIncludes = [], - installIncludes = [], - options = PerCompilerFlavor - [] - [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = - PerCompilerFlavor [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}, - condBranchIfFalse = - Nothing}]}}]}}]}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq1.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/libpq1.genPackageFlags.expr new file mode 100644 index 00000000000..7d105954782 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/libpq1.genPackageFlags.expr @@ -0,0 +1,7 @@ +[ + MkPackageFlag { + flagName = FlagName + "use-pkg-config", + flagDescription = "", + flagDefault = False, + flagManual = True}] diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq1.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/libpq1.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/libpq1.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq1.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/libpq1.packageDescription.expr new file mode 100644 index 00000000000..643490a9dbf --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/libpq1.packageDescription.expr @@ -0,0 +1,113 @@ +PackageDescription { + specVersion = CabalSpecV1_8, + package = PackageIdentifier { + pkgName = PackageName + "postgresql-libpq", + pkgVersion = mkVersion + [0, 9, 4, 2]}, + licenseRaw = Right BSD3, + licenseFiles = [ + SymbolicPath "LICENSE"], + copyright = concat + [ + "(c) 2010 Grant Monroe\n", + "(c) 2011 Leon P Smith"], + maintainer = + "Oleg Grenrus ", + author = + "Grant Monroe, Leon P Smith, Joey Adams", + stability = "", + testedWith = [ + _×_ + GHC + (ThisVersion + (mkVersion [7, 0, 4])), + _×_ + GHC + (ThisVersion + (mkVersion [7, 2, 2])), + _×_ + GHC + (ThisVersion + (mkVersion [7, 4, 2])), + _×_ + GHC + (ThisVersion + (mkVersion [7, 6, 3])), + _×_ + GHC + (ThisVersion + (mkVersion [7, 8, 4])), + _×_ + GHC + (ThisVersion + (mkVersion [7, 10, 3])), + _×_ + GHC + (ThisVersion + (mkVersion [8, 0, 2])), + _×_ + GHC + (ThisVersion + (mkVersion [8, 2, 2])), + _×_ + GHC + (ThisVersion + (mkVersion [8, 4, 3])), + _×_ + GHC + (ThisVersion + (mkVersion [8, 6, 1]))], + homepage = + "https://github.com/phadej/postgresql-libpq", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = + "low-level binding to libpq", + description = concat + [ + "This is a binding to libpq: the C application\n", + "programmer's interface to PostgreSQL. libpq is a\n", + "set of library functions that allow client\n", + "programs to pass queries to the PostgreSQL\n", + "backend server and to receive the results of\n", + "these queries."], + category = "Database", + customFieldsPD = [], + buildTypeRaw = Just Custom, + setupBuildInfo = Just + SetupBuildInfo { + setupDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 3])) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "Cabal") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [1, 10])) + (EarlierVersion + (mkVersion [2, 5]))) + mainLibSet], + defaultSetupDepends = False}, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [ + SymbolicPath + "cbits/noticehandlers.h", + SymbolicPath "CHANGELOG.md"], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq2.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/libpq2.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/libpq2.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq2.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/libpq2.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/libpq2.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq2.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/libpq2.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/libpq2.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq2.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/libpq2.condLibrary.expr new file mode 100644 index 00000000000..e8976a455b2 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/libpq2.condLibrary.expr @@ -0,0 +1,639 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName + "Database.PostgreSQL.LibPQ", + ModuleName + "Database.PostgreSQL.LibPQ.Internal"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [ + ExeDependency + (PackageName "hsc2hs") + (UnqualComponentName "hsc2hs") + (OrLaterVersion + (mkVersion [0]))], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [ + SymbolicPath + "cbits/noticehandlers.c"], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "src"], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [ + SymbolicPath "cbits"], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + ["-Wall"] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 3])) + (EarlierVersion + (mkVersion [4, 13]))) + mainLibSet, + Dependency + (PackageName "bytestring") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 9, 1, 0])) + (EarlierVersion + (mkVersion [0, 11]))) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 3])) + (EarlierVersion + (mkVersion [4, 13]))) + mainLibSet, + Dependency + (PackageName "bytestring") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 9, 1, 0])) + (EarlierVersion + (mkVersion [0, 11]))) + mainLibSet], + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "unix") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [2, 4, 2, 0])) + (EarlierVersion + (mkVersion [2, 8]))) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "unix") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [2, 4, 2, 0])) + (EarlierVersion + (mkVersion [2, 8]))) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}, + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "Win32") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [2, 2, 0, 2])) + (EarlierVersion + (mkVersion [2, 7]))) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "Win32") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [2, 2, 0, 2])) + (EarlierVersion + (mkVersion [2, 7]))) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}, + CondBranch { + condBranchCondition = + `Var (PackageFlag (FlagName "use-pkg-config"))`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [ + PkgconfigDependency + (PkgconfigName "libpq") + (PcOrLaterVersion + (PkgconfigVersion "9.3h"))], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []}, + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + 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 = [], + jsppOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = ["libpq"], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []}, + 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 = [], + jsppOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = ["pq"], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `Var (OS OpenBSD)`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [], + extraLibs = ["crypto", "ssl"], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = + Nothing}]}}]}}]} diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq2.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/libpq2.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/libpq2.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq2.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/libpq2.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/libpq2.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq2.expr b/Cabal-tests/tests/ParserTests/regressions/libpq2.expr deleted file mode 100644 index 9f6a16ada6e..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/libpq2.expr +++ /dev/null @@ -1,771 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV3_0, - package = PackageIdentifier { - pkgName = PackageName - "postgresql-libpq", - pkgVersion = mkVersion - [0, 9, 4, 2]}, - licenseRaw = Left - (License - (ELicense - (ELicenseId BSD_3_Clause) - Nothing)), - licenseFiles = [ - SymbolicPath "LICENSE"], - copyright = concat - [ - "(c) 2010 Grant Monroe\n", - "(c) 2011 Leon P Smith"], - maintainer = - "Oleg Grenrus ", - author = - "Grant Monroe, Leon P Smith, Joey Adams", - stability = "", - testedWith = [ - _×_ - GHC - (ThisVersion - (mkVersion [7, 0, 4])), - _×_ - GHC - (ThisVersion - (mkVersion [7, 2, 2])), - _×_ - GHC - (ThisVersion - (mkVersion [7, 4, 2])), - _×_ - GHC - (ThisVersion - (mkVersion [7, 6, 3])), - _×_ - GHC - (ThisVersion - (mkVersion [7, 8, 4])), - _×_ - GHC - (ThisVersion - (mkVersion [7, 10, 3])), - _×_ - GHC - (ThisVersion - (mkVersion [8, 0, 2])), - _×_ - GHC - (ThisVersion - (mkVersion [8, 2, 2])), - _×_ - GHC - (ThisVersion - (mkVersion [8, 4, 3])), - _×_ - GHC - (ThisVersion - (mkVersion [8, 6, 1]))], - homepage = - "https://github.com/phadej/postgresql-libpq", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = - "low-level binding to libpq", - description = concat - [ - "This is a binding to libpq: the C application\n", - "programmer's interface to PostgreSQL. libpq is a\n", - "set of library functions that allow client\n", - "programs to pass queries to the PostgreSQL\n", - "backend server and to receive the results of\n", - "these queries."], - category = "Database", - customFieldsPD = [], - buildTypeRaw = Just Custom, - setupBuildInfo = Just - SetupBuildInfo { - setupDepends = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [4, 3])) - (EarlierVersion - (mkVersion [5]))) - mainLibSet, - Dependency - (PackageName "Cabal") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [1, 10])) - (EarlierVersion - (mkVersion [2, 5]))) - mainLibSet], - defaultSetupDepends = False}, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [ - SymbolicPath - "cbits/noticehandlers.h", - SymbolicPath "CHANGELOG.md"], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [ - MkPackageFlag { - flagName = FlagName - "use-pkg-config", - flagDescription = "", - flagDefault = False, - flagManual = True}], - condLibrary = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [ - ModuleName - "Database.PostgreSQL.LibPQ", - ModuleName - "Database.PostgreSQL.LibPQ.Internal"], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [ - ExeDependency - (PackageName "hsc2hs") - (UnqualComponentName "hsc2hs") - (OrLaterVersion - (mkVersion [0]))], - cppOptions = [], - jsppOptions = [], - asmOptions = [], - cmmOptions = [], - ccOptions = [], - cxxOptions = [], - ldOptions = [], - hsc2hsOptions = [], - pkgconfigDepends = [], - frameworks = [], - extraFrameworkDirs = [], - asmSources = [], - cmmSources = [], - cSources = [ - SymbolicPath - "cbits/noticehandlers.c"], - cxxSources = [], - jsSources = [], - hsSourceDirs = [ - SymbolicPath "src"], - otherModules = [], - virtualModules = [], - autogenModules = [], - defaultLanguage = Nothing, - otherLanguages = [], - defaultExtensions = [], - otherExtensions = [], - oldExtensions = [], - extraLibs = [], - extraLibsStatic = [], - extraGHCiLibs = [], - extraBundledLibs = [], - extraLibFlavours = [], - extraDynLibFlavours = [], - extraLibDirs = [], - extraLibDirsStatic = [], - includeDirs = [ - SymbolicPath "cbits"], - includes = [], - autogenIncludes = [], - installIncludes = [], - options = PerCompilerFlavor - ["-Wall"] - [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = - PerCompilerFlavor [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [4, 3])) - (EarlierVersion - (mkVersion [4, 13]))) - mainLibSet, - Dependency - (PackageName "bytestring") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [0, 9, 1, 0])) - (EarlierVersion - (mkVersion [0, 11]))) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [4, 3])) - (EarlierVersion - (mkVersion [4, 13]))) - mainLibSet, - Dependency - (PackageName "bytestring") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [0, 9, 1, 0])) - (EarlierVersion - (mkVersion [0, 11]))) - mainLibSet], - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "unix") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [2, 4, 2, 0])) - (EarlierVersion - (mkVersion [2, 8]))) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "unix") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [2, 4, 2, 0])) - (EarlierVersion - (mkVersion [2, 8]))) - mainLibSet], - condTreeComponents = []}, - condBranchIfFalse = Nothing}, - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "Win32") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [2, 2, 0, 2])) - (EarlierVersion - (mkVersion [2, 7]))) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "Win32") - (IntersectVersionRanges - (OrLaterVersion - (mkVersion [2, 2, 0, 2])) - (EarlierVersion - (mkVersion [2, 7]))) - mainLibSet], - condTreeComponents = []}, - condBranchIfFalse = Nothing}, - CondBranch { - condBranchCondition = - `Var (PackageFlag (FlagName "use-pkg-config"))`, - condBranchIfTrue = CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - asmOptions = [], - cmmOptions = [], - ccOptions = [], - cxxOptions = [], - ldOptions = [], - hsc2hsOptions = [], - pkgconfigDepends = [ - PkgconfigDependency - (PkgconfigName "libpq") - (PcOrLaterVersion - (PkgconfigVersion "9.3h"))], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}, - condBranchIfFalse = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - 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 = [], - jsppOptions = [], - 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 = ["libpq"], - extraLibsStatic = [], - extraGHCiLibs = [], - extraBundledLibs = [], - extraLibFlavours = [], - extraDynLibFlavours = [], - extraLibDirs = [], - extraLibDirsStatic = [], - includeDirs = [], - includes = [], - autogenIncludes = [], - installIncludes = [], - options = PerCompilerFlavor - [] - [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = - PerCompilerFlavor [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}, - condBranchIfFalse = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 = ["pq"], - extraLibsStatic = [], - extraGHCiLibs = [], - extraBundledLibs = [], - extraLibFlavours = [], - extraDynLibFlavours = [], - extraLibDirs = [], - extraLibDirsStatic = [], - includeDirs = [], - includes = [], - autogenIncludes = [], - installIncludes = [], - options = PerCompilerFlavor - [] - [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = - PerCompilerFlavor [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = [ - CondBranch { - condBranchCondition = - `Var (OS OpenBSD)`, - condBranchIfTrue = CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 = ["crypto", "ssl"], - extraLibsStatic = [], - extraGHCiLibs = [], - extraBundledLibs = [], - extraLibFlavours = [], - extraDynLibFlavours = [], - extraLibDirs = [], - extraLibDirsStatic = [], - includeDirs = [], - includes = [], - autogenIncludes = [], - installIncludes = [], - options = PerCompilerFlavor - [] - [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = - PerCompilerFlavor [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}, - condBranchIfFalse = - Nothing}]}}]}}]}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq2.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/libpq2.genPackageFlags.expr new file mode 100644 index 00000000000..7d105954782 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/libpq2.genPackageFlags.expr @@ -0,0 +1,7 @@ +[ + MkPackageFlag { + flagName = FlagName + "use-pkg-config", + flagDescription = "", + flagDefault = False, + flagManual = True}] diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq2.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/libpq2.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/libpq2.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq2.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/libpq2.packageDescription.expr new file mode 100644 index 00000000000..8aba27c4e4e --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/libpq2.packageDescription.expr @@ -0,0 +1,117 @@ +PackageDescription { + specVersion = CabalSpecV3_0, + package = PackageIdentifier { + pkgName = PackageName + "postgresql-libpq", + pkgVersion = mkVersion + [0, 9, 4, 2]}, + licenseRaw = Left + (License + (ELicense + (ELicenseId BSD_3_Clause) + Nothing)), + licenseFiles = [ + SymbolicPath "LICENSE"], + copyright = concat + [ + "(c) 2010 Grant Monroe\n", + "(c) 2011 Leon P Smith"], + maintainer = + "Oleg Grenrus ", + author = + "Grant Monroe, Leon P Smith, Joey Adams", + stability = "", + testedWith = [ + _×_ + GHC + (ThisVersion + (mkVersion [7, 0, 4])), + _×_ + GHC + (ThisVersion + (mkVersion [7, 2, 2])), + _×_ + GHC + (ThisVersion + (mkVersion [7, 4, 2])), + _×_ + GHC + (ThisVersion + (mkVersion [7, 6, 3])), + _×_ + GHC + (ThisVersion + (mkVersion [7, 8, 4])), + _×_ + GHC + (ThisVersion + (mkVersion [7, 10, 3])), + _×_ + GHC + (ThisVersion + (mkVersion [8, 0, 2])), + _×_ + GHC + (ThisVersion + (mkVersion [8, 2, 2])), + _×_ + GHC + (ThisVersion + (mkVersion [8, 4, 3])), + _×_ + GHC + (ThisVersion + (mkVersion [8, 6, 1]))], + homepage = + "https://github.com/phadej/postgresql-libpq", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = + "low-level binding to libpq", + description = concat + [ + "This is a binding to libpq: the C application\n", + "programmer's interface to PostgreSQL. libpq is a\n", + "set of library functions that allow client\n", + "programs to pass queries to the PostgreSQL\n", + "backend server and to receive the results of\n", + "these queries."], + category = "Database", + customFieldsPD = [], + buildTypeRaw = Just Custom, + setupBuildInfo = Just + SetupBuildInfo { + setupDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 3])) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "Cabal") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [1, 10])) + (EarlierVersion + (mkVersion [2, 5]))) + mainLibSet], + defaultSetupDepends = False}, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [ + SymbolicPath + "cbits/noticehandlers.h", + SymbolicPath "CHANGELOG.md"], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-1.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-1.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-1.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-1.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-1.condExecutables.expr new file mode 100644 index 00000000000..37e461be943 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-1.condExecutables.expr @@ -0,0 +1,122 @@ +[ + _×_ + (UnqualComponentName + "str-example") + CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "str-example", + modulePath = SymbolicPath + "Main.hs", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "str-example"], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "str-string") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "str-bytestring") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = [ + Mixin { + mixinPackageName = PackageName + "str-string", + mixinLibraryName = LMainLibName, + mixinIncludeRenaming = + IncludeRenaming { + includeProvidesRn = + ModuleRenaming + [ + _×_ + (ModuleName "Str") + (ModuleName "Str.String")], + includeRequiresRn = + DefaultRenaming}}, + Mixin { + mixinPackageName = PackageName + "str-bytestring", + mixinLibraryName = LMainLibName, + mixinIncludeRenaming = + IncludeRenaming { + includeProvidesRn = + ModuleRenaming + [ + _×_ + (ModuleName "Str") + (ModuleName "Str.ByteString")], + includeRequiresRn = + DefaultRenaming}}]}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "str-string") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "str-bytestring") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-1.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-1.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-1.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-1.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-1.condLibrary.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-1.condLibrary.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-1.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-1.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-1.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-1.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-1.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-1.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-1.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-1.expr deleted file mode 100644 index 0a137660468..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/mixin-1.expr +++ /dev/null @@ -1,165 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV2_0, - package = PackageIdentifier { - pkgName = PackageName "mixin", - pkgVersion = mkVersion [0]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = "", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Just Simple, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Nothing, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [ - _×_ - (UnqualComponentName - "str-example") - CondNode { - condTreeData = Executable { - exeName = UnqualComponentName - "str-example", - modulePath = SymbolicPath - "Main.hs", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - asmOptions = [], - cmmOptions = [], - ccOptions = [], - cxxOptions = [], - ldOptions = [], - hsc2hsOptions = [], - pkgconfigDepends = [], - frameworks = [], - extraFrameworkDirs = [], - asmSources = [], - cmmSources = [], - cSources = [], - cxxSources = [], - jsSources = [], - hsSourceDirs = [ - SymbolicPath "str-example"], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "str-string") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "str-bytestring") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - mixins = [ - Mixin { - mixinPackageName = PackageName - "str-string", - mixinLibraryName = LMainLibName, - mixinIncludeRenaming = - IncludeRenaming { - includeProvidesRn = - ModuleRenaming - [ - _×_ - (ModuleName "Str") - (ModuleName "Str.String")], - includeRequiresRn = - DefaultRenaming}}, - Mixin { - mixinPackageName = PackageName - "str-bytestring", - mixinLibraryName = LMainLibName, - mixinIncludeRenaming = - IncludeRenaming { - includeProvidesRn = - ModuleRenaming - [ - _×_ - (ModuleName "Str") - (ModuleName "Str.ByteString")], - includeRequiresRn = - DefaultRenaming}}]}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "str-string") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "str-bytestring") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeComponents = []}], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-1.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-1.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-1.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-1.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-1.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-1.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-1.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-1.packageDescription.expr new file mode 100644 index 00000000000..a4f28a066ef --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-1.packageDescription.expr @@ -0,0 +1,34 @@ +PackageDescription { + specVersion = CabalSpecV2_0, + package = PackageIdentifier { + pkgName = PackageName "mixin", + pkgVersion = mkVersion [0]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = "", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-2.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-2.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-2.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-2.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-2.condExecutables.expr new file mode 100644 index 00000000000..37e461be943 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-2.condExecutables.expr @@ -0,0 +1,122 @@ +[ + _×_ + (UnqualComponentName + "str-example") + CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "str-example", + modulePath = SymbolicPath + "Main.hs", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "str-example"], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "str-string") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "str-bytestring") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = [ + Mixin { + mixinPackageName = PackageName + "str-string", + mixinLibraryName = LMainLibName, + mixinIncludeRenaming = + IncludeRenaming { + includeProvidesRn = + ModuleRenaming + [ + _×_ + (ModuleName "Str") + (ModuleName "Str.String")], + includeRequiresRn = + DefaultRenaming}}, + Mixin { + mixinPackageName = PackageName + "str-bytestring", + mixinLibraryName = LMainLibName, + mixinIncludeRenaming = + IncludeRenaming { + includeProvidesRn = + ModuleRenaming + [ + _×_ + (ModuleName "Str") + (ModuleName "Str.ByteString")], + includeRequiresRn = + DefaultRenaming}}]}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "str-string") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "str-bytestring") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-2.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-2.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-2.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-2.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-2.condLibrary.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-2.condLibrary.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-2.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-2.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-2.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-2.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-2.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-2.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-2.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-2.expr deleted file mode 100644 index 6c2239df825..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/mixin-2.expr +++ /dev/null @@ -1,165 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV3_0, - package = PackageIdentifier { - pkgName = PackageName "mixin", - pkgVersion = mkVersion [0]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = "", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Nothing, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Nothing, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [ - _×_ - (UnqualComponentName - "str-example") - CondNode { - condTreeData = Executable { - exeName = UnqualComponentName - "str-example", - modulePath = SymbolicPath - "Main.hs", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - asmOptions = [], - cmmOptions = [], - ccOptions = [], - cxxOptions = [], - ldOptions = [], - hsc2hsOptions = [], - pkgconfigDepends = [], - frameworks = [], - extraFrameworkDirs = [], - asmSources = [], - cmmSources = [], - cSources = [], - cxxSources = [], - jsSources = [], - hsSourceDirs = [ - SymbolicPath "str-example"], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "str-string") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "str-bytestring") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - mixins = [ - Mixin { - mixinPackageName = PackageName - "str-string", - mixinLibraryName = LMainLibName, - mixinIncludeRenaming = - IncludeRenaming { - includeProvidesRn = - ModuleRenaming - [ - _×_ - (ModuleName "Str") - (ModuleName "Str.String")], - includeRequiresRn = - DefaultRenaming}}, - Mixin { - mixinPackageName = PackageName - "str-bytestring", - mixinLibraryName = LMainLibName, - mixinIncludeRenaming = - IncludeRenaming { - includeProvidesRn = - ModuleRenaming - [ - _×_ - (ModuleName "Str") - (ModuleName "Str.ByteString")], - includeRequiresRn = - DefaultRenaming}}]}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "str-string") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "str-bytestring") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeComponents = []}], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-2.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-2.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-2.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-2.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-2.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-2.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-2.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-2.packageDescription.expr new file mode 100644 index 00000000000..418d0c7efac --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-2.packageDescription.expr @@ -0,0 +1,34 @@ +PackageDescription { + specVersion = CabalSpecV3_0, + package = PackageIdentifier { + pkgName = PackageName "mixin", + pkgVersion = mkVersion [0]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = "", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Nothing, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-3.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-3.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-3.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-3.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-3.condExecutables.expr new file mode 100644 index 00000000000..51f0f596c3c --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-3.condExecutables.expr @@ -0,0 +1,105 @@ +[ + _×_ + (UnqualComponentName + "str-example") + CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "str-example", + modulePath = SymbolicPath + "Main.hs", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "str-example"], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "str-string") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "str-bytestring") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = [ + Mixin { + mixinPackageName = PackageName + "str", + mixinLibraryName = LMainLibName, + mixinIncludeRenaming = + IncludeRenaming { + includeProvidesRn = + HidingRenaming + [ModuleName "Foo"], + includeRequiresRn = + DefaultRenaming}}]}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "str-string") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "str-bytestring") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-3.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-3.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-3.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-3.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-3.condLibrary.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-3.condLibrary.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-3.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-3.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-3.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-3.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-3.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-3.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-3.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-3.expr deleted file mode 100644 index a4a94aac32c..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/mixin-3.expr +++ /dev/null @@ -1,148 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV3_0, - package = PackageIdentifier { - pkgName = PackageName "mixin", - pkgVersion = mkVersion [0]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = "", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Nothing, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Nothing, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [ - _×_ - (UnqualComponentName - "str-example") - CondNode { - condTreeData = Executable { - exeName = UnqualComponentName - "str-example", - modulePath = SymbolicPath - "Main.hs", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - asmOptions = [], - cmmOptions = [], - ccOptions = [], - cxxOptions = [], - ldOptions = [], - hsc2hsOptions = [], - pkgconfigDepends = [], - frameworks = [], - extraFrameworkDirs = [], - asmSources = [], - cmmSources = [], - cSources = [], - cxxSources = [], - jsSources = [], - hsSourceDirs = [ - SymbolicPath "str-example"], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "str-string") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "str-bytestring") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - mixins = [ - Mixin { - mixinPackageName = PackageName - "str", - mixinLibraryName = LMainLibName, - mixinIncludeRenaming = - IncludeRenaming { - includeProvidesRn = - HidingRenaming - [ModuleName "Foo"], - includeRequiresRn = - DefaultRenaming}}]}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "str-string") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "str-bytestring") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeComponents = []}], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-3.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-3.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-3.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-3.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-3.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-3.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-3.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-3.packageDescription.expr new file mode 100644 index 00000000000..418d0c7efac --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-3.packageDescription.expr @@ -0,0 +1,34 @@ +PackageDescription { + specVersion = CabalSpecV3_0, + package = PackageIdentifier { + pkgName = PackageName "mixin", + pkgVersion = mkVersion [0]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = "", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Nothing, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/monad-param.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/monad-param.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/monad-param.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/monad-param.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/monad-param.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/monad-param.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/monad-param.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/monad-param.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/monad-param.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/monad-param.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/monad-param.condLibrary.expr new file mode 100644 index 00000000000..0076f3213d7 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/monad-param.condLibrary.expr @@ -0,0 +1,109 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName + "Control.Monad.Parameterized"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "src"], + otherModules = [], + virtualModules = [], + autogenModules = [], + defaultLanguage = Nothing, + otherLanguages = [], + defaultExtensions = [], + otherExtensions = [], + oldExtensions = [ + EnableExtension + MultiParamTypeClasses, + EnableExtension + FunctionalDependencies, + EnableExtension + OverlappingInstances, + EnableExtension + UndecidableInstances, + EnableExtension EmptyDataDecls, + DisableExtension + ImplicitPrelude], + extraLibs = [], + extraLibsStatic = [], + extraGHCiLibs = [], + extraBundledLibs = [], + extraLibFlavours = [], + extraDynLibFlavours = [], + extraLibDirs = [], + extraLibDirsStatic = [], + includeDirs = [], + includes = [], + autogenIncludes = [], + installIncludes = [], + options = PerCompilerFlavor + [ + "-funbox-strict-fields", + "-threaded", + "-fasm"] + [], + profOptions = PerCompilerFlavor + [] + [], + sharedOptions = + PerCompilerFlavor [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "mtl") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "stm") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "mtl") + (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "stm") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/monad-param.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/monad-param.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/monad-param.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/monad-param.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/monad-param.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/monad-param.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/monad-param.expr b/Cabal-tests/tests/ParserTests/regressions/monad-param.expr deleted file mode 100644 index db28c928ddb..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/monad-param.expr +++ /dev/null @@ -1,162 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV1_0, - package = PackageIdentifier { - pkgName = PackageName - "monad-param", - pkgVersion = mkVersion - [0, 0, 1]}, - licenseRaw = Right BSD3, - licenseFiles = [ - SymbolicPath "LICENSE"], - copyright = - "Copyright (C) 2006-2007, Edward Kmett", - maintainer = - "Edward Kmett ", - author = - "Edward Kmett ", - stability = "alpha", - testedWith = [], - homepage = - "http://comonad.com/haskell/monad-param/dist/doc/html/Control-Monad-Parameterized.html", - pkgUrl = - "http://comonad.com/haskell/monad-param", - bugReports = "", - sourceRepos = [], - synopsis = - "Parameterized monads", - description = - "Implements parameterized monads by overloading the monad sugar with more liberal types.", - category = "Control", - customFieldsPD = [], - buildTypeRaw = Nothing, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [ - ModuleName - "Control.Monad.Parameterized"], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - asmOptions = [], - cmmOptions = [], - ccOptions = [], - cxxOptions = [], - ldOptions = [], - hsc2hsOptions = [], - pkgconfigDepends = [], - frameworks = [], - extraFrameworkDirs = [], - asmSources = [], - cmmSources = [], - cSources = [], - cxxSources = [], - jsSources = [], - hsSourceDirs = [ - SymbolicPath "src"], - otherModules = [], - virtualModules = [], - autogenModules = [], - defaultLanguage = Nothing, - otherLanguages = [], - defaultExtensions = [], - otherExtensions = [], - oldExtensions = [ - EnableExtension - MultiParamTypeClasses, - EnableExtension - FunctionalDependencies, - EnableExtension - OverlappingInstances, - EnableExtension - UndecidableInstances, - EnableExtension EmptyDataDecls, - DisableExtension - ImplicitPrelude], - extraLibs = [], - extraLibsStatic = [], - extraGHCiLibs = [], - extraBundledLibs = [], - extraLibFlavours = [], - extraDynLibFlavours = [], - extraLibDirs = [], - extraLibDirsStatic = [], - includeDirs = [], - includes = [], - autogenIncludes = [], - installIncludes = [], - options = PerCompilerFlavor - [ - "-funbox-strict-fields", - "-threaded", - "-fasm"] - [], - profOptions = PerCompilerFlavor - [] - [], - sharedOptions = - PerCompilerFlavor [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "mtl") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "stm") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "mtl") - (OrLaterVersion (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "stm") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeComponents = []}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/monad-param.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/monad-param.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/monad-param.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/monad-param.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/monad-param.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/monad-param.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/monad-param.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/monad-param.packageDescription.expr new file mode 100644 index 00000000000..7d299f4371a --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/monad-param.packageDescription.expr @@ -0,0 +1,44 @@ +PackageDescription { + specVersion = CabalSpecV1_0, + package = PackageIdentifier { + pkgName = PackageName + "monad-param", + pkgVersion = mkVersion + [0, 0, 1]}, + licenseRaw = Right BSD3, + licenseFiles = [ + SymbolicPath "LICENSE"], + copyright = + "Copyright (C) 2006-2007, Edward Kmett", + maintainer = + "Edward Kmett ", + author = + "Edward Kmett ", + stability = "alpha", + testedWith = [], + homepage = + "http://comonad.com/haskell/monad-param/dist/doc/html/Control-Monad-Parameterized.html", + pkgUrl = + "http://comonad.com/haskell/monad-param", + bugReports = "", + sourceRepos = [], + synopsis = + "Parameterized monads", + description = + "Implements parameterized monads by overloading the monad sugar with more liberal types.", + category = "Control", + customFieldsPD = [], + buildTypeRaw = Nothing, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.condLibrary.expr new file mode 100644 index 00000000000..1b03802a873 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.condLibrary.expr @@ -0,0 +1,78 @@ +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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/anynone.expr b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.condSubLibraries.expr similarity index 63% rename from Cabal-tests/tests/ParserTests/regressions/anynone.expr rename to Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.condSubLibraries.expr index 927605d6058..8c40bfd5408 100644 --- a/Cabal-tests/tests/ParserTests/regressions/anynone.expr +++ b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.condSubLibraries.expr @@ -1,62 +1,27 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV3_0, - package = PackageIdentifier { - pkgName = PackageName "anynone", - pkgVersion = mkVersion [0]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = "The -any none demo", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Just Simple, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just +[ + _×_ + (UnqualComponentName "public") CondNode { condTreeData = Library { - libName = LMainLibName, + libName = LSubLibName + (UnqualComponentName "public"), exposedModules = [ - ModuleName "AnyNone"], + ModuleName "ElseIf2"], reexportedModules = [], signatures = [], libExposed = True, libVisibility = - LibraryVisibilityPublic, + LibraryVisibilityPrivate, libBuildInfo = BuildInfo { buildable = True, buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -113,9 +78,4 @@ GenericPackageDescription { (PackageName "base") (OrLaterVersion (mkVersion [0])) mainLibSet], - condTreeComponents = []}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} + condTreeComponents = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.expr b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.expr deleted file mode 100644 index d2f1efdd913..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.expr +++ /dev/null @@ -1,203 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV2_0, - package = PackageIdentifier { - pkgName = PackageName - "multiple-libs", - pkgVersion = mkVersion [0]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = - "visible flag only since 3.0", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Just Simple, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeComponents = []}, - condSubLibraries = [ - _×_ - (UnqualComponentName "public") - CondNode { - condTreeData = Library { - libName = LSubLibName - (UnqualComponentName "public"), - exposedModules = [ - ModuleName "ElseIf2"], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPrivate, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeComponents = []}], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.packageDescription.expr new file mode 100644 index 00000000000..ee605e1a73b --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.packageDescription.expr @@ -0,0 +1,36 @@ +PackageDescription { + specVersion = CabalSpecV2_0, + package = PackageIdentifier { + pkgName = PackageName + "multiple-libs", + pkgVersion = mkVersion [0]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = + "visible flag only since 3.0", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/noVersion.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/noVersion.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/noVersion.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/noVersion.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/noVersion.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/noVersion.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/noVersion.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/noVersion.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/noVersion.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/noVersion.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/noVersion.condLibrary.expr new file mode 100644 index 00000000000..3903f20bb88 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/noVersion.condLibrary.expr @@ -0,0 +1,78 @@ +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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "bad-package") + (EarlierVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "bad-package") + (EarlierVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/noVersion.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/noVersion.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/noVersion.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/noVersion.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/noVersion.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/noVersion.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/noVersion.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/noVersion.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/noVersion.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/noVersion.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/noVersion.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/noVersion.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/noVersion.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/noVersion.packageDescription.expr new file mode 100644 index 00000000000..621adc03c80 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/noVersion.packageDescription.expr @@ -0,0 +1,36 @@ +PackageDescription { + specVersion = CabalSpecV1_22, + package = PackageIdentifier { + pkgName = PackageName + "noVersion", + pkgVersion = mkVersion [0]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = + "-none in build-depends", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.condLibrary.expr new file mode 100644 index 00000000000..0832109a9a9 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.condLibrary.expr @@ -0,0 +1,141 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName "\937"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `CNot (Var (PackageFlag (FlagName "\\28961")))`, + condBranchIfTrue = CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = False, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]} diff --git a/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.genPackageFlags.expr new file mode 100644 index 00000000000..daae1f9b731 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.genPackageFlags.expr @@ -0,0 +1,6 @@ +[ + MkPackageFlag { + flagName = FlagName "\28961", + flagDescription = "\28961", + flagDefault = True, + flagManual = False}] diff --git a/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.packageDescription.expr new file mode 100644 index 00000000000..9b59e261e94 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.packageDescription.expr @@ -0,0 +1,46 @@ +PackageDescription { + specVersion = CabalSpecV1_10, + package = PackageIdentifier { + pkgName = PackageName "\28961", + 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 = + "The canonical non-package \28961", + description = "", + category = "", + customFieldsPD = [ + _×_ "x-\28961" "\28961"], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/shake.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/shake.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/shake.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/shake.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/shake.condExecutables.expr new file mode 100644 index 00000000000..d9e22f3b1ba --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/shake.condExecutables.expr @@ -0,0 +1,759 @@ +[ + _×_ + (UnqualComponentName "shake") + CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "shake", + modulePath = SymbolicPath + "Run.hs", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = SymbolicPath "", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = Nothing}, + CondBranch { + condBranchCondition = + `Var (PackageFlag (FlagName "portable"))`, + condBranchIfTrue = CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "shake", + modulePath = SymbolicPath "", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = ["-DPORTABLE"], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = SymbolicPath "", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = SymbolicPath "", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = [ + CondBranch { + condBranchCondition = + `CNot (Var (OS Windows))`, + condBranchIfTrue = CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "shake", + modulePath = SymbolicPath "", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = SymbolicPath "", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "unix") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "unix") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}] diff --git a/Cabal-tests/tests/ParserTests/regressions/shake.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/shake.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/shake.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/shake.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/shake.condLibrary.expr new file mode 100644 index 00000000000..dfc1e72bba3 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/shake.condLibrary.expr @@ -0,0 +1,681 @@ +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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "unix") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "unix") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]} diff --git a/Cabal-tests/tests/ParserTests/regressions/shake.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/shake.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/shake.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/shake.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/shake.condTestSuites.expr new file mode 100644 index 00000000000..0f7471e6ce4 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/shake.condTestSuites.expr @@ -0,0 +1,900 @@ +[ + _×_ + (UnqualComponentName + "shake-test") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + (SymbolicPath "Test.hs"), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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}]}] diff --git a/Cabal-tests/tests/ParserTests/regressions/shake.expr b/Cabal-tests/tests/ParserTests/regressions/shake.expr deleted file mode 100644 index 5be08b04064..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/shake.expr +++ /dev/null @@ -1,2504 +0,0 @@ -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 ", - author = - "Neil Mitchell ", - 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", - "\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 = [ - SymbolicPath "html/viz.js", - SymbolicPath - "html/profile.html", - SymbolicPath - "html/progress.html", - SymbolicPath "html/shake.js", - SymbolicPath - "docs/manual/build.bat", - SymbolicPath - "docs/manual/Build.hs", - SymbolicPath - "docs/manual/build.sh", - SymbolicPath - "docs/manual/constants.c", - SymbolicPath - "docs/manual/constants.h", - SymbolicPath - "docs/manual/main.c"], - dataDir = SymbolicPath ".", - extraSrcFiles = [ - SymbolicPath - "src/Test/C/constants.c", - SymbolicPath - "src/Test/C/constants.h", - SymbolicPath - "src/Test/C/main.c", - SymbolicPath - "src/Test/MakeTutor/Makefile", - SymbolicPath - "src/Test/MakeTutor/hellofunc.c", - SymbolicPath - "src/Test/MakeTutor/hellomake.c", - SymbolicPath - "src/Test/MakeTutor/hellomake.h", - SymbolicPath - "src/Test/Tar/list.txt", - SymbolicPath - "src/Test/Ninja/*.ninja", - SymbolicPath - "src/Test/Ninja/subdir/*.ninja", - SymbolicPath - "src/Test/Ninja/*.output", - SymbolicPath - "src/Test/Progress/*.prog", - SymbolicPath - "src/Test/Tup/hello.c", - SymbolicPath - "src/Test/Tup/root.cfg", - SymbolicPath - "src/Test/Tup/newmath/root.cfg", - SymbolicPath - "src/Test/Tup/newmath/square.c", - SymbolicPath - "src/Test/Tup/newmath/square.h", - SymbolicPath "src/Paths.hs", - SymbolicPath "docs/Manual.md", - SymbolicPath - "docs/shake-progress.png"], - extraTmpFiles = [], - extraDocFiles = [ - SymbolicPath "CHANGES.txt", - SymbolicPath "README.md"], - extraFiles = []}, - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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"], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = SymbolicPath - "Run.hs", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = SymbolicPath "", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}, - condBranchIfFalse = Nothing}, - CondBranch { - condBranchCondition = - `Var (PackageFlag (FlagName "portable"))`, - condBranchIfTrue = CondNode { - condTreeData = Executable { - exeName = UnqualComponentName - "shake", - modulePath = SymbolicPath "", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = ["-DPORTABLE"], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = SymbolicPath "", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = SymbolicPath "", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = [ - CondBranch { - condBranchCondition = - `CNot (Var (OS Windows))`, - condBranchIfTrue = CondNode { - condTreeData = Executable { - exeName = UnqualComponentName - "shake", - modulePath = SymbolicPath "", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = SymbolicPath "", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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]) - (SymbolicPath "Test.hs"), - testBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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"], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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/shake.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/shake.genPackageFlags.expr new file mode 100644 index 00000000000..ad40c55f7a8 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/shake.genPackageFlags.expr @@ -0,0 +1,7 @@ +[ + MkPackageFlag { + flagName = FlagName "portable", + flagDescription = + "Obtain FileTime using portable functions", + flagDefault = False, + flagManual = True}] diff --git a/Cabal-tests/tests/ParserTests/regressions/shake.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/shake.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/shake.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/shake.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/shake.packageDescription.expr new file mode 100644 index 00000000000..9f80a3777ff --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/shake.packageDescription.expr @@ -0,0 +1,151 @@ +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 ", + author = + "Neil Mitchell ", + 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", + "\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 = [ + SymbolicPath "html/viz.js", + SymbolicPath + "html/profile.html", + SymbolicPath + "html/progress.html", + SymbolicPath "html/shake.js", + SymbolicPath + "docs/manual/build.bat", + SymbolicPath + "docs/manual/Build.hs", + SymbolicPath + "docs/manual/build.sh", + SymbolicPath + "docs/manual/constants.c", + SymbolicPath + "docs/manual/constants.h", + SymbolicPath + "docs/manual/main.c"], + dataDir = SymbolicPath ".", + extraSrcFiles = [ + SymbolicPath + "src/Test/C/constants.c", + SymbolicPath + "src/Test/C/constants.h", + SymbolicPath + "src/Test/C/main.c", + SymbolicPath + "src/Test/MakeTutor/Makefile", + SymbolicPath + "src/Test/MakeTutor/hellofunc.c", + SymbolicPath + "src/Test/MakeTutor/hellomake.c", + SymbolicPath + "src/Test/MakeTutor/hellomake.h", + SymbolicPath + "src/Test/Tar/list.txt", + SymbolicPath + "src/Test/Ninja/*.ninja", + SymbolicPath + "src/Test/Ninja/subdir/*.ninja", + SymbolicPath + "src/Test/Ninja/*.output", + SymbolicPath + "src/Test/Progress/*.prog", + SymbolicPath + "src/Test/Tup/hello.c", + SymbolicPath + "src/Test/Tup/root.cfg", + SymbolicPath + "src/Test/Tup/newmath/root.cfg", + SymbolicPath + "src/Test/Tup/newmath/square.c", + SymbolicPath + "src/Test/Tup/newmath/square.h", + SymbolicPath "src/Paths.hs", + SymbolicPath "docs/Manual.md", + SymbolicPath + "docs/shake-progress.png"], + extraTmpFiles = [], + extraDocFiles = [ + SymbolicPath "CHANGES.txt", + SymbolicPath "README.md"], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-1.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-1.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-1.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-1.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-1.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-1.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-1.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-1.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-1.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-1.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-1.condLibrary.expr new file mode 100644 index 00000000000..acc4281010f --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-1.condLibrary.expr @@ -0,0 +1,69 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-1.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-1.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-1.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-1.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-1.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-1.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-1.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-1.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-1.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-1.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-1.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-1.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-1.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-1.packageDescription.expr new file mode 100644 index 00000000000..41d93e68b81 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-1.packageDescription.expr @@ -0,0 +1,35 @@ +PackageDescription { + specVersion = CabalSpecV2_0, + package = PackageIdentifier { + pkgName = PackageName "spdx", + pkgVersion = mkVersion [0]}, + licenseRaw = Right BSD3, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = + "testing positive parsing of spdx identifiers", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-2.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-2.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-2.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-2.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-2.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-2.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-2.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-2.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-2.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-2.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-2.condLibrary.expr new file mode 100644 index 00000000000..acc4281010f --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-2.condLibrary.expr @@ -0,0 +1,69 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-2.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-2.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-2.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-2.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-2.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-2.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-2.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-2.expr deleted file mode 100644 index 9cd00ea1103..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/spdx-2.expr +++ /dev/null @@ -1,117 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV2_2, - package = PackageIdentifier { - pkgName = PackageName "spdx", - pkgVersion = mkVersion [0]}, - licenseRaw = Left - (License - (ELicense - (ELicenseId AGPL_1_0) - Nothing)), - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = - "testing positive parsing of spdx identifiers", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Just Simple, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-2.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-2.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-2.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-2.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-2.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-2.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-2.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-2.packageDescription.expr new file mode 100644 index 00000000000..2b817e741b5 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-2.packageDescription.expr @@ -0,0 +1,39 @@ +PackageDescription { + specVersion = CabalSpecV2_2, + package = PackageIdentifier { + pkgName = PackageName "spdx", + pkgVersion = mkVersion [0]}, + licenseRaw = Left + (License + (ELicense + (ELicenseId AGPL_1_0) + Nothing)), + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = + "testing positive parsing of spdx identifiers", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-3.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-3.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-3.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-3.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-3.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-3.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-3.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-3.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-3.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-3.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-3.condLibrary.expr new file mode 100644 index 00000000000..acc4281010f --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-3.condLibrary.expr @@ -0,0 +1,69 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}}, + condTreeConstraints = [], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-3.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-3.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-3.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-3.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-3.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-3.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-3.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-3.expr deleted file mode 100644 index e8b2eca8989..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/spdx-3.expr +++ /dev/null @@ -1,117 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV2_4, - package = PackageIdentifier { - pkgName = PackageName "spdx", - pkgVersion = mkVersion [0]}, - licenseRaw = Left - (License - (ELicense - (ELicenseId AGPL_1_0_only) - Nothing)), - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = - "testing positive parsing of spdx identifiers", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Just Simple, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}}, - condTreeConstraints = [], - condTreeComponents = []}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-3.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-3.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-3.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-3.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-3.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-3.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-3.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-3.packageDescription.expr new file mode 100644 index 00000000000..24eabcdd94d --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-3.packageDescription.expr @@ -0,0 +1,39 @@ +PackageDescription { + specVersion = CabalSpecV2_4, + package = PackageIdentifier { + pkgName = PackageName "spdx", + pkgVersion = mkVersion [0]}, + licenseRaw = Left + (License + (ELicense + (ELicenseId AGPL_1_0_only) + Nothing)), + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = + "testing positive parsing of spdx identifiers", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.cabal b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.cabal new file mode 100644 index 00000000000..7383cc88244 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.cabal @@ -0,0 +1,68 @@ +cabal-version: 2.2 +name: supervisors +version: 0.2.1.0 +stability: Experimental +synopsis: Monitor groups of threads with non-hierarchical lifetimes. +description: + The @supervisors@ package provides a useful abstraction for managing the + groups of Haskell threads, which may not have a strictly hierarchical + structure to their lifetimes. + . + Concretely, the library provides a `Supervisor` construct, which can be + used to safely spawn threads while guaranteeing that: + . + * When the supervisor is killed, all of the threads it supervises will be + killed. + * Child threads can terminate in any order, and memory usage will always + be proportional to the number of *live* supervised threads. + . + One way to think of it is that @supervisors@ is to @async@ as + @resourcet@ is to @bracket@. + . + Note that this package is EXPERIMENTAL; it needs more careful testing before + I can earnestly recommend relying on it. + . + See the README and module documentation for more information. +homepage: https://github.com/zenhack/haskell-supervisors +bug-reports: https://github.com/zenhack/haskell-supervisors/issues +license: MIT +license-file: LICENSE +author: Ian Denhardt +maintainer: ian@zenhack.net +copyright: 2018 Ian Denhardt +category: Concurrency +build-type: Simple +extra-source-files: + CHANGELOG.md + , README.md + , .gitignore + +common shared-opts + build-depends: + base >=4.11 && <5 + +library + import: shared-opts + exposed-modules: Supervisors + hs-source-dirs: src/ + build-depends: + stm ^>=2.5 + , containers >=0.5.9 && <0.7 + , safe-exceptions ^>= 0.1.7 + , async ^>=2.2.1 + default-language: Haskell2010 + +test-suite tests + import: shared-opts + type: exitcode-stdio-1.0 + main-is: Main.hs + hs-source-dirs: tests/ + build-depends: + supervisors + , hspec >=2.6.0 && <2.8 + default-language: Haskell2010 + +source-repository head + type: git + branch: master + location: https://github.com/zenhack/haskell-supervisors.git diff --git a/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.condLibrary.expr new file mode 100644 index 00000000000..d8a36ba0d5d --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.condLibrary.expr @@ -0,0 +1,133 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName "Supervisors"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "src/"], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 11])) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "stm") + (MajorBoundVersion + (mkVersion [2, 5])) + mainLibSet, + Dependency + (PackageName "containers") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 5, 9])) + (EarlierVersion + (mkVersion [0, 7]))) + mainLibSet, + Dependency + (PackageName "safe-exceptions") + (MajorBoundVersion + (mkVersion [0, 1, 7])) + mainLibSet, + Dependency + (PackageName "async") + (MajorBoundVersion + (mkVersion [2, 2, 1])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 11])) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "stm") + (MajorBoundVersion + (mkVersion [2, 5])) + mainLibSet, + Dependency + (PackageName "containers") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [0, 5, 9])) + (EarlierVersion + (mkVersion [0, 7]))) + mainLibSet, + Dependency + (PackageName "safe-exceptions") + (MajorBoundVersion + (mkVersion [0, 1, 7])) + mainLibSet, + Dependency + (PackageName "async") + (MajorBoundVersion + (mkVersion [2, 2, 1])) + mainLibSet], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.expr b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.condTestSuites.expr similarity index 55% rename from Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.expr rename to Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.condTestSuites.expr index 553b88dc595..a3550addbef 100644 --- a/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.expr +++ b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.condTestSuites.expr @@ -1,64 +1,23 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV3_0, - package = PackageIdentifier { - pkgName = PackageName - "hidden-main-lib", - pkgVersion = mkVersion [0]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = - "main lib have to be visible", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Just Simple, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just +[ + _×_ + (UnqualComponentName "tests") CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [ - ModuleName "ElseIf"], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + (SymbolicPath "Main.hs"), + testBuildInfo = BuildInfo { buildable = True, buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -69,7 +28,8 @@ GenericPackageDescription { cSources = [], cxxSources = [], jsSources = [], - hsSourceDirs = [], + hsSourceDirs = [ + SymbolicPath "tests/"], otherModules = [], virtualModules = [], autogenModules = [], @@ -107,17 +67,45 @@ GenericPackageDescription { targetBuildDepends = [ Dependency (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 11])) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "supervisors") (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "hspec") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [2, 6, 0])) + (EarlierVersion + (mkVersion [2, 8]))) mainLibSet], - mixins = []}}, + mixins = []}, + testCodeGenerators = []}, condTreeConstraints = [ Dependency (PackageName "base") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [4, 11])) + (EarlierVersion + (mkVersion [5]))) + mainLibSet, + Dependency + (PackageName "supervisors") (OrLaterVersion (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "hspec") + (IntersectVersionRanges + (OrLaterVersion + (mkVersion [2, 6, 0])) + (EarlierVersion + (mkVersion [2, 8]))) mainLibSet], - condTreeComponents = []}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} + condTreeComponents = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.format b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.format new file mode 100644 index 00000000000..036bc904e3f --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.format @@ -0,0 +1,65 @@ +cabal-version: 2.2 +name: supervisors +version: 0.2.1.0 +license: MIT +license-file: LICENSE +copyright: 2018 Ian Denhardt +maintainer: ian@zenhack.net +author: Ian Denhardt +stability: Experimental +homepage: https://github.com/zenhack/haskell-supervisors +bug-reports: https://github.com/zenhack/haskell-supervisors/issues +synopsis: Monitor groups of threads with non-hierarchical lifetimes. +description: + The @supervisors@ package provides a useful abstraction for managing the + groups of Haskell threads, which may not have a strictly hierarchical + structure to their lifetimes. + . + Concretely, the library provides a `Supervisor` construct, which can be + used to safely spawn threads while guaranteeing that: + . + * When the supervisor is killed, all of the threads it supervises will be + killed. + * Child threads can terminate in any order, and memory usage will always + be proportional to the number of *live* supervised threads. + . + One way to think of it is that @supervisors@ is to @async@ as + @resourcet@ is to @bracket@. + . + Note that this package is EXPERIMENTAL; it needs more careful testing before + I can earnestly recommend relying on it. + . + See the README and module documentation for more information. + +category: Concurrency +build-type: Simple +extra-source-files: + CHANGELOG.md + README.md + .gitignore + +source-repository head + type: git + location: https://github.com/zenhack/haskell-supervisors.git + branch: master + +library + exposed-modules: Supervisors + hs-source-dirs: src/ + default-language: Haskell2010 + build-depends: + base >=4.11 && <5, + stm ^>=2.5, + containers >=0.5.9 && <0.7, + safe-exceptions ^>=0.1.7, + async ^>=2.2.1 + +test-suite tests + type: exitcode-stdio-1.0 + main-is: Main.hs + hs-source-dirs: tests/ + default-language: Haskell2010 + build-depends: + base >=4.11 && <5, + supervisors, + hspec >=2.6.0 && <2.8 diff --git a/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.packageDescription.expr new file mode 100644 index 00000000000..986ffb60e5d --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/supervisors-0.1.packageDescription.expr @@ -0,0 +1,78 @@ +PackageDescription { + specVersion = CabalSpecV2_2, + package = PackageIdentifier { + pkgName = PackageName + "supervisors", + pkgVersion = mkVersion + [0, 2, 1, 0]}, + licenseRaw = Left + (License + (ELicense + (ELicenseId MIT) + Nothing)), + licenseFiles = [ + SymbolicPath "LICENSE"], + copyright = "2018 Ian Denhardt", + maintainer = "ian@zenhack.net", + author = "Ian Denhardt", + stability = "Experimental", + testedWith = [], + homepage = + "https://github.com/zenhack/haskell-supervisors", + pkgUrl = "", + bugReports = + "https://github.com/zenhack/haskell-supervisors/issues", + sourceRepos = [ + SourceRepo { + repoKind = RepoHead, + repoType = Just + (KnownRepoType Git), + repoLocation = Just + "https://github.com/zenhack/haskell-supervisors.git", + repoModule = Nothing, + repoBranch = Just "master", + repoTag = Nothing, + repoSubdir = Nothing}], + synopsis = + "Monitor groups of threads with non-hierarchical lifetimes.", + description = + concat + [ + "The @supervisors@ package provides a useful abstraction for managing the\n", + "groups of Haskell threads, which may not have a strictly hierarchical\n", + "structure to their lifetimes.\n", + "\n", + "Concretely, the library provides a `Supervisor` construct, which can be\n", + "used to safely spawn threads while guaranteeing that:\n", + "\n", + "* When the supervisor is killed, all of the threads it supervises will be\n", + "killed.\n", + "* Child threads can terminate in any order, and memory usage will always\n", + "be proportional to the number of *live* supervised threads.\n", + "\n", + "One way to think of it is that @supervisors@ is to @async@ as\n", + "@resourcet@ is to @bracket@.\n", + "\n", + "Note that this package is EXPERIMENTAL; it needs more careful testing before\n", + "I can earnestly recommend relying on it.\n", + "\n", + "See the README and module documentation for more information."], + category = "Concurrency", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [ + SymbolicPath "CHANGELOG.md", + SymbolicPath "README.md", + SymbolicPath ".gitignore"], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.condLibrary.expr new file mode 100644 index 00000000000..9d38e7a75c1 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.condLibrary.expr @@ -0,0 +1,171 @@ +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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.condTestSuites.expr new file mode 100644 index 00000000000..62ecef18b01 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.condTestSuites.expr @@ -0,0 +1,360 @@ +[ + _×_ + (UnqualComponentName "tests") + CondNode { + condTreeData = TestSuite { + testName = UnqualComponentName + "", + testInterface = TestSuiteExeV10 + (mkVersion [1, 0]) + (SymbolicPath "Main.hs"), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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]) + (SymbolicPath "doctests.hs"), + testBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + 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 = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [], + mixins = []}, + testCodeGenerators = []}, + condTreeConstraints = [], + condTreeComponents = []}, + condBranchIfFalse = Nothing}]}] diff --git a/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.expr b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.expr deleted file mode 100644 index 2db686aa40f..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.expr +++ /dev/null @@ -1,602 +0,0 @@ -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 ", - 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 = SymbolicPath ".", - extraSrcFiles = [ - SymbolicPath ".ghci", - SymbolicPath ".gitignore", - SymbolicPath ".travis.yml", - SymbolicPath ".vim.custom", - SymbolicPath "README.md"], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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]) - (SymbolicPath "Main.hs"), - testBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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]) - (SymbolicPath "doctests.hs"), - testBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - 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 = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [], - mixins = []}, - testCodeGenerators = []}, - condTreeConstraints = [], - condTreeComponents = []}, - condBranchIfFalse = Nothing}]}], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.packageDescription.expr new file mode 100644 index 00000000000..a7da3fc91ee --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.packageDescription.expr @@ -0,0 +1,63 @@ +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 ", + 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 = SymbolicPath ".", + extraSrcFiles = [ + SymbolicPath ".ghci", + SymbolicPath ".gitignore", + SymbolicPath ".travis.yml", + SymbolicPath ".vim.custom", + SymbolicPath "README.md"], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/version-sets.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/version-sets.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/version-sets.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/version-sets.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/version-sets.condExecutables.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/version-sets.condExecutables.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/version-sets.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/version-sets.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/version-sets.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/version-sets.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/version-sets.condLibrary.expr new file mode 100644 index 00000000000..df733761c24 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/version-sets.condLibrary.expr @@ -0,0 +1,197 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "network") + (MajorBoundVersion + (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "base") + (ThisVersion (mkVersion [1])) + mainLibSet, + Dependency + (PackageName "base") + (ThisVersion (mkVersion [1])) + mainLibSet, + Dependency + (PackageName "base") + (UnionVersionRanges + (ThisVersion (mkVersion [1])) + (ThisVersion (mkVersion [2]))) + mainLibSet, + Dependency + (PackageName "base") + (ThisVersion (mkVersion [1, 2])) + mainLibSet, + Dependency + (PackageName "base") + (UnionVersionRanges + (ThisVersion (mkVersion [1, 2])) + (ThisVersion + (mkVersion [3, 4]))) + mainLibSet, + Dependency + (PackageName "ghc") + (UnionVersionRanges + (ThisVersion + (mkVersion [8, 6, 3])) + (UnionVersionRanges + (ThisVersion + (mkVersion [8, 4, 4])) + (UnionVersionRanges + (ThisVersion + (mkVersion [8, 2, 2])) + (UnionVersionRanges + (ThisVersion + (mkVersion [8, 0, 2])) + (UnionVersionRanges + (ThisVersion + (mkVersion [7, 10, 3])) + (UnionVersionRanges + (ThisVersion + (mkVersion [7, 8, 4])) + (UnionVersionRanges + (ThisVersion + (mkVersion [7, 6, 3])) + (ThisVersion + (mkVersion [7, 4, 2]))))))))) + mainLibSet, + Dependency + (PackageName "Cabal") + (UnionVersionRanges + (MajorBoundVersion + (mkVersion [2, 4, 1, 1])) + (MajorBoundVersion + (mkVersion [2, 2, 0, 0]))) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "network") + (MajorBoundVersion + (mkVersion [0])) + mainLibSet, + Dependency + (PackageName "base") + (ThisVersion (mkVersion [1])) + mainLibSet, + Dependency + (PackageName "base") + (ThisVersion (mkVersion [1])) + mainLibSet, + Dependency + (PackageName "base") + (UnionVersionRanges + (ThisVersion (mkVersion [1])) + (ThisVersion (mkVersion [2]))) + mainLibSet, + Dependency + (PackageName "base") + (ThisVersion (mkVersion [1, 2])) + mainLibSet, + Dependency + (PackageName "base") + (UnionVersionRanges + (ThisVersion (mkVersion [1, 2])) + (ThisVersion + (mkVersion [3, 4]))) + mainLibSet, + Dependency + (PackageName "ghc") + (UnionVersionRanges + (ThisVersion + (mkVersion [8, 6, 3])) + (UnionVersionRanges + (ThisVersion + (mkVersion [8, 4, 4])) + (UnionVersionRanges + (ThisVersion + (mkVersion [8, 2, 2])) + (UnionVersionRanges + (ThisVersion + (mkVersion [8, 0, 2])) + (UnionVersionRanges + (ThisVersion + (mkVersion [7, 10, 3])) + (UnionVersionRanges + (ThisVersion + (mkVersion [7, 8, 4])) + (UnionVersionRanges + (ThisVersion + (mkVersion [7, 6, 3])) + (ThisVersion + (mkVersion [7, 4, 2]))))))))) + mainLibSet, + Dependency + (PackageName "Cabal") + (UnionVersionRanges + (MajorBoundVersion + (mkVersion [2, 4, 1, 1])) + (MajorBoundVersion + (mkVersion [2, 2, 0, 0]))) + mainLibSet], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/version-sets.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/version-sets.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/version-sets.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/version-sets.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/version-sets.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/version-sets.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/version-sets.expr b/Cabal-tests/tests/ParserTests/regressions/version-sets.expr deleted file mode 100644 index c086ae618aa..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/version-sets.expr +++ /dev/null @@ -1,267 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV3_0, - package = PackageIdentifier { - pkgName = PackageName - "version-sets", - pkgVersion = mkVersion [0]}, - licenseRaw = Left NONE, - licenseFiles = [], - copyright = "", - maintainer = "", - author = "", - stability = "", - testedWith = [ - _×_ - GHC - (UnionVersionRanges - (ThisVersion - (mkVersion [8, 6, 3])) - (UnionVersionRanges - (ThisVersion - (mkVersion [8, 4, 4])) - (UnionVersionRanges - (ThisVersion - (mkVersion [8, 2, 2])) - (UnionVersionRanges - (ThisVersion - (mkVersion [8, 0, 2])) - (UnionVersionRanges - (ThisVersion - (mkVersion [7, 10, 3])) - (UnionVersionRanges - (ThisVersion - (mkVersion [7, 8, 4])) - (UnionVersionRanges - (ThisVersion - (mkVersion [7, 6, 3])) - (ThisVersion - (mkVersion [7, 4, 2])))))))))], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [], - synopsis = - "version set notation", - description = "", - category = "", - customFieldsPD = [], - buildTypeRaw = Nothing, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "network") - (MajorBoundVersion - (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "base") - (ThisVersion (mkVersion [1])) - mainLibSet, - Dependency - (PackageName "base") - (ThisVersion (mkVersion [1])) - mainLibSet, - Dependency - (PackageName "base") - (UnionVersionRanges - (ThisVersion (mkVersion [1])) - (ThisVersion (mkVersion [2]))) - mainLibSet, - Dependency - (PackageName "base") - (ThisVersion (mkVersion [1, 2])) - mainLibSet, - Dependency - (PackageName "base") - (UnionVersionRanges - (ThisVersion (mkVersion [1, 2])) - (ThisVersion - (mkVersion [3, 4]))) - mainLibSet, - Dependency - (PackageName "ghc") - (UnionVersionRanges - (ThisVersion - (mkVersion [8, 6, 3])) - (UnionVersionRanges - (ThisVersion - (mkVersion [8, 4, 4])) - (UnionVersionRanges - (ThisVersion - (mkVersion [8, 2, 2])) - (UnionVersionRanges - (ThisVersion - (mkVersion [8, 0, 2])) - (UnionVersionRanges - (ThisVersion - (mkVersion [7, 10, 3])) - (UnionVersionRanges - (ThisVersion - (mkVersion [7, 8, 4])) - (UnionVersionRanges - (ThisVersion - (mkVersion [7, 6, 3])) - (ThisVersion - (mkVersion [7, 4, 2]))))))))) - mainLibSet, - Dependency - (PackageName "Cabal") - (UnionVersionRanges - (MajorBoundVersion - (mkVersion [2, 4, 1, 1])) - (MajorBoundVersion - (mkVersion [2, 2, 0, 0]))) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "network") - (MajorBoundVersion - (mkVersion [0])) - mainLibSet, - Dependency - (PackageName "base") - (ThisVersion (mkVersion [1])) - mainLibSet, - Dependency - (PackageName "base") - (ThisVersion (mkVersion [1])) - mainLibSet, - Dependency - (PackageName "base") - (UnionVersionRanges - (ThisVersion (mkVersion [1])) - (ThisVersion (mkVersion [2]))) - mainLibSet, - Dependency - (PackageName "base") - (ThisVersion (mkVersion [1, 2])) - mainLibSet, - Dependency - (PackageName "base") - (UnionVersionRanges - (ThisVersion (mkVersion [1, 2])) - (ThisVersion - (mkVersion [3, 4]))) - mainLibSet, - Dependency - (PackageName "ghc") - (UnionVersionRanges - (ThisVersion - (mkVersion [8, 6, 3])) - (UnionVersionRanges - (ThisVersion - (mkVersion [8, 4, 4])) - (UnionVersionRanges - (ThisVersion - (mkVersion [8, 2, 2])) - (UnionVersionRanges - (ThisVersion - (mkVersion [8, 0, 2])) - (UnionVersionRanges - (ThisVersion - (mkVersion [7, 10, 3])) - (UnionVersionRanges - (ThisVersion - (mkVersion [7, 8, 4])) - (UnionVersionRanges - (ThisVersion - (mkVersion [7, 6, 3])) - (ThisVersion - (mkVersion [7, 4, 2]))))))))) - mainLibSet, - Dependency - (PackageName "Cabal") - (UnionVersionRanges - (MajorBoundVersion - (mkVersion [2, 4, 1, 1])) - (MajorBoundVersion - (mkVersion [2, 2, 0, 0]))) - mainLibSet], - condTreeComponents = []}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/version-sets.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/version-sets.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/version-sets.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/version-sets.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/version-sets.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/version-sets.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/version-sets.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/version-sets.packageDescription.expr new file mode 100644 index 00000000000..1bd11195017 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/version-sets.packageDescription.expr @@ -0,0 +1,61 @@ +PackageDescription { + specVersion = CabalSpecV3_0, + package = PackageIdentifier { + pkgName = PackageName + "version-sets", + pkgVersion = mkVersion [0]}, + licenseRaw = Left NONE, + licenseFiles = [], + copyright = "", + maintainer = "", + author = "", + stability = "", + testedWith = [ + _×_ + GHC + (UnionVersionRanges + (ThisVersion + (mkVersion [8, 6, 3])) + (UnionVersionRanges + (ThisVersion + (mkVersion [8, 4, 4])) + (UnionVersionRanges + (ThisVersion + (mkVersion [8, 2, 2])) + (UnionVersionRanges + (ThisVersion + (mkVersion [8, 0, 2])) + (UnionVersionRanges + (ThisVersion + (mkVersion [7, 10, 3])) + (UnionVersionRanges + (ThisVersion + (mkVersion [7, 8, 4])) + (UnionVersionRanges + (ThisVersion + (mkVersion [7, 6, 3])) + (ThisVersion + (mkVersion [7, 4, 2])))))))))], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [], + synopsis = + "version set notation", + description = "", + category = "", + customFieldsPD = [], + buildTypeRaw = Nothing, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.condBenchmarks.expr b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.condBenchmarks.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.condBenchmarks.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.condExecutables.expr b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.condExecutables.expr new file mode 100644 index 00000000000..51a66ba1496 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.condExecutables.expr @@ -0,0 +1,97 @@ +[ + _×_ + (UnqualComponentName + "wl-pprint-string-example") + CondNode { + condTreeData = Executable { + exeName = UnqualComponentName + "wl-pprint-string-example", + modulePath = SymbolicPath + "Main.hs", + exeScope = ExecutablePublic, + buildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + ldOptions = [], + hsc2hsOptions = [], + pkgconfigDepends = [], + frameworks = [], + extraFrameworkDirs = [], + asmSources = [], + cmmSources = [], + cSources = [], + cxxSources = [], + jsSources = [], + hsSourceDirs = [ + SymbolicPath "example-string"], + otherModules = [ + ModuleName "StringImpl"], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (EarlierVersion (mkVersion [5])) + mainLibSet, + Dependency + (PackageName "str-string") + (OrLaterVersion + (mkVersion [0, 1, 0, 0])) + mainLibSet, + Dependency + (PackageName "wl-pprint-indef") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (EarlierVersion (mkVersion [5])) + mainLibSet, + Dependency + (PackageName "str-string") + (OrLaterVersion + (mkVersion [0, 1, 0, 0])) + mainLibSet, + Dependency + (PackageName "wl-pprint-indef") + (OrLaterVersion (mkVersion [0])) + mainLibSet], + condTreeComponents = []}] diff --git a/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.condForeignLibs.expr b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.condForeignLibs.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.condForeignLibs.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.condLibrary.expr b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.condLibrary.expr new file mode 100644 index 00000000000..b002e47ae46 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.condLibrary.expr @@ -0,0 +1,88 @@ +Just + CondNode { + condTreeData = Library { + libName = LMainLibName, + exposedModules = [ + ModuleName + "Text.PrettyPrint.Leijen"], + reexportedModules = [], + signatures = [], + libExposed = True, + libVisibility = + LibraryVisibilityPublic, + libBuildInfo = BuildInfo { + buildable = True, + buildTools = [], + buildToolDepends = [], + cppOptions = [], + asmOptions = [], + cmmOptions = [], + ccOptions = [], + cxxOptions = [], + jsppOptions = [], + 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 [] [], + profSharedOptions = + PerCompilerFlavor [] [], + staticOptions = + PerCompilerFlavor [] [], + customFieldsBI = [], + targetBuildDepends = [ + Dependency + (PackageName "base") + (EarlierVersion (mkVersion [5])) + mainLibSet, + Dependency + (PackageName "str-sig") + (OrLaterVersion + (mkVersion [0, 1, 0, 0])) + mainLibSet], + mixins = []}}, + condTreeConstraints = [ + Dependency + (PackageName "base") + (EarlierVersion (mkVersion [5])) + mainLibSet, + Dependency + (PackageName "str-sig") + (OrLaterVersion + (mkVersion [0, 1, 0, 0])) + mainLibSet], + condTreeComponents = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.condSubLibraries.expr b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.condSubLibraries.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.condSubLibraries.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.condTestSuites.expr b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.condTestSuites.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.condTestSuites.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.expr b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.expr deleted file mode 100644 index e4e6a457a3d..00000000000 --- a/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.expr +++ /dev/null @@ -1,246 +0,0 @@ -GenericPackageDescription { - packageDescription = - PackageDescription { - specVersion = CabalSpecV1_6, - package = PackageIdentifier { - pkgName = PackageName - "wl-pprint-indef", - pkgVersion = mkVersion [1, 2]}, - licenseRaw = Right BSD3, - licenseFiles = [ - SymbolicPath "LICENSE"], - copyright = "", - maintainer = - "Noam Lewis ", - author = "Daan Leijen", - stability = "", - testedWith = [], - homepage = "", - pkgUrl = "", - bugReports = "", - sourceRepos = [ - SourceRepo { - repoKind = RepoHead, - repoType = Just - (KnownRepoType Git), - repoLocation = Just - "git@github.com:danidiaz/wl-pprint-indef.git", - repoModule = Nothing, - repoBranch = Nothing, - repoTag = Nothing, - repoSubdir = Nothing}], - synopsis = - "The Wadler/Leijen Pretty Printer", - description = - concat - [ - "This is a pretty printing library based on Wadler's paper \"A Prettier\n", - "Printer\". See the haddocks for full info. This version allows the\n", - "library user to declare overlapping instances of the 'Pretty' class."], - category = "Text", - customFieldsPD = [], - buildTypeRaw = Just Simple, - setupBuildInfo = Nothing, - library = Nothing, - subLibraries = [], - executables = [], - foreignLibs = [], - testSuites = [], - benchmarks = [], - dataFiles = [], - dataDir = SymbolicPath ".", - extraSrcFiles = [], - extraTmpFiles = [], - extraDocFiles = [], - extraFiles = []}, - gpdScannedVersion = Nothing, - genPackageFlags = [], - condLibrary = Just - CondNode { - condTreeData = Library { - libName = LMainLibName, - exposedModules = [ - ModuleName - "Text.PrettyPrint.Leijen"], - reexportedModules = [], - signatures = [], - libExposed = True, - libVisibility = - LibraryVisibilityPublic, - libBuildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (EarlierVersion (mkVersion [5])) - mainLibSet, - Dependency - (PackageName "str-sig") - (OrLaterVersion - (mkVersion [0, 1, 0, 0])) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (EarlierVersion (mkVersion [5])) - mainLibSet, - Dependency - (PackageName "str-sig") - (OrLaterVersion - (mkVersion [0, 1, 0, 0])) - mainLibSet], - condTreeComponents = []}, - condSubLibraries = [], - condForeignLibs = [], - condExecutables = [ - _×_ - (UnqualComponentName - "wl-pprint-string-example") - CondNode { - condTreeData = Executable { - exeName = UnqualComponentName - "wl-pprint-string-example", - modulePath = SymbolicPath - "Main.hs", - exeScope = ExecutablePublic, - buildInfo = BuildInfo { - buildable = True, - buildTools = [], - buildToolDepends = [], - cppOptions = [], - jsppOptions = [], - asmOptions = [], - cmmOptions = [], - ccOptions = [], - cxxOptions = [], - ldOptions = [], - hsc2hsOptions = [], - pkgconfigDepends = [], - frameworks = [], - extraFrameworkDirs = [], - asmSources = [], - cmmSources = [], - cSources = [], - cxxSources = [], - jsSources = [], - hsSourceDirs = [ - SymbolicPath "example-string"], - otherModules = [ - ModuleName "StringImpl"], - 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 [] [], - profSharedOptions = - PerCompilerFlavor [] [], - staticOptions = - PerCompilerFlavor [] [], - customFieldsBI = [], - targetBuildDepends = [ - Dependency - (PackageName "base") - (EarlierVersion (mkVersion [5])) - mainLibSet, - Dependency - (PackageName "str-string") - (OrLaterVersion - (mkVersion [0, 1, 0, 0])) - mainLibSet, - Dependency - (PackageName "wl-pprint-indef") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - mixins = []}}, - condTreeConstraints = [ - Dependency - (PackageName "base") - (EarlierVersion (mkVersion [5])) - mainLibSet, - Dependency - (PackageName "str-string") - (OrLaterVersion - (mkVersion [0, 1, 0, 0])) - mainLibSet, - Dependency - (PackageName "wl-pprint-indef") - (OrLaterVersion (mkVersion [0])) - mainLibSet], - condTreeComponents = []}], - condTestSuites = [], - condBenchmarks = []} diff --git a/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.genPackageFlags.expr b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.genPackageFlags.expr new file mode 100644 index 00000000000..fe51488c706 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.genPackageFlags.expr @@ -0,0 +1 @@ +[] diff --git a/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.gpdScannedVersion.expr b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.gpdScannedVersion.expr new file mode 100644 index 00000000000..4a584e49892 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.gpdScannedVersion.expr @@ -0,0 +1 @@ +Nothing diff --git a/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.packageDescription.expr b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.packageDescription.expr new file mode 100644 index 00000000000..d908d39c1a8 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.packageDescription.expr @@ -0,0 +1,53 @@ +PackageDescription { + specVersion = CabalSpecV1_6, + package = PackageIdentifier { + pkgName = PackageName + "wl-pprint-indef", + pkgVersion = mkVersion [1, 2]}, + licenseRaw = Right BSD3, + licenseFiles = [ + SymbolicPath "LICENSE"], + copyright = "", + maintainer = + "Noam Lewis ", + author = "Daan Leijen", + stability = "", + testedWith = [], + homepage = "", + pkgUrl = "", + bugReports = "", + sourceRepos = [ + SourceRepo { + repoKind = RepoHead, + repoType = Just + (KnownRepoType Git), + repoLocation = Just + "git@github.com:danidiaz/wl-pprint-indef.git", + repoModule = Nothing, + repoBranch = Nothing, + repoTag = Nothing, + repoSubdir = Nothing}], + synopsis = + "The Wadler/Leijen Pretty Printer", + description = + concat + [ + "This is a pretty printing library based on Wadler's paper \"A Prettier\n", + "Printer\". See the haddocks for full info. This version allows the\n", + "library user to declare overlapping instances of the 'Pretty' class."], + category = "Text", + customFieldsPD = [], + buildTypeRaw = Just Simple, + setupBuildInfo = Nothing, + library = Nothing, + subLibraries = [], + executables = [], + foreignLibs = [], + testSuites = [], + benchmarks = [], + dataFiles = [], + dataDir = SymbolicPath ".", + extraSrcFiles = [], + extraTmpFiles = [], + extraDocFiles = [], + extraFiles = []} diff --git a/Cabal-tests/tests/UnitTests/Distribution/Types/GenericPackageDescription.hs b/Cabal-tests/tests/UnitTests/Distribution/Types/GenericPackageDescription.hs index b8653abd38f..4554df8028e 100644 --- a/Cabal-tests/tests/UnitTests/Distribution/Types/GenericPackageDescription.hs +++ b/Cabal-tests/tests/UnitTests/Distribution/Types/GenericPackageDescription.hs @@ -17,14 +17,16 @@ tests = gpdFields :: [(String, GenericPackageDescription -> GenericPackageDescription)] gpdFields = - [ ("packageDescription", \gpd -> gpd { packageDescription = undefined }) - , ("genPackageFlags", \gpd -> gpd { genPackageFlags = undefined }) - , ("condLibrary", \gpd -> gpd { condLibrary = undefined }) - , ("condSubLibraries", \gpd -> gpd { condSubLibraries = undefined }) - , ("condForeignLibs", \gpd -> gpd { condForeignLibs = undefined }) - , ("condExecutables", \gpd -> gpd { condExecutables = undefined }) - , ("condTestSuites", \gpd -> gpd { condTestSuites = undefined }) - , ("condBenchmarks", \gpd -> gpd { condBenchmarks = undefined }) + [ ("packageDescriptionInternal", \gpd -> gpd { packageDescriptionInternal = undefined }) + , ("gpdScannedVersionInternal", \gpd -> gpd { gpdScannedVersionInternal = undefined }) + , ("genPackageFlagsInternal", \gpd -> gpd { genPackageFlagsInternal = undefined }) + , ("gpdCommonStanzas", \gpd -> gpd { gpdCommonStanzas = undefined }) + , ("condLibraryUnmerged", \gpd -> gpd { condLibraryUnmerged = undefined }) + , ("condSubLibrariesUnmerged", \gpd -> gpd { condSubLibrariesUnmerged = undefined }) + , ("condForeignLibsUnmerged", \gpd -> gpd { condForeignLibsUnmerged = undefined }) + , ("condExecutablesUnmerged", \gpd -> gpd { condExecutablesUnmerged = undefined }) + , ("condTestSuitesUnmerged", \gpd -> gpd { condTestSuitesUnmerged = undefined }) + , ("condBenchmarksUnmerged", \gpd -> gpd { condBenchmarksUnmerged = undefined }) ] gpdDeepseq :: Assertion diff --git a/Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs b/Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs index 129f8d0d85c..6be8ff30239 100644 --- a/Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs +++ b/Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs @@ -29,7 +29,7 @@ md5Check proxy md5Int = structureHash proxy @?= md5FromInteger md5Int md5CheckGenericPackageDescription :: Proxy GenericPackageDescription -> Assertion md5CheckGenericPackageDescription proxy = md5Check proxy - 0xc039c6741dead5203ad2b33bd3bf4dc8 + 0xf530c0714e09f028a58ab1527d235e0f md5CheckLocalBuildInfo :: Proxy LocalBuildInfo -> Assertion md5CheckLocalBuildInfo proxy = md5Check proxy diff --git a/Cabal-tests/tests/custom-setup/CabalDoctestSetup.hs b/Cabal-tests/tests/custom-setup/CabalDoctestSetup.hs index fc2268bad56..7f499e3b3aa 100644 --- a/Cabal-tests/tests/custom-setup/CabalDoctestSetup.hs +++ b/Cabal-tests/tests/custom-setup/CabalDoctestSetup.hs @@ -143,7 +143,9 @@ import Distribution.Types.UnqualComponentName import Distribution.PackageDescription (CondTree (..)) import Distribution.Types.GenericPackageDescription - (GenericPackageDescription (condTestSuites)) + ( GenericPackageDescription + , condTestSuites + ) import Distribution.Version (mkVersion) diff --git a/Cabal-tree-diff/src/Data/TreeDiff/Instances/Cabal.hs b/Cabal-tree-diff/src/Data/TreeDiff/Instances/Cabal.hs index f7e7ca5b7b6..592fa053c31 100644 --- a/Cabal-tree-diff/src/Data/TreeDiff/Instances/Cabal.hs +++ b/Cabal-tree-diff/src/Data/TreeDiff/Instances/Cabal.hs @@ -55,11 +55,13 @@ instance ToExpr Dependency where instance ToExpr (SymbolicPathX allowAbs from to) instance ToExpr a => ToExpr (InstallDirs a) +instance ToExpr a => ToExpr (WithImports a) instance ToExpr AbiDependency instance ToExpr AbiHash instance ToExpr Arch instance ToExpr Benchmark +instance ToExpr BenchmarkStanza instance ToExpr BenchmarkInterface instance ToExpr BenchmarkType instance ToExpr BuildInfo @@ -117,6 +119,7 @@ instance ToExpr SetupBuildInfo instance ToExpr SourceRepo instance ToExpr TestShowDetails instance ToExpr TestSuite +instance ToExpr TestSuiteStanza instance ToExpr TestSuiteInterface instance ToExpr TestType instance ToExpr UnitId diff --git a/Cabal/src/Distribution/PackageDescription/Check.hs b/Cabal/src/Distribution/PackageDescription/Check.hs index 0593ce8d905..27cb2aa5d55 100644 --- a/Cabal/src/Distribution/PackageDescription/Check.hs +++ b/Cabal/src/Distribution/PackageDescription/Check.hs @@ -238,8 +238,7 @@ checkGenericPackageDescription checkPackageDescription packageDescription_ -- Targets should be present... let condAllLibraries = - maybeToList condLibrary_ - ++ (map snd condSubLibraries_) + maybeToList condLibrary_ ++ map snd condSubLibraries_ checkP ( and [ null condExecutables_ @@ -958,24 +957,12 @@ pd2gpd pd = gpd gpd = emptyGenericPackageDescription { packageDescription = pd - , condLibrary = fmap t2c (library pd) + , condLibrary = t2c <$> (library pd) , condSubLibraries = map (t2cName ln id) (subLibraries pd) - , condForeignLibs = - map - (t2cName foreignLibName id) - (foreignLibs pd) - , condExecutables = - map - (t2cName exeName id) - (executables pd) - , condTestSuites = - map - (t2cName testName remTest) - (testSuites pd) - , condBenchmarks = - map - (t2cName benchmarkName remBench) - (benchmarks pd) + , condForeignLibs = map (t2cName foreignLibName id) (foreignLibs pd) + , condExecutables = map (t2cName exeName id) (executables pd) + , condTestSuites = map (t2cName testName remTest) (testSuites pd) + , condBenchmarks = map (t2cName benchmarkName remBench) (benchmarks pd) } -- From target to simple, unconditional CondTree. diff --git a/cabal-install-solver/src/Distribution/Solver/Modular/IndexConversion.hs b/cabal-install-solver/src/Distribution/Solver/Modular/IndexConversion.hs index 72d0b8193e3..38dc41e0885 100644 --- a/cabal-install-solver/src/Distribution/Solver/Modular/IndexConversion.hs +++ b/cabal-install-solver/src/Distribution/Solver/Modular/IndexConversion.hs @@ -218,7 +218,7 @@ convGPD os arch cinfo constraints strfl solveExes pn libComps = [ (ExposedLib LMainLibName, libToComponentInfo lib) | lib <- maybeToList mlib ] subLibComps = [ (ExposedLib (LSubLibName name), libToComponentInfo lib) - | (name, lib) <- sub_libs ] + | (name, lib) <- sub_libs ] exeComps = [ ( ExposedExe name , ComponentInfo { compIsVisible = IsVisible True diff --git a/cabal-install/src/Distribution/Client/IndexUtils.hs b/cabal-install/src/Distribution/Client/IndexUtils.hs index f85db2b74c1..8d30ac06c73 100644 --- a/cabal-install/src/Distribution/Client/IndexUtils.hs +++ b/cabal-install/src/Distribution/Client/IndexUtils.hs @@ -4,6 +4,7 @@ {-# LANGUAGE GADTs #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} @@ -80,7 +81,17 @@ import Distribution.Package import Distribution.PackageDescription ( GenericPackageDescription (..) , PackageDescription (..) + , condBenchmarks + , condExecutables + , condForeignLibs + , condLibrary + , condSubLibraries + , condTestSuites , emptyPackageDescription + , genPackageFlags + , gpdScannedVersion + , packageDescription + , pattern GenericPackageDescription ) import Distribution.Simple.Compiler import qualified Distribution.Simple.Configure as Configure diff --git a/cabal-install/src/Distribution/Client/Install.hs b/cabal-install/src/Distribution/Client/Install.hs index bd28046db6e..fb779cc1029 100644 --- a/cabal-install/src/Distribution/Client/Install.hs +++ b/cabal-install/src/Distribution/Client/Install.hs @@ -163,8 +163,8 @@ import Distribution.Package , packageVersion ) import Distribution.PackageDescription - ( GenericPackageDescription (..) - , PackageDescription + ( PackageDescription + , genPackageFlags ) import qualified Distribution.PackageDescription as PackageDescription import Distribution.PackageDescription.Configuration diff --git a/cabal-install/src/Distribution/Client/ScriptUtils.hs b/cabal-install/src/Distribution/Client/ScriptUtils.hs index 1c78d537c19..4e437d28766 100644 --- a/cabal-install/src/Distribution/Client/ScriptUtils.hs +++ b/cabal-install/src/Distribution/Client/ScriptUtils.hs @@ -157,6 +157,7 @@ import Distribution.Types.Executable import Distribution.Types.GenericPackageDescription as GPD ( GenericPackageDescription (..) , emptyGenericPackageDescription + , packageDescription ) import Distribution.Types.PackageDescription ( PackageDescription (..) diff --git a/cabal-install/src/Distribution/Client/SetupWrapper.hs b/cabal-install/src/Distribution/Client/SetupWrapper.hs index 69c8f888698..f11790c7441 100644 --- a/cabal-install/src/Distribution/Client/SetupWrapper.hs +++ b/cabal-install/src/Distribution/Client/SetupWrapper.hs @@ -48,7 +48,7 @@ import Distribution.Package ) import Distribution.PackageDescription ( BuildType (..) - , GenericPackageDescription (packageDescription) + , packageDescription , PackageDescription (..) , buildType , specVersion