diff --git a/Cabal/Cabal-QuickCheck/src/Test/QuickCheck/Instances/Cabal.hs b/Cabal/Cabal-QuickCheck/src/Test/QuickCheck/Instances/Cabal.hs
index 419243ab1be0dde79e56c0a09718f94274c1a4ef..f22d1134bed5b20eef167797b44999c3f4855117 100644
--- a/Cabal/Cabal-QuickCheck/src/Test/QuickCheck/Instances/Cabal.hs
+++ b/Cabal/Cabal-QuickCheck/src/Test/QuickCheck/Instances/Cabal.hs
@@ -176,8 +176,8 @@ instance Arbitrary Bound where
 -------------------------------------------------------------------------------
 
 instance Arbitrary Mixin where
-    arbitrary = genericArbitrary
-    shrink    = genericShrink
+    arbitrary = normaliseMixin <$> genericArbitrary
+    shrink    = fmap normaliseMixin . genericShrink
 
 instance Arbitrary IncludeRenaming where
     arbitrary = genericArbitrary
diff --git a/Cabal/Cabal-described/src/Distribution/Described.hs b/Cabal/Cabal-described/src/Distribution/Described.hs
index 6532f2c4419bd78e4098876575811ef8d0be8a4d..6db2f29e6f53e5b5ca74827da5f8389578216df5 100644
--- a/Cabal/Cabal-described/src/Distribution/Described.hs
+++ b/Cabal/Cabal-described/src/Distribution/Described.hs
@@ -431,7 +431,9 @@ instance Described LibVersionInfo where
         reDigits = reChars ['0'..'9']
 
 instance Described Mixin where
-    describe _ = RENamed "package-name" (describe (Proxy :: Proxy PackageName)) <>
+    describe _ =
+        RENamed "package-name" (describe (Proxy :: Proxy PackageName)) <>
+        REOpt (reChar ':' <> RENamed "library-name" (describe (Proxy :: Proxy UnqualComponentName))) <>
         REOpt (RESpaces1 <> describe (Proxy :: Proxy IncludeRenaming))
 
 instance Described ModuleName where
diff --git a/Cabal/Cabal.cabal b/Cabal/Cabal.cabal
index 0d913388635214b3f624c758adbe1c79eacb9ac0..f3f5a6c3b93ab702289c2dffccfdc4177383ad6f 100644
--- a/Cabal/Cabal.cabal
+++ b/Cabal/Cabal.cabal
@@ -156,6 +156,9 @@ extra-source-files:
   tests/ParserTests/regressions/ghc-option-j.check
   tests/ParserTests/regressions/haddock-api-2.18.1-check.cabal
   tests/ParserTests/regressions/haddock-api-2.18.1-check.check
+  tests/ParserTests/regressions/hasktorch.cabal
+  tests/ParserTests/regressions/hasktorch.expr
+  tests/ParserTests/regressions/hasktorch.format
   tests/ParserTests/regressions/hidden-main-lib.cabal
   tests/ParserTests/regressions/hidden-main-lib.expr
   tests/ParserTests/regressions/hidden-main-lib.format
diff --git a/Cabal/Distribution/Backpack/ConfiguredComponent.hs b/Cabal/Distribution/Backpack/ConfiguredComponent.hs
index df58ab838f2af0b4076a828d22481578baf28951..69178e048ce9e0146963650dc105f40106580e76 100644
--- a/Cabal/Distribution/Backpack/ConfiguredComponent.hs
+++ b/Cabal/Distribution/Backpack/ConfiguredComponent.hs
@@ -32,7 +32,6 @@ import Distribution.Types.PackageName
 import Distribution.Types.Mixin
 import Distribution.Types.ComponentName
 import Distribution.Types.LibraryName
-import Distribution.Types.UnqualComponentName
 import Distribution.Types.ComponentInclude
 import Distribution.Package
 import Distribution.PackageDescription
@@ -48,7 +47,8 @@ import qualified Data.Set as Set
 import qualified Distribution.Compat.NonEmptySet as NonEmptySet
 import qualified Data.Map as Map
 import Distribution.Pretty
-import Text.PrettyPrint
+import Text.PrettyPrint (Doc, hang, text, vcat, hsep, quotes, ($$))
+import qualified Text.PrettyPrint as PP
 
 -- | A configured component, we know exactly what its 'ComponentId' is,
 -- and the 'ComponentId's of the things it depends on.
@@ -112,13 +112,12 @@ mkConfiguredComponent
 mkConfiguredComponent pkg_descr this_cid lib_deps exe_deps component = do
     -- Resolve each @mixins@ into the actual dependency
     -- from @lib_deps@.
-    explicit_includes <- forM (mixins bi) $ \(Mixin name rns) -> do
-        let keys = fixFakePkgName pkg_descr name
-        aid <- case Map.lookup keys deps_map of
+    explicit_includes <- forM (mixins bi) $ \(Mixin pn ln rns) -> do
+        aid <- case Map.lookup (pn, CLibName ln) deps_map of
                 Nothing ->
                     dieProgress $
-                    text "Mix-in refers to non-existent package" <+>
-                    quotes (pretty name) $$
+                    text "Mix-in refers to non-existent library" <+>
+                    quotes (pretty pn <<>> prettyLN ln) $$
                     text "(did you forget to add the package to build-depends?)"
                 Just r  -> return r
         return ComponentInclude {
@@ -150,9 +149,17 @@ mkConfiguredComponent pkg_descr this_cid lib_deps exe_deps component = do
             cc_includes = explicit_includes ++ implicit_includes
         }
   where
+    bi :: BuildInfo
     bi = componentBuildInfo component
+
+    prettyLN :: LibraryName -> Doc
+    prettyLN LMainLibName    = PP.empty
+    prettyLN (LSubLibName n) = PP.colon <<>> pretty n
+
+    deps_map :: Map (PackageName, ComponentName) (AnnotatedId ComponentId)
     deps_map = Map.fromList [ ((packageName dep, ann_cname dep), dep)
                             | dep <- lib_deps ]
+
     is_public = componentName component == CLibName LMainLibName
 
 type ConfiguredComponentMap =
@@ -179,10 +186,7 @@ toConfiguredComponent pkg_descr this_cid lib_dep_map exe_dep_map component = do
                     -- Return all library components
                     forM (NonEmptySet.toList sublibs) $ \lib ->
                         let comp = CLibName lib in
-                        case Map.lookup (CLibName $ LSubLibName $
-                                         packageNameToUnqualComponentName name) pkg
-                         <|> Map.lookup comp pkg
-                        of
+                        case Map.lookup comp pkg of
                             Nothing ->
                                 dieProgress $
                                     text "Dependency on unbuildable" <+>
@@ -302,19 +306,3 @@ newPackageDepsBehaviourMinVersion = CabalSpecV1_8
 newPackageDepsBehaviour :: PackageDescription -> Bool
 newPackageDepsBehaviour pkg =
    specVersion pkg >= newPackageDepsBehaviourMinVersion
-
--- | 'build-depends:' stanzas are currently ambiguous as the external packages
--- and internal libraries are specified the same. For now, we assume internal
--- libraries shadow, and this function disambiguates accordingly, but soon the
--- underlying ambiguity will be addressed.
--- Multiple public libraries (cabal 3.0) added an unambiguous way of specifying
--- sublibraries, but we still have to support the old syntax for bc reasons.
-fixFakePkgName :: PackageDescription -> PackageName -> (PackageName, ComponentName)
-fixFakePkgName pkg_descr pn =
-  if subLibName `elem` internalLibraries
-  then (packageName pkg_descr, CLibName (LSubLibName subLibName))
-  else (pn,                    CLibName LMainLibName            )
-  where
-    subLibName        = packageNameToUnqualComponentName pn
-    internalLibraries = mapMaybe (libraryNameString . libName)
-                        (allLibraries pkg_descr)
diff --git a/Cabal/Distribution/PackageDescription/Parsec.hs b/Cabal/Distribution/PackageDescription/Parsec.hs
index 89cdc57d8f3190e51aa86c5603b5d96e11c150ac..dd969aec0277ffa74ae606d2a82939b7401a874d 100644
--- a/Cabal/Distribution/PackageDescription/Parsec.hs
+++ b/Cabal/Distribution/PackageDescription/Parsec.hs
@@ -47,7 +47,7 @@ import Distribution.Fields.LexerMonad                (LexWarning, toPWarnings)
 import Distribution.Fields.Parser
 import Distribution.Fields.ParseResult
 import Distribution.PackageDescription
-import Distribution.PackageDescription.Configuration (freeVars, transformAllBuildDependsN)
+import Distribution.PackageDescription.Configuration (freeVars, transformAllBuildInfos)
 import Distribution.PackageDescription.FieldGrammar
 import Distribution.PackageDescription.Quirks        (patchQuirks)
 import Distribution.Parsec                           (parsec, simpleParsecBS)
@@ -56,6 +56,7 @@ import Distribution.Parsec.Position                  (Position (..), zeroPos)
 import Distribution.Parsec.Warning                   (PWarnType (..))
 import Distribution.Pretty                           (prettyShow)
 import Distribution.Simple.Utils                     (fromUTF8BS, toUTF8BS)
+import Distribution.Types.Mixin                      (Mixin (..), mkMixin)
 import Distribution.Utils.Generic                    (breakMaybe, unfoldrM, validateUTF8)
 import Distribution.Verbosity                        (Verbosity)
 import Distribution.Version                          (Version, mkVersion, versionNumbers)
@@ -71,6 +72,7 @@ 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
 import qualified Text.Parsec                                       as P
 
 -- ---------------------------------------------------------------
@@ -727,14 +729,25 @@ checkForUndefinedFlags gpd = do
 -- i.e. what you write is what you get;
 -- For pre-3.4 we post-process the file.
 --
+-- Similarly, we process mixins.
+-- See https://github.com/haskell/cabal/issues/6281
+--
 
 postProcessInternalDeps :: CabalSpecVersion -> GenericPackageDescription -> GenericPackageDescription
 postProcessInternalDeps specVer gpd
     | specVer >= CabalSpecV3_4 = gpd
-    | otherwise                = transformAllBuildDependsN (concatMap f) gpd
+    | otherwise                = transformAllBuildInfos transformBI transformSBI gpd
   where
-    f :: Dependency -> [Dependency]
-    f (Dependency pn vr ln)
+    transformBI :: BuildInfo -> BuildInfo
+    transformBI
+        = over L.targetBuildDepends (concatMap transformD)
+        . over L.mixins (map transformM)
+
+    transformSBI :: SetupBuildInfo -> SetupBuildInfo
+    transformSBI = over L.setupDepends (concatMap transformD)
+
+    transformD :: Dependency -> [Dependency]
+    transformD (Dependency pn vr ln)
         | uqn `Set.member` internalLibs
         , LMainLibName `NES.member` ln
         = case NES.delete LMainLibName ln of
@@ -744,7 +757,16 @@ postProcessInternalDeps specVer gpd
         uqn = packageNameToUnqualComponentName pn
         dep = Dependency thisPn vr (NES.singleton (LSubLibName uqn))
 
-    f d = [d]
+    transformD d = [d]
+
+    transformM :: Mixin -> Mixin
+    transformM (Mixin pn LMainLibName incl)
+        | uqn `Set.member` internalLibs
+        = mkMixin thisPn (LSubLibName uqn) incl
+      where
+        uqn = packageNameToUnqualComponentName pn
+
+    transformM m = m
 
     thisPn :: PackageName
     thisPn = pkgName (package (packageDescription gpd))
diff --git a/Cabal/Distribution/PackageDescription/PrettyPrint.hs b/Cabal/Distribution/PackageDescription/PrettyPrint.hs
index 9d8e35230381465f7451fa8a1e99f6c158b193e5..e556554636e8455fd1cf34ca217ca591708e9ea9 100644
--- a/Cabal/Distribution/PackageDescription/PrettyPrint.hs
+++ b/Cabal/Distribution/PackageDescription/PrettyPrint.hs
@@ -33,17 +33,20 @@ import Prelude ()
 
 import Distribution.CabalSpecVersion
 import Distribution.Fields.Pretty
+import Distribution.Compat.Lens
 import Distribution.PackageDescription
 import Distribution.Pretty
-import Distribution.Simple.Utils
-
+import Distribution.Simple.Utils (writeFileAtomic, writeUTF8File)
+import Distribution.Types.Mixin                      (Mixin (..), mkMixin)
 import Distribution.FieldGrammar                     (PrettyFieldGrammar', prettyFieldGrammar)
-import Distribution.PackageDescription.Configuration (transformAllBuildDependsN)
+import Distribution.PackageDescription.Configuration (transformAllBuildInfos)
 import Distribution.PackageDescription.FieldGrammar
        (benchmarkFieldGrammar, buildInfoFieldGrammar, executableFieldGrammar, flagFieldGrammar, foreignLibFieldGrammar, libraryFieldGrammar,
        packageDescriptionFieldGrammar, setupBInfoFieldGrammar, sourceRepoFieldGrammar, testSuiteFieldGrammar)
 
 import qualified Distribution.PackageDescription.FieldGrammar as FG
+import qualified Distribution.Types.BuildInfo.Lens                 as L
+import qualified Distribution.Types.SetupBuildInfo.Lens            as L
 
 import Text.PrettyPrint (Doc, char, hsep, parens, text)
 
@@ -228,10 +231,18 @@ pdToGpd pd = GenericPackageDescription
 preProcessInternalDeps :: CabalSpecVersion -> GenericPackageDescription -> GenericPackageDescription
 preProcessInternalDeps specVer gpd
     | specVer >= CabalSpecV3_4 = gpd
-    | otherwise                = transformAllBuildDependsN (concatMap f) gpd
+    | otherwise                = transformAllBuildInfos transformBI transformSBI gpd
   where
-    f :: Dependency -> [Dependency]
-    f (Dependency pn vr ln)
+    transformBI :: BuildInfo -> BuildInfo
+    transformBI
+        = over L.targetBuildDepends (concatMap transformD)
+        . over L.mixins (map transformM)
+
+    transformSBI :: SetupBuildInfo -> SetupBuildInfo
+    transformSBI = over L.setupDepends (concatMap transformD)
+
+    transformD :: Dependency -> [Dependency]
+    transformD (Dependency pn vr ln)
         | pn == thisPn
         = if LMainLibName `NES.member` ln
           then Dependency thisPn vr mainLibSet : sublibs
@@ -242,7 +253,13 @@ preProcessInternalDeps specVer gpd
             | LSubLibName uqn <- NES.toList ln
             ]
 
-    f d = [d]
+    transformD d = [d]
+
+    transformM :: Mixin -> Mixin
+    transformM (Mixin pn (LSubLibName uqn) inc)
+        | pn == thisPn
+        = mkMixin (unqualComponentNameToPackageName uqn) LMainLibName inc
+    transformM m = m
 
     thisPn :: PackageName
     thisPn = pkgName (package (packageDescription gpd))
diff --git a/Cabal/Distribution/Types/GenericPackageDescription.hs b/Cabal/Distribution/Types/GenericPackageDescription.hs
index 96fa0620d65089c32771487dcbb05568cbfe7afe..24b2c4d0f0896467e2d5968065a490fcd5959e07 100644
--- a/Cabal/Distribution/Types/GenericPackageDescription.hs
+++ b/Cabal/Distribution/Types/GenericPackageDescription.hs
@@ -2,6 +2,7 @@
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE ScopedTypeVariables #-}
 
 module Distribution.Types.GenericPackageDescription (
     GenericPackageDescription(..),
@@ -74,14 +75,31 @@ emptyGenericPackageDescription = GenericPackageDescription emptyPackageDescripti
 -- Traversal Instances
 
 instance L.HasBuildInfos GenericPackageDescription where
-  traverseBuildInfos f (GenericPackageDescription p v a1 x1 x2 x3 x4 x5 x6) =
-    GenericPackageDescription
-        <$> L.traverseBuildInfos f p
-        <*> pure v
-        <*> pure a1
-        <*> (traverse . traverse . L.buildInfo) f x1
-        <*> (traverse . L._2 . traverse . L.buildInfo) f x2
-        <*> (traverse . L._2 . traverse . L.buildInfo) f x3
-        <*> (traverse . L._2 . traverse . L.buildInfo) f x4
-        <*> (traverse . L._2 . traverse . L.buildInfo) f x5
-        <*> (traverse . L._2 . traverse . L.buildInfo) f x6
+    traverseBuildInfos f (GenericPackageDescription p v a1 x1 x2 x3 x4 x5 x6) =
+        GenericPackageDescription
+            <$> L.traverseBuildInfos f p
+            <*> pure v
+            <*> pure a1
+            <*> (traverse . traverseCondTreeBuildInfo) f x1
+            <*> (traverse . L._2 . traverseCondTreeBuildInfo) f x2
+            <*> (traverse . L._2 . traverseCondTreeBuildInfo) f x3
+            <*> (traverse . L._2 . traverseCondTreeBuildInfo) f x4
+            <*> (traverse . L._2 . traverseCondTreeBuildInfo) f x5
+            <*> (traverse . L._2 . traverseCondTreeBuildInfo) f x6
+      where
+
+-- We use this traversal to keep [Dependency] field in CondTree up to date.
+traverseCondTreeBuildInfo
+    :: forall f comp v. (Applicative f, L.HasBuildInfo comp)
+    => LensLike' f (CondTree v [Dependency] comp) L.BuildInfo
+traverseCondTreeBuildInfo g = node where
+    mkCondNode :: comp -> [CondBranch v [Dependency] comp] -> CondTree v [Dependency] comp
+    mkCondNode comp branches = CondNode comp (view L.targetBuildDepends comp) branches
+
+    node (CondNode comp _ branches) = mkCondNode
+        <$> L.buildInfo g comp
+        <*> traverse branch branches
+
+    branch (CondBranch v x y) = CondBranch v
+        <$> node x
+        <*> traverse node y
diff --git a/Cabal/Distribution/Types/Mixin.hs b/Cabal/Distribution/Types/Mixin.hs
index 404388e4ce3f5d75403f91e3d681b518e9b5ce8d..2719258086d70e3d270254f08186dc20b32cc3a6 100644
--- a/Cabal/Distribution/Types/Mixin.hs
+++ b/Cabal/Distribution/Types/Mixin.hs
@@ -3,19 +3,32 @@
 
 module Distribution.Types.Mixin (
     Mixin(..),
+    mkMixin,
+    normaliseMixin,
 ) where
 
 import Distribution.Compat.Prelude
 import Prelude ()
 
+import Distribution.CabalSpecVersion
 import Distribution.Parsec
 import Distribution.Pretty
 import Distribution.Types.IncludeRenaming
+import Distribution.Types.LibraryName
 import Distribution.Types.PackageName
+import Distribution.Types.UnqualComponentName
 
 import qualified Distribution.Compat.CharParsing as P
+import qualified Text.PrettyPrint                as PP
 
+-- |
+--
+-- /Invariant:/ if 'mixinLibraryName' is 'LSubLibName', it's not
+-- the same as 'mixinPackageName'. In other words,
+-- the same invariant as 'Dependency' has.
+--
 data Mixin = Mixin { mixinPackageName :: PackageName
+                   , mixinLibraryName :: LibraryName
                    , mixinIncludeRenaming :: IncludeRenaming }
     deriving (Show, Read, Eq, Ord, Typeable, Data, Generic)
 
@@ -25,11 +38,54 @@ instance Structured Mixin
 instance NFData Mixin where rnf = genericRnf
 
 instance Pretty Mixin where
-    pretty (Mixin pkg_name incl) = pretty pkg_name <+> pretty incl
+    pretty (Mixin pn LMainLibName incl)     = pretty pn <+> pretty incl
+    pretty (Mixin pn (LSubLibName ln) incl) = pretty pn <<>> PP.colon <<>> pretty ln <+> pretty incl
 
+-- |
+--
+-- >>>  simpleParsec "mylib" :: Maybe Mixin
+-- Just (Mixin {mixinPackageName = PackageName "mylib", mixinLibraryName = LMainLibName, mixinIncludeRenaming = IncludeRenaming {includeProvidesRn = DefaultRenaming, includeRequiresRn = DefaultRenaming}})
+--
+-- >>>  simpleParsec "thatlib:sublib" :: Maybe Mixin
+-- Just (Mixin {mixinPackageName = PackageName "thatlib", mixinLibraryName = LSubLibName (UnqualComponentName "sublib"), mixinIncludeRenaming = IncludeRenaming {includeProvidesRn = DefaultRenaming, includeRequiresRn = DefaultRenaming}})
+--
+-- >>>  simpleParsec "thatlib:thatlib" :: Maybe Mixin
+-- Just (Mixin {mixinPackageName = PackageName "thatlib", mixinLibraryName = LMainLibName, mixinIncludeRenaming = IncludeRenaming {includeProvidesRn = DefaultRenaming, includeRequiresRn = DefaultRenaming}})
+--
+-- Sublibrary syntax is accepted since @cabal-version: 3.4@.
+--
+-- >>> map (`simpleParsec'` "mylib:sub") [CabalSpecV3_0, CabalSpecV3_4] :: [Maybe Mixin]
+-- [Nothing,Just (Mixin {mixinPackageName = PackageName "mylib", mixinLibraryName = LSubLibName (UnqualComponentName "sub"), mixinIncludeRenaming = IncludeRenaming {includeProvidesRn = DefaultRenaming, includeRequiresRn = DefaultRenaming}})]
+--
 instance Parsec Mixin where
     parsec = do
-        mod_name <- parsec
+        pn <- parsec
+        ln <- P.option LMainLibName $ do
+            _ <- P.char ':'
+            versionGuardMultilibs
+            parsecWarning PWTExperimental "colon specifier is experimental feature (issue #5660)"
+            LSubLibName <$> parsec
         P.spaces
         incl <- parsec
-        return (Mixin mod_name incl)
+        return (mkMixin pn ln incl)
+      where
+
+versionGuardMultilibs :: CabalParsing m => m ()
+versionGuardMultilibs = do
+  csv <- askCabalSpecVersion
+  when (csv < CabalSpecV3_4) $ fail $ unwords
+    [ "Sublibrary mixin syntax used."
+    , "To use this syntax the package needs to specify at least 'cabal-version: 3.4'."
+    ]
+
+-- | Smart constructor of 'Mixin', enforces invariant.
+mkMixin :: PackageName -> LibraryName -> IncludeRenaming -> Mixin
+mkMixin pn (LSubLibName uqn) incl
+    | packageNameToUnqualComponentName pn == uqn
+    = Mixin pn LMainLibName incl
+mkMixin pn ln incl
+    = Mixin pn ln incl
+
+-- | Restore invariant
+normaliseMixin :: Mixin -> Mixin
+normaliseMixin (Mixin pn ln incl) = mkMixin pn ln incl
diff --git a/Cabal/doc/buildinfo-fields-reference.rst b/Cabal/doc/buildinfo-fields-reference.rst
index 27e660027574e74636670005aaf0b02409704f9a..a7449c7cbce47c90fd2512cef57fe5839ddc3792 100644
--- a/Cabal/doc/buildinfo-fields-reference.rst
+++ b/Cabal/doc/buildinfo-fields-reference.rst
@@ -197,7 +197,7 @@ build-depends
     * Documentation of :pkg-field:`build-depends`
 
     .. math::
-        \mathrm{commalist}\left(\mathop{\mathit{pkg\text{-}name}}{\left(\mathop{\mathord{``}\mathtt{\text{:}}\mathord{"}}\left\{ \mathop{\mathit{unqual\text{-}name}}\mid\mathop{\mathord{``}\mathtt{\{}\mathord{"}}\circ{\mathop{\mathit{unqual\text{-}name}}}^\ast_{\left(\circ\mathop{\mathord{``}\mathtt{\text{,}}\mathord{"}}\circ\right)}\circ\mathop{\mathord{``}\mathtt{\}}\mathord{"}} \right\}\right)}^?{\left(\circ\mathop{\mathit{version\text{-}range}}\right)}^?\right)
+        \mathrm{commalist}\left(\mathop{\mathit{pkg\text{-}name}}{\left(\mathop{\mathord{``}\mathtt{\text{:}}\mathord{"}}\left\{ \mathop{\mathit{unqual\text{-}name}}\mid\mathop{\mathord{``}\mathtt{\{}\mathord{"}}\circ{\mathop{\mathit{unqual\text{-}name}}}^+_{\left(\circ\mathop{\mathord{``}\mathtt{\text{,}}\mathord{"}}\circ\right)}\circ\mathop{\mathord{``}\mathtt{\}}\mathord{"}} \right\}\right)}^?{\left(\circ\mathop{\mathit{version\text{-}range}}\right)}^?\right)
 
 build-tool-depends
     * Monoidal field
@@ -452,7 +452,7 @@ mixins
     * Documentation of :pkg-field:`mixins`
 
     .. math::
-        \mathrm{commalist}\left(\mathop{\mathit{package\text{-}name}}{\left(\bullet\left\{ \mid\mathop{\mathord{``}\mathtt{hiding}\mathord{"}}\circ\mathop{\mathord{``}\mathtt{\text{(}}\mathord{"}}\circ{\mathop{\mathit{module\text{-}name}}}^\ast_{\left(\circ\mathop{\mathord{``}\mathtt{\text{,}}\mathord{"}}\circ\right)}\circ\mathop{\mathord{``}\mathtt{\text{)}}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{\text{(}}\mathord{"}}\circ{\left(\mathop{\mathit{module\text{-}name}}{\left(\bullet\mathop{\mathord{``}\mathtt{as}\mathord{"}}\bullet\mathop{\mathit{module\text{-}name}}\right)}^?\right)}^\ast_{\left(\circ\mathop{\mathord{``}\mathtt{\text{,}}\mathord{"}}\circ\right)}\circ\mathop{\mathord{``}\mathtt{\text{)}}\mathord{"}} \right\}{\left(\circ\mathop{\mathord{``}\mathtt{requires}\mathord{"}}\bullet\left\{ \mid\mathop{\mathord{``}\mathtt{hiding}\mathord{"}}\circ\mathop{\mathord{``}\mathtt{\text{(}}\mathord{"}}\circ{\mathop{\mathit{module\text{-}name}}}^\ast_{\left(\circ\mathop{\mathord{``}\mathtt{\text{,}}\mathord{"}}\circ\right)}\circ\mathop{\mathord{``}\mathtt{\text{)}}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{\text{(}}\mathord{"}}\circ{\left(\mathop{\mathit{module\text{-}name}}{\left(\bullet\mathop{\mathord{``}\mathtt{as}\mathord{"}}\bullet\mathop{\mathit{module\text{-}name}}\right)}^?\right)}^\ast_{\left(\circ\mathop{\mathord{``}\mathtt{\text{,}}\mathord{"}}\circ\right)}\circ\mathop{\mathord{``}\mathtt{\text{)}}\mathord{"}} \right\}\right)}^?\right)}^?\right)
+        \mathrm{commalist}\left(\mathop{\mathit{package\text{-}name}}{\left(\mathop{\mathord{``}\mathtt{\text{:}}\mathord{"}}\mathop{\mathit{library\text{-}name}}\right)}^?{\left(\bullet\left\{ \mid\mathop{\mathord{``}\mathtt{hiding}\mathord{"}}\circ\mathop{\mathord{``}\mathtt{\text{(}}\mathord{"}}\circ{\mathop{\mathit{module\text{-}name}}}^\ast_{\left(\circ\mathop{\mathord{``}\mathtt{\text{,}}\mathord{"}}\circ\right)}\circ\mathop{\mathord{``}\mathtt{\text{)}}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{\text{(}}\mathord{"}}\circ{\left(\mathop{\mathit{module\text{-}name}}{\left(\bullet\mathop{\mathord{``}\mathtt{as}\mathord{"}}\bullet\mathop{\mathit{module\text{-}name}}\right)}^?\right)}^\ast_{\left(\circ\mathop{\mathord{``}\mathtt{\text{,}}\mathord{"}}\circ\right)}\circ\mathop{\mathord{``}\mathtt{\text{)}}\mathord{"}} \right\}{\left(\circ\mathop{\mathord{``}\mathtt{requires}\mathord{"}}\bullet\left\{ \mid\mathop{\mathord{``}\mathtt{hiding}\mathord{"}}\circ\mathop{\mathord{``}\mathtt{\text{(}}\mathord{"}}\circ{\mathop{\mathit{module\text{-}name}}}^\ast_{\left(\circ\mathop{\mathord{``}\mathtt{\text{,}}\mathord{"}}\circ\right)}\circ\mathop{\mathord{``}\mathtt{\text{)}}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{\text{(}}\mathord{"}}\circ{\left(\mathop{\mathit{module\text{-}name}}{\left(\bullet\mathop{\mathord{``}\mathtt{as}\mathord{"}}\bullet\mathop{\mathit{module\text{-}name}}\right)}^?\right)}^\ast_{\left(\circ\mathop{\mathord{``}\mathtt{\text{,}}\mathord{"}}\circ\right)}\circ\mathop{\mathord{``}\mathtt{\text{)}}\mathord{"}} \right\}\right)}^?\right)}^?\right)
 
 other-extensions
     * Monoidal field
diff --git a/Cabal/tests/ParserTests.hs b/Cabal/tests/ParserTests.hs
index 61596dba8a4d31406ec5934e0ee8458fc37a429c..981be3b4ccea7acd278c729fac9949999ef65757 100644
--- a/Cabal/tests/ParserTests.hs
+++ b/Cabal/tests/ParserTests.hs
@@ -195,6 +195,7 @@ regressionTests = testGroup "regressions"
     , regressionTest "big-version.cabal"
     , regressionTest "anynone.cabal"
     , regressionTest "monad-param.cabal"
+    , regressionTest "hasktorch.cabal"
     ]
 
 regressionTest :: FilePath -> TestTree
diff --git a/Cabal/tests/ParserTests/regressions/hasktorch.cabal b/Cabal/tests/ParserTests/regressions/hasktorch.cabal
new file mode 100644
index 0000000000000000000000000000000000000000..4dfd66e343e041e15793da86cf53913f8feaf3cb
--- /dev/null
+++ b/Cabal/tests/ParserTests/regressions/hasktorch.cabal
@@ -0,0 +1,558 @@
+cabal-version: 2.2
+-- ================================================================ --
+-- ======== This cabal file has been modified from dhall ========== --
+-- ======== This constitutes the 0.0.1.0 release.        ========== --
+-- ======== Dhall can generate this file, but will never ========== --
+-- ======== be able to upload to hackage. For more, see: ========== --
+-- ==== https://github.com/haskell/hackage-server/issues/795 ====== --
+-- ================================================================ --
+name: hasktorch
+version: 0.0.1.0
+license: BSD-3-Clause
+maintainer: Sam Stites <fnz@fgvgrf.vb>, Austin Huang <nhfgvau@nyhz.zvg.rqh> - cipher:ROT13
+author: Hasktorch dev team
+homepage: https://github.com/hasktorch/hasktorch#readme
+bug-reports: https://github.com/hasktorch/hasktorch/issues
+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
+build-type: Simple
+
+source-repository head
+    type: git
+    location: https://github.com/hasktorch/hasktorch
+
+flag cuda
+    description:
+        build with THC support
+    default: False
+
+flag lite
+    description:
+        only build with Double and Long support
+    default: False
+
+library
+    exposed-modules:
+        Torch.Core.Exceptions
+        Torch.Core.Random
+        Torch.Core.LogAdd
+    reexported-modules: Torch.Types.Numeric,
+                        Torch.Long,
+                        Torch.Long.Dynamic,
+                        Torch.Long.Storage,
+                        Torch.Double,
+                        Torch.Double.Dynamic,
+                        Torch.Double.Storage,
+                        Torch.Double.NN,
+                        Torch.Double.NN.Activation,
+                        Torch.Double.NN.Backprop,
+                        Torch.Double.NN.Conv1d,
+                        Torch.Double.NN.Conv2d,
+                        Torch.Double.NN.Criterion,
+                        Torch.Double.NN.Layers,
+                        Torch.Double.NN.Linear,
+                        Torch.Double.NN.Math,
+                        Torch.Double.NN.Padding,
+                        Torch.Double.NN.Pooling,
+                        Torch.Double.NN.Sampling,
+                        Torch.Double.Dynamic.NN,
+                        Torch.Double.Dynamic.NN.Activation,
+                        Torch.Double.Dynamic.NN.Pooling,
+                        Torch.Double.Dynamic.NN.Criterion
+    hs-source-dirs: utils
+    default-language: Haskell2010
+    default-extensions: LambdaCase DataKinds TypeFamilies
+                        TypeSynonymInstances ScopedTypeVariables FlexibleContexts CPP
+    build-depends:
+        base (==4.7 || >4.7) && <5,
+        -- containers ==0.5.10 || >0.5.10,
+        -- deepseq ==1.3.0 || >1.3.0,
+        dimensions ==1.0 || >1.0,
+        -- managed (==1.0.0 || >1.0.0) && <1.1,
+        -- microlens ==0.4.8 || >0.4.8,
+        -- numeric-limits ==0.1.0 || >0.1.0,
+        safe-exceptions ==0.1.0 || >0.1.0,
+        singletons ==2.2 || >2.2,
+        text ==1.2.2 || >1.2.2,
+        -- typelits-witnesses ==0.2.3 || >0.2.3,
+        hasktorch-cpu -any,
+        hasktorch-ffi-th (==0.0.1 || >0.0.1) && <0.0.2,
+        hasktorch-types-th (==0.0.1 || >0.0.1) && <0.0.2
+
+    -- <><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><> --
+    -- BEGIN EDITS
+    -- <><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><> --
+    if !flag(lite)
+      reexported-modules:
+        Torch.Byte,
+        Torch.Byte.Dynamic,
+        Torch.Byte.Storage,
+        Torch.Char,
+        Torch.Char.Dynamic,
+        Torch.Char.Storage,
+        Torch.Short,
+        Torch.Short.Dynamic,
+        Torch.Short.Storage,
+        Torch.Int,
+        Torch.Int.Dynamic,
+        Torch.Int.Storage,
+        Torch.Float,
+        Torch.Float.Dynamic,
+        Torch.Float.Storage
+
+    if flag(cuda)
+      build-depends:
+        hasktorch-gpu -any
+      reexported-modules:
+        Torch.Cuda.Long,
+        Torch.Cuda.Long.Dynamic,
+        Torch.Cuda.Long.Storage,
+        Torch.Cuda.Double,
+        Torch.Cuda.Double.Dynamic,
+        Torch.Cuda.Double.Storage,
+        Torch.Cuda.Double.NN,
+        Torch.Cuda.Double.NN.Activation,
+        Torch.Cuda.Double.NN.Backprop,
+        Torch.Cuda.Double.NN.Conv1d,
+        Torch.Cuda.Double.NN.Conv2d,
+        Torch.Cuda.Double.NN.Criterion,
+        Torch.Cuda.Double.NN.Layers,
+        Torch.Cuda.Double.NN.Linear,
+        Torch.Cuda.Double.NN.Math,
+        Torch.Cuda.Double.NN.Padding,
+        Torch.Cuda.Double.NN.Pooling,
+        Torch.Cuda.Double.NN.Sampling,
+        Torch.Cuda.Double.Dynamic.NN,
+        Torch.Cuda.Double.Dynamic.NN.Activation,
+        Torch.Cuda.Double.Dynamic.NN.Pooling,
+        Torch.Cuda.Double.Dynamic.NN.Criterion
+      if !flag(lite)
+        reexported-modules:
+          Torch.Cuda.Byte,
+          Torch.Cuda.Byte.Dynamic,
+          Torch.Cuda.Byte.Storage,
+          Torch.Cuda.Char,
+          Torch.Cuda.Char.Dynamic,
+          Torch.Cuda.Char.Storage,
+          Torch.Cuda.Short,
+          Torch.Cuda.Short.Dynamic,
+          Torch.Cuda.Short.Storage,
+          Torch.Cuda.Int,
+          Torch.Cuda.Int.Dynamic,
+          Torch.Cuda.Int.Storage,
+          Torch.Cuda.Float,
+          Torch.Cuda.Float.Dynamic,
+          Torch.Cuda.Float.Storage
+    -- <><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><> --
+    -- END EDITS
+    -- <><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><> --
+
+library hasktorch-cpu
+    exposed-modules:
+        Torch.Long
+        Torch.Long.Dynamic
+        Torch.Long.Storage
+        Torch.Double
+        Torch.Double.Dynamic
+        Torch.Double.Storage
+    reexported-modules: Torch.Double.NN,
+                        Torch.Double.NN.Activation,
+                        Torch.Double.NN.Backprop,
+                        Torch.Double.NN.Conv1d,
+                        Torch.Double.NN.Conv2d,
+                        Torch.Double.NN.Criterion,
+                        Torch.Double.NN.Layers,
+                        Torch.Double.NN.Linear,
+                        Torch.Double.NN.Math,
+                        Torch.Double.NN.Padding,
+                        Torch.Double.NN.Pooling,
+                        Torch.Double.NN.Sampling,
+                        Torch.Double.Dynamic.NN,
+                        Torch.Double.Dynamic.NN.Activation,
+                        Torch.Double.Dynamic.NN.Pooling,
+                        Torch.Double.Dynamic.NN.Criterion,
+                        Torch.Float.NN,
+                        Torch.Float.NN.Activation,
+                        Torch.Float.NN.Backprop,
+                        Torch.Float.NN.Conv1d,
+                        Torch.Float.NN.Conv2d,
+                        Torch.Float.NN.Criterion,
+                        Torch.Float.NN.Layers,
+                        Torch.Float.NN.Linear,
+                        Torch.Float.NN.Math,
+                        Torch.Float.NN.Padding,
+                        Torch.Float.NN.Pooling,
+                        Torch.Float.NN.Sampling,
+                        Torch.Float.Dynamic.NN,
+                        Torch.Float.Dynamic.NN.Activation,
+                        Torch.Float.Dynamic.NN.Pooling,
+                        Torch.Float.Dynamic.NN.Criterion
+    hs-source-dirs: utils src
+    other-modules:
+        Torch.Core.Exceptions
+        Torch.Core.Random
+        Torch.Core.LogAdd
+    default-language: Haskell2010
+    default-extensions: LambdaCase DataKinds TypeFamilies
+                        TypeSynonymInstances ScopedTypeVariables FlexibleContexts CPP
+    build-depends:
+        base (==4.7 || >4.7) && <5,
+        hasktorch-types-th (==0.0.1 || >0.0.1) && <0.0.2,
+        -- containers ==0.5.10 || >0.5.10,
+        -- deepseq ==1.3.0 || >1.3.0,
+        dimensions ==1.0 || >1.0,
+        hasktorch-ffi-th (==0.0.1 || >0.0.1) && <0.0.2,
+        hasktorch-types-th (==0.0.1 || >0.0.1) && <0.0.2,
+        -- managed (==1.0.0 || >1.0.0) && <1.1,
+        -- microlens ==0.4.8 || >0.4.8,
+        -- numeric-limits ==0.1.0 || >0.1.0,
+        safe-exceptions ==0.1.0 || >0.1.0,
+        singletons ==2.2 || >2.2,
+        text ==1.2.2 || >1.2.2,
+        -- typelits-witnesses ==0.2.3 || >0.2.3,
+        hasktorch-indef-floating -any,
+        hasktorch-indef-signed -any
+    mixins: hasktorch-indef-signed (Torch.Indef.Storage as Torch.Indef.Long.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Long.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Long.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Long.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Long.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Long.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Long.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Long.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Long.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Long.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Long.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Long.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Long.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Long.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Long.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Long.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Long.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Long.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Long.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Long.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Long.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Long.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Long.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Long.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Long.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Long.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Long.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Long.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Long.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Long.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Long.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Long.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Long.Types, Torch.Indef.Index as Torch.Long.Index, Torch.Indef.Mask as Torch.Long.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Long.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Long.Dynamic.Tensor.Math.Pointwise.Signed) requires (Torch.Sig.Index.Tensor as Torch.FFI.TH.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.TH.Long.FreeTensor, Torch.Sig.Mask.Tensor as Torch.FFI.TH.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.TH.Byte.FreeTensor, Torch.Sig.Mask.MathReduce as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.State as Torch.Types.TH, Torch.Sig.Types.Global as Torch.Types.TH, Torch.Sig.Types as Torch.Types.TH.Long, Torch.Sig.Storage as Torch.FFI.TH.Long.Storage, Torch.Sig.Storage.Copy as Torch.FFI.TH.Long.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.TH.Long.FreeStorage, Torch.Sig.Tensor as Torch.FFI.TH.Long.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.TH.Long.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.TH.Long.FreeTensor, Torch.Sig.Tensor.Index as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Masked as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Math as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Math.Scan as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Mode as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.ScatterGather as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Sort as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.TopK as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Math.Pointwise.Signed as Torch.FFI.TH.Long.TensorMath),
+            hasktorch-indef-floating (Torch.Indef.Storage as Torch.Indef.Double.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Double.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Double.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Double.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Double.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Double.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Double.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Double.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Double.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Double.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Double.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Double.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Double.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Double.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Double.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Double.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Double.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Double.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Double.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Double.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Double.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Double.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Double.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Double.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Double.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Double.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Double.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Double.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Double.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Double.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Double.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Double.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Double.Types, Torch.Indef.Index as Torch.Double.Index, Torch.Indef.Mask as Torch.Double.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Double.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Double.Dynamic.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Blas as Torch.Indef.Double.Dynamic.Tensor.Math.Blas, Torch.Indef.Dynamic.Tensor.Math.Lapack as Torch.Indef.Double.Dynamic.Tensor.Math.Lapack, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Floating as Torch.Indef.Double.Dynamic.Tensor.Math.Pointwise.Floating, Torch.Indef.Dynamic.Tensor.Math.Reduce.Floating as Torch.Indef.Double.Dynamic.Tensor.Math.Reduce.Floating, Torch.Indef.Dynamic.Tensor.Math.Floating as Torch.Indef.Double.Dynamic.Tensor.Math.Floating, Torch.Indef.Static.Tensor.Math.Blas as Torch.Indef.Double.Tensor.Math.Blas, Torch.Indef.Static.Tensor.Math.Lapack as Torch.Indef.Double.Tensor.Math.Lapack, Torch.Indef.Static.Tensor.Math.Pointwise.Floating as Torch.Indef.Double.Tensor.Math.Pointwise.Floating, Torch.Indef.Static.Tensor.Math.Reduce.Floating as Torch.Indef.Double.Tensor.Math.Reduce.Floating, Torch.Indef.Static.Tensor.Math.Floating as Torch.Indef.Double.Tensor.Math.Floating, Torch.Indef.Static.Tensor.Random.TH as Torch.Indef.Double.Tensor.Random.TH, Torch.Indef.Static.Tensor.Math.Random.TH as Torch.Indef.Double.Tensor.Math.Random.TH, Torch.Indef.Dynamic.Tensor.Random.TH as Torch.Indef.Double.Dynamic.Tensor.Random.TH, Torch.Indef.Dynamic.Tensor.Math.Random.TH as Torch.Indef.Double.Dynamic.Tensor.Math.Random.TH, Torch.Undefined.Tensor.Random.THC as Torch.Undefined.Double.Tensor.Random.THC, Torch.Indef.Storage as Torch.Indef.Double.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Double.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Double.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Double.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Double.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Double.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Double.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Double.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Double.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Double.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Double.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Double.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Double.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Double.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Double.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Double.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Double.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Double.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Double.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Double.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Double.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Double.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Double.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Double.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Double.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Double.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Double.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Double.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Double.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Double.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Double.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Double.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Double.Types, Torch.Indef.Index as Torch.Double.Index, Torch.Indef.Mask as Torch.Double.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Double.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Double.Dynamic.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.NN as Torch.Double.Dynamic.NN, Torch.Indef.Dynamic.NN.Activation as Torch.Double.Dynamic.NN.Activation, Torch.Indef.Dynamic.NN.Pooling as Torch.Double.Dynamic.NN.Pooling, Torch.Indef.Dynamic.NN.Criterion as Torch.Double.Dynamic.NN.Criterion, Torch.Indef.Static.NN as Torch.Double.NN, Torch.Indef.Static.NN as Torch.Double.NN, Torch.Indef.Static.NN.Activation as Torch.Double.NN.Activation, Torch.Indef.Static.NN.Backprop as Torch.Double.NN.Backprop, Torch.Indef.Static.NN.Conv1d as Torch.Double.NN.Conv1d, Torch.Indef.Static.NN.Conv2d as Torch.Double.NN.Conv2d, Torch.Indef.Static.NN.Criterion as Torch.Double.NN.Criterion, Torch.Indef.Static.NN.Layers as Torch.Double.NN.Layers, Torch.Indef.Static.NN.Linear as Torch.Double.NN.Linear, Torch.Indef.Static.NN.Math as Torch.Double.NN.Math, Torch.Indef.Static.NN.Padding as Torch.Double.NN.Padding, Torch.Indef.Static.NN.Pooling as Torch.Double.NN.Pooling, Torch.Indef.Static.NN.Sampling as Torch.Double.NN.Sampling) requires (Torch.Sig.Index.Tensor as Torch.FFI.TH.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.TH.Long.FreeTensor, Torch.Sig.Mask.Tensor as Torch.FFI.TH.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.TH.Byte.FreeTensor, Torch.Sig.Mask.MathReduce as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.State as Torch.Types.TH, Torch.Sig.Types.Global as Torch.Types.TH, Torch.Sig.Types as Torch.Types.TH.Double, Torch.Sig.Storage as Torch.FFI.TH.Double.Storage, Torch.Sig.Storage.Copy as Torch.FFI.TH.Double.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.TH.Double.FreeStorage, Torch.Sig.Tensor as Torch.FFI.TH.Double.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.TH.Double.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.TH.Double.FreeTensor, Torch.Sig.Tensor.Index as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Masked as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Scan as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Mode as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.ScatterGather as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Sort as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.TopK as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Pointwise.Signed as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Pointwise.Floating as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Reduce.Floating as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Floating as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Blas as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Lapack as Torch.FFI.TH.Double.TensorLapack, Torch.Sig.NN as Torch.FFI.TH.NN.Double, Torch.Sig.Types.NN as Torch.Types.TH, Torch.Sig.Tensor.Math.Random.TH as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Random.TH as Torch.FFI.TH.Double.TensorRandom, Torch.Sig.Tensor.Random.THC as Torch.Undefined.Double.Tensor.Random.THC)
+    
+    if flag(lite)
+    else
+        exposed-modules:
+            Torch.Byte
+            Torch.Byte.Dynamic
+            Torch.Byte.Storage
+            Torch.Char
+            Torch.Char.Dynamic
+            Torch.Char.Storage
+            Torch.Short
+            Torch.Short.Dynamic
+            Torch.Short.Storage
+            Torch.Int
+            Torch.Int.Dynamic
+            Torch.Int.Storage
+            Torch.Float
+            Torch.Float.Dynamic
+            Torch.Float.Storage
+        build-depends:
+            hasktorch-indef-unsigned -any
+        mixins: hasktorch-indef-unsigned (Torch.Indef.Storage as Torch.Indef.Byte.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Byte.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Byte.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Byte.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Byte.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Byte.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Byte.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Byte.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Byte.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Byte.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Byte.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Byte.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Byte.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Byte.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Byte.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Byte.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Byte.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Byte.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Byte.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Byte.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Byte.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Byte.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Byte.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Byte.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Byte.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Byte.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Byte.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Byte.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Byte.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Byte.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Byte.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Byte.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Byte.Types, Torch.Indef.Index as Torch.Byte.Index, Torch.Indef.Mask as Torch.Byte.Mask) requires (Torch.Sig.Index.Tensor as Torch.FFI.TH.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.TH.Long.FreeTensor, Torch.Sig.Mask.Tensor as Torch.FFI.TH.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.TH.Byte.FreeTensor, Torch.Sig.Mask.MathReduce as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.State as Torch.Types.TH, Torch.Sig.Types.Global as Torch.Types.TH, Torch.Sig.Types as Torch.Types.TH.Byte, Torch.Sig.Storage as Torch.FFI.TH.Byte.Storage, Torch.Sig.Storage.Copy as Torch.FFI.TH.Byte.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.TH.Byte.FreeStorage, Torch.Sig.Tensor as Torch.FFI.TH.Byte.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.TH.Byte.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.TH.Byte.FreeTensor, Torch.Sig.Tensor.Index as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.Masked as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.Math as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.Math.Scan as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.Mode as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.ScatterGather as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.Sort as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.TopK as Torch.FFI.TH.Byte.TensorMath),
+                hasktorch-indef-unsigned (Torch.Indef.Storage as Torch.Indef.Char.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Char.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Char.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Char.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Char.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Char.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Char.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Char.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Char.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Char.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Char.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Char.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Char.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Char.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Char.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Char.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Char.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Char.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Char.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Char.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Char.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Char.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Char.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Char.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Char.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Char.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Char.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Char.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Char.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Char.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Char.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Char.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Char.Types, Torch.Indef.Index as Torch.Char.Index, Torch.Indef.Mask as Torch.Char.Mask) requires (Torch.Sig.Index.Tensor as Torch.FFI.TH.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.TH.Long.FreeTensor, Torch.Sig.Mask.Tensor as Torch.FFI.TH.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.TH.Byte.FreeTensor, Torch.Sig.Mask.MathReduce as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.State as Torch.Types.TH, Torch.Sig.Types.Global as Torch.Types.TH, Torch.Sig.Types as Torch.Types.TH.Char, Torch.Sig.Storage as Torch.FFI.TH.Char.Storage, Torch.Sig.Storage.Copy as Torch.FFI.TH.Char.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.TH.Char.FreeStorage, Torch.Sig.Tensor as Torch.FFI.TH.Char.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.TH.Char.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.TH.Char.FreeTensor, Torch.Sig.Tensor.Index as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.Masked as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.Math as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.Math.Scan as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.Mode as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.ScatterGather as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.Sort as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.TopK as Torch.FFI.TH.Char.TensorMath),
+                hasktorch-indef-signed (Torch.Indef.Storage as Torch.Indef.Short.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Short.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Short.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Short.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Short.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Short.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Short.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Short.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Short.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Short.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Short.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Short.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Short.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Short.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Short.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Short.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Short.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Short.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Short.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Short.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Short.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Short.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Short.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Short.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Short.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Short.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Short.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Short.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Short.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Short.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Short.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Short.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Short.Types, Torch.Indef.Index as Torch.Short.Index, Torch.Indef.Mask as Torch.Short.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Short.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Short.Dynamic.Tensor.Math.Pointwise.Signed) requires (Torch.Sig.Index.Tensor as Torch.FFI.TH.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.TH.Long.FreeTensor, Torch.Sig.Mask.Tensor as Torch.FFI.TH.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.TH.Byte.FreeTensor, Torch.Sig.Mask.MathReduce as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.State as Torch.Types.TH, Torch.Sig.Types.Global as Torch.Types.TH, Torch.Sig.Types as Torch.Types.TH.Short, Torch.Sig.Storage as Torch.FFI.TH.Short.Storage, Torch.Sig.Storage.Copy as Torch.FFI.TH.Short.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.TH.Short.FreeStorage, Torch.Sig.Tensor as Torch.FFI.TH.Short.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.TH.Short.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.TH.Short.FreeTensor, Torch.Sig.Tensor.Index as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Masked as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Math as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Math.Scan as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Mode as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.ScatterGather as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Sort as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.TopK as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Math.Pointwise.Signed as Torch.FFI.TH.Short.TensorMath),
+                hasktorch-indef-signed (Torch.Indef.Storage as Torch.Indef.Int.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Int.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Int.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Int.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Int.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Int.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Int.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Int.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Int.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Int.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Int.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Int.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Int.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Int.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Int.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Int.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Int.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Int.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Int.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Int.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Int.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Int.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Int.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Int.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Int.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Int.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Int.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Int.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Int.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Int.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Int.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Int.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Int.Types, Torch.Indef.Index as Torch.Int.Index, Torch.Indef.Mask as Torch.Int.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Int.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Int.Dynamic.Tensor.Math.Pointwise.Signed) requires (Torch.Sig.Index.Tensor as Torch.FFI.TH.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.TH.Long.FreeTensor, Torch.Sig.Mask.Tensor as Torch.FFI.TH.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.TH.Byte.FreeTensor, Torch.Sig.Mask.MathReduce as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.State as Torch.Types.TH, Torch.Sig.Types.Global as Torch.Types.TH, Torch.Sig.Types as Torch.Types.TH.Int, Torch.Sig.Storage as Torch.FFI.TH.Int.Storage, Torch.Sig.Storage.Copy as Torch.FFI.TH.Int.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.TH.Int.FreeStorage, Torch.Sig.Tensor as Torch.FFI.TH.Int.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.TH.Int.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.TH.Int.FreeTensor, Torch.Sig.Tensor.Index as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Masked as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Math as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Math.Scan as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Mode as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.ScatterGather as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Sort as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.TopK as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Math.Pointwise.Signed as Torch.FFI.TH.Int.TensorMath),
+                hasktorch-indef-floating (Torch.Indef.Storage as Torch.Indef.Float.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Float.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Float.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Float.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Float.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Float.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Float.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Float.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Float.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Float.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Float.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Float.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Float.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Float.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Float.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Float.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Float.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Float.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Float.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Float.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Float.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Float.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Float.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Float.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Float.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Float.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Float.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Float.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Float.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Float.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Float.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Float.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Float.Types, Torch.Indef.Index as Torch.Float.Index, Torch.Indef.Mask as Torch.Float.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Float.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Float.Dynamic.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Blas as Torch.Indef.Float.Dynamic.Tensor.Math.Blas, Torch.Indef.Dynamic.Tensor.Math.Lapack as Torch.Indef.Float.Dynamic.Tensor.Math.Lapack, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Floating as Torch.Indef.Float.Dynamic.Tensor.Math.Pointwise.Floating, Torch.Indef.Dynamic.Tensor.Math.Reduce.Floating as Torch.Indef.Float.Dynamic.Tensor.Math.Reduce.Floating, Torch.Indef.Dynamic.Tensor.Math.Floating as Torch.Indef.Float.Dynamic.Tensor.Math.Floating, Torch.Indef.Static.Tensor.Math.Blas as Torch.Indef.Float.Tensor.Math.Blas, Torch.Indef.Static.Tensor.Math.Lapack as Torch.Indef.Float.Tensor.Math.Lapack, Torch.Indef.Static.Tensor.Math.Pointwise.Floating as Torch.Indef.Float.Tensor.Math.Pointwise.Floating, Torch.Indef.Static.Tensor.Math.Reduce.Floating as Torch.Indef.Float.Tensor.Math.Reduce.Floating, Torch.Indef.Static.Tensor.Math.Floating as Torch.Indef.Float.Tensor.Math.Floating, Torch.Indef.Static.Tensor.Random.TH as Torch.Indef.Float.Tensor.Random.TH, Torch.Indef.Static.Tensor.Math.Random.TH as Torch.Indef.Float.Tensor.Math.Random.TH, Torch.Indef.Dynamic.Tensor.Random.TH as Torch.Indef.Float.Dynamic.Tensor.Random.TH, Torch.Indef.Dynamic.Tensor.Math.Random.TH as Torch.Indef.Float.Dynamic.Tensor.Math.Random.TH, Torch.Undefined.Tensor.Random.THC as Torch.Undefined.Float.Tensor.Random.THC, Torch.Indef.Storage as Torch.Indef.Float.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Float.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Float.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Float.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Float.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Float.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Float.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Float.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Float.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Float.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Float.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Float.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Float.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Float.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Float.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Float.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Float.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Float.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Float.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Float.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Float.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Float.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Float.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Float.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Float.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Float.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Float.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Float.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Float.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Float.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Float.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Float.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Float.Types, Torch.Indef.Index as Torch.Float.Index, Torch.Indef.Mask as Torch.Float.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Float.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Float.Dynamic.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.NN as Torch.Float.Dynamic.NN, Torch.Indef.Dynamic.NN.Activation as Torch.Float.Dynamic.NN.Activation, Torch.Indef.Dynamic.NN.Pooling as Torch.Float.Dynamic.NN.Pooling, Torch.Indef.Dynamic.NN.Criterion as Torch.Float.Dynamic.NN.Criterion, Torch.Indef.Static.NN as Torch.Float.NN, Torch.Indef.Static.NN as Torch.Float.NN, Torch.Indef.Static.NN.Activation as Torch.Float.NN.Activation, Torch.Indef.Static.NN.Backprop as Torch.Float.NN.Backprop, Torch.Indef.Static.NN.Conv1d as Torch.Float.NN.Conv1d, Torch.Indef.Static.NN.Conv2d as Torch.Float.NN.Conv2d, Torch.Indef.Static.NN.Criterion as Torch.Float.NN.Criterion, Torch.Indef.Static.NN.Layers as Torch.Float.NN.Layers, Torch.Indef.Static.NN.Linear as Torch.Float.NN.Linear, Torch.Indef.Static.NN.Math as Torch.Float.NN.Math, Torch.Indef.Static.NN.Padding as Torch.Float.NN.Padding, Torch.Indef.Static.NN.Pooling as Torch.Float.NN.Pooling, Torch.Indef.Static.NN.Sampling as Torch.Float.NN.Sampling) requires (Torch.Sig.Index.Tensor as Torch.FFI.TH.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.TH.Long.FreeTensor, Torch.Sig.Mask.Tensor as Torch.FFI.TH.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.TH.Byte.FreeTensor, Torch.Sig.Mask.MathReduce as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.State as Torch.Types.TH, Torch.Sig.Types.Global as Torch.Types.TH, Torch.Sig.Types as Torch.Types.TH.Float, Torch.Sig.Storage as Torch.FFI.TH.Float.Storage, Torch.Sig.Storage.Copy as Torch.FFI.TH.Float.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.TH.Float.FreeStorage, Torch.Sig.Tensor as Torch.FFI.TH.Float.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.TH.Float.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.TH.Float.FreeTensor, Torch.Sig.Tensor.Index as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Masked as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Scan as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Mode as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.ScatterGather as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Sort as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.TopK as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Pointwise.Signed as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Pointwise.Floating as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Reduce.Floating as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Floating as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Blas as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Lapack as Torch.FFI.TH.Float.TensorLapack, Torch.Sig.NN as Torch.FFI.TH.NN.Float, Torch.Sig.Types.NN as Torch.Types.TH, Torch.Sig.Tensor.Math.Random.TH as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Random.TH as Torch.FFI.TH.Float.TensorRandom, Torch.Sig.Tensor.Random.THC as Torch.Undefined.Float.Tensor.Random.THC)
+
+library hasktorch-gpu
+    exposed-modules:
+        Torch.Cuda.Long
+        Torch.Cuda.Long.Dynamic
+        Torch.Cuda.Long.Storage
+        Torch.Cuda.Double
+        Torch.Cuda.Double.Dynamic
+        Torch.Cuda.Double.Storage
+    reexported-modules: Torch.Cuda.Double.NN,
+                        Torch.Cuda.Double.NN.Activation,
+                        Torch.Cuda.Double.NN.Backprop,
+                        Torch.Cuda.Double.NN.Conv1d,
+                        Torch.Cuda.Double.NN.Conv2d,
+                        Torch.Cuda.Double.NN.Criterion,
+                        Torch.Cuda.Double.NN.Layers,
+                        Torch.Cuda.Double.NN.Linear,
+                        Torch.Cuda.Double.NN.Math,
+                        Torch.Cuda.Double.NN.Padding,
+                        Torch.Cuda.Double.NN.Pooling,
+                        Torch.Cuda.Double.NN.Sampling,
+                        Torch.Cuda.Double.Dynamic.NN,
+                        Torch.Cuda.Double.Dynamic.NN.Activation,
+                        Torch.Cuda.Double.Dynamic.NN.Pooling,
+                        Torch.Cuda.Double.Dynamic.NN.Criterion
+    cpp-options: -DCUDA -DHASKTORCH_INTERNAL_CUDA
+    hs-source-dirs: utils src
+    other-modules:
+        Torch.Core.Exceptions
+        Torch.Core.Random
+        Torch.Core.LogAdd
+    default-language: Haskell2010
+    default-extensions: LambdaCase DataKinds TypeFamilies
+                        TypeSynonymInstances ScopedTypeVariables FlexibleContexts CPP
+    build-depends:
+        base (==4.7 || >4.7) && <5,
+        hasktorch-types-th (==0.0.1 || >0.0.1) && <0.0.2,
+        -- containers ==0.5.10 || >0.5.10,
+        -- deepseq ==1.3.0 || >1.3.0,
+        dimensions ==1.0 || >1.0,
+        hasktorch-ffi-th (==0.0.1 || >0.0.1) && <0.0.2,
+        hasktorch-types-th (==0.0.1 || >0.0.1) && <0.0.2,
+        -- managed (==1.0.0 || >1.0.0) && <1.1,
+        -- microlens ==0.4.8 || >0.4.8,
+        -- numeric-limits ==0.1.0 || >0.1.0,
+        safe-exceptions ==0.1.0 || >0.1.0,
+        singletons ==2.2 || >2.2,
+        text ==1.2.2 || >1.2.2,
+        -- typelits-witnesses ==0.2.3 || >0.2.3,
+        hasktorch-indef-floating -any,
+        hasktorch-indef-signed -any,
+        hasktorch-ffi-thc (==0.0.1 || >0.0.1) && <0.0.2,
+        hasktorch-types-thc (==0.0.1 || >0.0.1) && <0.0.2
+    mixins: hasktorch-indef-signed (Torch.Indef.Storage as Torch.Indef.Cuda.Long.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Cuda.Long.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Cuda.Long.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Cuda.Long.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Cuda.Long.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Cuda.Long.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Cuda.Long.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Cuda.Long.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Cuda.Long.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Cuda.Long.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Cuda.Long.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Cuda.Long.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Cuda.Long.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Cuda.Long.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Cuda.Long.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Cuda.Long.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Cuda.Long.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Cuda.Long.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Cuda.Long.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Cuda.Long.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Cuda.Long.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Cuda.Long.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Cuda.Long.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Cuda.Long.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Cuda.Long.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Cuda.Long.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Cuda.Long.Types, Torch.Indef.Index as Torch.Cuda.Long.Index, Torch.Indef.Mask as Torch.Cuda.Long.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Cuda.Long.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Pointwise.Signed) requires (Torch.Sig.Index.Tensor as Torch.FFI.THC.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.THC.Long.Tensor, Torch.Sig.Mask.Tensor as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.MathReduce as Torch.FFI.THC.Byte.TensorMathReduce, Torch.Sig.State as Torch.FFI.THC.State, Torch.Sig.Types.Global as Torch.Types.THC, Torch.Sig.Types as Torch.Types.THC.Long, Torch.Sig.Storage as Torch.FFI.THC.Long.Storage, Torch.Sig.Storage.Copy as Torch.FFI.THC.Long.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.THC.Long.Storage, Torch.Sig.Tensor as Torch.FFI.THC.Long.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.THC.Long.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.THC.Long.Tensor, Torch.Sig.Tensor.Index as Torch.FFI.THC.Long.TensorIndex, Torch.Sig.Tensor.Masked as Torch.FFI.THC.Long.TensorMasked, Torch.Sig.Tensor.Math as Torch.FFI.THC.Long.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.THC.Long.TensorMathCompare, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.THC.Long.TensorMathCompareT, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.THC.Long.TensorMathPairwise, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.THC.Long.TensorMathPointwise, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.THC.Long.TensorMathReduce, Torch.Sig.Tensor.Math.Scan as Torch.FFI.THC.Long.TensorMathScan, Torch.Sig.Tensor.Mode as Torch.FFI.THC.Long.TensorMode, Torch.Sig.Tensor.ScatterGather as Torch.FFI.THC.Long.TensorScatterGather, Torch.Sig.Tensor.Sort as Torch.FFI.THC.Long.TensorSort, Torch.Sig.Tensor.TopK as Torch.FFI.THC.Long.TensorTopK, Torch.Sig.Tensor.Math.Pointwise.Signed as Torch.FFI.THC.Long.TensorMathPointwise),
+            hasktorch-indef-floating (Torch.Indef.Storage as Torch.Indef.Cuda.Double.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Cuda.Double.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Cuda.Double.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Cuda.Double.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Cuda.Double.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Cuda.Double.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Cuda.Double.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Cuda.Double.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Cuda.Double.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Cuda.Double.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Cuda.Double.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Cuda.Double.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Cuda.Double.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Cuda.Double.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Cuda.Double.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Cuda.Double.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Cuda.Double.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Cuda.Double.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Cuda.Double.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Cuda.Double.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Cuda.Double.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Cuda.Double.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Cuda.Double.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Cuda.Double.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Cuda.Double.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Cuda.Double.Types, Torch.Indef.Index as Torch.Cuda.Double.Index, Torch.Indef.Mask as Torch.Cuda.Double.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Cuda.Double.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Blas as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Blas, Torch.Indef.Dynamic.Tensor.Math.Lapack as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Lapack, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Floating as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pointwise.Floating, Torch.Indef.Dynamic.Tensor.Math.Reduce.Floating as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Reduce.Floating, Torch.Indef.Dynamic.Tensor.Math.Floating as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Floating, Torch.Indef.Static.Tensor.Math.Blas as Torch.Indef.Cuda.Double.Tensor.Math.Blas, Torch.Indef.Static.Tensor.Math.Lapack as Torch.Indef.Cuda.Double.Tensor.Math.Lapack, Torch.Indef.Static.Tensor.Math.Pointwise.Floating as Torch.Indef.Cuda.Double.Tensor.Math.Pointwise.Floating, Torch.Indef.Static.Tensor.Math.Reduce.Floating as Torch.Indef.Cuda.Double.Tensor.Math.Reduce.Floating, Torch.Indef.Static.Tensor.Math.Floating as Torch.Indef.Cuda.Double.Tensor.Math.Floating, Torch.Undefined.Tensor.Random.TH as Torch.Undefined.Cuda.Double.Tensor.Random.TH, Torch.Undefined.Tensor.Math.Random.TH as Torch.Undefined.Cuda.Double.Tensor.Math.Random.TH, Torch.Indef.Static.Tensor.Random.THC as Torch.Indef.Cuda.Double.Tensor.Random.THC, Torch.Indef.Dynamic.Tensor.Random.THC as Torch.Indef.Cuda.Double.Dynamic.Tensor.Random.THC, Torch.Indef.Storage as Torch.Indef.Cuda.Double.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Cuda.Double.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Cuda.Double.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Cuda.Double.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Cuda.Double.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Cuda.Double.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Cuda.Double.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Cuda.Double.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Cuda.Double.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Cuda.Double.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Cuda.Double.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Cuda.Double.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Cuda.Double.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Cuda.Double.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Cuda.Double.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Cuda.Double.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Cuda.Double.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Cuda.Double.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Cuda.Double.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Cuda.Double.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Cuda.Double.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Cuda.Double.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Cuda.Double.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Cuda.Double.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Cuda.Double.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Cuda.Double.Types, Torch.Indef.Index as Torch.Cuda.Double.Index, Torch.Indef.Mask as Torch.Cuda.Double.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Cuda.Double.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.NN as Torch.Cuda.Double.Dynamic.NN, Torch.Indef.Dynamic.NN.Activation as Torch.Cuda.Double.Dynamic.NN.Activation, Torch.Indef.Dynamic.NN.Pooling as Torch.Cuda.Double.Dynamic.NN.Pooling, Torch.Indef.Dynamic.NN.Criterion as Torch.Cuda.Double.Dynamic.NN.Criterion, Torch.Indef.Static.NN as Torch.Cuda.Double.NN, Torch.Indef.Static.NN as Torch.Cuda.Double.NN, Torch.Indef.Static.NN.Activation as Torch.Cuda.Double.NN.Activation, Torch.Indef.Static.NN.Backprop as Torch.Cuda.Double.NN.Backprop, Torch.Indef.Static.NN.Conv1d as Torch.Cuda.Double.NN.Conv1d, Torch.Indef.Static.NN.Conv2d as Torch.Cuda.Double.NN.Conv2d, Torch.Indef.Static.NN.Criterion as Torch.Cuda.Double.NN.Criterion, Torch.Indef.Static.NN.Layers as Torch.Cuda.Double.NN.Layers, Torch.Indef.Static.NN.Linear as Torch.Cuda.Double.NN.Linear, Torch.Indef.Static.NN.Math as Torch.Cuda.Double.NN.Math, Torch.Indef.Static.NN.Padding as Torch.Cuda.Double.NN.Padding, Torch.Indef.Static.NN.Pooling as Torch.Cuda.Double.NN.Pooling, Torch.Indef.Static.NN.Sampling as Torch.Cuda.Double.NN.Sampling) requires (Torch.Sig.Index.Tensor as Torch.FFI.THC.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.THC.Long.Tensor, Torch.Sig.Mask.Tensor as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.MathReduce as Torch.FFI.THC.Byte.TensorMathReduce, Torch.Sig.State as Torch.FFI.THC.State, Torch.Sig.Types.Global as Torch.Types.THC, Torch.Sig.Types as Torch.Types.THC.Double, Torch.Sig.Storage as Torch.FFI.THC.Double.Storage, Torch.Sig.Storage.Copy as Torch.FFI.THC.Double.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.THC.Double.Storage, Torch.Sig.Tensor as Torch.FFI.THC.Double.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.THC.Double.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.THC.Double.Tensor, Torch.Sig.Tensor.Index as Torch.FFI.THC.Double.TensorIndex, Torch.Sig.Tensor.Masked as Torch.FFI.THC.Double.TensorMasked, Torch.Sig.Tensor.Math as Torch.FFI.THC.Double.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.THC.Double.TensorMathCompare, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.THC.Double.TensorMathCompareT, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.THC.Double.TensorMathPairwise, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.THC.Double.TensorMathPointwise, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.THC.Double.TensorMathReduce, Torch.Sig.Tensor.Math.Scan as Torch.FFI.THC.Double.TensorMathScan, Torch.Sig.Tensor.Mode as Torch.FFI.THC.Double.TensorMode, Torch.Sig.Tensor.ScatterGather as Torch.FFI.THC.Double.TensorScatterGather, Torch.Sig.Tensor.Sort as Torch.FFI.THC.Double.TensorSort, Torch.Sig.Tensor.TopK as Torch.FFI.THC.Double.TensorTopK, Torch.Sig.Tensor.Math.Pointwise.Signed as Torch.FFI.THC.Double.TensorMathPointwise, Torch.Sig.Tensor.Math.Pointwise.Floating as Torch.FFI.THC.Double.TensorMathPointwise, Torch.Sig.Tensor.Math.Reduce.Floating as Torch.FFI.THC.Double.TensorMathReduce, Torch.Sig.Tensor.Math.Floating as Torch.FFI.THC.Double.TensorMath, Torch.Sig.Tensor.Math.Blas as Torch.FFI.THC.Double.TensorMathBlas, Torch.Sig.Tensor.Math.Lapack as Torch.FFI.THC.Double.TensorMathMagma, Torch.Sig.NN as Torch.FFI.THC.NN.Double, Torch.Sig.Types.NN as Torch.Types.THC, Torch.Sig.Tensor.Math.Random.TH as Torch.Undefined.Cuda.Double.Tensor.Math.Random.TH, Torch.Sig.Tensor.Random.TH as Torch.Undefined.Cuda.Double.Tensor.Random.TH, Torch.Sig.Tensor.Random.THC as Torch.FFI.THC.Double.TensorRandom)
+    
+    if flag(lite)
+    else
+        exposed-modules:
+            Torch.Cuda.Byte
+            Torch.Cuda.Byte.Dynamic
+            Torch.Cuda.Byte.Storage
+            Torch.Cuda.Char
+            Torch.Cuda.Char.Dynamic
+            Torch.Cuda.Char.Storage
+            Torch.Cuda.Short
+            Torch.Cuda.Short.Dynamic
+            Torch.Cuda.Short.Storage
+            Torch.Cuda.Int
+            Torch.Cuda.Int.Dynamic
+            Torch.Cuda.Int.Storage
+        build-depends:
+            hasktorch-indef-unsigned -any
+        mixins: hasktorch-indef-unsigned (Torch.Indef.Storage as Torch.Indef.Cuda.Byte.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Cuda.Byte.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Cuda.Byte.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Cuda.Byte.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Cuda.Byte.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Cuda.Byte.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Cuda.Byte.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Cuda.Byte.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Cuda.Byte.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Cuda.Byte.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Cuda.Byte.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Cuda.Byte.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Cuda.Byte.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Cuda.Byte.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Cuda.Byte.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Cuda.Byte.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Cuda.Byte.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Cuda.Byte.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Cuda.Byte.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Cuda.Byte.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Cuda.Byte.Types, Torch.Indef.Index as Torch.Cuda.Byte.Index, Torch.Indef.Mask as Torch.Cuda.Byte.Mask) requires (Torch.Sig.Index.Tensor as Torch.FFI.THC.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.THC.Long.Tensor, Torch.Sig.Mask.Tensor as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.MathReduce as Torch.FFI.THC.Byte.TensorMathReduce, Torch.Sig.State as Torch.FFI.THC.State, Torch.Sig.Types.Global as Torch.Types.THC, Torch.Sig.Types as Torch.Types.THC.Byte, Torch.Sig.Storage as Torch.FFI.THC.Byte.Storage, Torch.Sig.Storage.Copy as Torch.FFI.THC.Byte.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.THC.Byte.Storage, Torch.Sig.Tensor as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.THC.Byte.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Tensor.Index as Torch.FFI.THC.Byte.TensorIndex, Torch.Sig.Tensor.Masked as Torch.FFI.THC.Byte.TensorMasked, Torch.Sig.Tensor.Math as Torch.FFI.THC.Byte.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.THC.Byte.TensorMathCompare, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.THC.Byte.TensorMathCompareT, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.THC.Byte.TensorMathPairwise, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.THC.Byte.TensorMathPointwise, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.THC.Byte.TensorMathReduce, Torch.Sig.Tensor.Math.Scan as Torch.FFI.THC.Byte.TensorMathScan, Torch.Sig.Tensor.Mode as Torch.FFI.THC.Byte.TensorMode, Torch.Sig.Tensor.ScatterGather as Torch.FFI.THC.Byte.TensorScatterGather, Torch.Sig.Tensor.Sort as Torch.FFI.THC.Byte.TensorSort, Torch.Sig.Tensor.TopK as Torch.FFI.THC.Byte.TensorTopK),
+                hasktorch-indef-unsigned (Torch.Indef.Storage as Torch.Indef.Cuda.Char.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Cuda.Char.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Cuda.Char.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Cuda.Char.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Cuda.Char.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Cuda.Char.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Cuda.Char.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Cuda.Char.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Cuda.Char.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Cuda.Char.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Cuda.Char.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Cuda.Char.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Cuda.Char.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Cuda.Char.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Cuda.Char.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Cuda.Char.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Cuda.Char.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Cuda.Char.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Cuda.Char.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Cuda.Char.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Cuda.Char.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Cuda.Char.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Cuda.Char.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Cuda.Char.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Cuda.Char.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Cuda.Char.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Cuda.Char.Types, Torch.Indef.Index as Torch.Cuda.Char.Index, Torch.Indef.Mask as Torch.Cuda.Char.Mask) requires (Torch.Sig.Index.Tensor as Torch.FFI.THC.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.THC.Long.Tensor, Torch.Sig.Mask.Tensor as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.MathReduce as Torch.FFI.THC.Byte.TensorMathReduce, Torch.Sig.State as Torch.FFI.THC.State, Torch.Sig.Types.Global as Torch.Types.THC, Torch.Sig.Types as Torch.Types.THC.Char, Torch.Sig.Storage as Torch.FFI.THC.Char.Storage, Torch.Sig.Storage.Copy as Torch.FFI.THC.Char.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.THC.Char.Storage, Torch.Sig.Tensor as Torch.FFI.THC.Char.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.THC.Char.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.THC.Char.Tensor, Torch.Sig.Tensor.Index as Torch.FFI.THC.Char.TensorIndex, Torch.Sig.Tensor.Masked as Torch.FFI.THC.Char.TensorMasked, Torch.Sig.Tensor.Math as Torch.FFI.THC.Char.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.THC.Char.TensorMathCompare, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.THC.Char.TensorMathCompareT, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.THC.Char.TensorMathPairwise, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.THC.Char.TensorMathPointwise, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.THC.Char.TensorMathReduce, Torch.Sig.Tensor.Math.Scan as Torch.FFI.THC.Char.TensorMathScan, Torch.Sig.Tensor.Mode as Torch.FFI.THC.Char.TensorMode, Torch.Sig.Tensor.ScatterGather as Torch.FFI.THC.Char.TensorScatterGather, Torch.Sig.Tensor.Sort as Torch.FFI.THC.Char.TensorSort, Torch.Sig.Tensor.TopK as Torch.FFI.THC.Char.TensorTopK),
+                hasktorch-indef-signed (Torch.Indef.Storage as Torch.Indef.Cuda.Short.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Cuda.Short.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Cuda.Short.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Cuda.Short.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Cuda.Short.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Cuda.Short.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Cuda.Short.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Cuda.Short.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Cuda.Short.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Cuda.Short.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Cuda.Short.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Cuda.Short.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Cuda.Short.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Cuda.Short.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Cuda.Short.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Cuda.Short.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Cuda.Short.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Cuda.Short.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Cuda.Short.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Cuda.Short.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Cuda.Short.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Cuda.Short.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Cuda.Short.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Cuda.Short.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Cuda.Short.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Cuda.Short.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Cuda.Short.Types, Torch.Indef.Index as Torch.Cuda.Short.Index, Torch.Indef.Mask as Torch.Cuda.Short.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Cuda.Short.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Pointwise.Signed) requires (Torch.Sig.Index.Tensor as Torch.FFI.THC.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.THC.Long.Tensor, Torch.Sig.Mask.Tensor as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.MathReduce as Torch.FFI.THC.Byte.TensorMathReduce, Torch.Sig.State as Torch.FFI.THC.State, Torch.Sig.Types.Global as Torch.Types.THC, Torch.Sig.Types as Torch.Types.THC.Short, Torch.Sig.Storage as Torch.FFI.THC.Short.Storage, Torch.Sig.Storage.Copy as Torch.FFI.THC.Short.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.THC.Short.Storage, Torch.Sig.Tensor as Torch.FFI.THC.Short.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.THC.Short.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.THC.Short.Tensor, Torch.Sig.Tensor.Index as Torch.FFI.THC.Short.TensorIndex, Torch.Sig.Tensor.Masked as Torch.FFI.THC.Short.TensorMasked, Torch.Sig.Tensor.Math as Torch.FFI.THC.Short.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.THC.Short.TensorMathCompare, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.THC.Short.TensorMathCompareT, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.THC.Short.TensorMathPairwise, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.THC.Short.TensorMathPointwise, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.THC.Short.TensorMathReduce, Torch.Sig.Tensor.Math.Scan as Torch.FFI.THC.Short.TensorMathScan, Torch.Sig.Tensor.Mode as Torch.FFI.THC.Short.TensorMode, Torch.Sig.Tensor.ScatterGather as Torch.FFI.THC.Short.TensorScatterGather, Torch.Sig.Tensor.Sort as Torch.FFI.THC.Short.TensorSort, Torch.Sig.Tensor.TopK as Torch.FFI.THC.Short.TensorTopK, Torch.Sig.Tensor.Math.Pointwise.Signed as Torch.FFI.THC.Short.TensorMathPointwise),
+                hasktorch-indef-signed (Torch.Indef.Storage as Torch.Indef.Cuda.Int.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Cuda.Int.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Cuda.Int.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Cuda.Int.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Cuda.Int.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Cuda.Int.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Cuda.Int.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Cuda.Int.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Cuda.Int.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Cuda.Int.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Cuda.Int.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Cuda.Int.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Cuda.Int.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Cuda.Int.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Cuda.Int.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Cuda.Int.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Cuda.Int.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Cuda.Int.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Cuda.Int.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Cuda.Int.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Cuda.Int.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Cuda.Int.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Cuda.Int.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Cuda.Int.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Cuda.Int.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Cuda.Int.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Cuda.Int.Types, Torch.Indef.Index as Torch.Cuda.Int.Index, Torch.Indef.Mask as Torch.Cuda.Int.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Cuda.Int.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Pointwise.Signed) requires (Torch.Sig.Index.Tensor as Torch.FFI.THC.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.THC.Long.Tensor, Torch.Sig.Mask.Tensor as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.MathReduce as Torch.FFI.THC.Byte.TensorMathReduce, Torch.Sig.State as Torch.FFI.THC.State, Torch.Sig.Types.Global as Torch.Types.THC, Torch.Sig.Types as Torch.Types.THC.Int, Torch.Sig.Storage as Torch.FFI.THC.Int.Storage, Torch.Sig.Storage.Copy as Torch.FFI.THC.Int.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.THC.Int.Storage, Torch.Sig.Tensor as Torch.FFI.THC.Int.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.THC.Int.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.THC.Int.Tensor, Torch.Sig.Tensor.Index as Torch.FFI.THC.Int.TensorIndex, Torch.Sig.Tensor.Masked as Torch.FFI.THC.Int.TensorMasked, Torch.Sig.Tensor.Math as Torch.FFI.THC.Int.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.THC.Int.TensorMathCompare, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.THC.Int.TensorMathCompareT, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.THC.Int.TensorMathPairwise, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.THC.Int.TensorMathPointwise, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.THC.Int.TensorMathReduce, Torch.Sig.Tensor.Math.Scan as Torch.FFI.THC.Int.TensorMathScan, Torch.Sig.Tensor.Mode as Torch.FFI.THC.Int.TensorMode, Torch.Sig.Tensor.ScatterGather as Torch.FFI.THC.Int.TensorScatterGather, Torch.Sig.Tensor.Sort as Torch.FFI.THC.Int.TensorSort, Torch.Sig.Tensor.TopK as Torch.FFI.THC.Int.TensorTopK, Torch.Sig.Tensor.Math.Pointwise.Signed as Torch.FFI.THC.Int.TensorMathPointwise)
+
+library hasktorch-indef-unsigned
+    reexported-modules: Torch.Indef.Index,
+                        Torch.Indef.Mask,
+                        Torch.Indef.Types,
+                        Torch.Indef.Storage,
+                        Torch.Indef.Storage.Copy,
+                        Torch.Indef.Dynamic.Print,
+                        Torch.Indef.Dynamic.Tensor,
+                        Torch.Indef.Dynamic.Tensor.Copy,
+                        Torch.Indef.Dynamic.Tensor.Index,
+                        Torch.Indef.Dynamic.Tensor.Masked,
+                        Torch.Indef.Dynamic.Tensor.Math,
+                        Torch.Indef.Dynamic.Tensor.Math.Compare,
+                        Torch.Indef.Dynamic.Tensor.Math.CompareT,
+                        Torch.Indef.Dynamic.Tensor.Math.Pairwise,
+                        Torch.Indef.Dynamic.Tensor.Math.Pointwise,
+                        Torch.Indef.Dynamic.Tensor.Math.Reduce,
+                        Torch.Indef.Dynamic.Tensor.Math.Scan,
+                        Torch.Indef.Dynamic.Tensor.Mode,
+                        Torch.Indef.Dynamic.Tensor.ScatterGather,
+                        Torch.Indef.Dynamic.Tensor.Sort,
+                        Torch.Indef.Dynamic.Tensor.TopK,
+                        Torch.Indef.Static.Tensor,
+                        Torch.Indef.Static.Tensor.Copy,
+                        Torch.Indef.Static.Tensor.Index,
+                        Torch.Indef.Static.Tensor.Masked,
+                        Torch.Indef.Static.Tensor.Math,
+                        Torch.Indef.Static.Tensor.Math.Compare,
+                        Torch.Indef.Static.Tensor.Math.CompareT,
+                        Torch.Indef.Static.Tensor.Math.Pairwise,
+                        Torch.Indef.Static.Tensor.Math.Pointwise,
+                        Torch.Indef.Static.Tensor.Math.Reduce,
+                        Torch.Indef.Static.Tensor.Math.Scan,
+                        Torch.Indef.Static.Tensor.Mode,
+                        Torch.Indef.Static.Tensor.ScatterGather,
+                        Torch.Indef.Static.Tensor.Sort,
+                        Torch.Indef.Static.Tensor.TopK
+    default-language: Haskell2010
+    build-depends:
+        base (==4.7 || >4.7) && <5,
+        hasktorch-signatures-partial (==0.0.1 || >0.0.1) && <0.0.2,
+        hasktorch-indef -any
+    mixins: hasktorch-indef requires (Torch.Sig.NN as Torch.Undefined.NN, Torch.Sig.Types.NN as Torch.Undefined.Types.NN, Torch.Sig.Tensor.Math.Blas as Torch.Undefined.Tensor.Math.Blas, Torch.Sig.Tensor.Math.Floating as Torch.Undefined.Tensor.Math.Floating, Torch.Sig.Tensor.Math.Lapack as Torch.Undefined.Tensor.Math.Lapack, Torch.Sig.Tensor.Math.Pointwise.Signed as Torch.Undefined.Tensor.Math.Pointwise.Signed, Torch.Sig.Tensor.Math.Pointwise.Floating as Torch.Undefined.Tensor.Math.Pointwise.Floating, Torch.Sig.Tensor.Math.Reduce.Floating as Torch.Undefined.Tensor.Math.Reduce.Floating, Torch.Sig.Tensor.Math.Random.TH as Torch.Undefined.Tensor.Math.Random.TH, Torch.Sig.Tensor.Random.TH as Torch.Undefined.Tensor.Random.TH, Torch.Sig.Tensor.Random.THC as Torch.Undefined.Tensor.Random.THC)
+
+library hasktorch-indef-signed
+    reexported-modules: Torch.Indef.Index,
+                        Torch.Indef.Mask,
+                        Torch.Indef.Types,
+                        Torch.Indef.Storage,
+                        Torch.Indef.Storage.Copy,
+                        Torch.Indef.Dynamic.Print,
+                        Torch.Indef.Dynamic.Tensor,
+                        Torch.Indef.Dynamic.Tensor.Copy,
+                        Torch.Indef.Dynamic.Tensor.Index,
+                        Torch.Indef.Dynamic.Tensor.Masked,
+                        Torch.Indef.Dynamic.Tensor.Math,
+                        Torch.Indef.Dynamic.Tensor.Math.Compare,
+                        Torch.Indef.Dynamic.Tensor.Math.CompareT,
+                        Torch.Indef.Dynamic.Tensor.Math.Pairwise,
+                        Torch.Indef.Dynamic.Tensor.Math.Pointwise,
+                        Torch.Indef.Dynamic.Tensor.Math.Reduce,
+                        Torch.Indef.Dynamic.Tensor.Math.Scan,
+                        Torch.Indef.Dynamic.Tensor.Mode,
+                        Torch.Indef.Dynamic.Tensor.ScatterGather,
+                        Torch.Indef.Dynamic.Tensor.Sort,
+                        Torch.Indef.Dynamic.Tensor.TopK,
+                        Torch.Indef.Static.Tensor,
+                        Torch.Indef.Static.Tensor.Copy,
+                        Torch.Indef.Static.Tensor.Index,
+                        Torch.Indef.Static.Tensor.Masked,
+                        Torch.Indef.Static.Tensor.Math,
+                        Torch.Indef.Static.Tensor.Math.Compare,
+                        Torch.Indef.Static.Tensor.Math.CompareT,
+                        Torch.Indef.Static.Tensor.Math.Pairwise,
+                        Torch.Indef.Static.Tensor.Math.Pointwise,
+                        Torch.Indef.Static.Tensor.Math.Reduce,
+                        Torch.Indef.Static.Tensor.Math.Scan,
+                        Torch.Indef.Static.Tensor.Mode,
+                        Torch.Indef.Static.Tensor.ScatterGather,
+                        Torch.Indef.Static.Tensor.Sort,
+                        Torch.Indef.Static.Tensor.TopK,
+                        Torch.Indef.Static.Tensor.Math.Pointwise.Signed,
+                        Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed
+    default-language: Haskell2010
+    build-depends:
+        base (==4.7 || >4.7) && <5,
+        hasktorch-signatures-partial (==0.0.1 || >0.0.1) && <0.0.2,
+        hasktorch-indef -any
+    mixins: hasktorch-indef requires (Torch.Sig.NN as Torch.Undefined.NN, Torch.Sig.Types.NN as Torch.Undefined.Types.NN, Torch.Sig.Tensor.Math.Blas as Torch.Undefined.Tensor.Math.Blas, Torch.Sig.Tensor.Math.Floating as Torch.Undefined.Tensor.Math.Floating, Torch.Sig.Tensor.Math.Lapack as Torch.Undefined.Tensor.Math.Lapack, Torch.Sig.Tensor.Math.Pointwise.Floating as Torch.Undefined.Tensor.Math.Pointwise.Floating, Torch.Sig.Tensor.Math.Reduce.Floating as Torch.Undefined.Tensor.Math.Reduce.Floating, Torch.Sig.Tensor.Math.Random.TH as Torch.Undefined.Tensor.Math.Random.TH, Torch.Sig.Tensor.Random.TH as Torch.Undefined.Tensor.Random.TH, Torch.Sig.Tensor.Random.THC as Torch.Undefined.Tensor.Random.THC)
+
+library hasktorch-indef-floating
+    reexported-modules: Torch.Indef.Index,
+                        Torch.Indef.Mask,
+                        Torch.Indef.Types,
+                        Torch.Indef.Storage,
+                        Torch.Indef.Storage.Copy,
+                        Torch.Indef.Dynamic.Print,
+                        Torch.Indef.Dynamic.Tensor,
+                        Torch.Indef.Dynamic.Tensor.Copy,
+                        Torch.Indef.Dynamic.Tensor.Index,
+                        Torch.Indef.Dynamic.Tensor.Masked,
+                        Torch.Indef.Dynamic.Tensor.Math,
+                        Torch.Indef.Dynamic.Tensor.Math.Compare,
+                        Torch.Indef.Dynamic.Tensor.Math.CompareT,
+                        Torch.Indef.Dynamic.Tensor.Math.Pairwise,
+                        Torch.Indef.Dynamic.Tensor.Math.Pointwise,
+                        Torch.Indef.Dynamic.Tensor.Math.Reduce,
+                        Torch.Indef.Dynamic.Tensor.Math.Scan,
+                        Torch.Indef.Dynamic.Tensor.Mode,
+                        Torch.Indef.Dynamic.Tensor.ScatterGather,
+                        Torch.Indef.Dynamic.Tensor.Sort,
+                        Torch.Indef.Dynamic.Tensor.TopK,
+                        Torch.Indef.Static.Tensor,
+                        Torch.Indef.Static.Tensor.Copy,
+                        Torch.Indef.Static.Tensor.Index,
+                        Torch.Indef.Static.Tensor.Masked,
+                        Torch.Indef.Static.Tensor.Math,
+                        Torch.Indef.Static.Tensor.Math.Compare,
+                        Torch.Indef.Static.Tensor.Math.CompareT,
+                        Torch.Indef.Static.Tensor.Math.Pairwise,
+                        Torch.Indef.Static.Tensor.Math.Pointwise,
+                        Torch.Indef.Static.Tensor.Math.Reduce,
+                        Torch.Indef.Static.Tensor.Math.Scan,
+                        Torch.Indef.Static.Tensor.Mode,
+                        Torch.Indef.Static.Tensor.ScatterGather,
+                        Torch.Indef.Static.Tensor.Sort,
+                        Torch.Indef.Static.Tensor.TopK,
+                        Torch.Indef.Static.Tensor.Math.Pointwise.Signed,
+                        Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed,
+                        Torch.Indef.Dynamic.Tensor.Math.Blas,
+                        Torch.Indef.Dynamic.Tensor.Math.Floating,
+                        Torch.Indef.Dynamic.Tensor.Math.Lapack,
+                        Torch.Indef.Dynamic.Tensor.Math.Pointwise.Floating,
+                        Torch.Indef.Dynamic.Tensor.Math.Reduce.Floating,
+                        Torch.Indef.Dynamic.Tensor.Random.TH,
+                        Torch.Indef.Dynamic.Tensor.Random.THC,
+                        Torch.Indef.Dynamic.Tensor.Math.Random.TH,
+                        Torch.Indef.Static.Tensor.Math.Blas,
+                        Torch.Indef.Static.Tensor.Math.Floating,
+                        Torch.Indef.Static.Tensor.Math.Lapack,
+                        Torch.Indef.Static.Tensor.Math.Pointwise.Floating,
+                        Torch.Indef.Static.Tensor.Math.Reduce.Floating,
+                        Torch.Indef.Static.Tensor.Random.TH,
+                        Torch.Indef.Static.Tensor.Random.THC,
+                        Torch.Indef.Static.Tensor.Math.Random.TH,
+                        Torch.Indef.Dynamic.NN,
+                        Torch.Indef.Dynamic.NN.Activation,
+                        Torch.Indef.Dynamic.NN.Pooling,
+                        Torch.Indef.Dynamic.NN.Criterion,
+                        Torch.Indef.Static.NN,
+                        Torch.Indef.Static.NN.Activation,
+                        Torch.Indef.Static.NN.Backprop,
+                        Torch.Indef.Static.NN.Conv1d,
+                        Torch.Indef.Static.NN.Conv2d,
+                        Torch.Indef.Static.NN.Criterion,
+                        Torch.Indef.Static.NN.Layers,
+                        Torch.Indef.Static.NN.Linear,
+                        Torch.Indef.Static.NN.Math,
+                        Torch.Indef.Static.NN.Padding,
+                        Torch.Indef.Static.NN.Pooling,
+                        Torch.Indef.Static.NN.Sampling,
+                        Torch.Undefined.Tensor.Math.Random.TH,
+                        Torch.Undefined.Tensor.Random.TH,
+                        Torch.Undefined.Tensor.Random.THC
+    default-language: Haskell2010
+    build-depends:
+        base (==4.7 || >4.7) && <5,
+        hasktorch-indef -any,
+        hasktorch-signatures-partial (==0.0.1 || >0.0.1) && <0.0.2
+
+executable isdefinite-cpu
+    main-is: Noop.hs
+    hs-source-dirs: exe
+    default-language: Haskell2010
+    build-depends:
+        base (==4.7 || >4.7) && <5,
+        hasktorch-cpu -any
+
+executable isdefinite-gpu
+    main-is: Noop.hs
+    hs-source-dirs: exe
+    default-language: Haskell2010
+    build-depends:
+        base (==4.7 || >4.7) && <5,
+        hasktorch-gpu -any
+
+executable isdefinite
+    main-is: Noop.hs
+    hs-source-dirs: exe
+    default-language: Haskell2010
+    build-depends:
+        base (==4.7 || >4.7) && <5,
+        hasktorch -any
+
+executable memcheck
+    main-is: Memcheck.hs
+    hs-source-dirs: exe
+    default-language: Haskell2010
+    build-depends:
+        base (==4.7 || >4.7) && <5,
+        hasktorch -any
+
+test-suite spec
+    type: exitcode-stdio-1.0
+    main-is: Spec.hs
+    hs-source-dirs: tests
+    other-modules:
+        Orphans
+        MemorySpec
+        RawLapackSVDSpec
+        GarbageCollectionSpec
+        Torch.Prelude.Extras
+        Torch.Core.LogAddSpec
+        Torch.Core.RandomSpec
+        Torch.Static.NN.AbsSpec
+        Torch.Static.NN.LinearSpec
+    default-language: Haskell2010
+    default-extensions: LambdaCase DataKinds TypeFamilies
+                        TypeSynonymInstances ScopedTypeVariables FlexibleContexts CPP
+    build-depends:
+        QuickCheck ==2.11 || >2.11,
+        backprop ==0.2.5 || >0.2.5,
+        base (==4.7 || >4.7) && <5,
+        dimensions ==1.0 || >1.0,
+        ghc-typelits-natnormalise -any,
+        hasktorch -any,
+        hspec ==2.4.4 || >2.4.4,
+        singletons ==2.2 || >2.2,
+        -- text ==1.2.2 || >1.2.2,
+        mtl ==2.2.2 || >2.2.2,
+        microlens-platform ==0.3.10 || >0.3.10,
+        monad-loops ==0.4.3 || >0.4.3,
+        time ==1.8.0 || >1.8.0,
+        transformers ==0.5.5 || >0.5.5,
+        generic-lens -any
+
diff --git a/Cabal/tests/ParserTests/regressions/hasktorch.expr b/Cabal/tests/ParserTests/regressions/hasktorch.expr
new file mode 100644
index 0000000000000000000000000000000000000000..839f850f71004e8c1203f8e1dd0d8b6c54b9eeba
--- /dev/null
+++ b/Cabal/tests/ParserTests/regressions/hasktorch.expr
@@ -0,0 +1,9817 @@
+GenericPackageDescription
+  {condBenchmarks = [],
+   condExecutables = [_×_
+                        (UnqualComponentName "isdefinite-cpu")
+                        CondNode
+                          {condTreeComponents = [],
+                           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")]))],
+                           condTreeData = Executable
+                                            {buildInfo = BuildInfo
+                                                           {asmOptions = [],
+                                                            asmSources = [],
+                                                            autogenIncludes = [],
+                                                            autogenModules = [],
+                                                            buildToolDepends = [],
+                                                            buildTools = [],
+                                                            buildable = True,
+                                                            cSources = [],
+                                                            ccOptions = [],
+                                                            cmmOptions = [],
+                                                            cmmSources = [],
+                                                            cppOptions = [],
+                                                            customFieldsBI = [],
+                                                            cxxOptions = [],
+                                                            cxxSources = [],
+                                                            defaultExtensions = [],
+                                                            defaultLanguage = Just Haskell2010,
+                                                            extraBundledLibs = [],
+                                                            extraDynLibFlavours = [],
+                                                            extraFrameworkDirs = [],
+                                                            extraGHCiLibs = [],
+                                                            extraLibDirs = [],
+                                                            extraLibFlavours = [],
+                                                            extraLibs = [],
+                                                            frameworks = [],
+                                                            hsSourceDirs = ["exe"],
+                                                            includeDirs = [],
+                                                            includes = [],
+                                                            installIncludes = [],
+                                                            jsSources = [],
+                                                            ldOptions = [],
+                                                            mixins = [],
+                                                            oldExtensions = [],
+                                                            options = PerCompilerFlavor [] [],
+                                                            otherExtensions = [],
+                                                            otherLanguages = [],
+                                                            otherModules = [],
+                                                            pkgconfigDepends = [],
+                                                            profOptions = PerCompilerFlavor [] [],
+                                                            sharedOptions = PerCompilerFlavor [] [],
+                                                            staticOptions = PerCompilerFlavor [] [],
+                                                            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")]))],
+                                                            virtualModules = []},
+                                             exeName = UnqualComponentName "isdefinite-cpu",
+                                             exeScope = ExecutablePublic,
+                                             modulePath = "Noop.hs"}},
+                      _×_
+                        (UnqualComponentName "isdefinite-gpu")
+                        CondNode
+                          {condTreeComponents = [],
+                           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")]))],
+                           condTreeData = Executable
+                                            {buildInfo = BuildInfo
+                                                           {asmOptions = [],
+                                                            asmSources = [],
+                                                            autogenIncludes = [],
+                                                            autogenModules = [],
+                                                            buildToolDepends = [],
+                                                            buildTools = [],
+                                                            buildable = True,
+                                                            cSources = [],
+                                                            ccOptions = [],
+                                                            cmmOptions = [],
+                                                            cmmSources = [],
+                                                            cppOptions = [],
+                                                            customFieldsBI = [],
+                                                            cxxOptions = [],
+                                                            cxxSources = [],
+                                                            defaultExtensions = [],
+                                                            defaultLanguage = Just Haskell2010,
+                                                            extraBundledLibs = [],
+                                                            extraDynLibFlavours = [],
+                                                            extraFrameworkDirs = [],
+                                                            extraGHCiLibs = [],
+                                                            extraLibDirs = [],
+                                                            extraLibFlavours = [],
+                                                            extraLibs = [],
+                                                            frameworks = [],
+                                                            hsSourceDirs = ["exe"],
+                                                            includeDirs = [],
+                                                            includes = [],
+                                                            installIncludes = [],
+                                                            jsSources = [],
+                                                            ldOptions = [],
+                                                            mixins = [],
+                                                            oldExtensions = [],
+                                                            options = PerCompilerFlavor [] [],
+                                                            otherExtensions = [],
+                                                            otherLanguages = [],
+                                                            otherModules = [],
+                                                            pkgconfigDepends = [],
+                                                            profOptions = PerCompilerFlavor [] [],
+                                                            sharedOptions = PerCompilerFlavor [] [],
+                                                            staticOptions = PerCompilerFlavor [] [],
+                                                            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")]))],
+                                                            virtualModules = []},
+                                             exeName = UnqualComponentName "isdefinite-gpu",
+                                             exeScope = ExecutablePublic,
+                                             modulePath = "Noop.hs"}},
+                      _×_
+                        (UnqualComponentName "isdefinite")
+                        CondNode
+                          {condTreeComponents = [],
+                           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],
+                           condTreeData = Executable
+                                            {buildInfo = BuildInfo
+                                                           {asmOptions = [],
+                                                            asmSources = [],
+                                                            autogenIncludes = [],
+                                                            autogenModules = [],
+                                                            buildToolDepends = [],
+                                                            buildTools = [],
+                                                            buildable = True,
+                                                            cSources = [],
+                                                            ccOptions = [],
+                                                            cmmOptions = [],
+                                                            cmmSources = [],
+                                                            cppOptions = [],
+                                                            customFieldsBI = [],
+                                                            cxxOptions = [],
+                                                            cxxSources = [],
+                                                            defaultExtensions = [],
+                                                            defaultLanguage = Just Haskell2010,
+                                                            extraBundledLibs = [],
+                                                            extraDynLibFlavours = [],
+                                                            extraFrameworkDirs = [],
+                                                            extraGHCiLibs = [],
+                                                            extraLibDirs = [],
+                                                            extraLibFlavours = [],
+                                                            extraLibs = [],
+                                                            frameworks = [],
+                                                            hsSourceDirs = ["exe"],
+                                                            includeDirs = [],
+                                                            includes = [],
+                                                            installIncludes = [],
+                                                            jsSources = [],
+                                                            ldOptions = [],
+                                                            mixins = [],
+                                                            oldExtensions = [],
+                                                            options = PerCompilerFlavor [] [],
+                                                            otherExtensions = [],
+                                                            otherLanguages = [],
+                                                            otherModules = [],
+                                                            pkgconfigDepends = [],
+                                                            profOptions = PerCompilerFlavor [] [],
+                                                            sharedOptions = PerCompilerFlavor [] [],
+                                                            staticOptions = PerCompilerFlavor [] [],
+                                                            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],
+                                                            virtualModules = []},
+                                             exeName = UnqualComponentName "isdefinite",
+                                             exeScope = ExecutablePublic,
+                                             modulePath = "Noop.hs"}},
+                      _×_
+                        (UnqualComponentName "memcheck")
+                        CondNode
+                          {condTreeComponents = [],
+                           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],
+                           condTreeData = Executable
+                                            {buildInfo = BuildInfo
+                                                           {asmOptions = [],
+                                                            asmSources = [],
+                                                            autogenIncludes = [],
+                                                            autogenModules = [],
+                                                            buildToolDepends = [],
+                                                            buildTools = [],
+                                                            buildable = True,
+                                                            cSources = [],
+                                                            ccOptions = [],
+                                                            cmmOptions = [],
+                                                            cmmSources = [],
+                                                            cppOptions = [],
+                                                            customFieldsBI = [],
+                                                            cxxOptions = [],
+                                                            cxxSources = [],
+                                                            defaultExtensions = [],
+                                                            defaultLanguage = Just Haskell2010,
+                                                            extraBundledLibs = [],
+                                                            extraDynLibFlavours = [],
+                                                            extraFrameworkDirs = [],
+                                                            extraGHCiLibs = [],
+                                                            extraLibDirs = [],
+                                                            extraLibFlavours = [],
+                                                            extraLibs = [],
+                                                            frameworks = [],
+                                                            hsSourceDirs = ["exe"],
+                                                            includeDirs = [],
+                                                            includes = [],
+                                                            installIncludes = [],
+                                                            jsSources = [],
+                                                            ldOptions = [],
+                                                            mixins = [],
+                                                            oldExtensions = [],
+                                                            options = PerCompilerFlavor [] [],
+                                                            otherExtensions = [],
+                                                            otherLanguages = [],
+                                                            otherModules = [],
+                                                            pkgconfigDepends = [],
+                                                            profOptions = PerCompilerFlavor [] [],
+                                                            sharedOptions = PerCompilerFlavor [] [],
+                                                            staticOptions = PerCompilerFlavor [] [],
+                                                            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],
+                                                            virtualModules = []},
+                                             exeName = UnqualComponentName "memcheck",
+                                             exeScope = ExecutablePublic,
+                                             modulePath = "Memcheck.hs"}}],
+   condForeignLibs = [],
+   condLibrary = Just
+                   CondNode
+                     {condTreeComponents = [CondBranch
+                                              {condBranchCondition = `CNot (Var (PackageFlag (FlagName "lite")))`,
+                                               condBranchIfFalse = Nothing,
+                                               condBranchIfTrue = CondNode
+                                                                    {condTreeComponents = [],
+                                                                     condTreeConstraints = [],
+                                                                     condTreeData = Library
+                                                                                      {exposedModules = [],
+                                                                                       libBuildInfo = BuildInfo
+                                                                                                        {asmOptions = [],
+                                                                                                         asmSources = [],
+                                                                                                         autogenIncludes = [],
+                                                                                                         autogenModules = [],
+                                                                                                         buildToolDepends = [],
+                                                                                                         buildTools = [],
+                                                                                                         buildable = True,
+                                                                                                         cSources = [],
+                                                                                                         ccOptions = [],
+                                                                                                         cmmOptions = [],
+                                                                                                         cmmSources = [],
+                                                                                                         cppOptions = [],
+                                                                                                         customFieldsBI = [],
+                                                                                                         cxxOptions = [],
+                                                                                                         cxxSources = [],
+                                                                                                         defaultExtensions = [],
+                                                                                                         defaultLanguage = Nothing,
+                                                                                                         extraBundledLibs = [],
+                                                                                                         extraDynLibFlavours = [],
+                                                                                                         extraFrameworkDirs = [],
+                                                                                                         extraGHCiLibs = [],
+                                                                                                         extraLibDirs = [],
+                                                                                                         extraLibFlavours = [],
+                                                                                                         extraLibs = [],
+                                                                                                         frameworks = [],
+                                                                                                         hsSourceDirs = [],
+                                                                                                         includeDirs = [],
+                                                                                                         includes = [],
+                                                                                                         installIncludes = [],
+                                                                                                         jsSources = [],
+                                                                                                         ldOptions = [],
+                                                                                                         mixins = [],
+                                                                                                         oldExtensions = [],
+                                                                                                         options = PerCompilerFlavor
+                                                                                                                     []
+                                                                                                                     [],
+                                                                                                         otherExtensions = [],
+                                                                                                         otherLanguages = [],
+                                                                                                         otherModules = [],
+                                                                                                         pkgconfigDepends = [],
+                                                                                                         profOptions = PerCompilerFlavor
+                                                                                                                         []
+                                                                                                                         [],
+                                                                                                         sharedOptions = PerCompilerFlavor
+                                                                                                                           []
+                                                                                                                           [],
+                                                                                                         staticOptions = PerCompilerFlavor
+                                                                                                                           []
+                                                                                                                           [],
+                                                                                                         targetBuildDepends = [],
+                                                                                                         virtualModules = []},
+                                                                                       libExposed = True,
+                                                                                       libName = LMainLibName,
+                                                                                       libVisibility = LibraryVisibilityPublic,
+                                                                                       reexportedModules = [ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Byte",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Byte",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Byte.Dynamic",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Byte.Dynamic",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Byte.Storage",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Byte.Storage",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Char",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Char",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Char.Dynamic",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Char.Dynamic",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Char.Storage",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Char.Storage",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Short",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Short",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Short.Dynamic",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Short.Dynamic",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Short.Storage",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Short.Storage",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Int",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Int",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Int.Dynamic",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Int.Dynamic",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Int.Storage",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Int.Storage",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Float",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Float",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Float.Dynamic",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Float.Dynamic",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Float.Storage",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Float.Storage",
+                                                                                                               moduleReexportOriginalPackage = Nothing}],
+                                                                                       signatures = []}}},
+                                            CondBranch
+                                              {condBranchCondition = `Var (PackageFlag (FlagName "cuda"))`,
+                                               condBranchIfFalse = Nothing,
+                                               condBranchIfTrue = CondNode
+                                                                    {condTreeComponents = [CondBranch
+                                                                                             {condBranchCondition = `CNot (Var (PackageFlag (FlagName "lite")))`,
+                                                                                              condBranchIfFalse = Nothing,
+                                                                                              condBranchIfTrue = CondNode
+                                                                                                                   {condTreeComponents = [],
+                                                                                                                    condTreeConstraints = [],
+                                                                                                                    condTreeData = Library
+                                                                                                                                     {exposedModules = [],
+                                                                                                                                      libBuildInfo = BuildInfo
+                                                                                                                                                       {asmOptions = [],
+                                                                                                                                                        asmSources = [],
+                                                                                                                                                        autogenIncludes = [],
+                                                                                                                                                        autogenModules = [],
+                                                                                                                                                        buildToolDepends = [],
+                                                                                                                                                        buildTools = [],
+                                                                                                                                                        buildable = True,
+                                                                                                                                                        cSources = [],
+                                                                                                                                                        ccOptions = [],
+                                                                                                                                                        cmmOptions = [],
+                                                                                                                                                        cmmSources = [],
+                                                                                                                                                        cppOptions = [],
+                                                                                                                                                        customFieldsBI = [],
+                                                                                                                                                        cxxOptions = [],
+                                                                                                                                                        cxxSources = [],
+                                                                                                                                                        defaultExtensions = [],
+                                                                                                                                                        defaultLanguage = Nothing,
+                                                                                                                                                        extraBundledLibs = [],
+                                                                                                                                                        extraDynLibFlavours = [],
+                                                                                                                                                        extraFrameworkDirs = [],
+                                                                                                                                                        extraGHCiLibs = [],
+                                                                                                                                                        extraLibDirs = [],
+                                                                                                                                                        extraLibFlavours = [],
+                                                                                                                                                        extraLibs = [],
+                                                                                                                                                        frameworks = [],
+                                                                                                                                                        hsSourceDirs = [],
+                                                                                                                                                        includeDirs = [],
+                                                                                                                                                        includes = [],
+                                                                                                                                                        installIncludes = [],
+                                                                                                                                                        jsSources = [],
+                                                                                                                                                        ldOptions = [],
+                                                                                                                                                        mixins = [],
+                                                                                                                                                        oldExtensions = [],
+                                                                                                                                                        options = PerCompilerFlavor
+                                                                                                                                                                    []
+                                                                                                                                                                    [],
+                                                                                                                                                        otherExtensions = [],
+                                                                                                                                                        otherLanguages = [],
+                                                                                                                                                        otherModules = [],
+                                                                                                                                                        pkgconfigDepends = [],
+                                                                                                                                                        profOptions = PerCompilerFlavor
+                                                                                                                                                                        []
+                                                                                                                                                                        [],
+                                                                                                                                                        sharedOptions = PerCompilerFlavor
+                                                                                                                                                                          []
+                                                                                                                                                                          [],
+                                                                                                                                                        staticOptions = PerCompilerFlavor
+                                                                                                                                                                          []
+                                                                                                                                                                          [],
+                                                                                                                                                        targetBuildDepends = [],
+                                                                                                                                                        virtualModules = []},
+                                                                                                                                      libExposed = True,
+                                                                                                                                      libName = LMainLibName,
+                                                                                                                                      libVisibility = LibraryVisibilityPublic,
+                                                                                                                                      reexportedModules = [ModuleReexport
+                                                                                                                                                             {moduleReexportName = ModuleName
+                                                                                                                                                                                     "Torch.Cuda.Byte",
+                                                                                                                                                              moduleReexportOriginalName = ModuleName
+                                                                                                                                                                                             "Torch.Cuda.Byte",
+                                                                                                                                                              moduleReexportOriginalPackage = Nothing},
+                                                                                                                                                           ModuleReexport
+                                                                                                                                                             {moduleReexportName = ModuleName
+                                                                                                                                                                                     "Torch.Cuda.Byte.Dynamic",
+                                                                                                                                                              moduleReexportOriginalName = ModuleName
+                                                                                                                                                                                             "Torch.Cuda.Byte.Dynamic",
+                                                                                                                                                              moduleReexportOriginalPackage = Nothing},
+                                                                                                                                                           ModuleReexport
+                                                                                                                                                             {moduleReexportName = ModuleName
+                                                                                                                                                                                     "Torch.Cuda.Byte.Storage",
+                                                                                                                                                              moduleReexportOriginalName = ModuleName
+                                                                                                                                                                                             "Torch.Cuda.Byte.Storage",
+                                                                                                                                                              moduleReexportOriginalPackage = Nothing},
+                                                                                                                                                           ModuleReexport
+                                                                                                                                                             {moduleReexportName = ModuleName
+                                                                                                                                                                                     "Torch.Cuda.Char",
+                                                                                                                                                              moduleReexportOriginalName = ModuleName
+                                                                                                                                                                                             "Torch.Cuda.Char",
+                                                                                                                                                              moduleReexportOriginalPackage = Nothing},
+                                                                                                                                                           ModuleReexport
+                                                                                                                                                             {moduleReexportName = ModuleName
+                                                                                                                                                                                     "Torch.Cuda.Char.Dynamic",
+                                                                                                                                                              moduleReexportOriginalName = ModuleName
+                                                                                                                                                                                             "Torch.Cuda.Char.Dynamic",
+                                                                                                                                                              moduleReexportOriginalPackage = Nothing},
+                                                                                                                                                           ModuleReexport
+                                                                                                                                                             {moduleReexportName = ModuleName
+                                                                                                                                                                                     "Torch.Cuda.Char.Storage",
+                                                                                                                                                              moduleReexportOriginalName = ModuleName
+                                                                                                                                                                                             "Torch.Cuda.Char.Storage",
+                                                                                                                                                              moduleReexportOriginalPackage = Nothing},
+                                                                                                                                                           ModuleReexport
+                                                                                                                                                             {moduleReexportName = ModuleName
+                                                                                                                                                                                     "Torch.Cuda.Short",
+                                                                                                                                                              moduleReexportOriginalName = ModuleName
+                                                                                                                                                                                             "Torch.Cuda.Short",
+                                                                                                                                                              moduleReexportOriginalPackage = Nothing},
+                                                                                                                                                           ModuleReexport
+                                                                                                                                                             {moduleReexportName = ModuleName
+                                                                                                                                                                                     "Torch.Cuda.Short.Dynamic",
+                                                                                                                                                              moduleReexportOriginalName = ModuleName
+                                                                                                                                                                                             "Torch.Cuda.Short.Dynamic",
+                                                                                                                                                              moduleReexportOriginalPackage = Nothing},
+                                                                                                                                                           ModuleReexport
+                                                                                                                                                             {moduleReexportName = ModuleName
+                                                                                                                                                                                     "Torch.Cuda.Short.Storage",
+                                                                                                                                                              moduleReexportOriginalName = ModuleName
+                                                                                                                                                                                             "Torch.Cuda.Short.Storage",
+                                                                                                                                                              moduleReexportOriginalPackage = Nothing},
+                                                                                                                                                           ModuleReexport
+                                                                                                                                                             {moduleReexportName = ModuleName
+                                                                                                                                                                                     "Torch.Cuda.Int",
+                                                                                                                                                              moduleReexportOriginalName = ModuleName
+                                                                                                                                                                                             "Torch.Cuda.Int",
+                                                                                                                                                              moduleReexportOriginalPackage = Nothing},
+                                                                                                                                                           ModuleReexport
+                                                                                                                                                             {moduleReexportName = ModuleName
+                                                                                                                                                                                     "Torch.Cuda.Int.Dynamic",
+                                                                                                                                                              moduleReexportOriginalName = ModuleName
+                                                                                                                                                                                             "Torch.Cuda.Int.Dynamic",
+                                                                                                                                                              moduleReexportOriginalPackage = Nothing},
+                                                                                                                                                           ModuleReexport
+                                                                                                                                                             {moduleReexportName = ModuleName
+                                                                                                                                                                                     "Torch.Cuda.Int.Storage",
+                                                                                                                                                              moduleReexportOriginalName = ModuleName
+                                                                                                                                                                                             "Torch.Cuda.Int.Storage",
+                                                                                                                                                              moduleReexportOriginalPackage = Nothing},
+                                                                                                                                                           ModuleReexport
+                                                                                                                                                             {moduleReexportName = ModuleName
+                                                                                                                                                                                     "Torch.Cuda.Float",
+                                                                                                                                                              moduleReexportOriginalName = ModuleName
+                                                                                                                                                                                             "Torch.Cuda.Float",
+                                                                                                                                                              moduleReexportOriginalPackage = Nothing},
+                                                                                                                                                           ModuleReexport
+                                                                                                                                                             {moduleReexportName = ModuleName
+                                                                                                                                                                                     "Torch.Cuda.Float.Dynamic",
+                                                                                                                                                              moduleReexportOriginalName = ModuleName
+                                                                                                                                                                                             "Torch.Cuda.Float.Dynamic",
+                                                                                                                                                              moduleReexportOriginalPackage = Nothing},
+                                                                                                                                                           ModuleReexport
+                                                                                                                                                             {moduleReexportName = ModuleName
+                                                                                                                                                                                     "Torch.Cuda.Float.Storage",
+                                                                                                                                                              moduleReexportOriginalName = ModuleName
+                                                                                                                                                                                             "Torch.Cuda.Float.Storage",
+                                                                                                                                                              moduleReexportOriginalPackage = Nothing}],
+                                                                                                                                      signatures = []}}}],
+                                                                     condTreeConstraints = [Dependency
+                                                                                              (PackageName
+                                                                                                 "hasktorch")
+                                                                                              (OrLaterVersion
+                                                                                                 (mkVersion
+                                                                                                    [0]))
+                                                                                              (NonEmptySet.fromNonEmpty
+                                                                                                 (NE.fromList
+                                                                                                    [LSubLibName
+                                                                                                       (UnqualComponentName
+                                                                                                          "hasktorch-gpu")]))],
+                                                                     condTreeData = Library
+                                                                                      {exposedModules = [],
+                                                                                       libBuildInfo = BuildInfo
+                                                                                                        {asmOptions = [],
+                                                                                                         asmSources = [],
+                                                                                                         autogenIncludes = [],
+                                                                                                         autogenModules = [],
+                                                                                                         buildToolDepends = [],
+                                                                                                         buildTools = [],
+                                                                                                         buildable = True,
+                                                                                                         cSources = [],
+                                                                                                         ccOptions = [],
+                                                                                                         cmmOptions = [],
+                                                                                                         cmmSources = [],
+                                                                                                         cppOptions = [],
+                                                                                                         customFieldsBI = [],
+                                                                                                         cxxOptions = [],
+                                                                                                         cxxSources = [],
+                                                                                                         defaultExtensions = [],
+                                                                                                         defaultLanguage = Nothing,
+                                                                                                         extraBundledLibs = [],
+                                                                                                         extraDynLibFlavours = [],
+                                                                                                         extraFrameworkDirs = [],
+                                                                                                         extraGHCiLibs = [],
+                                                                                                         extraLibDirs = [],
+                                                                                                         extraLibFlavours = [],
+                                                                                                         extraLibs = [],
+                                                                                                         frameworks = [],
+                                                                                                         hsSourceDirs = [],
+                                                                                                         includeDirs = [],
+                                                                                                         includes = [],
+                                                                                                         installIncludes = [],
+                                                                                                         jsSources = [],
+                                                                                                         ldOptions = [],
+                                                                                                         mixins = [],
+                                                                                                         oldExtensions = [],
+                                                                                                         options = PerCompilerFlavor
+                                                                                                                     []
+                                                                                                                     [],
+                                                                                                         otherExtensions = [],
+                                                                                                         otherLanguages = [],
+                                                                                                         otherModules = [],
+                                                                                                         pkgconfigDepends = [],
+                                                                                                         profOptions = PerCompilerFlavor
+                                                                                                                         []
+                                                                                                                         [],
+                                                                                                         sharedOptions = PerCompilerFlavor
+                                                                                                                           []
+                                                                                                                           [],
+                                                                                                         staticOptions = PerCompilerFlavor
+                                                                                                                           []
+                                                                                                                           [],
+                                                                                                         targetBuildDepends = [Dependency
+                                                                                                                                 (PackageName
+                                                                                                                                    "hasktorch")
+                                                                                                                                 (OrLaterVersion
+                                                                                                                                    (mkVersion
+                                                                                                                                       [0]))
+                                                                                                                                 (NonEmptySet.fromNonEmpty
+                                                                                                                                    (NE.fromList
+                                                                                                                                       [LSubLibName
+                                                                                                                                          (UnqualComponentName
+                                                                                                                                             "hasktorch-gpu")]))],
+                                                                                                         virtualModules = []},
+                                                                                       libExposed = True,
+                                                                                       libName = LMainLibName,
+                                                                                       libVisibility = LibraryVisibilityPublic,
+                                                                                       reexportedModules = [ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Long",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Long",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Long.Dynamic",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Long.Dynamic",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Long.Storage",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Long.Storage",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Double",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Double",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Double.Dynamic",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Double.Dynamic",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Double.Storage",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Double.Storage",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Double.NN",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Double.NN",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Double.NN.Activation",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Double.NN.Activation",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Double.NN.Backprop",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Double.NN.Backprop",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Double.NN.Conv1d",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Double.NN.Conv1d",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Double.NN.Conv2d",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Double.NN.Conv2d",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Double.NN.Criterion",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Double.NN.Criterion",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Double.NN.Layers",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Double.NN.Layers",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Double.NN.Linear",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Double.NN.Linear",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Double.NN.Math",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Double.NN.Math",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Double.NN.Padding",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Double.NN.Padding",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Double.NN.Pooling",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Double.NN.Pooling",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Double.NN.Sampling",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Double.NN.Sampling",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Double.Dynamic.NN",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Double.Dynamic.NN",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Double.Dynamic.NN.Activation",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Double.Dynamic.NN.Activation",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Double.Dynamic.NN.Pooling",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Double.Dynamic.NN.Pooling",
+                                                                                                               moduleReexportOriginalPackage = Nothing},
+                                                                                                            ModuleReexport
+                                                                                                              {moduleReexportName = ModuleName
+                                                                                                                                      "Torch.Cuda.Double.Dynamic.NN.Criterion",
+                                                                                                               moduleReexportOriginalName = ModuleName
+                                                                                                                                              "Torch.Cuda.Double.Dynamic.NN.Criterion",
+                                                                                                               moduleReexportOriginalPackage = Nothing}],
+                                                                                       signatures = []}}}],
+                      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],
+                      condTreeData = Library
+                                       {exposedModules = [ModuleName "Torch.Core.Exceptions",
+                                                          ModuleName "Torch.Core.Random",
+                                                          ModuleName "Torch.Core.LogAdd"],
+                                        libBuildInfo = BuildInfo
+                                                         {asmOptions = [],
+                                                          asmSources = [],
+                                                          autogenIncludes = [],
+                                                          autogenModules = [],
+                                                          buildToolDepends = [],
+                                                          buildTools = [],
+                                                          buildable = True,
+                                                          cSources = [],
+                                                          ccOptions = [],
+                                                          cmmOptions = [],
+                                                          cmmSources = [],
+                                                          cppOptions = [],
+                                                          customFieldsBI = [],
+                                                          cxxOptions = [],
+                                                          cxxSources = [],
+                                                          defaultExtensions = [EnableExtension
+                                                                                 LambdaCase,
+                                                                               EnableExtension
+                                                                                 DataKinds,
+                                                                               EnableExtension
+                                                                                 TypeFamilies,
+                                                                               EnableExtension
+                                                                                 TypeSynonymInstances,
+                                                                               EnableExtension
+                                                                                 ScopedTypeVariables,
+                                                                               EnableExtension
+                                                                                 FlexibleContexts,
+                                                                               EnableExtension CPP],
+                                                          defaultLanguage = Just Haskell2010,
+                                                          extraBundledLibs = [],
+                                                          extraDynLibFlavours = [],
+                                                          extraFrameworkDirs = [],
+                                                          extraGHCiLibs = [],
+                                                          extraLibDirs = [],
+                                                          extraLibFlavours = [],
+                                                          extraLibs = [],
+                                                          frameworks = [],
+                                                          hsSourceDirs = ["utils"],
+                                                          includeDirs = [],
+                                                          includes = [],
+                                                          installIncludes = [],
+                                                          jsSources = [],
+                                                          ldOptions = [],
+                                                          mixins = [],
+                                                          oldExtensions = [],
+                                                          options = PerCompilerFlavor [] [],
+                                                          otherExtensions = [],
+                                                          otherLanguages = [],
+                                                          otherModules = [],
+                                                          pkgconfigDepends = [],
+                                                          profOptions = PerCompilerFlavor [] [],
+                                                          sharedOptions = PerCompilerFlavor [] [],
+                                                          staticOptions = PerCompilerFlavor [] [],
+                                                          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],
+                                                          virtualModules = []},
+                                        libExposed = True,
+                                        libName = LMainLibName,
+                                        libVisibility = LibraryVisibilityPublic,
+                                        reexportedModules = [ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Types.Numeric",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Types.Numeric",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Long",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Long",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Long.Dynamic",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Long.Dynamic",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Long.Storage",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Long.Storage",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Double",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Double",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Double.Dynamic",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Double.Dynamic",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Double.Storage",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Double.Storage",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Double.NN",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Double.NN",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Double.NN.Activation",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Double.NN.Activation",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Double.NN.Backprop",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Double.NN.Backprop",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Double.NN.Conv1d",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Double.NN.Conv1d",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Double.NN.Conv2d",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Double.NN.Conv2d",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Double.NN.Criterion",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Double.NN.Criterion",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Double.NN.Layers",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Double.NN.Layers",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Double.NN.Linear",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Double.NN.Linear",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Double.NN.Math",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Double.NN.Math",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Double.NN.Padding",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Double.NN.Padding",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Double.NN.Pooling",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Double.NN.Pooling",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Double.NN.Sampling",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Double.NN.Sampling",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Double.Dynamic.NN",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Double.Dynamic.NN",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Double.Dynamic.NN.Activation",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Double.Dynamic.NN.Activation",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Double.Dynamic.NN.Pooling",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Double.Dynamic.NN.Pooling",
+                                                                moduleReexportOriginalPackage = Nothing},
+                                                             ModuleReexport
+                                                               {moduleReexportName = ModuleName
+                                                                                       "Torch.Double.Dynamic.NN.Criterion",
+                                                                moduleReexportOriginalName = ModuleName
+                                                                                               "Torch.Double.Dynamic.NN.Criterion",
+                                                                moduleReexportOriginalPackage = Nothing}],
+                                        signatures = []}},
+   condSubLibraries = [_×_
+                         (UnqualComponentName "hasktorch-cpu")
+                         CondNode
+                           {condTreeComponents = [CondBranch
+                                                    {condBranchCondition = `Var (PackageFlag (FlagName "lite"))`,
+                                                     condBranchIfFalse = Just
+                                                                           CondNode
+                                                                             {condTreeComponents = [],
+                                                                              condTreeConstraints = [Dependency
+                                                                                                       (PackageName
+                                                                                                          "hasktorch")
+                                                                                                       (OrLaterVersion
+                                                                                                          (mkVersion
+                                                                                                             [0]))
+                                                                                                       (NonEmptySet.fromNonEmpty
+                                                                                                          (NE.fromList
+                                                                                                             [LSubLibName
+                                                                                                                (UnqualComponentName
+                                                                                                                   "hasktorch-indef-unsigned")]))],
+                                                                              condTreeData = Library
+                                                                                               {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"],
+                                                                                                libBuildInfo = BuildInfo
+                                                                                                                 {asmOptions = [],
+                                                                                                                  asmSources = [],
+                                                                                                                  autogenIncludes = [],
+                                                                                                                  autogenModules = [],
+                                                                                                                  buildToolDepends = [],
+                                                                                                                  buildTools = [],
+                                                                                                                  buildable = True,
+                                                                                                                  cSources = [],
+                                                                                                                  ccOptions = [],
+                                                                                                                  cmmOptions = [],
+                                                                                                                  cmmSources = [],
+                                                                                                                  cppOptions = [],
+                                                                                                                  customFieldsBI = [],
+                                                                                                                  cxxOptions = [],
+                                                                                                                  cxxSources = [],
+                                                                                                                  defaultExtensions = [],
+                                                                                                                  defaultLanguage = Nothing,
+                                                                                                                  extraBundledLibs = [],
+                                                                                                                  extraDynLibFlavours = [],
+                                                                                                                  extraFrameworkDirs = [],
+                                                                                                                  extraGHCiLibs = [],
+                                                                                                                  extraLibDirs = [],
+                                                                                                                  extraLibFlavours = [],
+                                                                                                                  extraLibs = [],
+                                                                                                                  frameworks = [],
+                                                                                                                  hsSourceDirs = [],
+                                                                                                                  includeDirs = [],
+                                                                                                                  includes = [],
+                                                                                                                  installIncludes = [],
+                                                                                                                  jsSources = [],
+                                                                                                                  ldOptions = [],
+                                                                                                                  mixins = [Mixin
+                                                                                                                              {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")]},
+                                                                                                                               mixinLibraryName = LSubLibName
+                                                                                                                                                    (UnqualComponentName
+                                                                                                                                                       "hasktorch-indef-unsigned"),
+                                                                                                                               mixinPackageName = PackageName
+                                                                                                                                                    "hasktorch"},
+                                                                                                                            Mixin
+                                                                                                                              {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")]},
+                                                                                                                               mixinLibraryName = LSubLibName
+                                                                                                                                                    (UnqualComponentName
+                                                                                                                                                       "hasktorch-indef-unsigned"),
+                                                                                                                               mixinPackageName = PackageName
+                                                                                                                                                    "hasktorch"},
+                                                                                                                            Mixin
+                                                                                                                              {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")]},
+                                                                                                                               mixinLibraryName = LSubLibName
+                                                                                                                                                    (UnqualComponentName
+                                                                                                                                                       "hasktorch-indef-signed"),
+                                                                                                                               mixinPackageName = PackageName
+                                                                                                                                                    "hasktorch"},
+                                                                                                                            Mixin
+                                                                                                                              {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")]},
+                                                                                                                               mixinLibraryName = LSubLibName
+                                                                                                                                                    (UnqualComponentName
+                                                                                                                                                       "hasktorch-indef-signed"),
+                                                                                                                               mixinPackageName = PackageName
+                                                                                                                                                    "hasktorch"},
+                                                                                                                            Mixin
+                                                                                                                              {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")]},
+                                                                                                                               mixinLibraryName = LSubLibName
+                                                                                                                                                    (UnqualComponentName
+                                                                                                                                                       "hasktorch-indef-floating"),
+                                                                                                                               mixinPackageName = PackageName
+                                                                                                                                                    "hasktorch"}],
+                                                                                                                  oldExtensions = [],
+                                                                                                                  options = PerCompilerFlavor
+                                                                                                                              []
+                                                                                                                              [],
+                                                                                                                  otherExtensions = [],
+                                                                                                                  otherLanguages = [],
+                                                                                                                  otherModules = [],
+                                                                                                                  pkgconfigDepends = [],
+                                                                                                                  profOptions = PerCompilerFlavor
+                                                                                                                                  []
+                                                                                                                                  [],
+                                                                                                                  sharedOptions = PerCompilerFlavor
+                                                                                                                                    []
+                                                                                                                                    [],
+                                                                                                                  staticOptions = PerCompilerFlavor
+                                                                                                                                    []
+                                                                                                                                    [],
+                                                                                                                  targetBuildDepends = [Dependency
+                                                                                                                                          (PackageName
+                                                                                                                                             "hasktorch")
+                                                                                                                                          (OrLaterVersion
+                                                                                                                                             (mkVersion
+                                                                                                                                                [0]))
+                                                                                                                                          (NonEmptySet.fromNonEmpty
+                                                                                                                                             (NE.fromList
+                                                                                                                                                [LSubLibName
+                                                                                                                                                   (UnqualComponentName
+                                                                                                                                                      "hasktorch-indef-unsigned")]))],
+                                                                                                                  virtualModules = []},
+                                                                                                libExposed = True,
+                                                                                                libName = LSubLibName
+                                                                                                            (UnqualComponentName
+                                                                                                               "hasktorch-cpu"),
+                                                                                                libVisibility = LibraryVisibilityPrivate,
+                                                                                                reexportedModules = [],
+                                                                                                signatures = []}},
+                                                     condBranchIfTrue = CondNode
+                                                                          {condTreeComponents = [],
+                                                                           condTreeConstraints = [],
+                                                                           condTreeData = Library
+                                                                                            {exposedModules = [],
+                                                                                             libBuildInfo = BuildInfo
+                                                                                                              {asmOptions = [],
+                                                                                                               asmSources = [],
+                                                                                                               autogenIncludes = [],
+                                                                                                               autogenModules = [],
+                                                                                                               buildToolDepends = [],
+                                                                                                               buildTools = [],
+                                                                                                               buildable = True,
+                                                                                                               cSources = [],
+                                                                                                               ccOptions = [],
+                                                                                                               cmmOptions = [],
+                                                                                                               cmmSources = [],
+                                                                                                               cppOptions = [],
+                                                                                                               customFieldsBI = [],
+                                                                                                               cxxOptions = [],
+                                                                                                               cxxSources = [],
+                                                                                                               defaultExtensions = [],
+                                                                                                               defaultLanguage = Nothing,
+                                                                                                               extraBundledLibs = [],
+                                                                                                               extraDynLibFlavours = [],
+                                                                                                               extraFrameworkDirs = [],
+                                                                                                               extraGHCiLibs = [],
+                                                                                                               extraLibDirs = [],
+                                                                                                               extraLibFlavours = [],
+                                                                                                               extraLibs = [],
+                                                                                                               frameworks = [],
+                                                                                                               hsSourceDirs = [],
+                                                                                                               includeDirs = [],
+                                                                                                               includes = [],
+                                                                                                               installIncludes = [],
+                                                                                                               jsSources = [],
+                                                                                                               ldOptions = [],
+                                                                                                               mixins = [],
+                                                                                                               oldExtensions = [],
+                                                                                                               options = PerCompilerFlavor
+                                                                                                                           []
+                                                                                                                           [],
+                                                                                                               otherExtensions = [],
+                                                                                                               otherLanguages = [],
+                                                                                                               otherModules = [],
+                                                                                                               pkgconfigDepends = [],
+                                                                                                               profOptions = PerCompilerFlavor
+                                                                                                                               []
+                                                                                                                               [],
+                                                                                                               sharedOptions = PerCompilerFlavor
+                                                                                                                                 []
+                                                                                                                                 [],
+                                                                                                               staticOptions = PerCompilerFlavor
+                                                                                                                                 []
+                                                                                                                                 [],
+                                                                                                               targetBuildDepends = [],
+                                                                                                               virtualModules = []},
+                                                                                             libExposed = True,
+                                                                                             libName = LSubLibName
+                                                                                                         (UnqualComponentName
+                                                                                                            "hasktorch-cpu"),
+                                                                                             libVisibility = LibraryVisibilityPrivate,
+                                                                                             reexportedModules = [],
+                                                                                             signatures = []}}}],
+                            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")]))],
+                            condTreeData = Library
+                                             {exposedModules = [ModuleName "Torch.Long",
+                                                                ModuleName "Torch.Long.Dynamic",
+                                                                ModuleName "Torch.Long.Storage",
+                                                                ModuleName "Torch.Double",
+                                                                ModuleName "Torch.Double.Dynamic",
+                                                                ModuleName "Torch.Double.Storage"],
+                                              libBuildInfo = BuildInfo
+                                                               {asmOptions = [],
+                                                                asmSources = [],
+                                                                autogenIncludes = [],
+                                                                autogenModules = [],
+                                                                buildToolDepends = [],
+                                                                buildTools = [],
+                                                                buildable = True,
+                                                                cSources = [],
+                                                                ccOptions = [],
+                                                                cmmOptions = [],
+                                                                cmmSources = [],
+                                                                cppOptions = [],
+                                                                customFieldsBI = [],
+                                                                cxxOptions = [],
+                                                                cxxSources = [],
+                                                                defaultExtensions = [EnableExtension
+                                                                                       LambdaCase,
+                                                                                     EnableExtension
+                                                                                       DataKinds,
+                                                                                     EnableExtension
+                                                                                       TypeFamilies,
+                                                                                     EnableExtension
+                                                                                       TypeSynonymInstances,
+                                                                                     EnableExtension
+                                                                                       ScopedTypeVariables,
+                                                                                     EnableExtension
+                                                                                       FlexibleContexts,
+                                                                                     EnableExtension
+                                                                                       CPP],
+                                                                defaultLanguage = Just Haskell2010,
+                                                                extraBundledLibs = [],
+                                                                extraDynLibFlavours = [],
+                                                                extraFrameworkDirs = [],
+                                                                extraGHCiLibs = [],
+                                                                extraLibDirs = [],
+                                                                extraLibFlavours = [],
+                                                                extraLibs = [],
+                                                                frameworks = [],
+                                                                hsSourceDirs = ["utils", "src"],
+                                                                includeDirs = [],
+                                                                includes = [],
+                                                                installIncludes = [],
+                                                                jsSources = [],
+                                                                ldOptions = [],
+                                                                mixins = [Mixin
+                                                                            {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")]},
+                                                                             mixinLibraryName = LSubLibName
+                                                                                                  (UnqualComponentName
+                                                                                                     "hasktorch-indef-signed"),
+                                                                             mixinPackageName = PackageName
+                                                                                                  "hasktorch"},
+                                                                          Mixin
+                                                                            {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")]},
+                                                                             mixinLibraryName = LSubLibName
+                                                                                                  (UnqualComponentName
+                                                                                                     "hasktorch-indef-floating"),
+                                                                             mixinPackageName = PackageName
+                                                                                                  "hasktorch"}],
+                                                                oldExtensions = [],
+                                                                options = PerCompilerFlavor [] [],
+                                                                otherExtensions = [],
+                                                                otherLanguages = [],
+                                                                otherModules = [ModuleName
+                                                                                  "Torch.Core.Exceptions",
+                                                                                ModuleName
+                                                                                  "Torch.Core.Random",
+                                                                                ModuleName
+                                                                                  "Torch.Core.LogAdd"],
+                                                                pkgconfigDepends = [],
+                                                                profOptions = PerCompilerFlavor
+                                                                                [] [],
+                                                                sharedOptions = PerCompilerFlavor
+                                                                                  [] [],
+                                                                staticOptions = PerCompilerFlavor
+                                                                                  [] [],
+                                                                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")]))],
+                                                                virtualModules = []},
+                                              libExposed = True,
+                                              libName = LSubLibName
+                                                          (UnqualComponentName "hasktorch-cpu"),
+                                              libVisibility = LibraryVisibilityPrivate,
+                                              reexportedModules = [ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Double.NN",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Double.NN",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Double.NN.Activation",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Double.NN.Activation",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Double.NN.Backprop",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Double.NN.Backprop",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Double.NN.Conv1d",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Double.NN.Conv1d",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Double.NN.Conv2d",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Double.NN.Conv2d",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Double.NN.Criterion",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Double.NN.Criterion",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Double.NN.Layers",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Double.NN.Layers",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Double.NN.Linear",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Double.NN.Linear",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Double.NN.Math",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Double.NN.Math",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Double.NN.Padding",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Double.NN.Padding",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Double.NN.Pooling",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Double.NN.Pooling",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Double.NN.Sampling",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Double.NN.Sampling",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Double.Dynamic.NN",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Double.Dynamic.NN",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Double.Dynamic.NN.Activation",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Double.Dynamic.NN.Activation",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Double.Dynamic.NN.Pooling",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Double.Dynamic.NN.Pooling",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Double.Dynamic.NN.Criterion",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Double.Dynamic.NN.Criterion",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Float.NN",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Float.NN",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Float.NN.Activation",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Float.NN.Activation",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Float.NN.Backprop",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Float.NN.Backprop",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Float.NN.Conv1d",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Float.NN.Conv1d",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Float.NN.Conv2d",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Float.NN.Conv2d",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Float.NN.Criterion",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Float.NN.Criterion",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Float.NN.Layers",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Float.NN.Layers",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Float.NN.Linear",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Float.NN.Linear",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Float.NN.Math",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Float.NN.Math",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Float.NN.Padding",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Float.NN.Padding",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Float.NN.Pooling",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Float.NN.Pooling",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Float.NN.Sampling",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Float.NN.Sampling",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Float.Dynamic.NN",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Float.Dynamic.NN",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Float.Dynamic.NN.Activation",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Float.Dynamic.NN.Activation",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Float.Dynamic.NN.Pooling",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Float.Dynamic.NN.Pooling",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Float.Dynamic.NN.Criterion",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Float.Dynamic.NN.Criterion",
+                                                                      moduleReexportOriginalPackage = Nothing}],
+                                              signatures = []}},
+                       _×_
+                         (UnqualComponentName "hasktorch-gpu")
+                         CondNode
+                           {condTreeComponents = [CondBranch
+                                                    {condBranchCondition = `Var (PackageFlag (FlagName "lite"))`,
+                                                     condBranchIfFalse = Just
+                                                                           CondNode
+                                                                             {condTreeComponents = [],
+                                                                              condTreeConstraints = [Dependency
+                                                                                                       (PackageName
+                                                                                                          "hasktorch")
+                                                                                                       (OrLaterVersion
+                                                                                                          (mkVersion
+                                                                                                             [0]))
+                                                                                                       (NonEmptySet.fromNonEmpty
+                                                                                                          (NE.fromList
+                                                                                                             [LSubLibName
+                                                                                                                (UnqualComponentName
+                                                                                                                   "hasktorch-indef-unsigned")]))],
+                                                                              condTreeData = Library
+                                                                                               {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"],
+                                                                                                libBuildInfo = BuildInfo
+                                                                                                                 {asmOptions = [],
+                                                                                                                  asmSources = [],
+                                                                                                                  autogenIncludes = [],
+                                                                                                                  autogenModules = [],
+                                                                                                                  buildToolDepends = [],
+                                                                                                                  buildTools = [],
+                                                                                                                  buildable = True,
+                                                                                                                  cSources = [],
+                                                                                                                  ccOptions = [],
+                                                                                                                  cmmOptions = [],
+                                                                                                                  cmmSources = [],
+                                                                                                                  cppOptions = [],
+                                                                                                                  customFieldsBI = [],
+                                                                                                                  cxxOptions = [],
+                                                                                                                  cxxSources = [],
+                                                                                                                  defaultExtensions = [],
+                                                                                                                  defaultLanguage = Nothing,
+                                                                                                                  extraBundledLibs = [],
+                                                                                                                  extraDynLibFlavours = [],
+                                                                                                                  extraFrameworkDirs = [],
+                                                                                                                  extraGHCiLibs = [],
+                                                                                                                  extraLibDirs = [],
+                                                                                                                  extraLibFlavours = [],
+                                                                                                                  extraLibs = [],
+                                                                                                                  frameworks = [],
+                                                                                                                  hsSourceDirs = [],
+                                                                                                                  includeDirs = [],
+                                                                                                                  includes = [],
+                                                                                                                  installIncludes = [],
+                                                                                                                  jsSources = [],
+                                                                                                                  ldOptions = [],
+                                                                                                                  mixins = [Mixin
+                                                                                                                              {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")]},
+                                                                                                                               mixinLibraryName = LSubLibName
+                                                                                                                                                    (UnqualComponentName
+                                                                                                                                                       "hasktorch-indef-unsigned"),
+                                                                                                                               mixinPackageName = PackageName
+                                                                                                                                                    "hasktorch"},
+                                                                                                                            Mixin
+                                                                                                                              {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")]},
+                                                                                                                               mixinLibraryName = LSubLibName
+                                                                                                                                                    (UnqualComponentName
+                                                                                                                                                       "hasktorch-indef-unsigned"),
+                                                                                                                               mixinPackageName = PackageName
+                                                                                                                                                    "hasktorch"},
+                                                                                                                            Mixin
+                                                                                                                              {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")]},
+                                                                                                                               mixinLibraryName = LSubLibName
+                                                                                                                                                    (UnqualComponentName
+                                                                                                                                                       "hasktorch-indef-signed"),
+                                                                                                                               mixinPackageName = PackageName
+                                                                                                                                                    "hasktorch"},
+                                                                                                                            Mixin
+                                                                                                                              {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")]},
+                                                                                                                               mixinLibraryName = LSubLibName
+                                                                                                                                                    (UnqualComponentName
+                                                                                                                                                       "hasktorch-indef-signed"),
+                                                                                                                               mixinPackageName = PackageName
+                                                                                                                                                    "hasktorch"}],
+                                                                                                                  oldExtensions = [],
+                                                                                                                  options = PerCompilerFlavor
+                                                                                                                              []
+                                                                                                                              [],
+                                                                                                                  otherExtensions = [],
+                                                                                                                  otherLanguages = [],
+                                                                                                                  otherModules = [],
+                                                                                                                  pkgconfigDepends = [],
+                                                                                                                  profOptions = PerCompilerFlavor
+                                                                                                                                  []
+                                                                                                                                  [],
+                                                                                                                  sharedOptions = PerCompilerFlavor
+                                                                                                                                    []
+                                                                                                                                    [],
+                                                                                                                  staticOptions = PerCompilerFlavor
+                                                                                                                                    []
+                                                                                                                                    [],
+                                                                                                                  targetBuildDepends = [Dependency
+                                                                                                                                          (PackageName
+                                                                                                                                             "hasktorch")
+                                                                                                                                          (OrLaterVersion
+                                                                                                                                             (mkVersion
+                                                                                                                                                [0]))
+                                                                                                                                          (NonEmptySet.fromNonEmpty
+                                                                                                                                             (NE.fromList
+                                                                                                                                                [LSubLibName
+                                                                                                                                                   (UnqualComponentName
+                                                                                                                                                      "hasktorch-indef-unsigned")]))],
+                                                                                                                  virtualModules = []},
+                                                                                                libExposed = True,
+                                                                                                libName = LSubLibName
+                                                                                                            (UnqualComponentName
+                                                                                                               "hasktorch-gpu"),
+                                                                                                libVisibility = LibraryVisibilityPrivate,
+                                                                                                reexportedModules = [],
+                                                                                                signatures = []}},
+                                                     condBranchIfTrue = CondNode
+                                                                          {condTreeComponents = [],
+                                                                           condTreeConstraints = [],
+                                                                           condTreeData = Library
+                                                                                            {exposedModules = [],
+                                                                                             libBuildInfo = BuildInfo
+                                                                                                              {asmOptions = [],
+                                                                                                               asmSources = [],
+                                                                                                               autogenIncludes = [],
+                                                                                                               autogenModules = [],
+                                                                                                               buildToolDepends = [],
+                                                                                                               buildTools = [],
+                                                                                                               buildable = True,
+                                                                                                               cSources = [],
+                                                                                                               ccOptions = [],
+                                                                                                               cmmOptions = [],
+                                                                                                               cmmSources = [],
+                                                                                                               cppOptions = [],
+                                                                                                               customFieldsBI = [],
+                                                                                                               cxxOptions = [],
+                                                                                                               cxxSources = [],
+                                                                                                               defaultExtensions = [],
+                                                                                                               defaultLanguage = Nothing,
+                                                                                                               extraBundledLibs = [],
+                                                                                                               extraDynLibFlavours = [],
+                                                                                                               extraFrameworkDirs = [],
+                                                                                                               extraGHCiLibs = [],
+                                                                                                               extraLibDirs = [],
+                                                                                                               extraLibFlavours = [],
+                                                                                                               extraLibs = [],
+                                                                                                               frameworks = [],
+                                                                                                               hsSourceDirs = [],
+                                                                                                               includeDirs = [],
+                                                                                                               includes = [],
+                                                                                                               installIncludes = [],
+                                                                                                               jsSources = [],
+                                                                                                               ldOptions = [],
+                                                                                                               mixins = [],
+                                                                                                               oldExtensions = [],
+                                                                                                               options = PerCompilerFlavor
+                                                                                                                           []
+                                                                                                                           [],
+                                                                                                               otherExtensions = [],
+                                                                                                               otherLanguages = [],
+                                                                                                               otherModules = [],
+                                                                                                               pkgconfigDepends = [],
+                                                                                                               profOptions = PerCompilerFlavor
+                                                                                                                               []
+                                                                                                                               [],
+                                                                                                               sharedOptions = PerCompilerFlavor
+                                                                                                                                 []
+                                                                                                                                 [],
+                                                                                                               staticOptions = PerCompilerFlavor
+                                                                                                                                 []
+                                                                                                                                 [],
+                                                                                                               targetBuildDepends = [],
+                                                                                                               virtualModules = []},
+                                                                                             libExposed = True,
+                                                                                             libName = LSubLibName
+                                                                                                         (UnqualComponentName
+                                                                                                            "hasktorch-gpu"),
+                                                                                             libVisibility = LibraryVisibilityPrivate,
+                                                                                             reexportedModules = [],
+                                                                                             signatures = []}}}],
+                            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],
+                            condTreeData = Library
+                                             {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"],
+                                              libBuildInfo = BuildInfo
+                                                               {asmOptions = [],
+                                                                asmSources = [],
+                                                                autogenIncludes = [],
+                                                                autogenModules = [],
+                                                                buildToolDepends = [],
+                                                                buildTools = [],
+                                                                buildable = True,
+                                                                cSources = [],
+                                                                ccOptions = [],
+                                                                cmmOptions = [],
+                                                                cmmSources = [],
+                                                                cppOptions = ["-DCUDA",
+                                                                              "-DHASKTORCH_INTERNAL_CUDA"],
+                                                                customFieldsBI = [],
+                                                                cxxOptions = [],
+                                                                cxxSources = [],
+                                                                defaultExtensions = [EnableExtension
+                                                                                       LambdaCase,
+                                                                                     EnableExtension
+                                                                                       DataKinds,
+                                                                                     EnableExtension
+                                                                                       TypeFamilies,
+                                                                                     EnableExtension
+                                                                                       TypeSynonymInstances,
+                                                                                     EnableExtension
+                                                                                       ScopedTypeVariables,
+                                                                                     EnableExtension
+                                                                                       FlexibleContexts,
+                                                                                     EnableExtension
+                                                                                       CPP],
+                                                                defaultLanguage = Just Haskell2010,
+                                                                extraBundledLibs = [],
+                                                                extraDynLibFlavours = [],
+                                                                extraFrameworkDirs = [],
+                                                                extraGHCiLibs = [],
+                                                                extraLibDirs = [],
+                                                                extraLibFlavours = [],
+                                                                extraLibs = [],
+                                                                frameworks = [],
+                                                                hsSourceDirs = ["utils", "src"],
+                                                                includeDirs = [],
+                                                                includes = [],
+                                                                installIncludes = [],
+                                                                jsSources = [],
+                                                                ldOptions = [],
+                                                                mixins = [Mixin
+                                                                            {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")]},
+                                                                             mixinLibraryName = LSubLibName
+                                                                                                  (UnqualComponentName
+                                                                                                     "hasktorch-indef-signed"),
+                                                                             mixinPackageName = PackageName
+                                                                                                  "hasktorch"},
+                                                                          Mixin
+                                                                            {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")]},
+                                                                             mixinLibraryName = LSubLibName
+                                                                                                  (UnqualComponentName
+                                                                                                     "hasktorch-indef-floating"),
+                                                                             mixinPackageName = PackageName
+                                                                                                  "hasktorch"}],
+                                                                oldExtensions = [],
+                                                                options = PerCompilerFlavor [] [],
+                                                                otherExtensions = [],
+                                                                otherLanguages = [],
+                                                                otherModules = [ModuleName
+                                                                                  "Torch.Core.Exceptions",
+                                                                                ModuleName
+                                                                                  "Torch.Core.Random",
+                                                                                ModuleName
+                                                                                  "Torch.Core.LogAdd"],
+                                                                pkgconfigDepends = [],
+                                                                profOptions = PerCompilerFlavor
+                                                                                [] [],
+                                                                sharedOptions = PerCompilerFlavor
+                                                                                  [] [],
+                                                                staticOptions = PerCompilerFlavor
+                                                                                  [] [],
+                                                                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],
+                                                                virtualModules = []},
+                                              libExposed = True,
+                                              libName = LSubLibName
+                                                          (UnqualComponentName "hasktorch-gpu"),
+                                              libVisibility = LibraryVisibilityPrivate,
+                                              reexportedModules = [ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Cuda.Double.NN",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Cuda.Double.NN",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Cuda.Double.NN.Activation",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Cuda.Double.NN.Activation",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Cuda.Double.NN.Backprop",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Cuda.Double.NN.Backprop",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Cuda.Double.NN.Conv1d",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Cuda.Double.NN.Conv1d",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Cuda.Double.NN.Conv2d",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Cuda.Double.NN.Conv2d",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Cuda.Double.NN.Criterion",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Cuda.Double.NN.Criterion",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Cuda.Double.NN.Layers",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Cuda.Double.NN.Layers",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Cuda.Double.NN.Linear",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Cuda.Double.NN.Linear",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Cuda.Double.NN.Math",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Cuda.Double.NN.Math",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Cuda.Double.NN.Padding",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Cuda.Double.NN.Padding",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Cuda.Double.NN.Pooling",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Cuda.Double.NN.Pooling",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Cuda.Double.NN.Sampling",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Cuda.Double.NN.Sampling",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Cuda.Double.Dynamic.NN",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Cuda.Double.Dynamic.NN",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Cuda.Double.Dynamic.NN.Activation",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Cuda.Double.Dynamic.NN.Activation",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Cuda.Double.Dynamic.NN.Pooling",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Cuda.Double.Dynamic.NN.Pooling",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Cuda.Double.Dynamic.NN.Criterion",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Cuda.Double.Dynamic.NN.Criterion",
+                                                                      moduleReexportOriginalPackage = Nothing}],
+                                              signatures = []}},
+                       _×_
+                         (UnqualComponentName "hasktorch-indef-unsigned")
+                         CondNode
+                           {condTreeComponents = [],
+                            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],
+                            condTreeData = Library
+                                             {exposedModules = [],
+                                              libBuildInfo = BuildInfo
+                                                               {asmOptions = [],
+                                                                asmSources = [],
+                                                                autogenIncludes = [],
+                                                                autogenModules = [],
+                                                                buildToolDepends = [],
+                                                                buildTools = [],
+                                                                buildable = True,
+                                                                cSources = [],
+                                                                ccOptions = [],
+                                                                cmmOptions = [],
+                                                                cmmSources = [],
+                                                                cppOptions = [],
+                                                                customFieldsBI = [],
+                                                                cxxOptions = [],
+                                                                cxxSources = [],
+                                                                defaultExtensions = [],
+                                                                defaultLanguage = Just Haskell2010,
+                                                                extraBundledLibs = [],
+                                                                extraDynLibFlavours = [],
+                                                                extraFrameworkDirs = [],
+                                                                extraGHCiLibs = [],
+                                                                extraLibDirs = [],
+                                                                extraLibFlavours = [],
+                                                                extraLibs = [],
+                                                                frameworks = [],
+                                                                hsSourceDirs = [],
+                                                                includeDirs = [],
+                                                                includes = [],
+                                                                installIncludes = [],
+                                                                jsSources = [],
+                                                                ldOptions = [],
+                                                                mixins = [Mixin
+                                                                            {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")]},
+                                                                             mixinLibraryName = LMainLibName,
+                                                                             mixinPackageName = PackageName
+                                                                                                  "hasktorch-indef"}],
+                                                                oldExtensions = [],
+                                                                options = PerCompilerFlavor [] [],
+                                                                otherExtensions = [],
+                                                                otherLanguages = [],
+                                                                otherModules = [],
+                                                                pkgconfigDepends = [],
+                                                                profOptions = PerCompilerFlavor
+                                                                                [] [],
+                                                                sharedOptions = PerCompilerFlavor
+                                                                                  [] [],
+                                                                staticOptions = PerCompilerFlavor
+                                                                                  [] [],
+                                                                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],
+                                                                virtualModules = []},
+                                              libExposed = True,
+                                              libName = LSubLibName
+                                                          (UnqualComponentName
+                                                             "hasktorch-indef-unsigned"),
+                                              libVisibility = LibraryVisibilityPrivate,
+                                              reexportedModules = [ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Index",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Index",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Mask",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Mask",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Types",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Types",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Storage",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Storage",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Storage.Copy",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Storage.Copy",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Print",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Print",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Copy",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Copy",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Index",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Index",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Masked",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Masked",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Compare",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Compare",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.CompareT",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.CompareT",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Pairwise",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Pairwise",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Pointwise",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Pointwise",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Reduce",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Reduce",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Scan",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Scan",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Mode",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Mode",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.ScatterGather",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.ScatterGather",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Sort",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Sort",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.TopK",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.TopK",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Copy",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Copy",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Index",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Index",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Masked",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Masked",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Compare",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Compare",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.CompareT",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.CompareT",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Pairwise",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Pairwise",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Pointwise",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Pointwise",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Reduce",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Reduce",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Scan",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Scan",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Mode",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Mode",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.ScatterGather",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.ScatterGather",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Sort",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Sort",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.TopK",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.TopK",
+                                                                      moduleReexportOriginalPackage = Nothing}],
+                                              signatures = []}},
+                       _×_
+                         (UnqualComponentName "hasktorch-indef-signed")
+                         CondNode
+                           {condTreeComponents = [],
+                            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],
+                            condTreeData = Library
+                                             {exposedModules = [],
+                                              libBuildInfo = BuildInfo
+                                                               {asmOptions = [],
+                                                                asmSources = [],
+                                                                autogenIncludes = [],
+                                                                autogenModules = [],
+                                                                buildToolDepends = [],
+                                                                buildTools = [],
+                                                                buildable = True,
+                                                                cSources = [],
+                                                                ccOptions = [],
+                                                                cmmOptions = [],
+                                                                cmmSources = [],
+                                                                cppOptions = [],
+                                                                customFieldsBI = [],
+                                                                cxxOptions = [],
+                                                                cxxSources = [],
+                                                                defaultExtensions = [],
+                                                                defaultLanguage = Just Haskell2010,
+                                                                extraBundledLibs = [],
+                                                                extraDynLibFlavours = [],
+                                                                extraFrameworkDirs = [],
+                                                                extraGHCiLibs = [],
+                                                                extraLibDirs = [],
+                                                                extraLibFlavours = [],
+                                                                extraLibs = [],
+                                                                frameworks = [],
+                                                                hsSourceDirs = [],
+                                                                includeDirs = [],
+                                                                includes = [],
+                                                                installIncludes = [],
+                                                                jsSources = [],
+                                                                ldOptions = [],
+                                                                mixins = [Mixin
+                                                                            {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")]},
+                                                                             mixinLibraryName = LMainLibName,
+                                                                             mixinPackageName = PackageName
+                                                                                                  "hasktorch-indef"}],
+                                                                oldExtensions = [],
+                                                                options = PerCompilerFlavor [] [],
+                                                                otherExtensions = [],
+                                                                otherLanguages = [],
+                                                                otherModules = [],
+                                                                pkgconfigDepends = [],
+                                                                profOptions = PerCompilerFlavor
+                                                                                [] [],
+                                                                sharedOptions = PerCompilerFlavor
+                                                                                  [] [],
+                                                                staticOptions = PerCompilerFlavor
+                                                                                  [] [],
+                                                                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],
+                                                                virtualModules = []},
+                                              libExposed = True,
+                                              libName = LSubLibName
+                                                          (UnqualComponentName
+                                                             "hasktorch-indef-signed"),
+                                              libVisibility = LibraryVisibilityPrivate,
+                                              reexportedModules = [ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Index",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Index",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Mask",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Mask",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Types",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Types",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Storage",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Storage",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Storage.Copy",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Storage.Copy",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Print",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Print",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Copy",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Copy",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Index",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Index",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Masked",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Masked",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Compare",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Compare",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.CompareT",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.CompareT",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Pairwise",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Pairwise",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Pointwise",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Pointwise",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Reduce",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Reduce",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Scan",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Scan",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Mode",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Mode",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.ScatterGather",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.ScatterGather",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Sort",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Sort",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.TopK",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.TopK",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Copy",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Copy",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Index",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Index",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Masked",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Masked",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Compare",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Compare",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.CompareT",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.CompareT",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Pairwise",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Pairwise",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Pointwise",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Pointwise",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Reduce",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Reduce",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Scan",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Scan",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Mode",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Mode",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.ScatterGather",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.ScatterGather",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Sort",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Sort",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.TopK",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.TopK",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Pointwise.Signed",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Pointwise.Signed",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed",
+                                                                      moduleReexportOriginalPackage = Nothing}],
+                                              signatures = []}},
+                       _×_
+                         (UnqualComponentName "hasktorch-indef-floating")
+                         CondNode
+                           {condTreeComponents = [],
+                            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],
+                            condTreeData = Library
+                                             {exposedModules = [],
+                                              libBuildInfo = BuildInfo
+                                                               {asmOptions = [],
+                                                                asmSources = [],
+                                                                autogenIncludes = [],
+                                                                autogenModules = [],
+                                                                buildToolDepends = [],
+                                                                buildTools = [],
+                                                                buildable = True,
+                                                                cSources = [],
+                                                                ccOptions = [],
+                                                                cmmOptions = [],
+                                                                cmmSources = [],
+                                                                cppOptions = [],
+                                                                customFieldsBI = [],
+                                                                cxxOptions = [],
+                                                                cxxSources = [],
+                                                                defaultExtensions = [],
+                                                                defaultLanguage = Just Haskell2010,
+                                                                extraBundledLibs = [],
+                                                                extraDynLibFlavours = [],
+                                                                extraFrameworkDirs = [],
+                                                                extraGHCiLibs = [],
+                                                                extraLibDirs = [],
+                                                                extraLibFlavours = [],
+                                                                extraLibs = [],
+                                                                frameworks = [],
+                                                                hsSourceDirs = [],
+                                                                includeDirs = [],
+                                                                includes = [],
+                                                                installIncludes = [],
+                                                                jsSources = [],
+                                                                ldOptions = [],
+                                                                mixins = [],
+                                                                oldExtensions = [],
+                                                                options = PerCompilerFlavor [] [],
+                                                                otherExtensions = [],
+                                                                otherLanguages = [],
+                                                                otherModules = [],
+                                                                pkgconfigDepends = [],
+                                                                profOptions = PerCompilerFlavor
+                                                                                [] [],
+                                                                sharedOptions = PerCompilerFlavor
+                                                                                  [] [],
+                                                                staticOptions = PerCompilerFlavor
+                                                                                  [] [],
+                                                                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],
+                                                                virtualModules = []},
+                                              libExposed = True,
+                                              libName = LSubLibName
+                                                          (UnqualComponentName
+                                                             "hasktorch-indef-floating"),
+                                              libVisibility = LibraryVisibilityPrivate,
+                                              reexportedModules = [ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Index",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Index",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Mask",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Mask",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Types",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Types",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Storage",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Storage",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Storage.Copy",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Storage.Copy",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Print",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Print",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Copy",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Copy",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Index",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Index",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Masked",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Masked",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Compare",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Compare",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.CompareT",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.CompareT",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Pairwise",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Pairwise",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Pointwise",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Pointwise",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Reduce",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Reduce",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Scan",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Scan",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Mode",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Mode",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.ScatterGather",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.ScatterGather",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Sort",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Sort",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.TopK",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.TopK",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Copy",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Copy",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Index",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Index",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Masked",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Masked",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Compare",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Compare",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.CompareT",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.CompareT",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Pairwise",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Pairwise",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Pointwise",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Pointwise",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Reduce",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Reduce",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Scan",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Scan",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Mode",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Mode",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.ScatterGather",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.ScatterGather",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Sort",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Sort",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.TopK",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.TopK",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Pointwise.Signed",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Pointwise.Signed",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Blas",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Blas",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Floating",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Floating",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Lapack",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Lapack",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Floating",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Pointwise.Floating",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Reduce.Floating",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Reduce.Floating",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Random.TH",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Random.TH",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Random.THC",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Random.THC",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.Tensor.Math.Random.TH",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.Tensor.Math.Random.TH",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Blas",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Blas",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Floating",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Floating",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Lapack",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Lapack",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Pointwise.Floating",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Pointwise.Floating",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Reduce.Floating",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Reduce.Floating",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Random.TH",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Random.TH",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Random.THC",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Random.THC",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.Tensor.Math.Random.TH",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.Tensor.Math.Random.TH",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.NN",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.NN",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.NN.Activation",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.NN.Activation",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.NN.Pooling",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.NN.Pooling",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Dynamic.NN.Criterion",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Dynamic.NN.Criterion",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.NN",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.NN",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.NN.Activation",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.NN.Activation",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.NN.Backprop",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.NN.Backprop",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.NN.Conv1d",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.NN.Conv1d",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.NN.Conv2d",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.NN.Conv2d",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.NN.Criterion",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.NN.Criterion",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.NN.Layers",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.NN.Layers",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.NN.Linear",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.NN.Linear",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.NN.Math",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.NN.Math",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.NN.Padding",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.NN.Padding",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.NN.Pooling",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.NN.Pooling",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Indef.Static.NN.Sampling",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Indef.Static.NN.Sampling",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Undefined.Tensor.Math.Random.TH",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Undefined.Tensor.Math.Random.TH",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Undefined.Tensor.Random.TH",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Undefined.Tensor.Random.TH",
+                                                                      moduleReexportOriginalPackage = Nothing},
+                                                                   ModuleReexport
+                                                                     {moduleReexportName = ModuleName
+                                                                                             "Torch.Undefined.Tensor.Random.THC",
+                                                                      moduleReexportOriginalName = ModuleName
+                                                                                                     "Torch.Undefined.Tensor.Random.THC",
+                                                                      moduleReexportOriginalPackage = Nothing}],
+                                              signatures = []}}],
+   condTestSuites = [_×_
+                       (UnqualComponentName "spec")
+                       CondNode
+                         {condTreeComponents = [],
+                          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],
+                          condTreeData = TestSuite
+                                           {testBuildInfo = BuildInfo
+                                                              {asmOptions = [],
+                                                               asmSources = [],
+                                                               autogenIncludes = [],
+                                                               autogenModules = [],
+                                                               buildToolDepends = [],
+                                                               buildTools = [],
+                                                               buildable = True,
+                                                               cSources = [],
+                                                               ccOptions = [],
+                                                               cmmOptions = [],
+                                                               cmmSources = [],
+                                                               cppOptions = [],
+                                                               customFieldsBI = [],
+                                                               cxxOptions = [],
+                                                               cxxSources = [],
+                                                               defaultExtensions = [EnableExtension
+                                                                                      LambdaCase,
+                                                                                    EnableExtension
+                                                                                      DataKinds,
+                                                                                    EnableExtension
+                                                                                      TypeFamilies,
+                                                                                    EnableExtension
+                                                                                      TypeSynonymInstances,
+                                                                                    EnableExtension
+                                                                                      ScopedTypeVariables,
+                                                                                    EnableExtension
+                                                                                      FlexibleContexts,
+                                                                                    EnableExtension
+                                                                                      CPP],
+                                                               defaultLanguage = Just Haskell2010,
+                                                               extraBundledLibs = [],
+                                                               extraDynLibFlavours = [],
+                                                               extraFrameworkDirs = [],
+                                                               extraGHCiLibs = [],
+                                                               extraLibDirs = [],
+                                                               extraLibFlavours = [],
+                                                               extraLibs = [],
+                                                               frameworks = [],
+                                                               hsSourceDirs = ["tests"],
+                                                               includeDirs = [],
+                                                               includes = [],
+                                                               installIncludes = [],
+                                                               jsSources = [],
+                                                               ldOptions = [],
+                                                               mixins = [],
+                                                               oldExtensions = [],
+                                                               options = PerCompilerFlavor [] [],
+                                                               otherExtensions = [],
+                                                               otherLanguages = [],
+                                                               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"],
+                                                               pkgconfigDepends = [],
+                                                               profOptions = PerCompilerFlavor
+                                                                               [] [],
+                                                               sharedOptions = PerCompilerFlavor
+                                                                                 [] [],
+                                                               staticOptions = PerCompilerFlavor
+                                                                                 [] [],
+                                                               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],
+                                                               virtualModules = []},
+                                            testInterface = TestSuiteExeV10
+                                                              (mkVersion [1, 0]) "Spec.hs",
+                                            testName = UnqualComponentName ""}}],
+   genPackageFlags = [MkPackageFlag
+                        {flagDefault = False,
+                         flagDescription = "build with THC support",
+                         flagManual = False,
+                         flagName = FlagName "cuda"},
+                      MkPackageFlag
+                        {flagDefault = False,
+                         flagDescription = "only build with Double and Long support",
+                         flagManual = False,
+                         flagName = FlagName "lite"}],
+   gpdScannedVersion = Nothing,
+   packageDescription = PackageDescription
+                          {author = "Hasktorch dev team",
+                           benchmarks = [],
+                           bugReports = "https://github.com/hasktorch/hasktorch/issues",
+                           buildTypeRaw = Just Simple,
+                           category = "Tensors, Machine Learning, AI",
+                           copyright = "",
+                           customFieldsPD = [],
+                           dataDir = "",
+                           dataFiles = [],
+                           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).*",
+                           executables = [],
+                           extraDocFiles = [],
+                           extraSrcFiles = [],
+                           extraTmpFiles = [],
+                           foreignLibs = [],
+                           homepage = "https://github.com/hasktorch/hasktorch#readme",
+                           library = Nothing,
+                           licenseFiles = [],
+                           licenseRaw = Left
+                                          (License (ELicense (ELicenseId BSD_3_Clause) Nothing)),
+                           maintainer = "Sam Stites <fnz@fgvgrf.vb>, Austin Huang <nhfgvau@nyhz.zvg.rqh> - cipher:ROT13",
+                           package = PackageIdentifier
+                                       {pkgName = PackageName "hasktorch",
+                                        pkgVersion = mkVersion [0, 0, 1, 0]},
+                           pkgUrl = "",
+                           setupBuildInfo = Nothing,
+                           sourceRepos = [SourceRepo
+                                            {repoBranch = Nothing,
+                                             repoKind = RepoHead,
+                                             repoLocation = Just
+                                                              "https://github.com/hasktorch/hasktorch",
+                                             repoModule = Nothing,
+                                             repoSubdir = Nothing,
+                                             repoTag = Nothing,
+                                             repoType = Just (KnownRepoType Git)}],
+                           specVersion = CabalSpecV2_2,
+                           stability = "",
+                           subLibraries = [],
+                           synopsis = "Torch for tensors and neural networks in Haskell",
+                           testSuites = [],
+                           testedWith = []}}
diff --git a/Cabal/tests/ParserTests/regressions/hasktorch.format b/Cabal/tests/ParserTests/regressions/hasktorch.format
new file mode 100644
index 0000000000000000000000000000000000000000..93a81ddd29f20b2b28975ec792fb710ba12e72fe
--- /dev/null
+++ b/Cabal/tests/ParserTests/regressions/hasktorch.format
@@ -0,0 +1,565 @@
+cabal-version: 2.2
+name:          hasktorch
+version:       0.0.1.0
+license:       BSD-3-Clause
+maintainer:
+    Sam Stites <fnz@fgvgrf.vb>, Austin Huang <nhfgvau@nyhz.zvg.rqh> - cipher:ROT13
+
+author:        Hasktorch dev team
+homepage:      https://github.com/hasktorch/hasktorch#readme
+bug-reports:   https://github.com/hasktorch/hasktorch/issues
+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
+build-type:    Simple
+
+source-repository head
+    type:     git
+    location: https://github.com/hasktorch/hasktorch
+
+flag cuda
+    description: build with THC support
+    default:     False
+
+flag lite
+    description: only build with Double and Long support
+    default:     False
+
+library
+    exposed-modules:
+        Torch.Core.Exceptions
+        Torch.Core.Random
+        Torch.Core.LogAdd
+
+    reexported-modules:
+        Torch.Types.Numeric,
+        Torch.Long,
+        Torch.Long.Dynamic,
+        Torch.Long.Storage,
+        Torch.Double,
+        Torch.Double.Dynamic,
+        Torch.Double.Storage,
+        Torch.Double.NN,
+        Torch.Double.NN.Activation,
+        Torch.Double.NN.Backprop,
+        Torch.Double.NN.Conv1d,
+        Torch.Double.NN.Conv2d,
+        Torch.Double.NN.Criterion,
+        Torch.Double.NN.Layers,
+        Torch.Double.NN.Linear,
+        Torch.Double.NN.Math,
+        Torch.Double.NN.Padding,
+        Torch.Double.NN.Pooling,
+        Torch.Double.NN.Sampling,
+        Torch.Double.Dynamic.NN,
+        Torch.Double.Dynamic.NN.Activation,
+        Torch.Double.Dynamic.NN.Pooling,
+        Torch.Double.Dynamic.NN.Criterion
+
+    hs-source-dirs:     utils
+    default-language:   Haskell2010
+    default-extensions:
+        LambdaCase DataKinds TypeFamilies TypeSynonymInstances
+        ScopedTypeVariables FlexibleContexts CPP
+
+    build-depends:
+        base (==4.7 || >4.7) && <5,
+        dimensions ==1.0 || >1.0,
+        safe-exceptions ==0.1.0 || >0.1.0,
+        singletons ==2.2 || >2.2,
+        text ==1.2.2 || >1.2.2,
+        hasktorch-cpu,
+        hasktorch-ffi-th (==0.0.1 || >0.0.1) && <0.0.2,
+        hasktorch-types-th (==0.0.1 || >0.0.1) && <0.0.2
+
+    if !flag(lite)
+        reexported-modules:
+            Torch.Byte,
+            Torch.Byte.Dynamic,
+            Torch.Byte.Storage,
+            Torch.Char,
+            Torch.Char.Dynamic,
+            Torch.Char.Storage,
+            Torch.Short,
+            Torch.Short.Dynamic,
+            Torch.Short.Storage,
+            Torch.Int,
+            Torch.Int.Dynamic,
+            Torch.Int.Storage,
+            Torch.Float,
+            Torch.Float.Dynamic,
+            Torch.Float.Storage
+
+    if flag(cuda)
+        reexported-modules:
+            Torch.Cuda.Long,
+            Torch.Cuda.Long.Dynamic,
+            Torch.Cuda.Long.Storage,
+            Torch.Cuda.Double,
+            Torch.Cuda.Double.Dynamic,
+            Torch.Cuda.Double.Storage,
+            Torch.Cuda.Double.NN,
+            Torch.Cuda.Double.NN.Activation,
+            Torch.Cuda.Double.NN.Backprop,
+            Torch.Cuda.Double.NN.Conv1d,
+            Torch.Cuda.Double.NN.Conv2d,
+            Torch.Cuda.Double.NN.Criterion,
+            Torch.Cuda.Double.NN.Layers,
+            Torch.Cuda.Double.NN.Linear,
+            Torch.Cuda.Double.NN.Math,
+            Torch.Cuda.Double.NN.Padding,
+            Torch.Cuda.Double.NN.Pooling,
+            Torch.Cuda.Double.NN.Sampling,
+            Torch.Cuda.Double.Dynamic.NN,
+            Torch.Cuda.Double.Dynamic.NN.Activation,
+            Torch.Cuda.Double.Dynamic.NN.Pooling,
+            Torch.Cuda.Double.Dynamic.NN.Criterion
+
+        build-depends:      hasktorch-gpu
+
+        if !flag(lite)
+            reexported-modules:
+                Torch.Cuda.Byte,
+                Torch.Cuda.Byte.Dynamic,
+                Torch.Cuda.Byte.Storage,
+                Torch.Cuda.Char,
+                Torch.Cuda.Char.Dynamic,
+                Torch.Cuda.Char.Storage,
+                Torch.Cuda.Short,
+                Torch.Cuda.Short.Dynamic,
+                Torch.Cuda.Short.Storage,
+                Torch.Cuda.Int,
+                Torch.Cuda.Int.Dynamic,
+                Torch.Cuda.Int.Storage,
+                Torch.Cuda.Float,
+                Torch.Cuda.Float.Dynamic,
+                Torch.Cuda.Float.Storage
+
+library hasktorch-cpu
+    exposed-modules:
+        Torch.Long
+        Torch.Long.Dynamic
+        Torch.Long.Storage
+        Torch.Double
+        Torch.Double.Dynamic
+        Torch.Double.Storage
+
+    reexported-modules:
+        Torch.Double.NN,
+        Torch.Double.NN.Activation,
+        Torch.Double.NN.Backprop,
+        Torch.Double.NN.Conv1d,
+        Torch.Double.NN.Conv2d,
+        Torch.Double.NN.Criterion,
+        Torch.Double.NN.Layers,
+        Torch.Double.NN.Linear,
+        Torch.Double.NN.Math,
+        Torch.Double.NN.Padding,
+        Torch.Double.NN.Pooling,
+        Torch.Double.NN.Sampling,
+        Torch.Double.Dynamic.NN,
+        Torch.Double.Dynamic.NN.Activation,
+        Torch.Double.Dynamic.NN.Pooling,
+        Torch.Double.Dynamic.NN.Criterion,
+        Torch.Float.NN,
+        Torch.Float.NN.Activation,
+        Torch.Float.NN.Backprop,
+        Torch.Float.NN.Conv1d,
+        Torch.Float.NN.Conv2d,
+        Torch.Float.NN.Criterion,
+        Torch.Float.NN.Layers,
+        Torch.Float.NN.Linear,
+        Torch.Float.NN.Math,
+        Torch.Float.NN.Padding,
+        Torch.Float.NN.Pooling,
+        Torch.Float.NN.Sampling,
+        Torch.Float.Dynamic.NN,
+        Torch.Float.Dynamic.NN.Activation,
+        Torch.Float.Dynamic.NN.Pooling,
+        Torch.Float.Dynamic.NN.Criterion
+
+    hs-source-dirs:     utils src
+    other-modules:
+        Torch.Core.Exceptions
+        Torch.Core.Random
+        Torch.Core.LogAdd
+
+    default-language:   Haskell2010
+    default-extensions:
+        LambdaCase DataKinds TypeFamilies TypeSynonymInstances
+        ScopedTypeVariables FlexibleContexts CPP
+
+    build-depends:
+        base (==4.7 || >4.7) && <5,
+        hasktorch-types-th (==0.0.1 || >0.0.1) && <0.0.2,
+        dimensions ==1.0 || >1.0,
+        hasktorch-ffi-th (==0.0.1 || >0.0.1) && <0.0.2,
+        hasktorch-types-th (==0.0.1 || >0.0.1) && <0.0.2,
+        safe-exceptions ==0.1.0 || >0.1.0,
+        singletons ==2.2 || >2.2,
+        text ==1.2.2 || >1.2.2,
+        hasktorch-indef-floating,
+        hasktorch-indef-signed
+
+    mixins:
+        hasktorch-indef-signed (Torch.Indef.Storage as Torch.Indef.Long.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Long.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Long.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Long.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Long.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Long.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Long.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Long.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Long.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Long.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Long.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Long.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Long.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Long.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Long.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Long.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Long.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Long.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Long.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Long.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Long.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Long.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Long.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Long.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Long.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Long.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Long.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Long.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Long.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Long.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Long.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Long.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Long.Types, Torch.Indef.Index as Torch.Long.Index, Torch.Indef.Mask as Torch.Long.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Long.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Long.Dynamic.Tensor.Math.Pointwise.Signed) requires (Torch.Sig.Index.Tensor as Torch.FFI.TH.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.TH.Long.FreeTensor, Torch.Sig.Mask.Tensor as Torch.FFI.TH.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.TH.Byte.FreeTensor, Torch.Sig.Mask.MathReduce as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.State as Torch.Types.TH, Torch.Sig.Types.Global as Torch.Types.TH, Torch.Sig.Types as Torch.Types.TH.Long, Torch.Sig.Storage as Torch.FFI.TH.Long.Storage, Torch.Sig.Storage.Copy as Torch.FFI.TH.Long.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.TH.Long.FreeStorage, Torch.Sig.Tensor as Torch.FFI.TH.Long.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.TH.Long.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.TH.Long.FreeTensor, Torch.Sig.Tensor.Index as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Masked as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Math as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Math.Scan as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Mode as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.ScatterGather as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Sort as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.TopK as Torch.FFI.TH.Long.TensorMath, Torch.Sig.Tensor.Math.Pointwise.Signed as Torch.FFI.TH.Long.TensorMath),
+        hasktorch-indef-floating (Torch.Indef.Storage as Torch.Indef.Double.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Double.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Double.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Double.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Double.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Double.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Double.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Double.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Double.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Double.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Double.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Double.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Double.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Double.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Double.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Double.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Double.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Double.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Double.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Double.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Double.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Double.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Double.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Double.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Double.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Double.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Double.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Double.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Double.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Double.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Double.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Double.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Double.Types, Torch.Indef.Index as Torch.Double.Index, Torch.Indef.Mask as Torch.Double.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Double.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Double.Dynamic.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Blas as Torch.Indef.Double.Dynamic.Tensor.Math.Blas, Torch.Indef.Dynamic.Tensor.Math.Lapack as Torch.Indef.Double.Dynamic.Tensor.Math.Lapack, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Floating as Torch.Indef.Double.Dynamic.Tensor.Math.Pointwise.Floating, Torch.Indef.Dynamic.Tensor.Math.Reduce.Floating as Torch.Indef.Double.Dynamic.Tensor.Math.Reduce.Floating, Torch.Indef.Dynamic.Tensor.Math.Floating as Torch.Indef.Double.Dynamic.Tensor.Math.Floating, Torch.Indef.Static.Tensor.Math.Blas as Torch.Indef.Double.Tensor.Math.Blas, Torch.Indef.Static.Tensor.Math.Lapack as Torch.Indef.Double.Tensor.Math.Lapack, Torch.Indef.Static.Tensor.Math.Pointwise.Floating as Torch.Indef.Double.Tensor.Math.Pointwise.Floating, Torch.Indef.Static.Tensor.Math.Reduce.Floating as Torch.Indef.Double.Tensor.Math.Reduce.Floating, Torch.Indef.Static.Tensor.Math.Floating as Torch.Indef.Double.Tensor.Math.Floating, Torch.Indef.Static.Tensor.Random.TH as Torch.Indef.Double.Tensor.Random.TH, Torch.Indef.Static.Tensor.Math.Random.TH as Torch.Indef.Double.Tensor.Math.Random.TH, Torch.Indef.Dynamic.Tensor.Random.TH as Torch.Indef.Double.Dynamic.Tensor.Random.TH, Torch.Indef.Dynamic.Tensor.Math.Random.TH as Torch.Indef.Double.Dynamic.Tensor.Math.Random.TH, Torch.Undefined.Tensor.Random.THC as Torch.Undefined.Double.Tensor.Random.THC, Torch.Indef.Storage as Torch.Indef.Double.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Double.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Double.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Double.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Double.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Double.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Double.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Double.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Double.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Double.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Double.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Double.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Double.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Double.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Double.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Double.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Double.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Double.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Double.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Double.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Double.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Double.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Double.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Double.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Double.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Double.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Double.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Double.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Double.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Double.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Double.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Double.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Double.Types, Torch.Indef.Index as Torch.Double.Index, Torch.Indef.Mask as Torch.Double.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Double.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Double.Dynamic.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.NN as Torch.Double.Dynamic.NN, Torch.Indef.Dynamic.NN.Activation as Torch.Double.Dynamic.NN.Activation, Torch.Indef.Dynamic.NN.Pooling as Torch.Double.Dynamic.NN.Pooling, Torch.Indef.Dynamic.NN.Criterion as Torch.Double.Dynamic.NN.Criterion, Torch.Indef.Static.NN as Torch.Double.NN, Torch.Indef.Static.NN as Torch.Double.NN, Torch.Indef.Static.NN.Activation as Torch.Double.NN.Activation, Torch.Indef.Static.NN.Backprop as Torch.Double.NN.Backprop, Torch.Indef.Static.NN.Conv1d as Torch.Double.NN.Conv1d, Torch.Indef.Static.NN.Conv2d as Torch.Double.NN.Conv2d, Torch.Indef.Static.NN.Criterion as Torch.Double.NN.Criterion, Torch.Indef.Static.NN.Layers as Torch.Double.NN.Layers, Torch.Indef.Static.NN.Linear as Torch.Double.NN.Linear, Torch.Indef.Static.NN.Math as Torch.Double.NN.Math, Torch.Indef.Static.NN.Padding as Torch.Double.NN.Padding, Torch.Indef.Static.NN.Pooling as Torch.Double.NN.Pooling, Torch.Indef.Static.NN.Sampling as Torch.Double.NN.Sampling) requires (Torch.Sig.Index.Tensor as Torch.FFI.TH.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.TH.Long.FreeTensor, Torch.Sig.Mask.Tensor as Torch.FFI.TH.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.TH.Byte.FreeTensor, Torch.Sig.Mask.MathReduce as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.State as Torch.Types.TH, Torch.Sig.Types.Global as Torch.Types.TH, Torch.Sig.Types as Torch.Types.TH.Double, Torch.Sig.Storage as Torch.FFI.TH.Double.Storage, Torch.Sig.Storage.Copy as Torch.FFI.TH.Double.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.TH.Double.FreeStorage, Torch.Sig.Tensor as Torch.FFI.TH.Double.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.TH.Double.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.TH.Double.FreeTensor, Torch.Sig.Tensor.Index as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Masked as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Scan as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Mode as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.ScatterGather as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Sort as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.TopK as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Pointwise.Signed as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Pointwise.Floating as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Reduce.Floating as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Floating as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Blas as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Math.Lapack as Torch.FFI.TH.Double.TensorLapack, Torch.Sig.NN as Torch.FFI.TH.NN.Double, Torch.Sig.Types.NN as Torch.Types.TH, Torch.Sig.Tensor.Math.Random.TH as Torch.FFI.TH.Double.TensorMath, Torch.Sig.Tensor.Random.TH as Torch.FFI.TH.Double.TensorRandom, Torch.Sig.Tensor.Random.THC as Torch.Undefined.Double.Tensor.Random.THC)
+
+    if flag(lite)
+
+    else
+        exposed-modules:
+            Torch.Byte
+            Torch.Byte.Dynamic
+            Torch.Byte.Storage
+            Torch.Char
+            Torch.Char.Dynamic
+            Torch.Char.Storage
+            Torch.Short
+            Torch.Short.Dynamic
+            Torch.Short.Storage
+            Torch.Int
+            Torch.Int.Dynamic
+            Torch.Int.Storage
+            Torch.Float
+            Torch.Float.Dynamic
+            Torch.Float.Storage
+
+        build-depends:   hasktorch-indef-unsigned
+        mixins:
+            hasktorch-indef-unsigned (Torch.Indef.Storage as Torch.Indef.Byte.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Byte.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Byte.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Byte.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Byte.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Byte.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Byte.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Byte.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Byte.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Byte.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Byte.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Byte.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Byte.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Byte.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Byte.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Byte.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Byte.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Byte.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Byte.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Byte.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Byte.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Byte.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Byte.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Byte.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Byte.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Byte.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Byte.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Byte.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Byte.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Byte.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Byte.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Byte.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Byte.Types, Torch.Indef.Index as Torch.Byte.Index, Torch.Indef.Mask as Torch.Byte.Mask) requires (Torch.Sig.Index.Tensor as Torch.FFI.TH.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.TH.Long.FreeTensor, Torch.Sig.Mask.Tensor as Torch.FFI.TH.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.TH.Byte.FreeTensor, Torch.Sig.Mask.MathReduce as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.State as Torch.Types.TH, Torch.Sig.Types.Global as Torch.Types.TH, Torch.Sig.Types as Torch.Types.TH.Byte, Torch.Sig.Storage as Torch.FFI.TH.Byte.Storage, Torch.Sig.Storage.Copy as Torch.FFI.TH.Byte.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.TH.Byte.FreeStorage, Torch.Sig.Tensor as Torch.FFI.TH.Byte.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.TH.Byte.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.TH.Byte.FreeTensor, Torch.Sig.Tensor.Index as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.Masked as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.Math as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.Math.Scan as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.Mode as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.ScatterGather as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.Sort as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.Tensor.TopK as Torch.FFI.TH.Byte.TensorMath),
+            hasktorch-indef-unsigned (Torch.Indef.Storage as Torch.Indef.Char.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Char.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Char.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Char.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Char.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Char.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Char.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Char.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Char.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Char.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Char.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Char.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Char.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Char.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Char.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Char.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Char.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Char.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Char.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Char.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Char.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Char.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Char.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Char.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Char.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Char.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Char.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Char.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Char.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Char.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Char.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Char.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Char.Types, Torch.Indef.Index as Torch.Char.Index, Torch.Indef.Mask as Torch.Char.Mask) requires (Torch.Sig.Index.Tensor as Torch.FFI.TH.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.TH.Long.FreeTensor, Torch.Sig.Mask.Tensor as Torch.FFI.TH.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.TH.Byte.FreeTensor, Torch.Sig.Mask.MathReduce as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.State as Torch.Types.TH, Torch.Sig.Types.Global as Torch.Types.TH, Torch.Sig.Types as Torch.Types.TH.Char, Torch.Sig.Storage as Torch.FFI.TH.Char.Storage, Torch.Sig.Storage.Copy as Torch.FFI.TH.Char.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.TH.Char.FreeStorage, Torch.Sig.Tensor as Torch.FFI.TH.Char.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.TH.Char.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.TH.Char.FreeTensor, Torch.Sig.Tensor.Index as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.Masked as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.Math as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.Math.Scan as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.Mode as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.ScatterGather as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.Sort as Torch.FFI.TH.Char.TensorMath, Torch.Sig.Tensor.TopK as Torch.FFI.TH.Char.TensorMath),
+            hasktorch-indef-signed (Torch.Indef.Storage as Torch.Indef.Short.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Short.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Short.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Short.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Short.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Short.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Short.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Short.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Short.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Short.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Short.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Short.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Short.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Short.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Short.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Short.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Short.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Short.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Short.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Short.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Short.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Short.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Short.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Short.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Short.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Short.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Short.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Short.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Short.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Short.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Short.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Short.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Short.Types, Torch.Indef.Index as Torch.Short.Index, Torch.Indef.Mask as Torch.Short.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Short.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Short.Dynamic.Tensor.Math.Pointwise.Signed) requires (Torch.Sig.Index.Tensor as Torch.FFI.TH.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.TH.Long.FreeTensor, Torch.Sig.Mask.Tensor as Torch.FFI.TH.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.TH.Byte.FreeTensor, Torch.Sig.Mask.MathReduce as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.State as Torch.Types.TH, Torch.Sig.Types.Global as Torch.Types.TH, Torch.Sig.Types as Torch.Types.TH.Short, Torch.Sig.Storage as Torch.FFI.TH.Short.Storage, Torch.Sig.Storage.Copy as Torch.FFI.TH.Short.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.TH.Short.FreeStorage, Torch.Sig.Tensor as Torch.FFI.TH.Short.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.TH.Short.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.TH.Short.FreeTensor, Torch.Sig.Tensor.Index as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Masked as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Math as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Math.Scan as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Mode as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.ScatterGather as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Sort as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.TopK as Torch.FFI.TH.Short.TensorMath, Torch.Sig.Tensor.Math.Pointwise.Signed as Torch.FFI.TH.Short.TensorMath),
+            hasktorch-indef-signed (Torch.Indef.Storage as Torch.Indef.Int.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Int.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Int.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Int.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Int.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Int.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Int.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Int.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Int.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Int.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Int.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Int.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Int.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Int.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Int.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Int.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Int.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Int.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Int.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Int.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Int.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Int.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Int.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Int.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Int.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Int.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Int.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Int.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Int.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Int.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Int.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Int.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Int.Types, Torch.Indef.Index as Torch.Int.Index, Torch.Indef.Mask as Torch.Int.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Int.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Int.Dynamic.Tensor.Math.Pointwise.Signed) requires (Torch.Sig.Index.Tensor as Torch.FFI.TH.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.TH.Long.FreeTensor, Torch.Sig.Mask.Tensor as Torch.FFI.TH.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.TH.Byte.FreeTensor, Torch.Sig.Mask.MathReduce as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.State as Torch.Types.TH, Torch.Sig.Types.Global as Torch.Types.TH, Torch.Sig.Types as Torch.Types.TH.Int, Torch.Sig.Storage as Torch.FFI.TH.Int.Storage, Torch.Sig.Storage.Copy as Torch.FFI.TH.Int.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.TH.Int.FreeStorage, Torch.Sig.Tensor as Torch.FFI.TH.Int.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.TH.Int.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.TH.Int.FreeTensor, Torch.Sig.Tensor.Index as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Masked as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Math as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Math.Scan as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Mode as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.ScatterGather as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Sort as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.TopK as Torch.FFI.TH.Int.TensorMath, Torch.Sig.Tensor.Math.Pointwise.Signed as Torch.FFI.TH.Int.TensorMath),
+            hasktorch-indef-floating (Torch.Indef.Storage as Torch.Indef.Float.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Float.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Float.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Float.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Float.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Float.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Float.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Float.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Float.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Float.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Float.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Float.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Float.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Float.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Float.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Float.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Float.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Float.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Float.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Float.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Float.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Float.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Float.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Float.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Float.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Float.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Float.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Float.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Float.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Float.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Float.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Float.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Float.Types, Torch.Indef.Index as Torch.Float.Index, Torch.Indef.Mask as Torch.Float.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Float.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Float.Dynamic.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Blas as Torch.Indef.Float.Dynamic.Tensor.Math.Blas, Torch.Indef.Dynamic.Tensor.Math.Lapack as Torch.Indef.Float.Dynamic.Tensor.Math.Lapack, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Floating as Torch.Indef.Float.Dynamic.Tensor.Math.Pointwise.Floating, Torch.Indef.Dynamic.Tensor.Math.Reduce.Floating as Torch.Indef.Float.Dynamic.Tensor.Math.Reduce.Floating, Torch.Indef.Dynamic.Tensor.Math.Floating as Torch.Indef.Float.Dynamic.Tensor.Math.Floating, Torch.Indef.Static.Tensor.Math.Blas as Torch.Indef.Float.Tensor.Math.Blas, Torch.Indef.Static.Tensor.Math.Lapack as Torch.Indef.Float.Tensor.Math.Lapack, Torch.Indef.Static.Tensor.Math.Pointwise.Floating as Torch.Indef.Float.Tensor.Math.Pointwise.Floating, Torch.Indef.Static.Tensor.Math.Reduce.Floating as Torch.Indef.Float.Tensor.Math.Reduce.Floating, Torch.Indef.Static.Tensor.Math.Floating as Torch.Indef.Float.Tensor.Math.Floating, Torch.Indef.Static.Tensor.Random.TH as Torch.Indef.Float.Tensor.Random.TH, Torch.Indef.Static.Tensor.Math.Random.TH as Torch.Indef.Float.Tensor.Math.Random.TH, Torch.Indef.Dynamic.Tensor.Random.TH as Torch.Indef.Float.Dynamic.Tensor.Random.TH, Torch.Indef.Dynamic.Tensor.Math.Random.TH as Torch.Indef.Float.Dynamic.Tensor.Math.Random.TH, Torch.Undefined.Tensor.Random.THC as Torch.Undefined.Float.Tensor.Random.THC, Torch.Indef.Storage as Torch.Indef.Float.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Float.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Float.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Float.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Float.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Float.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Float.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Float.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Float.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Float.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Float.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Float.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Float.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Float.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Float.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Float.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Float.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Float.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Float.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Float.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Float.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Float.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Float.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Float.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Float.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Float.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Float.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Float.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Float.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Float.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Float.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Float.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Float.Types, Torch.Indef.Index as Torch.Float.Index, Torch.Indef.Mask as Torch.Float.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Float.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Float.Dynamic.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.NN as Torch.Float.Dynamic.NN, Torch.Indef.Dynamic.NN.Activation as Torch.Float.Dynamic.NN.Activation, Torch.Indef.Dynamic.NN.Pooling as Torch.Float.Dynamic.NN.Pooling, Torch.Indef.Dynamic.NN.Criterion as Torch.Float.Dynamic.NN.Criterion, Torch.Indef.Static.NN as Torch.Float.NN, Torch.Indef.Static.NN as Torch.Float.NN, Torch.Indef.Static.NN.Activation as Torch.Float.NN.Activation, Torch.Indef.Static.NN.Backprop as Torch.Float.NN.Backprop, Torch.Indef.Static.NN.Conv1d as Torch.Float.NN.Conv1d, Torch.Indef.Static.NN.Conv2d as Torch.Float.NN.Conv2d, Torch.Indef.Static.NN.Criterion as Torch.Float.NN.Criterion, Torch.Indef.Static.NN.Layers as Torch.Float.NN.Layers, Torch.Indef.Static.NN.Linear as Torch.Float.NN.Linear, Torch.Indef.Static.NN.Math as Torch.Float.NN.Math, Torch.Indef.Static.NN.Padding as Torch.Float.NN.Padding, Torch.Indef.Static.NN.Pooling as Torch.Float.NN.Pooling, Torch.Indef.Static.NN.Sampling as Torch.Float.NN.Sampling) requires (Torch.Sig.Index.Tensor as Torch.FFI.TH.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.TH.Long.FreeTensor, Torch.Sig.Mask.Tensor as Torch.FFI.TH.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.TH.Byte.FreeTensor, Torch.Sig.Mask.MathReduce as Torch.FFI.TH.Byte.TensorMath, Torch.Sig.State as Torch.Types.TH, Torch.Sig.Types.Global as Torch.Types.TH, Torch.Sig.Types as Torch.Types.TH.Float, Torch.Sig.Storage as Torch.FFI.TH.Float.Storage, Torch.Sig.Storage.Copy as Torch.FFI.TH.Float.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.TH.Float.FreeStorage, Torch.Sig.Tensor as Torch.FFI.TH.Float.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.TH.Float.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.TH.Float.FreeTensor, Torch.Sig.Tensor.Index as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Masked as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Scan as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Mode as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.ScatterGather as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Sort as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.TopK as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Pointwise.Signed as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Pointwise.Floating as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Reduce.Floating as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Floating as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Blas as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Math.Lapack as Torch.FFI.TH.Float.TensorLapack, Torch.Sig.NN as Torch.FFI.TH.NN.Float, Torch.Sig.Types.NN as Torch.Types.TH, Torch.Sig.Tensor.Math.Random.TH as Torch.FFI.TH.Float.TensorMath, Torch.Sig.Tensor.Random.TH as Torch.FFI.TH.Float.TensorRandom, Torch.Sig.Tensor.Random.THC as Torch.Undefined.Float.Tensor.Random.THC)
+
+library hasktorch-gpu
+    exposed-modules:
+        Torch.Cuda.Long
+        Torch.Cuda.Long.Dynamic
+        Torch.Cuda.Long.Storage
+        Torch.Cuda.Double
+        Torch.Cuda.Double.Dynamic
+        Torch.Cuda.Double.Storage
+
+    reexported-modules:
+        Torch.Cuda.Double.NN,
+        Torch.Cuda.Double.NN.Activation,
+        Torch.Cuda.Double.NN.Backprop,
+        Torch.Cuda.Double.NN.Conv1d,
+        Torch.Cuda.Double.NN.Conv2d,
+        Torch.Cuda.Double.NN.Criterion,
+        Torch.Cuda.Double.NN.Layers,
+        Torch.Cuda.Double.NN.Linear,
+        Torch.Cuda.Double.NN.Math,
+        Torch.Cuda.Double.NN.Padding,
+        Torch.Cuda.Double.NN.Pooling,
+        Torch.Cuda.Double.NN.Sampling,
+        Torch.Cuda.Double.Dynamic.NN,
+        Torch.Cuda.Double.Dynamic.NN.Activation,
+        Torch.Cuda.Double.Dynamic.NN.Pooling,
+        Torch.Cuda.Double.Dynamic.NN.Criterion
+
+    cpp-options:        -DCUDA -DHASKTORCH_INTERNAL_CUDA
+    hs-source-dirs:     utils src
+    other-modules:
+        Torch.Core.Exceptions
+        Torch.Core.Random
+        Torch.Core.LogAdd
+
+    default-language:   Haskell2010
+    default-extensions:
+        LambdaCase DataKinds TypeFamilies TypeSynonymInstances
+        ScopedTypeVariables FlexibleContexts CPP
+
+    build-depends:
+        base (==4.7 || >4.7) && <5,
+        hasktorch-types-th (==0.0.1 || >0.0.1) && <0.0.2,
+        dimensions ==1.0 || >1.0,
+        hasktorch-ffi-th (==0.0.1 || >0.0.1) && <0.0.2,
+        hasktorch-types-th (==0.0.1 || >0.0.1) && <0.0.2,
+        safe-exceptions ==0.1.0 || >0.1.0,
+        singletons ==2.2 || >2.2,
+        text ==1.2.2 || >1.2.2,
+        hasktorch-indef-floating,
+        hasktorch-indef-signed,
+        hasktorch-ffi-thc (==0.0.1 || >0.0.1) && <0.0.2,
+        hasktorch-types-thc (==0.0.1 || >0.0.1) && <0.0.2
+
+    mixins:
+        hasktorch-indef-signed (Torch.Indef.Storage as Torch.Indef.Cuda.Long.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Cuda.Long.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Cuda.Long.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Cuda.Long.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Cuda.Long.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Cuda.Long.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Cuda.Long.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Cuda.Long.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Cuda.Long.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Cuda.Long.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Cuda.Long.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Cuda.Long.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Cuda.Long.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Cuda.Long.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Cuda.Long.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Cuda.Long.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Cuda.Long.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Cuda.Long.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Cuda.Long.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Cuda.Long.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Cuda.Long.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Cuda.Long.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Cuda.Long.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Cuda.Long.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Cuda.Long.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Cuda.Long.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Cuda.Long.Types, Torch.Indef.Index as Torch.Cuda.Long.Index, Torch.Indef.Mask as Torch.Cuda.Long.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Cuda.Long.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Cuda.Long.Dynamic.Tensor.Math.Pointwise.Signed) requires (Torch.Sig.Index.Tensor as Torch.FFI.THC.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.THC.Long.Tensor, Torch.Sig.Mask.Tensor as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.MathReduce as Torch.FFI.THC.Byte.TensorMathReduce, Torch.Sig.State as Torch.FFI.THC.State, Torch.Sig.Types.Global as Torch.Types.THC, Torch.Sig.Types as Torch.Types.THC.Long, Torch.Sig.Storage as Torch.FFI.THC.Long.Storage, Torch.Sig.Storage.Copy as Torch.FFI.THC.Long.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.THC.Long.Storage, Torch.Sig.Tensor as Torch.FFI.THC.Long.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.THC.Long.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.THC.Long.Tensor, Torch.Sig.Tensor.Index as Torch.FFI.THC.Long.TensorIndex, Torch.Sig.Tensor.Masked as Torch.FFI.THC.Long.TensorMasked, Torch.Sig.Tensor.Math as Torch.FFI.THC.Long.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.THC.Long.TensorMathCompare, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.THC.Long.TensorMathCompareT, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.THC.Long.TensorMathPairwise, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.THC.Long.TensorMathPointwise, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.THC.Long.TensorMathReduce, Torch.Sig.Tensor.Math.Scan as Torch.FFI.THC.Long.TensorMathScan, Torch.Sig.Tensor.Mode as Torch.FFI.THC.Long.TensorMode, Torch.Sig.Tensor.ScatterGather as Torch.FFI.THC.Long.TensorScatterGather, Torch.Sig.Tensor.Sort as Torch.FFI.THC.Long.TensorSort, Torch.Sig.Tensor.TopK as Torch.FFI.THC.Long.TensorTopK, Torch.Sig.Tensor.Math.Pointwise.Signed as Torch.FFI.THC.Long.TensorMathPointwise),
+        hasktorch-indef-floating (Torch.Indef.Storage as Torch.Indef.Cuda.Double.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Cuda.Double.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Cuda.Double.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Cuda.Double.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Cuda.Double.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Cuda.Double.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Cuda.Double.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Cuda.Double.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Cuda.Double.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Cuda.Double.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Cuda.Double.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Cuda.Double.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Cuda.Double.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Cuda.Double.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Cuda.Double.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Cuda.Double.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Cuda.Double.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Cuda.Double.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Cuda.Double.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Cuda.Double.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Cuda.Double.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Cuda.Double.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Cuda.Double.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Cuda.Double.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Cuda.Double.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Cuda.Double.Types, Torch.Indef.Index as Torch.Cuda.Double.Index, Torch.Indef.Mask as Torch.Cuda.Double.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Cuda.Double.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Blas as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Blas, Torch.Indef.Dynamic.Tensor.Math.Lapack as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Lapack, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Floating as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pointwise.Floating, Torch.Indef.Dynamic.Tensor.Math.Reduce.Floating as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Reduce.Floating, Torch.Indef.Dynamic.Tensor.Math.Floating as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Floating, Torch.Indef.Static.Tensor.Math.Blas as Torch.Indef.Cuda.Double.Tensor.Math.Blas, Torch.Indef.Static.Tensor.Math.Lapack as Torch.Indef.Cuda.Double.Tensor.Math.Lapack, Torch.Indef.Static.Tensor.Math.Pointwise.Floating as Torch.Indef.Cuda.Double.Tensor.Math.Pointwise.Floating, Torch.Indef.Static.Tensor.Math.Reduce.Floating as Torch.Indef.Cuda.Double.Tensor.Math.Reduce.Floating, Torch.Indef.Static.Tensor.Math.Floating as Torch.Indef.Cuda.Double.Tensor.Math.Floating, Torch.Undefined.Tensor.Random.TH as Torch.Undefined.Cuda.Double.Tensor.Random.TH, Torch.Undefined.Tensor.Math.Random.TH as Torch.Undefined.Cuda.Double.Tensor.Math.Random.TH, Torch.Indef.Static.Tensor.Random.THC as Torch.Indef.Cuda.Double.Tensor.Random.THC, Torch.Indef.Dynamic.Tensor.Random.THC as Torch.Indef.Cuda.Double.Dynamic.Tensor.Random.THC, Torch.Indef.Storage as Torch.Indef.Cuda.Double.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Cuda.Double.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Cuda.Double.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Cuda.Double.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Cuda.Double.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Cuda.Double.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Cuda.Double.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Cuda.Double.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Cuda.Double.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Cuda.Double.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Cuda.Double.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Cuda.Double.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Cuda.Double.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Cuda.Double.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Cuda.Double.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Cuda.Double.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Cuda.Double.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Cuda.Double.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Cuda.Double.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Cuda.Double.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Cuda.Double.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Cuda.Double.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Cuda.Double.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Cuda.Double.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Cuda.Double.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Cuda.Double.Types, Torch.Indef.Index as Torch.Cuda.Double.Index, Torch.Indef.Mask as Torch.Cuda.Double.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Cuda.Double.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Cuda.Double.Dynamic.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.NN as Torch.Cuda.Double.Dynamic.NN, Torch.Indef.Dynamic.NN.Activation as Torch.Cuda.Double.Dynamic.NN.Activation, Torch.Indef.Dynamic.NN.Pooling as Torch.Cuda.Double.Dynamic.NN.Pooling, Torch.Indef.Dynamic.NN.Criterion as Torch.Cuda.Double.Dynamic.NN.Criterion, Torch.Indef.Static.NN as Torch.Cuda.Double.NN, Torch.Indef.Static.NN as Torch.Cuda.Double.NN, Torch.Indef.Static.NN.Activation as Torch.Cuda.Double.NN.Activation, Torch.Indef.Static.NN.Backprop as Torch.Cuda.Double.NN.Backprop, Torch.Indef.Static.NN.Conv1d as Torch.Cuda.Double.NN.Conv1d, Torch.Indef.Static.NN.Conv2d as Torch.Cuda.Double.NN.Conv2d, Torch.Indef.Static.NN.Criterion as Torch.Cuda.Double.NN.Criterion, Torch.Indef.Static.NN.Layers as Torch.Cuda.Double.NN.Layers, Torch.Indef.Static.NN.Linear as Torch.Cuda.Double.NN.Linear, Torch.Indef.Static.NN.Math as Torch.Cuda.Double.NN.Math, Torch.Indef.Static.NN.Padding as Torch.Cuda.Double.NN.Padding, Torch.Indef.Static.NN.Pooling as Torch.Cuda.Double.NN.Pooling, Torch.Indef.Static.NN.Sampling as Torch.Cuda.Double.NN.Sampling) requires (Torch.Sig.Index.Tensor as Torch.FFI.THC.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.THC.Long.Tensor, Torch.Sig.Mask.Tensor as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.MathReduce as Torch.FFI.THC.Byte.TensorMathReduce, Torch.Sig.State as Torch.FFI.THC.State, Torch.Sig.Types.Global as Torch.Types.THC, Torch.Sig.Types as Torch.Types.THC.Double, Torch.Sig.Storage as Torch.FFI.THC.Double.Storage, Torch.Sig.Storage.Copy as Torch.FFI.THC.Double.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.THC.Double.Storage, Torch.Sig.Tensor as Torch.FFI.THC.Double.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.THC.Double.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.THC.Double.Tensor, Torch.Sig.Tensor.Index as Torch.FFI.THC.Double.TensorIndex, Torch.Sig.Tensor.Masked as Torch.FFI.THC.Double.TensorMasked, Torch.Sig.Tensor.Math as Torch.FFI.THC.Double.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.THC.Double.TensorMathCompare, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.THC.Double.TensorMathCompareT, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.THC.Double.TensorMathPairwise, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.THC.Double.TensorMathPointwise, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.THC.Double.TensorMathReduce, Torch.Sig.Tensor.Math.Scan as Torch.FFI.THC.Double.TensorMathScan, Torch.Sig.Tensor.Mode as Torch.FFI.THC.Double.TensorMode, Torch.Sig.Tensor.ScatterGather as Torch.FFI.THC.Double.TensorScatterGather, Torch.Sig.Tensor.Sort as Torch.FFI.THC.Double.TensorSort, Torch.Sig.Tensor.TopK as Torch.FFI.THC.Double.TensorTopK, Torch.Sig.Tensor.Math.Pointwise.Signed as Torch.FFI.THC.Double.TensorMathPointwise, Torch.Sig.Tensor.Math.Pointwise.Floating as Torch.FFI.THC.Double.TensorMathPointwise, Torch.Sig.Tensor.Math.Reduce.Floating as Torch.FFI.THC.Double.TensorMathReduce, Torch.Sig.Tensor.Math.Floating as Torch.FFI.THC.Double.TensorMath, Torch.Sig.Tensor.Math.Blas as Torch.FFI.THC.Double.TensorMathBlas, Torch.Sig.Tensor.Math.Lapack as Torch.FFI.THC.Double.TensorMathMagma, Torch.Sig.NN as Torch.FFI.THC.NN.Double, Torch.Sig.Types.NN as Torch.Types.THC, Torch.Sig.Tensor.Math.Random.TH as Torch.Undefined.Cuda.Double.Tensor.Math.Random.TH, Torch.Sig.Tensor.Random.TH as Torch.Undefined.Cuda.Double.Tensor.Random.TH, Torch.Sig.Tensor.Random.THC as Torch.FFI.THC.Double.TensorRandom)
+
+    if flag(lite)
+
+    else
+        exposed-modules:
+            Torch.Cuda.Byte
+            Torch.Cuda.Byte.Dynamic
+            Torch.Cuda.Byte.Storage
+            Torch.Cuda.Char
+            Torch.Cuda.Char.Dynamic
+            Torch.Cuda.Char.Storage
+            Torch.Cuda.Short
+            Torch.Cuda.Short.Dynamic
+            Torch.Cuda.Short.Storage
+            Torch.Cuda.Int
+            Torch.Cuda.Int.Dynamic
+            Torch.Cuda.Int.Storage
+
+        build-depends:   hasktorch-indef-unsigned
+        mixins:
+            hasktorch-indef-unsigned (Torch.Indef.Storage as Torch.Indef.Cuda.Byte.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Cuda.Byte.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Cuda.Byte.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Cuda.Byte.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Cuda.Byte.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Cuda.Byte.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Cuda.Byte.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Cuda.Byte.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Cuda.Byte.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Cuda.Byte.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Cuda.Byte.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Cuda.Byte.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Cuda.Byte.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Cuda.Byte.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Cuda.Byte.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Cuda.Byte.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Cuda.Byte.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Cuda.Byte.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Cuda.Byte.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Cuda.Byte.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Cuda.Byte.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Cuda.Byte.Types, Torch.Indef.Index as Torch.Cuda.Byte.Index, Torch.Indef.Mask as Torch.Cuda.Byte.Mask) requires (Torch.Sig.Index.Tensor as Torch.FFI.THC.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.THC.Long.Tensor, Torch.Sig.Mask.Tensor as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.MathReduce as Torch.FFI.THC.Byte.TensorMathReduce, Torch.Sig.State as Torch.FFI.THC.State, Torch.Sig.Types.Global as Torch.Types.THC, Torch.Sig.Types as Torch.Types.THC.Byte, Torch.Sig.Storage as Torch.FFI.THC.Byte.Storage, Torch.Sig.Storage.Copy as Torch.FFI.THC.Byte.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.THC.Byte.Storage, Torch.Sig.Tensor as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.THC.Byte.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Tensor.Index as Torch.FFI.THC.Byte.TensorIndex, Torch.Sig.Tensor.Masked as Torch.FFI.THC.Byte.TensorMasked, Torch.Sig.Tensor.Math as Torch.FFI.THC.Byte.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.THC.Byte.TensorMathCompare, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.THC.Byte.TensorMathCompareT, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.THC.Byte.TensorMathPairwise, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.THC.Byte.TensorMathPointwise, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.THC.Byte.TensorMathReduce, Torch.Sig.Tensor.Math.Scan as Torch.FFI.THC.Byte.TensorMathScan, Torch.Sig.Tensor.Mode as Torch.FFI.THC.Byte.TensorMode, Torch.Sig.Tensor.ScatterGather as Torch.FFI.THC.Byte.TensorScatterGather, Torch.Sig.Tensor.Sort as Torch.FFI.THC.Byte.TensorSort, Torch.Sig.Tensor.TopK as Torch.FFI.THC.Byte.TensorTopK),
+            hasktorch-indef-unsigned (Torch.Indef.Storage as Torch.Indef.Cuda.Char.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Cuda.Char.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Cuda.Char.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Cuda.Char.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Cuda.Char.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Cuda.Char.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Cuda.Char.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Cuda.Char.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Cuda.Char.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Cuda.Char.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Cuda.Char.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Cuda.Char.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Cuda.Char.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Cuda.Char.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Cuda.Char.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Cuda.Char.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Cuda.Char.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Cuda.Char.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Cuda.Char.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Cuda.Char.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Cuda.Char.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Cuda.Char.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Cuda.Char.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Cuda.Char.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Cuda.Char.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Cuda.Char.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Cuda.Char.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Cuda.Char.Types, Torch.Indef.Index as Torch.Cuda.Char.Index, Torch.Indef.Mask as Torch.Cuda.Char.Mask) requires (Torch.Sig.Index.Tensor as Torch.FFI.THC.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.THC.Long.Tensor, Torch.Sig.Mask.Tensor as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.MathReduce as Torch.FFI.THC.Byte.TensorMathReduce, Torch.Sig.State as Torch.FFI.THC.State, Torch.Sig.Types.Global as Torch.Types.THC, Torch.Sig.Types as Torch.Types.THC.Char, Torch.Sig.Storage as Torch.FFI.THC.Char.Storage, Torch.Sig.Storage.Copy as Torch.FFI.THC.Char.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.THC.Char.Storage, Torch.Sig.Tensor as Torch.FFI.THC.Char.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.THC.Char.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.THC.Char.Tensor, Torch.Sig.Tensor.Index as Torch.FFI.THC.Char.TensorIndex, Torch.Sig.Tensor.Masked as Torch.FFI.THC.Char.TensorMasked, Torch.Sig.Tensor.Math as Torch.FFI.THC.Char.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.THC.Char.TensorMathCompare, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.THC.Char.TensorMathCompareT, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.THC.Char.TensorMathPairwise, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.THC.Char.TensorMathPointwise, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.THC.Char.TensorMathReduce, Torch.Sig.Tensor.Math.Scan as Torch.FFI.THC.Char.TensorMathScan, Torch.Sig.Tensor.Mode as Torch.FFI.THC.Char.TensorMode, Torch.Sig.Tensor.ScatterGather as Torch.FFI.THC.Char.TensorScatterGather, Torch.Sig.Tensor.Sort as Torch.FFI.THC.Char.TensorSort, Torch.Sig.Tensor.TopK as Torch.FFI.THC.Char.TensorTopK),
+            hasktorch-indef-signed (Torch.Indef.Storage as Torch.Indef.Cuda.Short.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Cuda.Short.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Cuda.Short.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Cuda.Short.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Cuda.Short.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Cuda.Short.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Cuda.Short.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Cuda.Short.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Cuda.Short.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Cuda.Short.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Cuda.Short.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Cuda.Short.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Cuda.Short.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Cuda.Short.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Cuda.Short.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Cuda.Short.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Cuda.Short.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Cuda.Short.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Cuda.Short.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Cuda.Short.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Cuda.Short.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Cuda.Short.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Cuda.Short.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Cuda.Short.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Cuda.Short.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Cuda.Short.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Cuda.Short.Types, Torch.Indef.Index as Torch.Cuda.Short.Index, Torch.Indef.Mask as Torch.Cuda.Short.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Cuda.Short.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Cuda.Short.Dynamic.Tensor.Math.Pointwise.Signed) requires (Torch.Sig.Index.Tensor as Torch.FFI.THC.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.THC.Long.Tensor, Torch.Sig.Mask.Tensor as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.MathReduce as Torch.FFI.THC.Byte.TensorMathReduce, Torch.Sig.State as Torch.FFI.THC.State, Torch.Sig.Types.Global as Torch.Types.THC, Torch.Sig.Types as Torch.Types.THC.Short, Torch.Sig.Storage as Torch.FFI.THC.Short.Storage, Torch.Sig.Storage.Copy as Torch.FFI.THC.Short.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.THC.Short.Storage, Torch.Sig.Tensor as Torch.FFI.THC.Short.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.THC.Short.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.THC.Short.Tensor, Torch.Sig.Tensor.Index as Torch.FFI.THC.Short.TensorIndex, Torch.Sig.Tensor.Masked as Torch.FFI.THC.Short.TensorMasked, Torch.Sig.Tensor.Math as Torch.FFI.THC.Short.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.THC.Short.TensorMathCompare, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.THC.Short.TensorMathCompareT, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.THC.Short.TensorMathPairwise, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.THC.Short.TensorMathPointwise, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.THC.Short.TensorMathReduce, Torch.Sig.Tensor.Math.Scan as Torch.FFI.THC.Short.TensorMathScan, Torch.Sig.Tensor.Mode as Torch.FFI.THC.Short.TensorMode, Torch.Sig.Tensor.ScatterGather as Torch.FFI.THC.Short.TensorScatterGather, Torch.Sig.Tensor.Sort as Torch.FFI.THC.Short.TensorSort, Torch.Sig.Tensor.TopK as Torch.FFI.THC.Short.TensorTopK, Torch.Sig.Tensor.Math.Pointwise.Signed as Torch.FFI.THC.Short.TensorMathPointwise),
+            hasktorch-indef-signed (Torch.Indef.Storage as Torch.Indef.Cuda.Int.Storage, Torch.Indef.Storage.Copy as Torch.Indef.Cuda.Int.Storage.Copy, Torch.Indef.Static.Tensor as Torch.Indef.Cuda.Int.Tensor, Torch.Indef.Static.Tensor.Copy as Torch.Indef.Cuda.Int.Tensor.Copy, Torch.Indef.Static.Tensor.Index as Torch.Indef.Cuda.Int.Tensor.Index, Torch.Indef.Static.Tensor.Masked as Torch.Indef.Cuda.Int.Tensor.Masked, Torch.Indef.Static.Tensor.Math as Torch.Indef.Cuda.Int.Tensor.Math, Torch.Indef.Static.Tensor.Math.Compare as Torch.Indef.Cuda.Int.Tensor.Math.Compare, Torch.Indef.Static.Tensor.Math.CompareT as Torch.Indef.Cuda.Int.Tensor.Math.CompareT, Torch.Indef.Static.Tensor.Math.Pairwise as Torch.Indef.Cuda.Int.Tensor.Math.Pairwise, Torch.Indef.Static.Tensor.Math.Pointwise as Torch.Indef.Cuda.Int.Tensor.Math.Pointwise, Torch.Indef.Static.Tensor.Math.Reduce as Torch.Indef.Cuda.Int.Tensor.Math.Reduce, Torch.Indef.Static.Tensor.Math.Scan as Torch.Indef.Cuda.Int.Tensor.Math.Scan, Torch.Indef.Static.Tensor.Mode as Torch.Indef.Cuda.Int.Tensor.Mode, Torch.Indef.Static.Tensor.ScatterGather as Torch.Indef.Cuda.Int.Tensor.ScatterGather, Torch.Indef.Static.Tensor.Sort as Torch.Indef.Cuda.Int.Tensor.Sort, Torch.Indef.Static.Tensor.TopK as Torch.Indef.Cuda.Int.Tensor.TopK, Torch.Indef.Dynamic.Tensor as Torch.Indef.Cuda.Int.Dynamic.Tensor, Torch.Indef.Dynamic.Tensor.Copy as Torch.Indef.Cuda.Int.Dynamic.Tensor.Copy, Torch.Indef.Dynamic.Tensor.Index as Torch.Indef.Cuda.Int.Dynamic.Tensor.Index, Torch.Indef.Dynamic.Tensor.Masked as Torch.Indef.Cuda.Int.Dynamic.Tensor.Masked, Torch.Indef.Dynamic.Tensor.Math as Torch.Indef.Cuda.Int.Dynamic.Tensor.Math, Torch.Indef.Dynamic.Tensor.Math.Compare as Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Compare, Torch.Indef.Dynamic.Tensor.Math.CompareT as Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.CompareT, Torch.Indef.Dynamic.Tensor.Math.Pairwise as Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Pairwise, Torch.Indef.Dynamic.Tensor.Math.Pointwise as Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Pointwise, Torch.Indef.Dynamic.Tensor.Math.Reduce as Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Reduce, Torch.Indef.Dynamic.Tensor.Math.Scan as Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Scan, Torch.Indef.Dynamic.Tensor.Mode as Torch.Indef.Cuda.Int.Dynamic.Tensor.Mode, Torch.Indef.Dynamic.Tensor.ScatterGather as Torch.Indef.Cuda.Int.Dynamic.Tensor.ScatterGather, Torch.Indef.Dynamic.Tensor.Sort as Torch.Indef.Cuda.Int.Dynamic.Tensor.Sort, Torch.Indef.Dynamic.Tensor.TopK as Torch.Indef.Cuda.Int.Dynamic.Tensor.TopK, Torch.Indef.Types as Torch.Cuda.Int.Types, Torch.Indef.Index as Torch.Cuda.Int.Index, Torch.Indef.Mask as Torch.Cuda.Int.Mask, Torch.Indef.Static.Tensor.Math.Pointwise.Signed as Torch.Indef.Cuda.Int.Tensor.Math.Pointwise.Signed, Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed as Torch.Indef.Cuda.Int.Dynamic.Tensor.Math.Pointwise.Signed) requires (Torch.Sig.Index.Tensor as Torch.FFI.THC.Long.Tensor, Torch.Sig.Index.TensorFree as Torch.FFI.THC.Long.Tensor, Torch.Sig.Mask.Tensor as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.TensorFree as Torch.FFI.THC.Byte.Tensor, Torch.Sig.Mask.MathReduce as Torch.FFI.THC.Byte.TensorMathReduce, Torch.Sig.State as Torch.FFI.THC.State, Torch.Sig.Types.Global as Torch.Types.THC, Torch.Sig.Types as Torch.Types.THC.Int, Torch.Sig.Storage as Torch.FFI.THC.Int.Storage, Torch.Sig.Storage.Copy as Torch.FFI.THC.Int.StorageCopy, Torch.Sig.Storage.Memory as Torch.FFI.THC.Int.Storage, Torch.Sig.Tensor as Torch.FFI.THC.Int.Tensor, Torch.Sig.Tensor.Copy as Torch.FFI.THC.Int.TensorCopy, Torch.Sig.Tensor.Memory as Torch.FFI.THC.Int.Tensor, Torch.Sig.Tensor.Index as Torch.FFI.THC.Int.TensorIndex, Torch.Sig.Tensor.Masked as Torch.FFI.THC.Int.TensorMasked, Torch.Sig.Tensor.Math as Torch.FFI.THC.Int.TensorMath, Torch.Sig.Tensor.Math.Compare as Torch.FFI.THC.Int.TensorMathCompare, Torch.Sig.Tensor.Math.CompareT as Torch.FFI.THC.Int.TensorMathCompareT, Torch.Sig.Tensor.Math.Pairwise as Torch.FFI.THC.Int.TensorMathPairwise, Torch.Sig.Tensor.Math.Pointwise as Torch.FFI.THC.Int.TensorMathPointwise, Torch.Sig.Tensor.Math.Reduce as Torch.FFI.THC.Int.TensorMathReduce, Torch.Sig.Tensor.Math.Scan as Torch.FFI.THC.Int.TensorMathScan, Torch.Sig.Tensor.Mode as Torch.FFI.THC.Int.TensorMode, Torch.Sig.Tensor.ScatterGather as Torch.FFI.THC.Int.TensorScatterGather, Torch.Sig.Tensor.Sort as Torch.FFI.THC.Int.TensorSort, Torch.Sig.Tensor.TopK as Torch.FFI.THC.Int.TensorTopK, Torch.Sig.Tensor.Math.Pointwise.Signed as Torch.FFI.THC.Int.TensorMathPointwise)
+
+library hasktorch-indef-unsigned
+    reexported-modules:
+        Torch.Indef.Index,
+        Torch.Indef.Mask,
+        Torch.Indef.Types,
+        Torch.Indef.Storage,
+        Torch.Indef.Storage.Copy,
+        Torch.Indef.Dynamic.Print,
+        Torch.Indef.Dynamic.Tensor,
+        Torch.Indef.Dynamic.Tensor.Copy,
+        Torch.Indef.Dynamic.Tensor.Index,
+        Torch.Indef.Dynamic.Tensor.Masked,
+        Torch.Indef.Dynamic.Tensor.Math,
+        Torch.Indef.Dynamic.Tensor.Math.Compare,
+        Torch.Indef.Dynamic.Tensor.Math.CompareT,
+        Torch.Indef.Dynamic.Tensor.Math.Pairwise,
+        Torch.Indef.Dynamic.Tensor.Math.Pointwise,
+        Torch.Indef.Dynamic.Tensor.Math.Reduce,
+        Torch.Indef.Dynamic.Tensor.Math.Scan,
+        Torch.Indef.Dynamic.Tensor.Mode,
+        Torch.Indef.Dynamic.Tensor.ScatterGather,
+        Torch.Indef.Dynamic.Tensor.Sort,
+        Torch.Indef.Dynamic.Tensor.TopK,
+        Torch.Indef.Static.Tensor,
+        Torch.Indef.Static.Tensor.Copy,
+        Torch.Indef.Static.Tensor.Index,
+        Torch.Indef.Static.Tensor.Masked,
+        Torch.Indef.Static.Tensor.Math,
+        Torch.Indef.Static.Tensor.Math.Compare,
+        Torch.Indef.Static.Tensor.Math.CompareT,
+        Torch.Indef.Static.Tensor.Math.Pairwise,
+        Torch.Indef.Static.Tensor.Math.Pointwise,
+        Torch.Indef.Static.Tensor.Math.Reduce,
+        Torch.Indef.Static.Tensor.Math.Scan,
+        Torch.Indef.Static.Tensor.Mode,
+        Torch.Indef.Static.Tensor.ScatterGather,
+        Torch.Indef.Static.Tensor.Sort,
+        Torch.Indef.Static.Tensor.TopK
+
+    default-language:   Haskell2010
+    build-depends:
+        base (==4.7 || >4.7) && <5,
+        hasktorch-signatures-partial (==0.0.1 || >0.0.1) && <0.0.2,
+        hasktorch-indef
+
+    mixins:
+        hasktorch-indef requires (Torch.Sig.NN as Torch.Undefined.NN, Torch.Sig.Types.NN as Torch.Undefined.Types.NN, Torch.Sig.Tensor.Math.Blas as Torch.Undefined.Tensor.Math.Blas, Torch.Sig.Tensor.Math.Floating as Torch.Undefined.Tensor.Math.Floating, Torch.Sig.Tensor.Math.Lapack as Torch.Undefined.Tensor.Math.Lapack, Torch.Sig.Tensor.Math.Pointwise.Signed as Torch.Undefined.Tensor.Math.Pointwise.Signed, Torch.Sig.Tensor.Math.Pointwise.Floating as Torch.Undefined.Tensor.Math.Pointwise.Floating, Torch.Sig.Tensor.Math.Reduce.Floating as Torch.Undefined.Tensor.Math.Reduce.Floating, Torch.Sig.Tensor.Math.Random.TH as Torch.Undefined.Tensor.Math.Random.TH, Torch.Sig.Tensor.Random.TH as Torch.Undefined.Tensor.Random.TH, Torch.Sig.Tensor.Random.THC as Torch.Undefined.Tensor.Random.THC)
+
+library hasktorch-indef-signed
+    reexported-modules:
+        Torch.Indef.Index,
+        Torch.Indef.Mask,
+        Torch.Indef.Types,
+        Torch.Indef.Storage,
+        Torch.Indef.Storage.Copy,
+        Torch.Indef.Dynamic.Print,
+        Torch.Indef.Dynamic.Tensor,
+        Torch.Indef.Dynamic.Tensor.Copy,
+        Torch.Indef.Dynamic.Tensor.Index,
+        Torch.Indef.Dynamic.Tensor.Masked,
+        Torch.Indef.Dynamic.Tensor.Math,
+        Torch.Indef.Dynamic.Tensor.Math.Compare,
+        Torch.Indef.Dynamic.Tensor.Math.CompareT,
+        Torch.Indef.Dynamic.Tensor.Math.Pairwise,
+        Torch.Indef.Dynamic.Tensor.Math.Pointwise,
+        Torch.Indef.Dynamic.Tensor.Math.Reduce,
+        Torch.Indef.Dynamic.Tensor.Math.Scan,
+        Torch.Indef.Dynamic.Tensor.Mode,
+        Torch.Indef.Dynamic.Tensor.ScatterGather,
+        Torch.Indef.Dynamic.Tensor.Sort,
+        Torch.Indef.Dynamic.Tensor.TopK,
+        Torch.Indef.Static.Tensor,
+        Torch.Indef.Static.Tensor.Copy,
+        Torch.Indef.Static.Tensor.Index,
+        Torch.Indef.Static.Tensor.Masked,
+        Torch.Indef.Static.Tensor.Math,
+        Torch.Indef.Static.Tensor.Math.Compare,
+        Torch.Indef.Static.Tensor.Math.CompareT,
+        Torch.Indef.Static.Tensor.Math.Pairwise,
+        Torch.Indef.Static.Tensor.Math.Pointwise,
+        Torch.Indef.Static.Tensor.Math.Reduce,
+        Torch.Indef.Static.Tensor.Math.Scan,
+        Torch.Indef.Static.Tensor.Mode,
+        Torch.Indef.Static.Tensor.ScatterGather,
+        Torch.Indef.Static.Tensor.Sort,
+        Torch.Indef.Static.Tensor.TopK,
+        Torch.Indef.Static.Tensor.Math.Pointwise.Signed,
+        Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed
+
+    default-language:   Haskell2010
+    build-depends:
+        base (==4.7 || >4.7) && <5,
+        hasktorch-signatures-partial (==0.0.1 || >0.0.1) && <0.0.2,
+        hasktorch-indef
+
+    mixins:
+        hasktorch-indef requires (Torch.Sig.NN as Torch.Undefined.NN, Torch.Sig.Types.NN as Torch.Undefined.Types.NN, Torch.Sig.Tensor.Math.Blas as Torch.Undefined.Tensor.Math.Blas, Torch.Sig.Tensor.Math.Floating as Torch.Undefined.Tensor.Math.Floating, Torch.Sig.Tensor.Math.Lapack as Torch.Undefined.Tensor.Math.Lapack, Torch.Sig.Tensor.Math.Pointwise.Floating as Torch.Undefined.Tensor.Math.Pointwise.Floating, Torch.Sig.Tensor.Math.Reduce.Floating as Torch.Undefined.Tensor.Math.Reduce.Floating, Torch.Sig.Tensor.Math.Random.TH as Torch.Undefined.Tensor.Math.Random.TH, Torch.Sig.Tensor.Random.TH as Torch.Undefined.Tensor.Random.TH, Torch.Sig.Tensor.Random.THC as Torch.Undefined.Tensor.Random.THC)
+
+library hasktorch-indef-floating
+    reexported-modules:
+        Torch.Indef.Index,
+        Torch.Indef.Mask,
+        Torch.Indef.Types,
+        Torch.Indef.Storage,
+        Torch.Indef.Storage.Copy,
+        Torch.Indef.Dynamic.Print,
+        Torch.Indef.Dynamic.Tensor,
+        Torch.Indef.Dynamic.Tensor.Copy,
+        Torch.Indef.Dynamic.Tensor.Index,
+        Torch.Indef.Dynamic.Tensor.Masked,
+        Torch.Indef.Dynamic.Tensor.Math,
+        Torch.Indef.Dynamic.Tensor.Math.Compare,
+        Torch.Indef.Dynamic.Tensor.Math.CompareT,
+        Torch.Indef.Dynamic.Tensor.Math.Pairwise,
+        Torch.Indef.Dynamic.Tensor.Math.Pointwise,
+        Torch.Indef.Dynamic.Tensor.Math.Reduce,
+        Torch.Indef.Dynamic.Tensor.Math.Scan,
+        Torch.Indef.Dynamic.Tensor.Mode,
+        Torch.Indef.Dynamic.Tensor.ScatterGather,
+        Torch.Indef.Dynamic.Tensor.Sort,
+        Torch.Indef.Dynamic.Tensor.TopK,
+        Torch.Indef.Static.Tensor,
+        Torch.Indef.Static.Tensor.Copy,
+        Torch.Indef.Static.Tensor.Index,
+        Torch.Indef.Static.Tensor.Masked,
+        Torch.Indef.Static.Tensor.Math,
+        Torch.Indef.Static.Tensor.Math.Compare,
+        Torch.Indef.Static.Tensor.Math.CompareT,
+        Torch.Indef.Static.Tensor.Math.Pairwise,
+        Torch.Indef.Static.Tensor.Math.Pointwise,
+        Torch.Indef.Static.Tensor.Math.Reduce,
+        Torch.Indef.Static.Tensor.Math.Scan,
+        Torch.Indef.Static.Tensor.Mode,
+        Torch.Indef.Static.Tensor.ScatterGather,
+        Torch.Indef.Static.Tensor.Sort,
+        Torch.Indef.Static.Tensor.TopK,
+        Torch.Indef.Static.Tensor.Math.Pointwise.Signed,
+        Torch.Indef.Dynamic.Tensor.Math.Pointwise.Signed,
+        Torch.Indef.Dynamic.Tensor.Math.Blas,
+        Torch.Indef.Dynamic.Tensor.Math.Floating,
+        Torch.Indef.Dynamic.Tensor.Math.Lapack,
+        Torch.Indef.Dynamic.Tensor.Math.Pointwise.Floating,
+        Torch.Indef.Dynamic.Tensor.Math.Reduce.Floating,
+        Torch.Indef.Dynamic.Tensor.Random.TH,
+        Torch.Indef.Dynamic.Tensor.Random.THC,
+        Torch.Indef.Dynamic.Tensor.Math.Random.TH,
+        Torch.Indef.Static.Tensor.Math.Blas,
+        Torch.Indef.Static.Tensor.Math.Floating,
+        Torch.Indef.Static.Tensor.Math.Lapack,
+        Torch.Indef.Static.Tensor.Math.Pointwise.Floating,
+        Torch.Indef.Static.Tensor.Math.Reduce.Floating,
+        Torch.Indef.Static.Tensor.Random.TH,
+        Torch.Indef.Static.Tensor.Random.THC,
+        Torch.Indef.Static.Tensor.Math.Random.TH,
+        Torch.Indef.Dynamic.NN,
+        Torch.Indef.Dynamic.NN.Activation,
+        Torch.Indef.Dynamic.NN.Pooling,
+        Torch.Indef.Dynamic.NN.Criterion,
+        Torch.Indef.Static.NN,
+        Torch.Indef.Static.NN.Activation,
+        Torch.Indef.Static.NN.Backprop,
+        Torch.Indef.Static.NN.Conv1d,
+        Torch.Indef.Static.NN.Conv2d,
+        Torch.Indef.Static.NN.Criterion,
+        Torch.Indef.Static.NN.Layers,
+        Torch.Indef.Static.NN.Linear,
+        Torch.Indef.Static.NN.Math,
+        Torch.Indef.Static.NN.Padding,
+        Torch.Indef.Static.NN.Pooling,
+        Torch.Indef.Static.NN.Sampling,
+        Torch.Undefined.Tensor.Math.Random.TH,
+        Torch.Undefined.Tensor.Random.TH,
+        Torch.Undefined.Tensor.Random.THC
+
+    default-language:   Haskell2010
+    build-depends:
+        base (==4.7 || >4.7) && <5,
+        hasktorch-indef,
+        hasktorch-signatures-partial (==0.0.1 || >0.0.1) && <0.0.2
+
+executable isdefinite-cpu
+    main-is:          Noop.hs
+    hs-source-dirs:   exe
+    default-language: Haskell2010
+    build-depends:
+        base (==4.7 || >4.7) && <5,
+        hasktorch-cpu
+
+executable isdefinite-gpu
+    main-is:          Noop.hs
+    hs-source-dirs:   exe
+    default-language: Haskell2010
+    build-depends:
+        base (==4.7 || >4.7) && <5,
+        hasktorch-gpu
+
+executable isdefinite
+    main-is:          Noop.hs
+    hs-source-dirs:   exe
+    default-language: Haskell2010
+    build-depends:
+        base (==4.7 || >4.7) && <5,
+        hasktorch
+
+executable memcheck
+    main-is:          Memcheck.hs
+    hs-source-dirs:   exe
+    default-language: Haskell2010
+    build-depends:
+        base (==4.7 || >4.7) && <5,
+        hasktorch
+
+test-suite spec
+    type:               exitcode-stdio-1.0
+    main-is:            Spec.hs
+    hs-source-dirs:     tests
+    other-modules:
+        Orphans
+        MemorySpec
+        RawLapackSVDSpec
+        GarbageCollectionSpec
+        Torch.Prelude.Extras
+        Torch.Core.LogAddSpec
+        Torch.Core.RandomSpec
+        Torch.Static.NN.AbsSpec
+        Torch.Static.NN.LinearSpec
+
+    default-language:   Haskell2010
+    default-extensions:
+        LambdaCase DataKinds TypeFamilies TypeSynonymInstances
+        ScopedTypeVariables FlexibleContexts CPP
+
+    build-depends:
+        QuickCheck ==2.11 || >2.11,
+        backprop ==0.2.5 || >0.2.5,
+        base (==4.7 || >4.7) && <5,
+        dimensions ==1.0 || >1.0,
+        ghc-typelits-natnormalise,
+        hasktorch,
+        hspec ==2.4.4 || >2.4.4,
+        singletons ==2.2 || >2.2,
+        mtl ==2.2.2 || >2.2.2,
+        microlens-platform ==0.3.10 || >0.3.10,
+        monad-loops ==0.4.3 || >0.4.3,
+        time ==1.8.0 || >1.8.0,
+        transformers ==0.5.5 || >0.5.5,
+        generic-lens
diff --git a/Cabal/tests/ParserTests/regressions/mixin-1.expr b/Cabal/tests/ParserTests/regressions/mixin-1.expr
index 9e350ff21732cf3f33a373ac062484ccf914e101..87beda6666024e7acbba6749d36c5695903d9db7 100644
--- a/Cabal/tests/ParserTests/regressions/mixin-1.expr
+++ b/Cabal/tests/ParserTests/regressions/mixin-1.expr
@@ -58,6 +58,7 @@ GenericPackageDescription
                                                                                                                             (ModuleName
                                                                                                                                "Str.String")],
                                                                                                    includeRequiresRn = DefaultRenaming},
+                                                                         mixinLibraryName = LMainLibName,
                                                                          mixinPackageName = PackageName
                                                                                               "str-string"},
                                                                       Mixin
@@ -69,6 +70,7 @@ GenericPackageDescription
                                                                                                                             (ModuleName
                                                                                                                                "Str.ByteString")],
                                                                                                    includeRequiresRn = DefaultRenaming},
+                                                                         mixinLibraryName = LMainLibName,
                                                                          mixinPackageName = PackageName
                                                                                               "str-bytestring"}],
                                                             oldExtensions = [],
diff --git a/Cabal/tests/ParserTests/regressions/mixin-2.expr b/Cabal/tests/ParserTests/regressions/mixin-2.expr
index afade09f0c71677f42aaba97e382ce5156ba627b..edf5b4b4ad032a2bb5c804c5486c0d089d6a87bf 100644
--- a/Cabal/tests/ParserTests/regressions/mixin-2.expr
+++ b/Cabal/tests/ParserTests/regressions/mixin-2.expr
@@ -58,6 +58,7 @@ GenericPackageDescription
                                                                                                                             (ModuleName
                                                                                                                                "Str.String")],
                                                                                                    includeRequiresRn = DefaultRenaming},
+                                                                         mixinLibraryName = LMainLibName,
                                                                          mixinPackageName = PackageName
                                                                                               "str-string"},
                                                                       Mixin
@@ -69,6 +70,7 @@ GenericPackageDescription
                                                                                                                             (ModuleName
                                                                                                                                "Str.ByteString")],
                                                                                                    includeRequiresRn = DefaultRenaming},
+                                                                         mixinLibraryName = LMainLibName,
                                                                          mixinPackageName = PackageName
                                                                                               "str-bytestring"}],
                                                             oldExtensions = [],
diff --git a/Cabal/tests/ParserTests/regressions/mixin-3.expr b/Cabal/tests/ParserTests/regressions/mixin-3.expr
index cb590f069a8e16637e3e2abda3937becbcd1272a..40625612d25a362a20f3d6a2145bc82707dc8e37 100644
--- a/Cabal/tests/ParserTests/regressions/mixin-3.expr
+++ b/Cabal/tests/ParserTests/regressions/mixin-3.expr
@@ -55,6 +55,7 @@ GenericPackageDescription
                                                                                                                          [ModuleName
                                                                                                                             "Foo"],
                                                                                                    includeRequiresRn = DefaultRenaming},
+                                                                         mixinLibraryName = LMainLibName,
                                                                          mixinPackageName = PackageName
                                                                                               "str"}],
                                                             oldExtensions = [],
diff --git a/Cabal/tests/UnitTests/Distribution/Utils/Structured.hs b/Cabal/tests/UnitTests/Distribution/Utils/Structured.hs
index 419d9203b71fa8b483ba7b4e6fad37b065f3e8da..0b658f42d96428144929f8e0f2d9e892a4dc26bc 100644
--- a/Cabal/tests/UnitTests/Distribution/Utils/Structured.hs
+++ b/Cabal/tests/UnitTests/Distribution/Utils/Structured.hs
@@ -24,7 +24,7 @@ tests = testGroup "Distribution.Utils.Structured"
     , testCase "SPDX.License"              $ structureHash (Proxy :: Proxy License)                    @?= md5FromInteger 0xd3d4a09f517f9f75bc3d16370d5a853a
     -- The difference is in encoding of newtypes
 #if MIN_VERSION_base(4,7,0)
-    , testCase "GenericPackageDescription" $ structureHash (Proxy :: Proxy GenericPackageDescription)  @?= md5FromInteger 0xf85c3579a0c9396821086624821832d8
-    , testCase "LocalBuildInfo"            $ structureHash (Proxy :: Proxy LocalBuildInfo)             @?= md5FromInteger 0xadb15a4ec2ab6f1c967683f9195c69ec
+    , testCase "GenericPackageDescription" $ structureHash (Proxy :: Proxy GenericPackageDescription)  @?= md5FromInteger 0xc3fd68379b7d09c2e3f751d10dde4fd6
+    , testCase "LocalBuildInfo"            $ structureHash (Proxy :: Proxy LocalBuildInfo)             @?= md5FromInteger 0xdafbf0d7fd7bf4dd63a8601c39475a8a
 #endif
     ]
diff --git a/cabal-testsuite/PackageTests/Backpack/Fail2/setup.cabal.out b/cabal-testsuite/PackageTests/Backpack/Fail2/setup.cabal.out
index b816c794a804028e4de305d5316a55da37f7cf88..e865213bc5603c16ff8ad36493676207fd426efe 100644
--- a/cabal-testsuite/PackageTests/Backpack/Fail2/setup.cabal.out
+++ b/cabal-testsuite/PackageTests/Backpack/Fail2/setup.cabal.out
@@ -1,5 +1,5 @@
 # Setup configure
 Configuring Fail2-0.1.0.0...
 Error:
-    Mix-in refers to non-existent package 'non-existent'
+    Mix-in refers to non-existent library 'non-existent'
     (did you forget to add the package to build-depends?)
diff --git a/cabal-testsuite/PackageTests/Backpack/Fail2/setup.out b/cabal-testsuite/PackageTests/Backpack/Fail2/setup.out
index b816c794a804028e4de305d5316a55da37f7cf88..e865213bc5603c16ff8ad36493676207fd426efe 100644
--- a/cabal-testsuite/PackageTests/Backpack/Fail2/setup.out
+++ b/cabal-testsuite/PackageTests/Backpack/Fail2/setup.out
@@ -1,5 +1,5 @@
 # Setup configure
 Configuring Fail2-0.1.0.0...
 Error:
-    Mix-in refers to non-existent package 'non-existent'
+    Mix-in refers to non-existent library 'non-existent'
     (did you forget to add the package to build-depends?)
diff --git a/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/cabal.out b/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/cabal.out
new file mode 100644
index 0000000000000000000000000000000000000000..e249741e23a0c50a93f4183bc693ef644412e846
--- /dev/null
+++ b/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/cabal.out
@@ -0,0 +1,16 @@
+# cabal v2-run
+Resolving dependencies...
+Build profile: -w ghc-<GHCVER> -O1
+In order, the following will be built:
+ - pkg-def-0.1.0.0 (lib) (first run)
+ - pkg-abc-0.1.0.0 (exe:program) (first run)
+Warning: pkg-def.cabal:13:27: visibility is experimental feature (issue #5660)
+Configuring library for pkg-def-0.1.0.0..
+Preprocessing library for pkg-def-0.1.0.0..
+Building library for pkg-def-0.1.0.0..
+Warning: pkg-abc.cabal:15:29: colon specifier is experimental feature (issue #5660)
+Warning: pkg-abc.cabal:20:15: colon specifier is experimental feature (issue #5660)
+Configuring executable 'program' for pkg-abc-0.1.0.0..
+Warning: The package has an extraneous version range for a dependency on an internal library: pkg-def >=0 && ==0.1.0.0. This version range includes the current package but isn't needed as the current package's library will always be used.
+Preprocessing executable 'program' for pkg-abc-0.1.0.0..
+Building executable 'program' for pkg-abc-0.1.0.0..
diff --git a/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/cabal.project b/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/cabal.project
new file mode 100644
index 0000000000000000000000000000000000000000..9b5dc06cd427bd3c3b83cb8974c4679d26382f80
--- /dev/null
+++ b/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/cabal.project
@@ -0,0 +1,4 @@
+packages:
+  pkg-abc
+  pkg-def
+
diff --git a/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/cabal.test.hs b/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/cabal.test.hs
new file mode 100644
index 0000000000000000000000000000000000000000..223349d5cf1747acdbcfe4e387725e80d68a1982
--- /dev/null
+++ b/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/cabal.test.hs
@@ -0,0 +1,6 @@
+import Test.Cabal.Prelude
+
+-- This is like T6083Pre, but also goes via mixins
+--
+main = cabalTest $
+    cabal' "v2-run" ["pkg-abc:program"] >>= assertOutputContains "pkg-def:pkg-def"
diff --git a/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/pkg-abc/exe/Main.hs b/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/pkg-abc/exe/Main.hs
new file mode 100644
index 0000000000000000000000000000000000000000..8e287385c6b8bff7dd0e7722c5c9221645a01ffa
--- /dev/null
+++ b/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/pkg-abc/exe/Main.hs
@@ -0,0 +1,5 @@
+module Main (main) where
+import Mixin (defValue)
+
+main :: IO ()
+main = print defValue
diff --git a/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/pkg-abc/pkg-abc.cabal b/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/pkg-abc/pkg-abc.cabal
new file mode 100644
index 0000000000000000000000000000000000000000..61f35d6084181a21435f31fd96a3587213238ca7
--- /dev/null
+++ b/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/pkg-abc/pkg-abc.cabal
@@ -0,0 +1,20 @@
+cabal-version: 3.4
+name:          pkg-abc
+version:       0.1.0.0
+
+library pkg-def
+  default-language: Haskell2010
+  hs-source-dirs:   pkg-def
+  build-depends:    base
+  exposed-modules:  PkgDef
+
+executable program
+  default-language: Haskell2010
+  hs-source-dirs:   exe
+  main-is:          Main.hs
+  mixins:           pkg-def:pkg-def (PkgDef as Mixin)
+
+  -- we want that to resolve to pkg-def main library.
+  build-depends:
+    , base
+    , pkg-def:pkg-def
diff --git a/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/pkg-abc/pkg-def/PkgDef.hs b/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/pkg-abc/pkg-def/PkgDef.hs
new file mode 100644
index 0000000000000000000000000000000000000000..4379d53caa4379d3fdcfc7d9451bb00a312f11fc
--- /dev/null
+++ b/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/pkg-abc/pkg-def/PkgDef.hs
@@ -0,0 +1,4 @@
+module PkgDef (defValue) where
+
+defValue :: String
+defValue = "pkg-abc:pkg-def"
diff --git a/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/pkg-def/pkg-def.cabal b/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/pkg-def/pkg-def.cabal
new file mode 100644
index 0000000000000000000000000000000000000000..a4d95cf4a01d1d7f87fa9455571a296c967d4bf7
--- /dev/null
+++ b/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/pkg-def/pkg-def.cabal
@@ -0,0 +1,17 @@
+cabal-version: 3.0
+name:          pkg-def
+version:       0.1.0.0
+
+library
+  default-language: Haskell2010
+  hs-source-dirs:   src
+  build-depends:    base
+  exposed-modules:  PkgDef
+
+library publib
+  default-language: Haskell2010
+  visibility:       public
+  hs-source-dirs:   publib
+  build-depends:    base
+  exposed-modules:  PkgDef
+
diff --git a/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/pkg-def/publib/PkgDef.hs b/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/pkg-def/publib/PkgDef.hs
new file mode 100644
index 0000000000000000000000000000000000000000..06ad039f434fe53a53b6f8a979c79738cf440a4e
--- /dev/null
+++ b/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/pkg-def/publib/PkgDef.hs
@@ -0,0 +1,4 @@
+module PkgDef (defValue) where
+
+defValue :: String
+defValue = "pkg-def:publib"
diff --git a/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/pkg-def/src/PkgDef.hs b/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/pkg-def/src/PkgDef.hs
new file mode 100644
index 0000000000000000000000000000000000000000..8c7d547cf70ddf8a03cc90f40b1ea0fd446befc3
--- /dev/null
+++ b/cabal-testsuite/PackageTests/MultipleLibraries/T6083PostMixin/pkg-def/src/PkgDef.hs
@@ -0,0 +1,4 @@
+module PkgDef (defValue) where
+
+defValue :: String
+defValue = "pkg-def:pkg-def"