- 02 May, 2016 5 commits
-
-
Facundo Domínguez authored
Summary: With this patch closed variables are allowed regardless of whether they are bound at the top level or not. The FloatOut pass is always performed. When optimizations are disabled, only expressions that go to the top level are floated. Thus, the applications of the StaticPtr data constructor are always floated. The CoreTidy pass makes sure the floated applications appear in the symbol table of object files. It also collects the floated bindings and inserts them in the static pointer table. The renamer does not check anymore if free variables appearing in the static form are top-level. Instead, the typechecker looks at the tct_closed flag to decide if the free variables are closed. The linter checks that applications of StaticPtr only occur at the top of top-level bindings after the FloatOut pass. The field spInfoName of StaticPtrInfo has been removed. It used to contain the name of the top-level binding that contains the StaticPtr application. However, this information is no longer available when the StaticPtr is constructed, as the binding name is determined now by the FloatOut pass. Test Plan: ./validate Reviewers: goldfire, simonpj, austin, hvr, bgamari Reviewed By: simonpj Subscribers: thomie, mpickering, mboes Differential Revision: https://phabricator.haskell.org/D2104 GHC Trac Issues: #11656
-
Ryan Scott authored
Summary: GHC choked when trying to derive the following: ``` {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE PolyKinds #-} module Example where class Category (cat :: k -> k -> *) where catId :: cat a a catComp :: cat b c -> cat a b -> cat a c newtype T (c :: * -> * -> *) a b = MkT (c a b) deriving Category ``` Unlike in #8865, where we were deriving `Category` for a concrete type like `Either`, in the above example we are attempting to derive an instance of the form: ``` instance Category * c => Category (T * c) where ... ``` (using `-fprint-explicit-kinds` syntax). But `validDerivPred` is checking if `sizePred (Category * c)` equals the number of free type variables in `Category * c`. But note that `sizePred` counts both type variables //and// type constructors, and `*` is a type constructor! So `validDerivPred` erroneously rejects the above instance. The fix is to make `validDerivPred` ignore non-visible arguments to the class type constructor (e.g., ignore `*` is `Category * c`) by using `filterOutInvisibleTypes`. Fixes #11833. Test Plan: ./validate Reviewers: goldfire, hvr, simonpj, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2112 GHC Trac Issues: #11833
-
Sergei Trofimovich authored
Signed-off-by:
Sergei Trofimovich <siarheit@google.com>
-
Sergei Trofimovich authored
glasgow_exts.rst:6525: WARNING: Inline literal start-string without end-string. Signed-off-by:
Sergei Trofimovich <siarheit@google.com>
-
Sergei Trofimovich authored
Signed-off-by:
Sergei Trofimovich <siarheit@google.com>
-
- 01 May, 2016 17 commits
-
-
Matthew Pickering authored
Beforehand, when a record pattern synonym was defined in GHCi the selectors would not be in scope. This is because of `is_sub_bndr` in `HscTypes.icExtendGblRdrEnv` was throwing away the selectors. This was broken by the fix to #10520 but it is easy to resolve. Reviewers: austin, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2147 GHC Trac Issues: #11985
-
niteria authored
It uses `eltsUFM` so it can introduce nondeterminism, but it isn't used so we can delete it. Test Plan: it builds Reviewers: simonpj, goldfire, simonmar, austin, bgamari Reviewed By: austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2161 GHC Trac Issues: #4012
-
Ryan Scott authored
This finishes what #5529 started by exporting the constructors for `IntPtr` and `WordPtr` from `Foreign.Ptr`, allowing them to be used in `foreign` declarations. Fixes #11983. Test Plan: `make TEST=T11983` Reviewers: simonpj, hvr, bgamari, austin Reviewed By: simonpj Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D2142 GHC Trac Issues: #11983
-
Ben Gamari authored
Missing a close paren.
-
Ömer Sinan Ağacan authored
Reviewers: bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2163 GHC Trac Issues: #11747
-
niteria authored
Test Plan: it compiles Reviewers: simonpj, austin, goldfire, bgamari, simonmar Reviewed By: simonmar Subscribers: thomie, simonmar Differential Revision: https://phabricator.haskell.org/D2160 GHC Trac Issues: #4012
-
Ben Gamari authored
This reworks the pthread-based itimer implementation to disarm the timer when events aren't needed. Thanks to hsyl20 for the nice design. Test Plan: Validate Reviewers: hsyl20, simonmar, austin Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2131 GHC Trac Issues: #1623, #11965
-
Ben Gamari authored
It declared nothing.
-
Ben Gamari authored
-
Ben Gamari authored
This shouldn't have any functional changes. It merely splits up what are essentially three distinct codepaths which are melding together with CPP. At the moment I merely #include the implementation to use with CPP although this really feels very yucky. Reviewers: erikd, austin, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2130
-
Ben Gamari authored
This fixes #11830, where the RTS would livelock if run with `-I0` due to a regression introduced by bbdc52f3. The reason for this is that the new codepath introduced a subtle race condition: 1. one thread could request that the ticker stop and would block until the ticker in fact stopped 2. meanwhile, another thread could sneak in and restart the ticker this was implemented in such a way where thread (1) would end up blocked forever. The solution here is to simply not block. The worst that will happen is that timer fires again, but is ignored since the ticker is stopped. Test Plan: Validate, try reproduction case in #11830. Need to find a nice testcase. Reviewers: simonmar, erikd, hsyl20, austin Reviewed By: erikd, hsyl20 Subscribers: erikd, thomie Differential Revision: https://phabricator.haskell.org/D2129 GHC Trac Issues: #11830
-
niksaz authored
This patch is trying to redesign the :set prompt option to take not a String but a Haskell function, like [String] -> Int -> IO String, where [String] is the list of the names of the currently loaded modules and Int is the line number. Currently you may set prompt function with **:set promt-function [String] -> Int -> IO String** option and old version is also available - :set prompt String. So, it looks like I've almost completed this patch: 1) Now we have a lot of escape sequences - 13 to be exact. Most of them are similar to bash prompt escape sequences. Thus they are quite handy. 2) We may use the special escape sequence to call shell functions, for example "%call(ls -l -a)". 3) We may use :set prompt-function to set PFunction to handle prompt. It is just [String] -> Int -> IO String. Reviewers: erikd, austin, mpickering, bgamari Reviewed By: mpickering, bgamari Subscribers: mpickering, thomie Differential Revision: https://phabricator.haskell.org/D2084 GHC Trac Issues: #5850
-
Ben Gamari authored
Fixes documentation installation.
-
Ben Gamari authored
-
Erik de Castro Lopo authored
Summary: The `lnat` type was deprecated in 2012 in commit 41737f12 with a note to use `StgWord` instead. Test Plan: Validate on Linux and OS X Reviewers: simonmar, austin, Phyx, hvr, bgamari Reviewed By: simonmar, Phyx, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2164
-
Tamar Christina authored
Summary: The aggressive cleanup routine of T1407 is removing files that don't belong to it. Constrain the test to only removing files it should by putting all it's generated binaries in it's own output folder. Test Plan: make test -C testsuite/tests/ghci/linking/dyn Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie, #ghc_windows_task_force Differential Revision: https://phabricator.haskell.org/D2165 GHC Trac Issues: #1407
-
Ömer Sinan Ağacan authored
-
- 30 Apr, 2016 5 commits
-
-
Ryan Scott authored
[ci skip]
-
Ryan Scott authored
[ci skip]
-
Ryan Scott authored
Previously, it was referring to Note [Decomposing equalities], but the name of it is actually Note [Decomposing equality]. [ci skip]
-
thomie authored
Test Plan: make TEST='ExtraNumAMROn TidyClash2' Differential Revision: https://phabricator.haskell.org/D2155 GHC Trac Issues: #9478
-
thomie authored
Also move the `cleanup` setting from `default_testopts` to `config`. The `cleanup` setting is the same for all tests, hence it belongs in `config`. Reviewed by: austin Differential Revision: https://phabricator.haskell.org/D2148
-
- 29 Apr, 2016 5 commits
-
-
Peter Trommler authored
Generate a clrr[wd]i instruction to clear the tag bits in a pointer. This saves one instruction and one temporary register. Optimize signed comparison with zero after andi. operation This saves one instruction when comparing a pointer tag with zero. This reduces code size by 0.6 % in all nofib benchmarks. Test Plan: validate on AIX and 32-bit Linux Reviewed By: erikd, hvr Differential Revision: https://phabricator.haskell.org/D2093
-
niteria authored
-
eir@cis.upenn.edu authored
-
eir@cis.upenn.edu authored
This patch removes splitTelescopeTvs by adding information about scoped type variables to TcTyCon. Vast simplification! This also fixes #11821 by bringing only unzonked vars into scope. Test case: polykinds/T11821
-
thomie authored
Some old stuff related to the PAR way. Reviewed by: austin, simonmar Differential Revision: https://phabricator.haskell.org/D2137
-
- 28 Apr, 2016 8 commits
-
-
Austin Seipp authored
As reported by Simon on ghc-devs, this causes the build on Windows to fail because it cannot find the `cc` command. The Makefile here actually already sets `GCC=gcc`, but for some reason then uses both `$(GCC)` and `$(CC)` to refer to C compilation. Signed-off-by:
Austin Seipp <austin@well-typed.com> Reviewed By: thomie Differential Revision: https://phabricator.haskell.org/D2158
-
Andrey Mokhov authored
Summary: The new Shake-based build system has been given a name -- Hadrian, and now lives in /hadrian directory. This fixes the path to the configuration file to be populated by the configure script. Test Plan: Run Hadrian build. Reviewers: thomie, bgamari, hvr, austin Reviewed By: austin Subscribers: erikd Differential Revision: https://phabricator.haskell.org/D2153
-
niteria authored
foldNameEnv is nondeterministic in the general case and it's currently unused so we can remove it.
-
niteria authored
foldFsEnv is nondeterministic in the general case and since it's unused we can just remove it.
-
Erik de Castro Lopo authored
Introduced in commit 177aec69. Test Plan: Validate on OSX and Linux. Reviewers: austin, bgamari, hvr Subscribers: goldfire, thomie Differential Revision: https://phabricator.haskell.org/D2140
-
Erik de Castro Lopo authored
Test Plan: validate Reviewers: carter, austin, simonmar, bgamari Reviewed By: simonmar, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2154 GHC Trac Issues: #11978
-
thomie authored
These tests no longer compile, because the hmatrix api has completely changed. Even if we managed to fix the tests, I don't think they would provided much value, since the ghc/llvm bug from #5054 was not reproducible in the first place. Reviewed by: bgamari Differential Revision: https://phabricator.haskell.org/D2139
-
thomie authored
The -fesc flag does not exist, and has never existed. Also delete now unused config.compiler_tags, and 'Project version' never contains a '-'. Reviewed by: bgamari Differential Revision: https://phabricator.haskell.org/D2138
-