- 18 Aug, 2015 5 commits
-
-
Matthew Pickering authored
When pattern synonyms were introduced a new sum type was used in places where DataCon used to be used. PatSyn and DataCon share many of the same fields, this patch adds selectors to ConLike for these fields. Reviewers: austin, goldfire, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1154
-
Sergei Trofimovich authored
Patch switches from linear lookup in unordered array to a hash table lookup. When debugging GHC array contains 658_445 elements. Found performance gap when tried to debug blackholes. Signed-off-by:
Sergei Trofimovich <siarheit@google.com> Reviewers: simonmar, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1150
-
Tamar Christina authored
The rdynamic tests and feature are marked broken on windows. This is because the flag used doesn't exist and the symbol lookup in the test did not account for platform differences in name mangling. This commit fixes the flag and tests for rdynamic on windows. Test Plan: make TEST="rdynamic" on both x86 and x86_64 Reviewers: austin, thomie, bgamari Reviewed By: thomie, bgamari Subscribers: #ghc_windows_task_force Differential Revision: https://phabricator.haskell.org/D1149 GHC Trac Issues: #9381
-
snoyberg authored
When the Windows codepage or *nix LANG variable is something besides UTF-8, dumping to file can cause GHC to exit currently. This changes the output encoding for files to match the defined input encoding for Haskell source code (UTF-8), making it easier for users and build tools to capture this output. Test Plan: Create a Haskell source file with non-Latin characters for identifier names and compile with: LANG=C ghc -ddump-to-file -ddump-hi filename.hs -fforce-recomp Without this patch, it will fail. With this patch, it succeeds Reviewers: austin, rwbarton, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1151 GHC Trac Issues: #10762
-
snoyberg authored
This avoids the compiler from crashing when, for example, a warning contains a non-Latin identifier and the LANG variable is set to C. Fixes #6037. Test Plan: Create a Haskell source file containing an identifier with non-Latin characters and no type signature. Compile with `LANG=C ghc -Wall foo.hs`, and it should fail. With this patch, it will succeed. Reviewers: austin, rwbarton, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1153 GHC Trac Issues: #6037, #10762
-
- 17 Aug, 2015 2 commits
-
-
Sergei Trofimovich authored
rts/ThreadLabels.c has a global hashtable for each running haskell thread. It's not synchronized across OS threads. Was discovered when ran -debug build of ghc itself as: $ ghc-stage2 -j8 +RTS -A256M -l and glibc detected double-free corruption: #2 in __libc_message (do_abort=do_abort@entry=2, fmt=fmt@entry=0x7fe0bcebf368 "*** Error in `%s': %s: 0x%s ***\n") #3 in malloc_printerr (action=3, str=0x7fe0bcebf4c0 "double free or corruption (fasttop)", ptr=<optimized out>) #4 in _int_free (av=<optimized out>, p=<optimized out>, have_lock=0) #5 in stgFree (p=0x7fe060001820) at rts/RtsUtils.c:108 #6 in freeHashTable (table=0x5929320, freeDataFun=0x36374df <stgFree>) at rts/Hash.c:360 #7 in freeThreadLabelTable () at rts/ThreadLabels.c:37 #8 in hs_exit_ (wait_foreign=rtsFalse) at rts/RtsStartup.c:403 #9 in shutdownHaskellAndExit (n=0, fastExit=0) at rts/RtsStartup.c:481 #10 in hs_main (...) at rts/RtsMain.c:91 #11 in main (...) at ghc/hschooks.c:63 Exposed itself after commit: > commit f6866824 > Author: Sergei Trofimovich <slyfox@gentoo.org> > Date: Mon Aug 4 08:10:33 2014 -0500 > > ghc --make: add nicer names to RTS threads (threaded IO manager, make workers) Signed-off-by:
Sergei Trofimovich <siarheit@google.com> Reviewers: austin, simonmar, ezyang, bgamari Reviewed By: ezyang, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1146
-
thomie authored
-
- 15 Aug, 2015 4 commits
- 13 Aug, 2015 2 commits
-
-
Ben Gamari authored
This is quite useful information to know. Spotted when looking at #10769.
-
Ben Gamari authored
The user's guide says hpc is incompatible with GHCi and #9903 would agree. Fixes #9903.
-
- 12 Aug, 2015 10 commits
-
-
Ben Gamari authored
-
Ben Gamari authored
-
Tamar Christina authored
This patch does a few things - Moved GHC x86 to MinGW-w64 (Using Awson's patch) - Moves Both GHCs to MSYS2 toolchains - Completely removes the dependencies on the git tarball repo - Downloads only the required tarball for the architecture for which we are building - Downloads the perl tarball is missing as well - Fixed a few bugs in the linker to fix tests on Windows The links currently point to repo.msys2.org and GitHub, it might be more desirable to mirror them on http://downloads.haskell.org/~ghc/mingw/ as with the previous patch attempt. For more details on what the MSYS2 packages I include see #10726 (Awson's comment). but it should contain all we need and no python or fortran, which makes the uncompressed tar a 1-2 hundreds mb smaller. The `GCC 5.2.0` in the package supports `libgcc` as a shared library, this is a problem since when compiling with -shared the produced dll now has a dependency on `libgcc_s_sjlj-1.dll`. To solve this the flag `-static-libgcc` is now being used for all GCC calls on windows. Test Plan: ./validate was ran both on x86 and x86_64 windows and compared against the baseline. A few test were failing due to Ld no longer being noisy. These were updated. The changes to the configure script *should* be validated by the build bots for the other platforms before landing Reviewers: simonmar, awson, bgamari, austin, thomie Reviewed By: thomie Subscribers: #ghc_windows_task_force, thomie, awson Differential Revision: https://phabricator.haskell.org/D1123 GHC Trac Issues: #10726, #9014, #9218, #10435
-
Ben Gamari authored
-
thomie authored
After 5d57087e ("Pretty: fix a broken invariant"), T3294 showed 50% more max_bytes_used (#3294). After this commit, max_bytes_used is back to what it was before, and the test passes again. This is a backport of a bug fix by Benedikt Huber (#2393), from commit 1e50748beaa4bd2281d323b18ea51c786bba04a1 in the pretty library. From https://mail.haskell.org/pipermail/libraries/2008-June/009991.html: vcat (hsep,cat) is implemented in an unneccessarily strict way. We only get some output after all of vcat's arguments are evaluated and checked against being Empty. This can be improved by only checking the right argument of foldr against being Empty, and then applying an Empty-filter on the resulting Doc. Space improvement is obvious. The microbenchmark (code.haskell.org/~bhuber/Text/PrettyPrint/ HughesPJPerfCheck.hs) suggests that the improvements in time are remarkable too.
-
thomie authored
Following libraries/pretty. I'm not sure why it converted to Double before. This function isn't used by GHC itself. It is exported from these two places: * compiler/utils/Outputable * libraries/template-haskell/Language/Haskell/TH/PprLib.hs
-
thomie authored
This is a backport of a bug fix from 6cfbd0444981c074bae10a3cf72733bcb8597bef in libraries/pretty: Fix a broken invariant Patch from #694, for the problem "empty is an identity for <> and $$" is currently broken by eg. isEmpty (empty<>empty)"
-
thomie authored
This is a backport of a bug fix by Benedikt Huber for the same problem in the pretty library (#1337), from commit 8d8866a8379c2fe8108ef034893c59e06d5e752f. The original explanation for the fix is attached below. Ticket #1776 originally reported an infinite loop when printing error message. This promptly got fixed in: commit 2d52ee06 Author: simonpj@microsoft.com <unknown> Date: Thu Mar 1 11:45:13 2007 +0000 Do not go into an infinite loop when pretty-printer finds a negative indent (Trac #1176) SPJ reports in the ticket: "So infinite loop is fixed, but the bad formatting remains. I've added a test, tcfail177." tcfail177 however hasn't triggered the formatting problem for years (as Ian reported in c9e0e606). This patch updates the test to a version that at least still failed with ghc-7.0 (from #1776#comment:7). ------------------- From https://mail.haskell.org/pipermail/libraries/2008-June/010013.html, by Benedikt Huber: Concerning ticket #1337, we have to change the formal specification of fill (it doesn't match the implementation): -- Current Specification: -- fill [] = empty -- fill [p] = p -- fill (p1:p2:ps) = oneLiner p1 <#> nest (length p1) -- (fill (oneLiner p2 : ps)) -- `union` -- p1 $$ fill ps Problem 1: We want to `unnest' the second argument of (p1 $$ fill ps), but not the first one In the definition above we have e.g. > getSecondLayout $ > fillDef False [text "a", text "b", text "a"] >> text "ab"; nilabove; nest -1; text "a"; empty >> |ab| >> |.a| Problem 2: The overlapping $$ should only be used for those layouts of p1 which aren't one liners (otherwise violating the invariant "Left union arg has shorter first line"). I suggest the following specification (i believe it almost matches the current implementation, modulo [fillNB: fix bug #1337] (see below): -- Revised Specification: -- fill g docs = fill' 0 docs -- gap g = if g then 1 else 0 -- fill' n [] = [] -- fill' n [p] = [p] -- fill' n (p1:p2:ps) = -- oneLiner p1 <g> (fill' (n+length p1+gap g) (oneLiner p2 : ps)) -- `union` -- (p1 $*$ nest (-n) (fill' g ps)) -- -- $*$ is defined for layouts (One-Layout Documents) as -- -- layout1 $*$ layout2 | isOneLiner layout1 = layout1 $+$ layout2 -- | otherwise = layout1 $$ layout2 I've also implemented the specification in HughesPJQuickCheck.hs, and checked them against the patched pretty printer. Concerning Bug #1337: ~~~~~~~~~~~~~~~~~~~~~ If the above formal specification is fine, it is easy to fix: elide the nests of (oneLiner p2) [see attached patch, record bug #1337]. > PrettyPrint(0) $ ./Bug1337 > ....ab > ...c The (long) explanation follows below. <snip/> =========================================================== Explanation of Bug #1337: Consider > fcat [ nest 1 $ text "a", nest 2 $ text "b", text "c"] --> expected: (nest 1; text "a"; text "b"; nest -3; "c") --> actual : (nest 1; text "a"; text "b"; nest -5; "c") Reduction: === (nest 1; text a) <> (fill (-2) (p2:ps)) ==> (nest 2 (text "b") $+$ text "c") ==> (nest 2 (text "b")) `nilabove` (nest (-3) (text "c")) ==> (nest 1; text a; text b; nest -5 c) The problem is that if we decide to layout (p1:p2:ps) as | p1 p2 | ps (call it layout A), then we want to have > (p1 <> p2) $+$ ps. But following law <n6> this means that > fcat_A [p1:nest k p2:ps] is equivalent to > fcat_A [p1,p2,ps] so the nest of p2 has to be removed. This is somewhat similar to bug #667, but easier to fix from a semantic point of view: p1,p2 and ps are distinct layouts - we only have to preserve the individual layouts, and no combinations of them.
-
thomie authored
This is a backport of a bug fix by Benedikt Huber (#2393), from commit 1e50748beaa4bd2281d323b18ea51c786bba04a1 in the pretty library. From https://mail.haskell.org/pipermail/libraries/2008-June/009991.html: Law <l1> states that > sep (ps++[empty]++qs) = sep (ps ++ qs) > ...ditto hsep, hcat, vcat, fill... In the current implementation, this fails for the paragraph fill variants. > render' $ fsep [ text "c", text "c",empty, text "c", text "b"] > where render' = renderStyle (Style PageMode 7 1.4) >> c c c >> b
-
Herbert Valerio Riedel authored
...since we already have introduced backward compat breakage that breaks packages such as QuickCheck-2.8.1 Differential Revision: https://phabricator.haskell.org/D1144
-
- 11 Aug, 2015 2 commits
-
-
thomie authored
-
eir@cis.upenn.edu authored
This clarifies that kind variables are inputs to type families and can be used to distinguish instances.
-
- 10 Aug, 2015 1 commit
-
-
Adam Sandberg Eriksson authored
Updates haddock submodule. Reviewers: tibbe, goldfire, simonpj, austin, bgamari Reviewed By: simonpj, bgamari Subscribers: goldfire, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D1069
-
- 09 Aug, 2015 3 commits
-
-
thomie authored
-
thomie authored
-
Herbert Valerio Riedel authored
Differential Revision: https://phabricator.haskell.org/D1140
-
- 08 Aug, 2015 2 commits
-
-
Joachim Breitner authored
and make sure these are implemented with an equality check, which is a shorter instruction. This was suggested by rwbarton in #10677. Differential Revision: https://phabricator.haskell.org/D1137
-
Joachim Breitner authored
akio wants to use oneShot with unlifted types as well, and there is no good reason not to let him. This changes the type of the built-in oneShot definition to open kinds, and also expand the documentation a little bit. Differential Revision: https://phabricator.haskell.org/D1136
-
- 07 Aug, 2015 5 commits
-
-
Herbert Valerio Riedel authored
[skip ci]
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
Edward Z. Yang authored
Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu>
-
Ben Gamari authored
-
- 06 Aug, 2015 4 commits
-
-
eir@cis.upenn.edu authored
Previously, the prot and flags variables were set but never used on Mac (darwin). This caused a warning, and the build setup stopped compilation. This commit is intended simply to omit these variables when building with darwin_HOST_OS set. No change in behavior on any platform is intended.
-
rwbarton authored
-
Ben Gamari authored
The LLVM mangler does not currently transform AVX instructions on x86-64 platforms, due to a missing #include. Also, it is significantly more complicated than necessary, due to the file into sections (not needed anymore), and is sensitive to the details of the whitespace in the assembly. Author: dobenour Test Plan: Validation on x86-64, x86-32, and ARM Reviewers: austin Subscribers: thomie, bgamari, rwbarton Differential Revision: https://phabricator.haskell.org/D1034 GHC Trac Issues: #10394
-
Fumiaki Kinoshita authored
This patch adds following instances: * Foldable ZipList * Traversable ZipList * Functor Complex * Applicative Complex * Monad Complex * Foldable Complex * Traversable Complex * Generic1 Complex * Monoid a => Monoid (Identity a) * Storable () Reviewers: ekmett, fumieval, hvr, austin Subscribers: thomie, #core_libraries_committee Projects: #core_libraries_committee Differential Revision: https://phabricator.haskell.org/D1049 GHC Trac Issues: #10609
-