- 18 Sep, 2013 2 commits
-
-
Simon Peyton Jones authored
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!
-
Jan Stolarek authored
In 6579a6c7 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.
-
- 13 Sep, 2013 2 commits
-
-
Joachim Breitner authored
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.
-
Iavor S. Diatchki authored
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`.
-
- 12 Sep, 2013 1 commit
-
-
Austin Seipp authored
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>
-
- 14 Aug, 2013 1 commit
-
-
Jan Stolarek authored
This patch modifies all comparison primops for Char#, Int#, Word#, Double#, Float# and Addr# to return Int# instead of Bool. A value of 1# represents True and 0# represents False. For a more detailed description of motivation for this change, discussion of implementation details and benchmarking results please visit the wiki page: http://hackage.haskell.org/trac/ghc/wiki/PrimBool There's also some cleanup: whitespace fixes in files that were extensively edited in this patch and constant folding rules for Integer div and mod operators (which for some reason have been left out up till now).
-
- 02 Aug, 2013 1 commit
-
-
eir@cis.upenn.edu authored
Roles are a solution to the GeneralizedNewtypeDeriving type-safety problem. Roles were first described in the "Generative type abstraction" paper, by Stephanie Weirich, Dimitrios Vytiniotis, Simon PJ, and Steve Zdancewic. The implementation is a little different than that paper. For a quick primer, check out Note [Roles] in Coercion. Also see http://ghc.haskell.org/trac/ghc/wiki/Roles and http://ghc.haskell.org/trac/ghc/wiki/RolesImplementation For a more formal treatment, check out docs/core-spec/core-spec.pdf. This fixes Trac #1496, #4846, #7148.
-
- 30 May, 2013 2 commits
-
-
Iavor S. Diatchki authored
The details of this are described in Note [magicSingIId magic] in basicTypes/MkId.lhs
-
Simon Peyton Jones authored
-
- 15 May, 2013 1 commit
-
-
Simon Peyton Jones authored
This fixes Trac #7888, where the user wanted to use 'undefined' in a context that needed ((forall a. a->a) -> Int). We allow OpenKind unification variables to be instantiate with polytypes (or unboxed types), hence the change. 'error' has always been like this; this change simply extends the special treatment to 'undefined'. It's still magical; you can't define your own wrapper for 'error' and get the same behaviour. Really just a convenience hack.
-
- 14 Feb, 2013 1 commit
-
-
Simon Peyton Jones authored
This work was all done by Achim Krause <achim.t.krause@gmail.com> George Giorgidze <giorgidze@gmail.com> Weijers Jeroen <jeroen.weijers@uni-tuebingen.de> It allows list syntax, such as [a,b], [a..b] and so on, to be overloaded so that it works for a variety of types. The design is described here: http://hackage.haskell.org/trac/ghc/wiki/OverloadedLists Eg. you can use it for maps, so that [(1,"foo"), (4,"bar")] :: Map Int String The main changes * The ExplicitList constructor of HsExpr gets witness field * Ditto ArithSeq constructor * Ditto the ListPat constructor of HsPat Everything else flows from this.
-
- 13 Feb, 2013 1 commit
-
-
jpm@cs.ox.ac.uk authored
-
- 12 Feb, 2013 1 commit
-
-
jpm@cs.ox.ac.uk authored
This patch makes the Data.Typeable.Typeable class work with arguments of any kind. In particular, this removes the Typeable1..7 class hierarchy, greatly simplyfing the whole Typeable story. Also added is the AutoDeriveTypeable language extension, which will automatically derive Typeable for all types and classes declared in that module. Since there is now no good reason to give handwritten instances of the Typeable class, those are ignored (for backwards compatibility), and a warning is emitted. The old, kind-* Typeable class is now called OldTypeable, and lives in the Data.OldTypeable module. It is deprecated, and should be removed in some future version of GHC.
-
- 01 Feb, 2013 4 commits
-
-
gmainlan@microsoft.com authored
-
gmainlan@microsoft.com authored
-
-
gmainlan@microsoft.com authored
This patch lays the groundwork needed for primop support for SIMD vectors. In addition to the groundwork, we add support for the FloatX4# primitive type and associated primops. * Add the FloatX4# primitive type and associated primops. * Add CodeGen support for Float vectors. * Compile vector operations to LLVM vector operations in the LLVM code generator. * Make the x86 native backend fail gracefully when encountering vector primops. * Only generate primop wrappers for vector primops when using LLVM.
-
- 25 Jan, 2013 1 commit
-
-
Simon Peyton Jones authored
-
- 04 Jan, 2013 1 commit
-
-
twanvl authored
Changed deriving of Functor, Foldable, Traversable to fix #7436. Added foldMap to derived Foldable instance. The derived instances will no longer eta-expand the function. I.e. instead of fmap f (Foo a) = Foo (fmap (\x -> f x) a) we now derive fmap f (Foo a) = Foo (fmap f a) Some superflous lambdas are generated as a result. For example data X a = X (a,a) fmap f (X x) = (\y -> case y of (a,b) -> (f a, f b)) x The optimizer should be able to simplify this code, as it is just beta reduction. The derived Foldable instance now includes foldMap in addition to foldr.
-
- 01 Jan, 2013 1 commit
-
-
Simon Peyton Jones authored
See Note [SingI and EvLit] in TcEvidence.
-
- 21 Dec, 2012 1 commit
-
-
Simon Peyton Jones authored
Note [Use expectP] in TcGenDeriv ~~~~~~~~~~~~~~~~~~ Note that we use expectP (Ident "T1") rather than Ident "T1" <- lexP The latter desugares to inline code for matching the Ident and the string, and this can be very voluminous. The former is much more compact. Cf Trac #7258, although that also concerned non-linearity in the occurrence analyser, a separate issue.
-
- 19 Dec, 2012 1 commit
-
-
Simon Peyton Jones authored
They properly belong in TysWiredIn, since they are defined in Haskell in GHC.TypeLits. Moveover, make them WiredIn (again as they should be) and use checkWiredInTyCon when encountering them in TcHsType.tc_hs_type, so that the interface file is loaded. This fixes Trac #7502.
-
- 21 Oct, 2012 1 commit
-
-
Adds better support for constant folding of Float/Double literals. - add rationalToFloat, rationalToDouble with associated Name/Id's in PrelNames. - add a matching rule in PrelRules for rationalTo* functions.
-
- 21 Jun, 2012 1 commit
-
-
jpm@cs.ox.ac.uk authored
This completes the support for generic programming introduced in GHC 7.2. Generic1 allows defining generic functions that operate on type containers, such as `fmap`, for instance. Along the way we have fixed #5936 and #5939, allowing deriving Generic/Generic1 for data families, and disallowing deriving Generic/Generic1 for instantiated types. Most of this patch is Nicolas Frisby's work.
-
- 13 Jun, 2012 1 commit
-
-
Simon Peyton Jones authored
This patch re-implements implicit parameters via a class with a functional dependency: class IP (n::Symbol) a | n -> a where ip :: a This definition is in the library module GHC.IP. Notice how it use a type-literal, so we can have constraints like IP "x" Int Now all the functional dependency machinery works right to make implicit parameters behave as they should. Much special-case processing for implicit parameters can be removed entirely. One particularly nice thing is not having a dedicated "original-name cache" for implicit parameters (the nsNames field of NameCache). But many other cases disappear: * BasicTypes.IPName * IPTyCon constructor in Tycon.TyCon * CIPCan constructor in TcRnTypes.Ct * IPPred constructor in Types.PredTree Implicit parameters remain special in a few ways: * Special syntax. Eg the constraint (IP "x" Int) is parsed and printed as (?x::Int). And we still have local bindings for implicit parameters, and occurrences thereof. * A implicit-parameter binding (let ?x = True in e) amounts to a local instance declaration, which we have not had before. It just generates an implication contraint (easy), but when going under it we must purge any existing bindings for ?x in the inert set. See Note [Shadowing of Implicit Parameters] in TcSimplify * TcMType.sizePred classifies implicit parameter constraints as size-0, as before the change There are accompanying patches to libraries 'base' and 'haddock' All the work was done by Iavor Diatchki
-
- 08 Jun, 2012 1 commit
-
-
Ian Lynagh authored
-
- 06 Jun, 2012 1 commit
-
-
Ian Lynagh authored
-
- 21 May, 2012 1 commit
-
-
Ian Lynagh authored
-
- 15 May, 2012 1 commit
-
-
batterseapower authored
This is done by a 'unarisation' pre-pass at the STG level which translates away all (live) binders binding something of unboxed tuple type. This has the following knock-on effects: * The subkind hierarchy is vastly simplified (no UbxTupleKind or ArgKind) * Various relaxed type checks in typechecker, 'foreign import prim' etc * All case binders may be live at the Core level
-
- 24 Apr, 2012 1 commit
-
- 13 Apr, 2012 2 commits
-
-
Simon Peyton Jones authored
Two problems, for now at any rate a) Breaks the build with lots of errors like No instance for (Show (IO ())) arising from a use of `print' b) Discussion of the approache hasn't converged yet (Simon M had a number of suggestions) This reverts commit eecd7c98.
-
dterei authored
This command allows you to lift user stmts in GHCi into an IO monad that implements the GHC.GHCi.GHCiSandboxIO type class. This allows for easy sandboxing of GHCi using :runmonad and Safe Haskell. Longer term it would be nice to allow a more general model for the Monad than GHCiSandboxIO but delaying this for the moment.
-
- 09 Apr, 2012 1 commit
-
-
Iavor S. Diatchki authored
-
- 22 Feb, 2012 1 commit
-
-
batterseapower authored
Jose's patch implementing kind-polymorphic core (09015be8) reverted many of the simplifying changes to interface file TyCon serialization I had made in a previous patch (5d7173f9). Based on the diff I think this was an unintended consequence of how Jose did the merge rather than a real change he intended to make. In fact, as a result of kind-polymorphic core we don't need to treat the Any TyCon specially any longer so my old simplifying changes can be made even simpler: IfaceTyCon is now just a newtype on IfaceExtName.
-
- 16 Feb, 2012 1 commit
-
-
Simon Peyton Jones authored
And in particular we now have BOX :: BOX See Note [SuperKind (BOX)] in TysPrim
-
- 25 Jan, 2012 1 commit
-
-
Iavor S. Diatchki authored
These are types that look like "this" and "that". They are of kind `Symbol`, defined in module `GHC.TypeLits`. For each type-level symbol `X`, we have a singleton type, `TSymbol X`. The value of the singleton type can be named with the overloaded constant `tSymbol`. Here is an example: tSymbol :: TSymbol "Hello"
-
- 13 Jan, 2012 1 commit
-
-
Simon Peyton Jones authored
There was a trivial typo which meant that important newly-added rules would never fire!
-
- 11 Jan, 2012 1 commit
-
-
Ian Lynagh authored
-
- 10 Jan, 2012 1 commit
-
-
Ian Lynagh authored
-
- 07 Jan, 2012 1 commit
-
-
Ian Lynagh authored
-