summaryrefslogtreecommitdiff
path: root/compiler/prelude
Commit message (Collapse)AuthorAgeFilesLines
...
* Simplify and tidy up the handling of tuple namesSimon Peyton Jones2014-04-042-45/+122
| | | | | | | | | | | | | 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.
* Add SmallArray# and SmallMutableArray# typesJohan Tibell2014-03-293-7/+172
| | | | | | | | | | | | | | | These array types are smaller than Array# and MutableArray# and are faster when the array size is small, as they don't have the overhead of a card table. Having no card table reduces the closure size with 2 words in the typical small array case and leads to less work when updating or GC:ing the array. Reduces both the runtime and memory allocation by 8.8% on my insert benchmark for the HashMap type in the unordered-containers package, which makes use of lots of small arrays. With tuned GC settings (i.e. `+RTS -A6M`) the runtime reduction is 15%. Fixes #8923.
* Make copy array ops out-of-line by defaultJohan Tibell2014-03-281-6/+6
| | | | | | This should reduce code size when there's little to gain from inlining these primops, while still retaining the inlining benefit when the size of the copy is known statically.
* codeGen: inline allocation optimization for clone array primopsJohan Tibell2014-03-221-0/+4
| | | | | | | | | | | | | | | | | | | | | | | | The inline allocation version is 69% faster than the out-of-line version, when cloning an array of 16 unit elements on a 64-bit machine. Comparing the new and the old primop implementations isn't straightforward. The old version had a missing heap check that I discovered during the development of the new version. Comparing the old and the new version would requiring fixing the old version, which in turn means reimplementing the equivalent of MAYBE_CG in StgCmmPrim. The inline allocation threshold is configurable via -fmax-inline-alloc-size which gives the maximum array size, in bytes, to allocate inline. The size does not include the closure header size. Allowing the same primop to be either inline or out-of-line has some implication for how we lay out heap checks. We always place a heap check around out-of-line primops, as they may allocate outside of our knowledge. However, for the inline primops we only allow allocation via the standard means (i.e. virtHp). Since the clone primops might be either inline or out-of-line the heap check layout code now consults shouldInlinePrimOp to know whether a primop will be inlined.
* Implement ordering comparisons for type-level naturals and symbols.Iavor S. Diatchki2014-03-182-0/+19
| | | | | This is done with two built-in type families: `CmpNat and `CmpSymbol`. Both of these return a promoted `Ordering` type (EQ, LT, or GT).
* Coercible is now exported from GHC.Types (#8894)Joachim Breitner2014-03-162-5/+1
| | | | | so do not export it in GHC.Prim, and also have the pseudo-code for GHC.Prim import GHC.Types, so that haddock is happy.
* Another reference to Note [Kind-changing of (~) and Coercible]Joachim Breitner2014-03-141-1/+4
|
* Reference Note [Kind-changing of (~) and Coercible]Joachim Breitner2014-03-141-0/+2
|
* Remove unused gHC_COERCIBLEJoachim Breitner2014-03-141-2/+1
|
* Improve copy/clone array primop docsJohan Tibell2014-03-131-13/+29
| | | | | | Clarify the order of the arguments. Also, remove any use of # in the comments, which would make the rest of that comment line disappear in the docs, due to being treated as a comment by the preprocessor.
* Add BuiltinRules for constant-folding not# and notI# (logical complement)Simon Peyton Jones2014-03-131-0/+9
| | | | | | | | I don't know why these constant-folding rules were implemented for and/or/xor but not for 'not'. Adding them is part of the fix for Trac #8832. (The other part is in Data.Bits.)
* Allow ($) to return an unlifted type (Trac #8739)Simon Peyton Jones2014-02-181-4/+1
| | | | | | | | | | | | Since ($) simply returns its result, via a tail call, it can perfectly well have an unlifted result type; e.g. foo $ True where foo :: Bool -> Int# should be perfectly fine. This used to work in GHC 7.2, but caused a Lint failure. This patch makes it work again (which involved removing code in TcExpr), but fixing the Lint failure meant I had to make ($) into a wired-in Id. Which is not hard to do (in MkId).
* Remove Coercible documentation from compiler/prelude/primops.txt.ppJoachim Breitner2014-01-301-41/+0
| | | | | We want it to show up in GHC.Exts, so we need to put the documentation in GHC.Types, where the datatype Coercible is defined.
* Implement pattern synonymsDr. ERDI Gergo2014-01-201-3/+4
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch implements Pattern Synonyms (enabled by -XPatternSynonyms), allowing y ou to assign names to a pattern and abstract over it. The rundown is this: * Named patterns are introduced by the new 'pattern' keyword, and can be either *unidirectional* or *bidirectional*. A unidirectional pattern is, in the simplest sense, simply an 'alias' for a pattern, where the LHS may mention variables to occur in the RHS. A bidirectional pattern synonym occurs when a pattern may also be used in expression context. * Unidirectional patterns are declared like thus: pattern P x <- x:_ The synonym 'P' may only occur in a pattern context: foo :: [Int] -> Maybe Int foo (P x) = Just x foo _ = Nothing * Bidirectional patterns are declared like thus: pattern P x y = [x, y] Here, P may not only occur as a pattern, but also as an expression when given values for 'x' and 'y', i.e. bar :: Int -> [Int] bar x = P x 10 * Patterns can't yet have their own type signatures; signatures are inferred. * Pattern synonyms may not be recursive, c.f. type synonyms. * Pattern synonyms are also exported/imported using the 'pattern' keyword in an import/export decl, i.e. module Foo (pattern Bar) where ... Note that pattern synonyms share the namespace of constructors, so this disambiguation is required as a there may also be a 'Bar' type in scope as well as the 'Bar' pattern. * The semantics of a pattern synonym differ slightly from a typical pattern: when using a synonym, the pattern itself is matched, followed by all the arguments. This means that the strictness differs slightly: pattern P x y <- [x, y] f (P True True) = True f _ = False g [True, True] = True g _ = False In the example, while `g (False:undefined)` evaluates to False, `f (False:undefined)` results in undefined as both `x` and `y` arguments are matched to `True`. For more information, see the wiki: https://ghc.haskell.org/trac/ghc/wiki/PatternSynonyms https://ghc.haskell.org/trac/ghc/wiki/PatternSynonyms/Implementation Reviewed-by: Simon Peyton Jones <simonpj@microsoft.com> Signed-off-by: Austin Seipp <austin@well-typed.com>
* Re-work the naming story for the GHCi prompt (Trac #8649)Simon Peyton Jones2014-01-091-6/+3
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The basic idea here is simple, and described in Note [The interactive package] in HscTypes, which starts thus: Note [The interactive package] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Type and class declarations at the command prompt are treated as if they were defined in modules interactive:Ghci1 interactive:Ghci2 ...etc... with each bunch of declarations using a new module, all sharing a common package 'interactive' (see Module.interactivePackageId, and PrelNames.mkInteractiveModule). This scheme deals well with shadowing. For example: ghci> data T = A ghci> data T = B ghci> :i A data Ghci1.T = A -- Defined at <interactive>:2:10 Here we must display info about constructor A, but its type T has been shadowed by the second declaration. But it has a respectable qualified name (Ghci1.T), and its source location says where it was defined. So the main invariant continues to hold, that in any session an original name M.T only refers to oe unique thing. (In a previous iteration both the T's above were called :Interactive.T, albeit with different uniques, which gave rise to all sorts of trouble.) This scheme deals nicely with the original problem. It allows us to eliminate a couple of grotseque hacks - Note [Outputable Orig RdrName] in HscTypes - Note [interactive name cache] in IfaceEnv (both these comments have gone, because the hacks they describe are no longer necessary). I was also able to simplify Outputable.QueryQualifyName, so that it takes a Module/OccName as args rather than a Name. However, matters are never simple, and this change took me an unreasonably long time to get right. There are some details in Note [The interactive package] in HscTypes.
* Document Proxy# (#8658)Austin Seipp2014-01-091-0/+12
| | | | Signed-off-by: Austin Seipp <austin@well-typed.com>
* Guarding against silly shiftsSimon Peyton Jones2013-12-121-12/+68
| | | | | This patch was authored by SPJ and extracted from "Improve the handling of used-once stuff" by Joachim.
* Assign strictness signatures to primitive operationsSimon Peyton Jones2013-12-121-2/+8
| | | | | This patch was authored by SPJ, and extracted from "Improve the handling of used-once stuff" by Joachim.
* Replace mkTopDmdType by mkClosedStrictSigJoachim Breitner2013-12-091-5/+5
| | | | | because it is not a top deman (see previous commit), and it is only used in an argument to mkStrictSig.
* Fix note reference [WildCard binders]Joachim Breitner2013-12-041-1/+1
|
* Update Notes for CoercibleJoachim Breitner2013-11-291-1/+1
|
* Get rid of EvCoercibleJoachim Breitner2013-11-271-1/+1
| | | | and use EvCoercion to describe the evidence for Coercible instances.
* Replace (State# RealWorld) with Void# where we just want a 0-bit valueSimon Peyton Jones2013-11-222-3/+14
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | We were re-using the super-magical "state token" type (which has VoidRep and is zero bits wide) for situations in which we simply want to lambda-abstract over a zero-bit argument. For example, join points: case (case x of { True -> e1; False -> e2 }) of Red -> f1 Blue -> True ==> let $j1 = \voidArg::Void# -> f1 in case x of True -> case e1 of Red -> $j1 void Blue -> True False -> case e2 of Red -> $j1 void Blue -> True This patch introduces * The new primitive type GHC.Prim.Void#, with PrimRep = VoidRep * A new global Id GHC.Prim.voidPrimId :: Void#. This has no binding because the code generator drops it, but is used as an argument (eg in the call of $j1) * A new local Id, MkId.voidArgId, which can be lambda-bound when you need to lambda-abstract over it. and uses them throughout. Now the State# thing is used only when we need state!
* Make Coercible higher-kindedJoachim Breitner2013-11-201-7/+11
| | | | | | This implements #8541. The changes are fully straight forward and work nicely for the examples from the ticket; this is mostly due to the existing code not checking for saturation and kindness.
* Update documentation concerning prefetch opsCarter Tazio Schonwald2013-11-031-22/+15
| | | | | | | Also remove can_fail=True since it's likely unnecessary upon discussion (see #8256.) Signed-off-by: Austin Seipp <austin@well-typed.com>
* Nuke trailing whitespace.Austin Seipp2013-11-021-8/+8
| | | | Signed-off-by: Austin Seipp <austin@well-typed.com>
* adding further documentation and explanation to the prefetch primopsCarter Tazio Schonwald2013-11-021-2/+25
| | | | | Signed-off-by: Carter Tazio Schonwald <carter.schonwald@gmail.com> Signed-off-by: Austin Seipp <austin@well-typed.com>
* Make SpecConstr also check for GHC.Types.SPECAustin Seipp2013-10-251-4/+12
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | SpecConstr has for a while now looked for types with the built in ForceSpecConstr annotation, in order to know where to be particularly aggressive. Unfortunately using an annotation has a number of downsides, the most prominent two being: A) ForceSpecConstr is vital for efficiency (even if it's a hack), but it means users of it must have GHCI - even though stage2 features are not required for anything but the annotation. B) Any user who might need it (read: vector) has to duplicate the same piece of code. In general there are few people actually doing this, but it's unclear why they should have to. This patch makes SpecConstr look for functions applied to the new GHC.Types.SPEC type - a copy of the already-extant 'SPEC' type - as well as look for annotations, in the stage2 compiler. In particular, this means `vector` can now be built with a stage1 compiler, since it no longer depends on stage2 for anything else. This is particularly important for e.g. iOS cross-compilers. This also means we should be able to build `vector` earlier in the build process too, but this patch doesn't address that. This requires an accompanying bump in ghc-prim. Signed-off-by: Austin Seipp <austin@well-typed.com>
* TyposKrzysztof Gogolewski2013-10-121-1/+1
|
* Update and clean-up the implmenation of GHC.TypeLitsIavor S. Diatchki2013-10-092-23/+29
| | | | | | | | | | | | | | | | | | * Replace class `SingI` with two separate classes: `KnownNat` and `KnownSymbol` * Rename `magicSingId` to `magicDictId`. * Simplify and clean-up the "magic" implementation. This version makes a lot more sense, at least to me :-) * Update notes about how it all works: Note [KnownNat & KnownSymbol and EvLit] explains the evidence for the built-in classes Note [magicDictId magic] explains how we coerce singleton values into dictionaries. This is used to turn run-time integers and strings into Proxy singletons of unknwon type (using an existential).
* Add support for prefetch with locality levels.Austin Seipp2013-10-011-8/+77
| | | | | | | | | | | | | | | | | This patch adds support for several new primitive operations which support using processor-specific instructions to help guide data and cache locality decisions. We have levels ranging from [0..3] For LLVM, we generate llvm.prefetch intrinsics at the proper locality level (similar to GCC.) For x86 we generate prefetch{NTA, t2, t1, t0} instructions. On SPARC and PowerPC, the locality levels are ignored. This closes #8256. Authored-by: Carter Tazio Schonwald <carter.schonwald@gmail.com> Signed-off-by: Austin Seipp <austin@well-typed.com>
* Globally replace "hackage.haskell.org" with "ghc.haskell.org"Simon Marlow2013-10-013-4/+4
|
* Make typeRep_RDR use typeRep# instead of typeRepAustin Seipp2013-09-271-1/+1
| | | | | | Authored-by: Edward Kmett <ekmett@gmail.com> Authored-by: Austin Seipp <austin@well-typed.com> Signed-off-by: Austin Seipp <austin@well-typed.com>
* Implement an unlifted Proxy type, Proxy#Austin Seipp2013-09-272-1/+20
| | | | | | | | | | | | | A value of type 'Proxy# a' can only be created through the new, primitive witness 'proxy# :: Proxy# a' - a Proxy# has no runtime representation and is thus free. This lets us clean up the internals of TypeRep, as well as Adam's future work concerning records (by using a zero-width primitive type.) Authored-by: Edward Kmett <ekmett@gmail.com> Authored-by: Austin Seipp <austin@well-typed.com> Signed-off-by: Austin Seipp <austin@well-typed.com>
* Add a type-function for subtraction.Iavor S. Diatchki2013-09-241-1/+2
| | | | | This is used in the definition of `ToNat1` in the `base` library (module GHC.TypeLits).
* Add 512-bit-wide SIMD primitives.Geoffrey Mainland2013-09-221-4/+12
|
* Add 256-bit-wide SIMD primitives.Geoffrey Mainland2013-09-221-4/+12
|
* Flesh out 128-bit wide SIMD primops.Geoffrey Mainland2013-09-221-5/+5
|
* SIMD primops are now generated using schemas that are polymorphic inGeoffrey Mainland2013-09-224-437/+147
| | | | | | | | | | | | | width and element type. SIMD primops are now polymorphic in vector size and element type, but only internally to the compiler. More specifically, utils/genprimopcode has been extended so that it "knows" about SIMD vectors. This allows us to, for example, write a single definition for the "add two vectors" primop in primops.txt.pp and have it instantiated at many vector types. This generates a primop in GHC.Prim for each vector type at which "add two vectors" is instantiated, but only one data constructor for the PrimOp data type, so the code generator is much, much simpler.
* Make Word# a wired-in TyCon (fix Trac #8280)Simon Peyton Jones2013-09-182-10/+10
| | | | | | | | wordTyCon was treated as wired-in, but * It didn't have a WiredInName * It didn't appear in the list of wiredInTyCons I'm not sure how anything worked!
* Restore old names of comparison primopsJan Stolarek2013-09-182-45/+44
| | | | | | | | | | | | In 6579a6c we removed existing comparison primops and introduced new ones returning Int# instead of Bool. This commit (and associated commits in array, base, dph, ghc-prim, integer-gmp, integer-simple, primitive, testsuite and template-haskell) restores old names of primops. This allows us to keep our API cleaner at the price of not having backwards compatibility. This patch also temporalily disables fix for #8317 (optimization of tagToEnum# at Core level). We need to fix #8326 first, otherwise our primops code will be very slow.
* Trailing whitespacesJan Stolarek2013-09-181-105/+105
|
* Implement checkable "minimal complete definitions" (#7633)Twan van Laarhoven2013-09-181-1/+2
| | | | | | | | | | | | | | This commit adds a `{-# MINIMAL #-}` pragma, which defines the possible minimal complete definitions for a class. The body of the pragma is a boolean formula of names. The old warning for missing methods is replaced with this new one. Note: The interface file format is changed to store the minimal complete definition. Authored-by: Twan van Laarhoven <twanvl@gmail.com> Signed-off-by: Herbert Valerio Riedel <hvr@gnu.org>
* Fix the type signatures of new copy primops.Austin Seipp2013-09-151-3/+3
| | | | | | | They claimed to work over 'ST RealWorld', when instead they should be parameterized in the state type. This fixes the cgrun070. Signed-off-by: Austin Seipp <austin@well-typed.com>
* New primops for byte range copies ByteArray# <-> Addr#Duncan Coutts2013-09-151-0/+36
| | | | | | | | | | | | | | | | | | | | | | | We have primops for copying ranges of bytes between ByteArray#s: * ByteArray# -> MutableByteArray# * MutableByteArray# -> MutableByteArray# This extends it with three further cases: * Addr# -> MutableByteArray# * ByteArray# -> Addr# * MutableByteArray# -> Addr# One use case for these is copying between ForeignPtr-based representations and in-heap arrays (like Text, UArray etc). The implementation is essentially the same as for the existing primops, and shares the memcpy stuff in the code generators. Defficiencies / future directions: none of these primops (existing or the new ones) let one take advantage of knowing that ByteArray#s are word-aligned in memory. Though it is unclear that any of the code generators would make use of this information unless the size to copy is also known at compile time. Signed-off-by: Austin Seipp <austin@well-typed.com>
* Introduce coerce :: Coercible a b -> a -> bcoercibleJoachim Breitner2013-09-134-3/+97
| | | | | | | | | | | This is the result of the design at http://ghc.haskell.org/trac/ghc/wiki/NewtypeWrappers The goal is to be able to convert between, say [First Int] and [Last Int] with zero run-time overhead. To that end, we introduce a special two parameter type class Coercible whose instances are created automatically and on-the fly. This relies on and exploits the recent addition of roles to core.
* Add support for evaluation of type-level natural numbers.Iavor S. Diatchki2013-09-123-14/+23
| | | | | | | | | | | | | | | | | | | | | | | | | This patch implements some simple evaluation of type-level expressions featuring natural numbers. We can evaluate *concrete* expressions that use the built-in type families (+), (*), (^), and (<=?), declared in GHC.TypeLits. We can also do some type inference involving these functions. For example, if we encounter a constraint such as `(2 + x) ~ 5` we can infer that `x` must be 3. Note, however, this is used only to resolve unification variables (i.e., as a form of a constraint improvement) and not to generate new facts. This is similar to how functional dependencies work in GHC. The patch adds a new form of coercion, `AxiomRuleCo`, which makes use of a new form of axiom called `CoAxiomRule`. This is the form of evidence generate when we solve a constraint, such as `(1 + 2) ~ 3`. The patch also adds support for built-in type-families, by adding a new form of TyCon rhs: `BuiltInSynFamTyCon`. such built-in type-family constructors contain a record with functions that are used by the constraint solver to simplify and improve constraints involving the built-in function (see `TcInteract`). The record in defined in `FamInst`. The type constructors and rules for evaluating the type-level functions are in a new module called `TcTypeNats`.
* Implement the AMP warning (#8004)Austin Seipp2013-09-111-3/+28
| | | | | | | | | | | | | | | | | | | | | | | | | | This patch implements a warning when definitions conflict with the Applicative-Monad Proposal (AMP), described in #8004. Namely, this will cause a warning iff: * You have an instance of Monad, but not Applicative * You have an instance of MonadPlus, but not Alternative * You locally defined a function named join, <*>, or pure. In GHC 7.10, these warnings will actually be enforced with superclass constraints through changes in base, so programs will fail to compile then. This warning is enabled by default. Unfortunately, not all of our upstream libraries have accepted the appropriate patches. So we temporarily fix ./validate by ignoring the AMP warning. Dan Rosén made an initial implementation of this change, and the remaining work was finished off by David Luposchainsky. I finally made some minor refactorings. Authored-by: Dan Rosén <danr@chalmers.se> Authored-by: David Luposchainsky <dluposchainsky@gmail.com> Signed-off-by: Austin Seipp <austin@well-typed.com>
* Fix AMP warnings.Austin Seipp2013-09-111-0/+12
| | | | | Authored-by: David Luposchainsky <dluposchainsky@gmail.com> Signed-off-by: Austin Seipp <austin@well-typed.com>
* Add basic support for GHCJSAustin Seipp2013-09-061-2/+8
| | | | | | | | | | | | | | | | | | | This patch encompasses most of the basic infrastructure for GHCJS. It includes: * A new extension, -XJavaScriptFFI * A new architecture, ArchJavaScript * Parser and lexer support for 'foreign import javascript', only available under -XJavaScriptFFI, using ArchJavaScript. * As a knock-on, there is also a new 'WayCustom' constructor in DynFlags, so clients of the GHC API can add custom 'tags' to their built files. This should be useful for other users as well. The remaining changes are really just the resulting fallout, making sure all the cases are handled appropriately for DynFlags and Platform. Authored-by: Luite Stegeman <stegeman@gmail.com> Signed-off-by: Austin Seipp <aseipp@pobox.com>