- 16 Aug, 2014 3 commits
-
-
Gabor Greif authored
this is z-encoding (as hvr tells me) This reverts commit 425d5178.
-
Gabor Greif authored
-
Herbert Valerio Riedel authored
The two new primops with the type-signatures resizeMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, MutableByteArray# s #) shrinkMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> State# s allow to resize MutableByteArray#s in-place (when possible), and are useful for algorithms where memory is temporarily over-allocated. The motivating use-case is for implementing integer backends, where the final target size of the result is either N or N+1, and only known after the operation has been performed. A future commit will implement a stateful variant of the `sizeofMutableByteArray#` operation (see #9447 for details), since now the size of a `MutableByteArray#` may change over its lifetime (i.e before it gets frozen or GCed). Test Plan: ./validate --slow Reviewers: ezyang, austin, simonmar Reviewed By: austin, simonmar Differential Revision: https://phabricator.haskell.org/D133
-
- 15 Aug, 2014 2 commits
-
-
pali.gabor@gmail.com authored
-
Ben Gamari authored
Summary: We previously did a wholesale replace of `%function` to `%object` to mangle object `.type` annotations. This is bad as it can end up replacing appearances of `"%function"` in the user's code. We now look for a proper `.type` keyword before performing the replacement. Thanks to @rwbarton for pointing out the bug. Test Plan: Previously, $ echo 'main = putStrLn "@function"' > test.hs $ ghc -fllvm test.hs $ ./test @object Now, $ echo 'main = putStrLn "@function"' > test.hs $ ghc -fllvm test.hs $ ./test @function Reviewers: rwbarton, austin Reviewed By: rwbarton, austin Subscribers: phaskell, simonmar, relrod, ezyang, carter Differential Revision: https://phabricator.haskell.org/D150 GHC Trac Issues: #9439
-
- 14 Aug, 2014 2 commits
-
-
Herbert Valerio Riedel authored
This will affect commands such as git submodule update --remote utils/haddock to use `ghc-head` instead of the default `master` branch
-
Herbert Valerio Riedel authored
This implements the new primops clz#, clz32#, clz64#, ctz#, ctz32#, ctz64# which provide efficient implementations of the popular count-leading-zero and count-trailing-zero respectively (see testcase for a pure Haskell reference implementation). On x86, NCG as well as LLVM generates code based on the BSF/BSR instructions (which need extra logic to make the 0-case well-defined). Test Plan: validate and succesful tests on i686 and amd64 Reviewers: rwbarton, simonmar, ezyang, austin Subscribers: simonmar, relrod, ezyang, carter Differential Revision: https://phabricator.haskell.org/D144 GHC Trac Issues: #9340
-
- 13 Aug, 2014 3 commits
-
-
Edward Z. Yang authored
Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu>
-
Edward Z. Yang authored
Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu>
-
Edward Z. Yang authored
Summary: When this occurs, it means that the user is using an old version of Cabal. In that case, don't barf out: just go ahead and install it as an old-style package key. The user won't be able to link multiple versions together, but that should not be a problem because their Cabal can't handle it anyway. What happens if old-style are mixed up with new-style? Well, currently with Cabal, it's indistinguishable. However, if at some later point we add private dependencies, libraries compiled with old style linker names are incompatible with each other. We'll cross that road when we come to it. Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: tibbe, hvr, austin Subscribers: simonmar, relrod, ezyang, carter Differential Revision: https://phabricator.haskell.org/D154
-
- 12 Aug, 2014 18 commits
-
-
tibbe authored
We use fixed size signed types to e.g. represent array sizes. This means that the size can overflow.
-
tibbe authored
-
tibbe authored
There were two overflow issues in shouldInlinePrimOp. The first one is due to a negative CmmInt literal being created if the array size was given as larger than 2^63-1 (on a 64-bit platform.) This meant that large array sizes could compare as being smaller than maxInlineAllocSize. The second issue is that we casted the Integer to an Int in the comparison, which again meant that large array sizes could compare as being smaller than maxInlineAllocSize. The attempt to allocate a large array inline then caused a segfault. Fixes #9416.
-
eir@cis.upenn.edu authored
-
eir@cis.upenn.edu authored
-
eir@cis.upenn.edu authored
This commit also removes 'KindCheckingStrategy' and related gubbins, instead including the notion of a CUSK into HsDecls.
-
eir@cis.upenn.edu authored
-
eir@cis.upenn.edu authored
-
eir@cis.upenn.edu authored
Now, a CUSK is when (and only when) all type variables are annotated. This allows classes to participate in polymorphic recursion.
-
eir@cis.upenn.edu authored
-
eir@cis.upenn.edu authored
-
eir@cis.upenn.edu authored
Abort typechecking when we detect a superclass cycle error, as ambiguity checking in the presence of superclass cycle errors can cause a loop.
-
eir@cis.upenn.edu authored
This was very simple: lists of different lengths are *maybe* apart, not *surely* apart.
-
eir@cis.upenn.edu authored
-
rwbarton authored
Summary: The 'popcnt r16, r/m16' instruction only writes the low 16 bits of the destination register, so we have to zero-extend the result to a full word as popCnt16# is supposed to return a Word#. For popCnt8# we could instead zero-extend the input to 32 bits and then do a 32-bit popcnt, and not have to zero-extend the result. LLVM produces the 16-bit popcnt sequence with two zero extensions, though, and who am I to argue? Test Plan: - ran "make TEST=cgrun071 EXTRA_HC_OPTS=-msse42" - then ran again adding "WAY=optasm", and verified that the popcnt sequences we generate match the ones produced by LLVM for its @llvm.ctpop.* intrinsics Reviewers: austin, hvr, tibbe Reviewed By: austin, hvr, tibbe Subscribers: phaskell, hvr, simonmar, relrod, ezyang, carter Differential Revision: https://phabricator.haskell.org/D147 GHC Trac Issues: #9435
-
Herbert Valerio Riedel authored
This is a pre-requisite for implementing count-{leading,trailing}-zero prim-ops (re #9340) and may be useful to NCG to help turn some code into branch-less code sequences. Test Plan: Compiles and validates in combination with clz/ctz primop impl Reviewers: ezyang, rwbarton, simonmar, austin Subscribers: simonmar, relrod, ezyang, carter Differential Revision: https://phabricator.haskell.org/D141
-
Herbert Valerio Riedel authored
This is a pre-requisite for implementing count-{leading,trailing}-zero prim-ops (re #9340) Reviewers: ezyang, rwbarton, simonmar, austin Subscribers: simonmar, relrod, ezyang, carter Differential Revision: https://phabricator.haskell.org/D141
-
Herbert Valerio Riedel authored
This was removed in bb003086 and caused some buildbots to stop working. So this commit just re-adds it as a no-op (wrt the current default).
-
- 11 Aug, 2014 4 commits
-
-
Austin Seipp authored
Signed-off-by:
Austin Seipp <austin@well-typed.com>
-
Joachim Breitner authored
-
Sergei Trofimovich authored
Summary: Noticed by Herbert Valerio Riedel Signed-off-by:
Sergei Trofimovich <slyfox@gentoo.org> Test Plan: build test Reviewers: simonmar, austin, hvr Reviewed By: hvr Subscribers: rwbarton, phaskell, simonmar, relrod, ezyang, carter Differential Revision: https://phabricator.haskell.org/D143
-
rwbarton authored
Test Plan: - ran validate - ran T9013 test with all ways - ran CarryOverflow test with all ways, for good measure Reviewers: austin, simonmar Reviewed By: simonmar Differential Revision: https://phabricator.haskell.org/D137
-
- 10 Aug, 2014 8 commits
-
-
rwbarton authored
... in preparation for backend-specific implementations. No functional changes in this commit (except in panic messages for ill-formed Cmm). Differential Revision: https://phabricator.haskell.org/D138
-
rwbarton authored
Summary: No functional changes except in panic messages. These functions were identical except for - x87 operations in genCCall32 - the fallback to genCCall32'/64' - "32" vs "64" in panic messages (one case was wrong!) - minor syntactic or otherwise non-functional differences. Test Plan: Ran "validate --no-dph --slow" before and after the change. Only differences were two tests that failed before the change but not after, further investigation revealed that those tests are in fact erratic. Reviewers: simonmar, austin Reviewed By: austin Subscribers: phaskell, simonmar, relrod, ezyang, carter Differential Revision: https://phabricator.haskell.org/D139
-
Michael Snoyman authored
Summary: Signed-off-by: Michael Snoyman <michael@snoyman.com> Test Plan: Review documentation change Reviewers: simonpj, austin Reviewed By: austin Subscribers: phaskell, hvr, simonmar, relrod, ezyang, carter Differential Revision: https://phabricator.haskell.org/D136 GHC Trac Issues: #9390
-
etrepum authored
Summary: Signed-off-by: Bob Ippolito <bob@redivi.com> Test Plan: See repro instructions in trac #9189 Reviewers: austin Reviewed By: austin Subscribers: phaskell, simonmar, relrod, ezyang, carter Differential Revision: https://phabricator.haskell.org/D120 GHC Trac Issues: #9189
-
Austin Seipp authored
Signed-off-by:
Austin Seipp <austin@well-typed.com>
-
Sergei Trofimovich authored
Summary: GHC's RTS contains ancient Zdecode code which changed format a bit. It's easier to drop broken part and show original names. The patch changes output for './hello +RTS -Da' (apply) from such gibberish: stg_ap_v_ret... PAP/1(0x92922a, &i!_-&i!_:<.s_r=Z) stg_ap_0_ret... base:GHC.MVar.MVar(0x7fd3d1f040f8) stg_ap_v_ret... THUNK(&i!_-&i!_i!f.Z) stg_ap_v_ret... PAP/1(0x92c1f3, EO_:<.s_r=Z, EP_:<.s_r=Z) stg_ap_0_ret... ghc-prim:GHC.Tuple.(,)(0x7fd3d1f04209, 0x7fd3d1f041fa) stg_ap_0_ret... ghc-prim:GHC.Types.:(0x7fd3d1f04301, 0x7fd3d1f042ea) stg_ap_0_ret... THUNK(3F0_i!f.Z, 0x9152a1) stg_ap_0_ret... FUN/3(&s=_GHCziIOziFD_z/fB_ff=r=/IOFD14_i!f.Z) stg_ap_ppv_ret... FUN/3(&s=_GHCziIOziFD_z/fB_ff=r=/IOFD14_i!f.Z) stg_ap_0_ret... FUN/2(&s=_GHCziIOziFD_z/fIOD=vi:=FD15_i!f.Z) stg_ap_pv_ret... FUN/2(&s=_GHCziIOziFD_z/fIOD=vi:=FD15_i!f.Z) stg_ap_0_ret... base:GHC.IO.Handle.Types.FileHandle(5'A_:<.s_r=Z, 0x7fd3d1f04ef0) stg_ap_v_ret... THUNK(*>_&+_2__+/_i!f.Z, 0x7fd3d1f0602a, 0x7fd3d1f04f10) stg_ap_v_ret... PAP/1(0x7fd3d1f0602a, 0x7fd3d1f04f10) to something more readable: stg_ap_v_ret... PAP/1(0x92922a, <Main_main_closure>[0x90b710]) stg_ap_0_ret... base:GHC.MVar.MVar(0x7f1e256040f8) stg_ap_v_ret... THUNK(<Main_main_info>[0x4046c8]) stg_ap_v_ret... PAP/1(0x92c1f3, <sEO_closure>[0x90b6f0], <sEP_closure>[0x90b6d0]) stg_ap_0_ret... ghc-prim:GHC.Tuple.(,)(0x7f1e25604209, 0x7f1e256041fa) stg_ap_0_ret... ghc-prim:GHC.Types.:(0x7f1e25604301, 0x7f1e256042ea) stg_ap_0_ret... THUNK(<s3F0_info>[0x434f70], 0x9152a1) stg_ap_0_ret... FUN/3(<base_GHCziIOziFD_zdfBufferedIOFD14_info>[0x5f5198]) stg_ap_ppv_ret... FUN/3(<base_GHCziIOziFD_zdfBufferedIOFD14_info>[0x5f5198]) stg_ap_0_ret... FUN/2(<base_GHCziIOziFD_zdfIODeviceFD15_info>[0x5f7c60]) stg_ap_pv_ret... FUN/2(<base_GHCziIOziFD_zdfIODeviceFD15_info>[0x5f7c60]) stg_ap_0_ret... base:GHC.IO.Handle.Types.FileHandle(<r5qA_closure>[0x91a920], 0x7f1e25604ef0) stg_ap_v_ret... THUNK(<stg_ap_2_upd_info>[0x6b1c60], 0x7f1e2560602a, 0x7f1e25604f10) stg_ap_v_ret... PAP/1(0x7f1e2560602a, 0x7f1e25604f10) First observed on '+RTS -Di' (interpreter) on unregisterised builds. Signed-off-by:
Sergei Trofimovich <slyfox@gentoo.org> Test Plan: built 'hello world' with -debug in moth modes and ran under '+RTS -Da' Reviewers: simonmar, austin, ezyang Reviewed By: austin, ezyang Subscribers: phaskell, rwbarton, simonmar, relrod, ezyang, carter Differential Revision: https://phabricator.haskell.org/D116
-
kgardas authored
Test Plan: validate Reviewers: simonmar, austin Reviewed By: austin Subscribers: phaskell, simonmar, relrod, ezyang, carter Differential Revision: https://phabricator.haskell.org/D127
-
Austin Seipp authored
Signed-off-by:
Austin Seipp <austin@well-typed.com>
-