From git at git.haskell.org Tue Apr 1 09:05:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Apr 2014 09:05:16 +0000 (UTC) Subject: [commit: packages/base] master: Typo (52c0b09) Message-ID: <20140401090516.4106F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/52c0b09036c36f1ed928663abb2f295fd36a88bb/base >--------------------------------------------------------------- commit 52c0b09036c36f1ed928663abb2f295fd36a88bb Author: Jose Pedro Magalhaes Date: Tue Apr 1 10:05:11 2014 +0100 Typo >--------------------------------------------------------------- 52c0b09036c36f1ed928663abb2f295fd36a88bb GHC/TypeLits.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/GHC/TypeLits.hs b/GHC/TypeLits.hs index 94a4288..083ae4d 100644 --- a/GHC/TypeLits.hs +++ b/GHC/TypeLits.hs @@ -62,7 +62,7 @@ data Symbol class KnownNat (n :: Nat) where natSing :: SNat n --- | This class gives the integer associated with a type-level symbol. +-- | This class gives the string associated with a type-level symbol. -- There are instances of the class for every concrete literal: "hello", etc. -- -- /Since: 4.7.0.0/ From git at git.haskell.org Tue Apr 1 11:39:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Apr 2014 11:39:11 +0000 (UTC) Subject: [commit: ghc] master: Support thin archive format (5d7f590) Message-ID: <20140401113911.8899B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5d7f59018703b94ebfe96cbef5574ec396a1c051/ghc >--------------------------------------------------------------- commit 5d7f59018703b94ebfe96cbef5574ec396a1c051 Author: Simon Marlow Date: Fri Mar 28 14:43:53 2014 +0000 Support thin archive format This is a patch from FB's internal build of GHC that I'm pushing upstream. Author: Andrew Gallagher This diff adds simple thin archive support to ghc's linker code, which basically just entails finding the member data from disk rather than from inside the archive (except for the case of the symbol index and gnu filename index, where the member data is still inline). >--------------------------------------------------------------- 5d7f59018703b94ebfe96cbef5574ec396a1c051 rts/Linker.c | 139 +++++++++++++++++++++++++++++++++++++--------------------- 1 file changed, 90 insertions(+), 49 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5d7f59018703b94ebfe96cbef5574ec396a1c051 From git at git.haskell.org Tue Apr 1 18:08:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Apr 2014 18:08:30 +0000 (UTC) Subject: [commit: haddock] v2.14: Bump version to 2.14.2 (5d2b82f) Message-ID: <20140401180831.0F2162406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/5d2b82f2f3b2e4e21f7f831fdfcb046c2f0c04c2 >--------------------------------------------------------------- commit 5d2b82f2f3b2e4e21f7f831fdfcb046c2f0c04c2 Author: Mateusz Kowalczyk Date: Tue Apr 1 18:39:23 2014 +0100 Bump version to 2.14.2 >--------------------------------------------------------------- 5d2b82f2f3b2e4e21f7f831fdfcb046c2f0c04c2 haddock.cabal | 2 +- html-test/ref/A.html | 2 +- html-test/ref/AdvanceTypes.html | 2 +- html-test/ref/B.html | 2 +- html-test/ref/Bold.html | 2 +- html-test/ref/Bug1.html | 2 +- html-test/ref/Bug195.html | 2 +- html-test/ref/Bug2.html | 2 +- html-test/ref/Bug3.html | 2 +- html-test/ref/Bug4.html | 2 +- html-test/ref/Bug6.html | 2 +- html-test/ref/Bug7.html | 2 +- html-test/ref/Bug8.html | 2 +- html-test/ref/BugDeprecated.html | 2 +- html-test/ref/BugExportHeadings.html | 2 +- html-test/ref/Bugs.html | 2 +- html-test/ref/DeprecatedClass.html | 2 +- html-test/ref/DeprecatedData.html | 2 +- html-test/ref/DeprecatedFunction.html | 2 +- html-test/ref/DeprecatedFunction2.html | 2 +- html-test/ref/DeprecatedFunction3.html | 2 +- html-test/ref/DeprecatedModule.html | 2 +- html-test/ref/DeprecatedModule2.html | 2 +- html-test/ref/DeprecatedNewtype.html | 2 +- html-test/ref/DeprecatedReExport.html | 2 +- html-test/ref/DeprecatedRecord.html | 2 +- html-test/ref/DeprecatedTypeFamily.html | 2 +- html-test/ref/DeprecatedTypeSynonym.html | 2 +- html-test/ref/Examples.html | 2 +- html-test/ref/Extensions.html | 2 +- html-test/ref/FunArgs.html | 2 +- html-test/ref/GADTRecords.html | 2 +- html-test/ref/Hash.html | 2 +- html-test/ref/HiddenInstances.html | 2 +- html-test/ref/HiddenInstancesB.html | 2 +- html-test/ref/Hyperlinks.html | 2 +- html-test/ref/IgnoreExports.html | 2 +- html-test/ref/ImplicitParams.html | 2 +- html-test/ref/Minimal.html | 2 +- html-test/ref/ModuleWithWarning.html | 2 +- html-test/ref/NamedDoc.html | 2 +- html-test/ref/Nesting.html | 2 +- html-test/ref/NoLayout.html | 2 +- html-test/ref/NonGreedy.html | 2 +- html-test/ref/Operators.html | 2 +- html-test/ref/PatternSyns.html | 2 +- html-test/ref/Properties.html | 2 +- html-test/ref/PruneWithWarning.html | 2 +- html-test/ref/QuasiExpr.html | 2 +- html-test/ref/QuasiQuote.html | 2 +- html-test/ref/SpuriousSuperclassConstraints.html | 2 +- html-test/ref/TH.html | 2 +- html-test/ref/TH2.html | 2 +- html-test/ref/Test.html | 2 +- html-test/ref/Ticket112.html | 2 +- html-test/ref/Ticket253_1.html | 2 +- html-test/ref/Ticket253_2.html | 2 +- html-test/ref/Ticket61.html | 2 +- html-test/ref/Ticket75.html | 2 +- html-test/ref/TitledPicture.html | 2 +- html-test/ref/TypeFamilies.html | 2 +- html-test/ref/TypeFamilies2.html | 2 +- html-test/ref/TypeOperators.html | 2 +- html-test/ref/Unicode.html | 2 +- html-test/ref/Visible.html | 2 +- 65 files changed, 65 insertions(+), 65 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5d2b82f2f3b2e4e21f7f831fdfcb046c2f0c04c2 From git at git.haskell.org Tue Apr 1 18:08:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Apr 2014 18:08:32 +0000 (UTC) Subject: [commit: haddock] v2.14: Drop needless --split-objs which slows us down. (76600a6) Message-ID: <20140401180833.1178C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/76600a683004b61b9871b92b078abf7cf8de1657 >--------------------------------------------------------------- commit 76600a683004b61b9871b92b078abf7cf8de1657 Author: Mateusz Kowalczyk Date: Sat Mar 22 16:36:16 2014 +0000 Drop needless --split-objs which slows us down. Involves tiny cleanup of all the dynflag bindings. Fixes #292. >--------------------------------------------------------------- 76600a683004b61b9871b92b078abf7cf8de1657 src/Haddock.hs | 30 ++++++++++++++---------------- 1 file changed, 14 insertions(+), 16 deletions(-) diff --git a/src/Haddock.hs b/src/Haddock.hs index e4c7fdc..a7bf45d 100644 --- a/src/Haddock.hs +++ b/src/Haddock.hs @@ -314,22 +314,20 @@ readInterfaceFiles name_cache_accessor pairs = do -- | Start a GHC session with the -haddock flag set. Also turn off -- compilation and linking. Then run the given 'Ghc' action. withGhc :: String -> [String] -> (DynFlags -> Ghc a) -> IO a -withGhc libDir flags ghcActs = do - runGhc (Just libDir) $ do - dynflags <- getSessionDynFlags - let dynflags' = gopt_set dynflags Opt_Haddock - let dynflags'' = dynflags' { - hscTarget = HscNothing, - ghcMode = CompManager, - ghcLink = NoLink - } - dynflags''' <- parseGhcFlags dynflags'' - defaultCleanupHandler dynflags''' $ do - -- ignore the following return-value, which is a list of packages - -- that may need to be re-linked: Haddock doesn't do any - -- dynamic or static linking at all! - _ <- setSessionDynFlags dynflags''' - ghcActs dynflags''' +withGhc libDir flags ghcActs = runGhc (Just libDir) $ do + dynflags <- getSessionDynFlags + dynflags' <- parseGhcFlags (gopt_set dynflags Opt_Haddock) { + hscTarget = HscNothing, + ghcMode = CompManager, + ghcLink = NoLink + } + let dynflags'' = gopt_unset dynflags' Opt_SplitObjs + defaultCleanupHandler dynflags'' $ do + -- ignore the following return-value, which is a list of packages + -- that may need to be re-linked: Haddock doesn't do any + -- dynamic or static linking at all! + _ <- setSessionDynFlags dynflags'' + ghcActs dynflags'' where parseGhcFlags :: MonadIO m => DynFlags -> m DynFlags parseGhcFlags dynflags = do From git at git.haskell.org Tue Apr 1 18:08:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Apr 2014 18:08:35 +0000 (UTC) Subject: [commit: haddock] v2.14: Drop leading whitespace in @-style blocks. (6a5053e) Message-ID: <20140401180835.1FBBA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/6a5053e64dfb7781b2202d58fca88bbd665b1d5a >--------------------------------------------------------------- commit 6a5053e64dfb7781b2202d58fca88bbd665b1d5a Author: Mateusz Kowalczyk Date: Mon Mar 31 18:29:04 2014 +0100 Drop leading whitespace in @-style blocks. Fixes #201. >--------------------------------------------------------------- 6a5053e64dfb7781b2202d58fca88bbd665b1d5a CHANGES | 2 + html-test/ref/{IgnoreExports.html => Bug201.html} | 53 +++++++++++---------- html-test/src/Bug201.hs | 28 +++++++++++ src/Haddock/Parser.hs | 31 ++++++++++-- test/Haddock/ParserSpec.hs | 28 +++++++++-- 5 files changed, 111 insertions(+), 31 deletions(-) diff --git a/CHANGES b/CHANGES index d587201..d1a3f6f 100644 --- a/CHANGES +++ b/CHANGES @@ -2,6 +2,8 @@ Changes in version 2.14.2 * Print kind signatures GADTs (#85) + * Drop single leading whitespace when reasonable from @-style blocks (#201) + Changes in version 2.14.1 * Render * and -> with their UnicodeSyntax equivalents if -U is enabled diff --git a/html-test/ref/IgnoreExports.html b/html-test/ref/Bug201.html similarity index 75% copy from html-test/ref/IgnoreExports.html copy to html-test/ref/Bug201.html index e1dab56..8b596cf 100644 --- a/html-test/ref/IgnoreExports.html +++ b/html-test/ref/Bug201.html @@ -3,13 +3,13 @@ >IgnoreExportsBug201

IgnoreExports

Bug201

Documentation

foo :: Int

f :: ()

documentation for foo

This leading whitespace
+should be dropped
+

bar :: Int

g :: ()

documentation for bar

 But this one
+ should not
+
this should
+be dropped
and so should this
+because there's a space before closing @
+
this should +> be dropped + +@ + and so should this + because there's a space before closing @ + @ +-} +g :: () +g = () diff --git a/src/Haddock/Parser.hs b/src/Haddock/Parser.hs index cd7bb02..bd5cd20 100644 --- a/src/Haddock/Parser.hs +++ b/src/Haddock/Parser.hs @@ -2,6 +2,7 @@ {-# LANGUAGE StandaloneDeriving , FlexibleInstances, UndecidableInstances , IncoherentInstances #-} +{-# LANGUAGE LambdaCase #-} -- | -- Module : Haddock.Parser -- Copyright : (c) Mateusz Kowalczyk 2013, @@ -21,7 +22,7 @@ import Control.Applicative import Data.Attoparsec.ByteString.Char8 hiding (parse, take, endOfLine) import qualified Data.ByteString.Char8 as BS import Data.Char (chr, isAsciiUpper) -import Data.List (stripPrefix, intercalate) +import Data.List (stripPrefix, intercalate, unfoldr) import Data.Maybe (fromMaybe) import Data.Monoid import DynFlags @@ -59,7 +60,8 @@ parseParas d = parse (p <* skipSpace) . encodeUtf8 . (++ "\n") p :: Parser (Doc RdrName) p = mconcat <$> paragraph d `sepBy` many (skipHorizontalSpace *> "\n") --- | Parse a text paragraph. +-- | Parse a text paragraph. Actually just a wrapper over 'parseStringBS' which +-- drops leading whitespace and encodes the string to UTF8 first. parseString :: DynFlags -> String -> Doc RdrName parseString d = parseStringBS d . encodeUtf8 . dropWhile isSpace @@ -366,8 +368,31 @@ property = DocProperty . strip . decodeUtf8 <$> ("prop>" *> takeWhile1 (/= '\n') -- for markup. codeblock :: DynFlags -> Parser (Doc RdrName) codeblock d = - DocCodeBlock . parseStringBS d <$> ("@" *> skipHorizontalSpace *> "\n" *> block' <* "@") + DocCodeBlock . parseStringBS d . dropSpaces + <$> ("@" *> skipHorizontalSpace *> "\n" *> block' <* "@") where + dropSpaces xs = + let rs = decodeUtf8 xs + in case splitByNl rs of + [] -> xs + ys -> case last ys of + ' ':_ -> case mapM dropSpace ys of + Nothing -> xs + Just zs -> encodeUtf8 $ intercalate "\n" zs + _ -> xs + + -- This is necessary because ?lines? swallows up a trailing newline + -- and we lose information about whether the last line belongs to @ or to + -- text which we need to decide whether we actually want to be dropping + -- anything at all. + splitByNl = unfoldr (\case '\n':s -> Just (span (/= '\n') s) + _ -> Nothing) + . ('\n' :) + + dropSpace "" = Just "" + dropSpace (' ':xs) = Just xs + dropSpace _ = Nothing + block' = scan False p where p isNewline c diff --git a/test/Haddock/ParserSpec.hs b/test/Haddock/ParserSpec.hs index db843cc..f44b7d0 100644 --- a/test/Haddock/ParserSpec.hs +++ b/test/Haddock/ParserSpec.hs @@ -432,12 +432,34 @@ spec = before initStaticOpts $ do ] `shouldParseTo` DocCodeBlock "foo\n@\nbar\n" it "accepts horizontal space before the @" $ do + unlines [ " @" + , "foo" + , "" + , "bar" + , "@" + ] `shouldParseTo` DocCodeBlock "foo\n\nbar\n" + + it "strips a leading space from a @ block if present" $ do + unlines [ " @" + , " hello" + , " world" + , " @" + ] `shouldParseTo` DocCodeBlock "hello\nworld\n" + unlines [ " @" - , " foo" + , " hello" , "" - , " bar" + , " world" , " @" - ] `shouldParseTo` DocCodeBlock " foo\n\n bar\n " + ] `shouldParseTo` DocCodeBlock "hello\n\nworld\n" + + it "only drops whitespace if there's some before closing @" $ do + unlines [ "@" + , " Formatting" + , " matters." + , "@" + ] + `shouldParseTo` DocCodeBlock " Formatting\n matters.\n" it "accepts unicode" $ do "@foo ?????? bar@" `shouldParseTo` DocCodeBlock "foo ?????? bar" From git at git.haskell.org Tue Apr 1 18:08:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Apr 2014 18:08:37 +0000 (UTC) Subject: [commit: haddock] v2.14: Crash when exporting record selectors of data family instances (32c8d6c) Message-ID: <20140401180837.58B0C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/32c8d6c36798a0d70f477ee56cc14099ee3c723c >--------------------------------------------------------------- commit 32c8d6c36798a0d70f477ee56cc14099ee3c723c Author: Niklas Haas Date: Mon Mar 31 20:02:36 2014 +0200 Crash when exporting record selectors of data family instances This fixes bug #294. This also fixes a related but never-before-mentioned bug about the display of GADT record selectors with non-polymorphic type signatures. Note: Associated data type constructors fail to show up if nothing is exported that they could be attached to. Exporting any of the data types in the instance head, or the class + data family itself, causes them to show up, but in the absence of either of these, exporting just the associated data type with the constructor itself will result in it being hidden. The only scenario I can come up that would involve this kind of situation involved OverlappingInstances, and even then it can be mitigated by just exporting the class itself, so I'm not going to solve it since the logic would most likely be very complicated. >--------------------------------------------------------------- 32c8d6c36798a0d70f477ee56cc14099ee3c723c .../ref/{HiddenInstances.html => Bug294.html} | 148 ++++++++++---------- html-test/src/Bug294.hs | 37 +++++ src/Haddock/Interface/Create.hs | 34 +++-- 3 files changed, 136 insertions(+), 83 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 32c8d6c36798a0d70f477ee56cc14099ee3c723c From git at git.haskell.org Tue Apr 1 18:08:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Apr 2014 18:08:39 +0000 (UTC) Subject: [commit: haddock] v2.14: Fix a few typos (0ca96fb) Message-ID: <20140401180839.72D062406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/0ca96fb4a79265bac69473b46bb62489e43d397f >--------------------------------------------------------------- commit 0ca96fb4a79265bac69473b46bb62489e43d397f Author: Herbert Valerio Riedel Date: Sun Mar 23 18:01:01 2014 +0100 Fix a few typos Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 0ca96fb4a79265bac69473b46bb62489e43d397f CHANGES | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/CHANGES b/CHANGES index a98a0e0..7929160 100644 --- a/CHANGES +++ b/CHANGES @@ -96,7 +96,7 @@ Changes in version 2.11.0 * Improved --qual option (no crashes, proper error messages) - * A new --qual option "aliased" which qualifies identifers by the module alias + * A new --qual option "aliased" which qualifies identifiers by the module alias used in the source code * The Haddock API restores GHC's static flags after invocation @@ -275,7 +275,7 @@ Changed in version 2.5.0: * Add --use-unicode flag for displaying prettier versions of common symbols - * Mutiple verbosity levels: remove --verbose and add --verbosity=n + * Multiple verbosity levels: remove --verbose and add --verbosity=n ----------------------------------------------------------------------------- @@ -304,7 +304,7 @@ Changed in version 2.4.2: * Do not indicate that a constructor argument is unboxed - * Fix problem with with non-working links to ghc-prim + * Fix problem with non-working links to ghc-prim * Allow referring to a specific section within a module in a module link (#65) @@ -400,7 +400,7 @@ Changes in version 2.0.0.0: * Haddock can generate documentation for some of the language extensions in GHC 6.8.2 - * Format of module attributes has changed. The only way of specifiying + * Format of module attributes has changed. The only way of specifying module attributes is via a new OPTIONS_HADDOCK pragma. Example: {-# OPTIONS_HADDOCK hide, prune #-} From git at git.haskell.org Tue Apr 1 18:08:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Apr 2014 18:08:41 +0000 (UTC) Subject: [commit: haddock] v2.14: Print kind signatures on GADTs (72d5d54) Message-ID: <20140401180842.186562406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/72d5d5490a324d3599085a009ce2d45a076988b6 >--------------------------------------------------------------- commit 72d5d5490a324d3599085a009ce2d45a076988b6 Author: Mateusz Kowalczyk Date: Tue Apr 1 18:44:47 2014 +0100 Print kind signatures on GADTs >--------------------------------------------------------------- 72d5d5490a324d3599085a009ce2d45a076988b6 CHANGES | 4 ++ html-test/ref/AdvanceTypes.html | 2 +- html-test/ref/{Ticket253_2.html => Bug85.html} | 86 +++++++++++++++--------- html-test/src/Bug85.hs | 15 +++++ src/Haddock/Backends/Xhtml/Decl.hs | 16 +++-- 5 files changed, 85 insertions(+), 38 deletions(-) diff --git a/CHANGES b/CHANGES index 7929160..d587201 100644 --- a/CHANGES +++ b/CHANGES @@ -1,3 +1,7 @@ +Changes in version 2.14.2 + + * Print kind signatures GADTs (#85) + Changes in version 2.14.1 * Render * and -> with their UnicodeSyntax equivalents if -U is enabled diff --git a/html-test/ref/AdvanceTypes.html b/html-test/ref/AdvanceTypes.html index 489b6e1..b594321 100644 --- a/html-test/ref/AdvanceTypes.html +++ b/html-test/ref/AdvanceTypes.html @@ -50,7 +50,7 @@ window.onload = function () {pageLoad();setSynopsis("mini_AdvanceTypes.html");}; >data Pattern :: [*] -> * where

Ticket253_2Bug85

Ticket253_2

Synopsis

Bug85

Documentation

bar :: Intdata Foo :: (* -> *) -> * -> * where

Comment

Constructors

Bar :: f x -> Foo f (f x) 
data Baz :: * where

data Qux where

Constructors

Quux :: Qux 

  • f :: ()
  • (<^>) :: (a -> a) -> a -> a
  • (<^) :: a -> a -> a
  • g(^>) :: a -> a -> a
  • (⋆^) :: a -> a -> a
  • f :: ()
Documentation

f :: ()

This leading whitespace
-should be dropped
-
(<^>) :: (a -> a) -> a -> a

(<^) :: a -> a -> a

(^>) :: a -> a -> a

(⋆^) :: a -> a -> a

gf :: ()

 But this one
- should not
-
this should
-be dropped
and so should this
-because there's a space before closing @
-

Links to <^> and ^>, <^ and ⋆^.

) :: (a -> a) -> a -> a +x <^> y = x y + +(<^) :: a -> a -> a +x <^ y = x + +(^>) :: a -> a -> a +x ^> y = y + +(?^) :: a -> a -> a +x ?^ y = y + +-- | Links to '<^>' and '^>', '<^' and '?^'. +f :: () +f = () diff --git a/src/Haddock/Parser.hs b/src/Haddock/Parser.hs index bd5cd20..ece9291 100644 --- a/src/Haddock/Parser.hs +++ b/src/Haddock/Parser.hs @@ -419,13 +419,21 @@ autoUrl = mkLink <$> url -- characters and does no actual validation itself. parseValid :: Parser String parseValid = do - vs <- many' $ satisfy (`elem` "_.!#$%&*+/<=>?@\\|-~:") <|> digit <|> letter_ascii + vs' <- many' $ utf8String "?" <|> return <$> idChar + let vs = concat vs' c <- peekChar case c of Just '`' -> return vs Just '\'' -> (\x -> vs ++ "'" ++ x) <$> ("'" *> parseValid) <|> return vs _ -> fail "outofvalid" + where + idChar = satisfy (`elem` "_.!#$%&*+/<=>?@\\|-~:^") + <|> digit <|> letter_ascii + +-- | Parses UTF8 strings from ByteString streams. +utf8String :: String -> Parser String +utf8String x = decodeUtf8 <$> string (encodeUtf8 x) -- | Parses identifiers with help of 'parseValid'. Asks GHC for 'RdrName' from the -- string it deems valid. From git at git.haskell.org Fri Apr 11 18:04:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Apr 2014 18:04:03 +0000 (UTC) Subject: [commit: haddock] v2.14: We don't actually want unicode here (99e3705) Message-ID: <20140411180404.9173024069@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/99e37051a544a2abd801f4ec69106bcb93f9e508 >--------------------------------------------------------------- commit 99e37051a544a2abd801f4ec69106bcb93f9e508 Author: Mateusz Kowalczyk Date: Fri Apr 11 16:52:23 2014 +0100 We don't actually want unicode here >--------------------------------------------------------------- 99e37051a544a2abd801f4ec69106bcb93f9e508 html-test/src/Bug85.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/html-test/src/Bug85.hs b/html-test/src/Bug85.hs index 9c5b768..e29b266 100644 --- a/html-test/src/Bug85.hs +++ b/html-test/src/Bug85.hs @@ -1,5 +1,4 @@ {-# LANGUAGE GADTs, KindSignatures #-} -{-# OPTIONS_HADDOCK use-unicode #-} module Bug85 where -- explicitly stated non-trivial kind From git at git.haskell.org Fri Apr 11 18:04:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Apr 2014 18:04:01 +0000 (UTC) Subject: [commit: haddock] v2.14: Version bump. (c1e330f) Message-ID: <20140411180404.76F372406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/c1e330fb1fcef3dc0b8431029b97f0bc41651a3c >--------------------------------------------------------------- commit c1e330fb1fcef3dc0b8431029b97f0bc41651a3c Author: Mateusz Kowalczyk Date: Fri Apr 11 18:48:39 2014 +0100 Version bump. >--------------------------------------------------------------- c1e330fb1fcef3dc0b8431029b97f0bc41651a3c doc/haddock.xml | 2 +- haddock.cabal | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/doc/haddock.xml b/doc/haddock.xml index da89ab2..98df2c9 100644 --- a/doc/haddock.xml +++ b/doc/haddock.xml @@ -21,7 +21,7 @@ Simon Marlow, David Waern - This document describes Haddock version 2.14.1, a Haskell + This document describes Haddock version 2.14.3, a Haskell documentation tool. diff --git a/haddock.cabal b/haddock.cabal index 4814331..d070460 100644 --- a/haddock.cabal +++ b/haddock.cabal @@ -1,5 +1,5 @@ name: haddock -version: 2.14.2 +version: 2.14.3 synopsis: A documentation-generation tool for Haskell libraries description: Haddock is a documentation-generation tool for Haskell libraries From git at git.haskell.org Fri Apr 11 18:04:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Apr 2014 18:04:05 +0000 (UTC) Subject: [commit: haddock] v2.14: Ignore version string during HTML tests. (4e9aa92) Message-ID: <20140411180406.09D8A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/4e9aa92d769ea334867e621033ca27cd6a284d3a >--------------------------------------------------------------- commit 4e9aa92d769ea334867e621033ca27cd6a284d3a Author: Mateusz Kowalczyk Date: Fri Apr 11 18:47:41 2014 +0100 Ignore version string during HTML tests. >--------------------------------------------------------------- 4e9aa92d769ea334867e621033ca27cd6a284d3a html-test/run.lhs | 14 +++++++++++++- 1 file changed, 13 insertions(+), 1 deletion(-) diff --git a/html-test/run.lhs b/html-test/run.lhs index e4c83da..153ab32 100755 --- a/html-test/run.lhs +++ b/html-test/run.lhs @@ -134,9 +134,21 @@ check modules strict = do else do putStrLn $ "Pass: " ++ mod ++ " (no .ref file)" +-- | A rather nasty way to drop the Haddock version string from the +-- end of the generated HTML files so that we don't have to change +-- every single test every time we change versions. We rely on the the +-- last paragraph of the document to be the version. We end up with +-- malformed HTML but we don't care as we never look at it ourselves. +dropVersion :: String -> String +dropVersion = reverse . dropTillP . reverse + where + dropTillP [] = [] + dropTillP ('p':'<':xs) = xs + dropTillP (_:xs) = dropTillP xs haddockEq :: String -> String -> Bool -haddockEq file1 file2 = stripLinks file1 == stripLinks file2 +haddockEq file1 file2 = + stripLinks (dropVersion file1) == stripLinks (dropVersion file2) stripLinks :: String -> String stripLinks str = From git at git.haskell.org Fri Apr 11 18:04:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Apr 2014 18:04:08 +0000 (UTC) Subject: [commit: haddock] v2.14: Parse identifiers with ^ and ⋆ in them. (81c379d) Message-ID: <20140411180408.388C72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/81c379daddb0e46c1f62cef5f34e933d481ec4a7 >--------------------------------------------------------------- commit 81c379daddb0e46c1f62cef5f34e933d481ec4a7 Author: Mateusz Kowalczyk Date: Fri Apr 11 16:58:34 2014 +0100 Parse identifiers with ^ and ? in them. Fixes #298. >--------------------------------------------------------------- 81c379daddb0e46c1f62cef5f34e933d481ec4a7 CHANGES | 4 ++ html-test/ref/{Bug201.html => Bug298.html} | 89 +++++++++++++++++++--------- html-test/src/Bug298.hs | 22 +++++++ src/Haddock/Parser.hs | 10 +++- 4 files changed, 95 insertions(+), 30 deletions(-) diff --git a/CHANGES b/CHANGES index b3fb8dc..1fe0249 100644 --- a/CHANGES +++ b/CHANGES @@ -1,3 +1,7 @@ +Changes in version 2.14.3 + + * Fix parsing of identifiers with ^ or ? in them (#298) + Changes in version 2.14.2 * Always drop --split-objs GHC flag for performance reasons (#292) diff --git a/html-test/ref/Bug201.html b/html-test/ref/Bug298.html similarity index 56% copy from html-test/ref/Bug201.html copy to html-test/ref/Bug298.html index 8b596cf..03ed5ee 100644 --- a/html-test/ref/Bug201.html +++ b/html-test/ref/Bug298.html @@ -3,13 +3,13 @@ >Bug201Bug298

Bug201

Bug298

  • f :: ()
  • (<^>) :: (a -> a) -> a -> a
  • (<^) :: a -> a -> a
  • g(^>) :: a -> a -> a
  • (⋆^) :: a -> a -> a
  • f :: ()
Documentation

f :: ()

This leading whitespace
-should be dropped
-
(<^>) :: (a -> a) -> a -> a

(<^) :: a -> a -> a

(^>) :: a -> a -> a

(⋆^) :: a -> a -> a

gf :: ()

 But this one
- should not
-
this should
-be dropped
and so should this
-because there's a space before closing @
-

Links to <^> and ^>, <^ and ⋆^.

Produced by Haddock version 2.14.2

version 2.15.0

) :: (a -> a) -> a -> a +x <^> y = x y + +(<^) :: a -> a -> a +x <^ y = x + +(^>) :: a -> a -> a +x ^> y = y + +(?^) :: a -> a -> a +x ?^ y = y + +-- | Links to '<^>' and '^>', '<^' and '?^'. +f :: () +f = () diff --git a/src/Haddock/Parser.hs b/src/Haddock/Parser.hs index bd5cd20..ece9291 100644 --- a/src/Haddock/Parser.hs +++ b/src/Haddock/Parser.hs @@ -419,13 +419,21 @@ autoUrl = mkLink <$> url -- characters and does no actual validation itself. parseValid :: Parser String parseValid = do - vs <- many' $ satisfy (`elem` "_.!#$%&*+/<=>?@\\|-~:") <|> digit <|> letter_ascii + vs' <- many' $ utf8String "?" <|> return <$> idChar + let vs = concat vs' c <- peekChar case c of Just '`' -> return vs Just '\'' -> (\x -> vs ++ "'" ++ x) <$> ("'" *> parseValid) <|> return vs _ -> fail "outofvalid" + where + idChar = satisfy (`elem` "_.!#$%&*+/<=>?@\\|-~:^") + <|> digit <|> letter_ascii + +-- | Parses UTF8 strings from ByteString streams. +utf8String :: String -> Parser String +utf8String x = decodeUtf8 <$> string (encodeUtf8 x) -- | Parses identifiers with help of 'parseValid'. Asks GHC for 'RdrName' from the -- string it deems valid. From git at git.haskell.org Fri Apr 11 18:04:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Apr 2014 18:04:10 +0000 (UTC) Subject: [commit: haddock] v2.14: Enforce strict GHC version in cabal file (0fce760) Message-ID: <20140411180410.13D532406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/0fce76004ef1746d475ab0ae7a6912d319ae811c >--------------------------------------------------------------- commit 0fce76004ef1746d475ab0ae7a6912d319ae811c Author: Mateusz Kowalczyk Date: Thu Apr 3 21:16:07 2014 +0100 Enforce strict GHC version in cabal file This stops people with 7.6.3 trying to install 2.15.x/2.14.3 which clearly won't work. >--------------------------------------------------------------- 0fce76004ef1746d475ab0ae7a6912d319ae811c haddock.cabal | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/haddock.cabal b/haddock.cabal index d070460..cdcbcb4 100644 --- a/haddock.cabal +++ b/haddock.cabal @@ -83,7 +83,7 @@ executable haddock array, xhtml >= 3000.2 && < 3000.3, Cabal >= 1.10, - ghc >= 7.7 && < 7.10, + ghc == 7.8.*, bytestring other-modules: @@ -143,7 +143,7 @@ library array, xhtml >= 3000.2 && < 3000.3, Cabal >= 1.10, - ghc >= 7.4 && < 7.10 + ghc == 7.8.* if flag(in-ghc-tree) cpp-options: -DIN_GHC_TREE From git at git.haskell.org Fri Apr 11 18:04:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Apr 2014 18:04:33 +0000 (UTC) Subject: [commit: haddock] master: Ignore version string during HTML tests. (1a4b54c) Message-ID: <20140411180433.E91EF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/1a4b54cca2239881a998af9ce472a2dc519f3ca4 >--------------------------------------------------------------- commit 1a4b54cca2239881a998af9ce472a2dc519f3ca4 Author: Mateusz Kowalczyk Date: Fri Apr 11 18:47:41 2014 +0100 Ignore version string during HTML tests. >--------------------------------------------------------------- 1a4b54cca2239881a998af9ce472a2dc519f3ca4 html-test/run.lhs | 14 +++++++++++++- 1 file changed, 13 insertions(+), 1 deletion(-) diff --git a/html-test/run.lhs b/html-test/run.lhs index e4c83da..153ab32 100755 --- a/html-test/run.lhs +++ b/html-test/run.lhs @@ -134,9 +134,21 @@ check modules strict = do else do putStrLn $ "Pass: " ++ mod ++ " (no .ref file)" +-- | A rather nasty way to drop the Haddock version string from the +-- end of the generated HTML files so that we don't have to change +-- every single test every time we change versions. We rely on the the +-- last paragraph of the document to be the version. We end up with +-- malformed HTML but we don't care as we never look at it ourselves. +dropVersion :: String -> String +dropVersion = reverse . dropTillP . reverse + where + dropTillP [] = [] + dropTillP ('p':'<':xs) = xs + dropTillP (_:xs) = dropTillP xs haddockEq :: String -> String -> Bool -haddockEq file1 file2 = stripLinks file1 == stripLinks file2 +haddockEq file1 file2 = + stripLinks (dropVersion file1) == stripLinks (dropVersion file2) stripLinks :: String -> String stripLinks str = From git at git.haskell.org Fri Apr 11 18:04:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Apr 2014 18:04:35 +0000 (UTC) Subject: [commit: haddock] master: Update CHANGES to follow 2.14.3 (8222e68) Message-ID: <20140411180435.B617D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/8222e68281558f9f6b4ebf1046aad2690d82e1bd >--------------------------------------------------------------- commit 8222e68281558f9f6b4ebf1046aad2690d82e1bd Author: Mateusz Kowalczyk Date: Fri Apr 11 18:59:30 2014 +0100 Update CHANGES to follow 2.14.3 >--------------------------------------------------------------- 8222e68281558f9f6b4ebf1046aad2690d82e1bd CHANGES | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/CHANGES b/CHANGES index 513c2c1..13ff810 100644 --- a/CHANGES +++ b/CHANGES @@ -2,6 +2,10 @@ Changes in version 2.15.0 * Always read in prologue files as UTF8 (#286 and Cabal #1721) +Changes in version 2.14.3 + + * Fix parsing of identifiers with ^ or ? in them (#298) + Changes in version 2.14.2 * Always drop --split-objs GHC flag for performance reasons (#292) From git at git.haskell.org Fri Apr 11 18:15:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Apr 2014 18:15:23 +0000 (UTC) Subject: [commit: ghc] master: Update Haddock submodule reference. (6782330) Message-ID: <20140411181523.2BBAC2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/67823309eb201f073d143b45176185ca830cd38b/ghc >--------------------------------------------------------------- commit 67823309eb201f073d143b45176185ca830cd38b Author: Mateusz Kowalczyk Date: Fri Apr 11 19:15:07 2014 +0100 Update Haddock submodule reference. >--------------------------------------------------------------- 67823309eb201f073d143b45176185ca830cd38b utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index b1420ef..8222e68 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit b1420ef9c8fdb2728128ad51fb0b636f69932eb7 +Subproject commit 8222e68281558f9f6b4ebf1046aad2690d82e1bd From git at git.haskell.org Sat Apr 12 01:01:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 12 Apr 2014 01:01:56 +0000 (UTC) Subject: [commit: ghc] master: Remove unused variable binding to fix validate (b7f51d6) Message-ID: <20140412010156.C6C6D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b7f51d60093ea13d0854bd7e1d4ecf58d12628a1/ghc >--------------------------------------------------------------- commit b7f51d60093ea13d0854bd7e1d4ecf58d12628a1 Author: Dr. ERDI Gergo Date: Sat Apr 12 08:57:27 2014 +0800 Remove unused variable binding to fix validate >--------------------------------------------------------------- b7f51d60093ea13d0854bd7e1d4ecf58d12628a1 compiler/typecheck/TcPatSyn.lhs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 00dfbe3..fdbee92 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -321,8 +321,8 @@ tcCheckPatSynPat = go go1 (PArrPat pats _) = mapM_ go pats go1 (ListPat pats _ _) = mapM_ go pats go1 (TuplePat pats _ _) = mapM_ go pats - go1 (LitPat lit) = return () - go1 (NPat n _ _) = return () + go1 LitPat{} = return () + go1 NPat{} = return () go1 (SigPatIn pat _) = go pat go1 (ViewPat _ pat _) = go pat go1 p at SplicePat{} = thInPatSynErr p From git at git.haskell.org Sat Apr 12 08:36:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 12 Apr 2014 08:36:09 +0000 (UTC) Subject: [commit: ghc] master: Add source file for new test that checks that as-patterns are rejected in pattern synonym definitions (dd3a6d2) Message-ID: <20140412083609.A17DC2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dd3a6d270f827a59f7a33f32facc506cb35af1fa/ghc >--------------------------------------------------------------- commit dd3a6d270f827a59f7a33f32facc506cb35af1fa Author: Dr. ERDI Gergo Date: Sat Apr 12 16:35:44 2014 +0800 Add source file for new test that checks that as-patterns are rejected in pattern synonym definitions >--------------------------------------------------------------- dd3a6d270f827a59f7a33f32facc506cb35af1fa testsuite/tests/patsyn/should_fail/{unidir.hs => as-pattern.hs} | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/patsyn/should_fail/unidir.hs b/testsuite/tests/patsyn/should_fail/as-pattern.hs similarity index 67% copy from testsuite/tests/patsyn/should_fail/unidir.hs copy to testsuite/tests/patsyn/should_fail/as-pattern.hs index 020fc12..2794bed 100644 --- a/testsuite/tests/patsyn/should_fail/unidir.hs +++ b/testsuite/tests/patsyn/should_fail/as-pattern.hs @@ -1,4 +1,4 @@ {-# LANGUAGE PatternSynonyms #-} module ShouldFail where -pattern Head x = x:_ +pattern P x y <- x@(Just y) From git at git.haskell.org Sat Apr 12 09:52:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 12 Apr 2014 09:52:38 +0000 (UTC) Subject: [commit: ghc] master: Expected output of as-pattern test (7233638) Message-ID: <20140412095238.D4F672406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7233638ba6e82179cc4bd1b981eff5292b18e118/ghc >--------------------------------------------------------------- commit 7233638ba6e82179cc4bd1b981eff5292b18e118 Author: Dr. ERDI Gergo Date: Sat Apr 12 17:52:26 2014 +0800 Expected output of as-pattern test >--------------------------------------------------------------- 7233638ba6e82179cc4bd1b981eff5292b18e118 testsuite/tests/patsyn/should_fail/as-pattern.stderr | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/testsuite/tests/patsyn/should_fail/as-pattern.stderr b/testsuite/tests/patsyn/should_fail/as-pattern.stderr new file mode 100644 index 0000000..62db28f --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/as-pattern.stderr @@ -0,0 +1,4 @@ + +as-pattern.hs:4:18: + Pattern synonym definition cannot contain as-patterns (@): + x@(Just y) From git at git.haskell.org Sat Apr 12 10:52:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 12 Apr 2014 10:52:01 +0000 (UTC) Subject: [commit: ghc] wip/pattern-synonyms: Store IfExtNames for PatSyn matchers and wrappers in interface file (e0f47fe) Message-ID: <20140412105201.A3FCB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/pattern-synonyms Link : http://ghc.haskell.org/trac/ghc/changeset/e0f47fe6346e7093cdba0b883bb3729dea93ca91/ghc >--------------------------------------------------------------- commit e0f47fe6346e7093cdba0b883bb3729dea93ca91 Author: Dr. ERDI Gergo Date: Sat Apr 12 18:46:35 2014 +0800 Store IfExtNames for PatSyn matchers and wrappers in interface file >--------------------------------------------------------------- e0f47fe6346e7093cdba0b883bb3729dea93ca91 compiler/iface/IfaceSyn.lhs | 19 ++++++++++++------- compiler/iface/MkIface.lhs | 6 +++++- compiler/iface/TcIface.lhs | 9 ++++++--- 3 files changed, 23 insertions(+), 11 deletions(-) diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 1283b09..534bb80 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -59,6 +59,7 @@ import HsBinds import Control.Monad import System.IO.Unsafe +import Data.Maybe ( isJust ) infixl 3 &&& \end{code} @@ -120,8 +121,9 @@ data IfaceDecl ifExtName :: Maybe FastString } | IfacePatSyn { ifName :: OccName, -- Name of the pattern synonym - ifPatHasWrapper :: Bool, ifPatIsInfix :: Bool, + ifPatMatcher :: IfExtName, + ifPatWrapper :: Maybe IfExtName, ifPatUnivTvs :: [IfaceTvBndr], ifPatExTvs :: [IfaceTvBndr], ifPatProvCtxt :: IfaceContext, @@ -186,7 +188,7 @@ instance Binary IfaceDecl where put_ bh a3 put_ bh a4 - put_ bh (IfacePatSyn name a2 a3 a4 a5 a6 a7 a8 a9) = do + put_ bh (IfacePatSyn name a2 a3 a4 a5 a6 a7 a8 a9 a10) = do putByte bh 6 put_ bh (occNameFS name) put_ bh a2 @@ -197,6 +199,7 @@ instance Binary IfaceDecl where put_ bh a7 put_ bh a8 put_ bh a9 + put_ bh a10 get bh = do h <- getByte bh @@ -253,8 +256,9 @@ instance Binary IfaceDecl where a7 <- get bh a8 <- get bh a9 <- get bh + a10 <- get bh occ <- return $! mkOccNameFS dataName a1 - return (IfacePatSyn occ a2 a3 a4 a5 a6 a7 a8 a9) + return (IfacePatSyn occ a2 a3 a4 a5 a6 a7 a8 a9 a10) _ -> panic (unwords ["Unknown IfaceDecl tag:", show h]) data IfaceSynTyConRhs @@ -1015,10 +1019,10 @@ ifaceDeclImplicitBndrs (IfaceClass {ifCtxt = sc_ctxt, ifName = cls_tc_occ, dc_occ = mkClassDataConOcc cls_tc_occ is_newtype = n_sigs + n_ctxt == 1 -- Sigh -ifaceDeclImplicitBndrs (IfacePatSyn{ ifName = ps_occ, ifPatHasWrapper = has_wrapper }) - = [wrap_occ | has_wrapper] +ifaceDeclImplicitBndrs (IfacePatSyn{ ifName = ps_occ, ifPatWrapper = wrapper_name }) + = [wrap_occ | isJust wrapper_name] where - wrap_occ = mkDataConWrapperOcc ps_occ -- Id namespace + wrap_occ = mkDataConWrapperOcc ps_occ ifaceDeclImplicitBndrs _ = [] @@ -1103,7 +1107,7 @@ pprIfaceDecl (IfaceAxiom {ifName = name, ifTyCon = tycon, ifAxBranches = branche = hang (ptext (sLit "axiom") <+> ppr name <> dcolon) 2 (vcat $ map (pprAxBranch $ Just tycon) branches) -pprIfaceDecl (IfacePatSyn { ifName = name, ifPatHasWrapper = has_wrap, +pprIfaceDecl (IfacePatSyn { ifName = name, ifPatWrapper = wrapper, ifPatIsInfix = is_infix, ifPatUnivTvs = _univ_tvs, ifPatExTvs = _ex_tvs, ifPatProvCtxt = prov_ctxt, ifPatReqCtxt = req_ctxt, @@ -1111,6 +1115,7 @@ pprIfaceDecl (IfacePatSyn { ifName = name, ifPatHasWrapper = has_wrap, ifPatTy = ty }) = pprPatSynSig name has_wrap args' ty' (pprCtxt prov_ctxt) (pprCtxt req_ctxt) where + has_wrap = isJust wrapper args' = case (is_infix, map snd args) of (True, [left_ty, right_ty]) -> InfixPatSyn (pprParendIfaceType left_ty) (pprParendIfaceType right_ty) diff --git a/compiler/iface/MkIface.lhs b/compiler/iface/MkIface.lhs index bb51cda..d504386 100644 --- a/compiler/iface/MkIface.lhs +++ b/compiler/iface/MkIface.lhs @@ -1488,7 +1488,8 @@ dataConToIfaceDecl dataCon patSynToIfaceDecl :: PatSyn -> IfaceDecl patSynToIfaceDecl ps = IfacePatSyn { ifName = getOccName . getName $ ps - , ifPatHasWrapper = isJust $ patSynWrapper ps + , ifPatMatcher = matcher + , ifPatWrapper = wrapper , ifPatIsInfix = patSynIsInfix ps , ifPatUnivTvs = toIfaceTvBndrs univ_tvs' , ifPatExTvs = toIfaceTvBndrs ex_tvs' @@ -1507,6 +1508,9 @@ patSynToIfaceDecl ps (env1, univ_tvs') = tidyTyVarBndrs emptyTidyEnv univ_tvs (env2, ex_tvs') = tidyTyVarBndrs env1 ex_tvs + matcher = idName (patSynMatcher ps) + wrapper = fmap idName (patSynWrapper ps) + -------------------------- coAxiomToIfaceDecl :: CoAxiom br -> IfaceDecl diff --git a/compiler/iface/TcIface.lhs b/compiler/iface/TcIface.lhs index cc45648..31c2bf7 100644 --- a/compiler/iface/TcIface.lhs +++ b/compiler/iface/TcIface.lhs @@ -583,7 +583,8 @@ tc_iface_decl _ _ (IfaceAxiom { ifName = ax_occ, ifTyCon = tc ; return (ACoAxiom axiom) } tc_iface_decl _ _ (IfacePatSyn{ ifName = occ_name - , ifPatHasWrapper = has_wrapper + , ifPatMatcher = matcher_name + , ifPatWrapper = wrapper_name , ifPatIsInfix = is_infix , ifPatUnivTvs = univ_tvs , ifPatExTvs = ex_tvs @@ -593,6 +594,8 @@ tc_iface_decl _ _ (IfacePatSyn{ ifName = occ_name , ifPatTy = pat_ty }) = do { name <- lookupIfaceTop occ_name ; traceIf (ptext (sLit "tc_iface_decl") <+> ppr name) + ; _matcher <- tcExt "Matcher" matcher_name + ; wrapper <- maybe (return Nothing) (fmap Just . tcExt "Wrapper") wrapper_name ; bindIfaceTyVars univ_tvs $ \univ_tvs -> do { bindIfaceTyVars ex_tvs $ \ex_tvs -> do { bindIfaceIdVars args $ \args -> do @@ -602,11 +605,11 @@ tc_iface_decl _ _ (IfacePatSyn{ ifName = occ_name ; pat_ty <- tcIfaceType pat_ty ; return (prov_theta, req_theta, pat_ty) } ; bindIfaceTyVar (fsLit "r", toIfaceKind liftedTypeKind) $ \tv -> do - { patsyn <- buildPatSyn name is_infix has_wrapper args univ_tvs ex_tvs prov_theta req_theta pat_ty tv + { patsyn <- buildPatSyn name is_infix (isJust wrapper) args univ_tvs ex_tvs prov_theta req_theta pat_ty tv ; return (AConLike (PatSynCon patsyn)) }}}}} where mk_doc n = ptext (sLit "Pattern synonym") <+> ppr n - + tcExt s name = forkM (ptext (sLit s) <+> ppr name) $ tcIfaceExtId name tc_ax_branches :: TyCon -> [IfaceAxBranch] -> IfL [CoAxBranch] tc_ax_branches tc if_branches = foldlM (tc_ax_branch (tyConKind tc)) [] if_branches From git at git.haskell.org Sat Apr 12 10:52:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 12 Apr 2014 10:52:04 +0000 (UTC) Subject: [commit: ghc] wip/pattern-synonyms's head updated: Store IfExtNames for PatSyn matchers and wrappers in interface file (e0f47fe) Message-ID: <20140412105204.AD75C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/pattern-synonyms' now includes: 466d069 Bump version: 7.7 -> 7.9 24669fe Update Win32 submodule to pull in version bump 9f58cec Fix glitch in core-spec pdf 48326cf Fix iOS build (fallout from 28b031c506) 99484c9 Add a perf-cross build setting. 044f233 Bump win32 version number in release notes 1dd38a5 Remove Coercible documentation from compiler/prelude/primops.txt.pp fda9beb Fix some edge cases in 8f8bd88c (#7134) 5671ad6 Update to latest Cabal 1.18 branch tip 71a412c No need to remove testsuite/.git 50e4d40 Individual sdist-foo targets a2269bf Remove some references to deprecated -fglasgow-exts in user's guide ea584ab Loopification jump between stack and heap checks c6ce808 Remove unnecessary LANGUAGE pragma 99c3ed8 Simplify Control Flow Optimisations Cmm pass 78afa20 Nuke dead code d5fb670 Fix a popular typo in comments f028975 Remove redundant NoMonoLocalBinds pragma b5c45d8 Remove unused import 5f64b2c Add test-case for #8726 526cbc7 Document deprecations in Hoopl dba9bf6 Eliminate duplicate code in Cmm pipeline 2b33f6e Final fix to #7134 (and #8717 as well.) 2f6d36f Tweak holes documentation 40ce203 Fix #8698 by properly handling long section names and reenabling .ctors handling 5bda0d0 Mention that MR is off by default in GHCi in documentation ad44e47 Switch to relative URLs in .gitmodules b755c7b Correctly clone submodules from github 41cfc96 Tweak documentation of monomorphism restriction 298a25b Fix __thread detection (#8722) b4eb630 Remove ios_HOST check for GCTDecl.h 03200e8 Fix some Python brainos in testlib (except e is not valid form). c3ff5f2 Add test case for #8743 312686c In deepSplitCprType_maybe, be more forgiving 218dead Fix #8706, documenting that type operators are not promoted. 4f6a0f4 T8256 needs vector 674c969 Fix #8631. e0a5541 Issue an error for pattern synonyms defined in a local scope (#8757) 719108f Add test suite for #8757 7561e37 double-negate test for Stage1Only to fix `make clean` 65170fc Let `make distclean` remove `/{ch01,ch02,index}.html` 02c7135 Move test case for #8631 to the correct directory. 8cc398f Fix #8758 by assuming RankNTypes when checking GND code. 9e0c1ae Test #6147, which was fixed with the roles commit. d1dff94 Test #7481, which had already been fixed. 6122efc Fix #8759 by not panicking with TH and patsyns. e0dadc8 Apply changes relative to TH.Pred becoming a TH.Type's synonym (issue #7021) 182ff9e Fix tests due to issue #7021 8e303d7 Refactor previous commit on fixing #7021. cdceadf Implement CallArity analysis 9bc8265 Add a unit test for CallArity 393ea73 Update test cases due to call arity a4450ec Note [Eta expansion in match] b4715d6 Replace forall'ed Coercible by ~R# in RULES f4fb94f In CoreSubst, optimize Coercible values aggressively d557d8c In simpleOptExpr, unfold compulsary unfoldings 8f16233 Add Case TyConAppCo to match_co 377672a Test case for RULE map coerce = coerce a27b298 Use exprIsLambda_maybe in match cde88e2 Test case: Looking through unfoldings when matching lambdas 5d04603 Remove eta-expansion in Rules.match e16826b Cleaned up Maybes.lhs 9f607ee Link to #minimal-pragma from release notes e2cacb6 Manual hlinting: or (map f) = any f 3477216 Fix Manual hlinting patch 3d80787 Fix some typos in comments 3d9644c Remove space after ASSERT. 473f12a Fix #5682. Now, '(:) parses. 1382975 Fix #8773. 68f0a6a Fix --enable-unregistered by passing NOSMP to .hc compiler (#8748) 4bb50ed Fix --enable-unregistered by declaring missing RTS functions (#8748) ebace69 rts/Capability.c: fix crash in -threaded mode on UNREG build 858a807 includes/Stg.h: add declarations for hs_popcnt and frinds 2d0fa9a rts/package.conf.in: fix UNREG on --with-system-libffi when include-dir is passed explicitely 2d5372c mk/config.mk.in: lower -O2 optimization down to -O1 on UNREG a365eab Fix installation of hpc (#8735) c83eabf Fix check for TLS support in Storage.c 5023c91 Fix #8754 in a round-about way. a8a01e7 Fix #8745 - GND is now -XSafe compatible. dc08091 Fix #8770 b626c3d Add comments explaining #8754 2931d19 More liberally eta-expand a case-expression 47f473b Use NoGen plan for unboxed-tuple bindings 5dd1cbb Allow ($) to return an unlifted type (Trac #8739) cd3a3a2 Add some more traceTcS calls 89d2c04 Keep kind-inconsistent Given type equalities (fixes Trac #8705) 642bba3 Revert "Add comments explaining #8754" e789a4f Revert "Fix #8754 in a round-about way." 4c93a40 Make CallArity make more use of many-calls fa353f2 Call Arity refactoring: Use a product domain 983fbbe Call Arity refactoring: Factor out callArityBound 7c603ab Call Arity refactoring: instance Outputable Count 2ab00bf Call Arity: Now also done on Top-Level binds 7e787e7 Move unit call arity unittests into subdirectory d51d7ef Call arity: Handle type application correctly f347bfe Support mutual recursion d3c579c Call arity testcase for #3924 ba4616b Call Arity: Update compiler perf number changes af7428e Call Arity refactoring: fakeBoringCalls 47d725f Update to primitive-0.5.2.1 43c314c add omitted FP_PROG_AR_SUPPORTS_ATFILE into the distribution configure.ac (fixes #8794) 5c6ced5 fix build failure on Solaris 10 due to RANLIB being set to ':' by configure (#8795) 27fe128 add more information about the nature of support of prefetch primops on none x86/AMD64 -fasm platforms (and -fvia) to the 7.8 release notes e638acb fix sed expression in build dependencies rules to work well with non-GNU sed (fixes #8764) e75ebc4 Switch on -dynamic-too with QuasiQuotes as well. 2b34947 Clear up docs regarding LLVM backend (#8792) f99a032 Fix #8801: exclude extra packages from the sdist. d3af980 Really fix #5682 (parsing of promoted datacons) 925b0a4 RetainerProfile.c: include missing header (#8810) 3361e6c Update to primitive-0.5.2.1 (again) 55cc01a Add test case for #8806. 5a57675 Add a test for d3af980 (#5682) c72e889 Fix #8754 again. 5075c19 Add VERSION file to gitignore. beac525 Fix installation of ghc-split (#8760) ed1aced Fix #8696 - don't generate static intra-package references. 4f69b1e Fix Haddock formatting ede5b51 Make Outputable instance for HsDocString useful 018676c Use U+2018 instead of U+201B quote mark in compiler messages 98b6756 Fix #8807. 32f41c7 Make distribution tarball compression format configurable b1ee32e Follow-up to 32f41c79 b1ddec1 Fix a bug in codegen for non-updatable selector thunks (#8817) 68c0d86 fix comment on allocate() (#8254) af6746f Add hs_thread_done() (#8124) 67029f2 PPC: Fix loads of PIC data with > 16 bit offsets (#7830). a864c34 Bump T6048 tests. 7161152 Documentation updates for 7.8.1 release 025a66e Fix binary-dist target with xz/gzip f962725 Note that we need Cabal-1.18 in the release notes 251b18a binary-dist: when using xz, use extreme compression. 3fba875 add missing files (#8124) 176205c fix copy/pasto afb42a5 Update time to 1.4.2 release 01f9ac3 Update `Cabal` to 1.18.1.3 release cb8a63c Major Call Arity rework 2d82846 Typos in comments eeb1400 Add some debug tracing 4b355cd Make the demand on a binder compatible with type (fixes Trac #8569) 96daafc Attach the right location to pattern synonym error message (fixes Trac #8841) bf9bf60 Test for Trac #8841 now works 7fa6c67 Trac #8569 fixed 1ac9114 Test #8851. 0014fb3 Run testcase for 8124 only with threaded ways 3efcb0a Make sync-all handle all github protocols correctly cdac487 Make -XDeriveFunctor more generous about non-last arguments (Trac #8678) cf1a0f9 Fix the treatment of lexically scoped kind variables (Trac #8856) 062391b Test Trac #8856 d246c62 Also allow http://github.com (#8824) 9d14262 Improve documentation of standalone deriving (c.f. Trac #8851) f521a26 Unify, rather than match, in GND processing (fixes Trac #8865) ddf79eb Add "bench" build flavour to build system 9c9bb00 Fix copy-paste error in build system comment a10ed3e Comments only ef44a42 Make SetLevels do substitution properly (fixes Trac #8714) 41f8031 Fix last-minute typo in SetLevels commit ef44a4 22f010e codeGen: allocate small arrays of statically known size inline a70e7b4 Represent offsets into heap objects with byte, not word, offsets b684f27 Refactor inline array allocation c1d74ab Fix incorrect loop condition in inline array allocation 22e4bba Add test for inline array allocation d8b3826 Validate computed sums in inline array allocation test d793a14 Add perf test for inline array allocation 7f919de Call Arity: Resurrect fakeBoringCalls b0416e7 Comments on virtHp, realHp (Trac #8864) b340681 A bit more tracing to do with SPECIALISE pragmas 60bbc0a Export runTcInteractive from TcRnDriver, and from GHC (Trac #8878) 7ef90e3 Comments only 8fd7d58 Add BuiltinRules for constant-folding not# and notI# (logical complement) ea6dcef Test Trac #8832 4d1b7b4 Add OutputableBndr instance for OccName 23c0f1e pprIfaceContextArr: print a context including the "=>" arrow 24eea38 pprIfaceDecl for IfacePatSyn: use pprPatSynSig 065c35a Pretty-print the following TyThings via their IfaceDecl counterpart: * AnId * ACoAxiom * AConLike ed2a8f0 Improve copy/clone array primop docs e55acf0 Update to containers-0.5.5.0 46d05ba Fix two issues in stg_newArrayzh a0bcbb5 fix SHELL makefile variable to be set by the configure script (fixes #8783) 623883f disable shared libs on sparc (linux/solaris) (fixes #8857) b7e5d72 Fix incorrect blocksize calculation on Win64 d574fcb config.mk.in: ARM now supports dynamic linking with the LLVM backend b84b5da DriverPipeline: Ensure -globalopt is passed to LLVM opt b99ace3 Fix incorrect maxStkSize calculation (#8858) cbdd832 Fix T2110 now that base has map/coerce rule. 210ccab codeGen: allocate small byte arrays of statically known size inline 5972229 Remove "Safe mode" check for Coercible instances 8ee6162 Recharacterize test according to discussion in #8851. 8c5ea91 Fix #8884. 337bac3 Fix typo in user's manual, changing "-j N" to "-jN". 797da5c Call Arity : Note about fakeBoringCalls 41ab584 Remove unused gHC_COERCIBLE c61d40e testsuite: look for tests-ghc directories for libraries df265b9 Update to containers-0.5.5.1 4133ff8 Reference Note [Kind-changing of (~) and Coercible] d53ccab Another reference to Note [Kind-changing of (~) and Coercible] 1e36a38 Document Coercible in the user guide f3eeb93 Honor Op_PrintExplicitForalls setting in pprIfaceForAllPart 5908a74 Use prefix notation in pprIfaceDecl for IfaceIds 5200369 Reinstate pretty-printing of AnIds via pprId (#8776) de32a95 Add test case for #8776 306d255 Call Arity: Never eta-expand thunks in recursive groups aab6b9b Call Arity test case: Check what happens with unboxed lets 7602bd4 Remove code reporting issues with Safe Haskell and coerce. 0142237 Test case: :info Coercible in GHCi db497cd Fix comment for ghci script files d59170b Coercible is now exported from GHC.Types (#8894) 5d59265 Remove support for "primclass" 7a7af1f Unflatten the constraints of an inferred types (Trac #8889) a79613a Revert ad15c2, which causes Windows seg-faults (Trac #8834) 7511d5b Fix validation issue due to Coercible move (#8894) 2b3feaa Comments only f4d15cb More debug info 0e2155d Test Trac #8889 a5ab610 Test case: ghci059: Forgot stdout file 3099e40 Add some documentation about type-level literals. 696bfc4 Update submodule to Win32-2.3.0.2 87bbc69 Make sure we occurrence-analyse unfoldings (fixes Trac #8892) 5e4bdb5 Implement ordering comparisons for type-level naturals and symbols. a3f78e2 isLexVarSym: check all characters of the name, not just the first one. 21028ee Update expected test outputs to match new format of pretty-printing interface contents a6939ec Don't use gcptr for interior pointers df409de Flush after TH in #8884 test case ba0c012 Typos f9b6a2b testsuite: add test for #8831 7a1c851 linker: Fix indirect calls for x86_64 windows (#2283) 99ef279 Update ghc --help references to --make and a.out (fixes #8600) 1eece45 codeGen: inline allocation optimization for clone array primops 4bc3c82 Mark test for #8831 as known-broken 1a63f17 Follow hs_popcntX changes in ghc-prim 16d04d9 Enable popcnt test now when segfault is fixed be2e0e8 Make cabal01 pass with Cabal 1.18 (#8738). 9b38f6a Comments only -- clarifying Notes around compatibility. b0bcbc0 Remove redundant compatibility check. 4779602 Add test case for #8917 c99941c Fix #8917. d523f9b sync-all: Skip END actions on exceptions ac24bf4 add --with-ar and --with-ranlib configure parameters ace7477 Add a simplistic Vagrantfile with bootstrapping 045b280 change deriveConstants to use nm in a POSIX way (fixes #8781) 34b0721 Convert haddock into a proper submodule (re #8545) 8f26728 ghc-cabal: force use of UTF8 when writing out `haddock-prologue.txt` ffed708 Apply the kind subst to the (kinds of the) quanitifed tyvars in deriveTyData 28e8d87 Simplify handling of the interactive package; fixes Trac #8831 7973bfb Test Trac #8893 1a7709e Trac #8831 is fixed 90142be Fix typo 4b4fc7d Catch a bunch of typos in comments 61654e5 The substitution is never needed, so don't prepare it 8f73037 Revert "Fix #8745 - GND is now -XSafe compatible." 15b1eb7 Revert "change deriveConstants to use nm in a POSIX way (fixes #8781)" 74894e0 Add missing kind-check for tcEqType on forall-types 3f59647 Don't export isTcReflCo_maybe (unused) 5a51b69 Comments only c89c57e For equalities with incompatible kinds, new IrredCan goes in the inert set, not work list 9f9b10f Debug tracing only 6ae678e Flattener preserves synonyms, rewriteEvidence can drop buggy "optimisation" a8b7b28 Implicit parameters should not be allowed in class and instance declarations 5c7ced0 Comments only 73cab20 relnotes: GND is not -XSafe compatible. 0b6fa3e Eliminate redundant seq's (Trac #8900) 41ba7cc Improve the desugaring of RULE left-hand-sides (fixes Trac #8848) b800e52 Comments only 88d9452 Test Trac #8848 2d1ecd2 Suppress uniques for simpl016 to normalise debug output ce335ce Typos in comments 11b31c3 Add flags to control memcpy and memset inlining f868254 Fixup help text 6189c76 --with-gcc overrides CC_STAGE0 when not cross-compiling (#8498) a6f2c85 Don't perform permission checks for scripts named with -ghci-script (#6017) 975e9cb Include EXTRA_LD_OPTS (amongst other things) when linking programs e7f26cd Pass custom CC and LD opts to Cabal when configuring a package d011cde Include SRC_CC_OPTS and SRC_LD_OPTS when compiling ghc-cabal 2aa7810 Use LDFLAGS when compiling ghc-pwd 261a97b increase bounds for T3064 c4eeacd Use the correct callClobberedRegs on Windows/x64 (#8834) 7ef3f0d rts: remove unused functions, fix validate on OS X e54828b Make copy array ops out-of-line by default 4c8edfd Remove debugging output 90329b6 Add SmallArray# and SmallMutableArray# types 838bfb2 Add missing symbols to linker dd02850 PrimOps.cmm: whitespace only 4de517f Add more missing linker symbols c310823 CopySmallArrayStressTest needs random 1a11e9b Add inline versions of copy ops for small arrays 345eea2 Update Haddock submodule 52c6dc9 Temporarily fight off build bogons on OS X 5d7f590 Support thin archive format 63b0e1b Update Haddock submodule 791f4fa Make sure that polykinded Typeable is defaultable (Trac #8931) 3671d00 Fix desguaring of bang patterns (Trac #8952) 8bf8ce1 Test Trac #8931 b20bc18 Parse the variables in a type signature in the order given (Trac #8945) 2033a58 Update Haddock submodule e94ed11 With AutoDeriveTypeable, derive for promoted constructors, too. 750271e Simplify and tidy up the handling of tuple names c6c8678 Revert "Revert ad15c2, which causes Windows seg-faults (Trac #8834)" f0af58d windows: Fix #8870 59b9b06 Fix copy/paste error (#8937) ee13437 Test return value of clock_gettime() for errors. e81d110 Disable thin archive support on Windows d468cd3 Fix #8958. f772344 Add test case for #8950. 8f831ec Require PatternSynonyms language flag when encountering a use of pattern synonym (#8961) d8d798b Small issue with signatures in a TH splice (fixes Trac #8932) bd79b98 Update long-out-of-date performance numbers on 32-bit ee481ff Ignore repeated loads of the same archive (#8942) ec3e949 Include LD_OPTS when building the RTS shared libs 54e6555 Derive Typable for promoted data constructors (Trac #8950) b059dcc users_guide: note -XPatternSynonyms is required for use sites b30771d Clarify bits about role inference in users' guide. cbe59d8 Improve tracing slightly 4dc9f98 Zonk the existential type variables in tcPatSynDecl 17c9554 Improve documentation of GeneralisedNewtypeDeriving d2c4f97 Add comments & notes explaining the typing of pattern synonym definitions 396648e Don't preprocess .s files 848f595 Allow a longer demand signature than arity 2c516c4 Refactor in worker/wrapper generation cc3ccf9 Test Trac #8963 50bfd42 Improve error reporting for untouchable type variables f8e12e2 Fix #5435, adding new test config check_stdout. b4dd566 Suppress uniques to stop output wobbling (test for Trac #8958) b8132a9 Fix egregious blunder in the type flattener c269b7e Split off pattern synonym definition checking from pattern inversion c7498bb Fix #8641, creating directories when we have stubs. 6782330 Update Haddock submodule reference. b7f51d6 Remove unused variable binding to fix validate dd3a6d2 Add source file for new test that checks that as-patterns are rejected in pattern synonym definitions 7233638 Expected output of as-pattern test e0f47fe Store IfExtNames for PatSyn matchers and wrappers in interface file From git at git.haskell.org Sun Apr 13 06:37:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 13 Apr 2014 06:37:05 +0000 (UTC) Subject: [commit: ghc] master: Fix linked list manipulation code (buggy on consecutive deletion) (e3938f3) Message-ID: <20140413063705.518392406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e3938f3adac0093b23694fd347774244ce121478/ghc >--------------------------------------------------------------- commit e3938f3adac0093b23694fd347774244ce121478 Author: Edward Z. Yang Date: Sat Apr 12 23:02:13 2014 -0700 Fix linked list manipulation code (buggy on consecutive deletion) Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- e3938f3adac0093b23694fd347774244ce121478 rts/CheckUnload.c | 3 ++- rts/Linker.c | 6 ++++-- 2 files changed, 6 insertions(+), 3 deletions(-) diff --git a/rts/CheckUnload.c b/rts/CheckUnload.c index f1f454c..98f184b 100644 --- a/rts/CheckUnload.c +++ b/rts/CheckUnload.c @@ -298,7 +298,7 @@ void checkUnload (StgClosure *static_objects) // marked as unreferenced can be physically unloaded, because we // have no references to it. prev = NULL; - for (oc = unloaded_objects; oc; prev = oc, oc = next) { + for (oc = unloaded_objects; oc; oc = next) { next = oc->next; if (oc->referenced == 0) { if (prev == NULL) { @@ -312,6 +312,7 @@ void checkUnload (StgClosure *static_objects) } else { IF_DEBUG(linker, debugBelch("Object file still in use: %" PATH_FMT "\n", oc->fileName)); + prev = oc; } } diff --git a/rts/Linker.c b/rts/Linker.c index af26d74..ab235e9 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -3016,8 +3016,8 @@ unloadObj( pathchar *path ) IF_DEBUG(linker, debugBelch("unloadObj: %" PATH_FMT "\n", path)); prev = NULL; - for (oc = objects; oc; prev = oc, oc = next) { - next = oc->next; + for (oc = objects; oc; oc = next) { + next = oc->next; // oc might be freed if (!pathcmp(oc->fileName,path)) { @@ -3075,6 +3075,8 @@ unloadObj( pathchar *path ) /* This could be a member of an archive so continue * unloading other members. */ unloadedAnyObj = HS_BOOL_TRUE; + } else { + prev = oc; } } From git at git.haskell.org Sun Apr 13 08:10:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 13 Apr 2014 08:10:00 +0000 (UTC) Subject: [commit: ghc] master: Make BlockAlloc.c comment slightly more accurate (fixes #8491) (7fa0b43) Message-ID: <20140413081000.456112406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7fa0b43593644fba8a3a60e5503a55268578d3c0/ghc >--------------------------------------------------------------- commit 7fa0b43593644fba8a3a60e5503a55268578d3c0 Author: Edward Z. Yang Date: Sun Apr 13 01:09:40 2014 -0700 Make BlockAlloc.c comment slightly more accurate (fixes #8491) Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 7fa0b43593644fba8a3a60e5503a55268578d3c0 rts/sm/BlockAlloc.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/sm/BlockAlloc.c b/rts/sm/BlockAlloc.c index 4d2685b..f06855e 100644 --- a/rts/sm/BlockAlloc.c +++ b/rts/sm/BlockAlloc.c @@ -45,7 +45,7 @@ static void initMBlock(void *mblock); bd->free is either: - zero for a non-group-head; bd->link points to the head - (-1) for the head of a free block group - - or it points within the block + - or it points within the block (group) bd->blocks is either: - zero for a non-group-head; bd->link points to the head From git at git.haskell.org Sun Apr 13 08:41:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 13 Apr 2014 08:41:36 +0000 (UTC) Subject: [commit: ghc] master: Instead of tracking Origin in LHsBindsLR, track it in MatchGroup (eeaea2d) Message-ID: <20140413084136.B35042406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eeaea2df3fa585db503034f419c6e4331a4d8a84/ghc >--------------------------------------------------------------- commit eeaea2df3fa585db503034f419c6e4331a4d8a84 Author: Dr. ERDI Gergo Date: Sat Apr 12 19:36:31 2014 +0800 Instead of tracking Origin in LHsBindsLR, track it in MatchGroup >--------------------------------------------------------------- eeaea2df3fa585db503034f419c6e4331a4d8a84 compiler/deSugar/Coverage.lhs | 8 +--- compiler/deSugar/DsArrows.lhs | 4 +- compiler/deSugar/DsBinds.lhs | 9 +--- compiler/deSugar/DsExpr.lhs | 17 +++---- compiler/deSugar/DsMeta.hs | 2 +- compiler/deSugar/Match.lhs | 12 +++-- compiler/hsSyn/Convert.lhs | 12 ++--- compiler/hsSyn/HsBinds.lhs | 6 +-- compiler/hsSyn/HsExpr.lhs | 3 +- compiler/hsSyn/HsUtils.lhs | 46 +++++++++--------- compiler/main/HscStats.hs | 4 +- compiler/parser/Parser.y.pp | 8 ++-- compiler/parser/RdrHsSyn.lhs | 4 +- compiler/rename/RnBinds.lhs | 27 ++++++----- compiler/rename/RnSource.lhs | 4 +- compiler/typecheck/TcArrows.lhs | 4 +- compiler/typecheck/TcBinds.lhs | 88 +++++++++++++++++------------------ compiler/typecheck/TcClassDcl.lhs | 18 +++---- compiler/typecheck/TcDeriv.lhs | 3 +- compiler/typecheck/TcForeign.lhs | 3 +- compiler/typecheck/TcGenDeriv.lhs | 20 ++++---- compiler/typecheck/TcHsSyn.lhs | 10 ++-- compiler/typecheck/TcInstDcls.lhs | 28 +++++------ compiler/typecheck/TcMatches.lhs | 6 +-- compiler/typecheck/TcPatSyn.lhs | 9 ++-- compiler/typecheck/TcRnDriver.lhs | 12 ++--- compiler/typecheck/TcRnMonad.lhs | 7 +-- compiler/typecheck/TcTyClsDecls.lhs | 8 ++-- utils/ghctags/Main.hs | 2 +- 29 files changed, 185 insertions(+), 199 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc eeaea2df3fa585db503034f419c6e4331a4d8a84 From git at git.haskell.org Sun Apr 13 08:41:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 13 Apr 2014 08:41:52 +0000 (UTC) Subject: [commit: haddock] master: remove Origin flag from LHsBindsLR (ac60bd1) Message-ID: <20140413084152.4B43D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/ac60bd1f98ad02644d3ea36dd4926ed6e105c789 >--------------------------------------------------------------- commit ac60bd1f98ad02644d3ea36dd4926ed6e105c789 Author: Dr. ERDI Gergo Date: Sat Apr 12 21:34:35 2014 +0800 remove Origin flag from LHsBindsLR >--------------------------------------------------------------- ac60bd1f98ad02644d3ea36dd4926ed6e105c789 src/Haddock/Interface/Create.hs | 16 ++++++++-------- 1 file changed, 8 insertions(+), 8 deletions(-) diff --git a/src/Haddock/Interface/Create.hs b/src/Haddock/Interface/Create.hs index fb1038f..08810d6 100644 --- a/src/Haddock/Interface/Create.hs +++ b/src/Haddock/Interface/Create.hs @@ -364,7 +364,7 @@ classDecls class_ = filterDecls . collectDocs . sortByLoc $ decls where decls = docs ++ defs ++ sigs ++ ats docs = mkDecls tcdDocs DocD class_ - defs = mkDecls (map snd . bagToList . tcdMeths) ValD class_ + defs = mkDecls (bagToList . tcdMeths) ValD class_ sigs = mkDecls tcdSigs SigD class_ ats = mkDecls tcdATs (TyClD . FamDecl) class_ @@ -384,13 +384,13 @@ mkFixMap group_ = M.fromList [ (n,f) ungroup :: HsGroup Name -> [LHsDecl Name] ungroup group_ = mkDecls (tyClGroupConcat . hs_tyclds) TyClD group_ ++ - mkDecls hs_derivds DerivD group_ ++ - mkDecls hs_defds DefD group_ ++ - mkDecls hs_fords ForD group_ ++ - mkDecls hs_docs DocD group_ ++ - mkDecls hs_instds InstD group_ ++ - mkDecls (typesigs . hs_valds) SigD group_ ++ - mkDecls (map snd . valbinds . hs_valds) ValD group_ + mkDecls hs_derivds DerivD group_ ++ + mkDecls hs_defds DefD group_ ++ + mkDecls hs_fords ForD group_ ++ + mkDecls hs_docs DocD group_ ++ + mkDecls hs_instds InstD group_ ++ + mkDecls (typesigs . hs_valds) SigD group_ ++ + mkDecls (valbinds . hs_valds) ValD group_ where typesigs (ValBindsOut _ sigs) = filter isVanillaLSig sigs typesigs _ = error "expected ValBindsOut" From git at git.haskell.org Sun Apr 13 11:59:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 13 Apr 2014 11:59:26 +0000 (UTC) Subject: [commit: ghc] master: Typos in comments (80bdb88) Message-ID: <20140413115926.C54242406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/80bdb88e9f379c3e0dd3c2281ee2ea315e1b8a5f/ghc >--------------------------------------------------------------- commit 80bdb88e9f379c3e0dd3c2281ee2ea315e1b8a5f Author: Gabor Greif Date: Sun Apr 13 13:57:15 2014 +0200 Typos in comments >--------------------------------------------------------------- 80bdb88e9f379c3e0dd3c2281ee2ea315e1b8a5f compiler/cmm/CmmSink.hs | 2 +- compiler/typecheck/TcCanonical.lhs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/cmm/CmmSink.hs b/compiler/cmm/CmmSink.hs index c404a2e..187f4c4 100644 --- a/compiler/cmm/CmmSink.hs +++ b/compiler/cmm/CmmSink.hs @@ -516,7 +516,7 @@ conflicts :: DynFlags -> Assignment -> CmmNode O x -> Bool conflicts dflags (r, rhs, addr) node -- (1) node defines registers used by rhs of assignment. This catches - -- assignmnets and all three kinds of calls. See Note [Sinking and calls] + -- assignments and all three kinds of calls. See Note [Sinking and calls] | globalRegistersConflict dflags rhs node = True | localRegistersConflict dflags rhs node = True diff --git a/compiler/typecheck/TcCanonical.lhs b/compiler/typecheck/TcCanonical.lhs index 9eecc47..5784d81 100644 --- a/compiler/typecheck/TcCanonical.lhs +++ b/compiler/typecheck/TcCanonical.lhs @@ -554,7 +554,7 @@ synonym. This works because TcTyConAppCo can deal with synonyms But (Trac #8979) for type T a = (F a, a) where F is a type function -we must expand the synonym in (say) T Int, to expose the type functoin +we must expand the synonym in (say) T Int, to expose the type function to the flattener. From git at git.haskell.org Mon Apr 14 07:07:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Apr 2014 07:07:54 +0000 (UTC) Subject: [commit: ghc] master: Update Haddock submodule to follow LHsBindsLR changes (b4a820f) Message-ID: <20140414070754.1D9022406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b4a820f97e48199a92f5ce7216731500f9a841c9/ghc >--------------------------------------------------------------- commit b4a820f97e48199a92f5ce7216731500f9a841c9 Author: Herbert Valerio Riedel Date: Mon Apr 14 09:04:31 2014 +0200 Update Haddock submodule to follow LHsBindsLR changes This submodule update was forgotten to be included in eeaea2df3fa585db503034f419c6e4331a4d8a84 Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- b4a820f97e48199a92f5ce7216731500f9a841c9 utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 8222e68..ac60bd1 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 8222e68281558f9f6b4ebf1046aad2690d82e1bd +Subproject commit ac60bd1f98ad02644d3ea36dd4926ed6e105c789 From git at git.haskell.org Mon Apr 14 12:04:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Apr 2014 12:04:07 +0000 (UTC) Subject: [commit: ghc] master: Better layout for coercion error message (70d263e) Message-ID: <20140414120408.4B19C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/70d263ecdcb5d11044c7fab570b70f1bf496a9fd/ghc >--------------------------------------------------------------- commit 70d263ecdcb5d11044c7fab570b70f1bf496a9fd Author: Simon Peyton Jones Date: Mon Apr 14 09:59:08 2014 +0100 Better layout for coercion error message >--------------------------------------------------------------- 70d263ecdcb5d11044c7fab570b70f1bf496a9fd compiler/typecheck/TcErrors.lhs | 11 ++++++----- compiler/typecheck/TcRnTypes.lhs | 6 +++--- 2 files changed, 9 insertions(+), 8 deletions(-) diff --git a/compiler/typecheck/TcErrors.lhs b/compiler/typecheck/TcErrors.lhs index 629c7a8..3ca1319 100644 --- a/compiler/typecheck/TcErrors.lhs +++ b/compiler/typecheck/TcErrors.lhs @@ -1083,8 +1083,9 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell)) no_inst_msg | clas == coercibleClass = let (ty1, ty2) = getEqPredTys pred - in ptext (sLit "Could not coerce from") <+> quotes (ppr ty1) <+> - ptext (sLit "to") <+> quotes (ppr ty2) + in sep [ ptext (sLit "Could not coerce from") <+> quotes (ppr ty1) + , nest 19 (ptext (sLit "to") <+> quotes (ppr ty2)) ] + -- The nesting makes the types line up | null givens && null matches = ptext (sLit "No instance for") <+> pprParendType pred | otherwise @@ -1192,9 +1193,9 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell)) Just msg <- coercible_msg_for_tycon rdr_env tc = msg | otherwise - = nest 2 $ hsep [ ptext $ sLit "because", quotes (ppr ty1), - ptext $ sLit "and", quotes (ppr ty2), - ptext $ sLit "are different types." ] + = nest 2 $ sep [ ptext (sLit "because") <+> quotes (ppr ty1) + , nest 4 (vcat [ ptext (sLit "and") <+> quotes (ppr ty2) + , ptext (sLit "are different types.") ]) ] where (ty1, ty2) = getEqPredTys pred diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index 44dc3fa..0355dab 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -1850,9 +1850,9 @@ pprO (DerivOriginDC dc n) = hsep [ ptext (sLit "the"), speakNth n, parens (ptext (sLit "type") <+> quotes (ppr ty)) ] where ty = dataConOrigArgTys dc !! (n-1) pprO (DerivOriginCoerce meth ty1 ty2) - = fsep [ ptext (sLit "the coercion"), ptext (sLit "of the method") - , quotes (ppr meth), ptext (sLit "from type"), quotes (ppr ty1) - , ptext (sLit "to type"), quotes (ppr ty2) ] + = sep [ ptext (sLit "the coercion of the method") <+> quotes (ppr meth) + , ptext (sLit "from type") <+> quotes (ppr ty1) + , nest 2 (ptext (sLit "to type") <+> quotes (ppr ty2)) ] pprO StandAloneDerivOrigin = ptext (sLit "a 'deriving' declaration") pprO DefaultOrigin = ptext (sLit "a 'default' declaration") pprO DoOrigin = ptext (sLit "a do statement") From git at git.haskell.org Mon Apr 14 12:04:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Apr 2014 12:04:10 +0000 (UTC) Subject: [commit: ghc] master: Tidy up trace message (bfd0064) Message-ID: <20140414120410.754EE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bfd00648c0b8527d56974d5af71fd5c149dbc565/ghc >--------------------------------------------------------------- commit bfd00648c0b8527d56974d5af71fd5c149dbc565 Author: Simon Peyton Jones Date: Mon Apr 14 10:01:12 2014 +0100 Tidy up trace message >--------------------------------------------------------------- bfd00648c0b8527d56974d5af71fd5c149dbc565 compiler/typecheck/TcInteract.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index 75835ad..b8c4c81 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -1830,7 +1830,7 @@ matchClassInst _ clas [ ty ] _ matchClassInst _ clas [ _k, ty1, ty2 ] loc | clas == coercibleClass = do - traceTcS "matchClassInst for" $ ppr clas <+> ppr ty1 <+> ppr ty2 <+> text "at depth" <+> ppr (ctLocDepth loc) + traceTcS "matchClassInst for" $ quotes (pprClassPred clas [ty1,ty2]) <+> text "at depth" <+> ppr (ctLocDepth loc) ev <- getCoercibleInst loc ty1 ty2 traceTcS "matchClassInst returned" $ ppr ev return ev From git at git.haskell.org Mon Apr 14 12:04:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Apr 2014 12:04:12 +0000 (UTC) Subject: [commit: ghc] master: A bit more trace information in an ASSERT failure (14046d0) Message-ID: <20140414120412.D562A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/14046d0387188a356d0fbc342506ca5ed3001b1c/ghc >--------------------------------------------------------------- commit 14046d0387188a356d0fbc342506ca5ed3001b1c Author: Simon Peyton Jones Date: Mon Apr 14 12:48:31 2014 +0100 A bit more trace information in an ASSERT failure >--------------------------------------------------------------- 14046d0387188a356d0fbc342506ca5ed3001b1c compiler/typecheck/TcMType.lhs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcMType.lhs b/compiler/typecheck/TcMType.lhs index b9f3d25..f646305 100644 --- a/compiler/typecheck/TcMType.lhs +++ b/compiler/typecheck/TcMType.lhs @@ -410,9 +410,9 @@ writeMetaTyVarRef tyvar ref ty -- Don't check kinds for updates to coercion variables && not (zonked_ty_kind `tcIsSubKind` zonked_tv_kind)) $ WARN( True, hang (text "Ill-kinded update to meta tyvar") - 2 ( ppr tyvar <+> text "::" <+> ppr tv_kind + 2 ( ppr tyvar <+> text "::" <+> (ppr tv_kind $$ ppr zonked_tv_kind) <+> text ":=" - <+> ppr ty <+> text "::" <+> ppr ty_kind) ) + <+> ppr ty <+> text "::" <+> (ppr ty_kind $$ ppr zonked_ty_kind) ) ) (return ()) } where tv_kind = tyVarKind tyvar From git at git.haskell.org Mon Apr 14 12:04:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Apr 2014 12:04:15 +0000 (UTC) Subject: [commit: ghc] master: Honour the untouchability of kind variables (e7f0ae7) Message-ID: <20140414120415.3CB832406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e7f0ae7ff4f2199abe42f20bac825a7802bff466/ghc >--------------------------------------------------------------- commit e7f0ae7ff4f2199abe42f20bac825a7802bff466 Author: Simon Peyton Jones Date: Mon Apr 14 13:03:40 2014 +0100 Honour the untouchability of kind variables Trac #8985 showed up a major shortcoming in the kind unifier: it was ignoring untoucability. This has unpredictably-bad consequences; notably, the skolem-escape check can fail. There were two things wrong * TcRnMonad.isTouchableTcM was returning a constant value for kind variables (wrong), and even worse the constant was back-to-front (it was always False). * We weren't even calling isTouchableTcM in TcType.unifyKindX. I'm not sure how this ever worked. Merge to 7.8.3 in due course. >--------------------------------------------------------------- e7f0ae7ff4f2199abe42f20bac825a7802bff466 compiler/typecheck/TcRnMonad.lhs | 5 -- compiler/typecheck/TcUnify.lhs | 138 +++++++++++++++++++++++--------------- 2 files changed, 84 insertions(+), 59 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e7f0ae7ff4f2199abe42f20bac825a7802bff466 From git at git.haskell.org Mon Apr 14 12:06:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Apr 2014 12:06:46 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #8985 (ff9f9a7) Message-ID: <20140414120646.BA30E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ff9f9a7f2e227fcda7b8a2f52ec8be66de2e76cd/ghc >--------------------------------------------------------------- commit ff9f9a7f2e227fcda7b8a2f52ec8be66de2e76cd Author: Simon Peyton Jones Date: Mon Apr 14 13:06:22 2014 +0100 Test Trac #8985 >--------------------------------------------------------------- ff9f9a7f2e227fcda7b8a2f52ec8be66de2e76cd testsuite/tests/polykinds/T8985.hs | 16 ++++++++++++++++ testsuite/tests/polykinds/all.T | 1 + 2 files changed, 17 insertions(+) diff --git a/testsuite/tests/polykinds/T8985.hs b/testsuite/tests/polykinds/T8985.hs new file mode 100644 index 0000000..28a354b --- /dev/null +++ b/testsuite/tests/polykinds/T8985.hs @@ -0,0 +1,16 @@ +{-# LANGUAGE DataKinds, PolyKinds, TypeFamilies, GADTs, TypeOperators #-} + +module T8905 where + +data X (xs :: [k]) = MkX +data Y :: (k -> *) -> [k] -> * where + MkY :: f x -> Y f (x ': xs) + +type family F (a :: [[*]]) :: * +type instance F xss = Y X xss + +works :: Y X '[ '[ ] ] -> () +works (MkY MkX) = () + +fails :: F '[ '[ ] ] -> () +fails (MkY MkX) = () diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T index 8dc1181..3634d83 100644 --- a/testsuite/tests/polykinds/all.T +++ b/testsuite/tests/polykinds/all.T @@ -99,3 +99,4 @@ test('T8616', normal, compile_fail,['']) test('T8566a', expect_broken(8566), compile,['']) test('T7481', normal, compile_fail,['']) test('T8705', normal, compile, ['']) +test('T8985', normal, compile, ['']) From git at git.haskell.org Mon Apr 14 12:34:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Apr 2014 12:34:23 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T8995-level-generalisation' created Message-ID: <20140414123423.56EF92406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T8995-level-generalisation Referencing: 2c58bef19ee9d245d4344c2ccb4b41e90d91c35a From git at git.haskell.org Mon Apr 14 12:34:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Apr 2014 12:34:25 +0000 (UTC) Subject: [commit: ghc] wip/T8995-level-generalisation: Work in progress on better generalisation technology (2c58bef) Message-ID: <20140414123425.AB2142406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8995-level-generalisation Link : http://ghc.haskell.org/trac/ghc/changeset/2c58bef19ee9d245d4344c2ccb4b41e90d91c35a/ghc >--------------------------------------------------------------- commit 2c58bef19ee9d245d4344c2ccb4b41e90d91c35a Author: Simon Peyton Jones Date: Mon Apr 14 13:33:27 2014 +0100 Work in progress on better generalisation technology There's a long explanation in Trac #8995. This branch just captures where I'm up to. >--------------------------------------------------------------- 2c58bef19ee9d245d4344c2ccb4b41e90d91c35a compiler/typecheck/FunDeps.lhs | 42 +------------ compiler/typecheck/TcBinds.lhs | 9 ++- compiler/typecheck/TcMType.lhs | 4 +- compiler/typecheck/TcRnDriver.lhs | 5 +- compiler/typecheck/TcRnMonad.lhs | 14 +++-- compiler/typecheck/TcSMonad.lhs | 4 +- compiler/typecheck/TcSimplify.lhs | 116 +++++++++++++++++++++++++---------- compiler/typecheck/TcTyClsDecls.lhs | 4 +- compiler/typecheck/TcType.lhs | 5 +- compiler/typecheck/TcUnify.lhs | 2 +- 10 files changed, 112 insertions(+), 93 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2c58bef19ee9d245d4344c2ccb4b41e90d91c35a From git at git.haskell.org Mon Apr 14 13:53:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Apr 2014 13:53:11 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Set RELEASE=NO (39f1f31) Message-ID: <20140414135311.9BBBD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/39f1f310ff16909e6dddd24d8141ac57f71bcfc6/ghc >--------------------------------------------------------------- commit 39f1f310ff16909e6dddd24d8141ac57f71bcfc6 Author: Austin Seipp Date: Mon Apr 14 07:36:31 2014 -0500 Set RELEASE=NO Signed-off-by: Austin Seipp >--------------------------------------------------------------- 39f1f310ff16909e6dddd24d8141ac57f71bcfc6 configure.ac | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/configure.ac b/configure.ac index 45f8232..4428dfd 100644 --- a/configure.ac +++ b/configure.ac @@ -16,7 +16,7 @@ dnl AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.8.2], [glasgow-haskell-bugs at haskell.org], [ghc]) # Set this to YES for a released version, otherwise NO -: ${RELEASE=YES} +: ${RELEASE=NO} # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line # above. If this is not a released version, then we will append the From git at git.haskell.org Mon Apr 14 13:53:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Apr 2014 13:53:14 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Fix linked list manipulation code (buggy on consecutive deletion) (f405460) Message-ID: <20140414135314.158A82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/f40546053913a2cffe158605337e35a319fe2804/ghc >--------------------------------------------------------------- commit f40546053913a2cffe158605337e35a319fe2804 Author: Edward Z. Yang Date: Sat Apr 12 23:02:13 2014 -0700 Fix linked list manipulation code (buggy on consecutive deletion) Signed-off-by: Edward Z. Yang (cherry picked from commit e3938f3adac0093b23694fd347774244ce121478) >--------------------------------------------------------------- f40546053913a2cffe158605337e35a319fe2804 rts/CheckUnload.c | 3 ++- rts/Linker.c | 6 ++++-- 2 files changed, 6 insertions(+), 3 deletions(-) diff --git a/rts/CheckUnload.c b/rts/CheckUnload.c index 8692dea..b381fca 100644 --- a/rts/CheckUnload.c +++ b/rts/CheckUnload.c @@ -290,7 +290,7 @@ void checkUnload (StgClosure *static_objects) // marked as unreferenced can be physically unloaded, because we // have no references to it. prev = NULL; - for (oc = unloaded_objects; oc; prev = oc, oc = next) { + for (oc = unloaded_objects; oc; oc = next) { next = oc->next; if (oc->referenced == 0) { if (prev == NULL) { @@ -304,6 +304,7 @@ void checkUnload (StgClosure *static_objects) } else { IF_DEBUG(linker, debugBelch("Object file still in use: %" PATH_FMT "\n", oc->fileName)); + prev = oc; } } diff --git a/rts/Linker.c b/rts/Linker.c index 814f930..c577cce 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -2928,8 +2928,8 @@ unloadObj( pathchar *path ) IF_DEBUG(linker, debugBelch("unloadObj: %" PATH_FMT "\n", path)); prev = NULL; - for (oc = objects; oc; prev = oc, oc = next) { - next = oc->next; + for (oc = objects; oc; oc = next) { + next = oc->next; // oc might be freed if (!pathcmp(oc->fileName,path)) { @@ -2987,6 +2987,8 @@ unloadObj( pathchar *path ) /* This could be a member of an archive so continue * unloading other members. */ unloadedAnyObj = HS_BOOL_TRUE; + } else { + prev = oc; } } From git at git.haskell.org Mon Apr 14 13:53:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Apr 2014 13:53:16 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: --with-gcc overrides CC_STAGE0 when not cross-compiling (#8498) (4395a06) Message-ID: <20140414135316.798B42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/4395a0624e1eac71bf891f2633cf92754267a604/ghc >--------------------------------------------------------------- commit 4395a0624e1eac71bf891f2633cf92754267a604 Author: Simon Marlow Date: Thu Mar 20 15:47:18 2014 +0000 --with-gcc overrides CC_STAGE0 when not cross-compiling (#8498) (cherry picked from commit 6189c7674fc5c735db1a446d0b222369a3767369) >--------------------------------------------------------------- 4395a0624e1eac71bf891f2633cf92754267a604 aclocal.m4 | 18 +++++++++++++++++- configure.ac | 7 ++++++- 2 files changed, 23 insertions(+), 2 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index c2a7ba2..be38031 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -643,6 +643,10 @@ AC_ARG_WITH($2, else $1=$withval fi + + # Remember that we set this manually. Used to override CC_STAGE0 + # and friends later, if we are not cross-compiling. + With_$2=$withval ], [ if test "$HostOS" != "mingw32" @@ -685,6 +689,10 @@ AC_ARG_WITH($2, else $1=$withval fi + + # Remember that we set this manually. Used to override CC_STAGE0 + # and friends later, if we are not cross-compiling. + With_$2=$withval ], [ if test "$HostOS" != "mingw32" @@ -2058,7 +2066,8 @@ AC_DEFUN([FIND_GCC],[ $1="$CC" else FP_ARG_WITH_PATH_GNU_PROG_OPTIONAL([$1], [$2], [$3]) - # From Xcode 5 on, OS X command line tools do not include gcc anymore. Use clang. + # From Xcode 5 on, OS X command line tools do not include gcc + # anymore. Use clang. if test -z "$$1" then FP_ARG_WITH_PATH_GNU_PROG_OPTIONAL([$1], [clang], [clang]) @@ -2071,4 +2080,11 @@ AC_DEFUN([FIND_GCC],[ AC_SUBST($1) ]) +AC_DEFUN([MAYBE_OVERRIDE_STAGE0],[ + if test ! -z "$With_$1" -a "$CrossCompiling" != "YES"; then + AC_MSG_NOTICE([Not cross-compiling, so --with-$1 also sets $2]) + $2=$With_$1 + fi +]) + # LocalWords: fi diff --git a/configure.ac b/configure.ac index 4428dfd..d6477d4 100644 --- a/configure.ac +++ b/configure.ac @@ -474,6 +474,11 @@ FIND_GCC([WhatGccIsCalled], [gcc], [gcc]) CC="$WhatGccIsCalled" export CC +# If --with-gcc was used, and we're not cross-compiling, then it also +# applies to the stage0 compiler. +MAYBE_OVERRIDE_STAGE0([gcc],[CC_STAGE0]) +MAYBE_OVERRIDE_STAGE0([ar],[AR_STAGE0]) + dnl ** Which ld to use? dnl -------------------------------------------------------------- FP_ARG_WITH_PATH_GNU_PROG([LD], [ld], [ld]) @@ -584,8 +589,8 @@ FP_PROG_LD_FILELIST FPTOOLS_SET_C_LD_FLAGS([target],[CFLAGS],[LDFLAGS],[IGNORE_LINKER_LD_FLAGS],[CPPFLAGS]) FPTOOLS_SET_C_LD_FLAGS([build],[CONF_CC_OPTS_STAGE0],[CONF_GCC_LINKER_OPTS_STAGE0],[CONF_LD_LINKER_OPTS_STAGE0],[CONF_CPP_OPTS_STAGE0]) FPTOOLS_SET_C_LD_FLAGS([target],[CONF_CC_OPTS_STAGE1],[CONF_GCC_LINKER_OPTS_STAGE1],[CONF_LD_LINKER_OPTS_STAGE1],[CONF_CPP_OPTS_STAGE1]) -# Stage 3 won't be supported by cross-compilation FPTOOLS_SET_C_LD_FLAGS([target],[CONF_CC_OPTS_STAGE2],[CONF_GCC_LINKER_OPTS_STAGE2],[CONF_LD_LINKER_OPTS_STAGE2],[CONF_CPP_OPTS_STAGE2]) +# Stage 3 won't be supported by cross-compilation FP_GCC_EXTRA_FLAGS From git at git.haskell.org Mon Apr 14 13:53:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Apr 2014 13:53:18 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Don't perform permission checks for scripts named with -ghci-script (#6017) (22402de) Message-ID: <20140414135318.E00FC2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/22402debae0109988eb9484edbd83e29b10b27d2/ghc >--------------------------------------------------------------- commit 22402debae0109988eb9484edbd83e29b10b27d2 Author: Simon Marlow Date: Thu Mar 20 21:47:22 2014 +0000 Don't perform permission checks for scripts named with -ghci-script (#6017) The user explicitly requested this script on the command-line, so it's unnecessary to require that the script is also owned by the user. Also, it is currently impossible to make a GHCi wrapper that invokes a custom script without first making a copy of the script to circumvent the permissions check, which seems wrong. (cherry picked from commit a6f2c852d49313fa8acea2deb3741ab86c6ef995) >--------------------------------------------------------------- 22402debae0109988eb9484edbd83e29b10b27d2 ghc/InteractiveUI.hs | 26 ++++++++++++++++++-------- ghc/ghc-bin.cabal.in | 1 + 2 files changed, 19 insertions(+), 8 deletions(-) diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index 1476f95..b41c2db 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -455,13 +455,18 @@ runGHCi paths maybe_exprs = do canonicalizePath' fp = liftM Just (canonicalizePath fp) `catchIO` \_ -> return Nothing - sourceConfigFile :: FilePath -> GHCi () - sourceConfigFile file = do + sourceConfigFile :: (FilePath, Bool) -> GHCi () + sourceConfigFile (file, check_perms) = do exists <- liftIO $ doesFileExist file when exists $ do - dir_ok <- liftIO $ checkPerms (getDirectory file) - file_ok <- liftIO $ checkPerms file - when (dir_ok && file_ok) $ do + perms_ok <- + if not check_perms + then return True + else do + dir_ok <- liftIO $ checkPerms (getDirectory file) + file_ok <- liftIO $ checkPerms file + return (dir_ok && file_ok) + when perms_ok $ do either_hdl <- liftIO $ tryIO (openFile file ReadMode) case either_hdl of Left _e -> return () @@ -479,9 +484,14 @@ runGHCi paths maybe_exprs = do setGHCContextFromGHCiState when (read_dot_files) $ do - mcfgs0 <- sequence $ [ current_dir, app_user_dir, home_dir ] ++ map (return . Just ) (ghciScripts dflags) - mcfgs <- liftIO $ mapM canonicalizePath' (catMaybes mcfgs0) - mapM_ sourceConfigFile $ nub $ catMaybes mcfgs + mcfgs0 <- catMaybes <$> sequence [ current_dir, app_user_dir, home_dir ] + let mcfgs1 = zip mcfgs0 (repeat True) + ++ zip (ghciScripts dflags) (repeat False) + -- False says "don't check permissions". We don't + -- require that a script explicitly added by + -- -ghci-script is owned by the current user. (#6017) + mcfgs <- liftIO $ mapM (\(f, b) -> (,b) <$> canonicalizePath' f) mcfgs1 + mapM_ sourceConfigFile $ nub $ [ (f,b) | (Just f, b) <- mcfgs ] -- nub, because we don't want to read .ghci twice if the -- CWD is $HOME. diff --git a/ghc/ghc-bin.cabal.in b/ghc/ghc-bin.cabal.in index 561c55c..68338f3 100644 --- a/ghc/ghc-bin.cabal.in +++ b/ghc/ghc-bin.cabal.in @@ -48,6 +48,7 @@ Executable ghc Extensions: ForeignFunctionInterface, UnboxedTuples, FlexibleInstances, + TupleSections, MagicHash Extensions: CPP, PatternGuards, NondecreasingIndentation From git at git.haskell.org Mon Apr 14 13:53:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Apr 2014 13:53:21 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Include EXTRA_LD_OPTS (amongst other things) when linking programs (eafe20d) Message-ID: <20140414135321.611262406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/eafe20d77d9507f98278323432fbc5293ecef0e5/ghc >--------------------------------------------------------------- commit eafe20d77d9507f98278323432fbc5293ecef0e5 Author: Simon Marlow Date: Tue Mar 25 14:32:28 2014 +0000 Include EXTRA_LD_OPTS (amongst other things) when linking programs One problem was that we weren't including $1_$2_DIST_LD_OPTS when linking a program, which looks to be accidental: it was being defined but not used anywhere. This meant that setting $1_$2_EXTRA_LD_OPTS, for example, had no effect. This commit straightens out the handling of LD_OPTS to be consistent with the way we handle CC_OPTS and HC_OPTS. (cherry picked from commit 975e9cb8e7744a0750bb6c8763f628e05672643e) >--------------------------------------------------------------- eafe20d77d9507f98278323432fbc5293ecef0e5 rules/build-prog.mk | 4 ++-- rules/distdir-way-opts.mk | 49 ++++++++++++++++++++++++++------------------- 2 files changed, 30 insertions(+), 23 deletions(-) diff --git a/rules/build-prog.mk b/rules/build-prog.mk index c6780d1..399369e 100644 --- a/rules/build-prog.mk +++ b/rules/build-prog.mk @@ -259,11 +259,11 @@ $1/$2/build/tmp/$$($1_$2_PROG).dll : $$($1_$2_$$($1_$2_PROGRAM_WAY)_HS_OBJS) $$( else ifeq "$$($1_$2_LINK_WITH_GCC)" "NO" $1/$2/build/tmp/$$($1_$2_PROG) : $$($1_$2_$$($1_$2_PROGRAM_WAY)_HS_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_C_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_S_OBJS) $$($1_$2_OTHER_OBJS) | $$$$(dir $$$$@)/. - $$(call cmd,$1_$2_HC) -o $$@ $$($1_$2_$$($1_$2_PROGRAM_WAY)_ALL_HC_OPTS) $$(LD_OPTS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_GHC_LD_OPTS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_HS_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_C_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_S_OBJS) $$($1_$2_OTHER_OBJS) $$(addprefix -l,$$($1_$2_EXTRA_LIBRARIES)) + $$(call cmd,$1_$2_HC) -o $$@ $$($1_$2_$$($1_$2_PROGRAM_WAY)_ALL_HC_OPTS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_GHC_LD_OPTS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_HS_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_C_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_S_OBJS) $$($1_$2_OTHER_OBJS) $$(addprefix -l,$$($1_$2_EXTRA_LIBRARIES)) else $1/$2/build/tmp/$$($1_$2_PROG) : $$($1_$2_$$($1_$2_PROGRAM_WAY)_HS_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_C_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_S_OBJS) $$($1_$2_OTHER_OBJS) | $$$$(dir $$$$@)/. - $$(call cmd,$1_$2_CC) -o $$@ $$($1_$2_$$($1_$2_PROGRAM_WAY)_ALL_CC_OPTS) $$(LD_OPTS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_HS_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_C_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_S_OBJS) $$($1_$2_OTHER_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_EXTRA_CC_OPTS) $$(addprefix -l,$$($1_$2_EXTRA_LIBRARIES)) + $$(call cmd,$1_$2_CC) -o $$@ $$($1_$2_$$($1_$2_PROGRAM_WAY)_ALL_CC_OPTS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_ALL_LD_OPTS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_HS_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_C_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_S_OBJS) $$($1_$2_OTHER_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_EXTRA_CC_OPTS) $$(addprefix -l,$$($1_$2_EXTRA_LIBRARIES)) endif endif diff --git a/rules/distdir-way-opts.mk b/rules/distdir-way-opts.mk index 8c0377e..93bc60b 100644 --- a/rules/distdir-way-opts.mk +++ b/rules/distdir-way-opts.mk @@ -131,20 +131,6 @@ endif endif endif -ifeq "$3" "dyn" -ifneq "$4" "0" -ifeq "$$(TargetElf)" "YES" -$1_$2_$3_GHC_LD_OPTS += \ - -fno-use-rpaths \ - $$(foreach d,$$($1_$2_TRANSITIVE_DEPS),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'$$$$ORIGIN/../$$d') -optl-Wl,-zorigin -else ifeq "$$(TargetOS_CPP)" "darwin" -$1_$2_$3_GHC_LD_OPTS += \ - -fno-use-rpaths \ - $$(foreach d,$$($1_$2_TRANSITIVE_DEPS),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'@loader_path/../$$d') -endif -endif -endif - $1_$2_$3_ALL_CC_OPTS = \ $$(WAY_$3_CC_OPTS) \ $$($1_$2_DIST_GCC_CC_OPTS) \ @@ -154,13 +140,20 @@ $1_$2_$3_ALL_CC_OPTS = \ $$(EXTRA_CC_OPTS) $1_$2_$3_GHC_CC_OPTS = \ - $$(addprefix -optc, \ - $$(WAY_$3_CC_OPTS) \ - $$($1_$2_DIST_CC_OPTS) \ - $$($1_$2_$3_CC_OPTS) \ - $$($$(basename $$<)_CC_OPTS) \ - $$($1_$2_EXTRA_CC_OPTS) \ - $$(EXTRA_CC_OPTS)) \ + $$(addprefix -optc, $$($1_$2_$3_ALL_CC_OPTS)) \ + $$($1_$2_$3_MOST_HC_OPTS) + +# Options for passing to plain ld +$1_$2_$3_ALL_LD_OPTS = \ + $$(WAY_$3_LD_OPTS) \ + $$($1_$2_DIST_LD_OPTS) \ + $$($1_$2_$3_LD_OPTS) \ + $$($1_$2_EXTRA_LD_OPTS) \ + $$(EXTRA_LD_OPTS) + +# Options for passing to GHC when we use it for linking +$1_$2_$3_GHC_LD_OPTS = \ + $$(addprefix -optl, $$($1_$2_$3_ALL_LD_OPTS)) \ $$($1_$2_$3_MOST_HC_OPTS) $1_$2_$3_ALL_AS_OPTS = \ @@ -172,5 +165,19 @@ $1_$2_$3_ALL_AS_OPTS = \ $$($1_$2_$3_AS_OPTS) \ $$(EXTRA_AS_OPTS) +ifeq "$3" "dyn" +ifneq "$4" "0" +ifeq "$$(TargetElf)" "YES" +$1_$2_$3_GHC_LD_OPTS += \ + -fno-use-rpaths \ + $$(foreach d,$$($1_$2_TRANSITIVE_DEPS),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'$$$$ORIGIN/../$$d') -optl-Wl,-zorigin +else ifeq "$$(TargetOS_CPP)" "darwin" +$1_$2_$3_GHC_LD_OPTS += \ + -fno-use-rpaths \ + $$(foreach d,$$($1_$2_TRANSITIVE_DEPS),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'@loader_path/../$$d') +endif +endif +endif + endef From git at git.haskell.org Mon Apr 14 13:53:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Apr 2014 13:53:23 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Pass custom CC and LD opts to Cabal when configuring a package (7d75064) Message-ID: <20140414135323.D9F062406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/7d75064846e16948af2a741b915e42baf4b56523/ghc >--------------------------------------------------------------- commit 7d75064846e16948af2a741b915e42baf4b56523 Author: Simon Marlow Date: Thu Mar 27 12:29:48 2014 +0000 Pass custom CC and LD opts to Cabal when configuring a package Cabal compiles a program to check for the existence of foreign libraries, so it needs to know our custom options, if any. (cherry picked from commit e7f26cd3e7e9eb92e3eb3457730e635747b43050) >--------------------------------------------------------------- 7d75064846e16948af2a741b915e42baf4b56523 rules/build-package-data.mk | 14 +++++++++++--- 1 file changed, 11 insertions(+), 3 deletions(-) diff --git a/rules/build-package-data.mk b/rules/build-package-data.mk index c53a084..aea2adb 100644 --- a/rules/build-package-data.mk +++ b/rules/build-package-data.mk @@ -49,9 +49,17 @@ endif # We filter out -Werror from SRC_CC_OPTS, because when configure tests # for a feature it may not generate warning-free C code, and thus may # think that the feature doesn't exist if -Werror is on. -$1_$2_CONFIGURE_OPTS += --configure-option=CFLAGS="$$(filter-out -Werror,$$(SRC_CC_OPTS)) $$(CONF_CC_OPTS_STAGE$3) $$($1_CC_OPTS) $$($1_$2_CC_OPTS) $$(SRC_CC_WARNING_OPTS)" -$1_$2_CONFIGURE_OPTS += --configure-option=LDFLAGS="$$(SRC_LD_OPTS) $$(CONF_GCC_LINKER_OPTS_STAGE$3) $$($1_LD_OPTS) $$($1_$2_LD_OPTS)" -$1_$2_CONFIGURE_OPTS += --configure-option=CPPFLAGS="$$(SRC_CPP_OPTS) $$(CONF_CPP_OPTS_STAGE$3) $$($1_CPP_OPTS) $$($1_$2_CPP_OPTS)" +$1_$2_CONFIGURE_CFLAGS = $$(filter-out -Werror,$$(SRC_CC_OPTS)) $$(CONF_CC_OPTS_STAGE$3) $$($1_CC_OPTS) $$($1_$2_CC_OPTS) $$(SRC_CC_WARNING_OPTS) +$1_$2_CONFIGURE_LDFLAGS = $$(SRC_LD_OPTS) $$(CONF_GCC_LINKER_OPTS_STAGE$3) $$($1_LD_OPTS) $$($1_$2_LD_OPTS) +$1_$2_CONFIGURE_CPPFLAGS = $$(SRC_CPP_OPTS) $$(CONF_CPP_OPTS_STAGE$3) $$($1_CPP_OPTS) $$($1_$2_CPP_OPTS) + +$1_$2_CONFIGURE_OPTS += --configure-option=CFLAGS="$$($1_$2_CONFIGURE_CFLAGS)" +$1_$2_CONFIGURE_OPTS += --configure-option=LDFLAGS="$$($1_$2_CONFIGURE_LDFLAGS)" +$1_$2_CONFIGURE_OPTS += --configure-option=CPPFLAGS="$$($1_$2_CONFIGURE_CPPFLAGS)" + +# Also pass these as gcc-options, because Cabal uses them to check for +# the existence of foreign libraries. +$1_$2_CONFIGURE_OPTS += --gcc-options="$$($1_$2_CONFIGURE_CFLAGS) $$($1_$2_CONFIGURE_LDFLAGS)" ifneq "$$(ICONV_INCLUDE_DIRS)" "" $1_$2_CONFIGURE_OPTS += --configure-option=--with-iconv-includes="$$(ICONV_INCLUDE_DIRS)" From git at git.haskell.org Mon Apr 14 13:53:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Apr 2014 13:53:26 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Include SRC_CC_OPTS and SRC_LD_OPTS when compiling ghc-cabal (8351e13) Message-ID: <20140414135326.3703E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/8351e13d45893766104e1cdb14e30bc53f3cbcc7/ghc >--------------------------------------------------------------- commit 8351e13d45893766104e1cdb14e30bc53f3cbcc7 Author: Simon Marlow Date: Thu Mar 27 12:33:44 2014 +0000 Include SRC_CC_OPTS and SRC_LD_OPTS when compiling ghc-cabal (cherry picked from commit d011cdefca7aa66cbcf71c941f38a4e6dd4c5579) >--------------------------------------------------------------- 8351e13d45893766104e1cdb14e30bc53f3cbcc7 utils/ghc-cabal/ghc.mk | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/utils/ghc-cabal/ghc.mk b/utils/ghc-cabal/ghc.mk index 29db69c..ff5762a 100644 --- a/utils/ghc-cabal/ghc.mk +++ b/utils/ghc-cabal/ghc.mk @@ -31,7 +31,10 @@ $(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*/*.hs) $(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*.hs) $(ghc-cabal_DIST_BINARY): utils/ghc-cabal/Main.hs $(TOUCH_DEP) | $$(dir $$@)/. bootstrapping/. - "$(GHC)" $(SRC_HC_OPTS) --make utils/ghc-cabal/Main.hs -o $@ \ + "$(GHC)" $(SRC_HC_OPTS) \ + $(addprefix -optc, $(SRC_CC_OPTS) $(CONF_CC_OPTS_STAGE0)) \ + $(addprefix -optl, $(SRC_LD_OPTS) $(CONF_LD_OPTS_STAGE0)) \ + --make utils/ghc-cabal/Main.hs -o $@ \ -no-user-$(GHC_PACKAGE_DB_FLAG) \ -Wall -fno-warn-unused-imports -fno-warn-warnings-deprecations \ -DCABAL_VERSION=$(CABAL_VERSION) \ @@ -65,4 +68,3 @@ utils/ghc-cabal_dist-install_WANT_BINDIST_WRAPPER = YES utils/ghc-cabal_dist-install_MODULES = Main $(eval $(call build-prog,utils/ghc-cabal,dist-install,1)) - From git at git.haskell.org Mon Apr 14 13:53:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Apr 2014 13:53:28 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Use LDFLAGS when compiling ghc-pwd (636f550) Message-ID: <20140414135328.A82842406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/636f5500722e2a1b0f8c764e85d7a2b51ec3f25f/ghc >--------------------------------------------------------------- commit 636f5500722e2a1b0f8c764e85d7a2b51ec3f25f Author: Simon Marlow Date: Thu Mar 27 12:34:38 2014 +0000 Use LDFLAGS when compiling ghc-pwd (cherry picked from commit 2aa78106ae8f3c9b71d7b85c2a8a5558c4c35fb4) >--------------------------------------------------------------- 636f5500722e2a1b0f8c764e85d7a2b51ec3f25f aclocal.m4 | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/aclocal.m4 b/aclocal.m4 index be38031..5f5c424 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -1806,7 +1806,13 @@ AC_MSG_NOTICE(Building in-tree ghc-pwd) dnl except we don't want to have to know what make is called. Sigh. rm -rf utils/ghc-pwd/dist-boot mkdir utils/ghc-pwd/dist-boot - if ! "$WithGhc" -v0 -no-user-$GHC_PACKAGE_DB_FLAG -hidir utils/ghc-pwd/dist-boot -odir utils/ghc-pwd/dist-boot -stubdir utils/ghc-pwd/dist-boot --make utils/ghc-pwd/Main.hs -o utils/ghc-pwd/dist-boot/ghc-pwd + dnl If special linker flags are needed to build things, then allow + dnl the user to pass them in via LDFLAGS. + changequote(, )dnl + GHC_LDFLAGS=`echo $LDFLAGS | sed 's/\(^\| \)\([^ ]\)/\1-optl\2/g'` + changequote([, ])dnl + echo $GHC_LDFLAGS + if ! "$WithGhc" $GHC_LDFLAGS -v0 -no-user-$GHC_PACKAGE_DB_FLAG -hidir utils/ghc-pwd/dist-boot -odir utils/ghc-pwd/dist-boot -stubdir utils/ghc-pwd/dist-boot --make utils/ghc-pwd/Main.hs -o utils/ghc-pwd/dist-boot/ghc-pwd then AC_MSG_ERROR([Building ghc-pwd failed]) fi From git at git.haskell.org Mon Apr 14 13:53:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Apr 2014 13:53:30 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Remove debugging output (0583834) Message-ID: <20140414135331.2CCB12406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/05838341dec1ec3acfa6523015b6b7c062f43998/ghc >--------------------------------------------------------------- commit 05838341dec1ec3acfa6523015b6b7c062f43998 Author: Simon Marlow Date: Fri Mar 28 09:09:38 2014 +0000 Remove debugging output (cherry picked from commit 4c8edfd2c722504baaa6896d194fd3a8c3f9b652) >--------------------------------------------------------------- 05838341dec1ec3acfa6523015b6b7c062f43998 aclocal.m4 | 1 - 1 file changed, 1 deletion(-) diff --git a/aclocal.m4 b/aclocal.m4 index 5f5c424..7cae3b5 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -1811,7 +1811,6 @@ AC_MSG_NOTICE(Building in-tree ghc-pwd) changequote(, )dnl GHC_LDFLAGS=`echo $LDFLAGS | sed 's/\(^\| \)\([^ ]\)/\1-optl\2/g'` changequote([, ])dnl - echo $GHC_LDFLAGS if ! "$WithGhc" $GHC_LDFLAGS -v0 -no-user-$GHC_PACKAGE_DB_FLAG -hidir utils/ghc-pwd/dist-boot -odir utils/ghc-pwd/dist-boot -stubdir utils/ghc-pwd/dist-boot --make utils/ghc-pwd/Main.hs -o utils/ghc-pwd/dist-boot/ghc-pwd then AC_MSG_ERROR([Building ghc-pwd failed]) From git at git.haskell.org Mon Apr 14 13:53:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Apr 2014 13:53:33 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Include LD_OPTS when building the RTS shared libs (cbb5460) Message-ID: <20140414135333.7B5702406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/cbb54604bb15ead8df7e663111dd32c361c5c551/ghc >--------------------------------------------------------------- commit cbb54604bb15ead8df7e663111dd32c361c5c551 Author: Simon Marlow Date: Mon Apr 7 13:51:29 2014 +0100 Include LD_OPTS when building the RTS shared libs (cherry picked from commit ec3e949e29990c054850f621e14a9d77e3197aee) >--------------------------------------------------------------- cbb54604bb15ead8df7e663111dd32c361c5c551 rts/ghc.mk | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/rts/ghc.mk b/rts/ghc.mk index 3929adb..0d2b341 100644 --- a/rts/ghc.mk +++ b/rts/ghc.mk @@ -190,7 +190,9 @@ $$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) rts/dist/libs.depend rts/d "$$(RM)" $$(RM_OPTS) $$@ "$$(rts_dist_HC)" -package-name rts -shared -dynamic -dynload deploy \ -no-auto-link-packages -Lrts/dist/build -l$$(LIBFFI_NAME) \ - `cat rts/dist/libs.depend` $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) -o $$@ + `cat rts/dist/libs.depend` $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) \ + $$(rts_dist_$1_GHC_LD_OPTS) \ + -o $$@ else ifneq "$$(UseSystemLibFFI)" "YES" LIBFFI_LIBS = -Lrts/dist/build -l$$(LIBFFI_NAME) @@ -209,6 +211,7 @@ $$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) rts/dist/libs.depend $$( "$$(RM)" $$(RM_OPTS) $$@ "$$(rts_dist_HC)" -package-name rts -shared -dynamic -dynload deploy \ -no-auto-link-packages $$(LIBFFI_LIBS) `cat rts/dist/libs.depend` $$(rts_$1_OBJS) \ + $$(rts_dist_$1_GHC_LD_OPTS) \ $$(rts_$1_DTRACE_OBJS) -o $$@ endif else From git at git.haskell.org Mon Apr 14 13:53:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Apr 2014 13:53:35 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Don't preprocess .s files (cb0d04e) Message-ID: <20140414135335.D992E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/cb0d04e60dec0f4cf5a2abc785179e86ce603197/ghc >--------------------------------------------------------------- commit cb0d04e60dec0f4cf5a2abc785179e86ce603197 Author: Simon Marlow Date: Tue Apr 8 10:21:27 2014 +0100 Don't preprocess .s files One important reason is that gcc 4.8.1 sometimes crashes: http://gcc.gnu.org/bugzilla/show_bug.cgi?id=60436 Another reason is that preprocessing assembly files unnecessarily slows down compilation. (cherry picked from commit 396648eebaa1144d4d1f5326db716e8130f73732) >--------------------------------------------------------------- cb0d04e60dec0f4cf5a2abc785179e86ce603197 compiler/main/DriverPhases.hs | 27 ++++++++++++++------------- compiler/main/DriverPipeline.hs | 21 ++++++++++++--------- ghc/Main.hs | 5 +++-- 3 files changed, 29 insertions(+), 24 deletions(-) diff --git a/compiler/main/DriverPhases.hs b/compiler/main/DriverPhases.hs index c406f6a..2981269 100644 --- a/compiler/main/DriverPhases.hs +++ b/compiler/main/DriverPhases.hs @@ -82,7 +82,7 @@ data Phase | HCc -- Haskellised C (as opposed to vanilla C) compilation | Splitter -- Assembly file splitter (part of '-split-objs') | SplitAs -- Assembler for split assembly files (part of '-split-objs') - | As -- Assembler for regular assembly files + | As Bool -- Assembler for regular assembly files (Bool: with-cpp) | LlvmOpt -- Run LLVM opt tool over llvm assembly | LlvmLlc -- LLVM bitcode to native assembly | LlvmMangle -- Fix up TNTC by processing assembly produced by LLVM @@ -119,7 +119,7 @@ eqPhase Cobjcpp Cobjcpp = True eqPhase HCc HCc = True eqPhase Splitter Splitter = True eqPhase SplitAs SplitAs = True -eqPhase As As = True +eqPhase (As x) (As y) = x == y eqPhase LlvmOpt LlvmOpt = True eqPhase LlvmLlc LlvmLlc = True eqPhase LlvmMangle LlvmMangle = True @@ -150,21 +150,21 @@ nextPhase dflags p Splitter -> SplitAs LlvmOpt -> LlvmLlc LlvmLlc -> LlvmMangle - LlvmMangle -> As + LlvmMangle -> As False SplitAs -> MergeStub - As -> MergeStub - Ccpp -> As - Cc -> As - Cobjc -> As - Cobjcpp -> As + As _ -> MergeStub + Ccpp -> As False + Cc -> As False + Cobjc -> As False + Cobjcpp -> As False CmmCpp -> Cmm Cmm -> maybeHCc - HCc -> As + HCc -> As False MergeStub -> StopLn StopLn -> panic "nextPhase: nothing after StopLn" where maybeHCc = if platformUnregisterised (targetPlatform dflags) then HCc - else As + else As False -- the first compilation phase for a given file is determined -- by its suffix. @@ -186,8 +186,8 @@ startPhase "mm" = Cobjcpp startPhase "cc" = Ccpp startPhase "cxx" = Ccpp startPhase "split_s" = Splitter -startPhase "s" = As -startPhase "S" = As +startPhase "s" = As False +startPhase "S" = As True startPhase "ll" = LlvmOpt startPhase "bc" = LlvmLlc startPhase "lm_s" = LlvmMangle @@ -215,7 +215,8 @@ phaseInputExt Cobjc = "m" phaseInputExt Cobjcpp = "mm" phaseInputExt Cc = "c" phaseInputExt Splitter = "split_s" -phaseInputExt As = "s" +phaseInputExt (As True) = "S" +phaseInputExt (As False) = "s" phaseInputExt LlvmOpt = "ll" phaseInputExt LlvmLlc = "bc" phaseInputExt LlvmMangle = "lm_s" diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 564edd2..2c71967 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -498,8 +498,8 @@ compileFile hsc_env stop_phase (src, mb_phase) = do | otherwise = Persistent stop_phase' = case stop_phase of - As | split -> SplitAs - _ -> stop_phase + As _ | split -> SplitAs + _ -> stop_phase ( _, out_file) <- runPipeline stop_phase' hsc_env (src, fmap RealPhase mb_phase) Nothing output @@ -730,7 +730,7 @@ getOutputFilename stop_phase output basename dflags next_phase maybe_location -- sometimes, we keep output from intermediate stages keep_this_output = case next_phase of - As | keep_s -> True + As _ | keep_s -> True LlvmOpt | keep_bc -> True HCc | keep_hc -> True _other -> False @@ -1078,7 +1078,7 @@ runPhase (RealPhase cc_phase) input_fn dflags | otherwise = [] -- Decide next phase - let next_phase = As + let next_phase = As False output_fn <- phaseOutputFilename next_phase let @@ -1190,7 +1190,7 @@ runPhase (RealPhase Splitter) input_fn dflags -- As, SpitAs phase : Assembler -- This is for calling the assembler on a regular assembly file (not split). -runPhase (RealPhase As) input_fn dflags +runPhase (RealPhase (As with_cpp)) input_fn dflags = do -- LLVM from version 3.0 onwards doesn't support the OS X system -- assembler, so we use clang as the assembler instead. (#5636) @@ -1231,7 +1231,10 @@ runPhase (RealPhase As) input_fn dflags then [SysTools.Option "-mcpu=v9"] else []) - ++ [ SysTools.Option "-x", SysTools.Option "assembler-with-cpp" + ++ [ SysTools.Option "-x" + , if with_cpp + then SysTools.Option "assembler-with-cpp" + else SysTools.Option "assembler" , SysTools.Option "-c" , SysTools.FileOption "" inputFilename , SysTools.Option "-o" @@ -1385,7 +1388,7 @@ runPhase (RealPhase LlvmLlc) input_fn dflags let next_phase = case gopt Opt_NoLlvmMangler dflags of False -> LlvmMangle True | gopt Opt_SplitObjs dflags -> Splitter - True -> As + True -> As False output_fn <- phaseOutputFilename next_phase @@ -1454,7 +1457,7 @@ runPhase (RealPhase LlvmLlc) input_fn dflags runPhase (RealPhase LlvmMangle) input_fn dflags = do - let next_phase = if gopt Opt_SplitObjs dflags then Splitter else As + let next_phase = if gopt Opt_SplitObjs dflags then Splitter else As False output_fn <- phaseOutputFilename next_phase liftIO $ llvmFixupAsm dflags input_fn output_fn return (RealPhase next_phase, output_fn) @@ -2186,7 +2189,7 @@ hscPostBackendPhase dflags _ hsc_lang = case hsc_lang of HscC -> HCc HscAsm | gopt Opt_SplitObjs dflags -> Splitter - | otherwise -> As + | otherwise -> As False HscLlvm -> LlvmOpt HscNothing -> StopLn HscInterpreted -> StopLn diff --git a/ghc/Main.hs b/ghc/Main.hs index 481e7df..d8be08a 100644 --- a/ghc/Main.hs +++ b/ghc/Main.hs @@ -562,7 +562,7 @@ mode_flags = , Flag "M" (PassFlag (setMode doMkDependHSMode)) , Flag "E" (PassFlag (setMode (stopBeforeMode anyHsc))) , Flag "C" (PassFlag (setMode (stopBeforeMode HCc))) - , Flag "S" (PassFlag (setMode (stopBeforeMode As))) + , Flag "S" (PassFlag (setMode (stopBeforeMode (As False)))) , Flag "-make" (PassFlag (setMode doMakeMode)) , Flag "-interactive" (PassFlag (setMode doInteractiveMode)) , Flag "-abi-hash" (PassFlag (setMode doAbiHashMode)) @@ -629,7 +629,8 @@ doMake srcs = do haskellish (f,Nothing) = looksLikeModuleName f || isHaskellUserSrcFilename f || '.' `notElem` f haskellish (_,Just phase) = - phase `notElem` [As, Cc, Cobjc, Cobjcpp, CmmCpp, Cmm, StopLn] + phase `notElem` [ As True, As False, Cc, Cobjc, Cobjcpp, CmmCpp, Cmm + , StopLn] hsc_env <- GHC.getSession From git at git.haskell.org Tue Apr 15 13:34:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Apr 2014 13:34:11 +0000 (UTC) Subject: [commit: ghc] master: s/FromList/isList in docs (a107737) Message-ID: <20140415133411.091842406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a107737f84f6738a9fa572ec9c5da49c9db8a8b5/ghc >--------------------------------------------------------------- commit a107737f84f6738a9fa572ec9c5da49c9db8a8b5 Author: Joachim Breitner Date: Tue Apr 15 15:33:39 2014 +0200 s/FromList/isList in docs This was reported by David Virebayre on haskell-cafe. >--------------------------------------------------------------- a107737f84f6738a9fa572ec9c5da49c9db8a8b5 docs/users_guide/glasgow_exts.xml | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index a19bc8b..acc7963 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -5317,7 +5317,7 @@ class IsList l where fromListN _ = fromList -The FromList class and its methods are intended to be +The IsList class and its methods are intended to be used in conjunction with the extension. The type function @@ -5349,32 +5349,32 @@ of IsList, so that list notation becomes useful for completely new data types. Here are several example instances: -instance FromList [a] where +instance IsList [a] where type Item [a] = a fromList = id toList = id -instance (Ord a) => FromList (Set a) where +instance (Ord a) => IsList (Set a) where type Item (Set a) = a fromList = Set.fromList toList = Set.toList -instance (Ord k) => FromList (Map k v) where +instance (Ord k) => IsList (Map k v) where type Item (Map k v) = (k,v) fromList = Map.fromList toList = Map.toList -instance FromList (IntMap v) where +instance IsList (IntMap v) where type Item (IntMap v) = (Int,v) fromList = IntMap.fromList toList = IntMap.toList -instance FromList Text where +instance IsList Text where type Item Text = Char fromList = Text.pack toList = Text.unpack -instance FromList (Vector a) where +instance IsList (Vector a) where type Item (Vector a) = a fromList = Vector.fromList fromListN = Vector.fromListN From git at git.haskell.org Tue Apr 15 20:07:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Apr 2014 20:07:43 +0000 (UTC) Subject: [commit: ghc] branch 'wip/Cabal-1.20' created Message-ID: <20140415200743.DF3D42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/Cabal-1.20 Referencing: e5d61a43c519d2cf6f4e84cb5ff57fb319d96ba6 From git at git.haskell.org Tue Apr 15 20:07:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Apr 2014 20:07:46 +0000 (UTC) Subject: [commit: ghc] wip/Cabal-1.20: Update Cabal to tip of v1.20 (e5d61a4) Message-ID: <20140415200746.4C01A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/Cabal-1.20 Link : http://ghc.haskell.org/trac/ghc/changeset/e5d61a43c519d2cf6f4e84cb5ff57fb319d96ba6/ghc >--------------------------------------------------------------- commit e5d61a43c519d2cf6f4e84cb5ff57fb319d96ba6 Author: Herbert Valerio Riedel Date: Tue Apr 15 11:09:45 2014 +0200 Update Cabal to tip of v1.20 This corresponds to the RC of the soon-to-be Cabal 1.20 release One noteworthy change is the removal of the `--with-ranlib` flag requiring a small adaptation in the GHC build system. Moreover two new licences were added, MPL and BSD2. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- e5d61a43c519d2cf6f4e84cb5ff57fb319d96ba6 libraries/Cabal | 2 +- .../bin-package-db/Distribution/InstalledPackageInfo/Binary.hs | 6 +++++- libraries/bin-package-db/bin-package-db.cabal | 2 +- rules/build-package-data.mk | 1 - utils/ghc-cabal/ghc-cabal.cabal | 2 +- utils/ghctags/Main.hs | 4 +--- utils/ghctags/ghctags.cabal | 2 +- 7 files changed, 10 insertions(+), 9 deletions(-) diff --git a/libraries/Cabal b/libraries/Cabal index c226c0d..38e361e 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit c226c0de042999bbe4c5c339c6c28a9be7f0c6d1 +Subproject commit 38e361e5ad2bb52d615166a5aef3772e5856c3d7 diff --git a/libraries/bin-package-db/Distribution/InstalledPackageInfo/Binary.hs b/libraries/bin-package-db/Distribution/InstalledPackageInfo/Binary.hs index 27e23d8..ab7fcf5 100644 --- a/libraries/bin-package-db/Distribution/InstalledPackageInfo/Binary.hs +++ b/libraries/bin-package-db/Distribution/InstalledPackageInfo/Binary.hs @@ -132,7 +132,9 @@ instance Binary License where put OtherLicense = do putWord8 7 put (Apache v) = do putWord8 8; put v put (AGPL v) = do putWord8 9; put v - put (UnknownLicense str) = do putWord8 10; put str + put BSD2 = do putWord8 10 + put (MPL v) = do putWord8 11; put v + put (UnknownLicense str) = do putWord8 12; put str get = do n <- getWord8 @@ -147,6 +149,8 @@ instance Binary License where 7 -> return OtherLicense 8 -> do v <- get; return (Apache v) 9 -> do v <- get; return (AGPL v) + 10 -> return BSD2 + 11 -> do v <- get; return (MPL v) _ -> do str <- get; return (UnknownLicense str) instance Binary Version where diff --git a/libraries/bin-package-db/bin-package-db.cabal b/libraries/bin-package-db/bin-package-db.cabal index 1d3054c..44408a7 100644 --- a/libraries/bin-package-db/bin-package-db.cabal +++ b/libraries/bin-package-db/bin-package-db.cabal @@ -19,7 +19,7 @@ Library { build-depends: base >= 4 && < 5 build-depends: binary >= 0.5 && < 0.8, - Cabal >= 1.18 && < 1.19 + Cabal >= 1.20 && < 1.21 extensions: CPP } diff --git a/rules/build-package-data.mk b/rules/build-package-data.mk index aea2adb..2e61001 100644 --- a/rules/build-package-data.mk +++ b/rules/build-package-data.mk @@ -94,7 +94,6 @@ endif $1_$2_CONFIGURE_OPTS += --configure-option=--with-cc="$$(CC_STAGE$3)" $1_$2_CONFIGURE_OPTS += --with-ar="$$(AR_STAGE$3)" -$1_$2_CONFIGURE_OPTS += --with-ranlib="$$(REAL_RANLIB_CMD)" $1_$2_CONFIGURE_OPTS += $$(if $$(ALEX),--with-alex="$$(ALEX)") $1_$2_CONFIGURE_OPTS += $$(if $$(HAPPY),--with-happy="$$(HAPPY)") diff --git a/utils/ghc-cabal/ghc-cabal.cabal b/utils/ghc-cabal/ghc-cabal.cabal index 10d6e0a..74399ce 100644 --- a/utils/ghc-cabal/ghc-cabal.cabal +++ b/utils/ghc-cabal/ghc-cabal.cabal @@ -17,7 +17,7 @@ Executable ghc-cabal Build-Depends: base >= 3 && < 5, bytestring >= 0.10 && < 0.11, - Cabal >= 1.18 && < 1.19, + Cabal >= 1.20 && < 1.21, directory >= 1.1 && < 1.3, filepath >= 1.2 && < 1.4 diff --git a/utils/ghctags/Main.hs b/utils/ghctags/Main.hs index 9bf1a2d..a67891e 100644 --- a/utils/ghctags/Main.hs +++ b/utils/ghctags/Main.hs @@ -20,7 +20,6 @@ import SrcLoc import Distribution.Simple.GHC ( componentGhcOptions ) import Distribution.Simple.Configure ( getPersistBuildConfig ) -import Distribution.Simple.Compiler ( compilerVersion ) import Distribution.Simple.Program.GHC ( renderGhcOptions ) import Distribution.PackageDescription ( library, libBuildInfo ) import Distribution.Simple.LocalBuildInfo @@ -191,8 +190,7 @@ flagsFromCabal distPref = do let bi = libBuildInfo lib odir = buildDir lbi opts = componentGhcOptions V.normal lbi bi clbi odir - version = compilerVersion (compiler lbi) - in return $ renderGhcOptions version opts + in return $ renderGhcOptions (compiler lbi) opts _ -> error "no library" ---------------------------------------------------------------- diff --git a/utils/ghctags/ghctags.cabal b/utils/ghctags/ghctags.cabal index 07221d3..0e97cca 100644 --- a/utils/ghctags/ghctags.cabal +++ b/utils/ghctags/ghctags.cabal @@ -17,6 +17,6 @@ Executable ghctags Build-Depends: base >= 4 && < 5, containers, - Cabal, + Cabal >= 1.20 && <1.21, ghc From git at git.haskell.org Wed Apr 16 15:00:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Apr 2014 15:00:53 +0000 (UTC) Subject: [commit: ghc] master: Update Cabal submodule to tip of v1.20 branch (8992d52) Message-ID: <20140416150054.0076A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8992d5269804b727fb77249511e89df678526907/ghc >--------------------------------------------------------------- commit 8992d5269804b727fb77249511e89df678526907 Author: Herbert Valerio Riedel Date: Tue Apr 15 11:09:45 2014 +0200 Update Cabal submodule to tip of v1.20 branch This corresponds to the RC of the soon-to-be Cabal 1.20 release One noteworthy change is the removal of the `--with-ranlib` flag requiring a small adaptation in the GHC build system. Moreover two new licences were added, MPL and BSD2. Due to https://github.com/haskell/cabal/issues/1622 Cabal-1.20 now allows to strip libraries as well, this doesn't work well with `ghc-cabal copy` being fed a `":"` strip-command argument which was simply ignored in the past. The current code tries to retain this semantics as backward compat. However, this needs more investigation as I'm not sure if/why the `test_bindist` step doesn't want the libraries to be stripped on installation. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 8992d5269804b727fb77249511e89df678526907 libraries/Cabal | 2 +- .../Distribution/InstalledPackageInfo/Binary.hs | 6 +++++- libraries/bin-package-db/bin-package-db.cabal | 2 +- rules/build-package-data.mk | 1 - utils/ghc-cabal/Main.hs | 10 ++++++++++ utils/ghc-cabal/ghc-cabal.cabal | 2 +- utils/ghctags/Main.hs | 4 +--- utils/ghctags/ghctags.cabal | 2 +- 8 files changed, 20 insertions(+), 9 deletions(-) diff --git a/libraries/Cabal b/libraries/Cabal index c226c0d..aaa6183 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit c226c0de042999bbe4c5c339c6c28a9be7f0c6d1 +Subproject commit aaa6183dba81d77637dff84f83136639d40f268f diff --git a/libraries/bin-package-db/Distribution/InstalledPackageInfo/Binary.hs b/libraries/bin-package-db/Distribution/InstalledPackageInfo/Binary.hs index 27e23d8..ab7fcf5 100644 --- a/libraries/bin-package-db/Distribution/InstalledPackageInfo/Binary.hs +++ b/libraries/bin-package-db/Distribution/InstalledPackageInfo/Binary.hs @@ -132,7 +132,9 @@ instance Binary License where put OtherLicense = do putWord8 7 put (Apache v) = do putWord8 8; put v put (AGPL v) = do putWord8 9; put v - put (UnknownLicense str) = do putWord8 10; put str + put BSD2 = do putWord8 10 + put (MPL v) = do putWord8 11; put v + put (UnknownLicense str) = do putWord8 12; put str get = do n <- getWord8 @@ -147,6 +149,8 @@ instance Binary License where 7 -> return OtherLicense 8 -> do v <- get; return (Apache v) 9 -> do v <- get; return (AGPL v) + 10 -> return BSD2 + 11 -> do v <- get; return (MPL v) _ -> do str <- get; return (UnknownLicense str) instance Binary Version where diff --git a/libraries/bin-package-db/bin-package-db.cabal b/libraries/bin-package-db/bin-package-db.cabal index 1d3054c..44408a7 100644 --- a/libraries/bin-package-db/bin-package-db.cabal +++ b/libraries/bin-package-db/bin-package-db.cabal @@ -19,7 +19,7 @@ Library { build-depends: base >= 4 && < 5 build-depends: binary >= 0.5 && < 0.8, - Cabal >= 1.18 && < 1.19 + Cabal >= 1.20 && < 1.21 extensions: CPP } diff --git a/rules/build-package-data.mk b/rules/build-package-data.mk index aea2adb..2e61001 100644 --- a/rules/build-package-data.mk +++ b/rules/build-package-data.mk @@ -94,7 +94,6 @@ endif $1_$2_CONFIGURE_OPTS += --configure-option=--with-cc="$$(CC_STAGE$3)" $1_$2_CONFIGURE_OPTS += --with-ar="$$(AR_STAGE$3)" -$1_$2_CONFIGURE_OPTS += --with-ranlib="$$(REAL_RANLIB_CMD)" $1_$2_CONFIGURE_OPTS += $$(if $$(ALEX),--with-alex="$$(ALEX)") $1_$2_CONFIGURE_OPTS += $$(if $$(HAPPY),--with-happy="$$(HAPPY)") diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs index a7d9e60..cfd3d27 100644 --- a/utils/ghc-cabal/Main.hs +++ b/utils/ghc-cabal/Main.hs @@ -12,6 +12,7 @@ import Distribution.Simple.Configure import Distribution.Simple.LocalBuildInfo import Distribution.Simple.Program import Distribution.Simple.Program.HcPkg +import Distribution.Simple.Setup (ConfigFlags(configStripLibs), fromFlag, toFlag) import Distribution.Simple.Utils (defaultPackageDesc, writeFileAtomic, toUTF8) import Distribution.Simple.Build (writeAutogenFiles) import Distribution.Simple.Register @@ -174,8 +175,17 @@ doCopy directory distDir let lbi' = lbi { withPrograms = progs', installDirTemplates = idts, + configFlags = cfg, + stripLibs = fromFlag (configStripLibs cfg), withSharedLib = withSharedLibs } + + -- This hack allows to interpret the "strip" + -- command-line argument being set to ':' to signify + -- disabled library stripping + cfg | strip == ":" = (configFlags lbi) { configStripLibs = toFlag False } + | otherwise = configFlags lbi + f pd lbi' us flags doRegister :: FilePath -> FilePath -> FilePath -> FilePath diff --git a/utils/ghc-cabal/ghc-cabal.cabal b/utils/ghc-cabal/ghc-cabal.cabal index 10d6e0a..74399ce 100644 --- a/utils/ghc-cabal/ghc-cabal.cabal +++ b/utils/ghc-cabal/ghc-cabal.cabal @@ -17,7 +17,7 @@ Executable ghc-cabal Build-Depends: base >= 3 && < 5, bytestring >= 0.10 && < 0.11, - Cabal >= 1.18 && < 1.19, + Cabal >= 1.20 && < 1.21, directory >= 1.1 && < 1.3, filepath >= 1.2 && < 1.4 diff --git a/utils/ghctags/Main.hs b/utils/ghctags/Main.hs index 9bf1a2d..a67891e 100644 --- a/utils/ghctags/Main.hs +++ b/utils/ghctags/Main.hs @@ -20,7 +20,6 @@ import SrcLoc import Distribution.Simple.GHC ( componentGhcOptions ) import Distribution.Simple.Configure ( getPersistBuildConfig ) -import Distribution.Simple.Compiler ( compilerVersion ) import Distribution.Simple.Program.GHC ( renderGhcOptions ) import Distribution.PackageDescription ( library, libBuildInfo ) import Distribution.Simple.LocalBuildInfo @@ -191,8 +190,7 @@ flagsFromCabal distPref = do let bi = libBuildInfo lib odir = buildDir lbi opts = componentGhcOptions V.normal lbi bi clbi odir - version = compilerVersion (compiler lbi) - in return $ renderGhcOptions version opts + in return $ renderGhcOptions (compiler lbi) opts _ -> error "no library" ---------------------------------------------------------------- diff --git a/utils/ghctags/ghctags.cabal b/utils/ghctags/ghctags.cabal index 07221d3..0e97cca 100644 --- a/utils/ghctags/ghctags.cabal +++ b/utils/ghctags/ghctags.cabal @@ -17,6 +17,6 @@ Executable ghctags Build-Depends: base >= 4 && < 5, containers, - Cabal, + Cabal >= 1.20 && <1.21, ghc From git at git.haskell.org Thu Apr 17 10:15:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Apr 2014 10:15:56 +0000 (UTC) Subject: [commit: ghc] master: Make qReport force its error message before printing it (241c660) Message-ID: <20140417101556.E5E462406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/241c6601568969156403fde8089c97024b082de0/ghc >--------------------------------------------------------------- commit 241c6601568969156403fde8089c97024b082de0 Author: Simon Peyton Jones Date: Thu Apr 17 11:15:16 2014 +0100 Make qReport force its error message before printing it Fixes Trac #8987. See Note [Exceptions in TH] Thanks to Yuras Shumovich for doing this. >--------------------------------------------------------------- 241c6601568969156403fde8089c97024b082de0 compiler/typecheck/TcSplice.lhs | 12 ++++++++++-- testsuite/tests/th/T8987.hs | 6 ++++++ testsuite/tests/th/T8987.stderr | 5 +++++ testsuite/tests/th/all.T | 1 + 4 files changed, 22 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcSplice.lhs b/compiler/typecheck/TcSplice.lhs index 2f4687d..7fce241 100644 --- a/compiler/typecheck/TcSplice.lhs +++ b/compiler/typecheck/TcSplice.lhs @@ -845,6 +845,12 @@ like that. Here's how it's processed: (qReport True s) by using addErr to add an error message to the bag of errors. The 'fail' in TcM raises an IOEnvFailure exception + * 'qReport' forces the message to ensure any exception hidden in unevaluated + thunk doesn't get into the bag of errors. Otherwise the following splice + will triger panic (Trac #8987): + $(fail undefined) + See also Note [Concealed TH exceptions] + * So, when running a splice, we catch all exceptions; then for - an IOEnvFailure exception, we assume the error is already in the error-bag (above) @@ -875,8 +881,10 @@ instance TH.Quasi (IOEnv (Env TcGblEnv TcLclEnv)) where ; let i = getKey u ; return (TH.mkNameU s i) } - qReport True msg = addErr (text msg) - qReport False msg = addWarn (text msg) + -- 'msg' is forced to ensure exceptions don't escape, + -- see Note [Exceptions in TH] + qReport True msg = seqList msg $ addErr (text msg) + qReport False msg = seqList msg $ addWarn (text msg) qLocation = do { m <- getModule ; l <- getSrcSpanM diff --git a/testsuite/tests/th/T8987.hs b/testsuite/tests/th/T8987.hs new file mode 100644 index 0000000..d6f5781 --- /dev/null +++ b/testsuite/tests/th/T8987.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T8987 where +import Language.Haskell.TH + +$(reportWarning ['1', undefined] >> return []) \ No newline at end of file diff --git a/testsuite/tests/th/T8987.stderr b/testsuite/tests/th/T8987.stderr new file mode 100644 index 0000000..2b128bb --- /dev/null +++ b/testsuite/tests/th/T8987.stderr @@ -0,0 +1,5 @@ + +T8987.hs:1:1: + Exception when trying to run compile-time code: + Prelude.undefined + Code: (>>) reportWarning ['1', undefined] return [] diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index ce723dd..22bb7cc 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -325,4 +325,5 @@ test('T8807', normal, compile, ['-v0']) test('T8884', normal, compile, ['-v0']) test('T8954', normal, compile, ['-v0']) test('T8932', normal, compile_fail, ['-v0']) +test('T8987', normal, compile_fail, ['-v0']) From git at git.haskell.org Thu Apr 17 15:32:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Apr 2014 15:32:20 +0000 (UTC) Subject: [commit: ghc] master: Update Cabal submodule to latest tip of 1.20 branch (dbe0b8c) Message-ID: <20140417153220.5BCD82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dbe0b8c28b846224fc6226e24780999dd88ea3ef/ghc >--------------------------------------------------------------- commit dbe0b8c28b846224fc6226e24780999dd88ea3ef Author: Herbert Valerio Riedel Date: Thu Apr 17 16:12:23 2014 +0200 Update Cabal submodule to latest tip of 1.20 branch The testsuite reference output for ghcpkg01 needs to be adapted since a "More diff friendly pretty printing of cabal files" is now performed. >--------------------------------------------------------------- dbe0b8c28b846224fc6226e24780999dd88ea3ef libraries/Cabal | 2 +- testsuite/tests/cabal/ghcpkg01.stdout | 108 ++++++++------------------------- 2 files changed, 25 insertions(+), 85 deletions(-) diff --git a/libraries/Cabal b/libraries/Cabal index aaa6183..045c843 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit aaa6183dba81d77637dff84f83136639d40f268f +Subproject commit 045c843f295ba1487ce39dd7b2d02cd333755c75 diff --git a/testsuite/tests/cabal/ghcpkg01.stdout b/testsuite/tests/cabal/ghcpkg01.stdout index 5a74666..da50cd9 100644 --- a/testsuite/tests/cabal/ghcpkg01.stdout +++ b/testsuite/tests/cabal/ghcpkg01.stdout @@ -10,29 +10,19 @@ maintainer: glasgow-haskell-users at haskell.org stability: stable homepage: http://www.haskell.org/ghc package-url: http://www.haskell.org/ghc -synopsis: -description: A Test Package +description: + A Test Package category: none author: simonmar at microsoft.com exposed: True -exposed-modules: A +exposed-modules: + A hidden-modules: B C.D trusted: False import-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" library-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" hs-libraries: testpkg-1.2.3.4 -extra-libraries: -extra-ghci-libraries: include-dirs: /usr/local/include/testpkg "c:/Program Files/testpkg" -includes: -depends: -hugs-options: -cc-options: -ld-options: -framework-dirs: -frameworks: -haddock-interfaces: -haddock-html: pkgroot: name: testpkg @@ -44,29 +34,19 @@ maintainer: glasgow-haskell-users at haskell.org stability: stable homepage: http://www.haskell.org/ghc package-url: http://www.haskell.org/ghc -synopsis: -description: A Test Package +description: + A Test Package category: none author: simonmar at microsoft.com exposed: True -exposed-modules: A +exposed-modules: + A hidden-modules: B C.D trusted: False import-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" library-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" hs-libraries: testpkg-1.2.3.4 -extra-libraries: -extra-ghci-libraries: include-dirs: /usr/local/include/testpkg "c:/Program Files/testpkg" -includes: -depends: -hugs-options: -cc-options: -ld-options: -framework-dirs: -frameworks: -haddock-interfaces: -haddock-html: pkgroot: import-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" @@ -84,29 +64,19 @@ maintainer: glasgow-haskell-users at haskell.org stability: unstable homepage: http://www.haskell.org/ghc package-url: http://www.haskell.org/ghc -synopsis: -description: A Test Package (new version) +description: + A Test Package (new version) category: none author: simonmar at microsoft.com exposed: False -exposed-modules: A +exposed-modules: + A hidden-modules: B C.D C.E trusted: False import-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" library-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" hs-libraries: testpkg-2.0 -extra-libraries: -extra-ghci-libraries: include-dirs: /usr/local/include/testpkg "c:/Program Files/testpkg" -includes: -depends: -hugs-options: -cc-options: -ld-options: -framework-dirs: -frameworks: -haddock-interfaces: -haddock-html: pkgroot: name: testpkg @@ -118,29 +88,19 @@ maintainer: glasgow-haskell-users at haskell.org stability: unstable homepage: http://www.haskell.org/ghc package-url: http://www.haskell.org/ghc -synopsis: -description: A Test Package (new version) +description: + A Test Package (new version) category: none author: simonmar at microsoft.com exposed: False -exposed-modules: A +exposed-modules: + A hidden-modules: B C.D C.E trusted: False import-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" library-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" hs-libraries: testpkg-2.0 -extra-libraries: -extra-ghci-libraries: include-dirs: /usr/local/include/testpkg "c:/Program Files/testpkg" -includes: -depends: -hugs-options: -cc-options: -ld-options: -framework-dirs: -frameworks: -haddock-interfaces: -haddock-html: pkgroot: --- name: testpkg @@ -152,29 +112,19 @@ maintainer: glasgow-haskell-users at haskell.org stability: stable homepage: http://www.haskell.org/ghc package-url: http://www.haskell.org/ghc -synopsis: -description: A Test Package +description: + A Test Package category: none author: simonmar at microsoft.com exposed: True -exposed-modules: A +exposed-modules: + A hidden-modules: B C.D trusted: False import-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" library-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" hs-libraries: testpkg-1.2.3.4 -extra-libraries: -extra-ghci-libraries: include-dirs: /usr/local/include/testpkg "c:/Program Files/testpkg" -includes: -depends: -hugs-options: -cc-options: -ld-options: -framework-dirs: -frameworks: -haddock-interfaces: -haddock-html: pkgroot: version: 2.0 @@ -193,29 +143,19 @@ maintainer: glasgow-haskell-users at haskell.org stability: stable homepage: http://www.haskell.org/ghc package-url: http://www.haskell.org/ghc -synopsis: -description: A Test Package +description: + A Test Package category: none author: simonmar at microsoft.com exposed: False -exposed-modules: A +exposed-modules: + A hidden-modules: B C.D trusted: False import-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" library-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" hs-libraries: testpkg-1.2.3.4 -extra-libraries: -extra-ghci-libraries: include-dirs: /usr/local/include/testpkg "c:/Program Files/testpkg" -includes: -depends: -hugs-options: -cc-options: -ld-options: -framework-dirs: -frameworks: -haddock-interfaces: -haddock-html: pkgroot: local01.package.conf: From git at git.haskell.org Fri Apr 18 11:17:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 18 Apr 2014 11:17:42 +0000 (UTC) Subject: [commit: ghc] master: Update Cabal submodule to fix Solaris build (dc4b66f) Message-ID: <20140418111742.AB1282406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dc4b66f6f266518ff9238edbe94c89702e98b8ad/ghc >--------------------------------------------------------------- commit dc4b66f6f266518ff9238edbe94c89702e98b8ad Author: Herbert Valerio Riedel Date: Fri Apr 18 12:31:51 2014 +0200 Update Cabal submodule to fix Solaris build see also https://github.com/haskell/cabal/issues/1789 >--------------------------------------------------------------- dc4b66f6f266518ff9238edbe94c89702e98b8ad libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index 045c843..8af39a5 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 045c843f295ba1487ce39dd7b2d02cd333755c75 +Subproject commit 8af39a5f827dcf5b5ca68badc2955e4cccbb039d From git at git.haskell.org Fri Apr 18 14:24:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 18 Apr 2014 14:24:26 +0000 (UTC) Subject: [commit: ghc] wip/pattern-synonyms: Fold mkPatSyn{Matcher, Wrapper}Id into TcPatSyn (d316f45) Message-ID: <20140418142426.CEC592409B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/pattern-synonyms Link : http://ghc.haskell.org/trac/ghc/changeset/d316f454a6a81753469301ea9523eddd16904877/ghc >--------------------------------------------------------------- commit d316f454a6a81753469301ea9523eddd16904877 Author: Dr. ERDI Gergo Date: Fri Apr 18 19:50:04 2014 +0800 Fold mkPatSyn{Matcher,Wrapper}Id into TcPatSyn >--------------------------------------------------------------- d316f454a6a81753469301ea9523eddd16904877 compiler/iface/BuildTyCl.lhs | 56 ++++----------------------------------- compiler/iface/TcIface.lhs | 7 +++-- compiler/typecheck/TcPatSyn.lhs | 30 ++++++++++++--------- 3 files changed, 25 insertions(+), 68 deletions(-) diff --git a/compiler/iface/BuildTyCl.lhs b/compiler/iface/BuildTyCl.lhs index e412d7e..ba59939 100644 --- a/compiler/iface/BuildTyCl.lhs +++ b/compiler/iface/BuildTyCl.lhs @@ -15,7 +15,7 @@ module BuildTyCl ( buildSynTyCon, buildAlgTyCon, buildDataCon, - buildPatSyn, mkPatSynMatcherId, mkPatSynWrapperId, + buildPatSyn, TcMethInfo, buildClass, distinctAbstractTyConRhs, totallyAbstractTyConRhs, mkNewTyConRhs, mkDataTyConRhs, @@ -36,8 +36,6 @@ import MkId import Class import TyCon import Type -import TypeRep -import TcType import Id import Coercion @@ -184,24 +182,15 @@ mkDataConStupidTheta tycon arg_tys univ_tvs ------------------------------------------------------ -buildPatSyn :: Name -> Bool -> Bool +buildPatSyn :: Name -> Bool + -> Id -> Maybe Id -> [Var] -> [TyVar] -> [TyVar] -- Univ and ext -> ThetaType -> ThetaType -- Prov and req -> Type -- Result type - -> TyVar -> TcRnIf m n PatSyn -buildPatSyn src_name declared_infix has_wrapper args univ_tvs ex_tvs prov_theta req_theta pat_ty tv - = do { (matcher, _, _) <- mkPatSynMatcherId src_name args - univ_tvs ex_tvs - prov_theta req_theta - pat_ty tv - ; wrapper <- case has_wrapper of - False -> return Nothing - True -> fmap Just $ - mkPatSynWrapperId src_name args - (univ_tvs ++ ex_tvs) (prov_theta ++ req_theta) - pat_ty +buildPatSyn src_name declared_infix matcher wrapper args univ_tvs ex_tvs prov_theta req_theta pat_ty + = do { pprTrace "buildPatSyn: matcher:" (ppr (idType matcher)) $ return () ; return $ mkPatSyn src_name declared_infix args univ_tvs ex_tvs @@ -210,41 +199,6 @@ buildPatSyn src_name declared_infix has_wrapper args univ_tvs ex_tvs prov_theta matcher wrapper } -mkPatSynMatcherId :: Name - -> [Var] - -> [TyVar] - -> [TyVar] - -> ThetaType -> ThetaType - -> Type - -> TyVar - -> TcRnIf n m (Id, Type, Type) -mkPatSynMatcherId name args univ_tvs ex_tvs prov_theta req_theta pat_ty res_tv - = do { matcher_name <- newImplicitBinder name mkMatcherOcc - - ; let res_ty = TyVarTy res_tv - cont_ty = mkSigmaTy ex_tvs prov_theta $ - mkFunTys (map varType args) res_ty - - ; let matcher_tau = mkFunTys [pat_ty, cont_ty, res_ty] res_ty - matcher_sigma = mkSigmaTy (res_tv:univ_tvs) req_theta matcher_tau - matcher_id = mkVanillaGlobal matcher_name matcher_sigma - ; return (matcher_id, res_ty, cont_ty) } - -mkPatSynWrapperId :: Name - -> [Var] - -> [TyVar] - -> ThetaType - -> Type - -> TcRnIf n m Id -mkPatSynWrapperId name args qtvs theta pat_ty - = do { wrapper_name <- newImplicitBinder name mkDataConWrapperOcc - - ; let wrapper_tau = mkFunTys (map varType args) pat_ty - wrapper_sigma = mkSigmaTy qtvs theta wrapper_tau - - ; let wrapper_id = mkVanillaGlobal wrapper_name wrapper_sigma - ; return wrapper_id } - \end{code} diff --git a/compiler/iface/TcIface.lhs b/compiler/iface/TcIface.lhs index 31c2bf7..4d3f4af 100644 --- a/compiler/iface/TcIface.lhs +++ b/compiler/iface/TcIface.lhs @@ -594,7 +594,7 @@ tc_iface_decl _ _ (IfacePatSyn{ ifName = occ_name , ifPatTy = pat_ty }) = do { name <- lookupIfaceTop occ_name ; traceIf (ptext (sLit "tc_iface_decl") <+> ppr name) - ; _matcher <- tcExt "Matcher" matcher_name + ; matcher <- tcExt "Matcher" matcher_name ; wrapper <- maybe (return Nothing) (fmap Just . tcExt "Wrapper") wrapper_name ; bindIfaceTyVars univ_tvs $ \univ_tvs -> do { bindIfaceTyVars ex_tvs $ \ex_tvs -> do @@ -604,9 +604,8 @@ tc_iface_decl _ _ (IfacePatSyn{ ifName = occ_name ; req_theta <- tcIfaceCtxt req_ctxt ; pat_ty <- tcIfaceType pat_ty ; return (prov_theta, req_theta, pat_ty) } - ; bindIfaceTyVar (fsLit "r", toIfaceKind liftedTypeKind) $ \tv -> do - { patsyn <- buildPatSyn name is_infix (isJust wrapper) args univ_tvs ex_tvs prov_theta req_theta pat_ty tv - ; return (AConLike (PatSynCon patsyn)) }}}}} + ; patsyn <- buildPatSyn name is_infix matcher wrapper args univ_tvs ex_tvs prov_theta req_theta pat_ty + ; return (AConLike (PatSynCon patsyn)) }}}} where mk_doc n = ptext (sLit "Pattern synonym") <+> ppr n tcExt s name = forkM (ptext (sLit s) <+> ppr name) $ tcIfaceExtId name diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 0b3b4e4..2337ccf 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -31,6 +31,7 @@ import Data.Monoid import Bag import TcEvidence import BuildTyCl +import TypeRep #include "HsVersions.h" \end{code} @@ -174,10 +175,15 @@ tcPatSynMatcher :: Located Name -> TcM (Id, LHsBinds Id) tcPatSynMatcher (L loc name) lpat args univ_tvs ex_tvs ev_binds prov_dicts req_dicts prov_theta req_theta pat_ty = do { res_tv <- zonkQuantifiedTyVar =<< newFlexiTyVar liftedTypeKind - ; (matcher_id, res_ty, cont_ty) <- mkPatSynMatcherId name args - univ_tvs ex_tvs - prov_theta req_theta - pat_ty res_tv + ; matcher_name <- newImplicitBinder name mkMatcherOcc + ; let res_ty = TyVarTy res_tv + cont_ty = mkSigmaTy ex_tvs prov_theta $ + mkFunTys (map varType args) res_ty + + ; let matcher_tau = mkFunTys [pat_ty, cont_ty, res_ty] res_ty + matcher_sigma = mkSigmaTy (res_tv:univ_tvs) req_theta matcher_tau + matcher_id = mkVanillaGlobal matcher_name matcher_sigma + ; traceTc "tcPatSynMatcher" (ppr name $$ ppr (idType matcher_id)) ; let matcher_lid = L loc matcher_id @@ -260,18 +266,16 @@ tc_pat_syn_wrapper_from_expr :: Located Name -> TcM (Id, LHsBinds Id) tc_pat_syn_wrapper_from_expr (L loc name) lexpr args univ_tvs ex_tvs theta pat_ty = do { let qtvs = univ_tvs ++ ex_tvs - ; (subst, qtvs') <- tcInstSkolTyVars qtvs - ; let theta' = substTheta subst theta + ; (subst, wrapper_tvs) <- tcInstSkolTyVars qtvs + ; let wrapper_theta = substTheta subst theta pat_ty' = substTy subst pat_ty args' = map (\arg -> setVarType arg $ substTy subst (varType arg)) args - - ; wrapper_id <- mkPatSynWrapperId name args qtvs theta pat_ty - ; let wrapper_name = getName wrapper_id - wrapper_lname = L loc wrapper_name - -- (wrapper_tvs, wrapper_theta, wrapper_tau) = tcSplitSigmaTy (idType wrapper_id) - wrapper_tvs = qtvs' - wrapper_theta = theta' wrapper_tau = mkFunTys (map varType args') pat_ty' + wrapper_sigma = mkSigmaTy wrapper_tvs wrapper_theta wrapper_tau + + ; wrapper_name <- newImplicitBinder name mkDataConWrapperOcc + ; let wrapper_lname = L loc wrapper_name + wrapper_id = mkVanillaGlobal wrapper_name wrapper_sigma ; let wrapper_args = map (noLoc . VarPat . Var.varName) args' wrapper_match = mkMatch wrapper_args lexpr EmptyLocalBinds From git at git.haskell.org Fri Apr 18 14:24:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 18 Apr 2014 14:24:29 +0000 (UTC) Subject: [commit: ghc] wip/pattern-synonyms: Reconstruct patsyn type from matcher type (f59ad68) Message-ID: <20140418142429.624C82409E@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/pattern-synonyms Link : http://ghc.haskell.org/trac/ghc/changeset/f59ad680150bc3dc27c04c36be58d8c18085c95a/ghc >--------------------------------------------------------------- commit f59ad680150bc3dc27c04c36be58d8c18085c95a Author: Dr. ERDI Gergo Date: Fri Apr 18 22:23:43 2014 +0800 Reconstruct patsyn type from matcher type >--------------------------------------------------------------- f59ad680150bc3dc27c04c36be58d8c18085c95a compiler/iface/BuildTyCl.lhs | 26 ++++++++++---------- compiler/iface/IfaceSyn.lhs | 54 ++++++++---------------------------------- compiler/iface/MkIface.lhs | 11 +-------- compiler/iface/TcIface.lhs | 23 ++++-------------- 4 files changed, 29 insertions(+), 85 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f59ad680150bc3dc27c04c36be58d8c18085c95a From git at git.haskell.org Fri Apr 18 14:24:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 18 Apr 2014 14:24:23 +0000 (UTC) Subject: [commit: ghc] wip/pattern-synonyms: Store IfExtNames for PatSyn matchers and wrappers in interface file (bea2018) Message-ID: <20140418142423.42F1F24097@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/pattern-synonyms Link : http://ghc.haskell.org/trac/ghc/changeset/bea20186c67bacc794ef4b25d28874103365ca2f/ghc >--------------------------------------------------------------- commit bea20186c67bacc794ef4b25d28874103365ca2f Author: Dr. ERDI Gergo Date: Fri Apr 18 19:21:37 2014 +0800 Store IfExtNames for PatSyn matchers and wrappers in interface file >--------------------------------------------------------------- bea20186c67bacc794ef4b25d28874103365ca2f compiler/iface/IfaceSyn.lhs | 21 ++++++++++++++------- compiler/iface/MkIface.lhs | 6 +++++- compiler/iface/TcIface.lhs | 9 ++++++--- 3 files changed, 25 insertions(+), 11 deletions(-) diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 1283b09..2fd2eb2 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -59,6 +59,7 @@ import HsBinds import Control.Monad import System.IO.Unsafe +import Data.Maybe ( isJust ) infixl 3 &&& \end{code} @@ -120,8 +121,9 @@ data IfaceDecl ifExtName :: Maybe FastString } | IfacePatSyn { ifName :: OccName, -- Name of the pattern synonym - ifPatHasWrapper :: Bool, ifPatIsInfix :: Bool, + ifPatMatcher :: IfExtName, + ifPatWrapper :: Maybe IfExtName, ifPatUnivTvs :: [IfaceTvBndr], ifPatExTvs :: [IfaceTvBndr], ifPatProvCtxt :: IfaceContext, @@ -186,7 +188,7 @@ instance Binary IfaceDecl where put_ bh a3 put_ bh a4 - put_ bh (IfacePatSyn name a2 a3 a4 a5 a6 a7 a8 a9) = do + put_ bh (IfacePatSyn name a2 a3 a4 a5 a6 a7 a8 a9 a10) = do putByte bh 6 put_ bh (occNameFS name) put_ bh a2 @@ -197,6 +199,7 @@ instance Binary IfaceDecl where put_ bh a7 put_ bh a8 put_ bh a9 + put_ bh a10 get bh = do h <- getByte bh @@ -253,8 +256,9 @@ instance Binary IfaceDecl where a7 <- get bh a8 <- get bh a9 <- get bh + a10 <- get bh occ <- return $! mkOccNameFS dataName a1 - return (IfacePatSyn occ a2 a3 a4 a5 a6 a7 a8 a9) + return (IfacePatSyn occ a2 a3 a4 a5 a6 a7 a8 a9 a10) _ -> panic (unwords ["Unknown IfaceDecl tag:", show h]) data IfaceSynTyConRhs @@ -1015,10 +1019,10 @@ ifaceDeclImplicitBndrs (IfaceClass {ifCtxt = sc_ctxt, ifName = cls_tc_occ, dc_occ = mkClassDataConOcc cls_tc_occ is_newtype = n_sigs + n_ctxt == 1 -- Sigh -ifaceDeclImplicitBndrs (IfacePatSyn{ ifName = ps_occ, ifPatHasWrapper = has_wrapper }) - = [wrap_occ | has_wrapper] +ifaceDeclImplicitBndrs (IfacePatSyn{ ifName = ps_occ, ifPatWrapper = wrapper_name }) + = [wrap_occ | isJust wrapper_name] where - wrap_occ = mkDataConWrapperOcc ps_occ -- Id namespace + wrap_occ = mkDataConWrapperOcc ps_occ ifaceDeclImplicitBndrs _ = [] @@ -1103,7 +1107,7 @@ pprIfaceDecl (IfaceAxiom {ifName = name, ifTyCon = tycon, ifAxBranches = branche = hang (ptext (sLit "axiom") <+> ppr name <> dcolon) 2 (vcat $ map (pprAxBranch $ Just tycon) branches) -pprIfaceDecl (IfacePatSyn { ifName = name, ifPatHasWrapper = has_wrap, +pprIfaceDecl (IfacePatSyn { ifName = name, ifPatWrapper = wrapper, ifPatIsInfix = is_infix, ifPatUnivTvs = _univ_tvs, ifPatExTvs = _ex_tvs, ifPatProvCtxt = prov_ctxt, ifPatReqCtxt = req_ctxt, @@ -1111,6 +1115,7 @@ pprIfaceDecl (IfacePatSyn { ifName = name, ifPatHasWrapper = has_wrap, ifPatTy = ty }) = pprPatSynSig name has_wrap args' ty' (pprCtxt prov_ctxt) (pprCtxt req_ctxt) where + has_wrap = isJust wrapper args' = case (is_infix, map snd args) of (True, [left_ty, right_ty]) -> InfixPatSyn (pprParendIfaceType left_ty) (pprParendIfaceType right_ty) @@ -1392,6 +1397,8 @@ freeNamesIfDecl d at IfaceAxiom{} = freeNamesIfTc (ifTyCon d) &&& fnList freeNamesIfAxBranch (ifAxBranches d) freeNamesIfDecl d at IfacePatSyn{} = + unitNameSet (ifPatMatcher d) &&& + maybe emptyNameSet unitNameSet (ifPatWrapper d) &&& freeNamesIfTvBndrs (ifPatUnivTvs d) &&& freeNamesIfTvBndrs (ifPatExTvs d) &&& freeNamesIfContext (ifPatProvCtxt d) &&& diff --git a/compiler/iface/MkIface.lhs b/compiler/iface/MkIface.lhs index bb51cda..d504386 100644 --- a/compiler/iface/MkIface.lhs +++ b/compiler/iface/MkIface.lhs @@ -1488,7 +1488,8 @@ dataConToIfaceDecl dataCon patSynToIfaceDecl :: PatSyn -> IfaceDecl patSynToIfaceDecl ps = IfacePatSyn { ifName = getOccName . getName $ ps - , ifPatHasWrapper = isJust $ patSynWrapper ps + , ifPatMatcher = matcher + , ifPatWrapper = wrapper , ifPatIsInfix = patSynIsInfix ps , ifPatUnivTvs = toIfaceTvBndrs univ_tvs' , ifPatExTvs = toIfaceTvBndrs ex_tvs' @@ -1507,6 +1508,9 @@ patSynToIfaceDecl ps (env1, univ_tvs') = tidyTyVarBndrs emptyTidyEnv univ_tvs (env2, ex_tvs') = tidyTyVarBndrs env1 ex_tvs + matcher = idName (patSynMatcher ps) + wrapper = fmap idName (patSynWrapper ps) + -------------------------- coAxiomToIfaceDecl :: CoAxiom br -> IfaceDecl diff --git a/compiler/iface/TcIface.lhs b/compiler/iface/TcIface.lhs index cc45648..31c2bf7 100644 --- a/compiler/iface/TcIface.lhs +++ b/compiler/iface/TcIface.lhs @@ -583,7 +583,8 @@ tc_iface_decl _ _ (IfaceAxiom { ifName = ax_occ, ifTyCon = tc ; return (ACoAxiom axiom) } tc_iface_decl _ _ (IfacePatSyn{ ifName = occ_name - , ifPatHasWrapper = has_wrapper + , ifPatMatcher = matcher_name + , ifPatWrapper = wrapper_name , ifPatIsInfix = is_infix , ifPatUnivTvs = univ_tvs , ifPatExTvs = ex_tvs @@ -593,6 +594,8 @@ tc_iface_decl _ _ (IfacePatSyn{ ifName = occ_name , ifPatTy = pat_ty }) = do { name <- lookupIfaceTop occ_name ; traceIf (ptext (sLit "tc_iface_decl") <+> ppr name) + ; _matcher <- tcExt "Matcher" matcher_name + ; wrapper <- maybe (return Nothing) (fmap Just . tcExt "Wrapper") wrapper_name ; bindIfaceTyVars univ_tvs $ \univ_tvs -> do { bindIfaceTyVars ex_tvs $ \ex_tvs -> do { bindIfaceIdVars args $ \args -> do @@ -602,11 +605,11 @@ tc_iface_decl _ _ (IfacePatSyn{ ifName = occ_name ; pat_ty <- tcIfaceType pat_ty ; return (prov_theta, req_theta, pat_ty) } ; bindIfaceTyVar (fsLit "r", toIfaceKind liftedTypeKind) $ \tv -> do - { patsyn <- buildPatSyn name is_infix has_wrapper args univ_tvs ex_tvs prov_theta req_theta pat_ty tv + { patsyn <- buildPatSyn name is_infix (isJust wrapper) args univ_tvs ex_tvs prov_theta req_theta pat_ty tv ; return (AConLike (PatSynCon patsyn)) }}}}} where mk_doc n = ptext (sLit "Pattern synonym") <+> ppr n - + tcExt s name = forkM (ptext (sLit s) <+> ppr name) $ tcIfaceExtId name tc_ax_branches :: TyCon -> [IfaceAxBranch] -> IfL [CoAxBranch] tc_ax_branches tc if_branches = foldlM (tc_ax_branch (tyConKind tc)) [] if_branches From git at git.haskell.org Fri Apr 18 14:24:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 18 Apr 2014 14:24:31 +0000 (UTC) Subject: [commit: ghc] wip/pattern-synonyms's head updated: Reconstruct patsyn type from matcher type (f59ad68) Message-ID: <20140418142431.F29A6240A0@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/pattern-synonyms' now includes: e3938f3 Fix linked list manipulation code (buggy on consecutive deletion) 7fa0b43 Make BlockAlloc.c comment slightly more accurate (fixes #8491) eeaea2d Instead of tracking Origin in LHsBindsLR, track it in MatchGroup 80bdb88 Typos in comments b4a820f Update Haddock submodule to follow LHsBindsLR changes 70d263e Better layout for coercion error message bfd0064 Tidy up trace message 14046d0 A bit more trace information in an ASSERT failure e7f0ae7 Honour the untouchability of kind variables ff9f9a7 Test Trac #8985 bea2018 Store IfExtNames for PatSyn matchers and wrappers in interface file d316f45 Fold mkPatSyn{Matcher,Wrapper}Id into TcPatSyn f59ad68 Reconstruct patsyn type from matcher type From git at git.haskell.org Fri Apr 18 15:40:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 18 Apr 2014 15:40:10 +0000 (UTC) Subject: [commit: ghc] wip/pattern-synonyms: Reconstruct patsyn type from matcher type (a7c34e8) Message-ID: <20140418154010.8133E240CB@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/pattern-synonyms Link : http://ghc.haskell.org/trac/ghc/changeset/a7c34e85a8702b501f18029f68a1c1ff8bde1b46/ghc >--------------------------------------------------------------- commit a7c34e85a8702b501f18029f68a1c1ff8bde1b46 Author: Dr. ERDI Gergo Date: Fri Apr 18 23:39:19 2014 +0800 Reconstruct patsyn type from matcher type >--------------------------------------------------------------- a7c34e85a8702b501f18029f68a1c1ff8bde1b46 compiler/iface/BuildTyCl.lhs | 31 +++++++++++++----------- compiler/iface/IfaceSyn.lhs | 55 ++++++++---------------------------------- compiler/iface/MkIface.lhs | 16 ++---------- compiler/iface/TcIface.lhs | 36 +++------------------------ 4 files changed, 33 insertions(+), 105 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a7c34e85a8702b501f18029f68a1c1ff8bde1b46 From git at git.haskell.org Fri Apr 18 23:28:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 18 Apr 2014 23:28:30 +0000 (UTC) Subject: [commit: ghc] master: Take account of the AvailTC invariant when importing (f964cd9) Message-ID: <20140418232830.162E22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f964cd9c5c411f8a2383cf2b080581a5c3349661/ghc >--------------------------------------------------------------- commit f964cd9c5c411f8a2383cf2b080581a5c3349661 Author: Simon Peyton Jones Date: Fri Apr 18 23:30:18 2014 +0100 Take account of the AvailTC invariant when importing In the rather gnarly filterImports code, someone had forgotten the AvailTC invariant: in AvailTC n [n,s1,s2], the 'n' is itself included in the list of names. >--------------------------------------------------------------- f964cd9c5c411f8a2383cf2b080581a5c3349661 compiler/rename/RnNames.lhs | 80 ++++++++++++++--------- testsuite/tests/rename/should_fail/T9006.hs | 3 + testsuite/tests/rename/should_fail/T9006.stderr | 2 + testsuite/tests/rename/should_fail/T9006a.hs | 3 + testsuite/tests/rename/should_fail/all.T | 3 + 5 files changed, 59 insertions(+), 32 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f964cd9c5c411f8a2383cf2b080581a5c3349661 From git at git.haskell.org Sat Apr 19 09:10:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 19 Apr 2014 09:10:41 +0000 (UTC) Subject: [commit: packages/binary] branch 'ghc-head' deleted Message-ID: <20140419091041.B6C6B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary Deleted branch: ghc-head From git at git.haskell.org Sat Apr 19 09:10:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 19 Apr 2014 09:10:43 +0000 (UTC) Subject: [commit: packages/binary] master: Add LANGUAGE extensions for inferred signatures. (a11b191) Message-ID: <20140419091043.AA07E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/a11b19189d8523d2425f2ce4d27e8582f1f0a37d >--------------------------------------------------------------- commit a11b19189d8523d2425f2ce4d27e8582f1f0a37d Author: Jan Stolarek Date: Sat Apr 19 09:04:02 2014 +0200 Add LANGUAGE extensions for inferred signatures. Some of the inferred signatures required LANGUAGE extensions that were not enabled. Since now GHC checks that we have to explicitly list required extensions. >--------------------------------------------------------------- a11b19189d8523d2425f2ce4d27e8582f1f0a37d src/Data/Binary/Get/Internal.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs index 7dac47d..a66f8dd 100644 --- a/src/Data/Binary/Get/Internal.hs +++ b/src/Data/Binary/Get/Internal.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, RankNTypes, MagicHash, BangPatterns #-} +{-# LANGUAGE CPP, RankNTypes, MagicHash, BangPatterns, TypeFamilies, TypeFamilies #-} -- CPP C style pre-precessing, the #if defined lines -- RankNTypes forall r. statement From git at git.haskell.org Sat Apr 19 09:10:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 19 Apr 2014 09:10:48 +0000 (UTC) Subject: [commit: packages/binary] master's head updated: Add LANGUAGE extensions for inferred signatures. (a11b191) Message-ID: <20140419091049.0382F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary Branch 'master' now includes: defe9c9 Partial implementation of push style Data.Binary.Get b920c40 Remove argument from needMore 28d5cbc Move the state from the Get monad to the Result type ba9eae1 Change my email 86b698c API and performance improvements 37b024b Tested (only) with GHC 6.12.1 6c70366 Remove INLINE, no performance enhancement with ghc 6.12.1 21cbcde Implement operators 'plus' and 'try' for error recovering d0f6403 Rename getPush into getPartial 0f65a54 skip: reimplement 73def8d getBytes: expose old part of the API, but depricate it 47f3578 When we know the length of the ByteString, use unsafeIndex instead of index 5d03d5d Remove backtracking, big performance boost 8420a65 Implement isEmpty d88d6c4 feed: keep adding input even if we didn't get a partial 18cbd69 lookAhead: implement for CPS 42e347e -Wall police for Get.hs 5b2d1cf Fix my email in source files a00b5f8 Implement remaining :: Get Int e8697e9 Change example slightly, change -fglasgow-exts into proper extensions bf530fa Use test-framework when testing, remove old custom framework 24328e3 Track the position of parsed input 2f56aa8 tests/MemBench.hs: fixed pointer arithmetics 9f71058 tests: added inplace-bench (builds against local binary source d21677a tests: inplace-bench should be PHONY b7d9cf9 get: increase byte counter when we consume data 836e6ce get: export the bytesRead function bec0d2d get: comments 12272ea get: implement runGetState for compatibility 7bf14be readN: force evaluation of new position. 4x speedup. 16d762b get: remove dead code; getS, putS a6e0b06 Write some haddock comments. 8918bc9 In benchmarks, use GHC to compile C sources a385307 Remove backtracking, simplifies code. e95acb2 Allow bounds check merging for Applicative code. Major speedup. 299bb2e Rewrite ensureN so that GHC can inline it. 9bdd3dd Force GHC to inline getWordXX by adding inlining RULES. 09ae27a Use unsafePerformeIO from System.IO.Unsafe instead of from Foreign. 715ca61 Add tests for checking values of Done, Partial and Fail. aa9a790 Extract core parts of Data.Binary.Get into Data.Binary.Get.Internal. 181feb8 Allow custom ghc executable and ghc-flags for benchmarks and tests. a7162f0 Don't track the position in the internal version of Get. 3c98a02 Switch to -fforce-recomp instead of the deprecated -no-recomp. 1f892ae Make sure <$> gets inlined by RULES. 08c3a07 Bump to 0.6.0.0. fecfde0 Uncomment decodeFile. 937d905 Add Haddock comments to Data.Binary.Get.Internal. 3cf6273 Remove commented out code from tests. e2fd799 Use some commented out code in tests. Cleanup. 1dbf0cc Add test to pass negative int to getByteString. fd28f55 Guard for negative ints passed to getByteString. a1de5b8 Reimplement string utilities. f20b910 Add tests for string util functions. 182b8d7 Add feedLBS which feeds a whole Lazy ByteString. b8a9c7b Fix compiler warnings. 9ea5261 Expose the Data.Binary.Get.Internal module. 3f39b7b Export the ensureN function from Data.Binary.Get.Internal. 0540290 Add comments, do cleanup and fix compiler warnings. e51871a Merge branch 'master' into cps b15923f Implement instance Alternative for the Get monad. 70c240e Use simple apG implementation, same performance. b0519e6 Make unsafeReadN be strict in the return value. 83e5d1e Remove -fasm flag from benchmark, it's default anyway. abbf463 For system-bench, disable any user package configs. 1b7efe4 Update homepage and source-repository. e147ebc Start on a criterion benchmark for the Get monad. e76da33 -Wall cleanup for QC tests. 8383ed9 Fix more -Wall warnings. d7ec182 Rename variables for consistency. cb2c095 Test for 'Binary Ratio a' instance. 3008823 Test for 'Binary (tuples with 5..10 elements)' instances. e04dcf3 Renames. ec0135e Make the builder test compile on GHC 7.6.1. 1f8d385 Make the get benchmark compile with GHC 7.6.1. bc936c7 Rename any occurence of 'parse*' to 'decode*'. 3849612 Implement 'bytesRead' from the 0.5 API. a2df8af Documentation fixes. 36f3650 Rename 'pushEndInput' -> 'pushEndOfInput'. 27334cc Add MachDeps.h to use WORD_SIZE_IN_BITS. 7dbb131 Merge branch 'cps' a83721d Documentation fix. fcd9cbc QuickCheck-2.5 already defines Arbitrary Ordering. 3755f41 'source-repository' needs cabal-version>=1.6. f2ec1de Fix -Wall warnings in builder. 56f57dd Documentation fix for 'remaining'. eceeff3 Docs. ecaa296 Allow to run tests through Cabal. a794da9 Remove old flags from cabal file. f3be53d Don't use Random Int64 instance. 15885fe Import GHC.Base for GHC < 7.2. For newer GHCs it's not needed. a37bbbf Require random-1.0.1.0 or newer. e9a5e36 Require random-1.0.1.0 or newer. f7f2dc1 Fix bug where a Decoder could return Partial multiple times. 951d66e Bump version to 0.6.1.0. 989cbe8 Fixes to upload 0.6.1.0 to hackage. aa5eddd fix some typos 3acee5e Further documentation fixes. f372f81 Add benchmarks to .cabal 7ca1d43 Fix a bug related to <|> and bytesRead. dce7362 Cleanup that also gave a nice speed improvement. 523ea49 No need to recompile everything each time for system-bench. acbf1ed Efficient versions of 'some' and 'many'. 6c6ca94 Remove developer flag from binary.cabal 3a47f76 Bump version to 0.6.2.0. da104c8 Add model based testing for bytesRead in <|>. e8878dc Implement NFData for Lazy ByteStrings 739707b Minor cleanup in Builder benchmark. 318ceb8 Add Mercurial ignore file 727a36e Quiet a GHC warning in tests c238719 Split Binary class into its own module 4c68865 Add runGetOrFail c50a122 Small documentation tweaks b7e83d9 Drop redundant info from .cabal file c5f6bd7 Almost-working generics, with deliberate type bug ede450c Fix up the default instances 7b59a09 A small doc improvement 357fe30 Drop unneeded LANGUAGE pragma 512a398 Make docs less confusing. 2912c6f Doc updates. 0ad4f7a Bump version to 0.6.3.0. 2f563b5 Fix build error for generics with ghc <= 7.6.1. 4e06dc5 Merge branch 'rungetorfail' of https://github.com/tibbe/binary into tibbe-rungetorfail 26f90db Bump version to 0.6.4.0. 876c9da Remove unused Ord constraint from Set and Map 598b46c Merge pull request #21 from Peaker/master 12f6ba2 Add Bas van Dijk to contributors as he wrote the original generics code 6350f16 Make runGetState more efficient, especially if called many times. bc92b38 Avoid rebuilding LBS with L.fromChunks. 5d07ba7 O(n) version of pushChunks, when joining unused chunks. fda9aa7 Add decodeOrFail and decodeFileOrFail. 104910e Docs for decodeFile and decodeFileOrFail. 63f186a Add test for encodeFile and decodeFile. ebe4289 Implement lookAhead. e114647 Add .cabal-sandbox to .gitignore. dc951eb Implement <|> using runAndKeepTrack. d523429 Model test: make sure decoded data is as expected (not only offset). 9b15563 Compile QC tests with -O2. 1bcb307 Implement lookAheadM. 7e73035 Cleanup instance Arbitrary of lazy bytestrings. 083bc0f Model test: provide better shrinking. 06ae376 Silent warning. b726e02 Function haddocks for lookAhead and lookAheadM. 638f8aa Update benchmark. Add cereal and attoparsec for comparison. e88822c Update Don Stewart's email address. 4d6d9c9 Remove ancient TODO a1478b3 Add all files to binary.cabal 485ab9e More documentation. 74c3afe Add module documentation for Data.Binary.Get. b97698b Clean up <|> benchmark. 9250a6a Special case when we pushBack an empty list. 18fc3b5 Fix the benchmark. 124f583 Only run bracket bench on 100kb of brackets. 4d890e4 Bump to 0.7.0.0 da72290 Fix code examples in documentation. 49c0420 Bump to 0.7.0.1 b014403 Typo. 228bdcc Add a Cereal bracket test. 3625372 Added MonadPlus instance. 775d9f4 Added .md extension to README file c2ec8d6 README updated with markdown format. b838290 README: Added info about a binary instance example. 27cc0ce Fixed a typo. e17fa33 Minor fixes to the README. 54041e7 Update binary.cabal about README.md's new name. 2d53508 Reimplement lookAheadE 679a4a8 Updates to the README. c35742a Depend on test-framework-quickcheck2 >= 0.3 2799c25 Version bump to 0.7.1.0. a11b191 Add LANGUAGE extensions for inferred signatures. From git at git.haskell.org Sat Apr 19 09:13:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 19 Apr 2014 09:13:59 +0000 (UTC) Subject: [commit: packages/binary] master: Remove duplicated extension in LANGUAGE pragma (2647d42) Message-ID: <20140419091403.4454E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/2647d42f19bedae46c020fc3af029073f5690d5b >--------------------------------------------------------------- commit 2647d42f19bedae46c020fc3af029073f5690d5b Author: Jan Stolarek Date: Sat Apr 19 11:13:11 2014 +0200 Remove duplicated extension in LANGUAGE pragma >--------------------------------------------------------------- 2647d42f19bedae46c020fc3af029073f5690d5b src/Data/Binary/Get/Internal.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs index a66f8dd..292a179 100644 --- a/src/Data/Binary/Get/Internal.hs +++ b/src/Data/Binary/Get/Internal.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, RankNTypes, MagicHash, BangPatterns, TypeFamilies, TypeFamilies #-} +{-# LANGUAGE CPP, RankNTypes, MagicHash, BangPatterns, TypeFamilies #-} -- CPP C style pre-precessing, the #if defined lines -- RankNTypes forall r. statement From git at git.haskell.org Sat Apr 19 09:14:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 19 Apr 2014 09:14:25 +0000 (UTC) Subject: [commit: packages/vector] branch 'ghc-head' deleted Message-ID: <20140419091425.5B3BD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/vector Deleted branch: ghc-head From git at git.haskell.org Sat Apr 19 09:14:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 19 Apr 2014 09:14:27 +0000 (UTC) Subject: [commit: packages/vector] master: Add LANGUAGE extensions for inferred signatures. (a6049ab) Message-ID: <20140419091427.8E3A72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/vector On branch : master Link : http://git.haskell.org/packages/vector.git/commitdiff/a6049abce040713e9a5f175887cf70d12b9057c6 >--------------------------------------------------------------- commit a6049abce040713e9a5f175887cf70d12b9057c6 Author: Jan Stolarek Date: Sat Apr 19 09:08:49 2014 +0200 Add LANGUAGE extensions for inferred signatures. Some of the inferred signatures required LANGUAGE extensions that were not enabled. Since now GHC checks that we have to explicitly list required extensions. >--------------------------------------------------------------- a6049abce040713e9a5f175887cf70d12b9057c6 Data/Vector/Generic/Mutable.hs | 3 ++- Data/Vector/Mutable.hs | 3 ++- 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/Data/Vector/Generic/Mutable.hs b/Data/Vector/Generic/Mutable.hs index 91e7036..17a7540 100644 --- a/Data/Vector/Generic/Mutable.hs +++ b/Data/Vector/Generic/Mutable.hs @@ -1,4 +1,5 @@ -{-# LANGUAGE MultiParamTypeClasses, BangPatterns, ScopedTypeVariables #-} +{-# LANGUAGE MultiParamTypeClasses, BangPatterns, ScopedTypeVariables, + TypeFamilies #-} -- | -- Module : Data.Vector.Generic.Mutable -- Copyright : (c) Roman Leshchinskiy 2008-2010 diff --git a/Data/Vector/Mutable.hs b/Data/Vector/Mutable.hs index e896f3a..e97c4a8 100644 --- a/Data/Vector/Mutable.hs +++ b/Data/Vector/Mutable.hs @@ -1,4 +1,5 @@ -{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, BangPatterns #-} +{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, BangPatterns, + TypeFamilies #-} -- | -- Module : Data.Vector.Mutable From git at git.haskell.org Sat Apr 19 09:14:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 19 Apr 2014 09:14:30 +0000 (UTC) Subject: [commit: packages/vector] master's head updated: Add LANGUAGE extensions for inferred signatures. (a6049ab) Message-ID: <20140419091430.83FEA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/vector Branch 'master' now includes: 20b94f6 Bump version 8aff1d7 Documentation ecd9b71 Strictness fix 1198dab Bump version 355e2d5 Export SPEC 79767a8 Use SPEC in stream comparisons 41c94d2 Change version number again fd18157 Allow streams to produce entire vectors as well as individual elements 2033706 Reimplement concat d01d9f6 Have streams carry chunk initialisers rather than vectors f2b0015 Fix docs 820b80e Require dev version of primitive e54a82f Improve basicSet for Storable vectors 84dae34 Improve basicSet for primitive vectors 18dc0ff Switch to record syntax for streams 072ebed Delete dead code 3fab96f Relax package upper bounds 427c50b Faster concatMap 8a0a0c0 Whitespace f375eff Add Maybe (v a) to Stream representations 3e88ef5 Use new Stream in length and null 1a5a602 Improve length and null 993b4b2 Added NFData instances for all vectors b058e75 Resolve conflict 3247dd1 Comment out the NFData instance for mutable boxed vectors for now 2fa70a6 Move eq and cmp to monadic streams a1204cf Add type signatures for GHC >= 7.4 deb38e5 Remove outdated Changelog file f1904ef Bump versions and dependencies 996eb93 Remove Safe Haskell support dc22722 Changelog b32e1c4 Add missing file 1e5c45e TAG 0.10 09e9cd1 Rename Stream -> Facets 7f29cf7 fromVectorStream -> concatVectors fe6fe7f INLINE_STREAM -> INLINE_FUSED 19d0dd4 liftStream -> lift 368ab31 Resolve conflict 977f285 Bump version number b3114f2 Work around bug in ghc-7.6.1 931e905 Rename Facets to Bundle 1480faf Finish Stream -> Bundle renaming 0518a4a Adapt tests to new names and modules 6d54109 Add internal checks 214c3e1 Readd Fusion.Stream.Monadic and use it Bundle.Monadic 9ff5b56 Make inplace fusion work on Streams rather than Bundles e16b39a Require primitive >= 0.5.0.1 34cf6a0 TAG 0.10.0.1 a3a65b5 Snapshot of the real 0.10.0.1 release 9097bb5 Update URLs in cabal file 6f6bec5 Add README 6982ea1 Add README to cabal file 1bc792e Fix test suite 0afe74d Implement poly-kinded Typeable 9baab44 Add gitignore file a6049ab Add LANGUAGE extensions for inferred signatures. From git at git.haskell.org Sat Apr 19 09:22:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 19 Apr 2014 09:22:18 +0000 (UTC) Subject: [commit: ghc] master: Validate inferred theta. Fixes #8883 (1d2ffb6) Message-ID: <20140419092218.CF16D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1d2ffb6ab1ef973c85f893b5ea4a72cfa59ce484/ghc >--------------------------------------------------------------- commit 1d2ffb6ab1ef973c85f893b5ea4a72cfa59ce484 Author: Jan Stolarek Date: Sat Apr 19 06:58:07 2014 +0200 Validate inferred theta. Fixes #8883 This checks that all the required extensions are enabled for the inferred type signature. Updates binary and vector submodules. >--------------------------------------------------------------- 1d2ffb6ab1ef973c85f893b5ea4a72cfa59ce484 compiler/llvmGen/LlvmCodeGen.hs | 1 + compiler/nativeGen/RegAlloc/Liveness.hs | 1 + compiler/nativeGen/X86/Instr.hs | 1 + compiler/typecheck/TcBinds.lhs | 5 +++++ compiler/typecheck/TcSMonad.lhs | 1 + libraries/binary | 2 +- libraries/vector | 2 +- .../indexed-types/should_compile/ColInference6.hs | 2 +- .../indexed-types/should_compile/IndTypesPerf.hs | 2 ++ .../should_compile/IndTypesPerfMerge.hs | 2 +- testsuite/tests/perf/should_run/T2902_A.hs | 2 +- testsuite/tests/perf/should_run/T2902_B.hs | 2 +- testsuite/tests/perf/should_run/T5113.hs | 2 +- testsuite/tests/rebindable/DoRestrictedM.hs | 2 +- testsuite/tests/typecheck/should_compile/tc168.hs | 2 +- testsuite/tests/typecheck/should_compile/tc231.hs | 2 +- testsuite/tests/typecheck/should_fail/T8883.hs | 20 ++++++++++++++++++++ testsuite/tests/typecheck/should_fail/T8883.stderr | 7 +++++++ testsuite/tests/typecheck/should_fail/tcfail093.hs | 2 +- 19 files changed, 49 insertions(+), 11 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1d2ffb6ab1ef973c85f893b5ea4a72cfa59ce484 From git at git.haskell.org Sat Apr 19 09:52:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 19 Apr 2014 09:52:14 +0000 (UTC) Subject: [commit: ghc] master: Add Data.List.sortOn function (re #9004 and #2659) (44512e3) Message-ID: <20140419095214.ECE392406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/44512e3c855d8fb36ab6580f4f97f842ebcf4c6c/ghc >--------------------------------------------------------------- commit 44512e3c855d8fb36ab6580f4f97f842ebcf4c6c Author: Alexander Berntsen Date: Fri Apr 18 21:41:11 2014 +0200 Add Data.List.sortOn function (re #9004 and #2659) `sortOn` sorts a list by comparing the results of a key function applied to each element. `sortOn f` is equivalent to `sortBy . comparing f`, but has the performance advantage of only evaluating `f` once for each element in the input list. Historical note: This was already proposed in 2008 as part of http://www.haskell.org/pipermail/libraries/2008-October/010797.html It was, however, the recent re-attempt http://www.haskell.org/pipermail/libraries/2014-April/022489.html that let `sortOn` make it into base at last. Maybe the other functions mentioned in #2659 might be worth reconsidering as well. >--------------------------------------------------------------- 44512e3c855d8fb36ab6580f4f97f842ebcf4c6c libraries/base/Data/List.hs | 14 ++++++++++++++ libraries/base/changelog.md | 2 ++ 2 files changed, 16 insertions(+) diff --git a/libraries/base/Data/List.hs b/libraries/base/Data/List.hs index 09aed9d..7f66528 100644 --- a/libraries/base/Data/List.hs +++ b/libraries/base/Data/List.hs @@ -164,6 +164,7 @@ module Data.List -- ** Ordered lists , sort + , sortOn , insert -- * Generalized functions @@ -207,6 +208,8 @@ module Data.List import Data.Maybe import Data.Char ( isSpace ) +import Data.Ord ( comparing ) +import Data.Tuple ( fst, snd ) import GHC.Num import GHC.Real @@ -957,6 +960,17 @@ rqpart cmp x (y:ys) rle rgt r = #endif /* USE_REPORT_PRELUDE */ +-- | Sort a list by comparing the results of a key function applied to each +-- element. @sortOn f@ is equivalent to @sortBy . comparing f@, but has the +-- performance advantage of only evaluating @f@ once for each element in the +-- input list. This is called the decorate-sort-undecorate paradigm, or +-- Schwartzian transform. +-- +-- /Since: 4.7.1.0/ +sortOn :: Ord b => (a -> b) -> [a] -> [a] +sortOn f = + map snd . sortBy (comparing fst) . map (\x -> let y = f x in y `seq` (y, x)) + -- | The 'unfoldr' function is a \`dual\' to 'foldr': while 'foldr' -- reduces a list to a summary value, 'unfoldr' builds a list from -- a seed value. The function takes the element and returns 'Nothing' diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 75e7710..3011fdf 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -6,6 +6,8 @@ * Add reverse application operator `Data.Function.(&)` + * Add `Data.List.sortOn` sorting function + ## 4.7.0.0 *Apr 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Sat Apr 19 09:52:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 19 Apr 2014 09:52:18 +0000 (UTC) Subject: [commit: ghc] master: Add reverse application operator Data.Function.(&) (1bf6c0e) Message-ID: <20140419095218.648562406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1bf6c0e482cfe4b9dfa0b5ed18a5741ba44fc226/ghc >--------------------------------------------------------------- commit 1bf6c0e482cfe4b9dfa0b5ed18a5741ba44fc226 Author: Alexander Berntsen Date: Thu Apr 17 21:43:35 2014 +0200 Add reverse application operator Data.Function.(&) Add `&` as the reverse application operator with `infixl 1`, which allows it to be nested in `$` (re #9008). Approved by the core libraries committee on 2013-10-14. This also bumps the `base` version number to 4.7.1.0 >--------------------------------------------------------------- 1bf6c0e482cfe4b9dfa0b5ed18a5741ba44fc226 libraries/base/Data/Function.hs | 11 +++++++++++ libraries/base/base.cabal | 2 +- libraries/base/changelog.md | 8 +++++++- 3 files changed, 19 insertions(+), 2 deletions(-) diff --git a/libraries/base/Data/Function.hs b/libraries/base/Data/Function.hs index 54eabbb..afb6e56 100644 --- a/libraries/base/Data/Function.hs +++ b/libraries/base/Data/Function.hs @@ -4,6 +4,7 @@ -- | -- Module : Data.Function -- Copyright : Nils Anders Danielsson 2006 +-- , Alexander Berntsen 2014 -- License : BSD-style (see the LICENSE file in the distribution) -- -- Maintainer : libraries at haskell.org @@ -18,6 +19,7 @@ module Data.Function ( -- * "Prelude" re-exports id, const, (.), flip, ($) -- * Other combinators + , (&) , fix , on ) where @@ -25,6 +27,7 @@ module Data.Function import Prelude infixl 0 `on` +infixl 1 & -- | @'fix' f@ is the least fixed point of the function @f@, -- i.e. the least defined @x@ such that @f x = x at . @@ -86,3 +89,11 @@ fix f = let x = f x in x on :: (b -> b -> c) -> (a -> b) -> a -> a -> c (.*.) `on` f = \x y -> f x .*. f y + +-- | '&' is a reverse application operator. This provides notational +-- convenience. Its precedence is one higher than that of the forward +-- application operator '$', which allows '&' to be nested in '$'. +-- +-- /Since: 4.7.1.0/ +(&) :: a -> (a -> b) -> b +x & f = f x diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal index f8937dc..22b40db 100644 --- a/libraries/base/base.cabal +++ b/libraries/base/base.cabal @@ -1,5 +1,5 @@ name: base -version: 4.7.0.0 +version: 4.7.1.0 -- GHC 7.6.1 released with 4.6.0.0 license: BSD3 license-file: LICENSE diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index c88c79e..75e7710 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -1,6 +1,12 @@ # Changelog for [`base` package](http://hackage.haskell.org/package/base) -## 4.7.0.0 *Feb 2014* +## 4.7.1.0 *TBA* + + * Bundled with GHC 7.10.1 + + * Add reverse application operator `Data.Function.(&)` + +## 4.7.0.0 *Apr 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Sat Apr 19 11:17:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 19 Apr 2014 11:17:28 +0000 (UTC) Subject: [commit: ghc] master: Fix sync-all error message introduced in 41f5b7e3e (dc2b8ae) Message-ID: <20140419111728.61AD02406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dc2b8ae261d0219657196dc91a408ec6f0f3de52/ghc >--------------------------------------------------------------- commit dc2b8ae261d0219657196dc91a408ec6f0f3de52 Author: Herbert Valerio Riedel Date: Sat Apr 19 13:12:40 2014 +0200 Fix sync-all error message introduced in 41f5b7e3e Curiously, 'aforesaid' has the same length as the word 'testsuite'... Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- dc2b8ae261d0219657196dc91a408ec6f0f3de52 sync-all | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/sync-all b/sync-all index 6b875bb..4c0e7c1 100755 --- a/sync-all +++ b/sync-all @@ -971,7 +971,7 @@ ATTENTION! You have a left-over testsuite/.git folder in your GHC tree! Please backup or remove it (e.g. "rm -r testsuite/.git") before -proceeding as the testsuite Git repository is now tracked as part of +proceeding as the aforesaid Git repository is now tracked as part of the ghc Git repository (see #8545 for more details) ============================ EOF @@ -987,7 +987,7 @@ ATTENTION! You have a left-over libraries/base/.git folder in your GHC tree! Please backup or remove it (e.g. "rm -r libraries/base/.git") before -proceeding as the testsuite Git repository is now tracked as part of +proceeding as the aforesaid Git repository is now tracked as part of the ghc Git repository (see #8545 for more details) ============================ EOF @@ -1002,7 +1002,7 @@ ATTENTION! You have a left-over libraries/ghc-prim/.git folder in your GHC tree! Please backup or remove it (e.g. "rm -r libraries/ghc-prim/.git") before -proceeding as the testsuite Git repository is now tracked as part of +proceeding as the aforesaid Git repository is now tracked as part of the ghc Git repository (see #8545 for more details) ============================ EOF @@ -1018,7 +1018,7 @@ ATTENTION! You have a left-over libraries/template-haskell/.git folder in your GHC tree! Please backup or remove it (e.g. "rm -r libraries/template-haskell/.git") before -proceeding as the testsuite Git repository is now tracked as part of +proceeding as the aforesaid Git repository is now tracked as part of the ghc Git repository (see #8545 for more details) ============================ EOF @@ -1034,7 +1034,7 @@ ATTENTION! You have a left-over libraries/integer-gmp/.git folder in your GHC tree! Please backup or remove it (e.g. "rm -r libraries/integer-gmp/.git") before -proceeding as the testsuite Git repository is now tracked as part of +proceeding as the aforesaid Git repository is now tracked as part of the ghc Git repository (see #8545 for more details) ============================ EOF @@ -1050,7 +1050,7 @@ ATTENTION! You have a left-over libraries/integer-simple/.git folder in your GHC tree! Please backup or remove it (e.g. "rm -r libraries/integer-simple/.git") before -proceeding as the testsuite Git repository is now tracked as part of +proceeding as the aforesaid Git repository is now tracked as part of the ghc Git repository (see #8545 for more details) ============================ EOF From git at git.haskell.org Sat Apr 19 12:27:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 19 Apr 2014 12:27:43 +0000 (UTC) Subject: [commit: ghc] master: Weaken constraints on Data.Complex functions (7b04d35) Message-ID: <20140419122743.E586A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7b04d35a87f1ee2904579a916ef1a6b0aa6fc7b8/ghc >--------------------------------------------------------------- commit 7b04d35a87f1ee2904579a916ef1a6b0aa6fc7b8 Author: Herbert Valerio Riedel Date: Sat Apr 19 13:56:36 2014 +0200 Weaken constraints on Data.Complex functions The RealFloat data type context was dropped from Data.Complex some time ago (see ea280135dd888ac41d8804a9e37e358180cf13ac). However, the rest of the API in that module was left as-is even though many of the accessors in that module would work with much more general types now. This change simplifies the signatures of the functions above, which in the current API all unnecessarily take a RealFloat constraint that they don't use (and which may cause to pass around superflous type-class dictionaries): realPart :: Complex a -> a imagPart :: Complex a -> a conjugate :: Num a => Complex a -> Complex a mkPolar :: Floating a => a -> a -> Complex a cis :: Floating a => a -> Complex a This was originally proposed by Edward Kmett in http://www.haskell.org/pipermail/libraries/2014-March/022358.html Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 7b04d35a87f1ee2904579a916ef1a6b0aa6fc7b8 libraries/base/Data/Complex.hs | 10 +++++----- libraries/base/changelog.md | 2 ++ 2 files changed, 7 insertions(+), 5 deletions(-) diff --git a/libraries/base/Data/Complex.hs b/libraries/base/Data/Complex.hs index 190c598..b03848b 100644 --- a/libraries/base/Data/Complex.hs +++ b/libraries/base/Data/Complex.hs @@ -58,27 +58,27 @@ data Complex a -- Functions over Complex -- | Extracts the real part of a complex number. -realPart :: (RealFloat a) => Complex a -> a +realPart :: Complex a -> a realPart (x :+ _) = x -- | Extracts the imaginary part of a complex number. -imagPart :: (RealFloat a) => Complex a -> a +imagPart :: Complex a -> a imagPart (_ :+ y) = y -- | The conjugate of a complex number. {-# SPECIALISE conjugate :: Complex Double -> Complex Double #-} -conjugate :: (RealFloat a) => Complex a -> Complex a +conjugate :: Num a => Complex a -> Complex a conjugate (x:+y) = x :+ (-y) -- | Form a complex number from polar components of magnitude and phase. {-# SPECIALISE mkPolar :: Double -> Double -> Complex Double #-} -mkPolar :: (RealFloat a) => a -> a -> Complex a +mkPolar :: Floating a => a -> a -> Complex a mkPolar r theta = r * cos theta :+ r * sin theta -- | @'cis' t@ is a complex value with magnitude @1@ -- and phase @t@ (modulo @2*'pi'@). {-# SPECIALISE cis :: Double -> Complex Double #-} -cis :: (RealFloat a) => a -> Complex a +cis :: Floating a => a -> Complex a cis theta = cos theta :+ sin theta -- | The function 'polar' takes a complex number and diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 3011fdf..a72e4e6 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -8,6 +8,8 @@ * Add `Data.List.sortOn` sorting function + * Weaken RealFloat constraints on some `Data.Complex` functions + ## 4.7.0.0 *Apr 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Sat Apr 19 12:47:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 19 Apr 2014 12:47:29 +0000 (UTC) Subject: [commit: ghc] master: Kill trailing whitespace in recently touched files (bd7b973) Message-ID: <20140419124729.602012406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bd7b97328d9326fb3a425bc6d01bad8b03990ed4/ghc >--------------------------------------------------------------- commit bd7b97328d9326fb3a425bc6d01bad8b03990ed4 Author: Herbert Valerio Riedel Date: Sat Apr 19 14:39:29 2014 +0200 Kill trailing whitespace in recently touched files Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- bd7b97328d9326fb3a425bc6d01bad8b03990ed4 libraries/base/Data/Complex.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/libraries/base/Data/Complex.hs b/libraries/base/Data/Complex.hs index b03848b..af593cd 100644 --- a/libraries/base/Data/Complex.hs +++ b/libraries/base/Data/Complex.hs @@ -173,4 +173,3 @@ instance (RealFloat a) => Floating (Complex a) where asinh z = log (z + sqrt (1+z*z)) acosh z = log (z + (z+1) * sqrt ((z-1)/(z+1))) atanh z = 0.5 * log ((1.0+z) / (1.0-z)) - From git at git.haskell.org Sat Apr 19 12:47:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 19 Apr 2014 12:47:31 +0000 (UTC) Subject: [commit: ghc] master: Normalize GHC Trac URLs (2eb40eb) Message-ID: <20140419124731.CC7882406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2eb40eba2629e23a79671ff7dfafc7f37f750e22/ghc >--------------------------------------------------------------- commit 2eb40eba2629e23a79671ff7dfafc7f37f750e22 Author: Herbert Valerio Riedel Date: Sat Apr 19 14:41:00 2014 +0200 Normalize GHC Trac URLs Update several old http://hackage.haskell.org/trac/ghc URLs references to the current http://ghc.haskell.org/trac/ghc URLs. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 2eb40eba2629e23a79671ff7dfafc7f37f750e22 compiler/main/GHC.hs | 2 +- libraries/base/Control/Category.hs | 2 +- libraries/base/Data/List.hs | 2 +- libraries/base/GHC/Event/Manager.hs | 2 +- libraries/base/GHC/Event/TimerManager.hs | 2 +- libraries/base/GHC/Event/Unique.hs | 2 +- libraries/base/tests/genericNegative001.hs | 2 +- libraries/integer-gmp/gmp/ghc.mk | 4 ++-- libraries/integer-gmp/mkGmpDerivedConstants/Makefile | 4 ++-- libraries/integer-gmp/mkGmpDerivedConstants/ghc.mk | 4 ++-- testsuite/README.md | 2 +- testsuite/tests/codeGen/should_run/cgrun071.hs | 2 +- testsuite/tests/deriving/should_compile/drv012.hs | 2 +- testsuite/tests/gadt/gadt17.hs | 2 +- testsuite/tests/simplCore/should_compile/simpl014.hs | 2 +- 15 files changed, 18 insertions(+), 18 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2eb40eba2629e23a79671ff7dfafc7f37f750e22 From git at git.haskell.org Sat Apr 19 13:48:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 19 Apr 2014 13:48:24 +0000 (UTC) Subject: [commit: ghc] master: sync-all: Apply submodule url rewriting also to stuff in util/ (974a97e) Message-ID: <20140419134824.CF07F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/974a97e3e5f74177d9c09ceda060205959e2f15a/ghc >--------------------------------------------------------------- commit 974a97e3e5f74177d9c09ceda060205959e2f15a Author: Joachim Breitner Date: Sat Apr 19 15:46:32 2014 +0200 sync-all: Apply submodule url rewriting also to stuff in util/ >--------------------------------------------------------------- 974a97e3e5f74177d9c09ceda060205959e2f15a sync-all | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/sync-all b/sync-all index 4c0e7c1..70c4254 100755 --- a/sync-all +++ b/sync-all @@ -476,13 +476,13 @@ sub gitall { $ignore_failure = 1; if ($remotepath eq '-') { $rpath = "$localpath.git"; # N.B.: $localpath lacks the .git suffix - if ($localpath =~ /^libraries\//) { + if ($localpath =~ m!^(?:libraries|utils)/!) { # FIXME: This is just a simple heuristic to # infer the remotepath for Git submodules. A # proper solution would require to parse the # .gitmodules file to obtain the actual # localpath<->remotepath mapping. - $rpath =~ s/^libraries\//packages\//; + $rpath =~ s!^(?:libraries|utils)/!packages/!; } $rpath = "$repo_base/$rpath"; } else { @@ -587,14 +587,14 @@ sub gitInitSubmodules { my $submodulespaths = &readgit(".", "config", "--get-regexp", "^submodule[.].*[.]url"); # if we came from github, change the urls appropriately - while ($submodulespaths =~ m!^(submodule.libraries/[a-zA-Z0-9]+.url) ($GITHUB)/ghc/packages/([a-zA-Z0-9]+).git$!gm) { + while ($submodulespaths =~ m!^(submodule.(?:libraries|utils)/[a-zA-Z0-9]+.url) ($GITHUB)/ghc/packages/([a-zA-Z0-9]+).git$!gm) { &git(".", "config", $1, "$2/ghc/packages-$3"); } # if we came from a local repository, grab our submodules from their # checkouts over there, if they exist. if ($repo_local) { - while ($submodulespaths =~ m!^(submodule.(libraries/[a-zA-Z0-9]+).url) .*$!gm) { + while ($submodulespaths =~ m!^(submodule.((?:libraries|utils)/[a-zA-Z0-9]+).url) .*$!gm) { if (-e "$repo_base/$2/.git") { &git(".", "config", $1, "$repo_base/$2"); } From git at git.haskell.org Sat Apr 19 13:58:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 19 Apr 2014 13:58:47 +0000 (UTC) Subject: [commit: ghc] master: Remove some redundancy in sync-all (f1f2d8f) Message-ID: <20140419135847.2CF6A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f1f2d8f8515ca4802410702eba5786674167b02e/ghc >--------------------------------------------------------------- commit f1f2d8f8515ca4802410702eba5786674167b02e Author: Joachim Breitner Date: Sat Apr 19 15:57:20 2014 +0200 Remove some redundancy in sync-all >--------------------------------------------------------------- f1f2d8f8515ca4802410702eba5786674167b02e sync-all | 183 ++++++++++++-------------------------------------------------- 1 file changed, 33 insertions(+), 150 deletions(-) diff --git a/sync-all b/sync-all index 70c4254..16165bb 100755 --- a/sync-all +++ b/sync-all @@ -962,102 +962,30 @@ BEGIN { $exit_via_die = 1; }; - #message "== Checking for left-over testsuite/.git folder"; - if (-d "testsuite/.git") { - print < /dev/null 2> /dev/null") == 0) { - print < /dev/null 2> /dev/null") == 0) { + print < /dev/null 2> /dev/null") == 0) { - print < /dev/null 2> /dev/null") == 0) { - print < /dev/null 2> /dev/null") == 0) { - print < Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bbf1cca551c1b401f869468ea53518765132a6c9/ghc >--------------------------------------------------------------- commit bbf1cca551c1b401f869468ea53518765132a6c9 Author: Joachim Breitner Date: Sat Apr 19 16:06:54 2014 +0200 More github url variants >--------------------------------------------------------------- bbf1cca551c1b401f869468ea53518765132a6c9 sync-all | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/sync-all b/sync-all index 16165bb..ba80cfe 100755 --- a/sync-all +++ b/sync-all @@ -20,7 +20,7 @@ my $bare_flag = ""; # NOT the opposite of checked_out_flag (describes local repo my %tags; -my $GITHUB = qr!(?:git@|git://|https://|http://)github.com!; +my $GITHUB = qr!(?:git@|git://|https://|http://|ssh://git@)github.com!; sub inDir { my $dir = shift; From git at git.haskell.org Sat Apr 19 14:15:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 19 Apr 2014 14:15:39 +0000 (UTC) Subject: [commit: ghc] master: Do not use basename() (33350ea) Message-ID: <20140419141539.2EBA32406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/33350eab727a24440ee583b854c6643d334eb75d/ghc >--------------------------------------------------------------- commit 33350eab727a24440ee583b854c6643d334eb75d Author: Joachim Breitner Date: Sat Apr 19 16:14:38 2014 +0200 Do not use basename() >--------------------------------------------------------------- 33350eab727a24440ee583b854c6643d334eb75d sync-all | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/sync-all b/sync-all index ba80cfe..e43a6f6 100755 --- a/sync-all +++ b/sync-all @@ -1002,7 +1002,7 @@ END { ); for (@obsolete_dirs) { my ($dir, $hash) = $_; - my $name = basename $dir; + my $name = $dir =~ m!/([^/]+)$!; message "== Checking for old $name repo"; if (-d "$dir/.git") { chdir($dir); From git at git.haskell.org Sat Apr 19 18:40:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 19 Apr 2014 18:40:16 +0000 (UTC) Subject: [commit: ghc] master: Update Cabal source-repository entries (re #8545) (386e874) Message-ID: <20140419184017.125EC2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/386e874e365e310214b701e6f3cb74b4f75348f4/ghc >--------------------------------------------------------------- commit 386e874e365e310214b701e6f3cb74b4f75348f4 Author: Herbert Valerio Riedel Date: Sat Apr 19 20:20:26 2014 +0200 Update Cabal source-repository entries (re #8545) This adapts the source-repository entries to match the new situation of base.git, ghc-prim.git, integer-gmp.git, integer-simple.git, and template-haskell.git being folded into ghc.git Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 386e874e365e310214b701e6f3cb74b4f75348f4 libraries/base/base.cabal | 3 ++- libraries/ghc-prim/ghc-prim.cabal | 8 ++------ libraries/integer-gmp/integer-gmp.cabal | 8 ++------ libraries/integer-simple/integer-simple.cabal | 3 ++- libraries/template-haskell/template-haskell.cabal | 8 ++------ 5 files changed, 10 insertions(+), 20 deletions(-) diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal index 22b40db..a70a661 100644 --- a/libraries/base/base.cabal +++ b/libraries/base/base.cabal @@ -39,7 +39,8 @@ extra-source-files: source-repository head type: git - location: http://git.haskell.org/packages/base.git + location: http://git.haskell.org/ghc.git + subdir: libraries/base Flag integer-simple Description: Use integer-simple diff --git a/libraries/ghc-prim/ghc-prim.cabal b/libraries/ghc-prim/ghc-prim.cabal index ffb32af..c861342 100644 --- a/libraries/ghc-prim/ghc-prim.cabal +++ b/libraries/ghc-prim/ghc-prim.cabal @@ -14,12 +14,8 @@ description: source-repository head type: git - location: http://git.haskell.org/packages/ghc-prim.git - -source-repository this - type: git - location: http://git.haskell.org/packages/ghc-prim.git - tag: ghc-prim-0.3.1.0-release + location: http://git.haskell.org/ghc.git + subdir: libraries/ghc-prim flag include-ghc-prim Description: Include GHC.Prim in exposed-modules diff --git a/libraries/integer-gmp/integer-gmp.cabal b/libraries/integer-gmp/integer-gmp.cabal index 817a854..c0f6b60 100644 --- a/libraries/integer-gmp/integer-gmp.cabal +++ b/libraries/integer-gmp/integer-gmp.cabal @@ -47,12 +47,8 @@ extra-tmp-files: source-repository head type: git - location: http://git.haskell.org/packages/integer-gmp.git - -source-repository this - type: git - location: http://git.haskell.org/packages/integer-gmp.git - tag: integer-gmp-0.5.1.0-release + location: http://git.haskell.org/ghc.git + subdir: libraries/integer-gmp Library default-language: Haskell2010 diff --git a/libraries/integer-simple/integer-simple.cabal b/libraries/integer-simple/integer-simple.cabal index 11c58dc..fa41c24 100644 --- a/libraries/integer-simple/integer-simple.cabal +++ b/libraries/integer-simple/integer-simple.cabal @@ -12,7 +12,8 @@ build-type: Simple source-repository head type: git - location: http://git.haskell.org/packages/integer-simple.git + location: http://git.haskell.org/ghc.git + subdir: libraries/integer-simple Library { build-depends: ghc-prim diff --git a/libraries/template-haskell/template-haskell.cabal b/libraries/template-haskell/template-haskell.cabal index d3cf0cc..ca0e344 100644 --- a/libraries/template-haskell/template-haskell.cabal +++ b/libraries/template-haskell/template-haskell.cabal @@ -18,12 +18,8 @@ description: source-repository head type: git - location: http://git.haskell.org/packages/template-haskell.git - -source-repository this - type: git - location: http://git.haskell.org/packages/template-haskell.git - tag: template-haskell-2.10.0.0-release + location: http://git.haskell.org/ghc.git + subdir: libraries/template-haskell Library default-language: Haskell2010 From git at git.haskell.org Sun Apr 20 06:00:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 20 Apr 2014 06:00:30 +0000 (UTC) Subject: [commit: packages/dph] master: dph-lifted-copy: s/join/joinG/ in TH.Repr (3ebad52) Message-ID: <20140420060030.A82A92406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/dph On branch : master Link : http://git.haskell.org/packages/dph.git/commitdiff/3ebad521cd1e3b5573d97b483305ca465a9cba69 >--------------------------------------------------------------- commit 3ebad521cd1e3b5573d97b483305ca465a9cba69 Author: Austin Seipp Date: Sun Apr 20 00:59:28 2014 -0500 dph-lifted-copy: s/join/joinG/ in TH.Repr This is the final piece for GHC to be AMP compliant. The use of 'join' here is totally internal, so rather than hiding the import, it's just as easy to rename to 'joinG' (for the Gen type). Signed-off-by: Austin Seipp >--------------------------------------------------------------- 3ebad521cd1e3b5573d97b483305ca465a9cba69 dph-lifted-copy/Data/Array/Parallel/Lifted/TH/Repr.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/dph-lifted-copy/Data/Array/Parallel/Lifted/TH/Repr.hs b/dph-lifted-copy/Data/Array/Parallel/Lifted/TH/Repr.hs index fb6b02b..c873e32 100644 --- a/dph-lifted-copy/Data/Array/Parallel/Lifted/TH/Repr.hs +++ b/dph-lifted-copy/Data/Array/Parallel/Lifted/TH/Repr.hs @@ -162,7 +162,7 @@ data Gen = Gen { recursiveCalls :: Int , recursiveName :: Name -> Name , split :: ArgVal -> (Split, Arg) - , join :: Val -> [ExpQ] -> ExpQ + , joinG :: Val -> [ExpQ] -> ExpQ , typeName :: String } @@ -171,7 +171,7 @@ recursiveMethod gen name avs res = simpleFunD (mkName $ nameBase name) (map pat splits) $ appE (varE 'traceFn `appEs` [stringE (nameBase name), stringE (typeName gen)]) $ foldr mk_case - (join gen res + (joinG gen res . recurse (recursiveCalls gen) . trans $ map expand args) @@ -378,7 +378,7 @@ wrapGen wrap unwrap pwrap = Gen { recursiveCalls = 1 , recursiveName = recursiveName' , split = split' - , join = join' + , joinG = join' , typeName = "Wrap a" } where @@ -447,7 +447,7 @@ tupGen :: Int -> Gen tupGen arity = Gen { recursiveCalls = arity , recursiveName = id , split = split' - , join = join' + , joinG = join' , typeName = tyname } where From git at git.haskell.org Sun Apr 20 06:02:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 20 Apr 2014 06:02:21 +0000 (UTC) Subject: [commit: ghc] master: Remove -fno-warn-amp sledgehammers for validate (6074c5d) Message-ID: <20140420060221.4CE822406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6074c5da7f48f10e9b3b88d14607ec4955735931/ghc >--------------------------------------------------------------- commit 6074c5da7f48f10e9b3b88d14607ec4955735931 Author: Austin Seipp Date: Sun Apr 20 01:00:44 2014 -0500 Remove -fno-warn-amp sledgehammers for validate GHC should now fully compliant with respect to the Applicative Monad proposal (including all upstream libraries), and does not need to suppress this warning anymore. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 6074c5da7f48f10e9b3b88d14607ec4955735931 mk/validate-settings.mk | 2 -- 1 file changed, 2 deletions(-) diff --git a/mk/validate-settings.mk b/mk/validate-settings.mk index 8797bf9..cac938d 100644 --- a/mk/validate-settings.mk +++ b/mk/validate-settings.mk @@ -32,7 +32,6 @@ SRC_HC_OPTS += $(WERROR) -Wall GhcStage1HcOpts += -fwarn-tabs GhcStage2HcOpts += -fwarn-tabs -GhcStage2HcOpts += -fno-warn-amp # Temporary sledgehammer until we sync upstream. utils/hpc_dist-install_EXTRA_HC_OPTS += -fwarn-tabs @@ -46,7 +45,6 @@ GhcStage2HcOpts += -O -dcore-lint # running of the tests, and faster building of the utils to be installed GhcLibHcOpts += -O -dcore-lint -GhcLibHcOpts += -fno-warn-amp # Temporary sledgehammer until we sync upstream. # We define DefaultFastGhcLibWays in this style so that the value is # correct even if the user alters DYNAMIC_GHC_PROGRAMS. From git at git.haskell.org Sun Apr 20 15:39:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 20 Apr 2014 15:39:40 +0000 (UTC) Subject: [commit: ghc] master: Update submodule to final Cabal-1.20.0.0 release (35d95a2) Message-ID: <20140420153940.CD8C12406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/35d95a2abe944f8c51c9faf798a404f458bc2ad2/ghc >--------------------------------------------------------------- commit 35d95a2abe944f8c51c9faf798a404f458bc2ad2 Author: Herbert Valerio Riedel Date: Sun Apr 20 17:31:34 2014 +0200 Update submodule to final Cabal-1.20.0.0 release Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 35d95a2abe944f8c51c9faf798a404f458bc2ad2 libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index 8af39a5..375cfd6 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 8af39a5f827dcf5b5ca68badc2955e4cccbb039d +Subproject commit 375cfd6650cc0360097dcd54515c97e42541af6d From git at git.haskell.org Sun Apr 20 21:56:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 20 Apr 2014 21:56:08 +0000 (UTC) Subject: [commit: ghc] master: testsuite/spec001: untabify, kill trailing whitespace (31dd5e5) Message-ID: <20140420215608.50C342406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/31dd5e5db965fa9ed30ac5b58514668f92843c01/ghc >--------------------------------------------------------------- commit 31dd5e5db965fa9ed30ac5b58514668f92843c01 Author: Austin Seipp Date: Sun Apr 20 16:55:14 2014 -0500 testsuite/spec001: untabify, kill trailing whitespace Signed-off-by: Austin Seipp >--------------------------------------------------------------- 31dd5e5db965fa9ed30ac5b58514668f92843c01 .../tests/simplCore/should_compile/spec001.hs | 182 ++++++++++---------- 1 file changed, 91 insertions(+), 91 deletions(-) diff --git a/testsuite/tests/simplCore/should_compile/spec001.hs b/testsuite/tests/simplCore/should_compile/spec001.hs index c4f9205..f4b4dd0 100644 --- a/testsuite/tests/simplCore/should_compile/spec001.hs +++ b/testsuite/tests/simplCore/should_compile/spec001.hs @@ -12,77 +12,77 @@ module Data.PackedString.Latin1 ( - -- * The @PackedString@ type + -- * The @PackedString@ type PackedString, -- abstract, instances: Eq, Ord, Show, Typeable -- * Converting to and from @PackedString at s - pack, - unpack, - - -- * I\/O with @PackedString at s - hPut, hGet, - - -- * List-like manipulation functions - nil, - cons, - head, - tail, - null, - append, - length, - index, - map, - filter, - reverse, - concat, - elem, - substr, - take, - drop, - splitAt, - foldl, - foldr, - takeWhile, - dropWhile, - span, - break, - lines, - unlines, - words, - unwords, - split, - splitWith, - join, --- unpackList, -- eek, otherwise it gets thrown away by the simplifier + pack, + unpack, + + -- * I\/O with @PackedString at s + hPut, hGet, + + -- * List-like manipulation functions + nil, + cons, + head, + tail, + null, + append, + length, + index, + map, + filter, + reverse, + concat, + elem, + substr, + take, + drop, + splitAt, + foldl, + foldr, + takeWhile, + dropWhile, + span, + break, + lines, + unlines, + words, + unwords, + split, + splitWith, + join, +-- unpackList, -- eek, otherwise it gets thrown away by the simplifier ) where import qualified Prelude import Prelude hiding ( - head, - tail, - null, - length, - (!!), - map, - filter, - reverse, - concat, - elem, - take, - drop, - foldl, - foldr, - splitAt, - takeWhile, - dropWhile, - span, - break, - lines, - unlines, - words, - unwords, - join + head, + tail, + null, + length, + (!!), + map, + filter, + reverse, + concat, + elem, + take, + drop, + foldl, + foldr, + splitAt, + takeWhile, + dropWhile, + span, + break, + lines, + unlines, + words, + unwords, + join ) import GHC.Exts @@ -100,11 +100,11 @@ import System.IO -- various efficient operations. A 'PackedString' contains Latin1 -- (8-bit) characters only. data PackedString = PS {-#UNPACK#-}!Int {-#UNPACK#-}!Int - {-#UNPACK#-}!(ForeignPtr Word8) - -- this is a pretty efficient representation, and can be - -- converted to/from a StorableArray. - -- When the ForeignPtr is unpacked, we get the Addr# stored - -- directly in the PS constructor. + {-#UNPACK#-}!(ForeignPtr Word8) + -- this is a pretty efficient representation, and can be + -- converted to/from a StorableArray. + -- When the ForeignPtr is unpacked, we get the Addr# stored + -- directly in the PS constructor. -- Perhaps making a slice should be conditional on the ratio of the -- slice/string size to limit memory leaks. @@ -117,9 +117,9 @@ instance Ord PackedString where comparePS (PS off1 len1 fp1) (PS off2 len2 fp2) = inlinePerformIO $ - withForeignPtr fp1 $ \p1 -> - withForeignPtr fp2 $ \p2 -> - cmp (p1 `plusPtr` off1) (p2 `plusPtr` off2) len1 + withForeignPtr fp1 $ \p1 -> + withForeignPtr fp2 $ \p2 -> + cmp (p1 `plusPtr` off1) (p2 `plusPtr` off2) len1 where cmp :: Ptr Word8 -> Ptr Word8 -> Int -> IO Ordering cmp p1 p2 n @@ -129,9 +129,9 @@ comparePS (PS off1 len1 fp1) (PS off2 len2 fp2) a <- peekElemOff p1 n b <- peekElemOff p2 n case a `compare` b of - EQ -> cmp p1 p2 (n+1) - LT -> return LT - GT -> return GT + EQ -> cmp p1 p2 (n+1) + LT -> return LT + GT -> return GT --instance Read PackedString: ToDo @@ -146,8 +146,8 @@ deriving instance Typeable PackedString -- | The 'nilPS' value is the empty string. nil :: PackedString nil = inlinePerformIO $ do - fp <- newForeignPtr_ nullPtr - return (PS 0 0 fp) + fp <- newForeignPtr_ nullPtr + return (PS 0 0 fp) -- | The 'consPS' function prepends the given character to the -- given string. @@ -159,8 +159,8 @@ packLen :: Int -> String -> PackedString packLen len str = inlinePerformIO $ do fp <- mallocForeignPtrBytes len withForeignPtr fp $ \p -> do - fill_it_in p 0 str - return (PS 0 len fp) + fill_it_in p 0 str + return (PS 0 len fp) fill_it_in p i [] = return () fill_it_in p i (c:cs) = do pokeElemOff p i (c2w c); fill_it_in p (i+1) cs @@ -246,7 +246,7 @@ take :: Int -> PackedString -> PackedString take n ps = substr ps 0 (n-1) -- | The 'drop' function drops the first @n@ characters of a 'PackedString'. -drop :: Int -> PackedString -> PackedString +drop :: Int -> PackedString -> PackedString drop n ps = substr ps n (length ps - 1) -- | The 'splitWith' function splits a 'PackedString' at a given index. @@ -334,15 +334,15 @@ splitWith' pred off len fp = withPackedString fp $ \p -> splitLoop pred p 0 off len fp splitLoop pred p idx off len fp - | p `seq` idx `seq` off `seq` fp `seq` False = undefined + | p `seq` idx `seq` off `seq` fp `seq` False = undefined splitLoop pred p idx off len fp - | idx >= len = return [PS off idx fp] - | otherwise = do - w <- peekElemOff p (off+idx) - if pred (w2c w) - then return (PS off idx fp : - splitWith' pred (off+idx+1) (len-idx-1) fp) - else splitLoop pred p (idx+1) off len fp + | idx >= len = return [PS off idx fp] + | otherwise = do + w <- peekElemOff p (off+idx) + if pred (w2c w) + then return (PS off idx fp : + splitWith' pred (off+idx+1) (len-idx-1) fp) + else splitLoop pred p (idx+1) off len fp -- ----------------------------------------------------------------------------- -- Local utility functions @@ -399,9 +399,9 @@ unpackList :: PackedString -> [Char] unpackList (PS off len fp) = withPackedString fp $ \p -> do let loop p (-1) acc = return acc - loop p n acc = do + loop p n acc = do a <- peekElemOff p n - loop p (n-1) (w2c a : acc) + loop p (n-1) (w2c a : acc) loop (p `plusPtr` off) (len-1) [] {-# INLINE [0] unpackFoldr #-} @@ -409,9 +409,9 @@ unpackFoldr :: PackedString -> (Char -> a -> a) -> a -> a unpackFoldr (PS off len fp) f c = withPackedString fp $ \p -> do let loop p (-1) acc = return acc - loop p n acc = do + loop p n acc = do a <- peekElemOff p n - loop p (n-1) (w2c a `f` acc) + loop p (n-1) (w2c a `f` acc) loop (p `plusPtr` off) (len-1) c -- ----------------------------------------------------------------------------- From git at git.haskell.org Sun Apr 20 21:56:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 20 Apr 2014 21:56:11 +0000 (UTC) Subject: [commit: ghc] master: Deprecate the AMP warnings. (3608f65) Message-ID: <20140420215611.65A2A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3608f657d55b7ea7dd711556a4faf6a15c509163/ghc >--------------------------------------------------------------- commit 3608f657d55b7ea7dd711556a4faf6a15c509163 Author: Austin Seipp Date: Sun Apr 20 01:10:15 2014 -0500 Deprecate the AMP warnings. Now that we're in development mode, Applicative will soon be a superclass of Monad in HEAD. So let's go ahead and deprecate the -fno-warn-amp flag, remove the checks, and tweak a few tests Signed-off-by: Austin Seipp >--------------------------------------------------------------- 3608f657d55b7ea7dd711556a4faf6a15c509163 compiler/main/DynFlags.hs | 4 +- compiler/typecheck/TcRnDriver.lhs | 215 +------------------- docs/users_guide/flags.xml | 2 +- .../tests/ghci.debugger/scripts/break006.stderr | 4 +- .../tests/ghci.debugger/scripts/print019.stderr | 2 +- .../should_fail/overloadedlistsfail01.stderr | 2 +- testsuite/tests/rename/should_compile/T7145b.hs | 3 - .../tests/rename/should_compile/T7145b.stderr | 2 +- .../tests/simplCore/should_compile/spec001.hs | 3 +- .../tests/typecheck/should_compile/holes2.stderr | 2 +- testsuite/tests/typecheck/should_fail/T5095.stderr | 2 - .../tests/typecheck/should_fail/tcfail072.stderr | 2 +- .../tests/typecheck/should_fail/tcfail133.stderr | 2 +- .../tests/typecheck/should_fail/tcfail181.stderr | 1 - 14 files changed, 14 insertions(+), 232 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3608f657d55b7ea7dd711556a4faf6a15c509163 From git at git.haskell.org Mon Apr 21 11:42:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 21 Apr 2014 11:42:33 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T9016' created Message-ID: <20140421114233.4B4792406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T9016 Referencing: c4ea79c71ad01287bfbdaafa78bdf195988411e2 From git at git.haskell.org Mon Apr 21 11:42:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 21 Apr 2014 11:42:35 +0000 (UTC) Subject: [commit: ghc] wip/T9016: Add System.Exit.die (re #9016) (c4ea79c) Message-ID: <20140421114235.C3EBE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T9016 Link : http://ghc.haskell.org/trac/ghc/changeset/c4ea79c71ad01287bfbdaafa78bdf195988411e2/ghc >--------------------------------------------------------------- commit c4ea79c71ad01287bfbdaafa78bdf195988411e2 Author: Simon Hengel Date: Mon Apr 21 11:34:38 2014 +0800 Add System.Exit.die (re #9016) The original proposal discussion can be found at http://thread.gmane.org/gmane.comp.lang.haskell.libraries/20872 >--------------------------------------------------------------- c4ea79c71ad01287bfbdaafa78bdf195988411e2 libraries/base/System/Exit.hs | 7 +++++++ libraries/base/changelog.md | 2 ++ 2 files changed, 9 insertions(+) diff --git a/libraries/base/System/Exit.hs b/libraries/base/System/Exit.hs index a3059fc..4f6eba6 100644 --- a/libraries/base/System/Exit.hs +++ b/libraries/base/System/Exit.hs @@ -20,9 +20,11 @@ module System.Exit , exitWith , exitFailure , exitSuccess + , die ) where import Prelude +import System.IO import GHC.IO import GHC.IO.Exception @@ -74,3 +76,8 @@ exitFailure = exitWith (ExitFailure 1) exitSuccess :: IO a exitSuccess = exitWith ExitSuccess +-- | Write given error message to `stderr` and terminate with `exitFailure`. +-- +-- /Since: 4.7.1.0/ +die :: String -> IO () +die err = hPutStrLn stderr err >> exitFailure diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index a72e4e6..c561165 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -8,6 +8,8 @@ * Add `Data.List.sortOn` sorting function + * Add `System.Exit.die` + * Weaken RealFloat constraints on some `Data.Complex` functions ## 4.7.0.0 *Apr 2014* From git at git.haskell.org Mon Apr 21 13:52:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 21 Apr 2014 13:52:48 +0000 (UTC) Subject: [commit: ghc] master: ghc: Do not add a space in '-U __PIC__' (574ef42) Message-ID: <20140421135248.858042406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/574ef4293b867609f2d28d85747e01f3ac0d052d/ghc >--------------------------------------------------------------- commit 574ef4293b867609f2d28d85747e01f3ac0d052d Author: Austin Seipp Date: Mon Apr 21 07:22:50 2014 -0500 ghc: Do not add a space in '-U __PIC__' GHC previously introduced a space here. However, this can in some cases be interpreted as "-U __PIC__" - note that in shell, the -U would still be recognized with an argument, but the argument would be " __PIC__", with a space in front, as opposed to the single string '__PIC__'. In practice most tools seem to handle this OK. But the Coverity Scan analysis tool does not: it errors on the fact that ' __PIC__' is an invalid CPP name to undefine. With this, it seems the Coverity analysis tool can easily analyze the entire GHC build. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 574ef4293b867609f2d28d85747e01f3ac0d052d compiler/main/DynFlags.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 1f7044c..ee4f8a7 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -3548,10 +3548,10 @@ picCCOpts dflags -- Don't generate "common" symbols - these are unwanted -- in dynamic libraries. - | gopt Opt_PIC dflags -> ["-fno-common", "-U __PIC__", "-D__PIC__"] + | gopt Opt_PIC dflags -> ["-fno-common", "-U__PIC__", "-D__PIC__"] | otherwise -> ["-mdynamic-no-pic"] OSMinGW32 -- no -fPIC for Windows - | gopt Opt_PIC dflags -> ["-U __PIC__", "-D__PIC__"] + | gopt Opt_PIC dflags -> ["-U__PIC__", "-D__PIC__"] | otherwise -> [] _ -- we need -fPIC for C files when we are compiling with -dynamic, @@ -3560,12 +3560,12 @@ picCCOpts dflags -- objects, but can't without -fPIC. See -- http://ghc.haskell.org/trac/ghc/wiki/Commentary/PositionIndependentCode | gopt Opt_PIC dflags || not (gopt Opt_Static dflags) -> - ["-fPIC", "-U __PIC__", "-D__PIC__"] + ["-fPIC", "-U__PIC__", "-D__PIC__"] | otherwise -> [] picPOpts :: DynFlags -> [String] picPOpts dflags - | gopt Opt_PIC dflags = ["-U __PIC__", "-D__PIC__"] + | gopt Opt_PIC dflags = ["-U__PIC__", "-D__PIC__"] | otherwise = [] -- ----------------------------------------------------------------------------- From git at git.haskell.org Mon Apr 21 15:17:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 21 Apr 2014 15:17:06 +0000 (UTC) Subject: [commit: haddock] master: Replace local `die` by new `System.Exit.die` (08aa509) Message-ID: <20140421151706.722392406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/08aa509ebac58bfb202ea79c7c41291ec280a1c5 >--------------------------------------------------------------- commit 08aa509ebac58bfb202ea79c7c41291ec280a1c5 Author: Herbert Valerio Riedel Date: Mon Apr 21 16:26:59 2014 +0200 Replace local `die` by new `System.Exit.die` Starting with GHC 7.10, System.Exit exports the new `die` which is essentially the same as Haddock.Util.die, so this commit changes Haddock.Util.die to be a simple re-export of System.Exit.die. See also https://ghc.haskell.org/trac/ghc/ticket/9016 for more details. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 08aa509ebac58bfb202ea79c7c41291ec280a1c5 src/Haddock/Utils.hs | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/src/Haddock/Utils.hs b/src/Haddock/Utils.hs index ee7bfd0..9ccca36 100644 --- a/src/Haddock/Utils.hs +++ b/src/Haddock/Utils.hs @@ -300,11 +300,7 @@ bye :: String -> IO a bye s = putStr s >> exitSuccess -die :: String -> IO a -die s = hPutStr stderr s >> exitWith (ExitFailure 1) - - -dieMsg :: String -> IO a +dieMsg :: String -> IO () dieMsg s = getProgramName >>= \prog -> die (prog ++ ": " ++ s) From git at git.haskell.org Mon Apr 21 15:18:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 21 Apr 2014 15:18:43 +0000 (UTC) Subject: [commit: ghc] master: Use import list to hide new System.Exit.die (e2b14c7) Message-ID: <20140421151844.17D4B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e2b14c70c800363db5ccb5c3032eed8b9d7d3747/ghc >--------------------------------------------------------------- commit e2b14c70c800363db5ccb5c3032eed8b9d7d3747 Author: Herbert Valerio Riedel Date: Mon Apr 21 16:37:30 2014 +0200 Use import list to hide new System.Exit.die Soon, System.Exit will export the new `die` (see #9016) which would clash with Cabal's own `die` implementation. This commit provides forward-compatiblity. This also updates the Cabal submodule which requires a similiar fix. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- e2b14c70c800363db5ccb5c3032eed8b9d7d3747 libraries/Cabal | 2 +- utils/ghc-cabal/Main.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/Cabal b/libraries/Cabal index 375cfd6..597ed8f 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 375cfd6650cc0360097dcd54515c97e42541af6d +Subproject commit 597ed8f613db327cfab958aa64da6c0f9e1ee291 diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs index cfd3d27..d33652f 100644 --- a/utils/ghc-cabal/Main.hs +++ b/utils/ghc-cabal/Main.hs @@ -28,7 +28,7 @@ import Data.Maybe import System.IO import System.Directory import System.Environment -import System.Exit +import System.Exit (exitWith, ExitCode(..)) import System.FilePath main :: IO () From git at git.haskell.org Mon Apr 21 15:18:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 21 Apr 2014 15:18:47 +0000 (UTC) Subject: [commit: ghc] master: Kill whitespace after cpp's `-I` flag (4ab8fc5) Message-ID: <20140421151847.1C5412406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4ab8fc55eb6119dbba2f487c5a01d30a7c6ae113/ghc >--------------------------------------------------------------- commit 4ab8fc55eb6119dbba2f487c5a01d30a7c6ae113 Author: Herbert Valerio Riedel Date: Mon Apr 21 16:55:11 2014 +0200 Kill whitespace after cpp's `-I` flag This clean-up is in a similiar spirit as 574ef4293b8676. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 4ab8fc55eb6119dbba2f487c5a01d30a7c6ae113 compiler/main/DriverPipeline.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 2816c94..b93cef1 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1045,7 +1045,7 @@ runPhase (RealPhase cc_phase) input_fn dflags -- files; this is the Value Add(TM) that using ghc instead of -- gcc gives you :) pkg_include_dirs <- liftIO $ getPackageIncludePath dflags pkgs - let include_paths = foldr (\ x xs -> "-I" : x : xs) [] + let include_paths = foldr (\ x xs -> ("-I" ++ x) : xs) [] (cmdline_include_paths ++ pkg_include_dirs) let gcc_extra_viac_flags = extraGccViaCFlags dflags From git at git.haskell.org Mon Apr 21 15:18:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 21 Apr 2014 15:18:50 +0000 (UTC) Subject: [commit: ghc] master: Add System.Exit.die (re #9016) (77ea2eb) Message-ID: <20140421151850.44E512406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/77ea2eb0ab36d1a610269f6737b509b6f6a376fa/ghc >--------------------------------------------------------------- commit 77ea2eb0ab36d1a610269f6737b509b6f6a376fa Author: Simon Hengel Date: Mon Apr 21 11:34:38 2014 +0800 Add System.Exit.die (re #9016) The original proposal discussion can be found at http://thread.gmane.org/gmane.comp.lang.haskell.libraries/20872 Note this also updates the Haddock submodule to remove Hadock's local `die` implementation. >--------------------------------------------------------------- 77ea2eb0ab36d1a610269f6737b509b6f6a376fa libraries/base/System/Exit.hs | 7 +++++++ libraries/base/changelog.md | 2 ++ utils/haddock | 2 +- 3 files changed, 10 insertions(+), 1 deletion(-) diff --git a/libraries/base/System/Exit.hs b/libraries/base/System/Exit.hs index a3059fc..4f6eba6 100644 --- a/libraries/base/System/Exit.hs +++ b/libraries/base/System/Exit.hs @@ -20,9 +20,11 @@ module System.Exit , exitWith , exitFailure , exitSuccess + , die ) where import Prelude +import System.IO import GHC.IO import GHC.IO.Exception @@ -74,3 +76,8 @@ exitFailure = exitWith (ExitFailure 1) exitSuccess :: IO a exitSuccess = exitWith ExitSuccess +-- | Write given error message to `stderr` and terminate with `exitFailure`. +-- +-- /Since: 4.7.1.0/ +die :: String -> IO () +die err = hPutStrLn stderr err >> exitFailure diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index a72e4e6..c561165 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -8,6 +8,8 @@ * Add `Data.List.sortOn` sorting function + * Add `System.Exit.die` + * Weaken RealFloat constraints on some `Data.Complex` functions ## 4.7.0.0 *Apr 2014* diff --git a/utils/haddock b/utils/haddock index ac60bd1..08aa509 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit ac60bd1f98ad02644d3ea36dd4926ed6e105c789 +Subproject commit 08aa509ebac58bfb202ea79c7c41291ec280a1c5 From git at git.haskell.org Mon Apr 21 18:56:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 21 Apr 2014 18:56:08 +0000 (UTC) Subject: [commit: ghc] master: Generalise type of recently added System.Exit.die (bcd989d) Message-ID: <20140421185608.A8F582406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bcd989d13072a189b49d9393b0d4b1bbaede9d36/ghc >--------------------------------------------------------------- commit bcd989d13072a189b49d9393b0d4b1bbaede9d36 Author: Herbert Valerio Riedel Date: Mon Apr 21 20:29:15 2014 +0200 Generalise type of recently added System.Exit.die This is a follow-up to 77ea2eb0ab36d1a (re #9016) which added `die` with a return type of `IO ()` even though all other functions in System.Exit have the more general return type `IO a`. It is assumed this was an oversight in the original proposal. Acked-by: Edward Kmett Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- bcd989d13072a189b49d9393b0d4b1bbaede9d36 libraries/base/System/Exit.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/System/Exit.hs b/libraries/base/System/Exit.hs index 4f6eba6..932cbfb 100644 --- a/libraries/base/System/Exit.hs +++ b/libraries/base/System/Exit.hs @@ -79,5 +79,5 @@ exitSuccess = exitWith ExitSuccess -- | Write given error message to `stderr` and terminate with `exitFailure`. -- -- /Since: 4.7.1.0/ -die :: String -> IO () +die :: String -> IO a die err = hPutStrLn stderr err >> exitFailure From git at git.haskell.org Tue Apr 22 03:12:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 03:12:22 +0000 (UTC) Subject: [commit: ghc] master: ghc & docs: kill unused flags (a383139) Message-ID: <20140422031222.2FCA32406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a3831391e1defdf69214dc258eebcf37d92991f2/ghc >--------------------------------------------------------------- commit a3831391e1defdf69214dc258eebcf37d92991f2 Author: Austin Seipp Date: Mon Apr 21 22:10:05 2014 -0500 ghc & docs: kill unused flags This removes the following, now defunct flags, which will not be recognized by GHC 7.10: -fwarn-lazy-unlifted-bindings -pgmm and -optm (used for the Mangler, long dead) -keep-raw-s-file & -keep-raw-s-files -monly[432]-reg-only Signed-off-by: Austin Seipp >--------------------------------------------------------------- a3831391e1defdf69214dc258eebcf37d92991f2 compiler/main/DynFlags.hs | 10 ---------- docs/users_guide/flags.xml | 14 -------------- docs/users_guide/phases.xml | 9 --------- 3 files changed, 33 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index ee4f8a7..72ebb38 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -457,7 +457,6 @@ data WarningFlag = | Opt_WarnTabs | Opt_WarnUnrecognisedPragmas | Opt_WarnDodgyForeignImports - | Opt_WarnLazyUnliftedBindings | Opt_WarnUnusedDoBind | Opt_WarnWrongDoBind | Opt_WarnAlternativeLayoutRuleTransitional @@ -2163,7 +2162,6 @@ dynamic_flags = [ , Flag "pgmP" (hasArg setPgmP) , Flag "pgmF" (hasArg (\f -> alterSettings (\s -> s { sPgm_F = f}))) , Flag "pgmc" (hasArg (\f -> alterSettings (\s -> s { sPgm_c = (f,[])}))) - , Flag "pgmm" (HasArg (\_ -> addWarn "The -pgmm flag does nothing; it will be removed in a future GHC release")) , Flag "pgms" (hasArg (\f -> alterSettings (\s -> s { sPgm_s = (f,[])}))) , Flag "pgma" (hasArg (\f -> alterSettings (\s -> s { sPgm_a = (f,[])}))) , Flag "pgml" (hasArg (\f -> alterSettings (\s -> s { sPgm_l = (f,[])}))) @@ -2178,7 +2176,6 @@ dynamic_flags = [ , Flag "optP" (hasArg addOptP) , Flag "optF" (hasArg (\f -> alterSettings (\s -> s { sOpt_F = f : sOpt_F s}))) , Flag "optc" (hasArg addOptc) - , Flag "optm" (HasArg (\_ -> addWarn "The -optm flag does nothing; it will be removed in a future GHC release")) , Flag "opta" (hasArg (\f -> alterSettings (\s -> s { sOpt_a = f : sOpt_a s}))) , Flag "optl" (hasArg addOptl) , Flag "optwindres" (hasArg (\f -> alterSettings (\s -> s { sOpt_windres = f : sOpt_windres s}))) @@ -2244,8 +2241,6 @@ dynamic_flags = [ , Flag "keep-hc-files" (NoArg (setGeneralFlag Opt_KeepHcFiles)) , Flag "keep-s-file" (NoArg (setGeneralFlag Opt_KeepSFiles)) , Flag "keep-s-files" (NoArg (setGeneralFlag Opt_KeepSFiles)) - , Flag "keep-raw-s-file" (NoArg (addWarn "The -keep-raw-s-file flag does nothing; it will be removed in a future GHC release")) - , Flag "keep-raw-s-files" (NoArg (addWarn "The -keep-raw-s-files flag does nothing; it will be removed in a future GHC release")) , Flag "keep-llvm-file" (NoArg (do setObjTarget HscLlvm setGeneralFlag Opt_KeepLlvmFiles)) , Flag "keep-llvm-files" (NoArg (do setObjTarget HscLlvm @@ -2385,9 +2380,6 @@ dynamic_flags = [ ------ Machine dependant (-m) stuff --------------------------- - , Flag "monly-2-regs" (NoArg (addWarn "The -monly-2-regs flag does nothing; it will be removed in a future GHC release")) - , Flag "monly-3-regs" (NoArg (addWarn "The -monly-3-regs flag does nothing; it will be removed in a future GHC release")) - , Flag "monly-4-regs" (NoArg (addWarn "The -monly-4-regs flag does nothing; it will be removed in a future GHC release")) , Flag "msse" (versionSuffix (\maj min d -> d{ sseVersion = Just (maj, min) })) , Flag "mavx" (noArg (\d -> d{ avx = True })) , Flag "mavx2" (noArg (\d -> d{ avx2 = True })) @@ -2612,8 +2604,6 @@ fWarningFlags = [ ( "warn-tabs", Opt_WarnTabs, nop ), ( "warn-typed-holes", Opt_WarnTypedHoles, nop ), ( "warn-unrecognised-pragmas", Opt_WarnUnrecognisedPragmas, nop ), - ( "warn-lazy-unlifted-bindings", Opt_WarnLazyUnliftedBindings, - \_ -> deprecate "it has no effect, and will be removed in GHC 7.10" ), ( "warn-unused-do-bind", Opt_WarnUnusedDoBind, nop ), ( "warn-wrong-do-bind", Opt_WarnWrongDoBind, nop ), ( "warn-alternative-layout-rule-transitional", Opt_WarnAlternativeLayoutRuleTransitional, nop ), diff --git a/docs/users_guide/flags.xml b/docs/users_guide/flags.xml index 43af1d7..593bf4b 100644 --- a/docs/users_guide/flags.xml +++ b/docs/users_guide/flags.xml @@ -2550,12 +2550,6 @@ - - option - pass option to the mangler - dynamic - - - - option pass option to the assembler dynamic @@ -2607,14 +2601,6 @@ - - - - - (x86 only) give some registers back to the C compiler - dynamic - - - - diff --git a/docs/users_guide/phases.xml b/docs/users_guide/phases.xml index acb53a7..db32f38 100644 --- a/docs/users_guide/phases.xml +++ b/docs/users_guide/phases.xml @@ -218,15 +218,6 @@ - option - - - - Pass option to the mangler. - - - - option From git at git.haskell.org Tue Apr 22 04:40:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 04:40:27 +0000 (UTC) Subject: [commit: ghc] master: ghc: initial AArch64 patches (c29bf98) Message-ID: <20140422044027.7F8BE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c29bf984dd20431cd4344e8a5c444d7a5be08389/ghc >--------------------------------------------------------------- commit c29bf984dd20431cd4344e8a5c444d7a5be08389 Author: Colin Watson Date: Mon Apr 21 22:26:56 2014 -0500 ghc: initial AArch64 patches Signed-off-by: Austin Seipp >--------------------------------------------------------------- c29bf984dd20431cd4344e8a5c444d7a5be08389 aclocal.m4 | 6 ++ compiler/nativeGen/AsmCodeGen.lhs | 1 + compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs | 4 ++ compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs | 1 + compiler/nativeGen/RegAlloc/Linear/Main.hs | 1 + compiler/nativeGen/TargetReg.hs | 5 ++ compiler/utils/Platform.hs | 1 + includes/stg/HaskellMachRegs.h | 1 + includes/stg/MachRegs.h | 57 ++++++++++++++++- rts/StgCRun.c | 66 ++++++++++++++++++++ 10 files changed, 142 insertions(+), 1 deletion(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c29bf984dd20431cd4344e8a5c444d7a5be08389 From git at git.haskell.org Tue Apr 22 04:40:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 04:40:29 +0000 (UTC) Subject: [commit: ghc] master: Be less untruthful about the prototypes of external functions (5a31f23) Message-ID: <20140422044030.322F22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5a31f231eebfb8140f9b519b166094d9d4fc2d79/ghc >--------------------------------------------------------------- commit 5a31f231eebfb8140f9b519b166094d9d4fc2d79 Author: Colin Watson Date: Sat Apr 12 01:55:07 2014 +0100 Be less untruthful about the prototypes of external functions GHC's generated C code uses dummy prototypes for foreign imports. At the moment these all claim to be (void), i.e. functions of zero arguments. On most platforms this doesn't matter very much: calls to these functions put the parameters in the usual places anyway, and (with the exception of varargs) things just work. However, the ELFv2 ABI on ppc64 optimises stack allocation (http://gcc.gnu.org/ml/gcc-patches/2013-11/msg01149.html): a call to a function that has a prototype, is not varargs, and receives all parameters in registers rather than on the stack does not require the caller to allocate an argument save area. The incorrect prototypes cause GCC to believe that all functions declared this way can be called without an argument save area, but if the callee has sufficiently many arguments then it will expect that area to be present, and will thus corrupt the caller's stack. This happens in particular with calls to runInteractiveProcess in libraries/process/cbits/runProcess.c. The simplest fix appears to be to declare these external functions with an unspecified argument list rather than a void argument list. This is no worse for platforms that don't care either way, and allows a successful bootstrap of GHC 7.8 on little-endian Linux ppc64 (which uses the ELFv2 ABI). Fixes #8965 Signed-off-by: Colin Watson Signed-off-by: Austin Seipp >--------------------------------------------------------------- 5a31f231eebfb8140f9b519b166094d9d4fc2d79 includes/Stg.h | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/includes/Stg.h b/includes/Stg.h index be966aa..1707c9b 100644 --- a/includes/Stg.h +++ b/includes/Stg.h @@ -213,7 +213,7 @@ typedef StgFunPtr F_; #define II_(X) static StgWordArray (X) GNU_ATTRIBUTE(aligned (8)) #define IF_(f) static StgFunPtr GNUC3_ATTRIBUTE(used) f(void) #define FN_(f) StgFunPtr f(void) -#define EF_(f) extern StgFunPtr f(void) +#define EF_(f) extern StgFunPtr f() /* ----------------------------------------------------------------------------- Tail calls From git at git.haskell.org Tue Apr 22 04:40:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 04:40:32 +0000 (UTC) Subject: [commit: ghc] master: Add the powerpc64le architecture (8586f60) Message-ID: <20140422044032.A82D72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8586f600613a6a99fee8fe707b00adab1a340641/ghc >--------------------------------------------------------------- commit 8586f600613a6a99fee8fe707b00adab1a340641 Author: Colin Watson Date: Sat Apr 12 02:13:48 2014 +0100 Add the powerpc64le architecture This is ArchUnknown for now, as it requires some porting work over and above powerpc64 due to such things as the different function calling sequence in the ELFv2 ABI. For now, an unregisterised port is better than nothing. Signed-off-by: Colin Watson Signed-off-by: Austin Seipp >--------------------------------------------------------------- 8586f600613a6a99fee8fe707b00adab1a340641 aclocal.m4 | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/aclocal.m4 b/aclocal.m4 index 0c9a697..f9b574b 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -209,7 +209,7 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS], mipsel) test -z "[$]2" || eval "[$]2=ArchMipsel" ;; - hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sparc64|vax) + hppa|hppa1_1|ia64|m68k|powerpc64le|rs6000|s390|s390x|sparc64|vax) test -z "[$]2" || eval "[$]2=ArchUnknown" ;; *) @@ -1890,6 +1890,9 @@ case "$1" in mips*) $2="mips" ;; + powerpc64le*) + $2="powerpc64le" + ;; powerpc64*) $2="powerpc64" ;; From git at git.haskell.org Tue Apr 22 04:40:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 04:40:35 +0000 (UTC) Subject: [commit: ghc] master: Separate thousands when printing allocated bytes (9ca17f8) Message-ID: <20140422044035.29F8A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9ca17f8850aeaf1fd2109532338da2ffc0e8be1b/ghc >--------------------------------------------------------------- commit 9ca17f8850aeaf1fd2109532338da2ffc0e8be1b Author: Erlend Hamberg Date: Thu Mar 6 23:27:29 2014 +0100 Separate thousands when printing allocated bytes When printing allocated bytes (`:set +s` in ghci), separate thousands to make it easier to read large allocations sizes, e.g. ?1,200,000 bytes?. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 9ca17f8850aeaf1fd2109532338da2ffc0e8be1b ghc/GhciMonad.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/ghc/GhciMonad.hs b/ghc/GhciMonad.hs index 54e7e0c..a4abe32 100644 --- a/ghc/GhciMonad.hs +++ b/ghc/GhciMonad.hs @@ -316,7 +316,12 @@ printTimes dflags allocs psecs secs_str = showFFloat (Just 2) secs putStrLn (showSDoc dflags ( parens (text (secs_str "") <+> text "secs" <> comma <+> - text (show allocs) <+> text "bytes"))) + text (separateThousands allocs) <+> text "bytes"))) + where + separateThousands n = reverse . sep . reverse . show $ n + where sep n' + | length n' <= 3 = n' + | otherwise = take 3 n' ++ "," ++ sep (drop 3 n') ----------------------------------------------------------------------------- -- reverting CAFs From git at git.haskell.org Tue Apr 22 04:40:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 04:40:37 +0000 (UTC) Subject: [commit: ghc] master: Fix `make help` (4842dde) Message-ID: <20140422044038.255252406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4842dde46b28b2c48fc65003b27403a4ed7acfcd/ghc >--------------------------------------------------------------- commit 4842dde46b28b2c48fc65003b27403a4ed7acfcd Author: Kyle J. Van Berendonck Date: Sat Mar 29 20:59:58 2014 +1100 Fix `make help` Signed-off-by: Austin Seipp >--------------------------------------------------------------- 4842dde46b28b2c48fc65003b27403a4ed7acfcd Makefile | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Makefile b/Makefile index 6872cb3..e5a7fb8 100644 --- a/Makefile +++ b/Makefile @@ -30,10 +30,10 @@ default : all # For help, type 'make help' .PHONY: help -help : +help: @cat MAKEHELP -ifneq "$(findstring clean,$(MAKECMDGOALS))" "" +ifneq "$(filter clean help,$(MAKECMDGOALS))" "" -include mk/config.mk else include mk/config.mk From git at git.haskell.org Tue Apr 22 06:08:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 06:08:51 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Fix #8641, creating directories when we have stubs. (15089e8) Message-ID: <20140422060851.A38C32406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/15089e8729297978ee3c0936953e4dfac59ea274/ghc >--------------------------------------------------------------- commit 15089e8729297978ee3c0936953e4dfac59ea274 Author: Edward Z. Yang Date: Thu Apr 10 18:28:11 2014 -0700 Fix #8641, creating directories when we have stubs. Signed-off-by: Edward Z. Yang (cherry picked from commit c7498bbdaa74dadd976c75c4e303c2050aa78277) >--------------------------------------------------------------- 15089e8729297978ee3c0936953e4dfac59ea274 compiler/main/DriverPipeline.hs | 2 ++ testsuite/tests/driver/B042stub/C.hs | 6 ++++++ testsuite/tests/driver/Makefile | 8 ++++++++ testsuite/tests/driver/all.T | 5 +++++ 4 files changed, 21 insertions(+) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 2c71967..2816c94 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1259,6 +1259,7 @@ runPhase (RealPhase SplitAs) _input_fn dflags osuf = objectSuf dflags split_odir = base_o ++ "_" ++ osuf ++ "_split" + -- this also creates the hierarchy liftIO $ createDirectoryIfMissing True split_odir -- remove M_split/ *.o, because we're going to archive M_split/ *.o @@ -1469,6 +1470,7 @@ runPhase (RealPhase MergeStub) input_fn dflags = do PipeState{maybe_stub_o} <- getPipeState output_fn <- phaseOutputFilename StopLn + liftIO $ createDirectoryIfMissing True (takeDirectory output_fn) case maybe_stub_o of Nothing -> panic "runPhase(MergeStub): no stub" diff --git a/testsuite/tests/driver/B042stub/C.hs b/testsuite/tests/driver/B042stub/C.hs new file mode 100644 index 0000000..73f069c --- /dev/null +++ b/testsuite/tests/driver/B042stub/C.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE ForeignFunctionInterface #-} +module B042stub.C where + +foreign export ccall foo :: IO () +foo :: IO () +foo = return () diff --git a/testsuite/tests/driver/Makefile b/testsuite/tests/driver/Makefile index 7673713..3603bb6 100644 --- a/testsuite/tests/driver/Makefile +++ b/testsuite/tests/driver/Makefile @@ -222,6 +222,14 @@ test042: "$(TEST_HC)" $(TEST_HC_OPTS_NO_RECOMP) -v0 --make B042/C.hs -odir obj042 test -f obj042/B042/C$(OBJSUFFIX) +# test -odir with stubs +test042stub: + $(RM) -rf obj042stub + mkdir obj042stub + $(RM) B042stub/C.hi + "$(TEST_HC)" $(TEST_HC_OPTS_NO_RECOMP) -v0 --make B042stub/C.hs -odir obj042stub + test -f obj042stub/B042stub/C$(OBJSUFFIX) + # test -hidir test043: $(RM) -f B043/C$(OBJSUFFIX) diff --git a/testsuite/tests/driver/all.T b/testsuite/tests/driver/all.T index aa4bc9b..ed0ce0f 100644 --- a/testsuite/tests/driver/all.T +++ b/testsuite/tests/driver/all.T @@ -142,6 +142,11 @@ test('driver042', run_command, ['$MAKE -s --no-print-directory test042']) +test('driver042stub', + extra_clean(['B042stub/C.hi', 'obj042stub/B042stub/C.o', 'obj042stub/B042stub/', 'obj042stub/']), + run_command, + ['$MAKE -s --no-print-directory test042stub']) + test('driver043', extra_clean(['B043/C.hi', 'B043/C.o', 'hi043/B043/C.hi', 'hi043/B043', 'hi043']), From git at git.haskell.org Tue Apr 22 06:08:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 06:08:55 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Small issue with signatures in a TH splice (fixes Trac #8932) (e2e6d12) Message-ID: <20140422060855.B50F02406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/e2e6d122e1c7f6cdcf2483379bfa7c5acb1022a1/ghc >--------------------------------------------------------------- commit e2e6d122e1c7f6cdcf2483379bfa7c5acb1022a1 Author: Simon Peyton Jones Date: Mon Apr 7 15:22:11 2014 +0100 Small issue with signatures in a TH splice (fixes Trac #8932) (cherry picked from commit d8d798b1b33ab0593ed03f193360b8725ba2c2ba) Conflicts: testsuite/tests/th/all.T >--------------------------------------------------------------- e2e6d122e1c7f6cdcf2483379bfa7c5acb1022a1 compiler/rename/RnEnv.lhs | 12 ++++++++++-- testsuite/tests/th/T8932.hs | 12 ++++++++++++ testsuite/tests/th/T8932.stderr | 5 +++++ testsuite/tests/th/all.T | 1 + 4 files changed, 28 insertions(+), 2 deletions(-) diff --git a/compiler/rename/RnEnv.lhs b/compiler/rename/RnEnv.lhs index 150b8ce..cfd1f48 100644 --- a/compiler/rename/RnEnv.lhs +++ b/compiler/rename/RnEnv.lhs @@ -270,8 +270,16 @@ lookupExactOcc name ; return name } - [gre] -> return (gre_name gre) - _ -> pprPanic "lookupExactOcc" (ppr name $$ ppr gres) } + (gre:_) -> return (gre_name gre) } + -- We can get more than one GRE here, if there are multiple + -- bindings for the same name; but there will already be a + -- reported error for the duplicate. (If we add the error + -- rather than stopping when we encounter it.) + -- So all we need do here is not crash. + -- Example is Trac #8932: + -- $( [d| foo :: a->a; foo x = x |]) + -- foo = True + -- Here the 'foo' in the splice turns into an Exact Name where exact_nm_err = hang (ptext (sLit "The exact Name") <+> quotes (ppr name) <+> ptext (sLit "is not in scope")) diff --git a/testsuite/tests/th/T8932.hs b/testsuite/tests/th/T8932.hs new file mode 100644 index 0000000..05630f3 --- /dev/null +++ b/testsuite/tests/th/T8932.hs @@ -0,0 +1,12 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T8932 where + +$([d| + foo :: a -> a + foo x = x + |]) + +foo :: a +foo = undefined + diff --git a/testsuite/tests/th/T8932.stderr b/testsuite/tests/th/T8932.stderr new file mode 100644 index 0000000..0e0f977 --- /dev/null +++ b/testsuite/tests/th/T8932.stderr @@ -0,0 +1,5 @@ + +T8932.hs:11:1: + Multiple declarations of ?foo? + Declared at: T8932.hs:5:3 + T8932.hs:11:1 diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index c39fc6d..4117cf1 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -320,3 +320,4 @@ test('T8625', normal, ghci_script, ['T8625.script']) test('T8759', normal, compile_fail, ['-v0']) test('T8759a', normal, compile_fail, ['-v0']) test('T8884', normal, compile, ['-v0']) +test('T8932', normal, compile_fail, ['-v0']) From git at git.haskell.org Tue Apr 22 06:08:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 06:08:58 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: ghc: Do not add a space in '-U __PIC__' (930a2ef) Message-ID: <20140422060858.C58822406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/930a2ef1066bad478fe36e4963c35b89b30e58e7/ghc >--------------------------------------------------------------- commit 930a2ef1066bad478fe36e4963c35b89b30e58e7 Author: Austin Seipp Date: Mon Apr 21 07:22:50 2014 -0500 ghc: Do not add a space in '-U __PIC__' GHC previously introduced a space here. However, this can in some cases be interpreted as "-U __PIC__" - note that in shell, the -U would still be recognized with an argument, but the argument would be " __PIC__", with a space in front, as opposed to the single string '__PIC__'. In practice most tools seem to handle this OK. But the Coverity Scan analysis tool does not: it errors on the fact that ' __PIC__' is an invalid CPP name to undefine. With this, it seems the Coverity analysis tool can easily analyze the entire GHC build. Signed-off-by: Austin Seipp (cherry picked from commit 574ef4293b867609f2d28d85747e01f3ac0d052d) >--------------------------------------------------------------- 930a2ef1066bad478fe36e4963c35b89b30e58e7 compiler/main/DynFlags.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 053026b..e744952 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -3523,10 +3523,10 @@ picCCOpts dflags -- Don't generate "common" symbols - these are unwanted -- in dynamic libraries. - | gopt Opt_PIC dflags -> ["-fno-common", "-U __PIC__", "-D__PIC__"] + | gopt Opt_PIC dflags -> ["-fno-common", "-U__PIC__", "-D__PIC__"] | otherwise -> ["-mdynamic-no-pic"] OSMinGW32 -- no -fPIC for Windows - | gopt Opt_PIC dflags -> ["-U __PIC__", "-D__PIC__"] + | gopt Opt_PIC dflags -> ["-U__PIC__", "-D__PIC__"] | otherwise -> [] _ -- we need -fPIC for C files when we are compiling with -dynamic, @@ -3535,12 +3535,12 @@ picCCOpts dflags -- objects, but can't without -fPIC. See -- http://ghc.haskell.org/trac/ghc/wiki/Commentary/PositionIndependentCode | gopt Opt_PIC dflags || not (gopt Opt_Static dflags) -> - ["-fPIC", "-U __PIC__", "-D__PIC__"] + ["-fPIC", "-U__PIC__", "-D__PIC__"] | otherwise -> [] picPOpts :: DynFlags -> [String] picPOpts dflags - | gopt Opt_PIC dflags = ["-U __PIC__", "-D__PIC__"] + | gopt Opt_PIC dflags = ["-U__PIC__", "-D__PIC__"] | otherwise = [] -- ----------------------------------------------------------------------------- From git at git.haskell.org Tue Apr 22 06:09:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 06:09:01 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Be less untruthful about the prototypes of external functions (06979d2) Message-ID: <20140422060901.D173C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/06979d2a437c59a959472e60c53873a575bcdda8/ghc >--------------------------------------------------------------- commit 06979d2a437c59a959472e60c53873a575bcdda8 Author: Colin Watson Date: Sat Apr 12 01:55:07 2014 +0100 Be less untruthful about the prototypes of external functions GHC's generated C code uses dummy prototypes for foreign imports. At the moment these all claim to be (void), i.e. functions of zero arguments. On most platforms this doesn't matter very much: calls to these functions put the parameters in the usual places anyway, and (with the exception of varargs) things just work. However, the ELFv2 ABI on ppc64 optimises stack allocation (http://gcc.gnu.org/ml/gcc-patches/2013-11/msg01149.html): a call to a function that has a prototype, is not varargs, and receives all parameters in registers rather than on the stack does not require the caller to allocate an argument save area. The incorrect prototypes cause GCC to believe that all functions declared this way can be called without an argument save area, but if the callee has sufficiently many arguments then it will expect that area to be present, and will thus corrupt the caller's stack. This happens in particular with calls to runInteractiveProcess in libraries/process/cbits/runProcess.c. The simplest fix appears to be to declare these external functions with an unspecified argument list rather than a void argument list. This is no worse for platforms that don't care either way, and allows a successful bootstrap of GHC 7.8 on little-endian Linux ppc64 (which uses the ELFv2 ABI). Fixes #8965 Signed-off-by: Colin Watson Signed-off-by: Austin Seipp (cherry picked from commit 5a31f231eebfb8140f9b519b166094d9d4fc2d79) >--------------------------------------------------------------- 06979d2a437c59a959472e60c53873a575bcdda8 includes/Stg.h | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/includes/Stg.h b/includes/Stg.h index be966aa..1707c9b 100644 --- a/includes/Stg.h +++ b/includes/Stg.h @@ -213,7 +213,7 @@ typedef StgFunPtr F_; #define II_(X) static StgWordArray (X) GNU_ATTRIBUTE(aligned (8)) #define IF_(f) static StgFunPtr GNUC3_ATTRIBUTE(used) f(void) #define FN_(f) StgFunPtr f(void) -#define EF_(f) extern StgFunPtr f(void) +#define EF_(f) extern StgFunPtr f() /* ----------------------------------------------------------------------------- Tail calls From git at git.haskell.org Tue Apr 22 06:09:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 06:09:04 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Add the powerpc64le architecture (8f71836) Message-ID: <20140422060904.DEC742406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/8f71836581f9abc1d03246193cb4cea4d52e63e9/ghc >--------------------------------------------------------------- commit 8f71836581f9abc1d03246193cb4cea4d52e63e9 Author: Colin Watson Date: Sat Apr 12 02:13:48 2014 +0100 Add the powerpc64le architecture This is ArchUnknown for now, as it requires some porting work over and above powerpc64 due to such things as the different function calling sequence in the ELFv2 ABI. For now, an unregisterised port is better than nothing. Signed-off-by: Colin Watson Signed-off-by: Austin Seipp (cherry picked from commit 8586f600613a6a99fee8fe707b00adab1a340641) >--------------------------------------------------------------- 8f71836581f9abc1d03246193cb4cea4d52e63e9 aclocal.m4 | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/aclocal.m4 b/aclocal.m4 index 7cae3b5..ce1e75e 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -206,7 +206,7 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS], mipsel) test -z "[$]2" || eval "[$]2=ArchMipsel" ;; - hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sparc64|vax) + hppa|hppa1_1|ia64|m68k|powerpc64le|rs6000|s390|s390x|sparc64|vax) test -z "[$]2" || eval "[$]2=ArchUnknown" ;; *) @@ -1884,6 +1884,9 @@ case "$1" in mips*) $2="mips" ;; + powerpc64le*) + $2="powerpc64le" + ;; powerpc64*) $2="powerpc64" ;; From git at git.haskell.org Tue Apr 22 06:09:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 06:09:07 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Kill whitespace after cpp's `-I` flag (5944331) Message-ID: <20140422060908.011AF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/5944331dfcbd703f6a1a249406a2f4476749a6e1/ghc >--------------------------------------------------------------- commit 5944331dfcbd703f6a1a249406a2f4476749a6e1 Author: Herbert Valerio Riedel Date: Mon Apr 21 16:55:11 2014 +0200 Kill whitespace after cpp's `-I` flag This clean-up is in a similiar spirit as 574ef4293b8676. Signed-off-by: Herbert Valerio Riedel (cherry picked from commit 4ab8fc55eb6119dbba2f487c5a01d30a7c6ae113) >--------------------------------------------------------------- 5944331dfcbd703f6a1a249406a2f4476749a6e1 compiler/main/DriverPipeline.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 2816c94..b93cef1 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1045,7 +1045,7 @@ runPhase (RealPhase cc_phase) input_fn dflags -- files; this is the Value Add(TM) that using ghc instead of -- gcc gives you :) pkg_include_dirs <- liftIO $ getPackageIncludePath dflags pkgs - let include_paths = foldr (\ x xs -> "-I" : x : xs) [] + let include_paths = foldr (\ x xs -> ("-I" ++ x) : xs) [] (cmdline_include_paths ++ pkg_include_dirs) let gcc_extra_viac_flags = extraGccViaCFlags dflags From git at git.haskell.org Tue Apr 22 07:08:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 07:08:09 +0000 (UTC) Subject: [commit: nofib] master: Remove nofib/real/HMMS/lib/haskell/Builtin.hi which is presumably there by mistake (4e4d70b) Message-ID: <20140422070809.257812406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4e4d70bb07d80ad5d3c32b88516f7c8efb5e7df8/nofib >--------------------------------------------------------------- commit 4e4d70bb07d80ad5d3c32b88516f7c8efb5e7df8 Author: Simon Peyton Jones Date: Thu Mar 6 13:21:35 2014 +0000 Remove nofib/real/HMMS/lib/haskell/Builtin.hi which is presumably there by mistake >--------------------------------------------------------------- 4e4d70bb07d80ad5d3c32b88516f7c8efb5e7df8 real/HMMS/lib/haskell/Builtin.hi | 3 --- 1 file changed, 3 deletions(-) diff --git a/real/HMMS/lib/haskell/Builtin.hi b/real/HMMS/lib/haskell/Builtin.hi deleted file mode 100644 index 8aff85e..0000000 --- a/real/HMMS/lib/haskell/Builtin.hi +++ /dev/null @@ -1,3 +0,0 @@ - -interface PreludeBuiltin where -unpackLitString# :: LitString# -> [Char] From git at git.haskell.org Tue Apr 22 07:27:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 07:27:15 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Zonk the existential type variables in tcPatSynDecl (7dc927d) Message-ID: <20140422072715.F30D92406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/7dc927d8c3b0bd68cdf2186702309e36dc223ec1/ghc >--------------------------------------------------------------- commit 7dc927d8c3b0bd68cdf2186702309e36dc223ec1 Author: Simon Peyton Jones Date: Tue Apr 8 09:42:51 2014 +0100 Zonk the existential type variables in tcPatSynDecl This was just an omission, which showed up as Trac #8966 (cherry picked from commit 4dc9f9869bfc82fdb8bd61864859007873ebcc27) >--------------------------------------------------------------- 7dc927d8c3b0bd68cdf2186702309e36dc223ec1 compiler/typecheck/TcPatSyn.lhs | 30 ++++++++++++------------ testsuite/tests/patsyn/should_compile/T8966.hs | 8 +++++++ testsuite/tests/patsyn/should_compile/all.T | 1 + 3 files changed, 24 insertions(+), 15 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index 94ee199..1464980 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -47,28 +47,28 @@ tcPatSynDecl lname@(L _ name) details lpat dir ; pat_ty <- newFlexiTyVarTy openTypeKind ; let (arg_names, is_infix) = case details of - PrefixPatSyn names -> (map unLoc names, False) + PrefixPatSyn names -> (map unLoc names, False) InfixPatSyn name1 name2 -> (map unLoc [name1, name2], True) - ; ((lpat', args), wanted) <- captureConstraints $ - tcPat PatSyn lpat pat_ty $ mapM tcLookupId arg_names + ; ((lpat', args), wanted) <- captureConstraints $ + tcPat PatSyn lpat pat_ty $ + mapM tcLookupId arg_names ; let named_taus = (name, pat_ty):map (\arg -> (getName arg, varType arg)) args ; traceTc "tcPatSynDecl::wanted" (ppr named_taus $$ ppr wanted) - ; (qtvs, given_dicts, _mr_bites, ev_binds) <- simplifyInfer True False named_taus wanted - ; let req_dicts = given_dicts + ; (qtvs, req_dicts, _mr_bites, ev_binds) <- simplifyInfer True False named_taus wanted ; (ex_vars, prov_dicts) <- tcCollectEx lpat' - ; let univ_tvs = filter (not . (`elemVarSet` ex_vars)) qtvs - ex_tvs = varSetElems ex_vars + ; let univ_tvs = filter (not . (`elemVarSet` ex_vars)) qtvs + ex_tvs = varSetElems ex_vars + prov_theta = map evVarPred prov_dicts + req_theta = map evVarPred req_dicts - ; pat_ty <- zonkTcType pat_ty - ; args <- mapM zonkId args - - ; univ_tvs <- mapM zonkQuantifiedTyVar univ_tvs - ; let prov_theta = map evVarPred prov_dicts - req_theta = map evVarPred req_dicts + ; univ_tvs <- mapM zonkQuantifiedTyVar univ_tvs + ; ex_tvs <- mapM zonkQuantifiedTyVar ex_tvs ; prov_theta <- zonkTcThetaType prov_theta - ; req_theta <- zonkTcThetaType req_theta + ; req_theta <- zonkTcThetaType req_theta + ; pat_ty <- zonkTcType pat_ty + ; args <- mapM zonkId args ; traceTc "tcPatSynDecl: ex" (ppr ex_tvs $$ ppr prov_theta $$ @@ -92,7 +92,7 @@ tcPatSynDecl lname@(L _ name) details lpat dir prov_theta req_theta pat_ty ; m_wrapper <- tcPatSynWrapper lname lpat dir args - univ_tvs ex_tvs theta pat_ty + univ_tvs ex_tvs theta pat_ty ; let binds = matcher_bind `unionBags` maybe emptyBag snd m_wrapper ; traceTc "tcPatSynDecl }" $ ppr name diff --git a/testsuite/tests/patsyn/should_compile/T8966.hs b/testsuite/tests/patsyn/should_compile/T8966.hs new file mode 100644 index 0000000..895ff1b --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T8966.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE PolyKinds, KindSignatures, PatternSynonyms, DataKinds, GADTs #-} + +module T8966 where + +data NQ :: [k] -> * where + D :: NQ '[a] + +pattern Q = D diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index 71b0b71..ecc4701 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -8,3 +8,4 @@ test('ex-num', normal, compile, ['']) test('num', normal, compile, ['']) test('incomplete', normal, compile, ['']) test('export', normal, compile, ['']) +test('T8966', normal, compile, ['']) From git at git.haskell.org Tue Apr 22 07:27:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 07:27:18 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Simplify and tidy up the handling of tuple names (6e207de) Message-ID: <20140422072718.C4D212406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/6e207dead24fc783f78ae7c786150cb9e7cd7022/ghc >--------------------------------------------------------------- commit 6e207dead24fc783f78ae7c786150cb9e7cd7022 Author: Simon Peyton Jones Date: Fri Apr 4 08:41:35 2014 +0100 Simplify and tidy up the handling of tuple names This fixes Trac #8954. There were actually three places where tuple occ-names were parsed: - IfaceEnv.lookupOrigNameCache - Convert.isBuiltInOcc - OccName.isTupleOcc_maybe I combined all three into TysWiredIn.isBuiltInOcc_maybe Much nicer. (cherry picked from commit 750271e61bdbaad50c19176406512e79abe404a8) Conflicts: testsuite/tests/th/all.T >--------------------------------------------------------------- 6e207dead24fc783f78ae7c786150cb9e7cd7022 compiler/basicTypes/OccName.lhs | 53 --------------------- compiler/hsSyn/Convert.lhs | 25 ++-------- compiler/iface/IfaceEnv.lhs | 40 +++++++++------- compiler/prelude/PrelNames.lhs | 97 ++++++++++++++++++++++----------------- compiler/prelude/TysWiredIn.lhs | 70 ++++++++++++++++++++++++++-- testsuite/tests/th/T8954.hs | 15 ++++++ testsuite/tests/th/all.T | 1 + 7 files changed, 166 insertions(+), 135 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6e207dead24fc783f78ae7c786150cb9e7cd7022 From git at git.haskell.org Tue Apr 22 07:27:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 07:27:21 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Honour the untouchability of kind variables (eefd614) Message-ID: <20140422072721.229462406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/eefd614ae7ebe49bcf3df0d7ab1144a40e647bdf/ghc >--------------------------------------------------------------- commit eefd614ae7ebe49bcf3df0d7ab1144a40e647bdf Author: Simon Peyton Jones Date: Mon Apr 14 13:03:40 2014 +0100 Honour the untouchability of kind variables Trac #8985 showed up a major shortcoming in the kind unifier: it was ignoring untoucability. This has unpredictably-bad consequences; notably, the skolem-escape check can fail. There were two things wrong * TcRnMonad.isTouchableTcM was returning a constant value for kind variables (wrong), and even worse the constant was back-to-front (it was always False). * We weren't even calling isTouchableTcM in TcType.unifyKindX. I'm not sure how this ever worked. Merge to 7.8.3 in due course. (cherry picked from commit e7f0ae7ff4f2199abe42f20bac825a7802bff466) >--------------------------------------------------------------- eefd614ae7ebe49bcf3df0d7ab1144a40e647bdf compiler/typecheck/TcRnMonad.lhs | 5 -- compiler/typecheck/TcUnify.lhs | 138 +++++++++++++++++++++++--------------- 2 files changed, 84 insertions(+), 59 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc eefd614ae7ebe49bcf3df0d7ab1144a40e647bdf From git at git.haskell.org Tue Apr 22 07:27:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 07:27:23 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Test Trac #8985 (1e0dddd) Message-ID: <20140422072723.C4A0D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/1e0dddd7c96d1e7b89e6ac05bd0bfcc617e834ac/ghc >--------------------------------------------------------------- commit 1e0dddd7c96d1e7b89e6ac05bd0bfcc617e834ac Author: Simon Peyton Jones Date: Mon Apr 14 13:06:22 2014 +0100 Test Trac #8985 (cherry picked from commit ff9f9a7f2e227fcda7b8a2f52ec8be66de2e76cd) >--------------------------------------------------------------- 1e0dddd7c96d1e7b89e6ac05bd0bfcc617e834ac testsuite/tests/polykinds/T8985.hs | 16 ++++++++++++++++ testsuite/tests/polykinds/all.T | 1 + 2 files changed, 17 insertions(+) diff --git a/testsuite/tests/polykinds/T8985.hs b/testsuite/tests/polykinds/T8985.hs new file mode 100644 index 0000000..28a354b --- /dev/null +++ b/testsuite/tests/polykinds/T8985.hs @@ -0,0 +1,16 @@ +{-# LANGUAGE DataKinds, PolyKinds, TypeFamilies, GADTs, TypeOperators #-} + +module T8905 where + +data X (xs :: [k]) = MkX +data Y :: (k -> *) -> [k] -> * where + MkY :: f x -> Y f (x ': xs) + +type family F (a :: [[*]]) :: * +type instance F xss = Y X xss + +works :: Y X '[ '[ ] ] -> () +works (MkY MkX) = () + +fails :: F '[ '[ ] ] -> () +fails (MkY MkX) = () diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T index 8dc1181..3634d83 100644 --- a/testsuite/tests/polykinds/all.T +++ b/testsuite/tests/polykinds/all.T @@ -99,3 +99,4 @@ test('T8616', normal, compile_fail,['']) test('T8566a', expect_broken(8566), compile,['']) test('T7481', normal, compile_fail,['']) test('T8705', normal, compile, ['']) +test('T8985', normal, compile, ['']) From git at git.haskell.org Tue Apr 22 07:55:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 07:55:28 +0000 (UTC) Subject: [commit: ghc] master: Adapt .gitignore (re #8545) (bb85759) Message-ID: <20140422075528.CE4362406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bb857596d1f09260908a0dd4f05cc25c2e822c4c/ghc >--------------------------------------------------------------- commit bb857596d1f09260908a0dd4f05cc25c2e822c4c Author: Herbert Valerio Riedel Date: Tue Apr 22 09:54:09 2014 +0200 Adapt .gitignore (re #8545) This adapts the top-level .gitignore file to match the new situation of base.git, ghc-prim.git, integer-gmp.git, integer-simple.git, and template-haskell.git being folded into ghc.git Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- bb857596d1f09260908a0dd4f05cc25c2e822c4c .gitignore | 5 ----- 1 file changed, 5 deletions(-) diff --git a/.gitignore b/.gitignore index e60382b..93fb881 100644 --- a/.gitignore +++ b/.gitignore @@ -48,26 +48,21 @@ _darcs/ /ghc-tarballs/ /libffi-tarballs/ /libraries/array/ -/libraries/base/ /libraries/deepseq/ /libraries/directory/ /libraries/dph/ /libraries/extensible-exceptions/ /libraries/filepath/ -/libraries/ghc-prim/ /libraries/haskell2010/ /libraries/haskell98/ /libraries/hoopl/ /libraries/hpc/ -/libraries/integer-gmp/ -/libraries/integer-simple/ /libraries/mtl/ /libraries/old-locale/ /libraries/old-time/ /libraries/parallel/ /libraries/process/ /libraries/stm/ -/libraries/template-haskell/ /libraries/unix/ /libraries/utf8-string/ /nofib/ From git at git.haskell.org Tue Apr 22 09:00:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 09:00:29 +0000 (UTC) Subject: [commit: haddock] branch 'orf' created Message-ID: <20140422090029.C7DD92406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock New branch : orf Referencing: 95ea70a1cd2f38dc5a8d0de6e30d6e4f77dff118 From git at git.haskell.org Tue Apr 22 09:00:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 09:00:31 +0000 (UTC) Subject: [commit: haddock] orf: Support for OverloadedRecordFields (95ea70a) Message-ID: <20140422090031.DF8AF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : orf Link : http://git.haskell.org/haddock.git/commitdiff/95ea70a1cd2f38dc5a8d0de6e30d6e4f77dff118 >--------------------------------------------------------------- commit 95ea70a1cd2f38dc5a8d0de6e30d6e4f77dff118 Author: Austin Seipp Date: Tue Apr 22 02:15:53 2014 -0500 Support for OverloadedRecordFields Signed-off-by: Austin Seipp >--------------------------------------------------------------- 95ea70a1cd2f38dc5a8d0de6e30d6e4f77dff118 .../ref/{Bug6.html => OverloadedRecordFields.html} | 258 ++++++++------------ html-test/src/OverloadedRecordFields.hs | 26 ++ src/Haddock/Backends/Hoogle.hs | 2 +- src/Haddock/Backends/LaTeX.hs | 37 ++- src/Haddock/Backends/Xhtml.hs | 3 +- src/Haddock/Backends/Xhtml/Decl.hs | 21 +- src/Haddock/Backends/Xhtml/Names.hs | 9 +- src/Haddock/Convert.hs | 6 +- src/Haddock/Interface/Create.hs | 24 +- src/Haddock/Interface/LexParseRn.hs | 45 ++-- src/Haddock/Interface/Rename.hs | 9 +- src/Haddock/InterfaceFile.hs | 6 +- src/Haddock/Types.hs | 14 ++ src/Haddock/Utils.hs | 4 +- 14 files changed, 244 insertions(+), 220 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 95ea70a1cd2f38dc5a8d0de6e30d6e4f77dff118 From git at git.haskell.org Tue Apr 22 09:02:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 09:02:32 +0000 (UTC) Subject: [commit: ghc] branch 'orf' created Message-ID: <20140422090232.8E9C12406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : orf Referencing: 138438dc238054db718162a136ca53722ae904b7 From git at git.haskell.org Tue Apr 22 09:02:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 09:02:36 +0000 (UTC) Subject: [commit: ghc] orf: ghc: implement OverloadedRecordFields (138438d) Message-ID: <20140422090236.7E28B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : orf Link : http://ghc.haskell.org/trac/ghc/changeset/138438dc238054db718162a136ca53722ae904b7/ghc >--------------------------------------------------------------- commit 138438dc238054db718162a136ca53722ae904b7 Author: Adam Gundry Date: Tue Apr 22 02:12:03 2014 -0500 ghc: implement OverloadedRecordFields This fully implements the new ORF extension, developed during the Google Summer of Code 2013, and as described on the wiki: https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields This also updates the Haddock submodule. Reviewed-by: Simon Peyton Jones Signed-off-by: Austin Seipp >--------------------------------------------------------------- 138438dc238054db718162a136ca53722ae904b7 compiler/basicTypes/Avail.hs | 149 ++++++- compiler/basicTypes/DataCon.lhs | 21 +- compiler/basicTypes/DataCon.lhs-boot | 2 + compiler/basicTypes/FieldLabel.lhs | 128 ++++++ compiler/basicTypes/Id.lhs | 12 +- compiler/basicTypes/MkId.lhs | 2 +- compiler/basicTypes/OccName.lhs | 8 + compiler/basicTypes/RdrName.lhs | 123 +++-- compiler/deSugar/Check.lhs | 4 +- compiler/deSugar/Coverage.lhs | 4 +- compiler/deSugar/Desugar.lhs | 2 + compiler/deSugar/DsExpr.lhs | 18 +- compiler/deSugar/DsMeta.hs | 4 +- compiler/deSugar/DsMonad.lhs | 1 + compiler/deSugar/MatchCon.lhs | 6 +- compiler/ghc.cabal.in | 3 + compiler/ghc.mk | 7 + compiler/hsSyn/Convert.lhs | 23 +- compiler/hsSyn/HsDecls.lhs | 6 + compiler/hsSyn/HsExpr.lhs | 5 +- compiler/hsSyn/HsImpExp.lhs | 33 +- compiler/hsSyn/HsPat.lhs | 39 +- compiler/hsSyn/HsTypes.lhs | 51 ++- compiler/hsSyn/HsUtils.lhs | 80 ++-- compiler/iface/BuildTyCl.lhs | 2 +- compiler/iface/IfaceSyn.lhs | 52 +-- compiler/iface/LoadIface.lhs | 19 +- compiler/iface/MkIface.lhs | 27 +- compiler/iface/TcIface.lhs | 36 +- compiler/main/DynFlags.hs | 9 + compiler/main/GHC.hs | 19 +- compiler/main/HscMain.hs | 16 +- compiler/main/HscTypes.lhs | 27 +- compiler/main/InteractiveEval.hs | 2 +- compiler/main/PprTyThing.hs | 12 +- compiler/main/TidyPgm.lhs | 12 +- compiler/parser/Parser.y.pp | 6 +- compiler/parser/RdrHsSyn.lhs | 6 +- compiler/prelude/PrelInfo.lhs | 2 +- compiler/prelude/PrelNames.lhs | 43 +- compiler/prelude/TysWiredIn.lhs | 2 +- compiler/rename/RnEnv.lhs | 321 ++++++++++--- compiler/rename/RnExpr.lhs | 20 +- compiler/rename/RnNames.lhs | 470 +++++++++++++++----- compiler/rename/RnPat.lhs | 75 ++-- compiler/rename/RnSource.lhs | 90 ++-- compiler/rename/RnTypes.lhs | 53 ++- compiler/typecheck/FamInst.lhs | 53 ++- compiler/typecheck/Inst.lhs | 3 +- compiler/typecheck/TcEnv.lhs | 57 +-- compiler/typecheck/TcErrors.lhs | 54 ++- compiler/typecheck/TcEvidence.lhs | 1 + compiler/typecheck/TcExpr.lhs | 320 ++++++++++--- compiler/typecheck/TcFldInsts.lhs | 468 +++++++++++++++++++ compiler/typecheck/TcGenDeriv.lhs | 11 +- compiler/typecheck/TcGenGenerics.lhs | 16 +- compiler/typecheck/TcHsSyn.lhs | 4 +- compiler/typecheck/TcHsType.lhs | 16 +- compiler/typecheck/TcInstDcls.lhs | 4 +- compiler/typecheck/TcInteract.lhs | 65 ++- compiler/typecheck/TcPat.lhs | 24 +- compiler/typecheck/TcRnDriver.lhs | 25 +- compiler/typecheck/TcRnMonad.lhs | 5 +- compiler/typecheck/TcRnTypes.lhs | 31 +- compiler/typecheck/TcSMonad.lhs | 18 +- compiler/typecheck/TcSplice.lhs | 2 +- compiler/typecheck/TcTyClsDecls.lhs | 79 ++-- compiler/typecheck/TcType.lhs | 9 + compiler/typecheck/TcValidity.lhs | 19 +- compiler/types/TyCon.lhs | 54 ++- compiler/types/Type.lhs | 29 +- compiler/types/Type.lhs-boot | 2 + compiler/types/TypeRep.lhs | 43 +- compiler/utils/Binary.hs | 1 - compiler/utils/FastStringEnv.lhs | 77 ++++ docs/users_guide/glasgow_exts.xml | 307 +++++++++++++ libraries/base/GHC/Base.lhs | 3 + libraries/base/GHC/TypeLits.hs | 8 +- libraries/base/base.cabal | 1 + testsuite/tests/driver/T4437.hs | 1 + testsuite/tests/ghci/scripts/ghci042.stdout | 2 +- testsuite/tests/module/mod176.stderr | 2 +- .../{annotations => overloadedrecflds}/Makefile | 0 .../ghci}/Makefile | 0 testsuite/tests/overloadedrecflds/ghci/all.T | 3 + .../ghci/overloadedrecfldsghci01.script | 13 + .../ghci/overloadedrecfldsghci01.stdout | 11 + .../should_fail}/Makefile | 0 .../should_fail/OverloadedRecFldsFail04_A.hs | 9 + .../should_fail/OverloadedRecFldsFail06_A.hs | 16 + .../should_fail/OverloadedRecFldsFail08_A.hs | 14 + .../tests/overloadedrecflds/should_fail/all.T | 16 + .../should_fail/overloadedrecfldsfail01.hs | 17 + .../should_fail/overloadedrecfldsfail01.stderr | 16 + .../should_fail/overloadedrecfldsfail02.hs | 19 + .../should_fail/overloadedrecfldsfail02.stderr | 50 +++ .../should_fail/overloadedrecfldsfail03.hs | 7 + .../should_fail/overloadedrecfldsfail03.stderr | 5 + .../should_fail/overloadedrecfldsfail04.hs | 9 + .../should_fail/overloadedrecfldsfail04.stderr | 5 + .../should_fail/overloadedrecfldsfail05.hs | 10 + .../should_fail/overloadedrecfldsfail05.stderr | 10 + .../should_fail/overloadedrecfldsfail06.hs | 10 + .../should_fail/overloadedrecfldsfail06.stderr | 15 + .../should_fail/overloadedrecfldsfail07.hs | 11 + .../should_fail/overloadedrecfldsfail07.stderr | 6 + .../should_fail/overloadedrecfldsfail08.hs | 13 + .../should_fail/overloadedrecfldsfail08.stderr | 47 ++ .../should_fail/overloadedrecfldsfail09.hs | 9 + .../should_fail/overloadedrecfldsfail09.stderr | 20 + .../should_fail/overloadedrecfldsfail10.hs | 11 + .../should_fail/overloadedrecfldsfail10.stderr | 9 + .../should_run}/Makefile | 0 .../should_run/OverloadedRecFldsRun01_A.hs | 9 + .../should_run/OverloadedRecFldsRun02_A.hs | 9 + .../should_run/OverloadedRecFldsRun07_A.hs | 11 + .../should_run/OverloadedRecFldsRun07_B.hs | 7 + .../should_run/OverloadedRecFldsRun08_A.hs | 11 + .../should_run/OverloadedRecFldsRun08_B.hs | 7 + .../should_run/OverloadedRecFldsRun08_C.hs | 7 + .../should_run/OverloadedRecFldsRun11_A.hs | 9 + .../should_run/OverloadedRecFldsRun11_A.hs-boot | 5 + .../should_run/OverloadedRecFldsRun11_B.hs | 7 + .../should_run/OverloadedRecFldsRun12_A.hs | 11 + .../should_run/OverloadedRecFldsRun12_B.hs | 7 + testsuite/tests/overloadedrecflds/should_run/all.T | 26 ++ .../should_run/overloadedrecfldsrun01.hs | 70 +++ .../should_run/overloadedrecfldsrun01.stdout | 13 + .../should_run/overloadedrecfldsrun02.hs | 6 + .../should_run/overloadedrecfldsrun02.stdout | 0 .../should_run/overloadedrecfldsrun03.hs | 18 + .../should_run/overloadedrecfldsrun03.stdout | 4 + .../should_run/overloadedrecfldsrun04.hs | 18 + .../should_run/overloadedrecfldsrun04.stdout | 3 + .../should_run/overloadedrecfldsrun05.hs | 34 ++ .../should_run/overloadedrecfldsrun05.stdout | 2 + .../should_run/overloadedrecfldsrun06.hs | 28 ++ .../should_run/overloadedrecfldsrun06.stdout | 1 + .../should_run/overloadedrecfldsrun07.hs | 7 + .../should_run/overloadedrecfldsrun07.stdout} | 0 .../should_run/overloadedrecfldsrun08.hs | 7 + .../should_run/overloadedrecfldsrun08.stdout | 2 + .../should_run/overloadedrecfldsrun09.hs | 8 + .../should_run/overloadedrecfldsrun09.stdout | 2 + .../should_run/overloadedrecfldsrun10.hs | 12 + .../should_run/overloadedrecfldsrun10.stderr | 2 + .../should_run/overloadedrecfldsrun11.hs | 5 + .../should_run/overloadedrecfldsrun11.stdout} | 0 .../should_run/overloadedrecfldsrun12.hs | 6 + .../should_run/overloadedrecfldsrun12.stdout | 2 + .../should_run/overloadedrecfldsrun13.hs | 9 + .../should_run/overloadedrecfldsrun13.stdout} | 0 testsuite/tests/rename/should_fail/T5892a.stderr | 2 +- .../tests/typecheck/should_fail/tcfail102.stderr | 3 +- utils/ghctags/Main.hs | 2 +- utils/haddock | 2 +- 156 files changed, 3882 insertions(+), 759 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 138438dc238054db718162a136ca53722ae904b7 From git at git.haskell.org Tue Apr 22 10:04:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 10:04:30 +0000 (UTC) Subject: [commit: ghc] master: Update integer-gmp's .gitignore file (c6a31d2) Message-ID: <20140422100432.07EA02406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c6a31d2d53f45ce0432296196340d0400d921eb7/ghc >--------------------------------------------------------------- commit c6a31d2d53f45ce0432296196340d0400d921eb7 Author: Herbert Valerio Riedel Date: Tue Apr 22 10:21:13 2014 +0200 Update integer-gmp's .gitignore file Note: the .gitignore pattern rules are not that obvious Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- c6a31d2d53f45ce0432296196340d0400d921eb7 libraries/integer-gmp/.gitignore | 25 +++++++++++++------------ 1 file changed, 13 insertions(+), 12 deletions(-) diff --git a/libraries/integer-gmp/.gitignore b/libraries/integer-gmp/.gitignore index 48e9d5e..295f5b2 100644 --- a/libraries/integer-gmp/.gitignore +++ b/libraries/integer-gmp/.gitignore @@ -1,12 +1,13 @@ -GNUmakefile -autom4te.cache/ -config.log -config.status -configure -dist-install/ -^/ghc.mk -gmp/config.mk -integer-gmp.buildinfo -cbits/GmpDerivedConstants.h -cbits/mkGmpDerivedConstants -include/HsIntegerGmp.h +/autom4te.cache/ +/cbits/GmpDerivedConstants.h +/cbits/mkGmpDerivedConstants +/config.log +/config.status +/configure +/dist-install/ +/ghc.mk +/gmp/config.mk +/GNUmakefile +/include/HsIntegerGmp.h +/integer-gmp.buildinfo +/mkGmpDerivedConstants/dist/ From git at git.haskell.org Tue Apr 22 10:04:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 10:04:32 +0000 (UTC) Subject: [commit: ghc] master: Handle base et al. specially in foreachLibrary.mk (33e585d) Message-ID: <20140422100432.EF01C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/33e585d6eacae19e83862a05b650373b536095fa/ghc >--------------------------------------------------------------- commit 33e585d6eacae19e83862a05b650373b536095fa Author: Herbert Valerio Riedel Date: Tue Apr 22 12:01:00 2014 +0200 Handle base et al. specially in foreachLibrary.mk This adapts the foreachLibrary rule to match the new situation of base.git, ghc-prim.git, integer-gmp.git, integer-simple.git, and template-haskell.git being folded into ghc.git (re #9016), and thus not being mentioned anymore in the `packages` file. One visible effect of this oversight was that the `clean_libraries` make target would fail to clean those packages. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 33e585d6eacae19e83862a05b650373b536095fa rules/foreachLibrary.mk | 17 +++++++++++++++-- 1 file changed, 15 insertions(+), 2 deletions(-) diff --git a/rules/foreachLibrary.mk b/rules/foreachLibrary.mk index b2353a0..cdd5496 100644 --- a/rules/foreachLibrary.mk +++ b/rules/foreachLibrary.mk @@ -23,13 +23,26 @@ # We use an FEL_ prefix for the variable names, to avoid trampling on # other variables, as make has no concept of local variables. -# We need to handle bin-package-db specially, as it doesn't have an -# entry in the packages file, as it isn't in its own repository. +# We need to handle the following packages specially, as those don't +# have an entry in the packages file, since they don't live in +# repositories of their own: +# +# - base +# - bin-package-db +# - ghc-prim +# - integer-gmp +# - integer-simple +# - template-haskell define foreachLibrary # $1 = function to call for each library # We will give it the package path and the tag as arguments $$(foreach hashline,libraries/bin-package-db#-#no-remote-repo#no-vcs \ + libraries/base#-#no-remote-repo#no-vcs \ + libraries/ghc-prim#-#no-remote-repo#no-vcs \ + libraries/integer-gmp#-#no-remote-repo#no-vcs \ + libraries/integer-simple#-#no-remote-repo#no-vcs \ + libraries/template-haskell#-#no-remote-repo#no-vcs \ $$(shell grep '^libraries/' packages | sed 's/ */#/g'),\ $$(eval FEL_line := $$(subst #,$$(space),$$(hashline))) \ $$(eval FEL_libdir := $$(word 1,$$(FEL_line))) \ From git at git.haskell.org Tue Apr 22 11:06:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 11:06:52 +0000 (UTC) Subject: [commit: packages/hoopl] master: Don't import Applicative explicitly (a2e34db) Message-ID: <20140422110652.78D602406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hoopl On branch : master Link : http://git.haskell.org/packages/hoopl.git/commitdiff/a2e34db038b737365c4126f69b1a32eae84dae6b >--------------------------------------------------------------- commit a2e34db038b737365c4126f69b1a32eae84dae6b Author: Austin Seipp Date: Tue Apr 22 06:06:13 2014 -0500 Don't import Applicative explicitly In 7.10, this import would be redundant since Applicative is in the Prelude. It's easiest to just make the import whole-sale. Signed-off-by: Austin Seipp >--------------------------------------------------------------- a2e34db038b737365c4126f69b1a32eae84dae6b src/Compiler/Hoopl/Unique.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Compiler/Hoopl/Unique.hs b/src/Compiler/Hoopl/Unique.hs index 8ea85ce..bf3de75 100644 --- a/src/Compiler/Hoopl/Unique.hs +++ b/src/Compiler/Hoopl/Unique.hs @@ -21,7 +21,7 @@ import Compiler.Hoopl.Collections import qualified Data.IntMap as M import qualified Data.IntSet as S -import Control.Applicative (Applicative(..)) +import Control.Applicative import Control.Monad (ap,liftM) ----------------------------------------------------------------------------- From git at git.haskell.org Tue Apr 22 11:10:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 11:10:33 +0000 (UTC) Subject: [commit: ghc] branch 'wip/amp' created Message-ID: <20140422111033.547542406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/amp Referencing: 88c9403264950326e39a05f262bbbb069cf12977 From git at git.haskell.org Tue Apr 22 11:10:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 11:10:35 +0000 (UTC) Subject: [commit: ghc] wip/amp: Make Applicative a superclass of Monad (88c9403) Message-ID: <20140422111035.CB4692406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/amp Link : http://ghc.haskell.org/trac/ghc/changeset/88c9403264950326e39a05f262bbbb069cf12977/ghc >--------------------------------------------------------------- commit 88c9403264950326e39a05f262bbbb069cf12977 Author: Austin Seipp Date: Tue Apr 22 06:09:40 2014 -0500 Make Applicative a superclass of Monad Signed-off-by: Austin Seipp >--------------------------------------------------------------- 88c9403264950326e39a05f262bbbb069cf12977 compiler/utils/Maybes.lhs | 3 + compiler/utils/Stream.hs | 3 + libraries/base/Control/Applicative.hs | 204 +------------------- libraries/base/Control/Arrow.hs | 8 + libraries/base/Control/Monad.hs | 62 ++++-- libraries/base/Control/Monad/ST/Lazy/Imp.hs | 4 + libraries/base/Data/Either.hs | 5 + libraries/base/Data/Maybe.hs | 16 ++ libraries/base/Data/Monoid.hs | 99 +--------- libraries/base/Data/Proxy.hs | 11 ++ libraries/base/GHC/Base.lhs | 203 ++++++++++++++++++- libraries/base/GHC/Conc/Sync.lhs | 12 +- libraries/base/GHC/Event/Array.hs | 2 +- libraries/base/GHC/Event/EPoll.hsc | 1 - libraries/base/GHC/Event/Internal.hs | 1 - libraries/base/GHC/Event/Manager.hs | 1 - libraries/base/GHC/Event/Poll.hsc | 1 - libraries/base/GHC/Event/TimerManager.hs | 1 - libraries/base/GHC/GHCi.hs | 9 +- libraries/base/GHC/ST.lhs | 4 + libraries/base/Prelude.hs | 3 +- libraries/base/Text/ParserCombinators/ReadP.hs | 51 +++-- libraries/base/Text/ParserCombinators/ReadPrec.hs | 11 +- .../template-haskell/Language/Haskell/TH/Syntax.hs | 4 +- 24 files changed, 373 insertions(+), 346 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 88c9403264950326e39a05f262bbbb069cf12977 From git at git.haskell.org Tue Apr 22 11:13:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 11:13:22 +0000 (UTC) Subject: [commit: ghc] branch 'orf' deleted Message-ID: <20140422111323.007772406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: orf From git at git.haskell.org Tue Apr 22 11:14:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 11:14:01 +0000 (UTC) Subject: [commit: haddock] branch 'orf' deleted Message-ID: <20140422111401.A3AEA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock Deleted branch: orf From git at git.haskell.org Tue Apr 22 11:16:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 11:16:27 +0000 (UTC) Subject: [commit: haddock] branch 'wip/orf' created Message-ID: <20140422111628.34A5B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock New branch : wip/orf Referencing: 7fbe75434728c8dfa170d110bfb580bc08477cfa From git at git.haskell.org Tue Apr 22 11:16:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 11:16:30 +0000 (UTC) Subject: [commit: haddock] wip/orf: Implement OverloadedRecordFields extension (7fbe754) Message-ID: <20140422111630.0EEA22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : wip/orf Link : http://git.haskell.org/haddock.git/commitdiff/7fbe75434728c8dfa170d110bfb580bc08477cfa >--------------------------------------------------------------- commit 7fbe75434728c8dfa170d110bfb580bc08477cfa Author: Adam Gundry Date: Fri Apr 18 16:29:33 2014 +0100 Implement OverloadedRecordFields extension See the wiki for more information: https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields Signed-off-by: Austin Seipp >--------------------------------------------------------------- 7fbe75434728c8dfa170d110bfb580bc08477cfa .../ref/{Bug6.html => OverloadedRecordFields.html} | 258 ++++++++------------ html-test/src/OverloadedRecordFields.hs | 26 ++ src/Haddock/Backends/Hoogle.hs | 2 +- src/Haddock/Backends/LaTeX.hs | 37 ++- src/Haddock/Backends/Xhtml.hs | 3 +- src/Haddock/Backends/Xhtml/Decl.hs | 21 +- src/Haddock/Backends/Xhtml/Names.hs | 9 +- src/Haddock/Convert.hs | 6 +- src/Haddock/Interface/Create.hs | 24 +- src/Haddock/Interface/LexParseRn.hs | 45 ++-- src/Haddock/Interface/Rename.hs | 9 +- src/Haddock/InterfaceFile.hs | 8 +- src/Haddock/Types.hs | 14 ++ src/Haddock/Utils.hs | 4 +- 14 files changed, 245 insertions(+), 221 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7fbe75434728c8dfa170d110bfb580bc08477cfa From git at git.haskell.org Tue Apr 22 11:17:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 11:17:19 +0000 (UTC) Subject: [commit: ghc] branch 'wip/orf' created Message-ID: <20140422111719.1D1EA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/orf Referencing: fe77cbf15dd44bb72943357d65bd8adf9f4deee5 From git at git.haskell.org Tue Apr 22 11:17:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 11:17:21 +0000 (UTC) Subject: [commit: ghc] wip/orf: ghc: implement OverloadedRecordFields (fe77cbf) Message-ID: <20140422111722.143EA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf Link : http://ghc.haskell.org/trac/ghc/changeset/fe77cbf15dd44bb72943357d65bd8adf9f4deee5/ghc >--------------------------------------------------------------- commit fe77cbf15dd44bb72943357d65bd8adf9f4deee5 Author: Adam Gundry Date: Tue Apr 22 02:12:03 2014 -0500 ghc: implement OverloadedRecordFields This fully implements the new ORF extension, developed during the Google Summer of Code 2013, and as described on the wiki: https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields This also updates the Haddock submodule. Reviewed-by: Simon Peyton Jones Signed-off-by: Austin Seipp >--------------------------------------------------------------- fe77cbf15dd44bb72943357d65bd8adf9f4deee5 compiler/basicTypes/Avail.hs | 149 ++++++- compiler/basicTypes/DataCon.lhs | 21 +- compiler/basicTypes/DataCon.lhs-boot | 2 + compiler/basicTypes/FieldLabel.lhs | 128 ++++++ compiler/basicTypes/Id.lhs | 12 +- compiler/basicTypes/MkId.lhs | 2 +- compiler/basicTypes/OccName.lhs | 8 + compiler/basicTypes/RdrName.lhs | 123 +++-- compiler/deSugar/Check.lhs | 4 +- compiler/deSugar/Coverage.lhs | 4 +- compiler/deSugar/Desugar.lhs | 2 + compiler/deSugar/DsExpr.lhs | 18 +- compiler/deSugar/DsMeta.hs | 4 +- compiler/deSugar/DsMonad.lhs | 1 + compiler/deSugar/MatchCon.lhs | 6 +- compiler/ghc.cabal.in | 3 + compiler/ghc.mk | 7 + compiler/hsSyn/Convert.lhs | 23 +- compiler/hsSyn/HsDecls.lhs | 6 + compiler/hsSyn/HsExpr.lhs | 5 +- compiler/hsSyn/HsImpExp.lhs | 33 +- compiler/hsSyn/HsPat.lhs | 39 +- compiler/hsSyn/HsTypes.lhs | 51 ++- compiler/hsSyn/HsUtils.lhs | 80 ++-- compiler/iface/BuildTyCl.lhs | 2 +- compiler/iface/IfaceSyn.lhs | 52 +-- compiler/iface/LoadIface.lhs | 19 +- compiler/iface/MkIface.lhs | 27 +- compiler/iface/TcIface.lhs | 36 +- compiler/main/DynFlags.hs | 9 + compiler/main/GHC.hs | 19 +- compiler/main/HscMain.hs | 16 +- compiler/main/HscTypes.lhs | 27 +- compiler/main/InteractiveEval.hs | 2 +- compiler/main/PprTyThing.hs | 12 +- compiler/main/TidyPgm.lhs | 12 +- compiler/parser/Parser.y.pp | 6 +- compiler/parser/RdrHsSyn.lhs | 6 +- compiler/prelude/PrelInfo.lhs | 2 +- compiler/prelude/PrelNames.lhs | 43 +- compiler/prelude/TysWiredIn.lhs | 2 +- compiler/rename/RnEnv.lhs | 321 ++++++++++--- compiler/rename/RnExpr.lhs | 20 +- compiler/rename/RnNames.lhs | 470 +++++++++++++++----- compiler/rename/RnPat.lhs | 75 ++-- compiler/rename/RnSource.lhs | 90 ++-- compiler/rename/RnTypes.lhs | 53 ++- compiler/typecheck/FamInst.lhs | 53 ++- compiler/typecheck/Inst.lhs | 3 +- compiler/typecheck/TcEnv.lhs | 57 +-- compiler/typecheck/TcErrors.lhs | 54 ++- compiler/typecheck/TcEvidence.lhs | 1 + compiler/typecheck/TcExpr.lhs | 320 ++++++++++--- compiler/typecheck/TcFldInsts.lhs | 468 +++++++++++++++++++ compiler/typecheck/TcGenDeriv.lhs | 11 +- compiler/typecheck/TcGenGenerics.lhs | 16 +- compiler/typecheck/TcHsSyn.lhs | 4 +- compiler/typecheck/TcHsType.lhs | 16 +- compiler/typecheck/TcInstDcls.lhs | 4 +- compiler/typecheck/TcInteract.lhs | 65 ++- compiler/typecheck/TcPat.lhs | 24 +- compiler/typecheck/TcRnDriver.lhs | 25 +- compiler/typecheck/TcRnMonad.lhs | 5 +- compiler/typecheck/TcRnTypes.lhs | 31 +- compiler/typecheck/TcSMonad.lhs | 18 +- compiler/typecheck/TcSplice.lhs | 2 +- compiler/typecheck/TcTyClsDecls.lhs | 79 ++-- compiler/typecheck/TcType.lhs | 9 + compiler/typecheck/TcValidity.lhs | 19 +- compiler/types/TyCon.lhs | 54 ++- compiler/types/Type.lhs | 29 +- compiler/types/Type.lhs-boot | 2 + compiler/types/TypeRep.lhs | 43 +- compiler/utils/Binary.hs | 1 - compiler/utils/FastStringEnv.lhs | 77 ++++ docs/users_guide/glasgow_exts.xml | 307 +++++++++++++ libraries/base/GHC/Base.lhs | 3 + libraries/base/GHC/Records.hs | 249 +++++++++++ libraries/base/GHC/TypeLits.hs | 8 +- libraries/base/base.cabal | 1 + testsuite/tests/driver/T4437.hs | 1 + testsuite/tests/ghci/scripts/ghci042.stdout | 2 +- testsuite/tests/module/mod176.stderr | 2 +- .../{annotations => overloadedrecflds}/Makefile | 0 .../ghci}/Makefile | 0 testsuite/tests/overloadedrecflds/ghci/all.T | 3 + .../ghci/overloadedrecfldsghci01.script | 13 + .../ghci/overloadedrecfldsghci01.stdout | 11 + .../should_fail}/Makefile | 0 .../should_fail/OverloadedRecFldsFail04_A.hs | 9 + .../should_fail/OverloadedRecFldsFail06_A.hs | 16 + .../should_fail/OverloadedRecFldsFail08_A.hs | 14 + .../tests/overloadedrecflds/should_fail/all.T | 16 + .../should_fail/overloadedrecfldsfail01.hs | 17 + .../should_fail/overloadedrecfldsfail01.stderr | 16 + .../should_fail/overloadedrecfldsfail02.hs | 19 + .../should_fail/overloadedrecfldsfail02.stderr | 50 +++ .../should_fail/overloadedrecfldsfail03.hs | 7 + .../should_fail/overloadedrecfldsfail03.stderr | 5 + .../should_fail/overloadedrecfldsfail04.hs | 9 + .../should_fail/overloadedrecfldsfail04.stderr | 5 + .../should_fail/overloadedrecfldsfail05.hs | 10 + .../should_fail/overloadedrecfldsfail05.stderr | 10 + .../should_fail/overloadedrecfldsfail06.hs | 10 + .../should_fail/overloadedrecfldsfail06.stderr | 15 + .../should_fail/overloadedrecfldsfail07.hs | 11 + .../should_fail/overloadedrecfldsfail07.stderr | 6 + .../should_fail/overloadedrecfldsfail08.hs | 13 + .../should_fail/overloadedrecfldsfail08.stderr | 47 ++ .../should_fail/overloadedrecfldsfail09.hs | 9 + .../should_fail/overloadedrecfldsfail09.stderr | 20 + .../should_fail/overloadedrecfldsfail10.hs | 11 + .../should_fail/overloadedrecfldsfail10.stderr | 9 + .../should_run}/Makefile | 0 .../should_run/OverloadedRecFldsRun01_A.hs | 9 + .../should_run/OverloadedRecFldsRun02_A.hs | 9 + .../should_run/OverloadedRecFldsRun07_A.hs | 11 + .../should_run/OverloadedRecFldsRun07_B.hs | 7 + .../should_run/OverloadedRecFldsRun08_A.hs | 11 + .../should_run/OverloadedRecFldsRun08_B.hs | 7 + .../should_run/OverloadedRecFldsRun08_C.hs | 7 + .../should_run/OverloadedRecFldsRun11_A.hs | 9 + .../should_run/OverloadedRecFldsRun11_A.hs-boot | 5 + .../should_run/OverloadedRecFldsRun11_B.hs | 7 + .../should_run/OverloadedRecFldsRun12_A.hs | 11 + .../should_run/OverloadedRecFldsRun12_B.hs | 7 + testsuite/tests/overloadedrecflds/should_run/all.T | 26 ++ .../should_run/overloadedrecfldsrun01.hs | 70 +++ .../should_run/overloadedrecfldsrun01.stdout | 13 + .../should_run/overloadedrecfldsrun02.hs | 6 + .../should_run/overloadedrecfldsrun02.stdout | 0 .../should_run/overloadedrecfldsrun03.hs | 18 + .../should_run/overloadedrecfldsrun03.stdout | 4 + .../should_run/overloadedrecfldsrun04.hs | 18 + .../should_run/overloadedrecfldsrun04.stdout | 3 + .../should_run/overloadedrecfldsrun05.hs | 34 ++ .../should_run/overloadedrecfldsrun05.stdout | 2 + .../should_run/overloadedrecfldsrun06.hs | 28 ++ .../should_run/overloadedrecfldsrun06.stdout | 1 + .../should_run/overloadedrecfldsrun07.hs | 7 + .../should_run/overloadedrecfldsrun07.stdout} | 0 .../should_run/overloadedrecfldsrun08.hs | 7 + .../should_run/overloadedrecfldsrun08.stdout | 2 + .../should_run/overloadedrecfldsrun09.hs | 8 + .../should_run/overloadedrecfldsrun09.stdout | 2 + .../should_run/overloadedrecfldsrun10.hs | 12 + .../should_run/overloadedrecfldsrun10.stderr | 2 + .../should_run/overloadedrecfldsrun11.hs | 5 + .../should_run/overloadedrecfldsrun11.stdout} | 0 .../should_run/overloadedrecfldsrun12.hs | 6 + .../should_run/overloadedrecfldsrun12.stdout | 2 + .../should_run/overloadedrecfldsrun13.hs | 9 + .../should_run/overloadedrecfldsrun13.stdout} | 0 testsuite/tests/rename/should_fail/T5892a.stderr | 2 +- .../tests/typecheck/should_fail/tcfail102.stderr | 3 +- utils/ghctags/Main.hs | 2 +- utils/haddock | 2 +- 157 files changed, 4131 insertions(+), 759 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fe77cbf15dd44bb72943357d65bd8adf9f4deee5 From chris at chrisdornan.com Tue Apr 22 13:22:48 2014 From: chris at chrisdornan.com (Chris Dornan) Date: Tue, 22 Apr 2014 14:22:48 +0100 Subject: [commit: ghc] wip/orf: ghc: implement OverloadedRecordFields (fe77cbf) In-Reply-To: <20140422111722.143EA2406B@ghc.haskell.org> References: <20140422111722.143EA2406B@ghc.haskell.org> Message-ID: Marvellous On 22/04/2014 12:17, "git at git.haskell.org" wrote: >Repository : ssh://git at git.haskell.org/ghc > >On branch : wip/orf >Link : >http://ghc.haskell.org/trac/ghc/changeset/fe77cbf15dd44bb72943357d65bd8adf >9f4deee5/ghc > >>--------------------------------------------------------------- > >commit fe77cbf15dd44bb72943357d65bd8adf9f4deee5 >Author: Adam Gundry >Date: Tue Apr 22 02:12:03 2014 -0500 > > ghc: implement OverloadedRecordFields > > This fully implements the new ORF extension, developed during the >Google > Summer of Code 2013, and as described on the wiki: > > https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields > > This also updates the Haddock submodule. > > Reviewed-by: Simon Peyton Jones > Signed-off-by: Austin Seipp > > >>--------------------------------------------------------------- > >fe77cbf15dd44bb72943357d65bd8adf9f4deee5 > compiler/basicTypes/Avail.hs | 149 ++++++- > compiler/basicTypes/DataCon.lhs | 21 +- > compiler/basicTypes/DataCon.lhs-boot | 2 + > compiler/basicTypes/FieldLabel.lhs | 128 ++++++ > compiler/basicTypes/Id.lhs | 12 +- > compiler/basicTypes/MkId.lhs | 2 +- > compiler/basicTypes/OccName.lhs | 8 + > compiler/basicTypes/RdrName.lhs | 123 +++-- > compiler/deSugar/Check.lhs | 4 +- > compiler/deSugar/Coverage.lhs | 4 +- > compiler/deSugar/Desugar.lhs | 2 + > compiler/deSugar/DsExpr.lhs | 18 +- > compiler/deSugar/DsMeta.hs | 4 +- > compiler/deSugar/DsMonad.lhs | 1 + > compiler/deSugar/MatchCon.lhs | 6 +- > compiler/ghc.cabal.in | 3 + > compiler/ghc.mk | 7 + > compiler/hsSyn/Convert.lhs | 23 +- > compiler/hsSyn/HsDecls.lhs | 6 + > compiler/hsSyn/HsExpr.lhs | 5 +- > compiler/hsSyn/HsImpExp.lhs | 33 +- > compiler/hsSyn/HsPat.lhs | 39 +- > compiler/hsSyn/HsTypes.lhs | 51 ++- > compiler/hsSyn/HsUtils.lhs | 80 ++-- > compiler/iface/BuildTyCl.lhs | 2 +- > compiler/iface/IfaceSyn.lhs | 52 +-- > compiler/iface/LoadIface.lhs | 19 +- > compiler/iface/MkIface.lhs | 27 +- > compiler/iface/TcIface.lhs | 36 +- > compiler/main/DynFlags.hs | 9 + > compiler/main/GHC.hs | 19 +- > compiler/main/HscMain.hs | 16 +- > compiler/main/HscTypes.lhs | 27 +- > compiler/main/InteractiveEval.hs | 2 +- > compiler/main/PprTyThing.hs | 12 +- > compiler/main/TidyPgm.lhs | 12 +- > compiler/parser/Parser.y.pp | 6 +- > compiler/parser/RdrHsSyn.lhs | 6 +- > compiler/prelude/PrelInfo.lhs | 2 +- > compiler/prelude/PrelNames.lhs | 43 +- > compiler/prelude/TysWiredIn.lhs | 2 +- > compiler/rename/RnEnv.lhs | 321 ++++++++++--- > compiler/rename/RnExpr.lhs | 20 +- > compiler/rename/RnNames.lhs | 470 >+++++++++++++++----- > compiler/rename/RnPat.lhs | 75 ++-- > compiler/rename/RnSource.lhs | 90 ++-- > compiler/rename/RnTypes.lhs | 53 ++- > compiler/typecheck/FamInst.lhs | 53 ++- > compiler/typecheck/Inst.lhs | 3 +- > compiler/typecheck/TcEnv.lhs | 57 +-- > compiler/typecheck/TcErrors.lhs | 54 ++- > compiler/typecheck/TcEvidence.lhs | 1 + > compiler/typecheck/TcExpr.lhs | 320 ++++++++++--- > compiler/typecheck/TcFldInsts.lhs | 468 >+++++++++++++++++++ > compiler/typecheck/TcGenDeriv.lhs | 11 +- > compiler/typecheck/TcGenGenerics.lhs | 16 +- > compiler/typecheck/TcHsSyn.lhs | 4 +- > compiler/typecheck/TcHsType.lhs | 16 +- > compiler/typecheck/TcInstDcls.lhs | 4 +- > compiler/typecheck/TcInteract.lhs | 65 ++- > compiler/typecheck/TcPat.lhs | 24 +- > compiler/typecheck/TcRnDriver.lhs | 25 +- > compiler/typecheck/TcRnMonad.lhs | 5 +- > compiler/typecheck/TcRnTypes.lhs | 31 +- > compiler/typecheck/TcSMonad.lhs | 18 +- > compiler/typecheck/TcSplice.lhs | 2 +- > compiler/typecheck/TcTyClsDecls.lhs | 79 ++-- > compiler/typecheck/TcType.lhs | 9 + > compiler/typecheck/TcValidity.lhs | 19 +- > compiler/types/TyCon.lhs | 54 ++- > compiler/types/Type.lhs | 29 +- > compiler/types/Type.lhs-boot | 2 + > compiler/types/TypeRep.lhs | 43 +- > compiler/utils/Binary.hs | 1 - > compiler/utils/FastStringEnv.lhs | 77 ++++ > docs/users_guide/glasgow_exts.xml | 307 +++++++++++++ > libraries/base/GHC/Base.lhs | 3 + > libraries/base/GHC/Records.hs | 249 +++++++++++ > libraries/base/GHC/TypeLits.hs | 8 +- > libraries/base/base.cabal | 1 + > testsuite/tests/driver/T4437.hs | 1 + > testsuite/tests/ghci/scripts/ghci042.stdout | 2 +- > testsuite/tests/module/mod176.stderr | 2 +- > .../{annotations => overloadedrecflds}/Makefile | 0 > .../ghci}/Makefile | 0 > testsuite/tests/overloadedrecflds/ghci/all.T | 3 + > .../ghci/overloadedrecfldsghci01.script | 13 + > .../ghci/overloadedrecfldsghci01.stdout | 11 + > .../should_fail}/Makefile | 0 > .../should_fail/OverloadedRecFldsFail04_A.hs | 9 + > .../should_fail/OverloadedRecFldsFail06_A.hs | 16 + > .../should_fail/OverloadedRecFldsFail08_A.hs | 14 + > .../tests/overloadedrecflds/should_fail/all.T | 16 + > .../should_fail/overloadedrecfldsfail01.hs | 17 + > .../should_fail/overloadedrecfldsfail01.stderr | 16 + > .../should_fail/overloadedrecfldsfail02.hs | 19 + > .../should_fail/overloadedrecfldsfail02.stderr | 50 +++ > .../should_fail/overloadedrecfldsfail03.hs | 7 + > .../should_fail/overloadedrecfldsfail03.stderr | 5 + > .../should_fail/overloadedrecfldsfail04.hs | 9 + > .../should_fail/overloadedrecfldsfail04.stderr | 5 + > .../should_fail/overloadedrecfldsfail05.hs | 10 + > .../should_fail/overloadedrecfldsfail05.stderr | 10 + > .../should_fail/overloadedrecfldsfail06.hs | 10 + > .../should_fail/overloadedrecfldsfail06.stderr | 15 + > .../should_fail/overloadedrecfldsfail07.hs | 11 + > .../should_fail/overloadedrecfldsfail07.stderr | 6 + > .../should_fail/overloadedrecfldsfail08.hs | 13 + > .../should_fail/overloadedrecfldsfail08.stderr | 47 ++ > .../should_fail/overloadedrecfldsfail09.hs | 9 + > .../should_fail/overloadedrecfldsfail09.stderr | 20 + > .../should_fail/overloadedrecfldsfail10.hs | 11 + > .../should_fail/overloadedrecfldsfail10.stderr | 9 + > .../should_run}/Makefile | 0 > .../should_run/OverloadedRecFldsRun01_A.hs | 9 + > .../should_run/OverloadedRecFldsRun02_A.hs | 9 + > .../should_run/OverloadedRecFldsRun07_A.hs | 11 + > .../should_run/OverloadedRecFldsRun07_B.hs | 7 + > .../should_run/OverloadedRecFldsRun08_A.hs | 11 + > .../should_run/OverloadedRecFldsRun08_B.hs | 7 + > .../should_run/OverloadedRecFldsRun08_C.hs | 7 + > .../should_run/OverloadedRecFldsRun11_A.hs | 9 + > .../should_run/OverloadedRecFldsRun11_A.hs-boot | 5 + > .../should_run/OverloadedRecFldsRun11_B.hs | 7 + > .../should_run/OverloadedRecFldsRun12_A.hs | 11 + > .../should_run/OverloadedRecFldsRun12_B.hs | 7 + > testsuite/tests/overloadedrecflds/should_run/all.T | 26 ++ > .../should_run/overloadedrecfldsrun01.hs | 70 +++ > .../should_run/overloadedrecfldsrun01.stdout | 13 + > .../should_run/overloadedrecfldsrun02.hs | 6 + > .../should_run/overloadedrecfldsrun02.stdout | 0 > .../should_run/overloadedrecfldsrun03.hs | 18 + > .../should_run/overloadedrecfldsrun03.stdout | 4 + > .../should_run/overloadedrecfldsrun04.hs | 18 + > .../should_run/overloadedrecfldsrun04.stdout | 3 + > .../should_run/overloadedrecfldsrun05.hs | 34 ++ > .../should_run/overloadedrecfldsrun05.stdout | 2 + > .../should_run/overloadedrecfldsrun06.hs | 28 ++ > .../should_run/overloadedrecfldsrun06.stdout | 1 + > .../should_run/overloadedrecfldsrun07.hs | 7 + > .../should_run/overloadedrecfldsrun07.stdout} | 0 > .../should_run/overloadedrecfldsrun08.hs | 7 + > .../should_run/overloadedrecfldsrun08.stdout | 2 + > .../should_run/overloadedrecfldsrun09.hs | 8 + > .../should_run/overloadedrecfldsrun09.stdout | 2 + > .../should_run/overloadedrecfldsrun10.hs | 12 + > .../should_run/overloadedrecfldsrun10.stderr | 2 + > .../should_run/overloadedrecfldsrun11.hs | 5 + > .../should_run/overloadedrecfldsrun11.stdout} | 0 > .../should_run/overloadedrecfldsrun12.hs | 6 + > .../should_run/overloadedrecfldsrun12.stdout | 2 + > .../should_run/overloadedrecfldsrun13.hs | 9 + > .../should_run/overloadedrecfldsrun13.stdout} | 0 > testsuite/tests/rename/should_fail/T5892a.stderr | 2 +- > .../tests/typecheck/should_fail/tcfail102.stderr | 3 +- > utils/ghctags/Main.hs | 2 +- > utils/haddock | 2 +- > 157 files changed, 4131 insertions(+), 759 deletions(-) > >Diff suppressed because of size. To see it, use: > > git diff-tree --root --patch-with-stat --no-color >--find-copies-harder --ignore-space-at-eol --cc >fe77cbf15dd44bb72943357d65bd8adf9f4deee5 >_______________________________________________ >ghc-commits mailing list >ghc-commits at haskell.org >http://www.haskell.org/mailman/listinfo/ghc-commits From git at git.haskell.org Tue Apr 22 21:00:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 22 Apr 2014 21:00:08 +0000 (UTC) Subject: [commit: ghc] master: Be more aggressive in `make clean` (0a0115f) Message-ID: <20140422210008.1A3F32406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0a0115fe17b22d1252220fe1ed0ba1dcc2839546/ghc >--------------------------------------------------------------- commit 0a0115fe17b22d1252220fe1ed0ba1dcc2839546 Author: Herbert Valerio Riedel Date: Tue Apr 22 22:23:56 2014 +0200 Be more aggressive in `make clean` This quiets down the utils/testremove/checkremove step Basically the idea is to have 'make clean' remove everything that was generated by `make`, while `make distclean` ought to remove everything created by `./configure`. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 0a0115fe17b22d1252220fe1ed0ba1dcc2839546 ghc.mk | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/ghc.mk b/ghc.mk index dab9050..666d0a9 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1202,6 +1202,11 @@ sdist_%: CLEAN_FILES += libraries/bootstrapping.conf CLEAN_FILES += libraries/integer-gmp/cbits/GmpDerivedConstants.h +CLEAN_FILES += libraries/integer-gmp/include/HsIntegerGmp.h +CLEAN_FILES += libraries/base/include/EventConfig.h +CLEAN_FILES += mk/config.mk.old +CLEAN_FILES += mk/project.mk.old +CLEAN_FILES += compiler/ghc.cabal.old # These are no longer generated, but we still clean them for a while # as they may still be in old GHC trees: @@ -1219,6 +1224,9 @@ clean : clean_files clean_libraries .PHONY: clean_files clean_files : $(call removeFiles,$(CLEAN_FILES)) +# this is here since CLEAN_FILES can't handle folders + $(call removeTrees,includes/dist-derivedconstants) + $(call removeTrees,inplace) .PHONY: clean_libraries clean_libraries: $(patsubst %,clean_libraries/%_dist-install,$(PACKAGES_STAGE1) $(PACKAGES_STAGE2)) From git at git.haskell.org Wed Apr 23 07:15:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 23 Apr 2014 07:15:15 +0000 (UTC) Subject: [commit: ghc] branch 'wip/coverity' created Message-ID: <20140423071516.1E20D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/coverity Referencing: 1aed176f5db8116c7e5cc74afd79996f24338d29 From git at git.haskell.org Wed Apr 23 07:15:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 23 Apr 2014 07:15:20 +0000 (UTC) Subject: [commit: ghc] wip/coverity: Fix potential memory leak in ProfHeap.c (1aed176) Message-ID: <20140423071520.11D862406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/coverity Link : http://ghc.haskell.org/trac/ghc/changeset/1aed176f5db8116c7e5cc74afd79996f24338d29/ghc >--------------------------------------------------------------- commit 1aed176f5db8116c7e5cc74afd79996f24338d29 Author: Austin Seipp Date: Wed Apr 23 02:14:15 2014 -0500 Fix potential memory leak in ProfHeap.c Discovered by Coverity. CID 43166. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 1aed176f5db8116c7e5cc74afd79996f24338d29 rts/ProfHeap.c | 1 + 1 file changed, 1 insertion(+) diff --git a/rts/ProfHeap.c b/rts/ProfHeap.c index d21b14a..9079c2b 100644 --- a/rts/ProfHeap.c +++ b/rts/ProfHeap.c @@ -337,6 +337,7 @@ void initProfiling2 (void) debugBelch("Can't open profiling report file %s\n", hp_filename); RtsFlags.ProfFlags.doHeapProfile = 0; + stgFree(prog); return; } } From git at git.haskell.org Thu Apr 24 07:09:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 24 Apr 2014 07:09:10 +0000 (UTC) Subject: [commit: ghc] branch 'wip/drop-containers-dep-from-th' created Message-ID: <20140424070910.C2C4A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/drop-containers-dep-from-th Referencing: 87ed0c0802aced52b189847601c57d2c3f798bfa From git at git.haskell.org Thu Apr 24 07:09:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 24 Apr 2014 07:09:14 +0000 (UTC) Subject: [commit: ghc] wip/drop-containers-dep-from-th: Drop external build-dep on `containers` (87ed0c0) Message-ID: <20140424070914.2F9C42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/drop-containers-dep-from-th Link : http://ghc.haskell.org/trac/ghc/changeset/87ed0c0802aced52b189847601c57d2c3f798bfa/ghc >--------------------------------------------------------------- commit 87ed0c0802aced52b189847601c57d2c3f798bfa Author: Herbert Valerio Riedel Date: Thu Apr 24 09:05:45 2014 +0200 Drop external build-dep on `containers` This is an attempt to address https://github.com/haskell/cabal/issues/1811 by ripping the less than 100 lines of code actually used from the containers package into an internal non-exposed `template-haskell` module. Moreover, `template-haskell` does not expose the `Map` type, so this change should have no visible effect on the public API. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 87ed0c0802aced52b189847601c57d2c3f798bfa .../Language/Haskell/TH/Lib/Map.hs | 108 ++++++++++++++++++++ .../template-haskell/Language/Haskell/TH/PprLib.hs | 4 +- libraries/template-haskell/template-haskell.cabal | 4 +- 3 files changed, 113 insertions(+), 3 deletions(-) diff --git a/libraries/template-haskell/Language/Haskell/TH/Lib/Map.hs b/libraries/template-haskell/Language/Haskell/TH/Lib/Map.hs new file mode 100644 index 0000000..ac24151 --- /dev/null +++ b/libraries/template-haskell/Language/Haskell/TH/Lib/Map.hs @@ -0,0 +1,108 @@ +{-# LANGUAGE BangPatterns #-} + +-- This is a non-exposed internal module +-- +-- The code in this module has been ripped from containers-0.5.5.1:Data.Map.Base [1] almost +-- verbatimely to avoid a dependency of 'template-haskell' on the containers package. +-- +-- [1] see https://hackage.haskell.org/package/containers-0.5.5.1 +-- +-- The original code is BSD-licensed and copyrighted by Daan Leijen, Andriy Palamarchuk, et al. + +module Language.Haskell.TH.Lib.Map + ( Map + , empty + , insert + , Language.Haskell.TH.Lib.Map.lookup + ) where + +data Map k a = Bin {-# UNPACK #-} !Size !k a !(Map k a) !(Map k a) + | Tip + +type Size = Int + +empty :: Map k a +empty = Tip +{-# INLINE empty #-} + +singleton :: k -> a -> Map k a +singleton k x = Bin 1 k x Tip Tip +{-# INLINE singleton #-} + +size :: Map k a -> Int +size Tip = 0 +size (Bin sz _ _ _ _) = sz +{-# INLINE size #-} + +lookup :: Ord k => k -> Map k a -> Maybe a +lookup = go + where + go _ Tip = Nothing + go !k (Bin _ kx x l r) = case compare k kx of + LT -> go k l + GT -> go k r + EQ -> Just x +{-# INLINABLE lookup #-} + + +insert :: Ord k => k -> a -> Map k a -> Map k a +insert = go + where + go :: Ord k => k -> a -> Map k a -> Map k a + go !kx x Tip = singleton kx x + go !kx x (Bin sz ky y l r) = + case compare kx ky of + LT -> balanceL ky y (go kx x l) r + GT -> balanceR ky y l (go kx x r) + EQ -> Bin sz kx x l r +{-# INLINABLE insert #-} + +balanceL :: k -> a -> Map k a -> Map k a -> Map k a +balanceL k x l r = case r of + Tip -> case l of + Tip -> Bin 1 k x Tip Tip + (Bin _ _ _ Tip Tip) -> Bin 2 k x l Tip + (Bin _ lk lx Tip (Bin _ lrk lrx _ _)) -> Bin 3 lrk lrx (Bin 1 lk lx Tip Tip) (Bin 1 k x Tip Tip) + (Bin _ lk lx ll@(Bin _ _ _ _ _) Tip) -> Bin 3 lk lx ll (Bin 1 k x Tip Tip) + (Bin ls lk lx ll@(Bin lls _ _ _ _) lr@(Bin lrs lrk lrx lrl lrr)) + | lrs < ratio*lls -> Bin (1+ls) lk lx ll (Bin (1+lrs) k x lr Tip) + | otherwise -> Bin (1+ls) lrk lrx (Bin (1+lls+size lrl) lk lx ll lrl) (Bin (1+size lrr) k x lrr Tip) + + (Bin rs _ _ _ _) -> case l of + Tip -> Bin (1+rs) k x Tip r + + (Bin ls lk lx ll lr) + | ls > delta*rs -> case (ll, lr) of + (Bin lls _ _ _ _, Bin lrs lrk lrx lrl lrr) + | lrs < ratio*lls -> Bin (1+ls+rs) lk lx ll (Bin (1+rs+lrs) k x lr r) + | otherwise -> Bin (1+ls+rs) lrk lrx (Bin (1+lls+size lrl) lk lx ll lrl) (Bin (1+rs+size lrr) k x lrr r) + (_, _) -> error "Failure in Data.Map.balanceL" + | otherwise -> Bin (1+ls+rs) k x l r +{-# NOINLINE balanceL #-} + +balanceR :: k -> a -> Map k a -> Map k a -> Map k a +balanceR k x l r = case l of + Tip -> case r of + Tip -> Bin 1 k x Tip Tip + (Bin _ _ _ Tip Tip) -> Bin 2 k x Tip r + (Bin _ rk rx Tip rr@(Bin _ _ _ _ _)) -> Bin 3 rk rx (Bin 1 k x Tip Tip) rr + (Bin _ rk rx (Bin _ rlk rlx _ _) Tip) -> Bin 3 rlk rlx (Bin 1 k x Tip Tip) (Bin 1 rk rx Tip Tip) + (Bin rs rk rx rl@(Bin rls rlk rlx rll rlr) rr@(Bin rrs _ _ _ _)) + | rls < ratio*rrs -> Bin (1+rs) rk rx (Bin (1+rls) k x Tip rl) rr + | otherwise -> Bin (1+rs) rlk rlx (Bin (1+size rll) k x Tip rll) (Bin (1+rrs+size rlr) rk rx rlr rr) + + (Bin ls _ _ _ _) -> case r of + Tip -> Bin (1+ls) k x l Tip + + (Bin rs rk rx rl rr) + | rs > delta*ls -> case (rl, rr) of + (Bin rls rlk rlx rll rlr, Bin rrs _ _ _ _) + | rls < ratio*rrs -> Bin (1+ls+rs) rk rx (Bin (1+ls+rls) k x l rl) rr + | otherwise -> Bin (1+ls+rs) rlk rlx (Bin (1+ls+size rll) k x l rll) (Bin (1+rrs+size rlr) rk rx rlr rr) + (_, _) -> error "Failure in Data.Map.balanceR" + | otherwise -> Bin (1+ls+rs) k x l r +{-# NOINLINE balanceR #-} + +delta,ratio :: Int +delta = 3 +ratio = 2 diff --git a/libraries/template-haskell/Language/Haskell/TH/PprLib.hs b/libraries/template-haskell/Language/Haskell/TH/PprLib.hs index 93e37ce..c4b0b77 100644 --- a/libraries/template-haskell/Language/Haskell/TH/PprLib.hs +++ b/libraries/template-haskell/Language/Haskell/TH/PprLib.hs @@ -40,8 +40,8 @@ import Language.Haskell.TH.Syntax import qualified Text.PrettyPrint as HPJ import Control.Applicative (Applicative(..)) import Control.Monad (liftM, liftM2, ap) -import Data.Map ( Map ) -import qualified Data.Map as Map ( lookup, insert, empty ) +import Language.Haskell.TH.Lib.Map ( Map ) +import qualified Language.Haskell.TH.Lib.Map as Map ( lookup, insert, empty ) import GHC.Base (Int(..)) infixl 6 <> diff --git a/libraries/template-haskell/template-haskell.cabal b/libraries/template-haskell/template-haskell.cabal index ca0e344..fb8dbd7 100644 --- a/libraries/template-haskell/template-haskell.cabal +++ b/libraries/template-haskell/template-haskell.cabal @@ -42,9 +42,11 @@ Library Language.Haskell.TH.Quote Language.Haskell.TH.Syntax + other-modules: + Language.Haskell.TH.Lib.Map + build-depends: base == 4.7.*, - containers == 0.5.*, pretty == 1.1.* -- We need to set the package name to template-haskell (without a From git at git.haskell.org Thu Apr 24 07:35:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 24 Apr 2014 07:35:16 +0000 (UTC) Subject: [commit: ghc] wip/drop-containers-dep-from-th: Drop external build-dep on `containers` (4233489) Message-ID: <20140424073516.A4BA12406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/drop-containers-dep-from-th Link : http://ghc.haskell.org/trac/ghc/changeset/4233489aecca5a3426ea48401c99ae95b4dfc23e/ghc >--------------------------------------------------------------- commit 4233489aecca5a3426ea48401c99ae95b4dfc23e Author: Herbert Valerio Riedel Date: Thu Apr 24 09:05:45 2014 +0200 Drop external build-dep on `containers` This is an attempt to address https://github.com/haskell/cabal/issues/1811 by ripping the less than 100 lines of code actually used from the containers package into an internal non-exposed `template-haskell` module. Moreover, `template-haskell` does not expose the `Map` type, so this change should have no visible effect on the public API. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 4233489aecca5a3426ea48401c99ae95b4dfc23e .../Language/Haskell/TH/Lib/Map.hs | 108 ++++++++++++++++++++ .../template-haskell/Language/Haskell/TH/PprLib.hs | 4 +- libraries/template-haskell/template-haskell.cabal | 4 +- testsuite/tests/th/TH_Roles2.stderr | 13 ++- 4 files changed, 119 insertions(+), 10 deletions(-) diff --git a/libraries/template-haskell/Language/Haskell/TH/Lib/Map.hs b/libraries/template-haskell/Language/Haskell/TH/Lib/Map.hs new file mode 100644 index 0000000..ac24151 --- /dev/null +++ b/libraries/template-haskell/Language/Haskell/TH/Lib/Map.hs @@ -0,0 +1,108 @@ +{-# LANGUAGE BangPatterns #-} + +-- This is a non-exposed internal module +-- +-- The code in this module has been ripped from containers-0.5.5.1:Data.Map.Base [1] almost +-- verbatimely to avoid a dependency of 'template-haskell' on the containers package. +-- +-- [1] see https://hackage.haskell.org/package/containers-0.5.5.1 +-- +-- The original code is BSD-licensed and copyrighted by Daan Leijen, Andriy Palamarchuk, et al. + +module Language.Haskell.TH.Lib.Map + ( Map + , empty + , insert + , Language.Haskell.TH.Lib.Map.lookup + ) where + +data Map k a = Bin {-# UNPACK #-} !Size !k a !(Map k a) !(Map k a) + | Tip + +type Size = Int + +empty :: Map k a +empty = Tip +{-# INLINE empty #-} + +singleton :: k -> a -> Map k a +singleton k x = Bin 1 k x Tip Tip +{-# INLINE singleton #-} + +size :: Map k a -> Int +size Tip = 0 +size (Bin sz _ _ _ _) = sz +{-# INLINE size #-} + +lookup :: Ord k => k -> Map k a -> Maybe a +lookup = go + where + go _ Tip = Nothing + go !k (Bin _ kx x l r) = case compare k kx of + LT -> go k l + GT -> go k r + EQ -> Just x +{-# INLINABLE lookup #-} + + +insert :: Ord k => k -> a -> Map k a -> Map k a +insert = go + where + go :: Ord k => k -> a -> Map k a -> Map k a + go !kx x Tip = singleton kx x + go !kx x (Bin sz ky y l r) = + case compare kx ky of + LT -> balanceL ky y (go kx x l) r + GT -> balanceR ky y l (go kx x r) + EQ -> Bin sz kx x l r +{-# INLINABLE insert #-} + +balanceL :: k -> a -> Map k a -> Map k a -> Map k a +balanceL k x l r = case r of + Tip -> case l of + Tip -> Bin 1 k x Tip Tip + (Bin _ _ _ Tip Tip) -> Bin 2 k x l Tip + (Bin _ lk lx Tip (Bin _ lrk lrx _ _)) -> Bin 3 lrk lrx (Bin 1 lk lx Tip Tip) (Bin 1 k x Tip Tip) + (Bin _ lk lx ll@(Bin _ _ _ _ _) Tip) -> Bin 3 lk lx ll (Bin 1 k x Tip Tip) + (Bin ls lk lx ll@(Bin lls _ _ _ _) lr@(Bin lrs lrk lrx lrl lrr)) + | lrs < ratio*lls -> Bin (1+ls) lk lx ll (Bin (1+lrs) k x lr Tip) + | otherwise -> Bin (1+ls) lrk lrx (Bin (1+lls+size lrl) lk lx ll lrl) (Bin (1+size lrr) k x lrr Tip) + + (Bin rs _ _ _ _) -> case l of + Tip -> Bin (1+rs) k x Tip r + + (Bin ls lk lx ll lr) + | ls > delta*rs -> case (ll, lr) of + (Bin lls _ _ _ _, Bin lrs lrk lrx lrl lrr) + | lrs < ratio*lls -> Bin (1+ls+rs) lk lx ll (Bin (1+rs+lrs) k x lr r) + | otherwise -> Bin (1+ls+rs) lrk lrx (Bin (1+lls+size lrl) lk lx ll lrl) (Bin (1+rs+size lrr) k x lrr r) + (_, _) -> error "Failure in Data.Map.balanceL" + | otherwise -> Bin (1+ls+rs) k x l r +{-# NOINLINE balanceL #-} + +balanceR :: k -> a -> Map k a -> Map k a -> Map k a +balanceR k x l r = case l of + Tip -> case r of + Tip -> Bin 1 k x Tip Tip + (Bin _ _ _ Tip Tip) -> Bin 2 k x Tip r + (Bin _ rk rx Tip rr@(Bin _ _ _ _ _)) -> Bin 3 rk rx (Bin 1 k x Tip Tip) rr + (Bin _ rk rx (Bin _ rlk rlx _ _) Tip) -> Bin 3 rlk rlx (Bin 1 k x Tip Tip) (Bin 1 rk rx Tip Tip) + (Bin rs rk rx rl@(Bin rls rlk rlx rll rlr) rr@(Bin rrs _ _ _ _)) + | rls < ratio*rrs -> Bin (1+rs) rk rx (Bin (1+rls) k x Tip rl) rr + | otherwise -> Bin (1+rs) rlk rlx (Bin (1+size rll) k x Tip rll) (Bin (1+rrs+size rlr) rk rx rlr rr) + + (Bin ls _ _ _ _) -> case r of + Tip -> Bin (1+ls) k x l Tip + + (Bin rs rk rx rl rr) + | rs > delta*ls -> case (rl, rr) of + (Bin rls rlk rlx rll rlr, Bin rrs _ _ _ _) + | rls < ratio*rrs -> Bin (1+ls+rs) rk rx (Bin (1+ls+rls) k x l rl) rr + | otherwise -> Bin (1+ls+rs) rlk rlx (Bin (1+ls+size rll) k x l rll) (Bin (1+rrs+size rlr) rk rx rlr rr) + (_, _) -> error "Failure in Data.Map.balanceR" + | otherwise -> Bin (1+ls+rs) k x l r +{-# NOINLINE balanceR #-} + +delta,ratio :: Int +delta = 3 +ratio = 2 diff --git a/libraries/template-haskell/Language/Haskell/TH/PprLib.hs b/libraries/template-haskell/Language/Haskell/TH/PprLib.hs index 93e37ce..c4b0b77 100644 --- a/libraries/template-haskell/Language/Haskell/TH/PprLib.hs +++ b/libraries/template-haskell/Language/Haskell/TH/PprLib.hs @@ -40,8 +40,8 @@ import Language.Haskell.TH.Syntax import qualified Text.PrettyPrint as HPJ import Control.Applicative (Applicative(..)) import Control.Monad (liftM, liftM2, ap) -import Data.Map ( Map ) -import qualified Data.Map as Map ( lookup, insert, empty ) +import Language.Haskell.TH.Lib.Map ( Map ) +import qualified Language.Haskell.TH.Lib.Map as Map ( lookup, insert, empty ) import GHC.Base (Int(..)) infixl 6 <> diff --git a/libraries/template-haskell/template-haskell.cabal b/libraries/template-haskell/template-haskell.cabal index ca0e344..fb8dbd7 100644 --- a/libraries/template-haskell/template-haskell.cabal +++ b/libraries/template-haskell/template-haskell.cabal @@ -42,9 +42,11 @@ Library Language.Haskell.TH.Quote Language.Haskell.TH.Syntax + other-modules: + Language.Haskell.TH.Lib.Map + build-depends: base == 4.7.*, - containers == 0.5.*, pretty == 1.1.* -- We need to set the package name to template-haskell (without a diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr index a4526e1..bd44d12 100644 --- a/testsuite/tests/th/TH_Roles2.stderr +++ b/testsuite/tests/th/TH_Roles2.stderr @@ -2,15 +2,14 @@ TYPE SIGNATURES TYPE CONSTRUCTORS T :: k -> * data T (k::BOX) (a::k) - No C type associated - Roles: [nominal, representational] - RecFlag NonRecursive, Not promotable - = - FamilyInstance: none + No C type associated + Roles: [nominal, representational] + RecFlag NonRecursive, Not promotable + = + FamilyInstance: none COERCION AXIOMS Dependent modules: [] -Dependent packages: [array-0.5.0.0, base, containers-0.5.5.1, - deepseq-1.3.0.2, ghc-prim, integer-gmp, pretty-1.1.1.1, +Dependent packages: [base, ghc-prim, integer-gmp, pretty-1.1.1.1, template-haskell] ==================== Typechecker ==================== From git at git.haskell.org Thu Apr 24 07:35:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 24 Apr 2014 07:35:56 +0000 (UTC) Subject: [commit: nofib] master: Add FlexibleContexts to two nofib benchmarks (d98f703) Message-ID: <20140424073556.8BDBE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d98f7038d1111e515db9cc27d5d3bbe237e6e14f/nofib >--------------------------------------------------------------- commit d98f7038d1111e515db9cc27d5d3bbe237e6e14f Author: Simon Peyton Jones Date: Thu Apr 24 08:34:41 2014 +0100 Add FlexibleContexts to two nofib benchmarks Turns out that these two have a local function with a (MArray (STUArray s) Double m) context, or something like that. The real issue here is that we don't yet know what 'm' is. A better solution would be MonoMonoBinds, but that would threaten perf comparison with older GHC's >--------------------------------------------------------------- d98f7038d1111e515db9cc27d5d3bbe237e6e14f imaginary/kahan/Main.hs | 5 +++++ spectral/fibheaps/Main.lhs | 6 ++++++ 2 files changed, 11 insertions(+) diff --git a/imaginary/kahan/Main.hs b/imaginary/kahan/Main.hs index 6b3f76b..cb8d155 100644 --- a/imaginary/kahan/Main.hs +++ b/imaginary/kahan/Main.hs @@ -1,3 +1,8 @@ +{-# LANGUAGE FlexibleContexts #-} +-- Inferred type for 'inner' has a constraint (MArray (STUArray s) Double m) +-- An alternative fix (better, but less faithful to backward perf comparison) +-- would be MonoLocalBinds + -- | Implementation of Kahan summation algorithm that tests -- performance of tight loops involving unboxed arrays and floating -- point arithmetic. diff --git a/spectral/fibheaps/Main.lhs b/spectral/fibheaps/Main.lhs index 452ae6e..5ce7bfc 100644 --- a/spectral/fibheaps/Main.lhs +++ b/spectral/fibheaps/Main.lhs @@ -1,3 +1,9 @@ +>{-# LANGUAGE FlexibleContexts #-} + + Inferred type for 'getMin' has a constraint (MArray a (MyMaybe t) m) + An alternative fix (better, but less faithful to backward perf + comparison) would be MonoLocalBinds + Date: Tue, 04 Jul 1995 13:10:58 -0400 From: Chris_Okasaki at LOCH.MESS.CS.CMU.EDU To: simonpj at dcs.gla.ac.uk From git at git.haskell.org Thu Apr 24 07:38:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 24 Apr 2014 07:38:01 +0000 (UTC) Subject: [commit: ghc] master: Add comments to explain the change to EF_ (Trac #8965) (31a7bb4) Message-ID: <20140424073802.57F0E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/31a7bb463b6a3e99ede6de994c1f449c43a9118c/ghc >--------------------------------------------------------------- commit 31a7bb463b6a3e99ede6de994c1f449c43a9118c Author: Simon Peyton Jones Date: Thu Apr 24 08:36:40 2014 +0100 Add comments to explain the change to EF_ (Trac #8965) >--------------------------------------------------------------- 31a7bb463b6a3e99ede6de994c1f449c43a9118c includes/Stg.h | 30 +++++++++++++++++++++++++++++- 1 file changed, 29 insertions(+), 1 deletion(-) diff --git a/includes/Stg.h b/includes/Stg.h index 1707c9b..9edb6a0 100644 --- a/includes/Stg.h +++ b/includes/Stg.h @@ -213,7 +213,35 @@ typedef StgFunPtr F_; #define II_(X) static StgWordArray (X) GNU_ATTRIBUTE(aligned (8)) #define IF_(f) static StgFunPtr GNUC3_ATTRIBUTE(used) f(void) #define FN_(f) StgFunPtr f(void) -#define EF_(f) extern StgFunPtr f() +#define EF_(f) extern StgFunPtr f() /* See Note [External function prototypes] */ + +/* Note [External function prototypes] See Trac #8965 + ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The external-function macro EF_(F) used to be defined as + extern StgFunPtr f(void) +i.e a function of zero arguments. On most platforms this doesn't +matter very much: calls to these functions put the parameters in the +usual places anyway, and (with the exception of varargs) things just +work. + +However, the ELFv2 ABI on ppc64 optimises stack allocation +(http://gcc.gnu.org/ml/gcc-patches/2013-11/msg01149.html): a call to a +function that has a prototype, is not varargs, and receives all parameters +in registers rather than on the stack does not require the caller to +allocate an argument save area. The incorrect prototypes cause GCC to +believe that all functions declared this way can be called without an +argument save area, but if the callee has sufficiently many arguments then +it will expect that area to be present, and will thus corrupt the caller's +stack. This happens in particular with calls to runInteractiveProcess in +libraries/process/cbits/runProcess.c, and led to Trac #8965. + +The simplest fix appears to be to declare these external functions with an +unspecified argument list rather than a void argument list. This is no +worse for platforms that don't care either way, and allows a successful +bootstrap of GHC 7.8 on little-endian Linux ppc64 (which uses the ELFv2 +ABI). +*/ + /* ----------------------------------------------------------------------------- Tail calls From git at git.haskell.org Thu Apr 24 07:43:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 24 Apr 2014 07:43:50 +0000 (UTC) Subject: [commit: ghc] master: Be less verbose when printing Names when we don't know what's in scope (134b722) Message-ID: <20140424074352.6E7A42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/134b722349b83c746f8f52f2dbd99b89d23b644c/ghc >--------------------------------------------------------------- commit 134b722349b83c746f8f52f2dbd99b89d23b644c Author: Simon Peyton Jones Date: Tue Apr 22 17:17:31 2014 +0100 Be less verbose when printing Names when we don't know what's in scope Previously we always printed qualified names, but that makes a lot of debug or warning output very verbose. So now we only print qualified names with -dppr-debug. Civilised output (from pukka error messages, with the environment available) is unaffected >--------------------------------------------------------------- 134b722349b83c746f8f52f2dbd99b89d23b644c compiler/stranal/WwLib.lhs | 2 +- compiler/utils/Outputable.lhs | 25 ++++++----- testsuite/tests/plugins/plugins02.stderr | 2 +- testsuite/tests/quasiquotation/T7918.stdout | 44 ++++++++++---------- .../safeHaskell/safeLanguage/SafeLang15.stderr | 2 +- .../tests/simplCore/should_compile/T5776.stdout | 2 +- .../tests/simplCore/should_compile/T7785.stderr | 7 ++-- .../tests/simplCore/should_compile/T8848.stderr | 2 +- .../tests/simplCore/should_compile/T8848a.stderr | 6 +-- testsuite/tests/simplCore/should_run/T2486.stderr | 28 ++++++------- 10 files changed, 56 insertions(+), 64 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 134b722349b83c746f8f52f2dbd99b89d23b644c From git at git.haskell.org Thu Apr 24 07:43:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 24 Apr 2014 07:43:54 +0000 (UTC) Subject: [commit: ghc] master: Make absolutely sure that 'done' and 'safeIndex' are strict in the index (68a1e67) Message-ID: <20140424074354.A98C32406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/68a1e679f0b97db99c552c3dbf69e651291826fa/ghc >--------------------------------------------------------------- commit 68a1e679f0b97db99c552c3dbf69e651291826fa Author: Simon Peyton Jones Date: Tue Apr 22 14:40:12 2014 +0100 Make absolutely sure that 'done' and 'safeIndex' are strict in the index This is just to make sure that there is no redundant boxing. For safeIndex, for example, the error path doesn't evaluate the index, so it may be passed boxed unless safeIndex is inlined bodily, which I don't want to rely on. >--------------------------------------------------------------- 68a1e679f0b97db99c552c3dbf69e651291826fa libraries/base/GHC/Arr.lhs | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) diff --git a/libraries/base/GHC/Arr.lhs b/libraries/base/GHC/Arr.lhs index 6d11e38..14bc917 100644 --- a/libraries/base/GHC/Arr.lhs +++ b/libraries/base/GHC/Arr.lhs @@ -491,7 +491,8 @@ fill marr# (I# i#, e) next {-# INLINE done #-} done :: Ix i => i -> i -> Int -> MutableArray# s e -> STRep s (Array i e) -- See NB on 'fill' -done l u n marr# +-- Make sure it is strict in 'n' +done l u n@(I# _) marr# = \s1# -> case unsafeFreezeArray# marr# s1# of (# s2#, arr# #) -> (# s2#, Array l u n arr# #) @@ -534,11 +535,13 @@ negRange = error "Negative range size" {-# INLINE[1] safeIndex #-} -- See Note [Double bounds-checking of index values] -- Inline *after* (!) so the rules can fire +-- Make sure it is strict in n safeIndex :: Ix i => (i, i) -> Int -> i -> Int -safeIndex (l,u) n i = let i' = index (l,u) i - in if (0 <= i') && (i' < n) - then i' - else badSafeIndex i' n +safeIndex (l,u) n@(I# _) i + | (0 <= i') && (i' < n) = i' + | otherwise = badSafeIndex i' n + where + i' = index (l,u) i -- See Note [Double bounds-checking of index values] {-# RULES From git at git.haskell.org Thu Apr 24 07:43:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 24 Apr 2014 07:43:57 +0000 (UTC) Subject: [commit: ghc] master: Be sure to UNPACK the size of an array (98aab76) Message-ID: <20140424074357.7F2A62406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/98aab76a5498b003635fd78188b7c1e3623c73d5/ghc >--------------------------------------------------------------- commit 98aab76a5498b003635fd78188b7c1e3623c73d5 Author: Simon Peyton Jones Date: Tue Apr 22 14:37:22 2014 +0100 Be sure to UNPACK the size of an array The code before did actually unpack the size, I think, but it wasn't very clear, and it's better to do it explicitly >--------------------------------------------------------------- 98aab76a5498b003635fd78188b7c1e3623c73d5 libraries/base/GHC/Arr.lhs | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/libraries/base/GHC/Arr.lhs b/libraries/base/GHC/Arr.lhs index 0235624..6d11e38 100644 --- a/libraries/base/GHC/Arr.lhs +++ b/libraries/base/GHC/Arr.lhs @@ -381,12 +381,12 @@ instance (Ix a1, Ix a2, Ix a3, Ix a4, Ix a5) => Ix (a1,a2,a3,a4,a5) where -- | The type of immutable non-strict (boxed) arrays -- with indices in @i@ and elements in @e at . data Array i e - = Array !i -- the lower bound, l - !i -- the upper bound, u - !Int -- a cache of (rangeSize (l,u)) - -- used to make sure an index is - -- really in range - (Array# e) -- The actual elements + = Array !i -- the lower bound, l + !i -- the upper bound, u + {-# UNPACK #-} !Int -- A cache of (rangeSize (l,u)) + -- used to make sure an index is + -- really in range + (Array# e) -- The actual elements -- | Mutable, boxed, non-strict arrays in the 'ST' monad. The type -- arguments are as follows: @@ -398,9 +398,9 @@ data Array i e -- * @e@: the element type of the array. -- data STArray s i e - = STArray !i -- the lower bound, l - !i -- the upper bound, u - !Int -- a cache of (rangeSize (l,u)) + = STArray !i -- the lower bound, l + !i -- the upper bound, u + {-# UNPACK #-} !Int -- A cache of (rangeSize (l,u)) -- used to make sure an index is -- really in range (MutableArray# s e) -- The actual elements From git at git.haskell.org Thu Apr 24 07:44:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 24 Apr 2014 07:44:00 +0000 (UTC) Subject: [commit: ghc] master: Don't eta-expand PAPs (fixes Trac #9020) (79e46ae) Message-ID: <20140424074400.B21A32406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/79e46aea1643b4dfdc7c846bbefe06b83b535efd/ghc >--------------------------------------------------------------- commit 79e46aea1643b4dfdc7c846bbefe06b83b535efd Author: Simon Peyton Jones Date: Thu Apr 24 08:43:07 2014 +0100 Don't eta-expand PAPs (fixes Trac #9020) See Note [Do not eta-expand PAPs] in SimplUtils. This has a tremendously good effect on compile times for some simple benchmarks. The test is now where it belongs, in perf/compiler/T9020 (instead of simpl015). I did a nofib run and got essentially zero change except for cacheprof which gets 4% more allocation. I investigated. Turns out that we have instance PP Reg where pp ppm ST_0 = "%st" pp ppm ST_1 = "%st(1)" pp ppm ST_2 = "%st(2)" pp ppm ST_3 = "%st(3)" pp ppm ST_4 = "%st(4)" pp ppm ST_5 = "%st(5)" pp ppm ST_6 = "%st(6)" pp ppm ST_7 = "%st(7)" pp ppm r = "%" ++ map toLower (show r) That (map toLower (show r) does a lot of map/toLowers. But if we inline show we get something like pp ppm ST_0 = "%st" pp ppm ST_1 = "%st(1)" pp ppm ST_2 = "%st(2)" pp ppm ST_3 = "%st(3)" pp ppm ST_4 = "%st(4)" pp ppm ST_5 = "%st(5)" pp ppm ST_6 = "%st(6)" pp ppm ST_7 = "%st(7)" pp ppm EAX = map toLower (show EAX) pp ppm EBX = map toLower (show EBX) ...etc... and all those map/toLower calls can now be floated to top level. This gives a 4% decrease in allocation. But it depends on inlining a pretty big 'show' function. With this new patch we get slightly better eta-expansion, which makes a function look slightly bigger, which just stops it being inlined. The previous behaviour was luck, so I'm not going to worry about losing it. I've added some notes to nofib/Simon-nofib-notes >--------------------------------------------------------------- 79e46aea1643b4dfdc7c846bbefe06b83b535efd compiler/coreSyn/CoreArity.lhs | 3 +- compiler/simplCore/SimplUtils.lhs | 44 +++++++++++++++----- .../simpl015.hs => perf/compiler/T9020.hs} | 0 testsuite/tests/perf/compiler/all.T | 8 ++++ .../should_compile => perf/compiler}/simpl015.hs | 0 testsuite/tests/simplCore/should_compile/all.T | 1 - 6 files changed, 43 insertions(+), 13 deletions(-) diff --git a/compiler/coreSyn/CoreArity.lhs b/compiler/coreSyn/CoreArity.lhs index 12d4274..ca7216f 100644 --- a/compiler/coreSyn/CoreArity.lhs +++ b/compiler/coreSyn/CoreArity.lhs @@ -73,7 +73,8 @@ should have arity 3, regardless of f's arity. \begin{code} manifestArity :: CoreExpr -> Arity --- ^ manifestArity sees how many leading value lambdas there are +-- ^ manifestArity sees how many leading value lambdas there are, +-- after looking through casts manifestArity (Lam v e) | isId v = 1 + manifestArity e | otherwise = manifestArity e manifestArity (Tick t e) | not (tickishIsCode t) = manifestArity e diff --git a/compiler/simplCore/SimplUtils.lhs b/compiler/simplCore/SimplUtils.lhs index bde7b6b..a3042a7 100644 --- a/compiler/simplCore/SimplUtils.lhs +++ b/compiler/simplCore/SimplUtils.lhs @@ -1190,15 +1190,14 @@ because the latter is not well-kinded. \begin{code} tryEtaExpandRhs :: SimplEnv -> OutId -> OutExpr -> SimplM (Arity, OutExpr) -- See Note [Eta-expanding at let bindings] --- and Note [Eta expansion to manifest arity] tryEtaExpandRhs env bndr rhs = do { dflags <- getDynFlags ; (new_arity, new_rhs) <- try_expand dflags - ; WARN( new_arity < old_arity, - (ptext (sLit "Arity decrease:") <+> (ppr bndr <+> ppr old_arity - <+> ppr new_arity) $$ ppr new_rhs) ) - -- Note [Arity decrease] + ; WARN( new_arity < old_id_arity, + (ptext (sLit "Arity decrease:") <+> (ppr bndr <+> ppr old_id_arity + <+> ppr old_arity <+> ppr new_arity) $$ ppr new_rhs) ) + -- Note [Arity decrease] in Simplify return (new_arity, new_rhs) } where try_expand dflags @@ -1209,14 +1208,14 @@ tryEtaExpandRhs env bndr rhs , let new_arity1 = findRhsArity dflags bndr rhs old_arity new_arity2 = idCallArity bndr new_arity = max new_arity1 new_arity2 - , new_arity > manifest_arity -- And the curent manifest arity isn't enough + , new_arity > old_arity -- And the curent manifest arity isn't enough = do { tick (EtaExpansion bndr) ; return (new_arity, etaExpand new_arity rhs) } | otherwise - = return (manifest_arity, rhs) + = return (old_arity, rhs) - manifest_arity = manifestArity rhs - old_arity = idArity bndr + old_arity = exprArity rhs -- See Note [Do not expand eta-expand PAPs] + old_id_arity = idArity bndr \end{code} Note [Eta-expanding at let bindings] @@ -1225,7 +1224,7 @@ We now eta expand at let-bindings, which is where the payoff comes. The most significant thing is that we can do a simple arity analysis (in CoreArity.findRhsArity), which we can't do for free-floating lambdas -One useful consequence is this example: +One useful consequence of not eta-expanding lambdas is this example: genMap :: C a => ... {-# INLINE genMap #-} genMap f xs = ... @@ -1235,7 +1234,7 @@ One useful consequence is this example: myMap = genMap Notice that 'genMap' should only inline if applied to two arguments. -In the InlineRule for myMap we'll have the unfolding +In the stable unfolding for myMap we'll have the unfolding (\d -> genMap Int (..d..)) We do not want to eta-expand to (\d f xs -> genMap Int (..d..) f xs) @@ -1243,6 +1242,29 @@ because then 'genMap' will inline, and it really shouldn't: at least as far as the programmer is concerned, it's not applied to two arguments! +Note [Do not eta-expand PAPs] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +We used to have old_arity = manifestArity rhs, which meant that we +would eta-expand even PAPs. But this gives no particular advantage, +and can lead to a massive blow-up in code size, exhibited by Trac #9020. +Suppose we have a PAP + foo :: IO () + foo = returnIO () +Then we can eta-expand do + foo = (\eta. (returnIO () |> sym g) eta) |> g +where + g :: IO () ~ State# RealWorld -> (# State# RealWorld, () #) + +But there is really no point in doing this, and it generates masses of +coercions and whatnot that eventually disappear again. For T9020, GHC +allocated 6.6G beore, and 0.8G afterwards; and residency dropped from +1.8G to 45M. + +But note that this won't eta-expand, say + f = \g -> map g +Does it matter not eta-expanding such functions? I'm not sure. Perhaps +strictness analysis will have less to bite on? + %************************************************************************ %* * diff --git a/testsuite/tests/simplCore/should_compile/simpl015.hs b/testsuite/tests/perf/compiler/T9020.hs similarity index 100% copy from testsuite/tests/simplCore/should_compile/simpl015.hs copy to testsuite/tests/perf/compiler/T9020.hs diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 2f4151f..2bff1c7 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -407,3 +407,11 @@ test('T6048', # 05/03/2014 110646312 amd64/Linux Call Arity became more elaborate ], compile,['']) + +test('T9020', + [ only_ways(['optasm']), + compiler_stats_num_field('bytes allocated', + [(wordsize(32), 40000000, 10), + (wordsize(64), 795469104, 10)]) + ], + compile,['']) diff --git a/testsuite/tests/simplCore/should_compile/simpl015.hs b/testsuite/tests/perf/compiler/simpl015.hs similarity index 100% rename from testsuite/tests/simplCore/should_compile/simpl015.hs rename to testsuite/tests/perf/compiler/simpl015.hs diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index 7239ffc..616b6cc 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -15,7 +15,6 @@ test('simpl011', normal, compile, ['']) test('simpl012', normal, compile, ['']) test('simpl013', normal, compile, ['']) test('simpl014', normal, compile, ['']) -test('simpl015', only_ways(['optasm']), compile, ['']) test('simpl016', normal, compile, ['-dsuppress-uniques']) test('simpl017', normal, compile_fail, ['']) test('simpl018', normal, compile, ['']) From git at git.haskell.org Thu Apr 24 11:42:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 24 Apr 2014 11:42:57 +0000 (UTC) Subject: [commit: ghc] master: Some typos in comments (4ceb5de) Message-ID: <20140424114257.B861A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4ceb5dec42ff8d17e24ed80d0265eb8fb60dd804/ghc >--------------------------------------------------------------- commit 4ceb5dec42ff8d17e24ed80d0265eb8fb60dd804 Author: Gabor Greif Date: Thu Apr 24 12:27:50 2014 +0200 Some typos in comments >--------------------------------------------------------------- 4ceb5dec42ff8d17e24ed80d0265eb8fb60dd804 compiler/simplCore/SimplUtils.lhs | 2 +- compiler/typecheck/TcDefaults.lhs | 2 +- testsuite/tests/perf/should_run/T149_A.hs | 2 +- testsuite/tests/perf/should_run/T149_B.hs | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/compiler/simplCore/SimplUtils.lhs b/compiler/simplCore/SimplUtils.lhs index a3042a7..59e5d4a 100644 --- a/compiler/simplCore/SimplUtils.lhs +++ b/compiler/simplCore/SimplUtils.lhs @@ -1208,7 +1208,7 @@ tryEtaExpandRhs env bndr rhs , let new_arity1 = findRhsArity dflags bndr rhs old_arity new_arity2 = idCallArity bndr new_arity = max new_arity1 new_arity2 - , new_arity > old_arity -- And the curent manifest arity isn't enough + , new_arity > old_arity -- And the current manifest arity isn't enough = do { tick (EtaExpansion bndr) ; return (new_arity, etaExpand new_arity rhs) } | otherwise diff --git a/compiler/typecheck/TcDefaults.lhs b/compiler/typecheck/TcDefaults.lhs index d05a948..a096e50 100644 --- a/compiler/typecheck/TcDefaults.lhs +++ b/compiler/typecheck/TcDefaults.lhs @@ -39,7 +39,7 @@ tcDefaults :: [LDefaultDecl Name] tcDefaults [] = getDeclaredDefaultTys -- No default declaration, so get the -- default types from the envt; - -- i.e. use the curent ones + -- i.e. use the current ones -- (the caller will put them back there) -- It's important not to return defaultDefaultTys here (which -- we used to do) because in a TH program, tcDefaults [] is called diff --git a/testsuite/tests/perf/should_run/T149_A.hs b/testsuite/tests/perf/should_run/T149_A.hs index dc24f4c..22ec276 100644 --- a/testsuite/tests/perf/should_run/T149_A.hs +++ b/testsuite/tests/perf/should_run/T149_A.hs @@ -2,7 +2,7 @@ module Main (main) where -- See Trac #149 --- Curently (with GHC 7.0) the CSE works, just, +-- Currently (with GHC 7.0) the CSE works, just, -- but it's delicate. diff --git a/testsuite/tests/perf/should_run/T149_B.hs b/testsuite/tests/perf/should_run/T149_B.hs index ef5b9c5..514fd16 100644 --- a/testsuite/tests/perf/should_run/T149_B.hs +++ b/testsuite/tests/perf/should_run/T149_B.hs @@ -2,7 +2,7 @@ module Main (main) where -- See Trac #149 --- Curently (with GHC 7.0) the CSE works, just, +-- Currently (with GHC 7.0) the CSE works, just, -- but it's delicate. From git at git.haskell.org Fri Apr 25 17:11:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 25 Apr 2014 17:11:15 +0000 (UTC) Subject: [commit: ghc] master: Drop `template-haskell`'s build-dep on `containers` (07388af) Message-ID: <20140425171115.117F12406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/07388af843ad61757207a54d75ab336606beed4f/ghc >--------------------------------------------------------------- commit 07388af843ad61757207a54d75ab336606beed4f Author: Herbert Valerio Riedel Date: Thu Apr 24 09:05:45 2014 +0200 Drop `template-haskell`'s build-dep on `containers` This is an attempt to address https://github.com/haskell/cabal/issues/1811 by replicating the less than 100 lines of code actually used from the containers package into an internal non-exposed `template-haskell` module. Moreover, `template-haskell` does not expose the `Map` type, so this change should have no visible effect on the public API. It may turn out that `Data.Map` is not necessary and that even a simple list-based associative list (`Prelude.lookup`) may suffice. However, in order to avoid any regressions, this commit takes the safe route and just clones `Data.Map` for now. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 07388af843ad61757207a54d75ab336606beed4f .../Language/Haskell/TH/Lib/Map.hs | 108 ++++++++++++++++++++ .../template-haskell/Language/Haskell/TH/PprLib.hs | 4 +- libraries/template-haskell/template-haskell.cabal | 4 +- testsuite/tests/th/TH_Roles2.stderr | 13 ++- 4 files changed, 119 insertions(+), 10 deletions(-) diff --git a/libraries/template-haskell/Language/Haskell/TH/Lib/Map.hs b/libraries/template-haskell/Language/Haskell/TH/Lib/Map.hs new file mode 100644 index 0000000..ac24151 --- /dev/null +++ b/libraries/template-haskell/Language/Haskell/TH/Lib/Map.hs @@ -0,0 +1,108 @@ +{-# LANGUAGE BangPatterns #-} + +-- This is a non-exposed internal module +-- +-- The code in this module has been ripped from containers-0.5.5.1:Data.Map.Base [1] almost +-- verbatimely to avoid a dependency of 'template-haskell' on the containers package. +-- +-- [1] see https://hackage.haskell.org/package/containers-0.5.5.1 +-- +-- The original code is BSD-licensed and copyrighted by Daan Leijen, Andriy Palamarchuk, et al. + +module Language.Haskell.TH.Lib.Map + ( Map + , empty + , insert + , Language.Haskell.TH.Lib.Map.lookup + ) where + +data Map k a = Bin {-# UNPACK #-} !Size !k a !(Map k a) !(Map k a) + | Tip + +type Size = Int + +empty :: Map k a +empty = Tip +{-# INLINE empty #-} + +singleton :: k -> a -> Map k a +singleton k x = Bin 1 k x Tip Tip +{-# INLINE singleton #-} + +size :: Map k a -> Int +size Tip = 0 +size (Bin sz _ _ _ _) = sz +{-# INLINE size #-} + +lookup :: Ord k => k -> Map k a -> Maybe a +lookup = go + where + go _ Tip = Nothing + go !k (Bin _ kx x l r) = case compare k kx of + LT -> go k l + GT -> go k r + EQ -> Just x +{-# INLINABLE lookup #-} + + +insert :: Ord k => k -> a -> Map k a -> Map k a +insert = go + where + go :: Ord k => k -> a -> Map k a -> Map k a + go !kx x Tip = singleton kx x + go !kx x (Bin sz ky y l r) = + case compare kx ky of + LT -> balanceL ky y (go kx x l) r + GT -> balanceR ky y l (go kx x r) + EQ -> Bin sz kx x l r +{-# INLINABLE insert #-} + +balanceL :: k -> a -> Map k a -> Map k a -> Map k a +balanceL k x l r = case r of + Tip -> case l of + Tip -> Bin 1 k x Tip Tip + (Bin _ _ _ Tip Tip) -> Bin 2 k x l Tip + (Bin _ lk lx Tip (Bin _ lrk lrx _ _)) -> Bin 3 lrk lrx (Bin 1 lk lx Tip Tip) (Bin 1 k x Tip Tip) + (Bin _ lk lx ll@(Bin _ _ _ _ _) Tip) -> Bin 3 lk lx ll (Bin 1 k x Tip Tip) + (Bin ls lk lx ll@(Bin lls _ _ _ _) lr@(Bin lrs lrk lrx lrl lrr)) + | lrs < ratio*lls -> Bin (1+ls) lk lx ll (Bin (1+lrs) k x lr Tip) + | otherwise -> Bin (1+ls) lrk lrx (Bin (1+lls+size lrl) lk lx ll lrl) (Bin (1+size lrr) k x lrr Tip) + + (Bin rs _ _ _ _) -> case l of + Tip -> Bin (1+rs) k x Tip r + + (Bin ls lk lx ll lr) + | ls > delta*rs -> case (ll, lr) of + (Bin lls _ _ _ _, Bin lrs lrk lrx lrl lrr) + | lrs < ratio*lls -> Bin (1+ls+rs) lk lx ll (Bin (1+rs+lrs) k x lr r) + | otherwise -> Bin (1+ls+rs) lrk lrx (Bin (1+lls+size lrl) lk lx ll lrl) (Bin (1+rs+size lrr) k x lrr r) + (_, _) -> error "Failure in Data.Map.balanceL" + | otherwise -> Bin (1+ls+rs) k x l r +{-# NOINLINE balanceL #-} + +balanceR :: k -> a -> Map k a -> Map k a -> Map k a +balanceR k x l r = case l of + Tip -> case r of + Tip -> Bin 1 k x Tip Tip + (Bin _ _ _ Tip Tip) -> Bin 2 k x Tip r + (Bin _ rk rx Tip rr@(Bin _ _ _ _ _)) -> Bin 3 rk rx (Bin 1 k x Tip Tip) rr + (Bin _ rk rx (Bin _ rlk rlx _ _) Tip) -> Bin 3 rlk rlx (Bin 1 k x Tip Tip) (Bin 1 rk rx Tip Tip) + (Bin rs rk rx rl@(Bin rls rlk rlx rll rlr) rr@(Bin rrs _ _ _ _)) + | rls < ratio*rrs -> Bin (1+rs) rk rx (Bin (1+rls) k x Tip rl) rr + | otherwise -> Bin (1+rs) rlk rlx (Bin (1+size rll) k x Tip rll) (Bin (1+rrs+size rlr) rk rx rlr rr) + + (Bin ls _ _ _ _) -> case r of + Tip -> Bin (1+ls) k x l Tip + + (Bin rs rk rx rl rr) + | rs > delta*ls -> case (rl, rr) of + (Bin rls rlk rlx rll rlr, Bin rrs _ _ _ _) + | rls < ratio*rrs -> Bin (1+ls+rs) rk rx (Bin (1+ls+rls) k x l rl) rr + | otherwise -> Bin (1+ls+rs) rlk rlx (Bin (1+ls+size rll) k x l rll) (Bin (1+rrs+size rlr) rk rx rlr rr) + (_, _) -> error "Failure in Data.Map.balanceR" + | otherwise -> Bin (1+ls+rs) k x l r +{-# NOINLINE balanceR #-} + +delta,ratio :: Int +delta = 3 +ratio = 2 diff --git a/libraries/template-haskell/Language/Haskell/TH/PprLib.hs b/libraries/template-haskell/Language/Haskell/TH/PprLib.hs index 93e37ce..c4b0b77 100644 --- a/libraries/template-haskell/Language/Haskell/TH/PprLib.hs +++ b/libraries/template-haskell/Language/Haskell/TH/PprLib.hs @@ -40,8 +40,8 @@ import Language.Haskell.TH.Syntax import qualified Text.PrettyPrint as HPJ import Control.Applicative (Applicative(..)) import Control.Monad (liftM, liftM2, ap) -import Data.Map ( Map ) -import qualified Data.Map as Map ( lookup, insert, empty ) +import Language.Haskell.TH.Lib.Map ( Map ) +import qualified Language.Haskell.TH.Lib.Map as Map ( lookup, insert, empty ) import GHC.Base (Int(..)) infixl 6 <> diff --git a/libraries/template-haskell/template-haskell.cabal b/libraries/template-haskell/template-haskell.cabal index ca0e344..fb8dbd7 100644 --- a/libraries/template-haskell/template-haskell.cabal +++ b/libraries/template-haskell/template-haskell.cabal @@ -42,9 +42,11 @@ Library Language.Haskell.TH.Quote Language.Haskell.TH.Syntax + other-modules: + Language.Haskell.TH.Lib.Map + build-depends: base == 4.7.*, - containers == 0.5.*, pretty == 1.1.* -- We need to set the package name to template-haskell (without a diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr index a4526e1..bd44d12 100644 --- a/testsuite/tests/th/TH_Roles2.stderr +++ b/testsuite/tests/th/TH_Roles2.stderr @@ -2,15 +2,14 @@ TYPE SIGNATURES TYPE CONSTRUCTORS T :: k -> * data T (k::BOX) (a::k) - No C type associated - Roles: [nominal, representational] - RecFlag NonRecursive, Not promotable - = - FamilyInstance: none + No C type associated + Roles: [nominal, representational] + RecFlag NonRecursive, Not promotable + = + FamilyInstance: none COERCION AXIOMS Dependent modules: [] -Dependent packages: [array-0.5.0.0, base, containers-0.5.5.1, - deepseq-1.3.0.2, ghc-prim, integer-gmp, pretty-1.1.1.1, +Dependent packages: [base, ghc-prim, integer-gmp, pretty-1.1.1.1, template-haskell] ==================== Typechecker ==================== From git at git.haskell.org Sun Apr 27 11:45:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 27 Apr 2014 11:45:32 +0000 (UTC) Subject: [commit: ghc] master: rts: Fix possible int overflow in resize_nursery (111b845) Message-ID: <20140427114532.E96922406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/111b8454cc1b64da5b9816b89d79f44a8ae24355/ghc >--------------------------------------------------------------- commit 111b8454cc1b64da5b9816b89d79f44a8ae24355 Author: Austin Seipp Date: Wed Apr 23 03:41:44 2014 -0500 rts: Fix possible int overflow in resize_nursery n_capabilities is declared as unsigned int (32bit), and so multiplication is 32-bit before being stored in a 64bit integer (StgWord). Instead, cast n_capabilities to StgWord before multiplying. Discovered by Coverity. CID 43164. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 111b8454cc1b64da5b9816b89d79f44a8ae24355 rts/sm/GC.c | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/rts/sm/GC.c b/rts/sm/GC.c index 1ecbaf5..d22a31e 100644 --- a/rts/sm/GC.c +++ b/rts/sm/GC.c @@ -1613,7 +1613,8 @@ resize_generations (void) static void resize_nursery (void) { - const StgWord min_nursery = RtsFlags.GcFlags.minAllocAreaSize * n_capabilities; + const StgWord min_nursery = + RtsFlags.GcFlags.minAllocAreaSize * (StgWord)n_capabilities; if (RtsFlags.GcFlags.generations == 1) { // Two-space collector: From git at git.haskell.org Sun Apr 27 11:45:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 27 Apr 2014 11:45:35 +0000 (UTC) Subject: [commit: ghc] master: rts: Fix potential memory leak in ProfHeap.c (95da409) Message-ID: <20140427114535.AD5CA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/95da409719bab6f92229dc1a632c471e248d2fdd/ghc >--------------------------------------------------------------- commit 95da409719bab6f92229dc1a632c471e248d2fdd Author: Austin Seipp Date: Wed Apr 23 02:14:15 2014 -0500 rts: Fix potential memory leak in ProfHeap.c Discovered by Coverity. CID 43166. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 95da409719bab6f92229dc1a632c471e248d2fdd rts/ProfHeap.c | 1 + 1 file changed, 1 insertion(+) diff --git a/rts/ProfHeap.c b/rts/ProfHeap.c index d21b14a..9079c2b 100644 --- a/rts/ProfHeap.c +++ b/rts/ProfHeap.c @@ -337,6 +337,7 @@ void initProfiling2 (void) debugBelch("Can't open profiling report file %s\n", hp_filename); RtsFlags.ProfFlags.doHeapProfile = 0; + stgFree(prog); return; } } From git at git.haskell.org Sun Apr 27 11:45:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 27 Apr 2014 11:45:38 +0000 (UTC) Subject: [commit: ghc] master: coverity: Suppress some time-of-check-time-of-use reports (6d11a0e) Message-ID: <20140427114538.2F2F22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6d11a0e1400e44e16e0ee7734279c67619442a1d/ghc >--------------------------------------------------------------- commit 6d11a0e1400e44e16e0ee7734279c67619442a1d Author: Austin Seipp Date: Sun Apr 27 04:19:24 2014 -0500 coverity: Suppress some time-of-check-time-of-use reports CID 43178 Signed-off-by: Austin Seipp >--------------------------------------------------------------- 6d11a0e1400e44e16e0ee7734279c67619442a1d rts/Linker.c | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/rts/Linker.c b/rts/Linker.c index ab235e9..1b0d48f 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -2810,6 +2810,7 @@ loadObj( pathchar *path ) /* Check that we haven't already loaded this object. Ignore requests to load multiple times */ + if (isAlreadyLoaded(path)) { IF_DEBUG(linker, debugBelch("ignoring repeated load of %" PATH_FMT "\n", path)); @@ -2828,8 +2829,10 @@ loadObj( pathchar *path ) /* On many architectures malloc'd memory isn't executable, so we need to use mmap. */ #if defined(openbsd_HOST_OS) + /* coverity[toctou] */ fd = open(path, O_RDONLY, S_IRUSR); #else + /* coverity[toctou] */ fd = open(path, O_RDONLY); #endif if (fd == -1) @@ -2841,6 +2844,7 @@ loadObj( pathchar *path ) #else /* !USE_MMAP */ /* load the image into memory */ + /* coverity[toctou] */ f = pathopen(path, WSTR("rb")); if (!f) barf("loadObj: can't read `%" PATH_FMT "'", path); From git at git.haskell.org Sun Apr 27 11:45:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 27 Apr 2014 11:45:40 +0000 (UTC) Subject: [commit: ghc] master: Check return value of sigaction (f2595fd) Message-ID: <20140427114541.1DC292406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f2595fd9d03803874df792072292d792a2c03bce/ghc >--------------------------------------------------------------- commit f2595fd9d03803874df792072292d792a2c03bce Author: Nicolas Trangez Date: Wed Apr 23 20:06:15 2014 +0200 Check return value of sigaction Issue discovered by Coverity scan, CID 43142. Signed-off-by: Austin Seipp >--------------------------------------------------------------- f2595fd9d03803874df792072292d792a2c03bce rts/posix/Signals.c | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/rts/posix/Signals.c b/rts/posix/Signals.c index 01d5347..f4a8341 100644 --- a/rts/posix/Signals.c +++ b/rts/posix/Signals.c @@ -574,7 +574,9 @@ set_sigtstp_action (rtsBool handle) } sa.sa_flags = 0; sigemptyset(&sa.sa_mask); - sigaction(SIGTSTP, &sa, NULL); + if (sigaction(SIGTSTP, &sa, NULL) != 0) { + sysErrorBelch("warning: failed to install SIGTSTP handler"); + } } /* ----------------------------------------------------------------------------- From git at git.haskell.org Sun Apr 27 11:45:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 27 Apr 2014 11:45:43 +0000 (UTC) Subject: [commit: ghc] master: Fix potential out-of-bound memory access (fa0cbd2) Message-ID: <20140427114543.93B0A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fa0cbd297ba12e02273efcaa5f52fe76e10b7126/ghc >--------------------------------------------------------------- commit fa0cbd297ba12e02273efcaa5f52fe76e10b7126 Author: Nicolas Trangez Date: Wed Apr 23 20:27:04 2014 +0200 Fix potential out-of-bound memory access Issue discovered by Coverity scan, CID 43165. Signed-off-by: Austin Seipp >--------------------------------------------------------------- fa0cbd297ba12e02273efcaa5f52fe76e10b7126 utils/hp2ps/HpFile.c | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/utils/hp2ps/HpFile.c b/utils/hp2ps/HpFile.c index 86cbfb2..bdbf201 100644 --- a/utils/hp2ps/HpFile.c +++ b/utils/hp2ps/HpFile.c @@ -332,7 +332,7 @@ GetHpTok(FILE *infp) * "thefloatish"). */ -static char numberstring[ NUMBER_LENGTH - 1 ]; +static char numberstring[ NUMBER_LENGTH + 1 ]; token GetNumber(FILE *infp) @@ -350,7 +350,7 @@ GetNumber(FILE *infp) ch = getc(infp); } - ASSERT(i < NUMBER_LENGTH); /* did not overflow */ + ASSERT(i <= NUMBER_LENGTH); /* did not overflow */ numberstring[ i ] = '\0'; From git at git.haskell.org Sun Apr 27 11:45:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 27 Apr 2014 11:45:46 +0000 (UTC) Subject: [commit: ghc] master: Check correct variable for NULL (6ed7123) Message-ID: <20140427114546.2CFCB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6ed7123dcc24c343a1ece85c7aa72ac1c34e6aff/ghc >--------------------------------------------------------------- commit 6ed7123dcc24c343a1ece85c7aa72ac1c34e6aff Author: Nicolas Trangez Date: Wed Apr 23 20:37:51 2014 +0200 Check correct variable for NULL Issue discovered by Coverity scan, CID 43163. This should fix CID 43172 as a side-effect as well. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 6ed7123dcc24c343a1ece85c7aa72ac1c34e6aff rts/Hpc.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/Hpc.c b/rts/Hpc.c index c4ff8d3..47d1acd 100644 --- a/rts/Hpc.c +++ b/rts/Hpc.c @@ -151,7 +151,7 @@ readTix(void) { ws(); lookup = lookupHashTable(moduleHash, (StgWord)tmpModule->modName); - if (tmpModule == NULL) { + if (lookup == NULL) { debugTrace(DEBUG_hpc,"readTix: new HpcModuleInfo for %s", tmpModule->modName); insertHashTable(moduleHash, (StgWord)tmpModule->modName, tmpModule); From git at git.haskell.org Sun Apr 27 11:45:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 27 Apr 2014 11:45:48 +0000 (UTC) Subject: [commit: ghc] master: Fix memleak in hp2ps (f17dcf0) Message-ID: <20140427114548.BE5962406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f17dcf09a5797bbefe22aef7d4c508d1672484df/ghc >--------------------------------------------------------------- commit f17dcf09a5797bbefe22aef7d4c508d1672484df Author: Nicolas Trangez Date: Wed Apr 23 21:14:23 2014 +0200 Fix memleak in hp2ps Issue discovered by Coverity scan, CID 43167. Signed-off-by: Austin Seipp >--------------------------------------------------------------- f17dcf09a5797bbefe22aef7d4c508d1672484df utils/hp2ps/HpFile.c | 2 ++ 1 file changed, 2 insertions(+) diff --git a/utils/hp2ps/HpFile.c b/utils/hp2ps/HpFile.c index bdbf201..5ee9cc2 100644 --- a/utils/hp2ps/HpFile.c +++ b/utils/hp2ps/HpFile.c @@ -423,6 +423,8 @@ GetString(FILE *infp) stringbuffer[i] = '\0'; thestring = copystring(stringbuffer); + free(stringbuffer); + ASSERT(ch == '\"'); ch = getc(infp); /* skip the '\"' that terminates the string */ From git at git.haskell.org Sun Apr 27 14:44:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 27 Apr 2014 14:44:15 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: rts: Fix potential memory leak in ProfHeap.c (8640d7b) Message-ID: <20140427144415.6BBA82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/8640d7b2a636702079878cd9cfb9b9349457c1e0/ghc >--------------------------------------------------------------- commit 8640d7b2a636702079878cd9cfb9b9349457c1e0 Author: Austin Seipp Date: Wed Apr 23 02:14:15 2014 -0500 rts: Fix potential memory leak in ProfHeap.c Discovered by Coverity. CID 43166. Signed-off-by: Austin Seipp (cherry picked from commit 95da409719bab6f92229dc1a632c471e248d2fdd) >--------------------------------------------------------------- 8640d7b2a636702079878cd9cfb9b9349457c1e0 rts/ProfHeap.c | 1 + 1 file changed, 1 insertion(+) diff --git a/rts/ProfHeap.c b/rts/ProfHeap.c index 6d78886..350f73b 100644 --- a/rts/ProfHeap.c +++ b/rts/ProfHeap.c @@ -337,6 +337,7 @@ void initProfiling2 (void) debugBelch("Can't open profiling report file %s\n", hp_filename); RtsFlags.ProfFlags.doHeapProfile = 0; + stgFree(prog); return; } } From git at git.haskell.org Sun Apr 27 14:44:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 27 Apr 2014 14:44:17 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: rts: Fix possible int overflow in resize_nursery (53c8e6e) Message-ID: <20140427144417.C28462406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/53c8e6e3b7fc8266c8843b7fa8f1e22d4413bc81/ghc >--------------------------------------------------------------- commit 53c8e6e3b7fc8266c8843b7fa8f1e22d4413bc81 Author: Austin Seipp Date: Wed Apr 23 03:41:44 2014 -0500 rts: Fix possible int overflow in resize_nursery n_capabilities is declared as unsigned int (32bit), and so multiplication is 32-bit before being stored in a 64bit integer (StgWord). Instead, cast n_capabilities to StgWord before multiplying. Discovered by Coverity. CID 43164. Signed-off-by: Austin Seipp (cherry picked from commit 111b8454cc1b64da5b9816b89d79f44a8ae24355) >--------------------------------------------------------------- 53c8e6e3b7fc8266c8843b7fa8f1e22d4413bc81 rts/sm/GC.c | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/rts/sm/GC.c b/rts/sm/GC.c index 1ecbaf5..d22a31e 100644 --- a/rts/sm/GC.c +++ b/rts/sm/GC.c @@ -1613,7 +1613,8 @@ resize_generations (void) static void resize_nursery (void) { - const StgWord min_nursery = RtsFlags.GcFlags.minAllocAreaSize * n_capabilities; + const StgWord min_nursery = + RtsFlags.GcFlags.minAllocAreaSize * (StgWord)n_capabilities; if (RtsFlags.GcFlags.generations == 1) { // Two-space collector: From git at git.haskell.org Sun Apr 27 14:44:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 27 Apr 2014 14:44:20 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Check return value of sigaction (2439da0) Message-ID: <20140427144420.DAE222406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/2439da08fb3525f94d340132dc698c36a102ab28/ghc >--------------------------------------------------------------- commit 2439da08fb3525f94d340132dc698c36a102ab28 Author: Nicolas Trangez Date: Wed Apr 23 20:06:15 2014 +0200 Check return value of sigaction Issue discovered by Coverity scan, CID 43142. Signed-off-by: Austin Seipp (cherry picked from commit f2595fd9d03803874df792072292d792a2c03bce) >--------------------------------------------------------------- 2439da08fb3525f94d340132dc698c36a102ab28 rts/posix/Signals.c | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/rts/posix/Signals.c b/rts/posix/Signals.c index 01d5347..f4a8341 100644 --- a/rts/posix/Signals.c +++ b/rts/posix/Signals.c @@ -574,7 +574,9 @@ set_sigtstp_action (rtsBool handle) } sa.sa_flags = 0; sigemptyset(&sa.sa_mask); - sigaction(SIGTSTP, &sa, NULL); + if (sigaction(SIGTSTP, &sa, NULL) != 0) { + sysErrorBelch("warning: failed to install SIGTSTP handler"); + } } /* ----------------------------------------------------------------------------- From git at git.haskell.org Sun Apr 27 14:44:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 27 Apr 2014 14:44:23 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Fix potential out-of-bound memory access (07fb613) Message-ID: <20140427144423.E504F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/07fb613bf599aa9237b1ef73861706b447173d38/ghc >--------------------------------------------------------------- commit 07fb613bf599aa9237b1ef73861706b447173d38 Author: Nicolas Trangez Date: Wed Apr 23 20:27:04 2014 +0200 Fix potential out-of-bound memory access Issue discovered by Coverity scan, CID 43165. Signed-off-by: Austin Seipp (cherry picked from commit fa0cbd297ba12e02273efcaa5f52fe76e10b7126) >--------------------------------------------------------------- 07fb613bf599aa9237b1ef73861706b447173d38 utils/hp2ps/HpFile.c | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/utils/hp2ps/HpFile.c b/utils/hp2ps/HpFile.c index 86cbfb2..bdbf201 100644 --- a/utils/hp2ps/HpFile.c +++ b/utils/hp2ps/HpFile.c @@ -332,7 +332,7 @@ GetHpTok(FILE *infp) * "thefloatish"). */ -static char numberstring[ NUMBER_LENGTH - 1 ]; +static char numberstring[ NUMBER_LENGTH + 1 ]; token GetNumber(FILE *infp) @@ -350,7 +350,7 @@ GetNumber(FILE *infp) ch = getc(infp); } - ASSERT(i < NUMBER_LENGTH); /* did not overflow */ + ASSERT(i <= NUMBER_LENGTH); /* did not overflow */ numberstring[ i ] = '\0'; From git at git.haskell.org Sun Apr 27 14:44:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 27 Apr 2014 14:44:26 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Check correct variable for NULL (27337de) Message-ID: <20140427144426.ECE382406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/27337de5999e43807131acb290447e4ab8aa334c/ghc >--------------------------------------------------------------- commit 27337de5999e43807131acb290447e4ab8aa334c Author: Nicolas Trangez Date: Wed Apr 23 20:37:51 2014 +0200 Check correct variable for NULL Issue discovered by Coverity scan, CID 43163. This should fix CID 43172 as a side-effect as well. Signed-off-by: Austin Seipp (cherry picked from commit 6ed7123dcc24c343a1ece85c7aa72ac1c34e6aff) >--------------------------------------------------------------- 27337de5999e43807131acb290447e4ab8aa334c rts/Hpc.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/Hpc.c b/rts/Hpc.c index c4ff8d3..47d1acd 100644 --- a/rts/Hpc.c +++ b/rts/Hpc.c @@ -151,7 +151,7 @@ readTix(void) { ws(); lookup = lookupHashTable(moduleHash, (StgWord)tmpModule->modName); - if (tmpModule == NULL) { + if (lookup == NULL) { debugTrace(DEBUG_hpc,"readTix: new HpcModuleInfo for %s", tmpModule->modName); insertHashTable(moduleHash, (StgWord)tmpModule->modName, tmpModule); From git at git.haskell.org Sun Apr 27 14:44:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 27 Apr 2014 14:44:29 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Fix memleak in hp2ps (e6f48ad) Message-ID: <20140427144429.895AC2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/e6f48ad41402a5aeed4e0569c323f5b8a567563b/ghc >--------------------------------------------------------------- commit e6f48ad41402a5aeed4e0569c323f5b8a567563b Author: Nicolas Trangez Date: Wed Apr 23 21:14:23 2014 +0200 Fix memleak in hp2ps Issue discovered by Coverity scan, CID 43167. Signed-off-by: Austin Seipp (cherry picked from commit f17dcf09a5797bbefe22aef7d4c508d1672484df) >--------------------------------------------------------------- e6f48ad41402a5aeed4e0569c323f5b8a567563b utils/hp2ps/HpFile.c | 2 ++ 1 file changed, 2 insertions(+) diff --git a/utils/hp2ps/HpFile.c b/utils/hp2ps/HpFile.c index bdbf201..5ee9cc2 100644 --- a/utils/hp2ps/HpFile.c +++ b/utils/hp2ps/HpFile.c @@ -423,6 +423,8 @@ GetString(FILE *infp) stringbuffer[i] = '\0'; thestring = copystring(stringbuffer); + free(stringbuffer); + ASSERT(ch == '\"'); ch = getc(infp); /* skip the '\"' that terminates the string */ From git at git.haskell.org Sun Apr 27 17:21:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 27 Apr 2014 17:21:07 +0000 (UTC) Subject: [commit: ghc] master: Don't require mk/config.mk for all cleanup targets (fa5ac96) Message-ID: <20140427172108.023C62406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fa5ac96970f99fe463d78ab424514ce28741804a/ghc >--------------------------------------------------------------- commit fa5ac96970f99fe463d78ab424514ce28741804a Author: Herbert Valerio Riedel Date: Sun Apr 27 19:15:16 2014 +0200 Don't require mk/config.mk for all cleanup targets `make clean` did already ignore a missing mk/config.mk, but `make distclean` and `make maintainer-clean` didn't. This commit rectifies this oversight. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- fa5ac96970f99fe463d78ab424514ce28741804a Makefile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Makefile b/Makefile index e5a7fb8..c4cce6d 100644 --- a/Makefile +++ b/Makefile @@ -33,7 +33,7 @@ default : all help: @cat MAKEHELP -ifneq "$(filter clean help,$(MAKECMDGOALS))" "" +ifneq "$(filter maintainer-clean distclean clean help,$(MAKECMDGOALS))" "" -include mk/config.mk else include mk/config.mk From git at git.haskell.org Mon Apr 28 00:41:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 00:41:05 +0000 (UTC) Subject: [commit: ghc] branch 'wip/ext-solver' created Message-ID: <20140428004105.B8A6E2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/ext-solver Referencing: f17dcf09a5797bbefe22aef7d4c508d1672484df From git at git.haskell.org Mon Apr 28 00:42:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 00:42:27 +0000 (UTC) Subject: [commit: ghc] wip/ext-solver: Code for connecting an SMT solver with the type-checker. (d2917c5) Message-ID: <20140428004227.C596E2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ext-solver Link : http://ghc.haskell.org/trac/ghc/changeset/d2917c5bffced002c0a5b0c467298f2540166d62/ghc >--------------------------------------------------------------- commit d2917c5bffced002c0a5b0c467298f2540166d62 Author: Iavor S. Diatchki Date: Sun Apr 27 17:42:18 2014 -0700 Code for connecting an SMT solver with the type-checker. >--------------------------------------------------------------- d2917c5bffced002c0a5b0c467298f2540166d62 compiler/typecheck/TcTypeNats.hs | 383 +++++++++++++++++++++++++++++++++++++- 1 file changed, 379 insertions(+), 4 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d2917c5bffced002c0a5b0c467298f2540166d62 From git at git.haskell.org Mon Apr 28 07:56:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 07:56:59 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #9036 (c4e9f24) Message-ID: <20140428075659.5711F2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c4e9f243398942499c9f5e21318e6ceb048d5880/ghc >--------------------------------------------------------------- commit c4e9f243398942499c9f5e21318e6ceb048d5880 Author: Simon Peyton Jones Date: Mon Apr 28 08:55:32 2014 +0100 Test Trac #9036 >--------------------------------------------------------------- c4e9f243398942499c9f5e21318e6ceb048d5880 testsuite/tests/indexed-types/should_fail/T9036.hs | 18 ++++++++++++++++++ .../tests/indexed-types/should_fail/T9036.stderr | 12 ++++++++++++ testsuite/tests/indexed-types/should_fail/all.T | 1 + 3 files changed, 31 insertions(+) diff --git a/testsuite/tests/indexed-types/should_fail/T9036.hs b/testsuite/tests/indexed-types/should_fail/T9036.hs new file mode 100644 index 0000000..550adb4 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T9036.hs @@ -0,0 +1,18 @@ +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE TypeFamilies #-} + + +module T9036 where + +class UncurryM t where + type GetMonad t :: * -> * + +class Curry a b where + type Curried a b :: * + +gSimple :: String -> String -> [String] +gSimple = simpleLogger (return ()) + +simpleLogger :: Maybe (GetMonad t after) -> t `Curried` [t] +simpleLogger _ _ = undefined diff --git a/testsuite/tests/indexed-types/should_fail/T9036.stderr b/testsuite/tests/indexed-types/should_fail/T9036.stderr new file mode 100644 index 0000000..2df53c7 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T9036.stderr @@ -0,0 +1,12 @@ + +T9036.hs:17:17: + Couldn't match type ?GetMonad t0? with ?GetMonad t? + NB: ?GetMonad? is a type function, and may not be injective + The type variable ?t0? is ambiguous + Expected type: Maybe (GetMonad t after) -> Curried t [t] + Actual type: Maybe (GetMonad t0 after) -> Curried t0 [t0] + In the ambiguity check for: + forall t after. Maybe (GetMonad t after) -> Curried t [t] + To defer the ambiguity check to use sites, enable AllowAmbiguousTypes + In the type signature for ?simpleLogger?: + simpleLogger :: Maybe (GetMonad t after) -> t `Curried` [t] diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T index 54a33cd..003b51d 100644 --- a/testsuite/tests/indexed-types/should_fail/all.T +++ b/testsuite/tests/indexed-types/should_fail/all.T @@ -119,4 +119,5 @@ test('T8129', test('T8368', normal, compile_fail, ['']) test('T8368a', normal, compile_fail, ['']) test('T8518', normal, compile_fail, ['']) +test('T9036', normal, compile_fail, ['']) From git at git.haskell.org Mon Apr 28 08:57:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 08:57:54 +0000 (UTC) Subject: [commit: ghc] branch 'wip/kill-extcore' created Message-ID: <20140428085754.EC0522406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/kill-extcore Referencing: 4852a59875f1dc89c1821871fdabd6fda65b4534 From git at git.haskell.org Mon Apr 28 08:57:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 08:57:58 +0000 (UTC) Subject: [commit: ghc] wip/kill-extcore: Remove external core (4852a59) Message-ID: <20140428085758.9C37D2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/kill-extcore Link : http://ghc.haskell.org/trac/ghc/changeset/4852a59875f1dc89c1821871fdabd6fda65b4534/ghc >--------------------------------------------------------------- commit 4852a59875f1dc89c1821871fdabd6fda65b4534 Author: Austin Seipp Date: Sun Apr 27 21:11:23 2014 -0500 Remove external core Signed-off-by: Austin Seipp >--------------------------------------------------------------- 4852a59875f1dc89c1821871fdabd6fda65b4534 aclocal.m4 | 2 +- compiler/coreSyn/ExternalCore.lhs | 118 -- compiler/coreSyn/MkExternalCore.lhs | 360 ------ compiler/coreSyn/PprExternalCore.lhs | 260 ---- compiler/ghc.cabal.in | 6 - compiler/hsSyn/HsSyn.lhs | 12 +- compiler/iface/TcIface.lhs | 35 +- compiler/main/DriverPhases.hs | 16 +- compiler/main/DriverPipeline.hs | 26 +- compiler/main/DynFlags.hs | 3 +- compiler/main/GHC.hs | 40 +- compiler/main/Hooks.lhs | 2 +- compiler/main/HscMain.hs | 36 +- compiler/parser/LexCore.hs | 115 -- compiler/parser/ParserCore.y | 397 ------ compiler/parser/ParserCoreUtils.hs | 77 -- compiler/typecheck/TcRnDriver.lhs | 129 +- compiler/typecheck/TcRnMonad.lhs | 11 - docs/users_guide/external_core.xml | 1804 ---------------------------- docs/users_guide/flags.xml | 2 +- docs/users_guide/glasgow_exts.xml | 63 - docs/users_guide/ug-book.xml.in | 1 - docs/users_guide/ug-ent.xml.in | 1 - docs/users_guide/using.xml | 38 - ghc.mk | 1 - mk/config.mk.in | 19 - testsuite/config/ghc | 7 +- testsuite/driver/testlib.py | 95 -- testsuite/tests/codeGen/should_run/all.T | 4 +- testsuite/tests/ext-core/Makefile | 29 - testsuite/tests/ext-core/T7239.hs | 8 - testsuite/tests/ext-core/all.T | 3 - testsuite/tests/ffi/should_compile/all.T | 21 +- testsuite/tests/ffi/should_run/all.T | 30 +- testsuite/tests/typecheck/should_run/all.T | 7 +- utils/genprimopcode/Main.hs | 6 +- 36 files changed, 51 insertions(+), 3733 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4852a59875f1dc89c1821871fdabd6fda65b4534 From git at git.haskell.org Mon Apr 28 09:15:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 09:15:48 +0000 (UTC) Subject: [commit: ghc] master: rm -rf ./docs/comm (0960a37) Message-ID: <20140428091548.0E4DD2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0960a37868e6d08857e86465c8ca346b29b1c813/ghc >--------------------------------------------------------------- commit 0960a37868e6d08857e86465c8ca346b29b1c813 Author: Austin Seipp Date: Mon Apr 28 04:13:07 2014 -0500 rm -rf ./docs/comm The Commentary is now on the wiki and far more complete. This copy will of course live on in the annals of history, but there's no reason to keep it around still. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 0960a37868e6d08857e86465c8ca346b29b1c813 docs/comm/exts/ndp.html | 360 ---------------- docs/comm/exts/th.html | 197 --------- docs/comm/feedback.html | 34 -- docs/comm/genesis/genesis.html | 82 ---- docs/comm/genesis/makefiles.html | 51 --- docs/comm/genesis/modules.html | 164 -------- docs/comm/index.html | 121 ------ docs/comm/others.html | 60 --- docs/comm/rts-libs/foreignptr.html | 68 --- docs/comm/rts-libs/multi-thread.html | 445 -------------------- docs/comm/rts-libs/non-blocking.html | 133 ------ docs/comm/rts-libs/prelfound.html | 57 --- docs/comm/rts-libs/prelude.html | 121 ------ docs/comm/rts-libs/primitives.html | 70 --- docs/comm/rts-libs/stgc.html | 45 -- docs/comm/rts-libs/threaded-rts.html | 126 ------ docs/comm/the-beast/alien.html | 56 --- docs/comm/the-beast/basicTypes.html | 132 ------ docs/comm/the-beast/coding-style.html | 230 ---------- docs/comm/the-beast/data-types.html | 242 ----------- docs/comm/the-beast/desugar.html | 156 ------- docs/comm/the-beast/driver.html | 179 -------- docs/comm/the-beast/fexport.html | 231 ---------- docs/comm/the-beast/ghci.html | 407 ------------------ docs/comm/the-beast/main.html | 35 -- docs/comm/the-beast/mangler.html | 79 ---- docs/comm/the-beast/modules.html | 80 ---- docs/comm/the-beast/names.html | 169 -------- docs/comm/the-beast/ncg.html | 749 --------------------------------- docs/comm/the-beast/optimistic.html | 65 --- docs/comm/the-beast/prelude.html | 207 --------- docs/comm/the-beast/renamer.html | 249 ----------- docs/comm/the-beast/simplifier.html | 86 ---- docs/comm/the-beast/stg.html | 164 -------- docs/comm/the-beast/syntax.html | 99 ----- docs/comm/the-beast/typecheck.html | 316 -------------- docs/comm/the-beast/types.html | 179 -------- docs/comm/the-beast/vars.html | 235 ----------- 38 files changed, 6479 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0960a37868e6d08857e86465c8ca346b29b1c813 From git at git.haskell.org Mon Apr 28 09:17:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 09:17:37 +0000 (UTC) Subject: [commit: ghc] branch 'wip/coverity' deleted Message-ID: <20140428091737.7607B2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/coverity From git at git.haskell.org Mon Apr 28 09:18:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 09:18:04 +0000 (UTC) Subject: [commit: ghc] branch 'wip/ermsb' created Message-ID: <20140428091804.452652406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/ermsb Referencing: e2cc1c5135c77736bfc8a188e7b4cc29fa50d39a From git at git.haskell.org Mon Apr 28 09:18:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 09:18:08 +0000 (UTC) Subject: [commit: ghc] wip/ermsb: ghc: Add new constants for -march/-mcpu options (6e9a997) Message-ID: <20140428091808.0E2E92406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ermsb Link : http://ghc.haskell.org/trac/ghc/changeset/6e9a99743cce3195e2f1dafa90068651752a3161/ghc >--------------------------------------------------------------- commit 6e9a99743cce3195e2f1dafa90068651752a3161 Author: Austin Seipp Date: Mon Apr 21 19:28:41 2014 -0500 ghc: Add new constants for -march/-mcpu options Signed-off-by: Austin Seipp >--------------------------------------------------------------- 6e9a99743cce3195e2f1dafa90068651752a3161 compiler/utils/Platform.hs | 115 ++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 115 insertions(+) diff --git a/compiler/utils/Platform.hs b/compiler/utils/Platform.hs index ca8f0de..14ce7bd 100644 --- a/compiler/utils/Platform.hs +++ b/compiler/utils/Platform.hs @@ -15,6 +15,12 @@ module Platform ( osMachOTarget, platformUsesFrameworks, platformBinariesAreStaticLibs, + + CPUDesc(..), isx86Desc, + IntelCPU(..), + IntelFeature(..), + descToCPU, + intelCPUFeatures ) where @@ -151,3 +157,112 @@ osBinariesAreStaticLibs _ = False platformBinariesAreStaticLibs :: Platform -> Bool platformBinariesAreStaticLibs = osBinariesAreStaticLibs . platformOS +-- ----------------------------------------------------------------------------- +-- Platform-specific micro architectures. + +-- CPU descriptions that may be fed to -mcpu or -march +data CPUDesc + = Generic + | Native + | Intel IntelCPU + +isx86Desc :: CPUDesc -> Bool +isx86Desc (Intel _) = True +isx86Desc _ = False + +-- ----------------------------------------------------------------------------- +-- Intel + +-- Description of all Intel CPUs. Order isn't necessarily important - +-- we'll discriminate on feature set later anyway. +data IntelCPU + = I386CPU + | I486CPU + | I586CPU + | PentiumMMX + | PentiumPro + | I686CPU + | Pentium2 + | Pentium3 + | Pentium3M + | PentiumM + | Pentium4 + | Pentium4M + | Prescott + | NoCona + | Core2 + | Nehalem + | Westmere + | Sandybridge + | Ivybridge + | Haswell + | Bonnell + | Silvermont + | Broadwell + +data IntelFeature + = MMX + | SSE + | SSE2 + | SSE3 + | SSSE3 + | SSE4 + | SSE41 + | SSE42 + | AVX1 + | ERMSB -- "Extended rep-movsb" + | AVX2 + +descToCPU :: String -> Maybe CPUDesc +descToCPU "generic" = Just Generic +descToCPU "native" = Just Native +descToCPU "i386" = Just $ Intel $ I386CPU +descToCPU "i486" = Just $ Intel $ I486CPU +descToCPU "i586" = Just $ Intel $ I586CPU +descToCPU "pentium" = Just $ Intel $ I586CPU +descToCPU "pentium-mmx" = Just $ Intel $ PentiumMMX +descToCPU "pentiumpro" = Just $ Intel $ PentiumPro +descToCPU "i686" = Just $ Intel $ PentiumPro +descToCPU "pentium2" = Just $ Intel $ Pentium2 +descToCPU "pentium3" = Just $ Intel $ Pentium3 +descToCPU "pentium3m" = Just $ Intel $ Pentium3M +descToCPU "pentium-m" = Just $ Intel $ PentiumM +descToCPU "pentium4" = Just $ Intel $ Pentium4 +descToCPU "pentium4m" = Just $ Intel $ Pentium4M +descToCPU "prescott" = Just $ Intel $ Prescott +descToCPU "nocona" = Just $ Intel $ NoCona +descToCPU "core2" = Just $ Intel $ Core2 +descToCPU "nehalem" = Just $ Intel $ Nehalem +descToCPU "westmere" = Just $ Intel $ Westmere +descToCPU "sandybridge" = Just $ Intel $ Sandybridge +descToCPU "ivybridge" = Just $ Intel $ Ivybridge +descToCPU "haswell" = Just $ Intel $ Haswell +descToCPU "bonnell" = Just $ Intel $ Bonnell +descToCPU "silvermont" = Just $ Intel $ Silvermont +descToCPU "broadwell" = Just $ Intel $ Broadwell +descToCPU _ = Nothing + +intelCPUFeatures :: IntelCPU -> [IntelFeature] +intelCPUFeatures I386CPU = [] +intelCPUFeatures I486CPU = [] +intelCPUFeatures I586CPU = [] +intelCPUFeatures PentiumMMX = [MMX] +intelCPUFeatures PentiumPro = [MMX] +intelCPUFeatures I686CPU = [MMX] +intelCPUFeatures Pentium2 = [MMX] +intelCPUFeatures Pentium3 = [MMX, SSE] +intelCPUFeatures Pentium3M = [MMX, SSE] +intelCPUFeatures PentiumM = [MMX, SSE, SSE2] +intelCPUFeatures Pentium4 = [MMX, SSE, SSE2] +intelCPUFeatures Pentium4M = [MMX, SSE, SSE2] +intelCPUFeatures Prescott = [MMX, SSE, SSE2, SSE3] +intelCPUFeatures NoCona = [MMX, SSE, SSE2, SSE3] +intelCPUFeatures Core2 = [MMX, SSE, SSE2, SSE3, SSSE3] +intelCPUFeatures Nehalem = [MMX, SSE, SSE2, SSE3, SSSE3, SSE4, SSE41, SSE42] +intelCPUFeatures Westmere = [MMX, SSE, SSE2, SSE3, SSSE3, SSE4, SSE41, SSE42] +intelCPUFeatures Sandybridge = [MMX, SSE, SSE2, SSE3, SSSE3, SSE4, SSE41, SSE42, AVX1] +intelCPUFeatures Ivybridge = [MMX, SSE, SSE2, SSE3, SSSE3, SSE4, SSE41, SSE42, AVX1, ERMSB] +intelCPUFeatures Haswell = [MMX, SSE, SSE2, SSE3, SSSE3, SSE4, SSE41, SSE42, AVX1, ERMSB, AVX2] +intelCPUFeatures Bonnell = [MMX, SSE, SSE2, SSE3, SSSE3, SSE4, SSE41, SSE42, AVX1, ERMSB, AVX2] +intelCPUFeatures Silvermont = [MMX, SSE, SSE2, SSE3, SSSE3, SSE4, SSE41, SSE42, AVX1, ERMSB, AVX2] +intelCPUFeatures Broadwell = [MMX, SSE, SSE2, SSE3, SSSE3, SSE4, SSE41, SSE42, AVX1, ERMSB, AVX2] From git at git.haskell.org Mon Apr 28 09:18:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 09:18:11 +0000 (UTC) Subject: [commit: ghc] wip/ermsb: When using Ivy Bridge, emit 'rep movsb' for copies (e2cc1c5) Message-ID: <20140428091812.32D442406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ermsb Link : http://ghc.haskell.org/trac/ghc/changeset/e2cc1c5135c77736bfc8a188e7b4cc29fa50d39a/ghc >--------------------------------------------------------------- commit e2cc1c5135c77736bfc8a188e7b4cc29fa50d39a Author: Austin Seipp Date: Mon Apr 21 22:05:59 2014 -0500 When using Ivy Bridge, emit 'rep movsb' for copies Signed-off-by: Austin Seipp >--------------------------------------------------------------- e2cc1c5135c77736bfc8a188e7b4cc29fa50d39a compiler/nativeGen/X86/CodeGen.hs | 33 +++++++++++++++++++++++++++++++++ compiler/nativeGen/X86/Instr.hs | 8 ++++++++ compiler/nativeGen/X86/Ppr.hs | 2 ++ compiler/utils/Platform.hs | 1 + 4 files changed, 44 insertions(+) diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs index e659488..e90667d 100644 --- a/compiler/nativeGen/X86/CodeGen.hs +++ b/compiler/nativeGen/X86/CodeGen.hs @@ -1568,6 +1568,39 @@ genCCall -- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - +-- Do NOT unroll memcpy calls if the compiler has -mcpu=ivybridge - +-- this can be done even better using 'enhanced rep movsb', which +-- is nearly as fast as an AVX-based memcpy. +-- +-- Note: this is implied with *both* -mcpu and -march. Why? -mcpu +-- traditionally controls tuning schedules etc for the particular +-- platform. -march controls *code generation* for that platform, +-- including what instructions can be emitted. +-- +-- In this case, the *instruction* does not change, it is still +-- backwards compatible. But the actual *performance* impact and +-- schedule of the code will change, hence why we check mcpu as well. +genCCall dflags is32Bit (PrimTarget MO_Memcpy) _ + [dst, src, + (CmmLit (CmmInt n _)), + (CmmLit (CmmInt _ _))] + | supportsERMSB dflags && not is32Bit = do + code_dst <- getAnyReg dst + dst_r <- getNewRegNat II64 + code_src <- getAnyReg src + src_r <- getNewRegNat II64 + return $ code_dst dst_r `appOL` code_src src_r `appOL` + unitOL (MOV II64 (OpReg src_r) (OpReg rsi)) `appOL` + unitOL (MOV II64 (OpReg dst_r) (OpReg rdi)) `appOL` + unitOL (MOV II64 (OpImm (ImmInteger n)) (OpReg rcx)) `appOL` + unitOL REPMOVSB `appOL` nilOL + + where + supportsERMSB dflags + | Intel x <- march dflags = any (== ERMSB) (intelCPUFeatures x) + | Intel x <- mcpu dflags = any (== ERMSB) (intelCPUFeatures x) + | otherwise = False + -- Unroll memcpy calls if the source and destination pointers are at -- least DWORD aligned and the number of bytes to copy isn't too -- large. Otherwise, call C's memcpy. diff --git a/compiler/nativeGen/X86/Instr.hs b/compiler/nativeGen/X86/Instr.hs index 75e5b9e..99731fb 100644 --- a/compiler/nativeGen/X86/Instr.hs +++ b/compiler/nativeGen/X86/Instr.hs @@ -183,6 +183,10 @@ data Instr | MOV Size Operand Operand | MOVZxL Size Operand Operand -- size is the size of operand 1 | MOVSxL Size Operand Operand -- size is the size of operand 1 + + -- Special case move for Ivy Bridge processors + | REPMOVSB + -- x86_64 note: plain mov into a 32-bit register always zero-extends -- into the 64-bit reg, in contrast to the 8 and 16-bit movs which -- don't affect the high bits of the register. @@ -425,6 +429,8 @@ x86_regUsageOfInstr platform instr POPCNT _ src dst -> mkRU (use_R src []) [dst] + REPMOVSB -> mkRU [] [] + -- note: might be a better way to do this PREFETCH _ _ src -> mkRU (use_R src []) [] @@ -570,6 +576,8 @@ x86_patchRegsOfInstr instr env PREFETCH lvl size src -> PREFETCH lvl size (patchOp src) + REPMOVSB -> REPMOVSB + _other -> panic "patchRegs: unrecognised instr" where diff --git a/compiler/nativeGen/X86/Ppr.hs b/compiler/nativeGen/X86/Ppr.hs index f38a04d..9af038c 100644 --- a/compiler/nativeGen/X86/Ppr.hs +++ b/compiler/nativeGen/X86/Ppr.hs @@ -582,6 +582,8 @@ pprInstr (PREFETCH Lvl0 size src) = pprSizeOp_ (sLit "prefetcht0") size src pprInstr (PREFETCH Lvl1 size src) = pprSizeOp_ (sLit "prefetcht1") size src pprInstr (PREFETCH Lvl2 size src) = pprSizeOp_ (sLit "prefetcht2") size src +pprInstr REPMOVSB = ptext (sLit "\trep movsb") + pprInstr (NOT size op) = pprSizeOp (sLit "not") size op pprInstr (BSWAP size op) = pprSizeOp (sLit "bswap") size (OpReg op) pprInstr (NEGI size op) = pprSizeOp (sLit "neg") size op diff --git a/compiler/utils/Platform.hs b/compiler/utils/Platform.hs index 14ce7bd..24891ab 100644 --- a/compiler/utils/Platform.hs +++ b/compiler/utils/Platform.hs @@ -212,6 +212,7 @@ data IntelFeature | AVX1 | ERMSB -- "Extended rep-movsb" | AVX2 + deriving Eq descToCPU :: String -> Maybe CPUDesc descToCPU "generic" = Just Generic From git at git.haskell.org Mon Apr 28 09:18:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 09:18:14 +0000 (UTC) Subject: [commit: ghc] wip/ermsb: ghc: add -march/-mcpu to DynFlags (41ddcd7) Message-ID: <20140428091814.CA7382406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ermsb Link : http://ghc.haskell.org/trac/ghc/changeset/41ddcd7d7909224ac891c7b1ced8f2c59cb07dfc/ghc >--------------------------------------------------------------- commit 41ddcd7d7909224ac891c7b1ced8f2c59cb07dfc Author: Austin Seipp Date: Mon Apr 21 19:53:59 2014 -0500 ghc: add -march/-mcpu to DynFlags Currently these are still unused, but now recognized by the command line. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 41ddcd7d7909224ac891c7b1ced8f2c59cb07dfc compiler/main/DynFlags.hs | 22 ++++++++++++++++++++++ 1 file changed, 22 insertions(+) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 72ebb38..ee84bf5 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -794,6 +794,9 @@ data DynFlags = DynFlags { avx512f :: Bool, -- Enable AVX-512 instructions. avx512pf :: Bool, -- Enable AVX-512 PreFetch Instructions. + march :: CPUDesc, + mcpu :: CPUDesc, + -- | Run-time linker information (what options we need, etc.) rtldInfo :: IORef (Maybe LinkerInfo), @@ -1459,6 +1462,8 @@ defaultDynFlags mySettings = avx512er = False, avx512f = False, avx512pf = False, + march = Generic, + mcpu = Generic, rtldInfo = panic "defaultDynFlags: no rtldInfo", rtccInfo = panic "defaultDynFlags: no rtccInfo", @@ -2388,6 +2393,9 @@ dynamic_flags = [ , Flag "mavx512f" (noArg (\d -> d{ avx512f = True })) , Flag "mavx512pf" (noArg (\d -> d{ avx512pf = True })) + , Flag "march" (HasArg hasMarch) + , Flag "mcpu" (HasArg hasMcpu) + ------ Warning opts ------------------------------------------------- , Flag "W" (NoArg (mapM_ setWarningFlag minusWOpts)) , Flag "Werror" (NoArg (setGeneralFlag Opt_WarnIsError)) @@ -3704,6 +3712,20 @@ setUnsafeGlobalDynFlags :: DynFlags -> IO () setUnsafeGlobalDynFlags = writeIORef v_unsafeGlobalDynFlags -- ----------------------------------------------------------------------------- +-- march/mcpu handling + +hasMarch :: String -> DynP () +hasMarch s = case descToCPU s of + Nothing -> addWarn ("Invalid argument for -march, '"++s++"'") + Just x -> do + upd (\d -> d { march = x }) + +hasMcpu :: String -> DynP () +hasMcpu s = case descToCPU s of + Nothing -> addWarn ("Invalid argument for -mcpu, '"++s++"'") + Just x -> upd (\d -> d { mcpu = x }) + +-- ----------------------------------------------------------------------------- -- SSE and AVX -- TODO: Instead of using a separate predicate (i.e. isSse2Enabled) to From git at git.haskell.org Mon Apr 28 09:38:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 09:38:42 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Start 7.8.3 release notes (1514a7e) Message-ID: <20140428093842.456062406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/1514a7e3ff2e24af6ecf4c9e6019cf28a7eee11c/ghc >--------------------------------------------------------------- commit 1514a7e3ff2e24af6ecf4c9e6019cf28a7eee11c Author: Austin Seipp Date: Mon Apr 28 04:33:07 2014 -0500 Start 7.8.3 release notes There are already quite a few bugfixes, I'll fill them out shortly. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 1514a7e3ff2e24af6ecf4c9e6019cf28a7eee11c docs/users_guide/7.8.3-notes.xml | 21 +++++++++++++++++++++ docs/users_guide/intro.xml | 1 + docs/users_guide/ug-ent.xml.in | 1 + 3 files changed, 23 insertions(+) diff --git a/docs/users_guide/7.8.3-notes.xml b/docs/users_guide/7.8.3-notes.xml new file mode 100644 index 0000000..1b88f5b --- /dev/null +++ b/docs/users_guide/7.8.3-notes.xml @@ -0,0 +1,21 @@ + + + Release notes for version 7.8.3 + + + The 7.8.3 release is a bugfix release. The changes relative to + 7.8.2 are listed below. + + + + GHC + + + + + TODO FIXME + + + + + diff --git a/docs/users_guide/intro.xml b/docs/users_guide/intro.xml index 3292334..fb7116e 100644 --- a/docs/users_guide/intro.xml +++ b/docs/users_guide/intro.xml @@ -309,6 +309,7 @@ &relnotes1; &relnotes2; +&relnotes3; diff --git a/docs/users_guide/ug-ent.xml.in b/docs/users_guide/ug-ent.xml.in index 0b343ec..5df3a04 100644 --- a/docs/users_guide/ug-ent.xml.in +++ b/docs/users_guide/ug-ent.xml.in @@ -5,6 +5,7 @@ + From git at git.haskell.org Mon Apr 28 10:00:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 10:00:18 +0000 (UTC) Subject: [commit: ghc] master: Do type-class defaulting even if there are insoluble constraints (ba2e201) Message-ID: <20140428100018.175CC2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ba2e20149e2addaccf5ce3122d3a6e93da696a0a/ghc >--------------------------------------------------------------- commit ba2e20149e2addaccf5ce3122d3a6e93da696a0a Author: Simon Peyton Jones Date: Fri Apr 25 00:04:45 2014 +0100 Do type-class defaulting even if there are insoluble constraints The argument in Trac #9033 is very compelling: we should not report 20 errors, fix one, and have the other 19 disappear. They were spurious in the first place. The fix was easy; do type-class defaulting uncondionally, rather than only if there are no insoluble constraints. See Note [When to do type-class defaulting] in TcSimplify. Error messages generally improve, especially tc211 which actually had an example of precisely this phenomenon. >--------------------------------------------------------------- ba2e20149e2addaccf5ce3122d3a6e93da696a0a compiler/typecheck/TcSimplify.lhs | 34 +++++++++-- .../tests/indexed-types/should_fail/T5934.stderr | 8 +-- .../tests/typecheck/should_compile/tc211.stderr | 63 +------------------- testsuite/tests/typecheck/should_fail/T8603.stderr | 8 +-- testsuite/tests/typecheck/should_fail/T9033.hs | 7 +++ testsuite/tests/typecheck/should_fail/T9033.stderr | 5 ++ testsuite/tests/typecheck/should_fail/all.T | 1 + testsuite/tests/typecheck/should_fail/mc24.stderr | 4 +- .../tests/typecheck/should_fail/tcfail004.stderr | 6 +- .../tests/typecheck/should_fail/tcfail005.stderr | 3 +- .../tests/typecheck/should_fail/tcfail140.stderr | 4 +- .../tests/typecheck/should_fail/tcfail189.stderr | 4 +- .../tests/typecheck/should_fail/tcfail206.stderr | 9 +-- 13 files changed, 70 insertions(+), 86 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ba2e20149e2addaccf5ce3122d3a6e93da696a0a From git at git.haskell.org Mon Apr 28 10:00:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 10:00:20 +0000 (UTC) Subject: [commit: ghc] master: Remove the definition of die, which is now provided by System.Exit (ef35d4c) Message-ID: <20140428100022.4428C2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ef35d4cfcfcb9b0b733f1ec8ec16a1e0020be1f5/ghc >--------------------------------------------------------------- commit ef35d4cfcfcb9b0b733f1ec8ec16a1e0020be1f5 Author: Simon Peyton Jones Date: Fri Apr 25 00:06:08 2014 +0100 Remove the definition of die, which is now provided by System.Exit >--------------------------------------------------------------- ef35d4cfcfcb9b0b733f1ec8ec16a1e0020be1f5 testsuite/timeout/timeout.hs | 4 ---- 1 file changed, 4 deletions(-) diff --git a/testsuite/timeout/timeout.hs b/testsuite/timeout/timeout.hs index 0806687..f78baa1 100644 --- a/testsuite/timeout/timeout.hs +++ b/testsuite/timeout/timeout.hs @@ -33,10 +33,6 @@ main = do _ -> die ("Can't parse " ++ show secs ++ " as a number of seconds") _ -> die ("Bad arguments " ++ show args) -die :: String -> IO () -die msg = do hPutStrLn stderr ("timeout: " ++ msg) - exitWith (ExitFailure 1) - timeoutMsg :: String timeoutMsg = "Timeout happened...killing process..." From git at git.haskell.org Mon Apr 28 10:00:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 10:00:23 +0000 (UTC) Subject: [commit: ghc] master: Update 32-bit perf numbers (7201e2a) Message-ID: <20140428100023.4CC7E2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7201e2add2834f16549869417e9fface94f83a90/ghc >--------------------------------------------------------------- commit 7201e2add2834f16549869417e9fface94f83a90 Author: Simon Peyton Jones Date: Fri Apr 25 00:07:20 2014 +0100 Update 32-bit perf numbers Many of these have never been initialised, I think. They were simply guesses from the 64-bit version. >--------------------------------------------------------------- 7201e2add2834f16549869417e9fface94f83a90 libraries/base/tests/all.T | 6 ++++-- testsuite/tests/perf/compiler/all.T | 8 +++++--- testsuite/tests/perf/haddock/all.T | 3 ++- testsuite/tests/perf/should_run/all.T | 13 +++++++++---- 4 files changed, 20 insertions(+), 10 deletions(-) diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T index d4a6c05..21e3d0c 100644 --- a/libraries/base/tests/all.T +++ b/libraries/base/tests/all.T @@ -156,10 +156,12 @@ test('topHandler03', test('T8766', - [ stats_num_field('bytes allocated', (16828144, 5)), + [ stats_num_field('bytes allocated', + [ (wordsize(64), 16828144, 5) # with GHC-7.6.3: 83937384 (but faster execution than the next line) # before: 58771216 (without call-arity-analysis) # expected value: 16828144 (2014-01-14) - only_ways(['normal'])], + , (wordsize(32), 8433644, 5) ]) + , only_ways(['normal'])], compile_and_run, ['-O']) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 2bff1c7..bd9a08f 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -42,11 +42,12 @@ test('T1969', # 2013-02-13 27, very unstable! # 2013-09-11 30 (amd64/Linux) compiler_stats_num_field('max_bytes_used', - [(platform('i386-unknown-mingw32'), 7295012, 20), + [(platform('i386-unknown-mingw32'), 5719436, 20), # 2010-05-17 5717704 (x86/Windows) # 2013-02-10 5159748 (x86/Windows) # 2013-02-10 5030080 (x86/Windows) # 2013-11-13 7295012 (x86/Windows, 64bit machine) + # 2014-04-24 5719436 (x86/Windows, 64bit machine) (wordsize(32), 6429864, 1), # 6707308 (x86/OS X) # 2009-12-31 6149572 (x86/Linux) @@ -110,12 +111,13 @@ else: test('T3294', [ compiler_stats_num_field('max_bytes_used', # Note [residency] - [(wordsize(32), 24009436, 15), + [(wordsize(32), 19882188, 15), # 17725476 (x86/OS X) # 14593500 (Windows) # 2013-02-10 20651576 (x86/Windows) # 2013-02-10 20772984 (x86/OSX) # 2013-11-13 24009436 (x86/Windows, 64bit machine) + # 2014-04-24 19882188 (x86/Windows, 64bit machine) (wordsize(64), 43224080, 15)]), # prev: 25753192 (amd64/Linux) # 29/08/2012: 37724352 (amd64/Linux) @@ -411,7 +413,7 @@ test('T6048', test('T9020', [ only_ways(['optasm']), compiler_stats_num_field('bytes allocated', - [(wordsize(32), 40000000, 10), + [(wordsize(32), 381360728, 10), (wordsize(64), 795469104, 10)]) ], compile,['']) diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index e1d7e9f..6a2ed82 100644 --- a/testsuite/tests/perf/haddock/all.T +++ b/testsuite/tests/perf/haddock/all.T @@ -101,10 +101,11 @@ test('haddock.Cabal', # 2013-11-21: 3908586784 (amd64/Linux) Cabal updated # 2013-12-12: 3828567272 (amd64/Linux) # 2014-01-12: 3979151552 (amd64/Linux) new parser - ,(platform('i386-unknown-mingw32'), 1966911336, 1) + ,(platform('i386-unknown-mingw32'), 2052220292, 5) # 2012-10-30: 1733638168 (x86/Windows) # 2013-02-10: 1906532680 (x86/Windows) # 2014-01-28: 1966911336 (x86/Windows) + # 2014-04-24: 2052220292 (x86/Windows) ,(wordsize(32), 1986290624, 1)]) # 2012-08-14: 1648610180 (x86/OSX) # 2014-01-22: 1986290624 (x86/Linux) diff --git a/testsuite/tests/perf/should_run/all.T b/testsuite/tests/perf/should_run/all.T index 606448b..8030251 100644 --- a/testsuite/tests/perf/should_run/all.T +++ b/testsuite/tests/perf/should_run/all.T @@ -311,7 +311,7 @@ test('T7850', test('T5949', [stats_num_field('bytes allocated', - [ (wordsize(32), 101000, 10), + [ (wordsize(32), 116020, 10), (wordsize(64), 201008, 10)]), # previously, it was >400000 bytes only_ways(['normal'])], @@ -320,7 +320,8 @@ test('T5949', test('T4267', [stats_num_field('bytes allocated', - [ (wordsize(32), 20992, 10) + [ (wordsize(32), 36012, 10) + # 32-bit value close to 64 bit; c.f. T7619 , (wordsize(64), 40992, 10) ]), # previously, it was >170000 bytes # 2014-01-17: 130000 @@ -331,7 +332,9 @@ test('T4267', test('T7619', [stats_num_field('bytes allocated', - [ (wordsize(32), 20992, 10) + [ (wordsize(32), 36012, 10) + # 32-bit close to 64-bit value; most of this very + # small number is standard start-up boilerplate I think , (wordsize(64), 40992, 10) ]), # previously, it was >400000 bytes only_ways(['normal'])], @@ -348,8 +351,10 @@ test('InlineArrayAlloc', test('InlineByteArrayAlloc', [stats_num_field('bytes allocated', - [ (wordsize(32), 720040960, 5) + [ (wordsize(32), 1360036012, 5) , (wordsize(64), 1440040960, 5) ]), + # 32 and 64 bit not so different, because + # we are allocating *byte* arrays only_ways(['normal'])], compile_and_run, ['-O2']) From git at git.haskell.org Mon Apr 28 10:23:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 10:23:31 +0000 (UTC) Subject: [commit: ghc] master: Start on 7.10.1 release notes (3c990bf) Message-ID: <20140428102331.F33762406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3c990bf582d4b8781a296b5521ee7734fd2ba494/ghc >--------------------------------------------------------------- commit 3c990bf582d4b8781a296b5521ee7734fd2ba494 Author: Austin Seipp Date: Mon Apr 28 04:31:14 2014 -0500 Start on 7.10.1 release notes Signed-off-by: Austin Seipp >--------------------------------------------------------------- 3c990bf582d4b8781a296b5521ee7734fd2ba494 docs/users_guide/7.10.1-notes.xml | 363 +++++++++++ docs/users_guide/7.8.1-notes.xml | 1251 ------------------------------------- docs/users_guide/ug-ent.xml.in | 2 +- 3 files changed, 364 insertions(+), 1252 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3c990bf582d4b8781a296b5521ee7734fd2ba494 From git at git.haskell.org Mon Apr 28 12:46:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 12:46:55 +0000 (UTC) Subject: [commit: ghc] master: Fix annotation reification for home package modules (48e475e) Message-ID: <20140428124655.2FC4D2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/48e475e45f517896c6618d38a09b8d223f3d7585/ghc >--------------------------------------------------------------- commit 48e475e45f517896c6618d38a09b8d223f3d7585 Author: Gergely Risko Date: Fri Apr 25 15:35:58 2014 +0200 Fix annotation reification for home package modules The reifyAnnotation method of the Q monad correctly gathered annotations from TCG and EPS. Unfortunately it didn't look into the Home Package Table. This resulted in annotations not being found if they are in the same package as the splice that is reifying and ghc --make is used for compilation management. Fix this by using the already existing prepareAnnotations method from HscTypes.lhs that correctly searches in HPT and EPS both. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 48e475e45f517896c6618d38a09b8d223f3d7585 compiler/typecheck/TcSplice.lhs | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcSplice.lhs b/compiler/typecheck/TcSplice.lhs index 7fce241..7ec8a9e 100644 --- a/compiler/typecheck/TcSplice.lhs +++ b/compiler/typecheck/TcSplice.lhs @@ -1507,13 +1507,14 @@ lookupThAnnLookup (TH.AnnLookupModule (TH.Module pn mn)) mkModule (stringToPackageId $ TH.pkgString pn) (mkModuleName $ TH.modString mn) reifyAnnotations :: Data a => TH.AnnLookup -> TcM [a] -reifyAnnotations th_nm - = do { name <- lookupThAnnLookup th_nm - ; eps <- getEps +reifyAnnotations th_name + = do { name <- lookupThAnnLookup th_name + ; topEnv <- getTopEnv + ; epsHptAnns <- liftIO $ prepareAnnotations topEnv Nothing ; tcg <- getGblEnv - ; let epsAnns = findAnns deserializeWithData (eps_ann_env eps) name - ; let envAnns = findAnns deserializeWithData (tcg_ann_env tcg) name - ; return (envAnns ++ epsAnns) } + ; let selectedEpsHptAnns = findAnns deserializeWithData epsHptAnns name + ; let selectedTcgAnns = findAnns deserializeWithData (tcg_ann_env tcg) name + ; return (selectedEpsHptAnns ++ selectedTcgAnns) } ------------------------------ modToTHMod :: Module -> TH.Module From git at git.haskell.org Mon Apr 28 12:46:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 12:46:58 +0000 (UTC) Subject: [commit: ghc] master: Add a comprehensive test for using Annotations from TH (5f5e326) Message-ID: <20140428124658.29EEB2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5f5e326c3c310c4bceb2b0bce291d3a0a3fc30d6/ghc >--------------------------------------------------------------- commit 5f5e326c3c310c4bceb2b0bce291d3a0a3fc30d6 Author: Gergely Risko Date: Fri Apr 25 15:39:26 2014 +0200 Add a comprehensive test for using Annotations from TH The provided tests test both annotation generation and reification from Template Haskell. Both --make and compilation via separate units (ghc -c) are tested. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 5f5e326c3c310c4bceb2b0bce291d3a0a3fc30d6 .../annotations/should_compile/th/AnnHelper.hs | 16 ++++++++++ .../tests/annotations/should_compile/th/Makefile | 33 ++++++++++++++++++++ .../annotations/should_compile/th/TestModule.hs | 11 +++++++ .../annotations/should_compile/th/TestModuleTH.hs | 18 +++++++++++ .../tests/annotations/should_compile/th/all.T | 18 +++++++++++ .../tests/annotations/should_compile/th/annth.hs | 26 +++++++++++++++ .../should_compile/th/annth_compunits.stdout | 7 +++++ .../should_compile/th/annth_make.stdout | 7 +++++ 8 files changed, 136 insertions(+) diff --git a/testsuite/tests/annotations/should_compile/th/AnnHelper.hs b/testsuite/tests/annotations/should_compile/th/AnnHelper.hs new file mode 100644 index 0000000..ac0f040 --- /dev/null +++ b/testsuite/tests/annotations/should_compile/th/AnnHelper.hs @@ -0,0 +1,16 @@ +module AnnHelper where + +import Language.Haskell.TH +import Language.Haskell.TH.Syntax + +traverseModuleAnnotations :: Q [String] +traverseModuleAnnotations = do + ModuleInfo children <- reifyModule =<< thisModule + go children [] [] + where + go [] _visited acc = return acc + go (x:xs) visited acc | x `elem` visited = go xs visited acc + | otherwise = do + ModuleInfo newMods <- reifyModule x + newAnns <- reifyAnnotations $ AnnLookupModule x + go (newMods ++ xs) (x:visited) (newAnns ++ acc) diff --git a/testsuite/tests/annotations/should_compile/th/Makefile b/testsuite/tests/annotations/should_compile/th/Makefile new file mode 100644 index 0000000..4159eee --- /dev/null +++ b/testsuite/tests/annotations/should_compile/th/Makefile @@ -0,0 +1,33 @@ +TOP=../../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +annth_make: + $(MAKE) clean_annth_make + mkdir build_make + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 --make \ + -odir build_make -hidir build_make -o build_make/annth annth.hs + +clean_annth_make: + rm -rf build_make + +annth_compunits: + $(MAKE) clean_annth_compunits + mkdir build_compunits + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -dynamic-too \ + -odir build_compunits -hidir build_compunits \ + -c AnnHelper.hs + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -dynamic-too \ + -odir build_compunits -hidir build_compunits \ + -c TestModule.hs + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -dynamic-too \ + -odir build_compunits -hidir build_compunits \ + -c TestModuleTH.hs + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -ibuild_compunits \ + -odir build_compunits -hidir build_compunits \ + -c annth.hs + +clean_annth_compunits: + rm -rf build_compunits + +.PHONY: annth_make clean_annth_make annth_compunits clean_annth_compunits diff --git a/testsuite/tests/annotations/should_compile/th/TestModule.hs b/testsuite/tests/annotations/should_compile/th/TestModule.hs new file mode 100644 index 0000000..d9519eb --- /dev/null +++ b/testsuite/tests/annotations/should_compile/th/TestModule.hs @@ -0,0 +1,11 @@ +module TestModule where + +{-# ANN module "Module annotation" #-} + +{-# ANN type TestType "Type annotation" #-} +{-# ANN TestType "Constructor annotation" #-} +data TestType = TestType + +{-# ANN testValue "Value annotation" #-} +testValue :: Int +testValue = 42 diff --git a/testsuite/tests/annotations/should_compile/th/TestModuleTH.hs b/testsuite/tests/annotations/should_compile/th/TestModuleTH.hs new file mode 100644 index 0000000..f21b137 --- /dev/null +++ b/testsuite/tests/annotations/should_compile/th/TestModuleTH.hs @@ -0,0 +1,18 @@ +{-# LANGUAGE TemplateHaskell #-} + +module TestModuleTH where + +import Language.Haskell.TH + +$(do + modAnn <- pragAnnD ModuleAnnotation + (stringE "TH module annotation") + [typ] <- [d| data TestTypeTH = TestTypeTH |] + conAnn <- pragAnnD (ValueAnnotation $ mkName "TestTypeTH") + (stringE "TH Constructor annotation") + typAnn <- pragAnnD (TypeAnnotation $ mkName "TestTypeTH") + (stringE "TH Type annotation") + valAnn <- pragAnnD (ValueAnnotation $ mkName "testValueTH") + (stringE "TH Value annotation") + [val] <- [d| testValueTH = (42 :: Int) |] + return [modAnn, conAnn, typAnn, typ, valAnn, val] ) diff --git a/testsuite/tests/annotations/should_compile/th/all.T b/testsuite/tests/annotations/should_compile/th/all.T new file mode 100644 index 0000000..777cf3d --- /dev/null +++ b/testsuite/tests/annotations/should_compile/th/all.T @@ -0,0 +1,18 @@ +setTestOpts(when(compiler_profiled(), skip)) + +# Annotations and Template Haskell, require runtime evaluation. In +# order for this to work with profiling, we would have to build the +# program twice and use -osuf p_o (see the TH_splitE5_prof test). For +# now, just disable the profiling ways. + +test('annth_make', + [req_interp, omit_ways(['profasm','profthreaded']), + clean_cmd('$MAKE -s clean_annth_make')], + run_command, + ['$MAKE -s --no-print-directory annth_make']) + +test('annth_compunits', + [req_interp, omit_ways(['profasm','profthreaded']), + clean_cmd('$MAKE -s clean_annth_compunits')], + run_command, + ['$MAKE -s --no-print-directory annth_compunits']) diff --git a/testsuite/tests/annotations/should_compile/th/annth.hs b/testsuite/tests/annotations/should_compile/th/annth.hs new file mode 100644 index 0000000..de5d4d3 --- /dev/null +++ b/testsuite/tests/annotations/should_compile/th/annth.hs @@ -0,0 +1,26 @@ +{-# LANGUAGE TemplateHaskell #-} + +import Language.Haskell.TH +import Language.Haskell.TH.Syntax + +import AnnHelper +import TestModule +import TestModuleTH + +main = do + $(do + anns <- traverseModuleAnnotations + runIO $ print (anns :: [String]) + anns <- reifyAnnotations (AnnLookupName 'testValue) + runIO $ print (anns :: [String]) + anns <- reifyAnnotations (AnnLookupName 'testValueTH) + runIO $ print (anns :: [String]) + anns <- reifyAnnotations (AnnLookupName ''TestType) + runIO $ print (anns :: [String]) + anns <- reifyAnnotations (AnnLookupName ''TestTypeTH) + runIO $ print (anns :: [String]) + anns <- reifyAnnotations (AnnLookupName 'TestType) + runIO $ print (anns :: [String]) + anns <- reifyAnnotations (AnnLookupName 'TestTypeTH) + runIO $ print (anns :: [String]) + [| return () |] ) diff --git a/testsuite/tests/annotations/should_compile/th/annth_compunits.stdout b/testsuite/tests/annotations/should_compile/th/annth_compunits.stdout new file mode 100644 index 0000000..96e4642 --- /dev/null +++ b/testsuite/tests/annotations/should_compile/th/annth_compunits.stdout @@ -0,0 +1,7 @@ +["TH module annotation","Module annotation"] +["Value annotation"] +["TH Value annotation"] +["Type annotation"] +["TH Type annotation"] +["Constructor annotation"] +["TH Constructor annotation"] diff --git a/testsuite/tests/annotations/should_compile/th/annth_make.stdout b/testsuite/tests/annotations/should_compile/th/annth_make.stdout new file mode 100644 index 0000000..96e4642 --- /dev/null +++ b/testsuite/tests/annotations/should_compile/th/annth_make.stdout @@ -0,0 +1,7 @@ +["TH module annotation","Module annotation"] +["Value annotation"] +["TH Value annotation"] +["Type annotation"] +["TH Type annotation"] +["Constructor annotation"] +["TH Constructor annotation"] From git at git.haskell.org Mon Apr 28 13:49:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 13:49:56 +0000 (UTC) Subject: [commit: ghc] master: tcrun045 should fail (implicit parameter as superclass) (7b967af) Message-ID: <20140428134956.3C3132406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7b967afa502d9550f4e6c4b5ec5dbd9d93e72947/ghc >--------------------------------------------------------------- commit 7b967afa502d9550f4e6c4b5ec5dbd9d93e72947 Author: Simon Peyton Jones Date: Mon Apr 28 10:31:15 2014 +0100 tcrun045 should fail (implicit parameter as superclass) >--------------------------------------------------------------- 7b967afa502d9550f4e6c4b5ec5dbd9d93e72947 testsuite/tests/typecheck/should_run/all.T | 2 +- .../should_run/T5472.stdout => typecheck/should_run/tcrun.stderr} | 0 2 files changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/typecheck/should_run/all.T b/testsuite/tests/typecheck/should_run/all.T index 735fa54..099f814 100755 --- a/testsuite/tests/typecheck/should_run/all.T +++ b/testsuite/tests/typecheck/should_run/all.T @@ -69,7 +69,7 @@ test('tcrun041', omit_ways(['ghci']), compile_and_run, ['']) test('tcrun042', normal, compile_and_run, ['']) test('tcrun043', normal, compile_and_run, ['']) test('tcrun044', normal, compile_and_run, ['']) -test('tcrun045', normal, compile_and_run, ['']) +test('tcrun045', normal, compile_fail, ['']) test('tcrun046', normal, compile_and_run, ['']) test('tcrun047', [omit_ways(['ghci']), only_compiler_types(['ghc'])], compile_and_run, ['']) diff --git a/testsuite/tests/deSugar/should_run/T5472.stdout b/testsuite/tests/typecheck/should_run/tcrun.stderr similarity index 100% copy from testsuite/tests/deSugar/should_run/T5472.stdout copy to testsuite/tests/typecheck/should_run/tcrun.stderr From git at git.haskell.org Mon Apr 28 13:49:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 13:49:58 +0000 (UTC) Subject: [commit: ghc] master: Print for-alls more often (Trac #9018) (2f3ea95) Message-ID: <20140428134958.D8C612406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2f3ea95285d0cccc2a999e7572d8fb78dc2ea441/ghc >--------------------------------------------------------------- commit 2f3ea95285d0cccc2a999e7572d8fb78dc2ea441 Author: Simon Peyton Jones Date: Mon Apr 28 14:49:21 2014 +0100 Print for-alls more often (Trac #9018) We now display the foralls of a type if any of the type variables is polykinded. This put kind polymorphism "in your face" a bit more often, but eliminates a lot of head scratching. The user manual reflects the new behaviour. >--------------------------------------------------------------- 2f3ea95285d0cccc2a999e7572d8fb78dc2ea441 compiler/main/PprTyThing.hs | 11 +++--- compiler/typecheck/TcRnTypes.lhs | 7 ++-- compiler/types/TypeRep.lhs | 36 +++++++++++++++----- docs/users_guide/using.xml | 29 ++++++++++++---- testsuite/tests/ghci/scripts/T7873.stdout | 3 +- testsuite/tests/ghci/scripts/ghci059.stdout | 4 ++- .../tests/indexed-types/should_fail/T7786.stderr | 2 +- testsuite/tests/polykinds/T7230.stderr | 4 +-- testsuite/tests/polykinds/T7438.stderr | 2 +- testsuite/tests/polykinds/T8566.stderr | 3 +- testsuite/tests/roles/should_compile/Roles1.stderr | 6 ++-- testsuite/tests/th/TH_Roles2.stderr | 2 +- 12 files changed, 74 insertions(+), 35 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2f3ea95285d0cccc2a999e7572d8fb78dc2ea441 From git at git.haskell.org Mon Apr 28 14:14:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 14:14:19 +0000 (UTC) Subject: [commit: ghc] master: annth_make, annth_compunits: Only run these tests if have_dynamic() (0fe7268) Message-ID: <20140428141419.B7BFE2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0fe726829d468badf830dd82bc296832d709733b/ghc >--------------------------------------------------------------- commit 0fe726829d468badf830dd82bc296832d709733b Author: Joachim Breitner Date: Mon Apr 28 16:14:10 2014 +0200 annth_make, annth_compunits: Only run these tests if have_dynamic() >--------------------------------------------------------------- 0fe726829d468badf830dd82bc296832d709733b testsuite/tests/annotations/should_compile/th/all.T | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/annotations/should_compile/th/all.T b/testsuite/tests/annotations/should_compile/th/all.T index 777cf3d..b44a0d5 100644 --- a/testsuite/tests/annotations/should_compile/th/all.T +++ b/testsuite/tests/annotations/should_compile/th/all.T @@ -6,13 +6,17 @@ setTestOpts(when(compiler_profiled(), skip)) # now, just disable the profiling ways. test('annth_make', - [req_interp, omit_ways(['profasm','profthreaded']), + [req_interp, + omit_ways(['profasm','profthreaded']), + unless(have_dynamic(),skip), clean_cmd('$MAKE -s clean_annth_make')], run_command, ['$MAKE -s --no-print-directory annth_make']) test('annth_compunits', - [req_interp, omit_ways(['profasm','profthreaded']), + [req_interp, + omit_ways(['profasm','profthreaded']), + unless(have_dynamic(),skip), clean_cmd('$MAKE -s clean_annth_compunits')], run_command, ['$MAKE -s --no-print-directory annth_compunits']) From git at git.haskell.org Mon Apr 28 19:56:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 19:56:54 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Mention TH pattern splices in 7.8.1 release notes (431da1a) Message-ID: <20140428195654.3532E2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/431da1a6a8db6a3f3065fe1e1590790f736309ce/ghc >--------------------------------------------------------------- commit 431da1a6a8db6a3f3065fe1e1590790f736309ce Author: Christiaan Baaij Date: Mon Apr 28 12:13:11 2014 +0200 Mention TH pattern splices in 7.8.1 release notes >--------------------------------------------------------------- 431da1a6a8db6a3f3065fe1e1590790f736309ce docs/users_guide/7.8.1-notes.xml | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/docs/users_guide/7.8.1-notes.xml b/docs/users_guide/7.8.1-notes.xml index 8f3e8ac..e4b9353 100644 --- a/docs/users_guide/7.8.1-notes.xml +++ b/docs/users_guide/7.8.1-notes.xml @@ -653,6 +653,11 @@ since it allows strictly more programs to be typed. + + + Template Haskell now supports pattern splices. + + From git at git.haskell.org Mon Apr 28 23:51:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 28 Apr 2014 23:51:22 +0000 (UTC) Subject: [commit: ghc] master: Improve implementation of unSubCo_maybe. (a3896ab) Message-ID: <20140428235122.E84F12406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a3896ab5d2dc88160f710705bf23e6e25e327da5/ghc >--------------------------------------------------------------- commit a3896ab5d2dc88160f710705bf23e6e25e327da5 Author: Richard Eisenberg Date: Mon Apr 28 13:33:13 2014 -0400 Improve implementation of unSubCo_maybe. This is the result of an email conversation (off list) with Conal Elliott, who needed a stronger unSubCo_maybe. This commit adds cases to upgrade the role of a coercion when recursion is necessary to do say (for example, for a use of TransCo). As a side effect, more coercion optimizations are now possible. This was not done previously because unSubCo_maybe was used only during coercion optimization, and the recursive cases looked to be unlikely. However, adding them can cause no harm. unSubCo_maybe is now also exported from Coercion, for use cases like Conal's. >--------------------------------------------------------------- a3896ab5d2dc88160f710705bf23e6e25e327da5 compiler/types/Coercion.lhs | 20 +++++++++++++++----- 1 file changed, 15 insertions(+), 5 deletions(-) diff --git a/compiler/types/Coercion.lhs b/compiler/types/Coercion.lhs index af2b2fa..f60fcbd 100644 --- a/compiler/types/Coercion.lhs +++ b/compiler/types/Coercion.lhs @@ -38,7 +38,7 @@ module Coercion ( splitAppCo_maybe, splitForAllCo_maybe, nthRole, tyConRolesX, - nextRole, + nextRole, unSubCo_maybe, -- ** Coercion variables mkCoVar, isCoVar, isCoVarType, coVarName, setCoVarName, setCoVarUnique, @@ -1051,16 +1051,26 @@ maybeSubCo2 r1 r2 co -- if co is Nominal, returns it; otherwise, unwraps a SubCo; otherwise, fails unSubCo_maybe :: Coercion -> Maybe Coercion +unSubCo_maybe co + | Nominal <- coercionRole co = Just co unSubCo_maybe (SubCo co) = Just co unSubCo_maybe (Refl _ ty) = Just $ Refl Nominal ty -unSubCo_maybe (TyConAppCo Representational tc cos) - = do { cos' <- mapM unSubCo_maybe cos +unSubCo_maybe (TyConAppCo Representational tc coes) + = do { cos' <- mapM unSubCo_maybe coes ; return $ TyConAppCo Nominal tc cos' } unSubCo_maybe (UnivCo Representational ty1 ty2) = Just $ UnivCo Nominal ty1 ty2 -- We do *not* promote UnivCo Phantom, as that's unsafe. -- UnivCo Nominal is no more unsafe than UnivCo Representational -unSubCo_maybe co - | Nominal <- coercionRole co = Just co +unSubCo_maybe (TransCo co1 co2) + = TransCo <$> unSubCo_maybe co1 <*> unSubCo_maybe co2 +unSubCo_maybe (AppCo co1 co2) + = AppCo <$> unSubCo_maybe co1 <*> pure co2 +unSubCo_maybe (ForAllCo tv co) + = ForAllCo tv <$> unSubCo_maybe co +unSubCo_maybe (NthCo n co) + = NthCo n <$> unSubCo_maybe co +unSubCo_maybe (InstCo co ty) + = InstCo <$> unSubCo_maybe co <*> pure ty unSubCo_maybe _ = Nothing -- takes any coercion and turns it into a Phantom coercion From git at git.haskell.org Tue Apr 29 06:32:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 06:32:56 +0000 (UTC) Subject: [commit: ghc] wip/ext-solver: Parsing of SMT results back into types. (e7fe976) Message-ID: <20140429063256.645F82406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ext-solver Link : http://ghc.haskell.org/trac/ghc/changeset/e7fe97661ce2f2bbc562caf94166f9db36c1990e/ghc >--------------------------------------------------------------- commit e7fe97661ce2f2bbc562caf94166f9db36c1990e Author: Iavor S. Diatchki Date: Mon Apr 28 19:34:12 2014 -0700 Parsing of SMT results back into types. >--------------------------------------------------------------- e7fe97661ce2f2bbc562caf94166f9db36c1990e compiler/typecheck/TcTypeNats.hs | 44 +++++++++++++++++++++++++++++++++++--- 1 file changed, 41 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcTypeNats.hs b/compiler/typecheck/TcTypeNats.hs index b455efe..17a1037 100644 --- a/compiler/typecheck/TcTypeNats.hs +++ b/compiler/typecheck/TcTypeNats.hs @@ -41,10 +41,12 @@ import Data.Map (Map) import qualified Data.Map as Map import Data.Set (Set) import qualified Data.Set as Set -import Data.Maybe ( isJust ) +import Data.Maybe ( isJust, mapMaybe ) import Data.Char ( isSpace ) import Data.List ( unfoldr, mapAccumL, foldl' ) -import Data.IORef ( newIORef, atomicModifyIORef', modifyIORef' ) +import Data.IORef ( newIORef, atomicModifyIORef', modifyIORef' + , readIORef + ) import Control.Monad (forever) import Control.Concurrent ( forkIO ) import qualified Control.Exception as X @@ -756,7 +758,10 @@ newExternalSolver exe opts = case res of SAtom "unsat" -> return ExtSolUnsat SAtom "unknown" -> return ExtSolUnknown - SAtom "sat" -> undefined + SAtom "sat" -> + do vs <- readIORef viRef + model <- smtGetModel proc vs + return (ExtSolSat model) _ -> unexpected res @@ -766,6 +771,16 @@ newExternalSolver exe opts = unexpected e = fail $ "Unexpected response by the solver: " ++ (renderSExpr e "") +smtGetModel :: SolverProcess -> VarInfo -> IO [(TyVar,Type)] +smtGetModel proc vi = + do res <- solverDo proc + $ SList [ SAtom "get-value", SList [ SAtom v | v <- inScope vi ] ] + return $ mapMaybe resolve $ Map.toList $ smtVals res + where + resolve (x,se) = do tv <- Map.lookup x (smtDeclaredVars vi) + ty <- knownValue se + return (tv,ty) + smtDeclarePerhaps :: VarInfo -> (TyVar, String, Ty) -> (VarInfo, [SExpr]) smtDeclarePerhaps vi (tv,x,ty) = (vi1, decls) where @@ -868,6 +883,13 @@ knownKind k = | tc == typeNatKindCon -> Just TNat _ -> Nothing +knownValue :: Expr -> Maybe Xi +knownValue expr = + case expr of + Num x -> Just (num x) + Bool x -> Just (bool x) + _ -> Nothing + thyVarName :: TyVar -> String thyVarName x = occNameString (nameOccName n) ++ "_" ++ show u @@ -915,6 +937,19 @@ smtDeclare x t = SList [SAtom "declare-fun", SAtom x, SList [], smtTy t] smtAssert :: Expr -> SExpr smtAssert e = SList [SAtom "assert", smtExpr e] +smtVals :: SExpr -> Map String Expr +smtVals (SList xs) = + Map.fromList [ (x,v) | SList [ SAtom x, SAtom sa ] <- xs, v <- parse sa ] + where + parse "true" = [Bool True] + parse "false" = [Bool False] + parse xs = [Num x | (x,"") <- reads xs ] +smtVals _ = Map.empty + + + + + -------------------------------------------------------------------------------- {- @@ -955,6 +990,9 @@ emptyVarInfo = VarInfo , smtOtherScopes = [] } +inScope :: VarInfo -> [String] +inScope vi = Set.toList $ Set.unions $ smtCurScope vi : smtOtherScopes vi + startScope :: VarInfo -> VarInfo startScope vi = vi { smtCurScope = Set.empty , smtOtherScopes = smtCurScope vi : smtOtherScopes vi } From git at git.haskell.org Tue Apr 29 06:32:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 06:32:59 +0000 (UTC) Subject: [commit: ghc] wip/ext-solver: Add an instance of the external solver to the TcSMonad (e55edee) Message-ID: <20140429063300.0947F2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ext-solver Link : http://ghc.haskell.org/trac/ghc/changeset/e55edee2c924ef7735faad8166ef555063e76825/ghc >--------------------------------------------------------------- commit e55edee2c924ef7735faad8166ef555063e76825 Author: Iavor S. Diatchki Date: Mon Apr 28 21:23:42 2014 -0700 Add an instance of the external solver to the TcSMonad >--------------------------------------------------------------- e55edee2c924ef7735faad8166ef555063e76825 compiler/typecheck/TcSMonad.lhs | 39 ++++++++++++++++++++++++++++++++++++++- 1 file changed, 38 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index 51f4945..6a43511 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -83,6 +83,8 @@ module TcSMonad ( Untouchables, isTouchableMetaTyVarTcS, isFilledMetaTyVar_maybe, zonkTyVarsAndFV, + TN.ExtSolRes(..), extSolSend, extSolPush, extSolPop, extSolCheck, + getDefaultInfo, getDynFlags, getGlobalRdrEnvTcS, matchFam, matchOpenFam, @@ -112,6 +114,7 @@ import TcType import DynFlags import Type import CoAxiom(sfMatchFam) +import qualified TcTypeNats as TN import TcEvidence import Class @@ -976,7 +979,9 @@ data TcSEnv -- while solving or canonicalising the current worklist. -- Specifically, when canonicalising (forall a. t1 ~ forall a. t2) -- from which we get the implication (forall a. t1 ~ t2) - tcs_implics :: IORef (Bag Implication) + tcs_implics :: IORef (Bag Implication), + + tcs_ext_solver :: TN.ExternalSolver } \end{code} @@ -1064,10 +1069,15 @@ runTcSWithEvBinds ev_binds_var tcs ; step_count <- TcM.newTcRef 0 ; inert_var <- TcM.newTcRef is + ; extSol <- liftIO $ + TN.newExternalSolver "cvc4" [ "--incremental" + , "--lang=smtlib2" ] + ; let env = TcSEnv { tcs_ev_binds = ev_binds_var , tcs_ty_binds = ty_binds_var , tcs_count = step_count , tcs_inerts = inert_var + , tcs_ext_solver = extSol , tcs_worklist = panic "runTcS: worklist" , tcs_implics = panic "runTcS: implics" } -- NB: Both these are initialised by withWorkList @@ -1087,6 +1097,7 @@ runTcSWithEvBinds ev_binds_var tcs ; ev_binds <- TcM.getTcEvBinds ev_binds_var ; checkForCyclicBinds ev_binds #endif + ; liftIO $ TN.extSolStop extSol ; return res } where @@ -1116,11 +1127,14 @@ checkForCyclicBinds ev_binds nestImplicTcS :: EvBindsVar -> Untouchables -> InertSet -> TcS a -> TcS a nestImplicTcS ref inner_untch inerts (TcS thing_inside) = TcS $ \ TcSEnv { tcs_ty_binds = ty_binds + , tcs_ext_solver = outer_solver , tcs_count = count } -> do { new_inert_var <- TcM.newTcRef inerts + ; liftIO (TN.extSolPush outer_solver) ; let nest_env = TcSEnv { tcs_ev_binds = ref , tcs_ty_binds = ty_binds , tcs_count = count + , tcs_ext_solver = outer_solver , tcs_inerts = new_inert_var , tcs_worklist = panic "nextImplicTcS: worklist" , tcs_implics = panic "nextImplicTcS: implics" @@ -1128,6 +1142,7 @@ nestImplicTcS ref inner_untch inerts (TcS thing_inside) } ; res <- TcM.setUntouchables inner_untch $ thing_inside nest_env + ; liftIO (TN.extSolPop outer_solver) #ifdef DEBUG -- Perform a check that the thing_inside did not cause cycles @@ -1905,3 +1920,25 @@ deferTcSForAllEq role loc (tvs1,body1) (tvs2,body2) } \end{code} +Interaction with an External SMT Solver +--------------------------------------- + +\begin{code} +extSolSend :: Ct -> TcS Bool +extSolSend ct = withExtSol (\s -> TN.extSolSend s ct) + +extSolPush :: TcS () +extSolPush = withExtSol TN.extSolPop + +extSolPop :: TcS () +extSolPop = withExtSol TN.extSolPop + +extSolCheck :: TcS TN.ExtSolRes +extSolCheck = withExtSol TN.extSolCheck + +withExtSol :: (TN.ExternalSolver -> IO a) -> TcS a +withExtSol m = TcS (liftIO . m . tcs_ext_solver) + + + +\end{code} From git at git.haskell.org Tue Apr 29 06:33:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 06:33:03 +0000 (UTC) Subject: [commit: ghc] wip/ext-solver: Separate terms by a space. (9e202c5) Message-ID: <20140429063303.A5D9C2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ext-solver Link : http://ghc.haskell.org/trac/ghc/changeset/9e202c54b359748b38b27903060b8b97a2d0ffb3/ghc >--------------------------------------------------------------- commit 9e202c54b359748b38b27903060b8b97a2d0ffb3 Author: Iavor S. Diatchki Date: Mon Apr 28 23:28:26 2014 -0700 Separate terms by a space. >--------------------------------------------------------------- 9e202c54b359748b38b27903060b8b97a2d0ffb3 compiler/typecheck/TcTypeNats.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcTypeNats.hs b/compiler/typecheck/TcTypeNats.hs index 17a1037..63d101f 100644 --- a/compiler/typecheck/TcTypeNats.hs +++ b/compiler/typecheck/TcTypeNats.hs @@ -1079,7 +1079,8 @@ renderSExpr ex = case ex of SAtom x -> showString x SList es -> showChar '(' . - foldr (\e m -> renderSExpr e . m) (showChar ')') es + foldr (\e m -> renderSExpr e . showChar ' ' . m) + (showChar ')') es parseSExpr :: String -> Maybe (SExpr, String) parseSExpr (c : more) | isSpace c = parseSExpr more From git at git.haskell.org Tue Apr 29 06:33:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 06:33:06 +0000 (UTC) Subject: [commit: ghc] wip/ext-solver: Evidence for proofs generate by external solver (fefcfc8) Message-ID: <20140429063306.E71492406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ext-solver Link : http://ghc.haskell.org/trac/ghc/changeset/fefcfc8fa9f3c522012d2147510e3f7381fd3b95/ghc >--------------------------------------------------------------- commit fefcfc8fa9f3c522012d2147510e3f7381fd3b95 Author: Iavor S. Diatchki Date: Mon Apr 28 23:29:25 2014 -0700 Evidence for proofs generate by external solver >--------------------------------------------------------------- fefcfc8fa9f3c522012d2147510e3f7381fd3b95 compiler/typecheck/TcTypeNats.hs | 24 ++++++++++++++++++++++-- 1 file changed, 22 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcTypeNats.hs b/compiler/typecheck/TcTypeNats.hs index 63d101f..66894a1 100644 --- a/compiler/typecheck/TcTypeNats.hs +++ b/compiler/typecheck/TcTypeNats.hs @@ -3,11 +3,13 @@ module TcTypeNats , typeNatCoAxiomRules , BuiltInSynFamily(..) , ExternalSolver(..), ExtSolRes(..), newExternalSolver + , evBySMT ) where import Type import Pair import TcType ( TcType, tcEqType ) +import TcEvidence ( mkTcAxiomRuleCo, EvTerm(..) ) import TyCon ( TyCon, SynTyConRhs(..), mkSynTyCon, TyConParent(..) ) import Coercion ( Role(..) ) import TcRnTypes ( Xi, Ct(..) ) @@ -288,9 +290,27 @@ typeNatCoAxiomRules = Map.fromList $ map (\x -> (coaxrName x, x)) ] +decisionProcedure :: String -> CoAxiomRule +decisionProcedure name = + CoAxiomRule + { coaxrName = fsLit name + , coaxrTypeArity = 2 + , coaxrAsmpRoles = [] + , coaxrRole = Nominal + , coaxrProves = \ts cs -> + case (ts,cs) of + ([s,t],[]) -> return (s === t) + _ -> Nothing + } -{------------------------------------------------------------------------------- -Various utilities for making axioms and types + +evBySMT :: String -> (Type, Type) -> EvTerm +evBySMT name (t1,t2) = + EvCoercion $ mkTcAxiomRuleCo (decisionProcedure name) [t1,t2] [] + + + +-- Various utilities for making axioms and types -------------------------------------------------------------------------------} (.+.) :: Type -> Type -> Type From git at git.haskell.org Tue Apr 29 06:33:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 06:33:10 +0000 (UTC) Subject: [commit: ghc] wip/ext-solver: Fix strictness bug; add `extSolProve` to the interface. (92c8e50) Message-ID: <20140429063311.269F22406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ext-solver Link : http://ghc.haskell.org/trac/ghc/changeset/92c8e509e19188984d9325cead7bd31b3add5a60/ghc >--------------------------------------------------------------- commit 92c8e509e19188984d9325cead7bd31b3add5a60 Author: Iavor S. Diatchki Date: Mon Apr 28 23:30:12 2014 -0700 Fix strictness bug; add `extSolProve` to the interface. >--------------------------------------------------------------- 92c8e509e19188984d9325cead7bd31b3add5a60 compiler/typecheck/TcTypeNats.hs | 79 ++++++++++++++++++++++++-------------- 1 file changed, 50 insertions(+), 29 deletions(-) diff --git a/compiler/typecheck/TcTypeNats.hs b/compiler/typecheck/TcTypeNats.hs index 66894a1..3b000e6 100644 --- a/compiler/typecheck/TcTypeNats.hs +++ b/compiler/typecheck/TcTypeNats.hs @@ -46,7 +46,8 @@ import qualified Data.Set as Set import Data.Maybe ( isJust, mapMaybe ) import Data.Char ( isSpace ) import Data.List ( unfoldr, mapAccumL, foldl' ) -import Data.IORef ( newIORef, atomicModifyIORef', modifyIORef' +import Data.IORef ( newIORef, atomicModifyIORef', + atomicModifyIORef, modifyIORef' , readIORef ) import Control.Monad (forever) @@ -723,11 +724,12 @@ genLog x base = Just (exactLoop 0 x) -- Interface data ExternalSolver = ExternalSolver - { extSolPush :: IO () - , extSolPop :: IO () - , extSolSend :: Ct -> IO Bool - , extSolCheck :: IO ExtSolRes - , extSolStop :: IO () + { extSolPush :: IO () -- ^ Mark current set of assumptions + , extSolPop :: IO () -- ^ Revert to the last marked place + , extSolAssume :: Ct -> IO Bool -- ^ Add an assumption + , extSolCheck :: IO ExtSolRes -- ^ Chkeck if assumptions are consistent + , extSolProve :: Ct -> IO Bool -- ^ Try to prove this + , extSolStop :: IO () -- ^ Exit the solver } data ExtSolRes = ExtSolSat [(TyVar, Type)] @@ -751,39 +753,57 @@ newExternalSolver exe opts = simpleCmd [ "set-option", ":produce-models", "true" ] simpleCmd [ "set-logic", "QF_LIA" ] - viRef <- newIORef emptyVarInfo - return ExternalSolver - { extSolPush = - do simpleCmd [ "push" ] - modifyIORef' viRef startScope - - , extSolPop = - do simpleCmd [ "pop" ] - modifyIORef' viRef endScope + let push = do simpleCmd [ "push" ] + modifyIORef' viRef startScope + pop = do simpleCmd [ "pop" ] + modifyIORef' viRef endScope - , extSolSend = \ct -> + assume neg ct = case knownCt ct of Nothing -> return False Just (vs,e) -> do stmtss <- atomicModifyIORef' viRef $ \vi -> mapAccumL smtDeclarePerhaps vi (eltsUFM vs) mapM_ (mapM_ ackCmd) stmtss - ackCmd $ smtAssert e + ackCmd $ smtAssert $ if neg then Not e else e return True - , extSolCheck = - do res <- solverDo proc (SList [ SAtom "check-sat" ]) - case res of - SAtom "unsat" -> return ExtSolUnsat - SAtom "unknown" -> return ExtSolUnknown - SAtom "sat" -> - do vs <- readIORef viRef - model <- smtGetModel proc vs - return (ExtSolSat model) + checkSimple = + do res <- solverDo proc (SList [ SAtom "check-sat" ]) + case res of + SAtom "unsat" -> return ExtSolUnsat + SAtom "unknown" -> return ExtSolUnknown + SAtom "sat" -> return (ExtSolSat []) + _ -> unexpected res - _ -> unexpected res + + + return ExternalSolver + { extSolPush = push + , extSolPop = pop + , extSolAssume = assume False + , extSolCheck = + do res <- checkSimple + case res of + ExtSolSat _ -> + do vs <- readIORef viRef + model <- smtGetModel proc vs + return (ExtSolSat model) + _ -> return res + + , extSolProve = \ct -> + do push + ours <- assume True ct + proved <- if ours + then do res <- checkSimple + case res of + ExtSolUnsat -> return True + _ -> return False + else return False + pop + return proved , extSolStop = solverStop proc } @@ -1074,12 +1094,13 @@ startSolverProcess exe opts = do txt <- hGetContents hOut ref <- newIORef (unfoldr parseSExpr txt) return $ - atomicModifyIORef' ref $ \xs -> + atomicModifyIORef ref $ \xs -> case xs of [] -> (xs, Nothing) y : ys -> (ys, Just y) - let cmd' c = do hPutStrLn hIn (renderSExpr c "") + let cmd' c = do let e = renderSExpr c "" + hPutStrLn hIn e hFlush hIn return SolverProcess From git at git.haskell.org Tue Apr 29 06:33:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 06:33:14 +0000 (UTC) Subject: [commit: ghc] wip/ext-solver: Fix definition of `push`; add a TcS wrapper form `extSolProve`. (bb9486f) Message-ID: <20140429063314.1E7C32406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ext-solver Link : http://ghc.haskell.org/trac/ghc/changeset/bb9486f1c4aa74431796b510863301404a93ae3a/ghc >--------------------------------------------------------------- commit bb9486f1c4aa74431796b510863301404a93ae3a Author: Iavor S. Diatchki Date: Mon Apr 28 23:31:37 2014 -0700 Fix definition of `push`; add a TcS wrapper form `extSolProve`. >--------------------------------------------------------------- bb9486f1c4aa74431796b510863301404a93ae3a compiler/typecheck/TcSMonad.lhs | 17 ++++++++++------- 1 file changed, 10 insertions(+), 7 deletions(-) diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index 6a43511..2c2c93c 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -83,7 +83,8 @@ module TcSMonad ( Untouchables, isTouchableMetaTyVarTcS, isFilledMetaTyVar_maybe, zonkTyVarsAndFV, - TN.ExtSolRes(..), extSolSend, extSolPush, extSolPop, extSolCheck, + TN.ExtSolRes(..), extSolAssume, extSolProve, extSolCheck, + extSolPush, extSolPop, getDefaultInfo, getDynFlags, getGlobalRdrEnvTcS, @@ -1069,9 +1070,8 @@ runTcSWithEvBinds ev_binds_var tcs ; step_count <- TcM.newTcRef 0 ; inert_var <- TcM.newTcRef is - ; extSol <- liftIO $ - TN.newExternalSolver "cvc4" [ "--incremental" - , "--lang=smtlib2" ] + ; extSol <- liftIO $ TN.newExternalSolver "cvc4" + [ "--incremental", "--lang=smtlib2" ] ; let env = TcSEnv { tcs_ev_binds = ev_binds_var , tcs_ty_binds = ty_binds_var @@ -1924,11 +1924,14 @@ Interaction with an External SMT Solver --------------------------------------- \begin{code} -extSolSend :: Ct -> TcS Bool -extSolSend ct = withExtSol (\s -> TN.extSolSend s ct) +extSolAssume :: Ct -> TcS Bool +extSolAssume ct = withExtSol (\s -> TN.extSolAssume s ct) + +extSolProve :: Ct -> TcS Bool +extSolProve ct = withExtSol (\s -> TN.extSolProve s ct) extSolPush :: TcS () -extSolPush = withExtSol TN.extSolPop +extSolPush = withExtSol TN.extSolPush extSolPop :: TcS () extSolPop = withExtSol TN.extSolPop From git at git.haskell.org Tue Apr 29 06:33:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 06:33:16 +0000 (UTC) Subject: [commit: ghc] wip/ext-solver: The external solver stage (incomplete, improvement is missing) (8cf639a) Message-ID: <20140429063316.A2FD12406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ext-solver Link : http://ghc.haskell.org/trac/ghc/changeset/8cf639ae223ec914cea79cf4c47bda9e1d385d07/ghc >--------------------------------------------------------------- commit 8cf639ae223ec914cea79cf4c47bda9e1d385d07 Author: Iavor S. Diatchki Date: Mon Apr 28 23:32:20 2014 -0700 The external solver stage (incomplete, improvement is missing) >--------------------------------------------------------------- 8cf639ae223ec914cea79cf4c47bda9e1d385d07 compiler/typecheck/TcInteract.lhs | 57 +++++++++++++++++++++++++++++++++++-- 1 file changed, 55 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index b8c4c81..8fce795 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -34,6 +34,7 @@ import Outputable import TcRnTypes import TcErrors import TcSMonad +import TcTypeNats(evBySMT) import Bag import Control.Monad ( foldM ) @@ -223,10 +224,61 @@ React with (F Int ~ b) ==> IR Stop True [] -- after substituting we re-canoni thePipeline :: [(String,SimplifierStage)] thePipeline = [ ("canonicalization", TcCanonical.canonicalize) , ("interact with inerts", interactWithInertsStage) - , ("top-level reactions", topReactionsStage) ] + , ("top-level reactions", topReactionsStage) + , ("external solver", externalSolverStage) ] \end{code} +******************************************************************************** +* +* External Solver +* +******************************************************************************** + +\begin{code} +externalSolverStage :: WorkItem -> TcS StopOrContinue +externalSolverStage wi + | isGivenCt wi = + extSolAssume wi >>= \ours -> if not ours then return (ContinueWith wi) else + do res <- extSolCheck + case res of + ExtSolUnsat -> emitInsoluble wi >> return Stop + ExtSolSat m -> improveFrom m >> return (ContinueWith wi) + ExtSolUnknown -> return (ContinueWith wi) + + | otherwise = + do extSolPush + ours <- extSolAssume wi + if not ours + then do extSolPop + return (ContinueWith wi) + else do res <- extSolCheck + extSolPop + case res of + ExtSolUnsat -> emitInsoluble wi >> return Stop + ExtSolSat m -> improveFrom m >> tryToProve + ExtSolUnknown -> tryToProve + + where + tryToProve = + do proved <- extSolProve wi + if proved + then do when (isWantedCt wi) + $ setEvBind (ctEvId $ ctEvidence wi) + $ evBySMT "SMT" $ getEqPredTys $ ctPred wi + return Stop + else do _ <- extSolAssume wi -- Remember for later + return (ContinueWith wi) + + -- XXX: Add improvements + improveFrom m = return () + +\end{code} + + + + + ********************************************************************************* * * The interact-with-inert Stage @@ -690,7 +742,8 @@ interactTyVarEq inerts workItem@(CTyEqCan { cc_tyvar = tv, cc_rhs = rhs , cc_ev ; return (Nothing, True) } | otherwise - = do { mb_solved <- trySpontaneousSolve ev tv rhs + = do { _ <- extSolAssume workItem + ; mb_solved <- trySpontaneousSolve ev tv rhs ; case mb_solved of SPCantSolve -- Includes givens -> do { untch <- getUntouchables From git at git.haskell.org Tue Apr 29 08:44:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 08:44:13 +0000 (UTC) Subject: [commit: ghc] master: Fix scavenge_stack crash (#9045) (ab8bb48) Message-ID: <20140429084413.6A7F22406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ab8bb4893be1896303f30d0f1adff8ea9c2470f6/ghc >--------------------------------------------------------------- commit ab8bb4893be1896303f30d0f1adff8ea9c2470f6 Author: Simon Marlow Date: Mon Apr 28 16:36:29 2014 +0100 Fix scavenge_stack crash (#9045) The new stg_gc_prim_p_ll stack frame was missing an info table. This is a regression since 7.6, because this stuff was part of a cleanup that happened in 7.7. >--------------------------------------------------------------- ab8bb4893be1896303f30d0f1adff8ea9c2470f6 rts/HeapStackCheck.cmm | 5 +++-- testsuite/tests/rts/T9045.hs | 22 ++++++++++++++++++++++ testsuite/tests/rts/all.T | 5 +++++ 3 files changed, 30 insertions(+), 2 deletions(-) diff --git a/rts/HeapStackCheck.cmm b/rts/HeapStackCheck.cmm index d826529..12bcfb2 100644 --- a/rts/HeapStackCheck.cmm +++ b/rts/HeapStackCheck.cmm @@ -196,7 +196,8 @@ stg_gc_prim_n (W_ arg, W_ fun) jump fun(arg); } -stg_gc_prim_p_ll_ret +INFO_TABLE_RET(stg_gc_prim_p_ll, RET_SMALL, W_ info, P_ arg, W_ fun) + /* explicit stack */ { W_ fun; P_ arg; @@ -216,7 +217,7 @@ stg_gc_prim_p_ll Sp_adj(-3); Sp(2) = fun; Sp(1) = arg; - Sp(0) = stg_gc_prim_p_ll_ret; + Sp(0) = stg_gc_prim_p_ll_info; jump stg_gc_noregs []; } diff --git a/testsuite/tests/rts/T9045.hs b/testsuite/tests/rts/T9045.hs new file mode 100644 index 0000000..1e581ef --- /dev/null +++ b/testsuite/tests/rts/T9045.hs @@ -0,0 +1,22 @@ +-- This is nofib/smp/threads006. It fails in GHC 7.8.2 with a GC crash. + +{-# OPTIONS_GHC -O2 #-} +import System.IO +import System.Environment +import System.CPUTime +import Text.Printf +import Control.Monad +import Control.Concurrent +import Control.Concurrent.MVar +import Control.Exception + +main :: IO () +main = do + hSetBuffering stdout NoBuffering + [nthreads] <- fmap (map read) getArgs + tids <- replicateM nthreads . mask $ \_ -> forkIO $ return () + m <- newEmptyMVar + -- do it in a subthread to avoid bound-thread overhead + forkIO $ do mapM_ killThread tids; putMVar m () + takeMVar m + return () diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index 9239f44..f5a72f8 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -222,3 +222,8 @@ test('T8124', [ only_ways(threaded_ways), omit_ways(['ghci']), # T8124_stub.h before compiling T8124_c.c, which # needs it. compile_and_run, ['T8124_c.c -no-hs-main']) + +# +RTS -A8k makes it fail faster +# The ghci way gets confused by the RTS options +test('T9045', [ omit_ways(['ghci']), extra_run_opts('10000 +RTS -A8k -RTS') ], compile_and_run, ['']) + From git at git.haskell.org Tue Apr 29 12:12:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 12:12:44 +0000 (UTC) Subject: [commit: ghc] wip/pattern-synonyms: Pattern synonyms have no implicit Ids (e51b7fa) Message-ID: <20140429121244.1EB992406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/pattern-synonyms Link : http://ghc.haskell.org/trac/ghc/changeset/e51b7fa368ff1ea91828aecd473057299e08f718/ghc >--------------------------------------------------------------- commit e51b7fa368ff1ea91828aecd473057299e08f718 Author: Simon Peyton Jones Date: Tue Apr 29 13:10:09 2014 +0100 Pattern synonyms have no implicit Ids >--------------------------------------------------------------- e51b7fa368ff1ea91828aecd473057299e08f718 compiler/iface/IfaceSyn.lhs | 6 ------ compiler/iface/TcIface.lhs | 5 ++++- compiler/main/HscTypes.lhs | 20 +++++++++++--------- 3 files changed, 15 insertions(+), 16 deletions(-) diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 61a2d69..47ce2cd 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -58,7 +58,6 @@ import BooleanFormula ( BooleanFormula ) import Control.Monad import System.IO.Unsafe -import Data.Maybe ( isJust ) infixl 3 &&& \end{code} @@ -1003,11 +1002,6 @@ ifaceDeclImplicitBndrs (IfaceClass {ifCtxt = sc_ctxt, ifName = cls_tc_occ, dc_occ = mkClassDataConOcc cls_tc_occ is_newtype = n_sigs + n_ctxt == 1 -- Sigh -ifaceDeclImplicitBndrs (IfacePatSyn{ ifName = ps_occ, ifPatWrapper = wrapper_name }) - = [wrap_occ | isJust wrapper_name] - where - wrap_occ = mkDataConWrapperOcc ps_occ - ifaceDeclImplicitBndrs _ = [] -- ----------------------------------------------------------------------------- diff --git a/compiler/iface/TcIface.lhs b/compiler/iface/TcIface.lhs index e8f2a15..df15c03 100644 --- a/compiler/iface/TcIface.lhs +++ b/compiler/iface/TcIface.lhs @@ -589,7 +589,10 @@ tc_iface_decl _ _ (IfacePatSyn{ ifName = occ_name , ifPatArgs = args }) = do { name <- lookupIfaceTop occ_name ; matcher <- tcExt "Matcher" matcher_name - ; wrapper <- maybe (return Nothing) (fmap Just . tcExt "Wrapper") wrapper_name + ; wrapper <- case wrapper_name of + Nothing -> return Nothing + Just wn -> do { wid <- tcExt "Wrapper" wn + ; return (Just wid) } ; argNames <- mapM (newIfaceName . mkVarOccFS) args ; return $ AConLike . PatSynCon $ buildPatSyn name is_infix matcher wrapper argNames } diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs index 6fcf8e2..58d0c58 100644 --- a/compiler/main/HscTypes.lhs +++ b/compiler/main/HscTypes.lhs @@ -1504,15 +1504,17 @@ implicitTyThings :: TyThing -> [TyThing] implicitTyThings (AnId _) = [] implicitTyThings (ACoAxiom _cc) = [] implicitTyThings (ATyCon tc) = implicitTyConThings tc -implicitTyThings (AConLike cl) = case cl of - RealDataCon dc -> - -- For data cons add the worker and (possibly) wrapper - map AnId (dataConImplicitIds dc) - PatSynCon ps -> - -- For bidirectional pattern synonyms, add the wrapper - case patSynWrapper ps of - Nothing -> [] - Just id -> [AnId id] +implicitTyThings (AConLike cl) = implicitConLikeThings cl + +implicitConLikeThings :: ConLike -> [TyThing] +implicitConLikeThings (RealDataCon dc) + = map AnId (dataConImplicitIds dc) + -- For data cons add the worker and (possibly) wrapper + +implicitConLikeThings (PatSynCon {}) + = [] -- Pattern synonyms have no implicit Ids; the wrapper and matcher + -- are not "implicit"; they are simply new top-level bindings, + -- and they have their own declaration in an interface fiel implicitClassThings :: Class -> [TyThing] implicitClassThings cl From git at git.haskell.org Tue Apr 29 12:12:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 12:12:48 +0000 (UTC) Subject: [commit: ghc] wip/pattern-synonyms: Move comments around and re-factor psTheta (d7c4c8a) Message-ID: <20140429121248.6A5962406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/pattern-synonyms Link : http://ghc.haskell.org/trac/ghc/changeset/d7c4c8ae08af03ad21c56ca6809979c056c1c28b/ghc >--------------------------------------------------------------- commit d7c4c8ae08af03ad21c56ca6809979c056c1c28b Author: Simon Peyton Jones Date: Tue Apr 29 13:11:33 2014 +0100 Move comments around and re-factor psTheta Cosmetic changes only in here. The only significant change is splitting psTheta into two fields >--------------------------------------------------------------- d7c4c8ae08af03ad21c56ca6809979c056c1c28b compiler/basicTypes/PatSyn.lhs | 83 +++++++++++++++++++++++++++++++-------- compiler/typecheck/TcPat.lhs | 2 +- compiler/typecheck/TcPatSyn.lhs | 57 +-------------------------- 3 files changed, 70 insertions(+), 72 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d7c4c8ae08af03ad21c56ca6809979c056c1c28b From git at git.haskell.org Tue Apr 29 12:12:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 12:12:53 +0000 (UTC) Subject: [commit: ghc] wip/pattern-synonyms: Comments and tracing only (e54d396) Message-ID: <20140429121253.AD6792406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/pattern-synonyms Link : http://ghc.haskell.org/trac/ghc/changeset/e54d39675227f24c91366928a86f4752e169ee25/ghc >--------------------------------------------------------------- commit e54d39675227f24c91366928a86f4752e169ee25 Author: Simon Peyton Jones Date: Tue Apr 29 13:11:51 2014 +0100 Comments and tracing only >--------------------------------------------------------------- e54d39675227f24c91366928a86f4752e169ee25 compiler/coreSyn/CorePrep.lhs | 1 + compiler/iface/LoadIface.lhs | 3 ++- compiler/main/TidyPgm.lhs | 2 +- 3 files changed, 4 insertions(+), 2 deletions(-) diff --git a/compiler/coreSyn/CorePrep.lhs b/compiler/coreSyn/CorePrep.lhs index 5e0cd65..d0a07cc 100644 --- a/compiler/coreSyn/CorePrep.lhs +++ b/compiler/coreSyn/CorePrep.lhs @@ -196,6 +196,7 @@ corePrepTopBinds initialCorePrepEnv binds mkDataConWorkers :: [TyCon] -> [CoreBind] -- See Note [Data constructor workers] +-- c.f. Note [Injecting implicit bindings] in TidyPgm mkDataConWorkers data_tycons = [ NonRec id (Var id) -- The ice is thin here, but it works | tycon <- data_tycons, -- CorePrep will eta-expand it diff --git a/compiler/iface/LoadIface.lhs b/compiler/iface/LoadIface.lhs index d787794..dfcad96 100644 --- a/compiler/iface/LoadIface.lhs +++ b/compiler/iface/LoadIface.lhs @@ -416,7 +416,6 @@ loadDecl ignore_prags mod (_version, decl) = do { -- Populate the name cache with final versions of all -- the names associated with the decl main_name <- lookupOrig mod (ifName decl) --- ; traceIf (text "Loading decl for " <> ppr main_name) -- Typecheck the thing, lazily -- NB. Firstly, the laziness is there in case we never need the @@ -490,6 +489,8 @@ loadDecl ignore_prags mod (_version, decl) pprPanic "loadDecl" (ppr main_name <+> ppr n $$ ppr (decl)) ; implicit_names <- mapM (lookupOrig mod) (ifaceDeclImplicitBndrs decl) + +-- ; traceIf (text "Loading decl for " <> ppr main_name $$ ppr implicit_names) ; return $ (main_name, thing) : -- uses the invariant that implicit_names and -- implictTyThings are bijective diff --git a/compiler/main/TidyPgm.lhs b/compiler/main/TidyPgm.lhs index b20658b..e9abb21 100644 --- a/compiler/main/TidyPgm.lhs +++ b/compiler/main/TidyPgm.lhs @@ -559,7 +559,7 @@ Oh: two other reasons for injecting them late: There is one sort of implicit binding that is injected still later, namely those for data constructor workers. Reason (I think): it's really just a code generation trick.... binding itself makes no sense. -See CorePrep Note [Data constructor workers]. +See Note [Data constructor workers] in CorePrep. \begin{code} getTyConImplicitBinds :: TyCon -> [CoreBind] From git at git.haskell.org Tue Apr 29 12:52:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 12:52:43 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Fix scavenge_stack crash (#9045) (ce6ab2d) Message-ID: <20140429125243.477DE2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/ce6ab2ddaec4d0440f9720279eb596f5932d9605/ghc >--------------------------------------------------------------- commit ce6ab2ddaec4d0440f9720279eb596f5932d9605 Author: Simon Marlow Date: Mon Apr 28 16:36:29 2014 +0100 Fix scavenge_stack crash (#9045) The new stg_gc_prim_p_ll stack frame was missing an info table. This is a regression since 7.6, because this stuff was part of a cleanup that happened in 7.7. (cherry picked from commit ab8bb4893be1896303f30d0f1adff8ea9c2470f6) >--------------------------------------------------------------- ce6ab2ddaec4d0440f9720279eb596f5932d9605 rts/HeapStackCheck.cmm | 5 +++-- testsuite/tests/rts/T9045.hs | 22 ++++++++++++++++++++++ testsuite/tests/rts/all.T | 5 +++++ 3 files changed, 30 insertions(+), 2 deletions(-) diff --git a/rts/HeapStackCheck.cmm b/rts/HeapStackCheck.cmm index d826529..12bcfb2 100644 --- a/rts/HeapStackCheck.cmm +++ b/rts/HeapStackCheck.cmm @@ -196,7 +196,8 @@ stg_gc_prim_n (W_ arg, W_ fun) jump fun(arg); } -stg_gc_prim_p_ll_ret +INFO_TABLE_RET(stg_gc_prim_p_ll, RET_SMALL, W_ info, P_ arg, W_ fun) + /* explicit stack */ { W_ fun; P_ arg; @@ -216,7 +217,7 @@ stg_gc_prim_p_ll Sp_adj(-3); Sp(2) = fun; Sp(1) = arg; - Sp(0) = stg_gc_prim_p_ll_ret; + Sp(0) = stg_gc_prim_p_ll_info; jump stg_gc_noregs []; } diff --git a/testsuite/tests/rts/T9045.hs b/testsuite/tests/rts/T9045.hs new file mode 100644 index 0000000..1e581ef --- /dev/null +++ b/testsuite/tests/rts/T9045.hs @@ -0,0 +1,22 @@ +-- This is nofib/smp/threads006. It fails in GHC 7.8.2 with a GC crash. + +{-# OPTIONS_GHC -O2 #-} +import System.IO +import System.Environment +import System.CPUTime +import Text.Printf +import Control.Monad +import Control.Concurrent +import Control.Concurrent.MVar +import Control.Exception + +main :: IO () +main = do + hSetBuffering stdout NoBuffering + [nthreads] <- fmap (map read) getArgs + tids <- replicateM nthreads . mask $ \_ -> forkIO $ return () + m <- newEmptyMVar + -- do it in a subthread to avoid bound-thread overhead + forkIO $ do mapM_ killThread tids; putMVar m () + takeMVar m + return () diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index f7c4986..102a671 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -207,3 +207,8 @@ test('T8124', [ only_ways(threaded_ways), omit_ways(['ghci']), # T8124_stub.h before compiling T8124_c.c, which # needs it. compile_and_run, ['T8124_c.c -no-hs-main']) + +# +RTS -A8k makes it fail faster +# The ghci way gets confused by the RTS options +test('T9045', [ omit_ways(['ghci']), extra_run_opts('10000 +RTS -A8k -RTS') ], compile_and_run, ['']) + From git at git.haskell.org Tue Apr 29 13:35:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 13:35:24 +0000 (UTC) Subject: [commit: ghc] master: Typo in comments (1d0798c) Message-ID: <20140429133524.7E4942406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1d0798c3f1b270a71cef39c1bb4da1ad3f11280c/ghc >--------------------------------------------------------------- commit 1d0798c3f1b270a71cef39c1bb4da1ad3f11280c Author: Gabor Greif Date: Tue Apr 29 15:34:29 2014 +0200 Typo in comments >--------------------------------------------------------------- 1d0798c3f1b270a71cef39c1bb4da1ad3f11280c compiler/typecheck/TcRnTypes.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index 4b86fa0..f3df0bf 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -294,7 +294,7 @@ data TcGblEnv -- ^ Allows us to choose unique DFun names. -- The next fields accumulate the payload of the module - -- The binds, rules and foreign-decl fiels are collected + -- The binds, rules and foreign-decl fields are collected -- initially in un-zonked form and are finally zonked in tcRnSrcDecls tcg_rn_exports :: Maybe [Located (IE Name)], From git at git.haskell.org Tue Apr 29 13:40:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 13:40:17 +0000 (UTC) Subject: [commit: ghc] master: Typo in comment (3a5c549) Message-ID: <20140429134017.B8F472406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3a5c549ee3ddd10b7c48527539d1e2fac5acb1c2/ghc >--------------------------------------------------------------- commit 3a5c549ee3ddd10b7c48527539d1e2fac5acb1c2 Author: Gabor Greif Date: Tue Apr 29 15:38:29 2014 +0200 Typo in comment >--------------------------------------------------------------- 3a5c549ee3ddd10b7c48527539d1e2fac5acb1c2 libraries/base/GHC/Enum.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/GHC/Enum.lhs b/libraries/base/GHC/Enum.lhs index fe2e6b6..d94e2ec 100644 --- a/libraries/base/GHC/Enum.lhs +++ b/libraries/base/GHC/Enum.lhs @@ -705,7 +705,7 @@ enumDeltaToIntegerFB c n x delta lim "enumDeltaToInteger1" [0] forall c n x . enumDeltaToIntegerFB c n x 1 = up_fb c n x 1 #-} -- This rule ensures that in the common case (delta = 1), we do not do the check here, --- and also that we have the chance to inline up_fb, which would allow the constuctor to be +-- and also that we have the chance to inline up_fb, which would allow the constructor to be -- inlined and good things to happen. -- We do not do it for Int this way because hand-tuned code already exists, and -- the special case varies more from the general case, due to the issue of overflows. From git at git.haskell.org Tue Apr 29 13:50:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 13:50:11 +0000 (UTC) Subject: [commit: ghc] master: rts: Add an initial Coverity model (4539400) Message-ID: <20140429135011.95ECE2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4539400a72ded7fa69149b28cfa9c84464f4739d/ghc >--------------------------------------------------------------- commit 4539400a72ded7fa69149b28cfa9c84464f4739d Author: Austin Seipp Date: Tue Apr 29 08:48:57 2014 -0500 rts: Add an initial Coverity model Signed-off-by: Austin Seipp >--------------------------------------------------------------- 4539400a72ded7fa69149b28cfa9c84464f4739d rts/Coverity.c | 112 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 112 insertions(+) diff --git a/rts/Coverity.c b/rts/Coverity.c new file mode 100644 index 0000000..d0a3708 --- /dev/null +++ b/rts/Coverity.c @@ -0,0 +1,112 @@ +/* Coverity Scan model + * This is a modeling file for Coverity Scan. Modeling helps to avoid false + * positives. + * + * - A model file can't import any header files. Some built-in primitives are + * available but not wchar_t, NULL etc. + * - Modeling doesn't need full structs and typedefs. Rudimentary structs + * and similar types are sufficient. + * - An uninitialized local variable signifies that the variable could be + * any value. + * + * The model file must be uploaded by an admin in the analysis settings of + * http://scan.coverity.com/projects/1919 + */ + +#define NULL ((void*)0) +#define assert(x) if (!(x)) __coverity_panic__(); + +/* type decls */ +typedef struct {} va_list; + +/* glibc functions */ +void *malloc (size_t); +void *calloc (size_t, size_t); +void *realloc (void *, size_t); +void free (void *); + +/* rts allocation functions */ + +void* stgMallocBytes(int n, char *msg) +{ + void *mem; + __coverity_negative_sink__((size_t)n); + mem = malloc((size_t)n); + assert(mem != NULL); + return mem; +} + +void* stgReallocBytes(void *p, int n, char *msg) +{ + void *mem; + __coverity_negative_sink__((size_t)n); + + /* man 3 realloc: if p == NULL, then realloc is equivalent to malloc() */ + if (p == NULL) { + mem = malloc((size_t)n); + assert(mem != NULL); + return mem; + } + + /* man 3 realloc: if n == 0, then realloc is equivalent to free() */ + if (n == 0) { + free(p); + return NULL; + } else { + mem = realloc(p, (size_t)n); + assert(mem != NULL); + return mem; + } +} + +void* stgCallocBytes(int n, int m, char *msg) +{ + void *mem; + __coverity_negative_sink__((size_t)n); + __coverity_negative_sink__((size_t)m); + mem = calloc(n, m); + assert(mem != NULL); + return mem; +} + +void stgFree(void* p) +{ + free(p); +} + +/* Kill paths */ + +void stg_exit(int n) +{ + __coverity_panic__(); +} + +void shutdownThread(void) +{ + __coverity_panic__(); +} + +void shutdownHaskellAndExit(int exitCode, int fastExit) +{ + __coverity_panic__(); +} + +void shutdownHaskellAndSignal(int sig, int fastExit) +{ + __coverity_panic__(); +} + +void _assertFail(const char *filename, unsigned int linenum) +{ + __coverity_panic__(); +} + +void barf(const char *s, ...) +{ + __coverity_panic__(); +} + +void vbarf(const char *s, va_list ap) +{ + __coverity_panic__(); +} From git at git.haskell.org Tue Apr 29 14:59:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 14:59:57 +0000 (UTC) Subject: [commit: ghc] master: Revert "rts: Add an initial Coverity model" (7400810) Message-ID: <20140429145957.DF6D12406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7400810e3fb0af85da0cfb2b940bfe563687863f/ghc >--------------------------------------------------------------- commit 7400810e3fb0af85da0cfb2b940bfe563687863f Author: Austin Seipp Date: Tue Apr 29 09:59:01 2014 -0500 Revert "rts: Add an initial Coverity model" This reverts commit 4539400a72ded7fa69149b28cfa9c84464f4739d. >--------------------------------------------------------------- 7400810e3fb0af85da0cfb2b940bfe563687863f rts/Coverity.c | 112 -------------------------------------------------------- 1 file changed, 112 deletions(-) diff --git a/rts/Coverity.c b/rts/Coverity.c deleted file mode 100644 index d0a3708..0000000 --- a/rts/Coverity.c +++ /dev/null @@ -1,112 +0,0 @@ -/* Coverity Scan model - * This is a modeling file for Coverity Scan. Modeling helps to avoid false - * positives. - * - * - A model file can't import any header files. Some built-in primitives are - * available but not wchar_t, NULL etc. - * - Modeling doesn't need full structs and typedefs. Rudimentary structs - * and similar types are sufficient. - * - An uninitialized local variable signifies that the variable could be - * any value. - * - * The model file must be uploaded by an admin in the analysis settings of - * http://scan.coverity.com/projects/1919 - */ - -#define NULL ((void*)0) -#define assert(x) if (!(x)) __coverity_panic__(); - -/* type decls */ -typedef struct {} va_list; - -/* glibc functions */ -void *malloc (size_t); -void *calloc (size_t, size_t); -void *realloc (void *, size_t); -void free (void *); - -/* rts allocation functions */ - -void* stgMallocBytes(int n, char *msg) -{ - void *mem; - __coverity_negative_sink__((size_t)n); - mem = malloc((size_t)n); - assert(mem != NULL); - return mem; -} - -void* stgReallocBytes(void *p, int n, char *msg) -{ - void *mem; - __coverity_negative_sink__((size_t)n); - - /* man 3 realloc: if p == NULL, then realloc is equivalent to malloc() */ - if (p == NULL) { - mem = malloc((size_t)n); - assert(mem != NULL); - return mem; - } - - /* man 3 realloc: if n == 0, then realloc is equivalent to free() */ - if (n == 0) { - free(p); - return NULL; - } else { - mem = realloc(p, (size_t)n); - assert(mem != NULL); - return mem; - } -} - -void* stgCallocBytes(int n, int m, char *msg) -{ - void *mem; - __coverity_negative_sink__((size_t)n); - __coverity_negative_sink__((size_t)m); - mem = calloc(n, m); - assert(mem != NULL); - return mem; -} - -void stgFree(void* p) -{ - free(p); -} - -/* Kill paths */ - -void stg_exit(int n) -{ - __coverity_panic__(); -} - -void shutdownThread(void) -{ - __coverity_panic__(); -} - -void shutdownHaskellAndExit(int exitCode, int fastExit) -{ - __coverity_panic__(); -} - -void shutdownHaskellAndSignal(int sig, int fastExit) -{ - __coverity_panic__(); -} - -void _assertFail(const char *filename, unsigned int linenum) -{ - __coverity_panic__(); -} - -void barf(const char *s, ...) -{ - __coverity_panic__(); -} - -void vbarf(const char *s, va_list ap) -{ - __coverity_panic__(); -} From git at git.haskell.org Tue Apr 29 18:52:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 18:52:49 +0000 (UTC) Subject: [commit: ghc] master: Add Note [Role twiddling functions] to Coercion. (91cc88b) Message-ID: <20140429185249.52CF82406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/91cc88b3d2dbbd64c63d6359bd32cf3ba3f546ab/ghc >--------------------------------------------------------------- commit 91cc88b3d2dbbd64c63d6359bd32cf3ba3f546ab Author: Richard Eisenberg Date: Tue Apr 29 11:55:56 2014 -0400 Add Note [Role twiddling functions] to Coercion. This commit also makes better names for several of these functions, and removes one that went unused. >--------------------------------------------------------------- 91cc88b3d2dbbd64c63d6359bd32cf3ba3f546ab compiler/types/Coercion.lhs | 152 ++++++++++++++++++++++++++-------------- compiler/types/OptCoercion.lhs | 2 +- 2 files changed, 100 insertions(+), 54 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 91cc88b3d2dbbd64c63d6359bd32cf3ba3f546ab From git at git.haskell.org Tue Apr 29 19:14:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 19:14:36 +0000 (UTC) Subject: [commit: ghc] master: rts: Add an initial Coverity model (275ea0f) Message-ID: <20140429191436.D818B2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/275ea0ff391297b184e5c9cf2f87b26906f0e7e9/ghc >--------------------------------------------------------------- commit 275ea0ff391297b184e5c9cf2f87b26906f0e7e9 Author: Austin Seipp Date: Tue Apr 29 10:07:50 2014 -0500 rts: Add an initial Coverity model Signed-off-by: Austin Seipp >--------------------------------------------------------------- 275ea0ff391297b184e5c9cf2f87b26906f0e7e9 utils/coverity/model.c | 112 ++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 112 insertions(+) diff --git a/utils/coverity/model.c b/utils/coverity/model.c new file mode 100644 index 0000000..d0a3708 --- /dev/null +++ b/utils/coverity/model.c @@ -0,0 +1,112 @@ +/* Coverity Scan model + * This is a modeling file for Coverity Scan. Modeling helps to avoid false + * positives. + * + * - A model file can't import any header files. Some built-in primitives are + * available but not wchar_t, NULL etc. + * - Modeling doesn't need full structs and typedefs. Rudimentary structs + * and similar types are sufficient. + * - An uninitialized local variable signifies that the variable could be + * any value. + * + * The model file must be uploaded by an admin in the analysis settings of + * http://scan.coverity.com/projects/1919 + */ + +#define NULL ((void*)0) +#define assert(x) if (!(x)) __coverity_panic__(); + +/* type decls */ +typedef struct {} va_list; + +/* glibc functions */ +void *malloc (size_t); +void *calloc (size_t, size_t); +void *realloc (void *, size_t); +void free (void *); + +/* rts allocation functions */ + +void* stgMallocBytes(int n, char *msg) +{ + void *mem; + __coverity_negative_sink__((size_t)n); + mem = malloc((size_t)n); + assert(mem != NULL); + return mem; +} + +void* stgReallocBytes(void *p, int n, char *msg) +{ + void *mem; + __coverity_negative_sink__((size_t)n); + + /* man 3 realloc: if p == NULL, then realloc is equivalent to malloc() */ + if (p == NULL) { + mem = malloc((size_t)n); + assert(mem != NULL); + return mem; + } + + /* man 3 realloc: if n == 0, then realloc is equivalent to free() */ + if (n == 0) { + free(p); + return NULL; + } else { + mem = realloc(p, (size_t)n); + assert(mem != NULL); + return mem; + } +} + +void* stgCallocBytes(int n, int m, char *msg) +{ + void *mem; + __coverity_negative_sink__((size_t)n); + __coverity_negative_sink__((size_t)m); + mem = calloc(n, m); + assert(mem != NULL); + return mem; +} + +void stgFree(void* p) +{ + free(p); +} + +/* Kill paths */ + +void stg_exit(int n) +{ + __coverity_panic__(); +} + +void shutdownThread(void) +{ + __coverity_panic__(); +} + +void shutdownHaskellAndExit(int exitCode, int fastExit) +{ + __coverity_panic__(); +} + +void shutdownHaskellAndSignal(int sig, int fastExit) +{ + __coverity_panic__(); +} + +void _assertFail(const char *filename, unsigned int linenum) +{ + __coverity_panic__(); +} + +void barf(const char *s, ...) +{ + __coverity_panic__(); +} + +void vbarf(const char *s, va_list ap) +{ + __coverity_panic__(); +} From git at git.haskell.org Tue Apr 29 19:14:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 19:14:39 +0000 (UTC) Subject: [commit: ghc] master: rts: Fix memory leak when loading ELF objects (b7278d3) Message-ID: <20140429191439.4F0782406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b7278d3d7bbe384eee7538b1e50bb741e99fb01d/ghc >--------------------------------------------------------------- commit b7278d3d7bbe384eee7538b1e50bb741e99fb01d Author: Austin Seipp Date: Tue Apr 29 09:09:25 2014 -0500 rts: Fix memory leak when loading ELF objects Issue discovered by Coverity Scan, CID 43168. Signed-off-by: Austin Seipp >--------------------------------------------------------------- b7278d3d7bbe384eee7538b1e50bb741e99fb01d rts/Linker.c | 1 + 1 file changed, 1 insertion(+) diff --git a/rts/Linker.c b/rts/Linker.c index 146e2d5..ea7c1c6 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -1900,6 +1900,7 @@ addDLL( pathchar *dll_name ) // success -- try to dlopen the first named file IF_DEBUG(linker, debugBelch("match%s\n","")); line[match[2].rm_eo] = '\0'; + stgFree((void*)errmsg); // Free old message before creating new one errmsg = internal_dlopen(line+match[2].rm_so); break; } From git at git.haskell.org Tue Apr 29 19:14:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 19:14:41 +0000 (UTC) Subject: [commit: ghc] master: rts: Fix leak of file archive handle (e597f5f) Message-ID: <20140429191444.5518E2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e597f5feb065c075c86715e24bf0ebd341fa8b9e/ghc >--------------------------------------------------------------- commit e597f5feb065c075c86715e24bf0ebd341fa8b9e Author: Austin Seipp Date: Tue Apr 29 09:05:38 2014 -0500 rts: Fix leak of file archive handle Issue discovered by Coverity Scan, CID 43171. Signed-off-by: Austin Seipp >--------------------------------------------------------------- e597f5feb065c075c86715e24bf0ebd341fa8b9e rts/Linker.c | 1 + 1 file changed, 1 insertion(+) diff --git a/rts/Linker.c b/rts/Linker.c index 1b0d48f..146e2d5 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -2718,6 +2718,7 @@ loadArchive( pathchar *path ) if (0 == loadOc(oc)) { stgFree(fileName); + fclose(f); return 0; } } From git at git.haskell.org Tue Apr 29 19:35:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 19:35:17 +0000 (UTC) Subject: [commit: ghc] master: Rts: Consistently use StgWord for sizes of bitmaps (43b3bab) Message-ID: <20140429193518.1A37B2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/43b3bab38eafef8c02a09fb4ff1e757f5cba6073/ghc >--------------------------------------------------------------- commit 43b3bab38eafef8c02a09fb4ff1e757f5cba6073 Author: Arash Rouhani Date: Thu Feb 13 15:28:11 2014 +0100 Rts: Consistently use StgWord for sizes of bitmaps A long debate is in issue #8742, but the main motivation is that this allows for applying a patch to reuse the function scavenge_small_bitmap without changing the .o-file output. Similarly, I changed the types in rts/sm/Compact.c, so I can create a STATIC_INLINE function for the redundant code block: while (size > 0) { if ((bitmap & 1) == 0) { thread((StgClosure **)p); } p++; bitmap = bitmap >> 1; size--; } >--------------------------------------------------------------- 43b3bab38eafef8c02a09fb4ff1e757f5cba6073 includes/rts/storage/ClosureMacros.h | 5 +++++ rts/sm/Compact.c | 14 +++++++------- rts/sm/Scav.c | 16 ++++++++-------- 3 files changed, 20 insertions(+), 15 deletions(-) diff --git a/includes/rts/storage/ClosureMacros.h b/includes/rts/storage/ClosureMacros.h index 92b78de..3407b71 100644 --- a/includes/rts/storage/ClosureMacros.h +++ b/includes/rts/storage/ClosureMacros.h @@ -338,6 +338,11 @@ EXTERN_INLINE StgWord bco_sizeW ( StgBCO *bco ); EXTERN_INLINE StgWord bco_sizeW ( StgBCO *bco ) { return bco->size; } +/* + * TODO: Consider to switch return type from 'nat' to 'StgWord' #8742 + * + * (Also for 'closure_sizeW' below) + */ EXTERN_INLINE nat closure_sizeW_ (StgClosure *p, StgInfoTable *info); EXTERN_INLINE nat closure_sizeW_ (StgClosure *p, StgInfoTable *info) diff --git a/rts/sm/Compact.c b/rts/sm/Compact.c index 8ae72a9..3731dd6 100644 --- a/rts/sm/Compact.c +++ b/rts/sm/Compact.c @@ -183,7 +183,7 @@ loop: // A word-aligned memmove will be faster for small objects than libc's or gcc's. // Remember, the two regions *might* overlap, but: to <= from. STATIC_INLINE void -move(StgPtr to, StgPtr from, W_ size) +move(StgPtr to, StgPtr from, StgWord size) { for(; size > 0; --size) { *to++ = *from++; @@ -225,7 +225,7 @@ thread_static( StgClosure* p ) } STATIC_INLINE void -thread_large_bitmap( StgPtr p, StgLargeBitmap *large_bitmap, W_ size ) +thread_large_bitmap( StgPtr p, StgLargeBitmap *large_bitmap, StgWord size ) { W_ i, b; StgWord bitmap; @@ -252,7 +252,7 @@ thread_arg_block (StgFunInfoTable *fun_info, StgClosure **args) { StgPtr p; StgWord bitmap; - W_ size; + StgWord size; p = (StgPtr)args; switch (fun_info->f.fun_type) { @@ -287,7 +287,7 @@ thread_stack(StgPtr p, StgPtr stack_end) { const StgRetInfoTable* info; StgWord bitmap; - W_ size; + StgWord size; // highly similar to scavenge_stack, but we do pointer threading here. @@ -327,7 +327,6 @@ thread_stack(StgPtr p, StgPtr stack_end) case RET_BCO: { StgBCO *bco; - nat size; p++; bco = (StgBCO *)*p; @@ -773,7 +772,7 @@ update_fwd_compact( bdescr *blocks ) #endif bdescr *bd, *free_bd; StgInfoTable *info; - nat size; + StgWord size; StgWord iptr; bd = blocks; @@ -858,7 +857,8 @@ update_bkwd_compact( generation *gen ) #endif bdescr *bd, *free_bd; StgInfoTable *info; - W_ size, free_blocks; + StgWord size; + W_ free_blocks; StgWord iptr; bd = free_bd = gen->old_blocks; diff --git a/rts/sm/Scav.c b/rts/sm/Scav.c index c35444b..5cf4cfa 100644 --- a/rts/sm/Scav.c +++ b/rts/sm/Scav.c @@ -32,7 +32,7 @@ static void scavenge_stack (StgPtr p, StgPtr stack_end); static void scavenge_large_bitmap (StgPtr p, StgLargeBitmap *large_bitmap, - nat size ); + StgWord size ); #if defined(THREADED_RTS) && !defined(PARALLEL_GC) # define evacuate(a) evacuate1(a) @@ -178,7 +178,7 @@ scavenge_arg_block (StgFunInfoTable *fun_info, StgClosure **args) { StgPtr p; StgWord bitmap; - nat size; + StgWord size; p = (StgPtr)args; switch (fun_info->f.fun_type) { @@ -1498,7 +1498,7 @@ scavenge_one(StgPtr p) { StgPtr start = gen->scan; bdescr *start_bd = gen->scan_bd; - nat size = 0; + StgWord size = 0; scavenge(&gen); if (start_bd != gen->scan_bd) { size += (P_)BLOCK_ROUND_UP(start) - start; @@ -1745,7 +1745,7 @@ scavenge_static(void) -------------------------------------------------------------------------- */ static void -scavenge_large_bitmap( StgPtr p, StgLargeBitmap *large_bitmap, nat size ) +scavenge_large_bitmap( StgPtr p, StgLargeBitmap *large_bitmap, StgWord size ) { nat i, j, b; StgWord bitmap; @@ -1766,7 +1766,7 @@ scavenge_large_bitmap( StgPtr p, StgLargeBitmap *large_bitmap, nat size ) } STATIC_INLINE StgPtr -scavenge_small_bitmap (StgPtr p, nat size, StgWord bitmap) +scavenge_small_bitmap (StgPtr p, StgWord size, StgWord bitmap) { while (size > 0) { if ((bitmap & 1) == 0) { @@ -1790,7 +1790,7 @@ scavenge_stack(StgPtr p, StgPtr stack_end) { const StgRetInfoTable* info; StgWord bitmap; - nat size; + StgWord size; /* * Each time around this loop, we are looking at a chunk of stack @@ -1874,7 +1874,7 @@ scavenge_stack(StgPtr p, StgPtr stack_end) case RET_BCO: { StgBCO *bco; - nat size; + StgWord size; p++; evacuate((StgClosure **)p); @@ -1889,7 +1889,7 @@ scavenge_stack(StgPtr p, StgPtr stack_end) // large bitmap (> 32 entries, or > 64 on a 64-bit machine) case RET_BIG: { - nat size; + StgWord size; size = GET_LARGE_BITMAP(&info->i)->size; p++; From git at git.haskell.org Tue Apr 29 19:35:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 19:35:20 +0000 (UTC) Subject: [commit: ghc] master: Rts: Reuse scavenge_small_bitmap (#8742) (05fcc33) Message-ID: <20140429193522.6BFA22406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/05fcc3331622995015ccba17ae333b9a0fc9bb77/ghc >--------------------------------------------------------------- commit 05fcc3331622995015ccba17ae333b9a0fc9bb77 Author: Arash Rouhani Date: Thu Feb 6 09:10:03 2014 +0100 Rts: Reuse scavenge_small_bitmap (#8742) The function was inlined at two places already. And the function is having the STATIC_INLINE annotation, so the assembly output should. be the same. To convince myself, I did diff the output of the object files before and after the patch and they matched on my 64-bit Ubuntu 13.10 machine, running gcc 4.8.1-10ubuntu9. Also, I had to move scavenge_small_bitmap up a bit since it's not in any .h-file. While I was at it, I also applied the analogous patch for Compact.c. Though I had to write `thread_small_bitmap` instead of just moving it. >--------------------------------------------------------------- 05fcc3331622995015ccba17ae333b9a0fc9bb77 rts/sm/Compact.c | 41 +++++++++++++++++------------------------ rts/sm/Scav.c | 45 ++++++++++++++++----------------------------- 2 files changed, 33 insertions(+), 53 deletions(-) diff --git a/rts/sm/Compact.c b/rts/sm/Compact.c index 3731dd6..b07a886 100644 --- a/rts/sm/Compact.c +++ b/rts/sm/Compact.c @@ -248,6 +248,20 @@ thread_large_bitmap( StgPtr p, StgLargeBitmap *large_bitmap, StgWord size ) } STATIC_INLINE StgPtr +thread_small_bitmap (StgPtr p, StgWord size, StgWord bitmap) +{ + while (size > 0) { + if ((bitmap & 1) == 0) { + thread((StgClosure **)p); + } + p++; + bitmap = bitmap >> 1; + size--; + } + return p; +} + +STATIC_INLINE StgPtr thread_arg_block (StgFunInfoTable *fun_info, StgClosure **args) { StgPtr p; @@ -269,14 +283,7 @@ thread_arg_block (StgFunInfoTable *fun_info, StgClosure **args) bitmap = BITMAP_BITS(stg_arg_bitmaps[fun_info->f.fun_type]); size = BITMAP_SIZE(stg_arg_bitmaps[fun_info->f.fun_type]); small_bitmap: - while (size > 0) { - if ((bitmap & 1) == 0) { - thread((StgClosure **)p); - } - p++; - bitmap = bitmap >> 1; - size--; - } + p = thread_small_bitmap(p, size, bitmap); break; } return p; @@ -315,14 +322,7 @@ thread_stack(StgPtr p, StgPtr stack_end) p++; // NOTE: the payload starts immediately after the info-ptr, we // don't have an StgHeader in the same sense as a heap closure. - while (size > 0) { - if ((bitmap & 1) == 0) { - thread((StgClosure **)p); - } - p++; - bitmap = bitmap >> 1; - size--; - } + p = thread_small_bitmap(p, size, bitmap); continue; case RET_BCO: { @@ -394,14 +394,7 @@ thread_PAP_payload (StgClosure *fun, StgClosure **payload, StgWord size) default: bitmap = BITMAP_BITS(stg_arg_bitmaps[fun_info->f.fun_type]); small_bitmap: - while (size > 0) { - if ((bitmap & 1) == 0) { - thread((StgClosure **)p); - } - p++; - bitmap = bitmap >> 1; - size--; - } + p = thread_small_bitmap(p, size, bitmap); break; } diff --git a/rts/sm/Scav.c b/rts/sm/Scav.c index 5cf4cfa..b9f8f12 100644 --- a/rts/sm/Scav.c +++ b/rts/sm/Scav.c @@ -168,6 +168,20 @@ static StgPtr scavenge_mut_arr_ptrs_marked (StgMutArrPtrs *a) return (StgPtr)a + mut_arr_ptrs_sizeW(a); } +STATIC_INLINE StgPtr +scavenge_small_bitmap (StgPtr p, StgWord size, StgWord bitmap) +{ + while (size > 0) { + if ((bitmap & 1) == 0) { + evacuate((StgClosure **)p); + } + p++; + bitmap = bitmap >> 1; + size--; + } + return p; +} + /* ----------------------------------------------------------------------------- Blocks of function args occur on the stack (at the top) and in PAPs. @@ -195,14 +209,7 @@ scavenge_arg_block (StgFunInfoTable *fun_info, StgClosure **args) bitmap = BITMAP_BITS(stg_arg_bitmaps[fun_info->f.fun_type]); size = BITMAP_SIZE(stg_arg_bitmaps[fun_info->f.fun_type]); small_bitmap: - while (size > 0) { - if ((bitmap & 1) == 0) { - evacuate((StgClosure **)p); - } - p++; - bitmap = bitmap >> 1; - size--; - } + p = scavenge_small_bitmap(p, size, bitmap); break; } return p; @@ -234,14 +241,7 @@ scavenge_PAP_payload (StgClosure *fun, StgClosure **payload, StgWord size) default: bitmap = BITMAP_BITS(stg_arg_bitmaps[fun_info->f.fun_type]); small_bitmap: - while (size > 0) { - if ((bitmap & 1) == 0) { - evacuate((StgClosure **)p); - } - p++; - bitmap = bitmap >> 1; - size--; - } + p = scavenge_small_bitmap(p, size, bitmap); break; } return p; @@ -1765,19 +1765,6 @@ scavenge_large_bitmap( StgPtr p, StgLargeBitmap *large_bitmap, StgWord size ) } } -STATIC_INLINE StgPtr -scavenge_small_bitmap (StgPtr p, StgWord size, StgWord bitmap) -{ - while (size > 0) { - if ((bitmap & 1) == 0) { - evacuate((StgClosure **)p); - } - p++; - bitmap = bitmap >> 1; - size--; - } - return p; -} /* ----------------------------------------------------------------------------- scavenge_stack walks over a section of stack and evacuates all the From git at git.haskell.org Tue Apr 29 19:35:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 19:35:23 +0000 (UTC) Subject: [commit: ghc] master: Don't inline non-register GlobalRegs (83a003f) Message-ID: <20140429193523.492DC2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/83a003fcaec93dbfd5b46837f2bf3353412b9877/ghc >--------------------------------------------------------------- commit 83a003fcaec93dbfd5b46837f2bf3353412b9877 Author: Simon Marlow Date: Tue Apr 29 20:32:50 2014 +0100 Don't inline non-register GlobalRegs >--------------------------------------------------------------- 83a003fcaec93dbfd5b46837f2bf3353412b9877 compiler/cmm/CmmSink.hs | 112 ++++++++++++++++++++++++++++++++++++++++++----- 1 file changed, 100 insertions(+), 12 deletions(-) diff --git a/compiler/cmm/CmmSink.hs b/compiler/cmm/CmmSink.hs index 187f4c4..4c02542 100644 --- a/compiler/cmm/CmmSink.hs +++ b/compiler/cmm/CmmSink.hs @@ -9,6 +9,7 @@ import BlockId import CmmLive import CmmUtils import Hoopl +import CodeGen.Platform import DynFlags import UniqFM @@ -16,6 +17,7 @@ import PprCmm () import Data.List (partition) import qualified Data.Set as Set +import Data.Maybe -- ----------------------------------------------------------------------------- -- Sinking and inlining @@ -197,7 +199,7 @@ cmmSink dflags graph = ofBlockList (g_entry graph) $ sink mapEmpty $ blocks drop_if a@(r,rhs,_) live_sets = (should_drop, live_sets') where should_drop = conflicts dflags a final_last - || not (isTrivial rhs) && live_in_multi live_sets r + || not (isTrivial dflags rhs) && live_in_multi live_sets r || r `Set.member` live_in_joins live_sets' | should_drop = live_sets @@ -219,26 +221,24 @@ cmmSink dflags graph = ofBlockList (g_entry graph) $ sink mapEmpty $ blocks -- small: an expression we don't mind duplicating isSmall :: CmmExpr -> Bool -isSmall (CmmReg (CmmLocal _)) = True -- not globals, we want to coalesce them instead* See below +isSmall (CmmReg (CmmLocal _)) = True -- isSmall (CmmLit _) = True isSmall (CmmMachOp (MO_Add _) [x,y]) = isTrivial x && isTrivial y isSmall (CmmRegOff (CmmLocal _) _) = True isSmall _ = False - -Coalesce global registers? What does that mean? We observed no decrease -in performance comming from inlining of global registers, hence we do it now -(see isTrivial function). Ideally we'd like to measure performance using -some tool like perf or VTune and make decisions what to inline based on that. -} -- -- We allow duplication of trivial expressions: registers (both local and -- global) and literals. -- -isTrivial :: CmmExpr -> Bool -isTrivial (CmmReg _) = True -isTrivial (CmmLit _) = True -isTrivial _ = False +isTrivial :: DynFlags -> CmmExpr -> Bool +isTrivial _ (CmmReg (CmmLocal _)) = True +isTrivial dflags (CmmReg (CmmGlobal r)) = -- see Note [Inline GlobalRegs?] + isJust (globalRegMaybe (targetPlatform dflags) r) + -- GlobalRegs that are loads from BaseReg are not trivial +isTrivial _ (CmmLit _) = True +isTrivial _ _ = False -- -- annotate each node with the set of registers live *after* the node @@ -401,7 +401,7 @@ tryToInline dflags live node assigs = go usages node [] assigs | cannot_inline = dont_inline | occurs_none = discard -- Note [discard during inlining] | occurs_once = inline_and_discard - | isTrivial rhs = inline_and_keep + | isTrivial dflags rhs = inline_and_keep | otherwise = dont_inline where inline_and_discard = go usages' inl_node skipped rest @@ -695,3 +695,91 @@ regAddr _ (CmmGlobal Hp) _ _ = HeapMem regAddr _ (CmmGlobal CurrentTSO) _ _ = HeapMem -- important for PrimOps regAddr dflags r _ _ | isGcPtrType (cmmRegType dflags r) = HeapMem -- yay! GCPtr pays for itself regAddr _ _ _ _ = AnyMem + +{- +Note [Inline GlobalRegs?] + +Should we freely inline GlobalRegs? + +Actually it doesn't make a huge amount of difference either way, so we +*do* currently treat GlobalRegs as "trivial" and inline them +everywhere, but for what it's worth, here is what I discovered when I +(SimonM) looked into this: + +Common sense says we should not inline GlobalRegs, because when we +have + + x = R1 + +the register allocator will coalesce this assignment, generating no +code, and simply record the fact that x is bound to $rbx (or +whatever). Furthermore, if we were to sink this assignment, then the +range of code over which R1 is live increases, and the range of code +over which x is live decreases. All things being equal, it is better +for x to be live than R1, because R1 is a fixed register whereas x can +live in any register. So we should neither sink nor inline 'x = R1'. + +However, not inlining GlobalRegs can have surprising +consequences. e.g. (cgrun020) + + c3EN: + _s3DB::P64 = R1; + _c3ES::P64 = _s3DB::P64 & 7; + if (_c3ES::P64 >= 2) goto c3EU; else goto c3EV; + c3EU: + _s3DD::P64 = P64[_s3DB::P64 + 6]; + _s3DE::P64 = P64[_s3DB::P64 + 14]; + I64[Sp - 8] = c3F0; + R1 = _s3DE::P64; + P64[Sp] = _s3DD::P64; + +inlining the GlobalReg gives: + + c3EN: + if (R1 & 7 >= 2) goto c3EU; else goto c3EV; + c3EU: + I64[Sp - 8] = c3F0; + _s3DD::P64 = P64[R1 + 6]; + R1 = P64[R1 + 14]; + P64[Sp] = _s3DD::P64; + +but if we don't inline the GlobalReg, instead we get: + + _s3DB::P64 = R1; + if (_s3DB::P64 & 7 >= 2) goto c3EU; else goto c3EV; + c3EU: + I64[Sp - 8] = c3F0; + R1 = P64[_s3DB::P64 + 14]; + P64[Sp] = P64[_s3DB::P64 + 6]; + +This looks better - we managed to inline _s3DD - but in fact it +generates an extra reg-reg move: + +.Lc3EU: + movq $c3F0_info,-8(%rbp) + movq %rbx,%rax + movq 14(%rbx),%rbx + movq 6(%rax),%rax + movq %rax,(%rbp) + +because _s3DB is now live across the R1 assignment, we lost the +benefit of coalescing. + +Who is at fault here? Perhaps if we knew that _s3DB was an alias for +R1, then we would not sink a reference to _s3DB past the R1 +assignment. Or perhaps we *should* do that - we might gain by sinking +it, despite losing the coalescing opportunity. + +Sometimes not inlining global registers wins by virtue of the rule +about not inlining into arguments of a foreign call, e.g. (T7163) this +is what happens when we inlined F1: + + _s3L2::F32 = F1; + _c3O3::F32 = %MO_F_Mul_W32(F1, 10.0 :: W32); + (_s3L7::F32) = call "ccall" arg hints: [] result hints: [] rintFloat(_c3O3::F32); + +but if we don't inline F1: + + (_s3L7::F32) = call "ccall" arg hints: [] result hints: [] rintFloat(%MO_F_Mul_W32(_s3L2::F32, + 10.0 :: W32)); +-} From git at git.haskell.org Tue Apr 29 21:10:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 21:10:14 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Allow a longer demand signature than arity (427dd3b) Message-ID: <20140429211015.6E3B22406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/427dd3bb748f241c555b331e99213b9f31be8d2a/ghc >--------------------------------------------------------------- commit 427dd3bb748f241c555b331e99213b9f31be8d2a Author: Simon Peyton Jones Date: Tue Apr 8 16:20:11 2014 +0100 Allow a longer demand signature than arity See Note [Demand analysis for trivial right-hand sides] in DmdAnal. This allows a function with arity 2 to have a DmdSig with 3 args; which in turn had a knock-on effect, which showed up in the test for Trac #8963. In fact it seems entirely reasonable, so this patch removes the WARN and CoreLint checks that were complaining. (cherry picked from commit 848f595266268f578480ceb4ab1ce4938611c97e) >--------------------------------------------------------------- 427dd3bb748f241c555b331e99213b9f31be8d2a compiler/coreSyn/CoreLint.lhs | 15 +++++++++------ compiler/simplCore/SimplUtils.lhs | 5 ++--- compiler/stranal/DmdAnal.lhs | 18 +++++++++++++----- 3 files changed, 24 insertions(+), 14 deletions(-) diff --git a/compiler/coreSyn/CoreLint.lhs b/compiler/coreSyn/CoreLint.lhs index 836164e..b5c7985 100644 --- a/compiler/coreSyn/CoreLint.lhs +++ b/compiler/coreSyn/CoreLint.lhs @@ -19,7 +19,6 @@ module CoreLint ( lintCoreBindings, lintUnfolding, lintExpr ) where #include "HsVersions.h" -import Demand import CoreSyn import CoreFVs import CoreUtils @@ -239,9 +238,13 @@ lintSingleBinding top_lvl_flag rec_flag (binder,rhs) -- Check whether arity and demand type are consistent (only if demand analysis -- already happened) - ; checkL (case dmdTy of - StrictSig dmd_ty -> idArity binder >= dmdTypeDepth dmd_ty || exprIsTrivial rhs) - (mkArityMsg binder) + -- + -- Note (Apr 2014): this is actually ok. See Note [Demand analysis for trivial right-hand sides] + -- in DmdAnal. After eta-expansion in CorePrep the rhs is no longer trivial. + -- ; let dmdTy = idStrictness binder + -- ; checkL (case dmdTy of + -- StrictSig dmd_ty -> idArity binder >= dmdTypeDepth dmd_ty || exprIsTrivial rhs) + -- (mkArityMsg binder) ; lintIdUnfolding binder binder_ty (idUnfolding binder) } @@ -249,7 +252,6 @@ lintSingleBinding top_lvl_flag rec_flag (binder,rhs) -- the unfolding is a SimplifiableCoreExpr. Give up for now. where binder_ty = idType binder - dmdTy = idStrictness binder bndr_vars = varSetElems (idFreeVars binder) -- If you edit this function, you may need to update the GHC formalism @@ -1421,6 +1423,7 @@ mkKindErrMsg tyvar arg_ty hang (ptext (sLit "Arg type:")) 4 (ppr arg_ty <+> dcolon <+> ppr (typeKind arg_ty))] +{- Not needed now mkArityMsg :: Id -> MsgDoc mkArityMsg binder = vcat [hsep [ptext (sLit "Demand type has"), @@ -1433,7 +1436,7 @@ mkArityMsg binder ] where (StrictSig dmd_ty) = idStrictness binder - +-} mkCastErr :: CoreExpr -> Coercion -> Type -> Type -> MsgDoc mkCastErr expr co from_ty expr_ty = vcat [ptext (sLit "From-type of Cast differs from type of enclosed expression"), diff --git a/compiler/simplCore/SimplUtils.lhs b/compiler/simplCore/SimplUtils.lhs index 6c7dcc2..655c976 100644 --- a/compiler/simplCore/SimplUtils.lhs +++ b/compiler/simplCore/SimplUtils.lhs @@ -1195,9 +1195,9 @@ tryEtaExpandRhs env bndr rhs = do { dflags <- getDynFlags ; (new_arity, new_rhs) <- try_expand dflags - ; WARN( new_arity < old_arity || new_arity < _dmd_arity, + ; WARN( new_arity < old_arity, (ptext (sLit "Arity decrease:") <+> (ppr bndr <+> ppr old_arity - <+> ppr new_arity <+> ppr _dmd_arity) $$ ppr new_rhs) ) + <+> ppr new_arity) $$ ppr new_rhs) ) -- Note [Arity decrease] return (new_arity, new_rhs) } where @@ -1215,7 +1215,6 @@ tryEtaExpandRhs env bndr rhs manifest_arity = manifestArity rhs old_arity = idArity bndr - _dmd_arity = length $ fst $ splitStrictSig $ idStrictness bndr \end{code} Note [Eta-expanding at let bindings] diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index e9a7ab4..1d27a53 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -595,7 +595,7 @@ dmdAnalRhs :: TopLevelFlag -- Process the RHS of the binding, add the strictness signature -- to the Id, and augment the environment with the signature as well. dmdAnalRhs top_lvl rec_flag env id rhs - | Just fn <- unpackTrivial rhs -- See Note [Trivial right-hand sides] + | Just fn <- unpackTrivial rhs -- See Note [Demand analysis for trivial right-hand sides] , let fn_str = getStrictness env fn = (fn_str, emptyDmdEnv, set_idStrictness env id fn_str, rhs) @@ -640,7 +640,7 @@ dmdAnalRhs top_lvl rec_flag env id rhs unpackTrivial :: CoreExpr -> Maybe Id -- Returns (Just v) if the arg is really equal to v, modulo -- casts, type applications etc --- See Note [Trivial right-hand sides] +-- See Note [Demand analysis for trivial right-hand sides] unpackTrivial (Var v) = Just v unpackTrivial (Cast e _) = unpackTrivial e unpackTrivial (Lam v e) | isTyVar v = unpackTrivial e @@ -648,16 +648,24 @@ unpackTrivial (App e a) | isTypeArg a = unpackTrivial e unpackTrivial _ = Nothing \end{code} -Note [Trivial right-hand sides] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Note [Demand analysis for trivial right-hand sides] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider foo = plusInt |> co where plusInt is an arity-2 function with known strictness. Clearly we want plusInt's strictness to propagate to foo! But because it has -no manifest lambdas, it won't do so automatically. So we have a +no manifest lambdas, it won't do so automatically, and indeed 'co' might +have type (Int->Int->Int) ~ T, so we *can't* eta-expand. So we have a special case for right-hand sides that are "trivial", namely variables, casts, type applications, and the like. +Note that this can mean that 'foo' has an arity that is smaller than that +indicated by its demand info. e.g. if co :: (Int->Int->Int) ~ T, then +foo's arity will be zero (see Note [exprArity invariant] in CoreArity), +but its demand signature will be that of plusInt. A small example is the +test case of Trac #8963. + + Note [Product demands for function body] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ This example comes from shootout/binary_trees: From git at git.haskell.org Tue Apr 29 21:10:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 21:10:17 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Test Trac #8963 (3fb1a08) Message-ID: <20140429211017.BEA9A2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/3fb1a0887d18cdddd6ff1691e80f3143fd0eedba/ghc >--------------------------------------------------------------- commit 3fb1a0887d18cdddd6ff1691e80f3143fd0eedba Author: Simon Peyton Jones Date: Tue Apr 8 16:28:56 2014 +0100 Test Trac #8963 (cherry picked from commit cc3ccf9f47c7f4684cdd2b08d0e2acf50b69bc18) Conflicts: testsuite/tests/deriving/should_compile/all.T >--------------------------------------------------------------- 3fb1a0887d18cdddd6ff1691e80f3143fd0eedba testsuite/tests/deriving/should_compile/T8963.hs | 9 +++++++++ testsuite/tests/deriving/should_compile/all.T | 1 + 2 files changed, 10 insertions(+) diff --git a/testsuite/tests/deriving/should_compile/T8963.hs b/testsuite/tests/deriving/should_compile/T8963.hs new file mode 100644 index 0000000..78dcf46 --- /dev/null +++ b/testsuite/tests/deriving/should_compile/T8963.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE TypeFamilies, GeneralizedNewtypeDeriving #-} + +module T8963 where + +class C c where + data F c r + +instance C Int where + newtype F Int r = F (IO r) deriving (Functor) diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T index b649ff6..f8ab42e 100644 --- a/testsuite/tests/deriving/should_compile/all.T +++ b/testsuite/tests/deriving/should_compile/all.T @@ -46,3 +46,4 @@ test('T8631', normal, compile, ['']) test('T8758', extra_clean(['T8758a.o', 'T8758a.hi']), multimod_compile, ['T8758a', '-v0']) test('T8865', normal, compile, ['']) test('T8893', normal, compile, ['']) +test('T8963', normal, compile, ['']) From git at git.haskell.org Tue Apr 29 21:10:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 21:10:20 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Fix annotation reification for home package modules (eddbbd1) Message-ID: <20140429211020.E08292406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/eddbbd1a0ab819aca339237ae97e6dc5d54d4817/ghc >--------------------------------------------------------------- commit eddbbd1a0ab819aca339237ae97e6dc5d54d4817 Author: Gergely Risko Date: Fri Apr 25 15:35:58 2014 +0200 Fix annotation reification for home package modules The reifyAnnotation method of the Q monad correctly gathered annotations from TCG and EPS. Unfortunately it didn't look into the Home Package Table. This resulted in annotations not being found if they are in the same package as the splice that is reifying and ghc --make is used for compilation management. Fix this by using the already existing prepareAnnotations method from HscTypes.lhs that correctly searches in HPT and EPS both. Signed-off-by: Austin Seipp (cherry picked from commit 48e475e45f517896c6618d38a09b8d223f3d7585) >--------------------------------------------------------------- eddbbd1a0ab819aca339237ae97e6dc5d54d4817 compiler/typecheck/TcSplice.lhs | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcSplice.lhs b/compiler/typecheck/TcSplice.lhs index 4dbf2d3..62e17d4 100644 --- a/compiler/typecheck/TcSplice.lhs +++ b/compiler/typecheck/TcSplice.lhs @@ -1508,13 +1508,14 @@ lookupThAnnLookup (TH.AnnLookupModule (TH.Module pn mn)) mkModule (stringToPackageId $ TH.pkgString pn) (mkModuleName $ TH.modString mn) reifyAnnotations :: Data a => TH.AnnLookup -> TcM [a] -reifyAnnotations th_nm - = do { name <- lookupThAnnLookup th_nm - ; eps <- getEps +reifyAnnotations th_name + = do { name <- lookupThAnnLookup th_name + ; topEnv <- getTopEnv + ; epsHptAnns <- liftIO $ prepareAnnotations topEnv Nothing ; tcg <- getGblEnv - ; let epsAnns = findAnns deserializeWithData (eps_ann_env eps) name - ; let envAnns = findAnns deserializeWithData (tcg_ann_env tcg) name - ; return (envAnns ++ epsAnns) } + ; let selectedEpsHptAnns = findAnns deserializeWithData epsHptAnns name + ; let selectedTcgAnns = findAnns deserializeWithData (tcg_ann_env tcg) name + ; return (selectedEpsHptAnns ++ selectedTcgAnns) } ------------------------------ modToTHMod :: Module -> TH.Module From git at git.haskell.org Tue Apr 29 21:10:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 21:10:23 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Add a comprehensive test for using Annotations from TH (bd6eea9) Message-ID: <20140429211023.9F3AC2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/bd6eea9f405ad195bcc70d7738bc33c6170cdc94/ghc >--------------------------------------------------------------- commit bd6eea9f405ad195bcc70d7738bc33c6170cdc94 Author: Gergely Risko Date: Fri Apr 25 15:39:26 2014 +0200 Add a comprehensive test for using Annotations from TH The provided tests test both annotation generation and reification from Template Haskell. Both --make and compilation via separate units (ghc -c) are tested. Signed-off-by: Austin Seipp (cherry picked from commit 5f5e326c3c310c4bceb2b0bce291d3a0a3fc30d6) >--------------------------------------------------------------- bd6eea9f405ad195bcc70d7738bc33c6170cdc94 .../annotations/should_compile/th/AnnHelper.hs | 16 ++++++++++ .../tests/annotations/should_compile/th/Makefile | 33 ++++++++++++++++++++ .../annotations/should_compile/th/TestModule.hs | 11 +++++++ .../annotations/should_compile/th/TestModuleTH.hs | 18 +++++++++++ .../tests/annotations/should_compile/th/all.T | 18 +++++++++++ .../tests/annotations/should_compile/th/annth.hs | 26 +++++++++++++++ .../should_compile/th/annth_compunits.stdout | 7 +++++ .../should_compile/th/annth_make.stdout | 7 +++++ 8 files changed, 136 insertions(+) diff --git a/testsuite/tests/annotations/should_compile/th/AnnHelper.hs b/testsuite/tests/annotations/should_compile/th/AnnHelper.hs new file mode 100644 index 0000000..ac0f040 --- /dev/null +++ b/testsuite/tests/annotations/should_compile/th/AnnHelper.hs @@ -0,0 +1,16 @@ +module AnnHelper where + +import Language.Haskell.TH +import Language.Haskell.TH.Syntax + +traverseModuleAnnotations :: Q [String] +traverseModuleAnnotations = do + ModuleInfo children <- reifyModule =<< thisModule + go children [] [] + where + go [] _visited acc = return acc + go (x:xs) visited acc | x `elem` visited = go xs visited acc + | otherwise = do + ModuleInfo newMods <- reifyModule x + newAnns <- reifyAnnotations $ AnnLookupModule x + go (newMods ++ xs) (x:visited) (newAnns ++ acc) diff --git a/testsuite/tests/annotations/should_compile/th/Makefile b/testsuite/tests/annotations/should_compile/th/Makefile new file mode 100644 index 0000000..4159eee --- /dev/null +++ b/testsuite/tests/annotations/should_compile/th/Makefile @@ -0,0 +1,33 @@ +TOP=../../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +annth_make: + $(MAKE) clean_annth_make + mkdir build_make + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 --make \ + -odir build_make -hidir build_make -o build_make/annth annth.hs + +clean_annth_make: + rm -rf build_make + +annth_compunits: + $(MAKE) clean_annth_compunits + mkdir build_compunits + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -dynamic-too \ + -odir build_compunits -hidir build_compunits \ + -c AnnHelper.hs + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -dynamic-too \ + -odir build_compunits -hidir build_compunits \ + -c TestModule.hs + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -dynamic-too \ + -odir build_compunits -hidir build_compunits \ + -c TestModuleTH.hs + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -ibuild_compunits \ + -odir build_compunits -hidir build_compunits \ + -c annth.hs + +clean_annth_compunits: + rm -rf build_compunits + +.PHONY: annth_make clean_annth_make annth_compunits clean_annth_compunits diff --git a/testsuite/tests/annotations/should_compile/th/TestModule.hs b/testsuite/tests/annotations/should_compile/th/TestModule.hs new file mode 100644 index 0000000..d9519eb --- /dev/null +++ b/testsuite/tests/annotations/should_compile/th/TestModule.hs @@ -0,0 +1,11 @@ +module TestModule where + +{-# ANN module "Module annotation" #-} + +{-# ANN type TestType "Type annotation" #-} +{-# ANN TestType "Constructor annotation" #-} +data TestType = TestType + +{-# ANN testValue "Value annotation" #-} +testValue :: Int +testValue = 42 diff --git a/testsuite/tests/annotations/should_compile/th/TestModuleTH.hs b/testsuite/tests/annotations/should_compile/th/TestModuleTH.hs new file mode 100644 index 0000000..f21b137 --- /dev/null +++ b/testsuite/tests/annotations/should_compile/th/TestModuleTH.hs @@ -0,0 +1,18 @@ +{-# LANGUAGE TemplateHaskell #-} + +module TestModuleTH where + +import Language.Haskell.TH + +$(do + modAnn <- pragAnnD ModuleAnnotation + (stringE "TH module annotation") + [typ] <- [d| data TestTypeTH = TestTypeTH |] + conAnn <- pragAnnD (ValueAnnotation $ mkName "TestTypeTH") + (stringE "TH Constructor annotation") + typAnn <- pragAnnD (TypeAnnotation $ mkName "TestTypeTH") + (stringE "TH Type annotation") + valAnn <- pragAnnD (ValueAnnotation $ mkName "testValueTH") + (stringE "TH Value annotation") + [val] <- [d| testValueTH = (42 :: Int) |] + return [modAnn, conAnn, typAnn, typ, valAnn, val] ) diff --git a/testsuite/tests/annotations/should_compile/th/all.T b/testsuite/tests/annotations/should_compile/th/all.T new file mode 100644 index 0000000..777cf3d --- /dev/null +++ b/testsuite/tests/annotations/should_compile/th/all.T @@ -0,0 +1,18 @@ +setTestOpts(when(compiler_profiled(), skip)) + +# Annotations and Template Haskell, require runtime evaluation. In +# order for this to work with profiling, we would have to build the +# program twice and use -osuf p_o (see the TH_splitE5_prof test). For +# now, just disable the profiling ways. + +test('annth_make', + [req_interp, omit_ways(['profasm','profthreaded']), + clean_cmd('$MAKE -s clean_annth_make')], + run_command, + ['$MAKE -s --no-print-directory annth_make']) + +test('annth_compunits', + [req_interp, omit_ways(['profasm','profthreaded']), + clean_cmd('$MAKE -s clean_annth_compunits')], + run_command, + ['$MAKE -s --no-print-directory annth_compunits']) diff --git a/testsuite/tests/annotations/should_compile/th/annth.hs b/testsuite/tests/annotations/should_compile/th/annth.hs new file mode 100644 index 0000000..de5d4d3 --- /dev/null +++ b/testsuite/tests/annotations/should_compile/th/annth.hs @@ -0,0 +1,26 @@ +{-# LANGUAGE TemplateHaskell #-} + +import Language.Haskell.TH +import Language.Haskell.TH.Syntax + +import AnnHelper +import TestModule +import TestModuleTH + +main = do + $(do + anns <- traverseModuleAnnotations + runIO $ print (anns :: [String]) + anns <- reifyAnnotations (AnnLookupName 'testValue) + runIO $ print (anns :: [String]) + anns <- reifyAnnotations (AnnLookupName 'testValueTH) + runIO $ print (anns :: [String]) + anns <- reifyAnnotations (AnnLookupName ''TestType) + runIO $ print (anns :: [String]) + anns <- reifyAnnotations (AnnLookupName ''TestTypeTH) + runIO $ print (anns :: [String]) + anns <- reifyAnnotations (AnnLookupName 'TestType) + runIO $ print (anns :: [String]) + anns <- reifyAnnotations (AnnLookupName 'TestTypeTH) + runIO $ print (anns :: [String]) + [| return () |] ) diff --git a/testsuite/tests/annotations/should_compile/th/annth_compunits.stdout b/testsuite/tests/annotations/should_compile/th/annth_compunits.stdout new file mode 100644 index 0000000..96e4642 --- /dev/null +++ b/testsuite/tests/annotations/should_compile/th/annth_compunits.stdout @@ -0,0 +1,7 @@ +["TH module annotation","Module annotation"] +["Value annotation"] +["TH Value annotation"] +["Type annotation"] +["TH Type annotation"] +["Constructor annotation"] +["TH Constructor annotation"] diff --git a/testsuite/tests/annotations/should_compile/th/annth_make.stdout b/testsuite/tests/annotations/should_compile/th/annth_make.stdout new file mode 100644 index 0000000..96e4642 --- /dev/null +++ b/testsuite/tests/annotations/should_compile/th/annth_make.stdout @@ -0,0 +1,7 @@ +["TH module annotation","Module annotation"] +["Value annotation"] +["TH Value annotation"] +["Type annotation"] +["TH Type annotation"] +["Constructor annotation"] +["TH Constructor annotation"] From git at git.haskell.org Tue Apr 29 21:10:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 21:10:26 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: rts: Fix leak of file archive handle (652789e) Message-ID: <20140429211026.3571D2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/652789e77d84f95120360211281f3771ae3e8e17/ghc >--------------------------------------------------------------- commit 652789e77d84f95120360211281f3771ae3e8e17 Author: Austin Seipp Date: Tue Apr 29 09:05:38 2014 -0500 rts: Fix leak of file archive handle Issue discovered by Coverity Scan, CID 43171. Signed-off-by: Austin Seipp (cherry picked from commit e597f5feb065c075c86715e24bf0ebd341fa8b9e) >--------------------------------------------------------------- 652789e77d84f95120360211281f3771ae3e8e17 rts/Linker.c | 1 + 1 file changed, 1 insertion(+) diff --git a/rts/Linker.c b/rts/Linker.c index c577cce..75389d5 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -2618,6 +2618,7 @@ loadArchive( pathchar *path ) if (0 == loadOc(oc)) { stgFree(fileName); + fclose(f); return 0; } } From git at git.haskell.org Tue Apr 29 21:10:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 29 Apr 2014 21:10:28 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: rts: Fix memory leak when loading ELF objects (8404e80) Message-ID: <20140429211029.600DA2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/8404e800a35380281a218c78a6799ed6836b6fad/ghc >--------------------------------------------------------------- commit 8404e800a35380281a218c78a6799ed6836b6fad Author: Austin Seipp Date: Tue Apr 29 09:09:25 2014 -0500 rts: Fix memory leak when loading ELF objects Issue discovered by Coverity Scan, CID 43168. Signed-off-by: Austin Seipp (cherry picked from commit b7278d3d7bbe384eee7538b1e50bb741e99fb01d) >--------------------------------------------------------------- 8404e800a35380281a218c78a6799ed6836b6fad rts/Linker.c | 1 + 1 file changed, 1 insertion(+) diff --git a/rts/Linker.c b/rts/Linker.c index 75389d5..26c7bc9 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -1878,6 +1878,7 @@ addDLL( pathchar *dll_name ) // success -- try to dlopen the first named file IF_DEBUG(linker, debugBelch("match%s\n","")); line[match[2].rm_eo] = '\0'; + stgFree((void*)errmsg); // Free old message before creating new one errmsg = internal_dlopen(line+match[2].rm_so); break; } From git at git.haskell.org Wed Apr 30 09:23:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 30 Apr 2014 09:23:39 +0000 (UTC) Subject: [commit: ghc] master: Replace all #!/usr/bin/perl with #!/usr/bin/env perl (34db5cc) Message-ID: <20140430092339.8EB172406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/34db5ccf52ec2a1b5e953c282d0c52a7fc82c02a/ghc >--------------------------------------------------------------- commit 34db5ccf52ec2a1b5e953c282d0c52a7fc82c02a Author: Joachim Breitner Date: Wed Apr 30 11:22:32 2014 +0200 Replace all #!/usr/bin/perl with #!/usr/bin/env perl As suggested in #9057. >--------------------------------------------------------------- 34db5ccf52ec2a1b5e953c282d0c52a7fc82c02a boot | 3 ++- distrib/remilestoning.pl | 3 ++- sync-all | 3 ++- utils/genargs/genargs.pl | 5 ++++- 4 files changed, 10 insertions(+), 4 deletions(-) diff --git a/boot b/boot index 676f434..8977eaf 100755 --- a/boot +++ b/boot @@ -1,5 +1,6 @@ -#!/usr/bin/perl -w +#!/usr/bin/env perl +use warnings; use strict; use Cwd; diff --git a/distrib/remilestoning.pl b/distrib/remilestoning.pl index a544dda..60a23af 100644 --- a/distrib/remilestoning.pl +++ b/distrib/remilestoning.pl @@ -1,5 +1,6 @@ -#!/usr/bin/perl +#!/usr/bin/env perl +use warnings; use strict; use DBI; diff --git a/sync-all b/sync-all index e43a6f6..ffc150e 100755 --- a/sync-all +++ b/sync-all @@ -1,5 +1,6 @@ -#!/usr/bin/perl -w +#!/usr/bin/env perl +use warnings; use strict; use Cwd; use English; diff --git a/utils/genargs/genargs.pl b/utils/genargs/genargs.pl index 2ef2dfa..33dd2a0 100644 --- a/utils/genargs/genargs.pl +++ b/utils/genargs/genargs.pl @@ -1,4 +1,7 @@ -#!/usr/bin/perl +#!/usr/bin/env perl + +use warnings; + my $quote_open = 0; my $quote_char = ''; my $accum = ""; From git at git.haskell.org Wed Apr 30 14:44:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 30 Apr 2014 14:44:17 +0000 (UTC) Subject: [commit: ghc] branch 'wip/cpr-vs-jp' deleted Message-ID: <20140430144417.998012406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/cpr-vs-jp From git at git.haskell.org Wed Apr 30 18:06:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 30 Apr 2014 18:06:28 +0000 (UTC) Subject: [commit: ghc] branch 'wip/drop-containers-dep-from-th' deleted Message-ID: <20140430180628.B330E2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/drop-containers-dep-from-th From git at git.haskell.org Wed Apr 30 18:06:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 30 Apr 2014 18:06:57 +0000 (UTC) Subject: [commit: ghc] branch 'wip/Cabal-1.20' deleted Message-ID: <20140430180657.6968D2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/Cabal-1.20 From git at git.haskell.org Wed Apr 30 18:09:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 30 Apr 2014 18:09:31 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T9016' deleted Message-ID: <20140430180932.7D2992406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/T9016