diff --git a/Cabal-syntax/Cabal-syntax.cabal b/Cabal-syntax/Cabal-syntax.cabal index 85137dc147c..b438f5d7e7a 100644 --- a/Cabal-syntax/Cabal-syntax.cabal +++ b/Cabal-syntax/Cabal-syntax.cabal @@ -18,6 +18,11 @@ build-type: Simple extra-doc-files: README.md ChangeLog.md +flag CABAL_PARSEC_DEBUG + description: Enable debug build for the cabal field lexer/parser. + default: False + manual: True + source-repository head type: git location: https://github.com/haskell/cabal/ @@ -59,6 +64,11 @@ library if impl(ghc >= 8.0) && impl(ghc < 8.8) ghc-options: -Wnoncanonical-monadfail-instances + if flag(CABAL_PARSEC_DEBUG) + CPP-Options: -DCABAL_PARSEC_DEBUG + build-depends: + vector + build-tool-depends: alex:alex exposed-modules: @@ -148,6 +158,8 @@ library Distribution.Types.ForeignLibOption Distribution.Types.ForeignLibType Distribution.Types.GenericPackageDescription + Distribution.Types.AnnotatedGenericPackageDescription + Distribution.Types.AnnotatedGenericPackageDescription.Lens Distribution.Types.GenericPackageDescription.Lens Distribution.Types.HookedBuildInfo Distribution.Types.IncludeRenaming diff --git a/Cabal-syntax/src/Distribution/FieldGrammar.hs b/Cabal-syntax/src/Distribution/FieldGrammar.hs index 78739a37cfa..804a2e8b01c 100644 --- a/Cabal-syntax/src/Distribution/FieldGrammar.hs +++ b/Cabal-syntax/src/Distribution/FieldGrammar.hs @@ -26,6 +26,7 @@ module Distribution.FieldGrammar , Section (..) , Fields , partitionFields + , extractComments , takeFields , runFieldParser , runFieldParser' @@ -38,6 +39,7 @@ module Distribution.FieldGrammar import Distribution.Compat.Prelude import Prelude () +import qualified Data.Bifunctor as Bi import qualified Data.Map.Strict as Map import Distribution.FieldGrammar.Class @@ -99,6 +101,7 @@ partitionFields = finalize . foldl' f (PS mempty mempty mempty) PS fs (MkSection name sargs sfields : s) ss -- | Take all fields from the front. +-- Returns a tuple containing the comments, nameless fields, and sections takeFields :: [Field ann] -> (Fields ann, [Field ann]) takeFields = finalize . spanMaybe match where @@ -106,3 +109,9 @@ takeFields = finalize . spanMaybe match match (Field (Name ann name) fs) = Just (name, [MkNamelessField ann fs]) match _ = Nothing + +extractComments :: (Foldable f, Functor f) => [f (WithComments ann)] -> ([Comment ann], [f ann]) +extractComments = Bi.first mconcat . unzip . map extractCommentsStep + +extractCommentsStep :: (Foldable f, Functor f) => f (WithComments ann) -> ([Comment ann], f ann) +extractCommentsStep f = (foldMap justComments f, fmap unComments f) diff --git a/Cabal-syntax/src/Distribution/Fields/Field.hs b/Cabal-syntax/src/Distribution/Fields/Field.hs index 496e847b1d0..4038347d236 100644 --- a/Cabal-syntax/src/Distribution/Fields/Field.hs +++ b/Cabal-syntax/src/Distribution/Fields/Field.hs @@ -1,4 +1,5 @@ {-# LANGUAGE CPP #-} +{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE StandaloneDeriving #-} @@ -17,6 +18,12 @@ module Distribution.Fields.Field , SectionArg (..) , sectionArgAnn + -- * Comment + , Comment (..) + , WithComments (..) + , mapComments + , mapCommentedData + -- * Name , FieldName , Name (..) @@ -44,11 +51,26 @@ import qualified Data.Foldable1 as F1 -- Cabal file ------------------------------------------------------------------------------- +data Comment ann = Comment !ByteString !ann + deriving (Show, Generic, Eq, Ord, Functor) + +data WithComments ann = WithComments + { justComments :: ![Comment ann] + , unComments :: !ann + } + deriving (Show, Generic, Eq, Ord, Functor) + +mapComments :: ([Comment ann] -> [Comment ann]) -> WithComments ann -> WithComments ann +mapComments f (WithComments cs x) = WithComments (f cs) x + +mapCommentedData :: (ann -> ann) -> WithComments ann -> WithComments ann +mapCommentedData f (WithComments cs x) = WithComments cs (f x) + -- | A Cabal-like file consists of a series of fields (@foo: bar@) and sections (@library ...@). data Field ann = Field !(Name ann) [FieldLine ann] | Section !(Name ann) [SectionArg ann] [Field ann] - deriving (Eq, Show, Functor, Foldable, Traversable) + deriving (Eq, Show, Functor, Foldable, Traversable, Generic) -- | @since 3.12.0.0 deriving instance Ord ann => Ord (Field ann) @@ -73,7 +95,7 @@ fieldUniverse f@(Field _ _) = [f] -- -- /Invariant:/ 'ByteString' has no newlines. data FieldLine ann = FieldLine !ann !ByteString - deriving (Eq, Show, Functor, Foldable, Traversable) + deriving (Eq, Show, Functor, Foldable, Traversable, Generic) -- | @since 3.12.0.0 deriving instance Ord ann => Ord (FieldLine ann) @@ -94,7 +116,7 @@ data SectionArg ann SecArgStr !ann !ByteString | -- | everything else, mm. operators (e.g. in if-section conditionals) SecArgOther !ann !ByteString - deriving (Eq, Show, Functor, Foldable, Traversable) + deriving (Eq, Show, Functor, Foldable, Traversable, Generic) -- | @since 3.12.0.0 deriving instance Ord ann => Ord (SectionArg ann) @@ -115,7 +137,7 @@ type FieldName = ByteString -- -- /Invariant/: 'ByteString' is lower-case ASCII. data Name ann = Name !ann !FieldName - deriving (Eq, Show, Functor, Foldable, Traversable) + deriving (Eq, Show, Functor, Foldable, Traversable, Generic) -- | @since 3.12.0.0 deriving instance Ord ann => Ord (Name ann) diff --git a/Cabal-syntax/src/Distribution/Fields/Lexer.x b/Cabal-syntax/src/Distribution/Fields/Lexer.x index b9b8ad54c4e..05e91f1f11d 100644 --- a/Cabal-syntax/src/Distribution/Fields/Lexer.x +++ b/Cabal-syntax/src/Distribution/Fields/Lexer.x @@ -31,7 +31,6 @@ import qualified Data.ByteString.Char8 as B.Char8 import qualified Data.Word as Word #ifdef CABAL_PARSEC_DEBUG -import Debug.Trace import qualified Data.Vector as V import qualified Data.Text as T import qualified Data.Text.Encoding as T @@ -84,8 +83,9 @@ tokens :- { @nbspspacetab* @nl { \pos len inp -> checkWhitespace pos len inp >> adjustPos retPos >> lexToken } -- no @nl here to allow for comments on last line of the file with no trailing \n - $spacetab* "--" $comment* ; -- TODO: check the lack of @nl works here - -- including counting line numbers + $spacetab* "--" $comment* { toki TokComment } + -- TODO: check the lack of @nl works here + -- including counting line numbers } { @@ -105,9 +105,8 @@ tokens :- } { - $spacetab+ ; --TODO: don't allow tab as leading space - - "--" $comment* ; + $spacetab+ ; --TODO: don't allow tab as leading space + "--" $comment* { toki TokComment } @name { toki TokSym } @string { \pos len inp -> return $! L pos (TokStr (B.take (len - 2) (B.tail inp))) } @@ -161,6 +160,7 @@ data Token = TokSym !ByteString -- ^ Haskell-like identifier, number or | Colon | OpenBrace | CloseBrace + | TokComment !ByteString | EOF | LexicalError InputStream --TODO: add separate string lexical error deriving Show @@ -230,7 +230,9 @@ lexToken = do setInput inp' let !len_bytes = B.length inp - B.length inp' t <- action pos len_bytes inp - --traceShow t $ return tok +#ifdef CABAL_PARSEC_DEBUG + traceShow t $ return tok +#endif return t @@ -241,10 +243,12 @@ checkPosition pos@(Position lineno colno) inp inp' len_chars = do let len_bytes = B.length inp - B.length inp' pos_txt | lineno-1 < V.length text_lines = T.take len_chars (T.drop (colno-1) (text_lines V.! (lineno-1))) | otherwise = T.empty - real_txt = B.take len_bytes inp + real_txt :: B.ByteString + real_txt = B.take len_bytes inp when (pos_txt /= T.decodeUtf8 real_txt) $ traceShow (pos, pos_txt, T.decodeUtf8 real_txt) $ - traceShow (take 3 (V.toList text_lines)) $ return () + traceShow (take 3 (V.toList text_lines)) $ + return () where getDbgText = Lex $ \s@LexState{ dbgText = txt } -> LexResult s txt #else diff --git a/Cabal-syntax/src/Distribution/Fields/Parser.hs b/Cabal-syntax/src/Distribution/Fields/Parser.hs index 8d04dfba260..183976c141f 100644 --- a/Cabal-syntax/src/Distribution/Fields/Parser.hs +++ b/Cabal-syntax/src/Distribution/Fields/Parser.hs @@ -22,6 +22,8 @@ module Distribution.Fields.Parser -- $grammar , readFields , readFields' + , readFieldsWithComments + , readFieldsWithComments' #ifdef CABAL_PARSEC_DEBUG -- * Internal @@ -29,6 +31,7 @@ module Distribution.Fields.Parser , parseStr , parseBS #endif + , formatError ) where {- FOURMOLU_ENABLE -} @@ -51,11 +54,10 @@ import Text.Parsec.Pos import Text.Parsec.Prim hiding (many, (<|>)) import Prelude () -#ifdef CABAL_PARSEC_DEBUG -import qualified Data.Text as T -import qualified Data.Text.Encoding as T +import qualified Data.Bifunctor as Bi +import qualified Data.Text as T +import qualified Data.Text.Encoding as T import qualified Data.Text.Encoding.Error as T -#endif -- $setup -- >>> import Data.Either (isLeft) @@ -78,6 +80,9 @@ instance Stream LexState' Identity LToken where L _ EOF -> return Nothing _ -> return (Just (tok, st')) +-- | A strict either for parser performance +data Either' a b = Left' !a | Right' !b + -- | Get lexer warnings accumulated so far getLexerWarnings :: Parser [LexWarning] getLexerWarnings = do @@ -114,6 +119,7 @@ describeToken t = case t of Colon -> "\":\"" OpenBrace -> "\"{\"" CloseBrace -> "\"}\"" + TokComment c -> "comment \"" ++ B8.unpack c ++ "\"" -- SemiColon -> "\";\"" EOF -> "end of file" LexicalError is -> "character in input " ++ show (B8.head is) @@ -134,6 +140,9 @@ tokOpenBrace = getTokenWithPos $ \t -> case t of L pos OpenBrace -> Just pos; _ tokCloseBrace = getToken $ \t -> case t of CloseBrace -> Just (); _ -> Nothing tokFieldLine = getTokenWithPos $ \t -> case t of L pos (TokFieldLine s) -> Just (FieldLine pos s); _ -> Nothing +tokComment :: Parser (Comment Position) +tokComment = getTokenWithPos $ \t -> case t of L pos (TokComment c) -> Just (Comment c pos); _ -> Nothing + colon, openBrace, closeBrace :: Parser () sectionArg :: Parser (SectionArg Position) sectionArg = tokSym' <|> tokStr <|> tokOther "section parameter" @@ -166,6 +175,8 @@ indentOfAtLeast (IndentLevel i) = try $ do newtype LexerMode = LexerMode Int +-- | This would change the state of the lexer and make interpretations of tokens different! +-- Certain lexer states are unreachable without it. inLexerMode :: LexerMode -> Parser p -> Parser p inLexerMode (LexerMode mode) p = do setLexerMode mode; x <- p; setLexerMode in_section; return x @@ -173,39 +184,43 @@ inLexerMode (LexerMode mode) p = ----------------------- -- Cabal file grammar -- +-- The non-terminals of the following grammar (symbols starting in uppercase) +-- have their corresponding parser of the same name, starting with lowercase +-- letter. -- $grammar -- -- @ --- CabalStyleFile ::= SecElems +-- CabalStyleFile ::= Elements -- --- SecElems ::= SecElem* '\\n'? --- SecElem ::= '\\n' SecElemLayout | SecElemBraces --- SecElemLayout ::= FieldLayout | FieldBraces | SectionLayout | SectionBraces --- SecElemBraces ::= FieldInline | FieldBraces | SectionBraces --- FieldLayout ::= name ':' line? ('\\n' line)* --- FieldBraces ::= name ':' '\\n'? '{' content '}' --- FieldInline ::= name ':' content --- SectionLayout ::= name arg* SecElems --- SectionBraces ::= name arg* '\\n'? '{' SecElems '}' +-- Elements ::= Elements* '\\n'? +-- Element ::= '\\n' ElementInLayoutContext +-- | ElementInNonLayoutContext +-- ElementInLayoutContext ::= FieldLayout | FieldBraces | SectionLayout | SectionBraces +-- ElementInNonLayoutContext ::= FieldInline | FieldBraces | SectionBraces +-- FieldLayout ::= name ':' line? ('\\n' line)* +-- FieldBraces ::= name ':' '\\n'? '{' content* '}' +-- FieldInline ::= name ':' content +-- SectionLayout ::= name arg* Elements +-- SectionBraces ::= name arg* '\\n'? '{' Elements '}' -- @ -- -- and the same thing but left factored... -- -- @ --- SecElems ::= SecElem* --- SecElem ::= '\\n' name SecElemLayout --- | name SecElemBraces --- SecElemLayout ::= ':' FieldLayoutOrBraces --- | arg* SectionLayoutOrBraces --- FieldLayoutOrBraces ::= '\\n'? '{' content '}' --- | line? ('\\n' line)* --- SectionLayoutOrBraces ::= '\\n'? '{' SecElems '\\n'? '}' --- | SecElems --- SecElemBraces ::= ':' FieldInlineOrBraces --- | arg* '\\n'? '{' SecElems '\\n'? '}' --- FieldInlineOrBraces ::= '\\n'? '{' content '}' --- | content +-- Elements ::= Comments* (Element Comment*)* +-- Element ::= '\\n' name ElementInLayoutContext +-- | name ElementInNonLayoutContext +-- ElementInLayoutContext ::= ':' FieldLayoutOrBraces +-- | arg* SectionLayoutOrBraces +-- FieldLayoutOrBraces ::= '\\n'? '{' comment* (content comment*)* '}' +-- | comment* line? comment* ('\\n' line comment*)* +-- SectionLayoutOrBraces ::= '\\n'? '{' Elements '\\n'? '}' +-- | Elements +-- ElementInNonLayoutContext ::= ':' FieldInlineOrBraces +-- | arg* '\\n'? '{' Elements '\\n'? '}' +-- FieldInlineOrBraces ::= '\\n'? '{' content '}' +-- | content -- @ -- -- Note how we have several productions with the sequence: @@ -225,18 +240,81 @@ inLexerMode (LexerMode mode) p = -- Top level of a file using cabal syntax -- -cabalStyleFile :: Parser [Field Position] +cabalStyleFile :: Parser [Field (WithComments Position)] cabalStyleFile = do es <- elements zeroIndentLevel eof - return es + case es of + Left' _ -> pure [] -- We discard the comments here, because it is not a valid cabal file + Right' es' -> pure es' + +-- | Collect in annotation one or more comments after a parser succeeds +-- Careful with the 'Functor' instance! +-- If you use this with Field you might attach the same comments everywhere +commentsAfter :: Functor f => Parser (f Position) -> Parser (f (WithComments Position)) +commentsAfter p = do + x <- p + postCmts <- many tokComment + pure $ fmap (WithComments postCmts) x + +noComments :: Functor f => f ann -> f (WithComments ann) +noComments = fmap (WithComments mempty) + +-- | Returns 'Nothing' when there is no field to attach the comments to. +prependCommentsFields :: [Comment ann] -> [Field (WithComments ann)] -> Maybe [Field (WithComments ann)] +prependCommentsFields cs fs = case fs of + [] -> Nothing + (f : fs') -> Just $ prependCommentsField cs f : fs' + +-- | We attach the comments to the name (foremost child) of 'Field', this hence cannot fail. +prependCommentsField :: [Comment ann] -> Field (WithComments ann) -> Field (WithComments ann) +prependCommentsField cs f = case f of + (Field name fls) -> Field (mapComments (cs ++) <$> name) fls + (Section name args fs) -> Section (mapComments (cs ++) <$> name) args fs + +-- | Returns 'Nothing' when there is no field to attach the comments to. +appendCommentsFields :: [Comment ann] -> [Field (WithComments ann)] -> Maybe [Field (WithComments ann)] +appendCommentsFields cs fs = case fs of + [] -> Nothing + [f] -> Just [appendCommentsField cs f] + (f : fs') -> (f :) <$> appendCommentsFields cs fs' + +appendCommentsField :: [Comment ann] -> Field (WithComments ann) -> Field (WithComments ann) +appendCommentsField cs f = case f of + (Field name fls) -> case appendCommentsFieldLines cs fls of + Nothing -> Field (mapComments (++ cs) <$> name) [] + Just fls' -> Field name fls' + (Section name args fs) -> case appendCommentsFields cs fs of + Nothing -> Section (mapComments (++ cs) <$> name) args [] + Just fs' -> Section name args fs' + +-- | Returns 'Nothing' when there is no field to attach the comments to. +appendCommentsFieldLines :: [Comment ann] -> [FieldLine (WithComments ann)] -> Maybe [FieldLine (WithComments ann)] +appendCommentsFieldLines cs fls = case fls of + [] -> Nothing + [fl] -> Just [mapComments (++ cs) <$> fl] + (f : fls') -> (f :) <$> appendCommentsFieldLines cs fls' -- Elements that live at the top level or inside a section, i.e. fields --- and sections content +-- and sections content. +-- +-- This returns either many fields with their comments attached, or just the +-- comments if there are no fields to attach them to. Only at the top level it +-- is deemed correct to discard these comments, because in that case having no +-- elements isn't a valid cabal file. -- --- elements ::= element* -elements :: IndentLevel -> Parser [Field Position] -elements ilevel = many (element ilevel) +-- elements ::= comment* (element comment*)* +elements :: IndentLevel -> Parser (Either' [Comment Position] [Field (WithComments Position)]) +elements ilevel = do + preCmts <- many tokComment + es <- many $ do + e <- element ilevel + postCmts <- many tokComment + pure $ appendCommentsField postCmts e + + case prependCommentsFields preCmts es of + Nothing -> pure $ Left' preCmts + Just es' -> pure $ Right' es' -- An individual element, ie a field or a section. These can either use -- layout style or braces style. For layout style then it must start on @@ -244,7 +322,7 @@ elements ilevel = many (element ilevel) -- -- element ::= '\\n' name elementInLayoutContext -- | name elementInNonLayoutContext -element :: IndentLevel -> Parser (Field Position) +element :: IndentLevel -> Parser (Field (WithComments Position)) element ilevel = ( do ilevel' <- indentOfAtLeast ilevel @@ -262,13 +340,16 @@ element ilevel = -- -- elementInLayoutContext ::= ':' fieldLayoutOrBraces -- | arg* sectionLayoutOrBraces -elementInLayoutContext :: IndentLevel -> Name Position -> Parser (Field Position) +elementInLayoutContext :: IndentLevel -> Name Position -> Parser (Field (WithComments Position)) elementInLayoutContext ilevel name = (do colon; fieldLayoutOrBraces ilevel name) <|> ( do args <- many sectionArg elems <- sectionLayoutOrBraces ilevel - return (Section name args elems) + case elems of + -- If there are no elements but comments, we attach them to the name (args can be multiple) + Left' onlyCmts -> return (Section (WithComments onlyCmts <$> name) (noComments <$> args) []) + Right' elems' -> return (Section (noComments name) (noComments <$> args) elems') ) -- An element (field or section) that is valid in a non-layout context. @@ -277,42 +358,52 @@ elementInLayoutContext ilevel name = -- -- elementInNonLayoutContext ::= ':' FieldInlineOrBraces -- | arg* '\\n'? '{' elements '\\n'? '}' -elementInNonLayoutContext :: Name Position -> Parser (Field Position) +elementInNonLayoutContext :: Name Position -> Parser (Field (WithComments Position)) elementInNonLayoutContext name = - (do colon; fieldInlineOrBraces name) + (do colon; noComments <$> fieldInlineOrBraces name) -- inline field or braces can never have comments <|> ( do args <- many sectionArg openBrace elems <- elements zeroIndentLevel optional tokIndent closeBrace - return (Section name args elems) + + case elems of + Left' elementCmts -> return (Section (WithComments elementCmts <$> name) (noComments <$> args) []) + Right' elems' -> return (Section (noComments name) (noComments <$> args) elems') ) -- The body of a field, using either layout style or braces style. -- --- fieldLayoutOrBraces ::= '\\n'? '{' content '}' --- | line? ('\\n' line)* -fieldLayoutOrBraces :: IndentLevel -> Name Position -> Parser (Field Position) +-- fieldLayoutOrBraces ::= '\\n'? '{' comment* (content comment*)* '}' +-- | comment* line? comment* ('\\n' line comment*)* +fieldLayoutOrBraces :: IndentLevel -> Name Position -> Parser (Field (WithComments Position)) fieldLayoutOrBraces ilevel name = braces <|> fieldLayout where + braces :: Parser (Field (WithComments Position)) braces = do openBrace - ls <- inLexerMode (LexerMode in_field_braces) (many fieldContent) + preCmts <- many tokComment + ls <- inLexerMode (LexerMode in_field_braces) (many $ commentsAfter fieldContent) closeBrace - return (Field name ls) + return $ Field (WithComments preCmts <$> name) ls + + fieldLayout :: Parser (Field (WithComments Position)) fieldLayout = inLexerMode (LexerMode in_field_layout) $ do - l <- optionMaybe fieldContent - ls <- many (do _ <- indentOfAtLeast ilevel; fieldContent) - return $ case l of - Nothing -> Field name ls - Just l' -> Field name (l' : ls) + preCmts <- many tokComment + l <- optionMaybe (commentsAfter fieldContent) + ls <- many (do _ <- indentOfAtLeast ilevel; commentsAfter fieldContent) + return + ( case l of + Nothing -> (Field (WithComments preCmts <$> name) ls) + Just l' -> (Field (WithComments preCmts <$> name) (l' : ls)) + ) -- The body of a section, using either layout style or braces style. -- -- sectionLayoutOrBraces ::= '\\n'? '{' elements \\n? '}' -- | elements -sectionLayoutOrBraces :: IndentLevel -> Parser [Field Position] +sectionLayoutOrBraces :: IndentLevel -> Parser (Either' [Comment Position] [Field (WithComments Position)]) sectionLayoutOrBraces ilevel = ( do openBrace @@ -367,11 +458,17 @@ fieldInlineOrBraces name = -- >>> readFields' "\xc2\xa0 foo: bar" -- Right ([Field (Name (Position 1 3) "foo") [FieldLine (Position 1 8) "bar"]],[LexWarning LexWarningNBSP (Position 1 1)]) readFields :: B8.ByteString -> Either ParseError [Field Position] -readFields s = fmap fst (readFields' s) +readFields = (fmap . map . fmap) unComments . readFieldsWithComments -- | Like 'readFields' but also return lexer warnings. readFields' :: B8.ByteString -> Either ParseError ([Field Position], [LexWarning]) -readFields' s = do +readFields' = (fmap . Bi.first . map . fmap) unComments . readFieldsWithComments' + +readFieldsWithComments :: B8.ByteString -> Either ParseError [Field (WithComments Position)] +readFieldsWithComments = fmap fst . readFieldsWithComments' + +readFieldsWithComments' :: B8.ByteString -> Either ParseError ([Field (WithComments Position)], [LexWarning]) +readFieldsWithComments' s = do parse parser "the input" lexSt where parser = do @@ -389,16 +486,16 @@ readFields' s = do -- -- To catch during parsing we would need to parse first field/section of a section -- and then parse the following ones (softly) requiring the exactly the same indentation. -checkIndentation :: [Field Position] -> [LexWarning] -> [LexWarning] +checkIndentation :: [Field (WithComments Position)] -> [LexWarning] -> [LexWarning] checkIndentation [] = id -checkIndentation (Field name _ : fs') = checkIndentation' (nameAnn name) fs' -checkIndentation (Section name _ fs : fs') = checkIndentation fs . checkIndentation' (nameAnn name) fs' +checkIndentation (Field name _ : fs') = checkIndentation' (unComments $ nameAnn name) fs' +checkIndentation (Section name _ fs : fs') = checkIndentation fs . checkIndentation' (unComments $ nameAnn name) fs' -- | We compare adjacent fields to reduce the amount of reported indentation warnings. -checkIndentation' :: Position -> [Field Position] -> [LexWarning] -> [LexWarning] +checkIndentation' :: Position -> [Field (WithComments Position)] -> [LexWarning] -> [LexWarning] checkIndentation' _ [] = id -checkIndentation' pos (Field name _ : fs') = checkIndentation'' pos (nameAnn name) . checkIndentation' (nameAnn name) fs' -checkIndentation' pos (Section name _ fs : fs') = checkIndentation'' pos (nameAnn name) . checkIndentation fs . checkIndentation' (nameAnn name) fs' +checkIndentation' pos (Field name _ : fs') = checkIndentation'' pos (unComments $ nameAnn name) . checkIndentation' (unComments $ nameAnn name) fs' +checkIndentation' pos (Section name _ fs : fs') = checkIndentation'' pos (unComments $ nameAnn name) . checkIndentation fs . checkIndentation' (unComments $ nameAnn name) fs' -- | Check that positions' columns are the same. checkIndentation'' :: Position -> Position -> [LexWarning] -> [LexWarning] @@ -424,33 +521,40 @@ parseStr p = parseBS p . B8.pack parseBS :: Show a => Parser a -> B8.ByteString -> IO () parseBS p = parseTest' p "" +#endif formatError :: B8.ByteString -> ParseError -> String formatError input perr = - unlines - [ "Parse error "++ show (errorPos perr) ++ ":" - , errLine - , indicator ++ errmsg ] + unlines + [ "Parse error " ++ show (errorPos perr) ++ ":" + , errLine + , indicator ++ errmsg + ] where - pos = errorPos perr - ls = lines' (T.decodeUtf8With T.lenientDecode input) - errLine = T.unpack (ls !! (sourceLine pos - 1)) + pos = errorPos perr + ls = lines' (T.decodeUtf8With T.lenientDecode input) + errLine = T.unpack (ls !! (sourceLine pos - 1)) indicator = replicate (sourceColumn pos) ' ' ++ "^" - errmsg = showErrorMessages "or" "unknown parse error" - "expecting" "unexpected" "end of file" - (errorMessages perr) + errmsg = + showErrorMessages + "or" + "unknown parse error" + "expecting" + "unexpected" + "end of file" + (errorMessages perr) -- | Handles windows/osx/unix line breaks uniformly lines' :: T.Text -> [T.Text] lines' s1 | T.null s1 = [] | otherwise = case T.break (\c -> c == '\r' || c == '\n') s1 of - (l, s2) | Just (c,s3) <- T.uncons s2 - -> case T.uncons s3 of - Just ('\n', s4) | c == '\r' -> l : lines' s4 - _ -> l : lines' s3 - | otherwise -> [l] -#endif + (l, s2) + | Just (c, s3) <- T.uncons s2 -> + case T.uncons s3 of + Just ('\n', s4) | c == '\r' -> l : lines' s4 + _ -> l : lines' s3 + | otherwise -> [l] eof :: Parser () eof = notFollowedBy anyToken "end of file" diff --git a/Cabal-syntax/src/Distribution/PackageDescription.hs b/Cabal-syntax/src/Distribution/PackageDescription.hs index 47d46673e5f..1f788872283 100644 --- a/Cabal-syntax/src/Distribution/PackageDescription.hs +++ b/Cabal-syntax/src/Distribution/PackageDescription.hs @@ -13,6 +13,7 @@ module Distribution.PackageDescription ( -- * PD and GPD module Distribution.Types.PackageDescription + , module Distribution.Types.AnnotatedGenericPackageDescription , module Distribution.Types.GenericPackageDescription -- * Components @@ -86,6 +87,7 @@ import Prelude () -- import Distribution.Compat.Prelude +import Distribution.Types.AnnotatedGenericPackageDescription import Distribution.Types.Benchmark import Distribution.Types.BenchmarkInterface import Distribution.Types.BenchmarkType diff --git a/Cabal-syntax/src/Distribution/PackageDescription/Parsec.hs b/Cabal-syntax/src/Distribution/PackageDescription/Parsec.hs index c7e327ddb7f..0b43ee20596 100644 --- a/Cabal-syntax/src/Distribution/PackageDescription/Parsec.hs +++ b/Cabal-syntax/src/Distribution/PackageDescription/Parsec.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE BangPatterns #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE Rank2Types #-} @@ -16,6 +17,8 @@ module Distribution.PackageDescription.Parsec ( -- * Package descriptions parseGenericPackageDescription , parseGenericPackageDescriptionMaybe + , parseAnnotatedGenericPackageDescription + , parseAnnotatedGenericPackageDescriptionMaybe -- ** Parsing , ParseResult @@ -40,7 +43,7 @@ import Distribution.Compat.Lens import Distribution.FieldGrammar import Distribution.FieldGrammar.Parsec (NamelessField (..)) import Distribution.Fields.ConfVar (parseConditionConfVar) -import Distribution.Fields.Field (FieldName, getName, sectionArgAnn) +import Distribution.Fields.Field (Comment (..), FieldName, WithComments, getName, sectionArgAnn) import Distribution.Fields.LexerMonad (LexWarning, toPWarnings) import Distribution.Fields.ParseResult import Distribution.Fields.Parser @@ -72,12 +75,29 @@ import qualified Text.Parsec as P ------------------------------------------------------------------------------ +-- Deep Evaluation +-- ~~~~~~~~~~~~~~~ +-- +-- See nothunks test, without this deepseq we get (at least): +-- Thunk in ThunkInfo {thunkContext = ["GenericPackageDescription"]} +-- +-- TODO: re-benchmark, whether `deepseq` is important (both cabal-benchmarks and solver-benchmarks) +-- TODO: remove the need for deepseq if `deepseq` in fact matters +-- NOTE: IIRC it does affect (maximal) memory usage, which causes less GC pressure + -- | Parses the given file into a 'GenericPackageDescription'. -- -- In Cabal 1.2 the syntax for package descriptions was changed to a format -- with sections and possibly indented property descriptions. parseGenericPackageDescription :: BS.ByteString -> ParseResult src GenericPackageDescription parseGenericPackageDescription bs = do + gpd <- parseAnnotatedGenericPackageDescription bs + let gpd' = unannotatedGpd gpd + -- See "Deep Evaluation" note + gpd' `deepseq` return gpd' + +parseAnnotatedGenericPackageDescription :: BS.ByteString -> ParseResult src AnnotatedGenericPackageDescription +parseAnnotatedGenericPackageDescription bs = do -- set scanned version setCabalSpecVersion ver @@ -93,12 +113,12 @@ parseGenericPackageDescription bs = do ++ cabalFormatVersionsDesc _ -> pure Nothing - case readFields' bs'' of + case readFieldsWithComments' bs'' of Right (fs, lexWarnings) -> do when patched $ parseWarning zeroPos PWTQuirkyCabalFile "Legacy cabal file" -- UTF8 is validated in a prepass step, afterwards parsing is lenient. - parseGenericPackageDescription' csv lexWarnings invalidUtf8 fs + parseAnnotatedGenericPackageDescription' csv lexWarnings invalidUtf8 fs -- TODO: better marshalling of errors Left perr -> parseFatalFailure pos (show perr) where @@ -117,8 +137,15 @@ parseGenericPackageDescription bs = do -- | 'Maybe' variant of 'parseGenericPackageDescription' parseGenericPackageDescriptionMaybe :: BS.ByteString -> Maybe GenericPackageDescription -parseGenericPackageDescriptionMaybe = - either (const Nothing) Just . snd . runParseResult . parseGenericPackageDescription +parseGenericPackageDescriptionMaybe bs = do + gpd <- parseAnnotatedGenericPackageDescriptionMaybe bs + let gpd' = unannotatedGpd gpd + -- See "Deep Evaluation" note + gpd' `deepseq` return gpd' + +parseAnnotatedGenericPackageDescriptionMaybe :: BS.ByteString -> Maybe AnnotatedGenericPackageDescription +parseAnnotatedGenericPackageDescriptionMaybe = + either (const Nothing) Just . snd . runParseResult . parseAnnotatedGenericPackageDescription fieldlinesToBS :: [FieldLine ann] -> BS.ByteString fieldlinesToBS = BS.intercalate "\n" . map (\(FieldLine _ bs) -> bs) @@ -147,18 +174,22 @@ stateCommonStanzas f (SectionS gpd cs) = SectionS gpd <$> f cs -- * first we parse fields of PackageDescription -- * then we parse sections (libraries, executables, etc) -parseGenericPackageDescription' +parseAnnotatedGenericPackageDescription' :: Maybe CabalSpecVersion -> [LexWarning] -> Maybe Int - -> [Field Position] - -> ParseResult src GenericPackageDescription -parseGenericPackageDescription' scannedVer lexWarnings utf8WarnPos fs = do + -> [Field (WithComments Position)] + -> ParseResult src AnnotatedGenericPackageDescription +parseAnnotatedGenericPackageDescription' scannedVer lexWarnings utf8WarnPos fs = do parseWarnings (toPWarnings lexWarnings) for_ utf8WarnPos $ \pos -> parseWarning zeroPos PWTUTF $ "UTF8 encoding problem at byte offset " ++ show pos - let (syntax, fs') = sectionizeFields fs - let (fields, sectionFields) = takeFields fs' + + let (comments, fs') = extractComments fs + !commentsMap = Map.fromList . map (\(Comment cmt pos) -> (pos, cmt)) $ comments + + let (syntax, fs'') = sectionizeFields fs' + let (fields, sectionFields) = takeFields fs'' -- cabal-version specVer <- case scannedVer of @@ -208,13 +239,11 @@ parseGenericPackageDescription' scannedVer lexWarnings utf8WarnPos fs = do let gpd2 = postProcessInternalDeps specVer gpd1 checkForUndefinedFlags gpd2 checkForUndefinedCustomSetup gpd2 - -- See nothunks test, without this deepseq we get (at least): - -- Thunk in ThunkInfo {thunkContext = ["PackageIdentifier","PackageDescription","GenericPackageDescription"]} - -- - -- TODO: re-benchmark, whether `deepseq` is important (both cabal-benchmarks and solver-benchmarks) - -- TODO: remove the need for deepseq if `deepseq` in fact matters - -- NOTE: IIRC it does affect (maximal) memory usage, which causes less GC pressure - gpd2 `deepseq` return gpd2 + return + AnnotatedGenericPackageDescription + { exactComments = commentsMap + , unannotatedGpd = gpd2 + } where safeLast :: [a] -> Maybe a safeLast = listToMaybe . reverse diff --git a/Cabal-syntax/src/Distribution/Parsec/Position.hs b/Cabal-syntax/src/Distribution/Parsec/Position.hs index 892fc8b8fda..d56433092de 100644 --- a/Cabal-syntax/src/Distribution/Parsec/Position.hs +++ b/Cabal-syntax/src/Distribution/Parsec/Position.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} module Distribution.Parsec.Position @@ -18,9 +19,10 @@ data Position = Position {-# UNPACK #-} !Int -- row {-# UNPACK #-} !Int -- column - deriving (Eq, Ord, Show, Generic) + deriving (Eq, Ord, Show, Generic, Data) instance Binary Position +instance Structured Position instance NFData Position where rnf = genericRnf -- | Shift position by n columns to the right. diff --git a/Cabal-syntax/src/Distribution/Types/AnnotatedGenericPackageDescription.hs b/Cabal-syntax/src/Distribution/Types/AnnotatedGenericPackageDescription.hs new file mode 100644 index 00000000000..1f515fe5aa9 --- /dev/null +++ b/Cabal-syntax/src/Distribution/Types/AnnotatedGenericPackageDescription.hs @@ -0,0 +1,25 @@ +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveGeneric #-} + +-- | Contains 'AnnotatedGenericPackageDescription', useful for exact print +-- We split this from 'GenericPackageDescription' type notably because the +-- exact comments breaks its 'Eq' instance. +module Distribution.Types.AnnotatedGenericPackageDescription + ( AnnotatedGenericPackageDescription (..) + , ExactComments + ) where + +import Distribution.Compat.Prelude +import Prelude () + +import Data.ByteString +import Distribution.Parsec.Position (Position) +import Distribution.Types.GenericPackageDescription + +data AnnotatedGenericPackageDescription = AnnotatedGenericPackageDescription + { exactComments :: ExactComments Position + , unannotatedGpd :: GenericPackageDescription + } + deriving (Show, Data, Generic) + +type ExactComments ann = Map ann ByteString diff --git a/Cabal-syntax/src/Distribution/Types/AnnotatedGenericPackageDescription/Lens.hs b/Cabal-syntax/src/Distribution/Types/AnnotatedGenericPackageDescription/Lens.hs new file mode 100644 index 00000000000..0d025c56165 --- /dev/null +++ b/Cabal-syntax/src/Distribution/Types/AnnotatedGenericPackageDescription/Lens.hs @@ -0,0 +1,10 @@ +module Distribution.Types.AnnotatedGenericPackageDescription.Lens where + +import Distribution.Compat.Lens +import Distribution.Compat.Prelude +import qualified Distribution.Types.AnnotatedGenericPackageDescription as T +import qualified Distribution.Types.GenericPackageDescription as T +import Prelude () + +unannotatedGpd :: Lens' T.AnnotatedGenericPackageDescription T.GenericPackageDescription +unannotatedGpd f s = fmap (\x -> s{T.unannotatedGpd = x}) (f (T.unannotatedGpd s)) diff --git a/Cabal-syntax/src/Distribution/Types/Lens.hs b/Cabal-syntax/src/Distribution/Types/Lens.hs index 2934d722fbd..8bcd0ca355d 100644 --- a/Cabal-syntax/src/Distribution/Types/Lens.hs +++ b/Cabal-syntax/src/Distribution/Types/Lens.hs @@ -3,6 +3,7 @@ module Distribution.Types.Lens , module Distribution.Types.BuildInfo.Lens , module Distribution.Types.Executable.Lens , module Distribution.Types.ForeignLib.Lens + , module Distribution.Types.AnnotatedGenericPackageDescription.Lens , module Distribution.Types.GenericPackageDescription.Lens , module Distribution.Types.Library.Lens , module Distribution.Types.PackageDescription.Lens @@ -12,6 +13,7 @@ module Distribution.Types.Lens , module Distribution.Types.TestSuite.Lens ) where +import Distribution.Types.AnnotatedGenericPackageDescription.Lens import Distribution.Types.Benchmark.Lens import Distribution.Types.BuildInfo.Lens import Distribution.Types.Executable.Lens diff --git a/Cabal-tests/tests/HackageTests.hs b/Cabal-tests/tests/HackageTests.hs index 1265c6cb13e..0290c9cf382 100644 --- a/Cabal-tests/tests/HackageTests.hs +++ b/Cabal-tests/tests/HackageTests.hs @@ -287,6 +287,7 @@ roundtripTest testFieldsTransform fpath bs = do print err exitFailure + -- we disable comparison on exactComments for now because we can't print it yet assertEqual' bs' x y = unless (x == y || fpath == "ixset/1.0.4/ixset.cabal") $ do putStrLn fpath #ifdef MIN_VERSION_tree_diff diff --git a/Cabal-tests/tests/NoThunks.hs b/Cabal-tests/tests/NoThunks.hs index a53d404dd1e..43414f8dcb4 100644 --- a/Cabal-tests/tests/NoThunks.hs +++ b/Cabal-tests/tests/NoThunks.hs @@ -20,6 +20,7 @@ import Distribution.CabalSpecVersion (CabalSpecVersion) import Distribution.Compat.NonEmptySet (NonEmptySet) import Distribution.Compiler (CompilerFlavor, PerCompilerFlavor) import Distribution.Fields (runParseResult) +import Distribution.Parsec.Position (Position) import Distribution.ModuleName (ModuleName) import Distribution.PackageDescription.Parsec (parseGenericPackageDescription, withSource) import Distribution.Parsec.Source @@ -94,6 +95,7 @@ instance NoThunks PackageDescription instance NoThunks PackageFlag instance NoThunks PackageIdentifier instance NoThunks PackageName +instance NoThunks Position instance NoThunks LegacyExeDependency instance NoThunks ExeDependency instance NoThunks PkgconfigName diff --git a/Cabal-tests/tests/ParserTests.hs b/Cabal-tests/tests/ParserTests.hs index 8368ed19451..281e9a789fb 100644 --- a/Cabal-tests/tests/ParserTests.hs +++ b/Cabal-tests/tests/ParserTests.hs @@ -14,8 +14,12 @@ import Control.Monad (unless, void) import Data.Algorithm.Diff (PolyDiff (..), getGroupedDiff) import Data.Maybe (isNothing) import Distribution.Fields (pwarning) -import Distribution.PackageDescription (GenericPackageDescription) -import Distribution.PackageDescription.Parsec (parseGenericPackageDescription) +import Distribution.Fields.Parser (readFieldsWithComments', formatError) +import Distribution.PackageDescription (GenericPackageDescription, exactComments) +import Distribution.PackageDescription.Parsec + ( parseGenericPackageDescription + , parseAnnotatedGenericPackageDescription + ) import Distribution.PackageDescription.PrettyPrint (showGenericPackageDescription) import Distribution.Parsec (PWarnType (..), PWarning (..), showPErrorWithSource, showPWarningWithSource) import Distribution.Pretty (prettyShow) @@ -42,6 +46,7 @@ tests :: TestTree tests = testGroup "parsec tests" [ regressionTests , warningTests + , commentTests , errorTests , ipiTests ] @@ -94,6 +99,67 @@ warningTest wt fp = testCase (show wt) $ do isRight (Right _) = True isRight _ = False + +------------------------------------------------------------------------------- +-- comment +------------------------------------------------------------------------------- + + +#ifdef MIN_VERSION_tree_diff +-- Verify that comments are parsed correctly +commentTests :: TestTree +commentTests = testGroup "comments" + [ + -- Imported from hackage integration test + readFieldTest "layout-complex-indented-comments.cabal" + , readFieldTest "layout-comment-in-fieldline.cabal" -- aligned leading comma after comment + + , commentTest "layout-nosections-before.cabal" + , commentTest "layout-nosections-after.cabal" + , commentTest "layout-nosections-mixed.cabal" + , commentTest "layout-many-sections.cabal" + , commentTest "layout-interleaved-in-section.cabal" + , commentTest "layout-fieldline-is-flag.cabal" + + , commentTest "hasktorch.cabal" -- Imported from regression test, has a lot of comments + ] + +-- Use this test to bypass the more sophisticated checks of whether a cabal file is valid +readFieldTest :: FilePath -> TestTree +readFieldTest fname = ediffGolden goldenTest fname exprFile $ do + contents <- BS.readFile input + let res = readFieldsWithComments' contents + + case res of + Left perr -> fail $ formatError contents perr + Right (fs, warns) -> do + unless (null warns) (fail $ unlines (map show warns)) + pure fs + + where + input = "tests" "ParserTests" "comments" fname + exprFile = replaceExtension input "expr" + +commentTest :: FilePath -> TestTree +commentTest fname = ediffGolden goldenTest fname exprFile $ do + contents <- BS.readFile input + let res = withSource (PCabalFile (input, contents)) $ parseAnnotatedGenericPackageDescription contents + let (warns, x) = runParseResult res + + unless (null warns) (fail $ + unlines (map (showPWarningWithSource . fmap renderCabalFileSource) warns) + ) + + case x of + Right output -> pure $ toExpr (exactComments output) + Left (v, errs) -> + fail $ + unlines $ ("VERSION: " ++ show v) : map (showPErrorWithSource . fmap renderCabalFileSource) (NE.toList errs) + where + input = "tests" "ParserTests" "comments" fname + exprFile = replaceExtension input "expr" +#endif + ------------------------------------------------------------------------------- -- Errors ------------------------------------------------------------------------------- diff --git a/Cabal-tests/tests/ParserTests/comments/hasktorch.cabal b/Cabal-tests/tests/ParserTests/comments/hasktorch.cabal new file mode 100644 index 00000000000..d9ca0a6c037 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/comments/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 , Austin Huang - 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/tests/ParserTests/comments/hasktorch.expr b/Cabal-tests/tests/ParserTests/comments/hasktorch.expr new file mode 100644 index 00000000000..247f593f9c1 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/comments/hasktorch.expr @@ -0,0 +1,98 @@ +Map.fromList + [ + _×_ + (Position 2 1) + "-- ================================================================ --", + _×_ + (Position 3 1) + "-- ======== This cabal file has been modified from dhall ========== --", + _×_ + (Position 4 1) + "-- ======== This constitutes the 0.0.1.0 release. ========== --", + _×_ + (Position 5 1) + "-- ======== Dhall can generate this file, but will never ========== --", + _×_ + (Position 6 1) + "-- ======== be able to upload to hackage. For more, see: ========== --", + _×_ + (Position 7 1) + "-- ==== https://github.com/haskell/hackage-server/issues/795 ====== --", + _×_ + (Position 8 1) + "-- ================================================================ --", + _×_ + (Position 70 1) + " -- containers ==0.5.10 || >0.5.10,", + _×_ + (Position 71 1) + " -- deepseq ==1.3.0 || >1.3.0,", + _×_ + (Position 73 1) + " -- managed (==1.0.0 || >1.0.0) && <1.1,", + _×_ + (Position 74 1) + " -- microlens ==0.4.8 || >0.4.8,", + _×_ + (Position 75 1) + " -- numeric-limits ==0.1.0 || >0.1.0,", + _×_ + (Position 79 1) + " -- typelits-witnesses ==0.2.3 || >0.2.3,", + _×_ + (Position 84 1) + " -- <><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><> --", + _×_ + (Position 85 1) + " -- BEGIN EDITS", + _×_ + (Position 86 1) + " -- <><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><> --", + _×_ + (Position 148 1) + " -- <><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><> --", + _×_ + (Position 149 1) + " -- END EDITS", + _×_ + (Position 150 1) + " -- <><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><> --", + _×_ + (Position 203 1) + " -- containers ==0.5.10 || >0.5.10,", + _×_ + (Position 204 1) + " -- deepseq ==1.3.0 || >1.3.0,", + _×_ + (Position 208 1) + " -- managed (==1.0.0 || >1.0.0) && <1.1,", + _×_ + (Position 209 1) + " -- microlens ==0.4.8 || >0.4.8,", + _×_ + (Position 210 1) + " -- numeric-limits ==0.1.0 || >0.1.0,", + _×_ + (Position 214 1) + " -- typelits-witnesses ==0.2.3 || >0.2.3,", + _×_ + (Position 282 1) + " -- containers ==0.5.10 || >0.5.10,", + _×_ + (Position 283 1) + " -- deepseq ==1.3.0 || >1.3.0,", + _×_ + (Position 287 1) + " -- managed (==1.0.0 || >1.0.0) && <1.1,", + _×_ + (Position 288 1) + " -- microlens ==0.4.8 || >0.4.8,", + _×_ + (Position 289 1) + " -- numeric-limits ==0.1.0 || >0.1.0,", + _×_ + (Position 293 1) + " -- typelits-witnesses ==0.2.3 || >0.2.3,", + _×_ + (Position 551 1) + " -- text ==1.2.2 || >1.2.2,"] diff --git a/Cabal-tests/tests/ParserTests/comments/layout-comment-in-fieldline.cabal b/Cabal-tests/tests/ParserTests/comments/layout-comment-in-fieldline.cabal new file mode 100644 index 00000000000..73981b27a78 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/comments/layout-comment-in-fieldline.cabal @@ -0,0 +1,11 @@ +Executable + Main-is: Main.hs + hs-source-dirs: + src + ghc-options: -Wall + Build-Depends: base + -- , foo + -- ^ This should be consumed after fieldContent + , bar + -- , comemnt + , baz diff --git a/Cabal-tests/tests/ParserTests/comments/layout-comment-in-fieldline.expr b/Cabal-tests/tests/ParserTests/comments/layout-comment-in-fieldline.expr new file mode 100644 index 00000000000..30d078ec9dd --- /dev/null +++ b/Cabal-tests/tests/ParserTests/comments/layout-comment-in-fieldline.expr @@ -0,0 +1,77 @@ +[ + Section + (Name + WithComments { + justComments = [], + unComments = Position 1 1} + "executable") + [] + [ + Field + (Name + WithComments { + justComments = [], + unComments = Position 2 5} + "main-is") + [ + FieldLine + WithComments { + justComments = [], + unComments = Position 2 26} + "Main.hs"], + Field + (Name + WithComments { + justComments = [], + unComments = Position 3 5} + "hs-source-dirs") + [ + FieldLine + WithComments { + justComments = [], + unComments = Position 4 9} + "src"], + Field + (Name + WithComments { + justComments = [], + unComments = Position 5 5} + "ghc-options") + [ + FieldLine + WithComments { + justComments = [], + unComments = Position 5 18} + "-Wall"], + Field + (Name + WithComments { + justComments = [], + unComments = Position 6 5} + "build-depends") + [ + FieldLine + WithComments { + justComments = + [ + Comment + " -- , foo" + (Position 7 1), + Comment + " -- ^ This should be consumed after fieldContent" + (Position 8 1)], + unComments = Position 6 22} + "base", + FieldLine + WithComments { + justComments = [ + Comment + " -- , comemnt" + (Position 10 1)], + unComments = Position 9 22} + ", bar", + FieldLine + WithComments { + justComments = [], + unComments = Position 11 22} + ", baz"]]] diff --git a/Cabal-tests/tests/ParserTests/comments/layout-complex-indented-comments.cabal b/Cabal-tests/tests/ParserTests/comments/layout-complex-indented-comments.cabal new file mode 100644 index 00000000000..cbc3d4db683 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/comments/layout-complex-indented-comments.cabal @@ -0,0 +1,38 @@ +-- This is the configuration file for the 'cabal' command line tool. +-- +-- The available configuration options are listed below. + + +repository hackage.haskell.org + url: http://hackage.haskell.org/ + -- secure: True + -- root-keys: + +-- ignore-expiry: False +-- http-transport: +remote-repo-cache: /home/foo/.cache/cabal/packages +-- logs-dir: /home/foo/.cache/cabal/logs +-- default-user-config: +build-summary: /home/foo/.cache/cabal/logs/build.log +-- build-log: +remote-build-reporting: none +-- report-planning-failure: False +-- per-component: True +jobs: $ncpus +-- keep-going: False +-- offline: False +installdir: /home/foo/.local/bin +-- token: +-- username: + +haddock + -- keep-temp-files: False + -- hoogle: False + +init + -- interactive: False + -- quiet: False + +program-locations + -- alex-location: + -- ar-location: diff --git a/Cabal-tests/tests/ParserTests/comments/layout-complex-indented-comments.expr b/Cabal-tests/tests/ParserTests/comments/layout-complex-indented-comments.expr new file mode 100644 index 00000000000..9a8538a518a --- /dev/null +++ b/Cabal-tests/tests/ParserTests/comments/layout-complex-indented-comments.expr @@ -0,0 +1,175 @@ +[ + Section + (Name + WithComments { + justComments = + [ + Comment + "-- This is the configuration file for the 'cabal' command line tool." + (Position 1 1), + Comment "--" (Position 2 1), + Comment + "-- The available configuration options are listed below." + (Position 3 1)], + unComments = Position 6 1} + "repository") + [ + SecArgName + WithComments { + justComments = [], + unComments = Position 6 12} + "hackage.haskell.org"] + [ + Field + (Name + WithComments { + justComments = [], + unComments = Position 7 3} + "url") + [ + FieldLine + WithComments { + justComments = [ + Comment + " -- secure: True" + (Position 8 1), + Comment + " -- root-keys:" + (Position 9 1), + Comment + "-- ignore-expiry: False" + (Position 11 1), + Comment + "-- http-transport:" + (Position 12 1)], + unComments = Position 7 8} + "http://hackage.haskell.org/"]], + Field + (Name + WithComments { + justComments = [], + unComments = Position 13 1} + "remote-repo-cache") + [ + FieldLine + WithComments { + justComments = [ + Comment + "-- logs-dir: /home/foo/.cache/cabal/logs" + (Position 14 1), + Comment + "-- default-user-config:" + (Position 15 1)], + unComments = Position 13 20} + "/home/foo/.cache/cabal/packages"], + Field + (Name + WithComments { + justComments = [], + unComments = Position 16 1} + "build-summary") + [ + FieldLine + WithComments { + justComments = [ + Comment + "-- build-log:" + (Position 17 1)], + unComments = Position 16 16} + "/home/foo/.cache/cabal/logs/build.log"], + Field + (Name + WithComments { + justComments = [], + unComments = Position 18 1} + "remote-build-reporting") + [ + FieldLine + WithComments { + justComments = [ + Comment + "-- report-planning-failure: False" + (Position 19 1), + Comment + "-- per-component: True" + (Position 20 1)], + unComments = Position 18 25} + "none"], + Field + (Name + WithComments { + justComments = [], + unComments = Position 21 1} + "jobs") + [ + FieldLine + WithComments { + justComments = [ + Comment + "-- keep-going: False" + (Position 22 1), + Comment + "-- offline: False" + (Position 23 1)], + unComments = Position 21 7} + "$ncpus"], + Field + (Name + WithComments { + justComments = [], + unComments = Position 24 1} + "installdir") + [ + FieldLine + WithComments { + justComments = [ + Comment + "-- token:" + (Position 25 1), + Comment + "-- username:" + (Position 26 1)], + unComments = Position 24 13} + "/home/foo/.local/bin"], + Section + (Name + WithComments { + justComments = [ + Comment + " -- keep-temp-files: False" + (Position 29 1), + Comment + " -- hoogle: False" + (Position 30 1)], + unComments = Position 28 1} + "haddock") + [] + [], + Section + (Name + WithComments { + justComments = [ + Comment + " -- interactive: False" + (Position 33 1), + Comment + " -- quiet: False" + (Position 34 1)], + unComments = Position 32 1} + "init") + [] + [], + Section + (Name + WithComments { + justComments = [ + Comment + " -- alex-location:" + (Position 37 1), + Comment + " -- ar-location:" + (Position 38 1)], + unComments = Position 36 1} + "program-locations") + [] + []] diff --git a/Cabal-tests/tests/ParserTests/comments/layout-fieldline-is-flag.cabal b/Cabal-tests/tests/ParserTests/comments/layout-fieldline-is-flag.cabal new file mode 100644 index 00000000000..adaebc31379 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/comments/layout-fieldline-is-flag.cabal @@ -0,0 +1,13 @@ +cabal-version: 2.2 +name: common +version: 0 +synopsis: Common-stanza demo +build-type: Simple + +test-suite doctests + type: exitcode-stdio-1.0 + main-is: doctests.hs + x-doctest-options: --preserve-it + -- The previous thing shouldn't be parsed as a comment because it's a flag + -- This however, is a comment + ghc-options: -Wall -threaded diff --git a/Cabal-tests/tests/ParserTests/comments/layout-fieldline-is-flag.expr b/Cabal-tests/tests/ParserTests/comments/layout-fieldline-is-flag.expr new file mode 100644 index 00000000000..22fa101117f --- /dev/null +++ b/Cabal-tests/tests/ParserTests/comments/layout-fieldline-is-flag.expr @@ -0,0 +1,8 @@ +Map.fromList + [ + _×_ + (Position 11 1) + " -- The previous thing shouldn't be parsed as a comment because it's a flag", + _×_ + (Position 12 1) + " -- This however, is a comment"] diff --git a/Cabal-tests/tests/ParserTests/comments/layout-interleaved-in-section.cabal b/Cabal-tests/tests/ParserTests/comments/layout-interleaved-in-section.cabal new file mode 100644 index 00000000000..4feeab2659a --- /dev/null +++ b/Cabal-tests/tests/ParserTests/comments/layout-interleaved-in-section.cabal @@ -0,0 +1,24 @@ +cabal-version: 2.2 +name: common +version: 0 +synopsis: Common-stanza demo +build-type: Simple + +source-repository head + Type: git + Location: https://github.com/hvr/-.git + +common deps + build-depends: + -- foo + base >=4.10 && <4.11, + -- bar + containers + -- baz + +library + import: deps + default-language: Haskell2010 + exposed-modules: ElseIf + build-depends: + ghc-prim diff --git a/Cabal-tests/tests/ParserTests/comments/layout-interleaved-in-section.expr b/Cabal-tests/tests/ParserTests/comments/layout-interleaved-in-section.expr new file mode 100644 index 00000000000..eabe7ac1e8b --- /dev/null +++ b/Cabal-tests/tests/ParserTests/comments/layout-interleaved-in-section.expr @@ -0,0 +1,11 @@ +Map.fromList + [ + _×_ + (Position 13 1) + " -- foo", + _×_ + (Position 15 1) + " -- bar", + _×_ + (Position 17 1) + " -- baz"] diff --git a/Cabal-tests/tests/ParserTests/comments/layout-many-sections.cabal b/Cabal-tests/tests/ParserTests/comments/layout-many-sections.cabal new file mode 100644 index 00000000000..4c67a264192 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/comments/layout-many-sections.cabal @@ -0,0 +1,31 @@ +cabal-version: 2.2 +name: common +version: 0 + -- comment 1 +synopsis: Common-stanza demo demo +build-type: Simple + +source-repository head + Type: git + -- comment 2 + Location: https://github.com/hvr/-.git + +common windows + if os(windows) + build-depends: Win32 + +common deps + build-depends: + base >=4.10 && <4.11, + containers + +library + import: deps + + -- comment 3 + default-language: Haskell2010 + exposed-modules: ElseIf +-- comment 4 + + build-depends: + ghc-prim diff --git a/Cabal-tests/tests/ParserTests/comments/layout-many-sections.expr b/Cabal-tests/tests/ParserTests/comments/layout-many-sections.expr new file mode 100644 index 00000000000..766117a5762 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/comments/layout-many-sections.expr @@ -0,0 +1,14 @@ +Map.fromList + [ + _×_ + (Position 4 1) + " -- comment 1", + _×_ + (Position 10 1) + " -- comment 2", + _×_ + (Position 25 1) + " -- comment 3", + _×_ + (Position 28 1) + "-- comment 4"] diff --git a/Cabal-tests/tests/ParserTests/comments/layout-nosections-after.cabal b/Cabal-tests/tests/ParserTests/comments/layout-nosections-after.cabal new file mode 100644 index 00000000000..a60e3734a22 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/comments/layout-nosections-after.cabal @@ -0,0 +1,8 @@ +name: comment-after-nameless-field +version: 1 +cabal-version: >= 1.8 +-- comment after + +library + build-depends: + base >= 4 diff --git a/Cabal-tests/tests/ParserTests/comments/layout-nosections-after.expr b/Cabal-tests/tests/ParserTests/comments/layout-nosections-after.expr new file mode 100644 index 00000000000..e758db9d2ea --- /dev/null +++ b/Cabal-tests/tests/ParserTests/comments/layout-nosections-after.expr @@ -0,0 +1,5 @@ +Map.fromList + [ + _×_ + (Position 4 1) + "-- comment after"] diff --git a/Cabal-tests/tests/ParserTests/comments/layout-nosections-before.cabal b/Cabal-tests/tests/ParserTests/comments/layout-nosections-before.cabal new file mode 100644 index 00000000000..e08cfc2fdd1 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/comments/layout-nosections-before.cabal @@ -0,0 +1,8 @@ +-- comment before +name: comment-before-nameless-field +version: 1 +cabal-version: >= 1.8 + +library + build-depends: + base >= 4 diff --git a/Cabal-tests/tests/ParserTests/comments/layout-nosections-before.expr b/Cabal-tests/tests/ParserTests/comments/layout-nosections-before.expr new file mode 100644 index 00000000000..b3216d5c8f8 --- /dev/null +++ b/Cabal-tests/tests/ParserTests/comments/layout-nosections-before.expr @@ -0,0 +1,5 @@ +Map.fromList + [ + _×_ + (Position 1 1) + "-- comment before"] diff --git a/Cabal-tests/tests/ParserTests/comments/layout-nosections-mixed.cabal b/Cabal-tests/tests/ParserTests/comments/layout-nosections-mixed.cabal new file mode 100644 index 00000000000..b3c9f48a7ca --- /dev/null +++ b/Cabal-tests/tests/ParserTests/comments/layout-nosections-mixed.cabal @@ -0,0 +1,12 @@ +-- comment before + +name: comment-after-nameless-field + -- comment within +version: 1 + -- another comment within +cabal-version: >= 1.8 +-- comment after + +library + build-depends: + base >= 4 diff --git a/Cabal-tests/tests/ParserTests/comments/layout-nosections-mixed.expr b/Cabal-tests/tests/ParserTests/comments/layout-nosections-mixed.expr new file mode 100644 index 00000000000..01bccdeef5c --- /dev/null +++ b/Cabal-tests/tests/ParserTests/comments/layout-nosections-mixed.expr @@ -0,0 +1,14 @@ +Map.fromList + [ + _×_ + (Position 1 1) + "-- comment before", + _×_ + (Position 4 1) + " -- comment within", + _×_ + (Position 6 1) + " -- another comment within", + _×_ + (Position 8 1) + "-- comment after"] diff --git a/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.expr b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.expr index 634b27b8828..3ddf33fb1df 100644 --- a/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.expr +++ b/Cabal-tests/tests/ParserTests/regressions/Octree-0.5.expr @@ -86,11 +86,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -199,11 +199,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -303,11 +303,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/anynone.expr b/Cabal-tests/tests/ParserTests/regressions/anynone.expr index 927605d6058..e2504a9be74 100644 --- a/Cabal-tests/tests/ParserTests/regressions/anynone.expr +++ b/Cabal-tests/tests/ParserTests/regressions/anynone.expr @@ -52,11 +52,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/big-version.expr b/Cabal-tests/tests/ParserTests/regressions/big-version.expr index 4d3659e4592..4764da0d35e 100644 --- a/Cabal-tests/tests/ParserTests/regressions/big-version.expr +++ b/Cabal-tests/tests/ParserTests/regressions/big-version.expr @@ -53,11 +53,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/common-conditional.expr b/Cabal-tests/tests/ParserTests/regressions/common-conditional.expr index 41e0fd5377a..6e1c25f7c66 100644 --- a/Cabal-tests/tests/ParserTests/regressions/common-conditional.expr +++ b/Cabal-tests/tests/ParserTests/regressions/common-conditional.expr @@ -69,11 +69,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -148,11 +148,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -242,11 +242,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -323,11 +323,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -402,11 +402,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -474,11 +474,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -569,11 +569,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -649,11 +649,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/common.expr b/Cabal-tests/tests/ParserTests/regressions/common.expr index e8c766460f2..67e4584eb12 100644 --- a/Cabal-tests/tests/ParserTests/regressions/common.expr +++ b/Cabal-tests/tests/ParserTests/regressions/common.expr @@ -67,11 +67,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -147,11 +147,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/common2.expr b/Cabal-tests/tests/ParserTests/regressions/common2.expr index af882207fc4..3305120e552 100644 --- a/Cabal-tests/tests/ParserTests/regressions/common2.expr +++ b/Cabal-tests/tests/ParserTests/regressions/common2.expr @@ -63,11 +63,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -166,11 +166,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -248,11 +248,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -353,11 +353,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -432,11 +432,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -535,11 +535,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -615,11 +615,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -695,11 +695,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/common3.expr b/Cabal-tests/tests/ParserTests/regressions/common3.expr index be783c4cab6..e8fb48890f2 100644 --- a/Cabal-tests/tests/ParserTests/regressions/common3.expr +++ b/Cabal-tests/tests/ParserTests/regressions/common3.expr @@ -67,11 +67,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -147,11 +147,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/elif.expr b/Cabal-tests/tests/ParserTests/regressions/elif.expr index e04821eaaef..66ce6c0177d 100644 --- a/Cabal-tests/tests/ParserTests/regressions/elif.expr +++ b/Cabal-tests/tests/ParserTests/regressions/elif.expr @@ -62,11 +62,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -133,11 +133,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/elif2.expr b/Cabal-tests/tests/ParserTests/regressions/elif2.expr index 88eb02d59d7..8e3adc55f10 100644 --- a/Cabal-tests/tests/ParserTests/regressions/elif2.expr +++ b/Cabal-tests/tests/ParserTests/regressions/elif2.expr @@ -62,11 +62,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -133,11 +133,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -209,11 +209,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -279,11 +279,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -355,11 +355,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.expr b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.expr index 02c4a4222c7..ac6faddb538 100644 --- a/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.expr +++ b/Cabal-tests/tests/ParserTests/regressions/encoding-0.8.expr @@ -67,11 +67,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/generics-sop.expr b/Cabal-tests/tests/ParserTests/regressions/generics-sop.expr index a7cdf1a4300..83123587f31 100644 --- a/Cabal-tests/tests/ParserTests/regressions/generics-sop.expr +++ b/Cabal-tests/tests/ParserTests/regressions/generics-sop.expr @@ -163,11 +163,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -334,11 +334,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -421,11 +421,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -526,11 +526,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -599,11 +599,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -673,11 +673,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -771,11 +771,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/hasktorch.expr b/Cabal-tests/tests/ParserTests/regressions/hasktorch.expr index 9dfa089a3d5..80c5927a1a1 100644 --- a/Cabal-tests/tests/ParserTests/regressions/hasktorch.expr +++ b/Cabal-tests/tests/ParserTests/regressions/hasktorch.expr @@ -268,11 +268,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -603,11 +603,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -848,11 +848,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -1051,11 +1051,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -1391,11 +1391,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -2713,11 +2713,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -2805,11 +2805,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -5034,11 +5034,11 @@ GenericPackageDescription { cppOptions = [ "-DCUDA", "-DHASKTORCH_INTERNAL_CUDA"], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -6406,11 +6406,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -6499,11 +6499,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -8169,11 +8169,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -8660,11 +8660,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -9426,11 +9426,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -9549,11 +9549,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -9657,11 +9657,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -9765,11 +9765,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -9862,11 +9862,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -9960,11 +9960,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.expr b/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.expr index 553b88dc595..47647f9b9cf 100644 --- a/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.expr +++ b/Cabal-tests/tests/ParserTests/regressions/hidden-main-lib.expr @@ -54,11 +54,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation.expr b/Cabal-tests/tests/ParserTests/regressions/indentation.expr index f36a8997717..9164dace33a 100644 --- a/Cabal-tests/tests/ParserTests/regressions/indentation.expr +++ b/Cabal-tests/tests/ParserTests/regressions/indentation.expr @@ -63,11 +63,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation2.expr b/Cabal-tests/tests/ParserTests/regressions/indentation2.expr index 11afbcfd5d3..3f7612ef50f 100644 --- a/Cabal-tests/tests/ParserTests/regressions/indentation2.expr +++ b/Cabal-tests/tests/ParserTests/regressions/indentation2.expr @@ -56,11 +56,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/indentation3.expr b/Cabal-tests/tests/ParserTests/regressions/indentation3.expr index 964bad3f924..87d3376c648 100644 --- a/Cabal-tests/tests/ParserTests/regressions/indentation3.expr +++ b/Cabal-tests/tests/ParserTests/regressions/indentation3.expr @@ -58,11 +58,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5055.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5055.expr index 996fa26eece..5fcae0b709b 100644 --- a/Cabal-tests/tests/ParserTests/regressions/issue-5055.expr +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5055.expr @@ -57,11 +57,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -143,11 +143,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -231,11 +231,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5846.expr b/Cabal-tests/tests/ParserTests/regressions/issue-5846.expr index c3e08359046..44d61d1d795 100644 --- a/Cabal-tests/tests/ParserTests/regressions/issue-5846.expr +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5846.expr @@ -51,11 +51,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.expr index 001d3c86515..876c944b620 100644 --- a/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.expr +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-a.expr @@ -51,11 +51,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -149,11 +149,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -219,11 +219,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -302,11 +302,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.expr index ca99e3d554f..14eb64397df 100644 --- a/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.expr +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-b.expr @@ -51,11 +51,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -149,11 +149,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -219,11 +219,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -312,11 +312,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.expr index b2f47a1a938..4d4450a78cb 100644 --- a/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.expr +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-c.expr @@ -51,11 +51,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -149,11 +149,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.expr b/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.expr index ce7c453e697..c38bd51f941 100644 --- a/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.expr +++ b/Cabal-tests/tests/ParserTests/regressions/issue-6083-pkg-pkg.expr @@ -51,11 +51,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-774.expr b/Cabal-tests/tests/ParserTests/regressions/issue-774.expr index 4aeb65cb960..31ea274249e 100644 --- a/Cabal-tests/tests/ParserTests/regressions/issue-774.expr +++ b/Cabal-tests/tests/ParserTests/regressions/issue-774.expr @@ -61,11 +61,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.expr b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.expr index b6dc81fee1b..bf3803b9417 100644 --- a/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.expr +++ b/Cabal-tests/tests/ParserTests/regressions/jaeger-flamegraph.expr @@ -93,11 +93,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -194,11 +194,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -361,11 +361,11 @@ GenericPackageDescription { (MajorBoundVersion (mkVersion [4, 2, 1]))], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.expr index 3a1d7d5f075..e8d07f99d94 100644 --- a/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.expr +++ b/Cabal-tests/tests/ParserTests/regressions/leading-comma-2.expr @@ -61,11 +61,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/leading-comma.expr b/Cabal-tests/tests/ParserTests/regressions/leading-comma.expr index 230ebf53136..15d01d4703d 100644 --- a/Cabal-tests/tests/ParserTests/regressions/leading-comma.expr +++ b/Cabal-tests/tests/ParserTests/regressions/leading-comma.expr @@ -54,11 +54,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq1.expr b/Cabal-tests/tests/ParserTests/regressions/libpq1.expr index b331abffcca..e3f93b194a4 100644 --- a/Cabal-tests/tests/ParserTests/regressions/libpq1.expr +++ b/Cabal-tests/tests/ParserTests/regressions/libpq1.expr @@ -144,11 +144,11 @@ GenericPackageDescription { (mkVersion [0]))], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -250,11 +250,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -337,11 +337,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -424,11 +424,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [ @@ -499,11 +499,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -569,11 +569,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -637,11 +637,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -707,11 +707,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/libpq2.expr b/Cabal-tests/tests/ParserTests/regressions/libpq2.expr index 9f6a16ada6e..0e0403dd8c0 100644 --- a/Cabal-tests/tests/ParserTests/regressions/libpq2.expr +++ b/Cabal-tests/tests/ParserTests/regressions/libpq2.expr @@ -149,11 +149,11 @@ GenericPackageDescription { (OrLaterVersion (mkVersion [0]))], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -255,11 +255,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -342,11 +342,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -429,11 +429,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [ @@ -501,11 +501,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -571,11 +571,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -639,11 +639,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -709,11 +709,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-1.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-1.expr index 0a137660468..1b9640c92a5 100644 --- a/Cabal-tests/tests/ParserTests/regressions/mixin-1.expr +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-1.expr @@ -55,11 +55,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-2.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-2.expr index 6c2239df825..decc098f78f 100644 --- a/Cabal-tests/tests/ParserTests/regressions/mixin-2.expr +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-2.expr @@ -55,11 +55,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/mixin-3.expr b/Cabal-tests/tests/ParserTests/regressions/mixin-3.expr index a4a94aac32c..e5278af9017 100644 --- a/Cabal-tests/tests/ParserTests/regressions/mixin-3.expr +++ b/Cabal-tests/tests/ParserTests/regressions/mixin-3.expr @@ -55,11 +55,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/monad-param.expr b/Cabal-tests/tests/ParserTests/regressions/monad-param.expr index db28c928ddb..8ab441164a5 100644 --- a/Cabal-tests/tests/ParserTests/regressions/monad-param.expr +++ b/Cabal-tests/tests/ParserTests/regressions/monad-param.expr @@ -63,11 +63,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.expr b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.expr index d2f1efdd913..d9b82eb2aec 100644 --- a/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.expr +++ b/Cabal-tests/tests/ParserTests/regressions/multiple-libs-2.expr @@ -54,11 +54,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -135,11 +135,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/noVersion.expr b/Cabal-tests/tests/ParserTests/regressions/noVersion.expr index 838f87733eb..1384c3eef4a 100644 --- a/Cabal-tests/tests/ParserTests/regressions/noVersion.expr +++ b/Cabal-tests/tests/ParserTests/regressions/noVersion.expr @@ -54,11 +54,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.expr b/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.expr index ccfe4421c7b..0bbfcbbbbac 100644 --- a/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.expr +++ b/Cabal-tests/tests/ParserTests/regressions/nothing-unicode.expr @@ -69,11 +69,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -140,11 +140,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/shake.expr b/Cabal-tests/tests/ParserTests/regressions/shake.expr index 5be08b04064..46b3bfa2729 100644 --- a/Cabal-tests/tests/ParserTests/regressions/shake.expr +++ b/Cabal-tests/tests/ParserTests/regressions/shake.expr @@ -189,11 +189,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -480,11 +480,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = ["-DPORTABLE"], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -550,11 +550,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -627,11 +627,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -697,11 +697,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -778,11 +778,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -857,11 +857,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -1183,11 +1183,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -1253,11 +1253,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = ["-DPORTABLE"], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -1320,11 +1320,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -1394,11 +1394,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -1461,11 +1461,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -1539,11 +1539,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -1617,11 +1617,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -1992,11 +1992,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -2064,11 +2064,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -2136,11 +2136,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = ["-DPORTABLE"], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -2207,11 +2207,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -2285,11 +2285,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -2356,11 +2356,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -2438,11 +2438,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-1.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-1.expr index 88500d2d365..d3a3797c1c9 100644 --- a/Cabal-tests/tests/ParserTests/regressions/spdx-1.expr +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-1.expr @@ -52,11 +52,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-2.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-2.expr index 9cd00ea1103..a9c2370712b 100644 --- a/Cabal-tests/tests/ParserTests/regressions/spdx-2.expr +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-2.expr @@ -56,11 +56,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/spdx-3.expr b/Cabal-tests/tests/ParserTests/regressions/spdx-3.expr index e8b2eca8989..83d37fc29d5 100644 --- a/Cabal-tests/tests/ParserTests/regressions/spdx-3.expr +++ b/Cabal-tests/tests/ParserTests/regressions/spdx-3.expr @@ -56,11 +56,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.expr b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.expr index 2db686aa40f..5cd098d5a94 100644 --- a/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.expr +++ b/Cabal-tests/tests/ParserTests/regressions/th-lift-instances.expr @@ -81,11 +81,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -254,11 +254,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -435,11 +435,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -544,11 +544,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/version-sets.expr b/Cabal-tests/tests/ParserTests/regressions/version-sets.expr index c086ae618aa..6242af7cb32 100644 --- a/Cabal-tests/tests/ParserTests/regressions/version-sets.expr +++ b/Cabal-tests/tests/ParserTests/regressions/version-sets.expr @@ -78,11 +78,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.expr b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.expr index e4e6a457a3d..3c9821a1185 100644 --- a/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.expr +++ b/Cabal-tests/tests/ParserTests/regressions/wl-pprint-indef.expr @@ -72,11 +72,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], @@ -161,11 +161,11 @@ GenericPackageDescription { buildTools = [], buildToolDepends = [], cppOptions = [], - jsppOptions = [], asmOptions = [], cmmOptions = [], ccOptions = [], cxxOptions = [], + jsppOptions = [], ldOptions = [], hsc2hsOptions = [], pkgconfigDepends = [], diff --git a/Cabal-tree-diff/src/Data/TreeDiff/Instances/Cabal.hs b/Cabal-tree-diff/src/Data/TreeDiff/Instances/Cabal.hs index f7e7ca5b7b6..9050b1defbe 100644 --- a/Cabal-tree-diff/src/Data/TreeDiff/Instances/Cabal.hs +++ b/Cabal-tree-diff/src/Data/TreeDiff/Instances/Cabal.hs @@ -13,9 +13,11 @@ import Data.TreeDiff.Instances.CabalVersion () import Distribution.Backpack (OpenModule, OpenUnitId) import Distribution.CabalSpecVersion (CabalSpecVersion) import Distribution.Compiler (CompilerFlavor, CompilerId, PerCompilerFlavor) +import Distribution.Fields.Field (Field, Name, FieldLine, SectionArg, Comment, WithComments) import Distribution.InstalledPackageInfo (AbiDependency, ExposedModule, InstalledPackageInfo) import Distribution.ModuleName (ModuleName) import Distribution.PackageDescription +import Distribution.Parsec.Position (Position) import Distribution.Simple.Compiler (DebugInfoLevel, OptimisationLevel, ProfDetailLevel) import Distribution.Simple.InstallDirs import Distribution.Simple.InstallDirs.Internal @@ -56,6 +58,12 @@ instance ToExpr (SymbolicPathX allowAbs from to) instance ToExpr a => ToExpr (InstallDirs a) +instance (ToExpr ann) => ToExpr (Comment ann) +instance (ToExpr ann) => ToExpr (WithComments ann) +instance (ToExpr ann) => ToExpr (Field ann) +instance (ToExpr ann) => ToExpr (FieldLine ann) +instance (ToExpr ann) => ToExpr (Name ann) +instance (ToExpr ann) => ToExpr (SectionArg ann) instance ToExpr AbiDependency instance ToExpr AbiHash instance ToExpr Arch @@ -80,6 +88,7 @@ instance ToExpr FlagName instance ToExpr ForeignLib instance ToExpr ForeignLibOption instance ToExpr ForeignLibType +instance ToExpr AnnotatedGenericPackageDescription instance ToExpr GenericPackageDescription instance ToExpr HaddockTarget instance ToExpr IncludeRenaming @@ -110,6 +119,7 @@ instance ToExpr PkgconfigDependency instance ToExpr PkgconfigName instance ToExpr PkgconfigVersion instance ToExpr PkgconfigVersionRange +instance ToExpr Position instance ToExpr ProfDetailLevel instance ToExpr RepoKind instance ToExpr RepoType