summaryrefslogtreecommitdiff
path: root/compiler/vectorise
Commit message (Collapse)AuthorAgeFilesLines
* Merge branch 'master' of http://darcs.haskell.org/ghcSimon Peyton Jones2013-01-302-6/+9
|\ | | | | | | | | Conflicts: compiler/types/Coercion.lhs
| * Pure refactoringSimon Peyton Jones2013-01-281-0/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | * Move tidyType and friends from TcType to TypeRep (It was always wrong to have it in TcType.) * Move mkCoAxBranch and friends from FamInst to Coercion * Move pprCoAxBranch and friends from FamInstEnv to Coercion No change in functionality, though there might be a little wibble in error message output, because I combined two different functions both called pprCoAxBranch!
| * More refactoring of FamInst/FamInstEnv; finally fixes Trac #7524Simon Peyton Jones2013-01-282-6/+8
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Quite a bit of tidying up here; the fix to #7524 is actually only a small part. * Be fully clear that the cab_tvs in a CoAxBranch are not fresh. See Note [CoAxBranch type variables] in CoAxiom. * Use CoAxBranch to replace the ATDfeault type in Class. CoAxBranch is perfect here. This change allowed me to delete quite a bit of boilerplate code, including the corresponding IfaceSynType. * Tidy up the construction of CoAxBranches, and when FamIntBranch is freshened. The latter onw happens only in FamInst.newFamInst. * Tidy the tyvars of a CoAxBranch when we build them, done in FamInst.mkCoAxBranch. See Note [Tidy axioms when we build them] in that module. This is what fixes #7524. Much niceer now.
* | Merge branch 'master' of http://darcs.haskell.org/ghcSimon Peyton Jones2013-01-252-0/+2
|\ \ | |/ | | | | | | Conflicts: compiler/basicTypes/DataCon.lhs
| * Refactor and improve the promotion inferenceSimon Peyton Jones2013-01-252-0/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | It should be the case that either an entire mutually recursive group of data type declarations can be promoted, or none of them. It's really odd to promote some data constructors of a type but not others. Eg data T a = T1 a | T2 Int Here T1 is sort-of-promotable but T2 isn't (becuase Int isn't promotable). This patch makes it all-or-nothing. At the same time I've made the TyCon point to its promoted cousin (via the tcPromoted field of an AlgTyCon), as well as vice versa (via the ty_con field of PromotedTyCon). The inference for the group is done in TcTyDecls, the same place that infers which data types are recursive, another global question.
* | Introduce CPR for sum types (Trac #5075)Simon Peyton Jones2013-01-241-5/+5
|/ | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The main payload of this patch is to extend CPR so that it detects when a function always returns a result constructed with the *same* constructor, even if the constructor comes from a sum type. This doesn't matter very often, but it does improve some things (results below). Binary sizes increase a little bit, I think because there are more wrappers. This with -split-objs. Without split-ojbs binary sizes increased by 6% even for HelloWorld.hs. It's hard to see exactly why, but I think it was because System.Posix.Types.o got included in the linked binary, whereas it didn't before. Program Size Allocs Runtime Elapsed TotalMem fluid +1.8% -0.3% 0.01 0.01 +0.0% tak +2.2% -0.2% 0.02 0.02 +0.0% ansi +1.7% -0.3% 0.00 0.00 +0.0% cacheprof +1.6% -0.3% +0.6% +0.5% +1.4% parstof +1.4% -4.4% 0.00 0.00 +0.0% reptile +2.0% +0.3% 0.02 0.02 +0.0% ---------------------------------------------------------------------- Min +1.1% -4.4% -4.7% -4.7% -15.0% Max +2.3% +0.3% +8.3% +9.4% +50.0% Geometric Mean +1.9% -0.1% +0.6% +0.7% +0.3% Other things in this commit ~~~~~~~~~~~~~~~~~~~~~~~~~~~ * Got rid of the Lattice class in Demand * Refactored the way that products and newtypes are decomposed (no change in functionality)
* Refactor invariants for FamInsts.Richard Eisenberg2013-01-052-4/+8
| | | | | | | | | | | | | This commit mirrors work done in the commit for ClsInsts, 5efe9b... Specifically: - All FamInsts have *fresh* type variables. So, no more freshness work in addLocalFamInst Also: - Some pretty-printing code around FamInsts was cleaned up a bit This caused location information to be added to CoAxioms and index information to be added to FamInstBranches.
* Merge branch 'master' of http://darcs.haskell.org/ghcSimon Peyton Jones2012-12-239-34/+47
|\ | | | | | | | | | | Conflicts: compiler/basicTypes/MkId.lhs compiler/iface/IfaceSyn.lhs
| * Implement overlapping type family instances.Richard Eisenberg2012-12-219-34/+47
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | An ordered, overlapping type family instance is introduced by 'type instance where', followed by equations. See the new section in the user manual (7.7.2.2) for details. The canonical example is Boolean equality at the type level: type family Equals (a :: k) (b :: k) :: Bool type instance where Equals a a = True Equals a b = False A branched family instance, such as this one, checks its equations in order and applies only the first the matches. As explained in the note [Instance checking within groups] in FamInstEnv.lhs, we must be careful not to simplify, say, (Equals Int b) to False, because b might later unify with Int. This commit includes all of the commits on the overlapping-tyfams branch. SPJ requested that I combine all my commits over the past several months into one monolithic commit. The following GHC repos are affected: ghc, testsuite, utils/haddock, libraries/template-haskell, and libraries/dph. Here are some details for the interested: - The definition of CoAxiom has been moved from TyCon.lhs to a new file CoAxiom.lhs. I made this decision because of the number of definitions necessary to support BranchList. - BranchList is a GADT whose type tracks whether it is a singleton list or not-necessarily-a-singleton-list. The reason I introduced this type is to increase static checking of places where GHC code assumes that a FamInst or CoAxiom is indeed a singleton. This assumption takes place roughly 10 times throughout the code. I was worried that a future change to GHC would invalidate the assumption, and GHC might subtly fail to do the right thing. By explicitly labeling CoAxioms and FamInsts as being Unbranched (singleton) or Branched (not-necessarily-singleton), we make this assumption explicit and checkable. Furthermore, to enforce the accuracy of this label, the list of branches of a CoAxiom or FamInst is stored using a BranchList, whose constructors constrain its type index appropriately. I think that the decision to use BranchList is probably the most controversial decision I made from a code design point of view. Although I provide conversions to/from ordinary lists, it is more efficient to use the brList... functions provided in CoAxiom than always to convert. The use of these functions does not wander far from the core CoAxiom/FamInst logic. BranchLists are motivated and explained in the note [Branched axioms] in CoAxiom.lhs. - The CoAxiom type has changed significantly. You can see the new type in CoAxiom.lhs. It uses a CoAxBranch type to track branches of the CoAxiom. Correspondingly various functions producing and consuming CoAxioms had to change, including the binary layout of interface files. - To get branched axioms to work correctly, it is important to have a notion of type "apartness": two types are apart if they cannot unify, and no substitution of variables can ever get them to unify, even after type family simplification. (This is different than the normal failure to unify because of the type family bit.) This notion in encoded in tcApartTys, in Unify.lhs. Because apartness is finer-grained than unification, the tcUnifyTys now calls tcApartTys. - CoreLinting axioms has been updated, both to reflect the new form of CoAxiom and to enforce the apartness rules of branch application. The formalization of the new rules is in docs/core-spec/core-spec.pdf. - The FamInst type (in types/FamInstEnv.lhs) has changed significantly, paralleling the changes to CoAxiom. Of course, this forced minor changes in many files. - There are several new Notes in FamInstEnv.lhs, including one discussing confluent overlap and why we're not doing it. - lookupFamInstEnv, lookupFamInstEnvConflicts, and lookup_fam_inst_env' (the function that actually does the work) have all been more-or-less completely rewritten. There is a Note [lookup_fam_inst_env' implementation] describing the implementation. One of the changes that affects other files is to change the type of matches from a pair of (FamInst, [Type]) to a new datatype (which now includes the index of the matching branch). This seemed a better design. - The TySynInstD constructor in Template Haskell was updated to use the new datatype TySynEqn. I also bumped the TH version number, requiring changes to DPH cabal files. (That's why the DPH repo has an overlapping-tyfams branch.) - As SPJ requested, I refactored some of the code in HsDecls: * splitting up TyDecl into SynDecl and DataDecl, correspondingly changing HsTyDefn to HsDataDefn (with only one constructor) * splitting FamInstD into TyFamInstD and DataFamInstD and splitting FamInstDecl into DataFamInstDecl and TyFamInstDecl * making the ClsInstD take a ClsInstDecl, for parallelism with InstDecl's other constructors * changing constructor TyFamily into FamDecl * creating a FamilyDecl type that stores the details for a family declaration; this is useful because FamilyDecls can appear in classes but other decls cannot * restricting the associated types and associated type defaults for a * class to be the new, more restrictive types * splitting cid_fam_insts into cid_tyfam_insts and cid_datafam_insts, according to the new types * perhaps one or two more that I'm overlooking None of these changes has far-reaching implications. - The user manual, section 7.7.2.2, is updated to describe the new type family instances.
* | Make {-# UNPACK #-} work for type/data family invocationsSimon Peyton Jones2012-12-232-5/+8
|/ | | | | | | | | | | | | | | | | | | | | This fixes most of Trac #3990. Consider data family D a data instance D Double = CD Int Int data T = T {-# UNPACK #-} !(D Double) Then we want the (D Double unpacked). To do this we need to construct a suitable coercion, and it's much safer to record that coercion in the interface file, lest the in-scope instances differ somehow. That in turn means elaborating the HsBang type to include a coercion. To do that I moved HsBang from BasicTypes to DataCon, which caused quite a few minor knock-on changes. Interface-file format has changed! Still to do: need to do knot-tying to allow instances to take effect within the same module.
* Remove getModuleDs; we now just use getModuleIan Lynagh2012-11-062-4/+5
|
* Refactor the way dump flags are handledIan Lynagh2012-10-181-2/+2
| | | | | | | | | | | | | We were being inconsistent about how we tested whether dump flags were enabled; in particular, sometimes we also checked the verbosity, and sometimes we didn't. This lead to oddities such as "ghc -v4" printing an "Asm code" section which didn't contain any code, and "-v4" enabled some parts of "-ddump-deriv" but not others. Now all the tests use dopt, which also takes the verbosity into account as appropriate.
* Some alpha renamingIan Lynagh2012-10-162-3/+3
| | | | | Mostly d -> g (matching DynFlag -> GeneralFlag). Also renamed if* to when*, matching the Haskell if/when names
* Rename DynFlag to GeneralFlagIan Lynagh2012-10-161-1/+1
| | | | | This avoids confusion due to [DynFlag] and DynFlags being completely different types.
* Move tARGET_* out of HaskellConstantsIan Lynagh2012-09-173-7/+12
|
* Fix dfun unfolding of PA instances generated by the vectoriserManuel M T Chakravarty2012-07-281-2/+4
|
* Fix PA dfun construction with silent superclass argsManuel M T Chakravarty2012-06-272-11/+2
|
* Add silent superclass parameters to the vectoriserManuel M T Chakravarty2012-06-274-35/+85
|
* Add silent superclass parameters (again)Simon Peyton Jones2012-06-271-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Silent superclass parameters solve the problem that the superclasses of a dicionary construction can easily turn out to be (wrongly) bottom. The problem and solution are described in Note [Silent superclass arguments] in TcInstDcls I first implemented this fix (with Dimitrios) in Dec 2010, but removed it again in Jun 2011 becuase we thought it wasn't necessary any more. (The reason we thought it wasn't necessary is that we'd stopped generating derived superclass constraints for *wanteds*. But we were wrong; that didn't solve the superclass-loop problem.) So we have to re-implement it. It's not hard. Main features: * The IdDetails for a DFunId says how many silent arguments it has * A DFunUnfolding describes which dictionary args are just parameters (DFunLamArg) and which are a function to apply to the parameters (DFunPolyArg). This adds the DFunArg type to CoreSyn * Consequential changes to IfaceSyn. (Binary hi file format changes slightly.) * TcInstDcls changes to generate the right dfuns * CoreSubst.exprIsConApp_maybe handles the new DFunUnfolding The thing taht is *not* done yet is to alter the vectoriser to pass the relevant extra argument when building a PA dictionary.
* Make -dtrace-level a dynamic flagIan Lynagh2012-06-181-5/+3
|
* Pass DynFlags down to showSDocIan Lynagh2012-06-129-47/+84
|
* Pass DynFlags down to showPprIan Lynagh2012-06-122-5/+9
|
* Remove the Show Var instanceIan Lynagh2012-06-121-2/+2
|
* Change how macros like ASSERT are definedIan Lynagh2012-06-052-0/+2
| | | | | By using Haskell's debugIsOn rather than CPP's "#ifdef DEBUG", we don't need to kludge things to keep the warning checker happy etc.
* Remove more uses of stdout and stderrIan Lynagh2012-05-292-9/+11
|
* Fix #6080 & house keeping in Vectorise.ExpManuel M T Chakravarty2012-05-082-465/+338
|
* removed superfluous flag for vectScalarFunGabriele Keller2012-04-252-24/+13
|
* Replaced tabsGabriele Keller2012-04-251-14/+14
|
* Vectorisation AvoidanceGabriele Keller2012-04-242-183/+328
| | | | Switched off by default. Use -favoid-vect to activate
* Partial VectoriasationGabriele Keller2012-04-243-26/+354
|
* Fixed typo (wrong max constant) in Initiialise.hsGabriele Keller2012-04-241-1/+1
|
* Add newline to the end of fileJose Pedro Magalhaes2012-04-192-2/+4
|
* Merge remote-tracking branch 'origin/master' into type-natsIavor S. Diatchki2012-03-132-0/+2
|\ | | | | | | | | | | | | | | | | | | | | | | | | Conflicts: compiler/coreSyn/CoreLint.lhs compiler/deSugar/DsBinds.lhs compiler/hsSyn/HsTypes.lhs compiler/iface/IfaceType.lhs compiler/rename/RnHsSyn.lhs compiler/rename/RnTypes.lhs compiler/stgSyn/StgLint.lhs compiler/typecheck/TcHsType.lhs compiler/utils/ListSetOps.lhs
| * Remove support for CTYPE pragmas on type synonymsIan Lynagh2012-02-221-1/+1
| | | | | | | | | | | | It's not clear whether it's desirable or not, and it turns out that the way we use coercions in GHC means we tend to lose information about type synonyms.
| * Implement the CTYPE pragma; part of the CApiFFI extensionIan Lynagh2012-02-163-1/+3
| | | | | | | | | | | | | | For now, the syntax is type {-# CTYPE "some C type" #-} Foo = ... newtype {-# CTYPE "some C type" #-} Foo = ... data {-# CTYPE "some C type" #-} Foo = ...
* | Merge remote-tracking branch 'origin/master' into type-natsIavor S. Diatchki2012-01-243-12/+35
|\ \ | |/ | | | | | | Conflicts: compiler/typecheck/TcEvidence.lhs
| * Fix vectorisation of classesManuel M T Chakravarty2012-01-163-12/+35
| | | | | | | | | | | | - Make sure that we have no implicit names in ifaces - Any vectorisation info makes a module an orphan module - Allow 'Show' in vectorised code without vectorising it for the moment
* | Mainly, rename LiteralTy to LitTySimon Peyton Jones2012-01-133-7/+7
| |
* | Merge remote-tracking branch 'origin/master' into type-natsIavor S. Diatchki2012-01-079-96/+93
|\ \ | |/
| * Major refactoring of CoAxiomsSimon Peyton Jones2012-01-039-96/+93
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch should have no user-visible effect. It implements a significant internal refactoring of the way that FC axioms are handled. The ultimate goal is to put us in a position to implement "pattern-matching axioms". But the changes here are only does refactoring; there is no change in functionality. Specifically: * We now treat data/type family instance declarations very, very similarly to types class instance declarations: - Renamed InstEnv.Instance as InstEnv.ClsInst, for symmetry with FamInstEnv.FamInst. This change does affect the GHC API, but for the better I think. - Previously, each family type/data instance declaration gave rise to a *TyCon*; typechecking a type/data instance decl produced that TyCon. Now, each type/data instance gives rise to a *FamInst*, by direct analogy with each class instance declaration giving rise to a ClsInst. - Just as each ClsInst contains its evidence, a DFunId, so each FamInst contains its evidence, a CoAxiom. See Note [FamInsts and CoAxioms] in FamInstEnv. The CoAxiom is a System-FC thing, and can relate any two types, whereas the FamInst relates directly to the Haskell source language construct, and always has a function (F tys) on the LHS. - Just as a DFunId has its own declaration in an interface file, so now do CoAxioms (see IfaceSyn.IfaceAxiom). These changes give rise to almost all the refactoring. * We used to have a hack whereby a type family instance produced a dummy type synonym, thus type instance F Int = Bool -> Bool translated to axiom FInt :: F Int ~ R:FInt type R:FInt = Bool -> Bool This was always a hack, and now it's gone. Instead the type instance declaration produces a FamInst, whose axiom has kind axiom FInt :: F Int ~ Bool -> Bool just as you'd expect. * Newtypes are done just as before; they generate a CoAxiom. These CoAxioms are "implicit" (do not generate an IfaceAxiom declaration), unlike the ones coming from family instance declarations. See Note [Implicit axioms] in TyCon On the whole the code gets significantly nicer. There were consequential tidy-ups in the vectoriser, but I think I got them right.
* | Merge branch 'master' into type-natsIavor S. Diatchki2011-12-182-7/+35
|\ \ | |/
| * Fix scalar vectorisation of superclasses and recursive dfunsManuel M T Chakravarty2011-12-182-7/+35
| |
* | Extend GHC's type with a representation for type level literals.Iavor S. Diatchki2011-12-183-0/+3
|/ | | | | Currently, we support only numeric literals but---hopefully---these modifications should make it fairly easy to add other ones, if necessary.
* Be more careful when deciding which functions are scalarManuel M T Chakravarty2011-12-143-12/+31
| | | | Although scalar functions can use any scalar data type, their arguments and functions may only involve primitive types at the moment.
* Fix -ddump-tc-trace for recursively defined type constructorsManuel M T Chakravarty2011-12-142-14/+18
|
* Revert "vectoriser: workaround bug in classiftTyCons"Manuel M T Chakravarty2011-12-141-9/+1
| | | | This reverts commit acbb3dba4490d53762b5aecfb9a45049dea15c79.
* vectoriser: workaround bug in classiftTyConsBen Lippmeier2011-12-121-1/+9
|
* Move vectorisation of (->) & [::] into the libraryManuel M T Chakravarty2011-11-276-46/+45
| | | | | - (->), [::], & PArray are now vectorised via pragmas (and related clean up) - Repeatedly vectorising a variable or type constructor now raises an error
* Fix newtype wrapper for 'PData[s] (Wrap a)' and fix VECTORISE type and ↵Manuel M T Chakravarty2011-11-256-59/+141
| | | | | | | | instance pragmas * Correct usage of new type wrappers from MkId * 'VECTORISE [SCALAR] type T = S' didn't work correctly across module boundaries * Clean up 'VECTORISE SCALAR instance'
* Fix and clean up 'PData' and 'Wrap' usage of the vectoriserManuel M T Chakravarty2011-11-238-572/+213
|