summaryrefslogtreecommitdiff
path: root/compiler/rename/RnSource.lhs
Commit message (Collapse)AuthorAgeFilesLines
* `M-x delete-trailing-whitespace` & `M-x untabify`Herbert Valerio Riedel2014-09-241-22/+22
|
* Export `Monoid(..)`/`Foldable(..)`/`Traversable(..)` from PreludeHerbert Valerio Riedel2014-09-211-0/+2
| | | | | | | | | | | | | | | This finally exposes also the methods of these 3 classes in the Prelude in order to allow to define basic class instances w/o needing imports. This almost completes the primary goal of #9586 NOTE: `fold`, `foldl'`, `foldr'`, and `toList` are not exposed yet, as they require upstream fixes for at least `containers` and `bytestring`, and are not required for defining basic instances. Reviewed By: ekmett, austin Differential Revision: https://phabricator.haskell.org/D236
* Add -fwarn-context-quantification (#4426)Krzysztof Gogolewski2014-09-181-4/+9
| | | | | | | | | | | | | | | | | | | | | | Summary: This warning (enabled by default) reports places where a context implicitly binds a type variable, for example type T a = {-forall m.-} Monad m => a -> m a Also update Haddock submodule. Test Plan: validate Reviewers: hvr, goldfire, simonpj, austin Reviewed By: austin Subscribers: simonmar, ezyang, carter Differential Revision: https://phabricator.haskell.org/D211 GHC Trac Issues: #4426
* PostTcType replaced with TypeAnnotAlan Zimmerman2014-09-061-1/+2
| | | | | | | | | | | | | | | | | | | | | Summary: This is a first step toward allowing generic traversals of the AST without 'landmines', by removing the `panic`s located throughout `placeHolderType`, `placeHolderKind` & co. See more on the discussion at https://www.mail-archive.com/ghc-devs@haskell.org/msg05564.html (This also makes a corresponding update to the `haddock` submodule.) Test Plan: `sh validate` and new tests pass. Reviewers: austin, simonpj, goldfire Reviewed By: austin, simonpj, goldfire Subscribers: edsko, Fuuzetsu, thomasw, holzensp, goldfire, simonmar, relrod, ezyang, carter Projects: #ghc Differential Revision: https://phabricator.haskell.org/D157
* Rename PackageId to PackageKey, distinguishing it from Cabal's PackageId.Edward Z. Yang2014-07-211-13/+13
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Previously, both Cabal and GHC defined the type PackageId, and we expected them to be roughly equivalent (but represented differently). This refactoring separates these two notions. A package ID is a user-visible identifier; it's the thing you write in a Cabal file, e.g. containers-0.9. The components of this ID are semantically meaningful, and decompose into a package name and a package vrsion. A package key is an opaque identifier used by GHC to generate linking symbols. Presently, it just consists of a package name and a package version, but pursuant to #9265 we are planning to extend it to record other information. Within a single executable, it uniquely identifies a package. It is *not* an InstalledPackageId, as the choice of a package key affects the ABI of a package (whereas an InstalledPackageId is computed after compilation.) Cabal computes a package key for the package and passes it to GHC using -package-name (now *extremely* misnamed). As an added bonus, we don't have to worry about shadowing anymore. As a follow on, we should introduce -current-package-key having the same role as -package-name, and deprecate the old flag. This commit is just renaming. The haddock submodule needed to be updated. Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: simonpj, simonmar, hvr, austin Subscribers: simonmar, relrod, carter Differential Revision: https://phabricator.haskell.org/D79 Conflicts: compiler/main/HscTypes.lhs compiler/main/Packages.lhs utils/haddock
* Entirely re-jig the handling of default type-family instances (fixes Trac #9063)Simon Peyton Jones2014-07-151-15/+30
| | | | | | | | | | | | | | | | | | | | | | | | | | | In looking at Trac #9063 I decided to re-design the default instances for associated type synonyms. Previously it was all jolly complicated, to support generality that no one wanted, and was arguably undesirable. Specifically * The default instance for an associated type can have only type variables on the LHS. (Not type patterns.) * There can be at most one default instances declaration for each associated type. To achieve this I had to do a surprisingly large amount of refactoring of HsSyn, specifically to parameterise HsDecls.TyFamEqn over the type of the LHS patterns. That change in HsDecls has a (trivial) knock-on effect in Haddock, so this commit does a submodule update too. The net result is good though. The code is simpler; the language specification is simpler. Happy days. Trac #9263 and #9264 are thereby fixed as well.
* Remove unused parameter in rnHsTyVarJan Stolarek2014-07-111-10/+9
|
* Overlapable pragmas for individual instances (#9242)Iavor S. Diatchki2014-06-291-2/+5
| | | | | | | | | | | | | | | | | | | | | | | | | | | Programmers may provide a pragma immediately after the `instance` keyword to control the overlap/incoherence behavior for individual instances. For example: instance {-# OVERLAP #-} C a where ... I chose this notation, rather than the other two outlined in the ticket for these reasons: 1. Having the pragma after the type looks odd, I think. 2. Having the pragma after there `where` does not work for stand-alone derived instances I have implemented 3 pragams: 1. NO_OVERLAP 2. OVERLAP 3. INCOHERENT These correspond directly to the internal modes currently supported by GHC. If a pragma is specified, it will be used no matter what flags are turned on. For example, putting `NO_OVERLAP` on an instance will mark it as non-overlapping, even if `OVERLAPPIN_INSTANCES` is turned on for the module.
* Add LANGUAGE pragmas to compiler/ source filesHerbert Valerio Riedel2014-05-151-0/+2
| | | | | | | | | | | | | | | | | | In some cases, the layout of the LANGUAGE/OPTIONS_GHC lines has been reorganized, while following the convention, to - place `{-# LANGUAGE #-}` pragmas at the top of the source file, before any `{-# OPTIONS_GHC #-}`-lines. - Moreover, if the list of language extensions fit into a single `{-# LANGUAGE ... -#}`-line (shorter than 80 characters), keep it on one line. Otherwise split into `{-# LANGUAGE ... -#}`-lines for each individual language extension. In both cases, try to keep the enumeration alphabetically ordered. (The latter layout is preferable as it's more diff-friendly) While at it, this also replaces obsolete `{-# OPTIONS ... #-}` pragma occurences by `{-# OPTIONS_GHC ... #-}` pragmas.
* Instead of tracking Origin in LHsBindsLR, track it in MatchGroupDr. ERDI Gergo2014-04-131-2/+2
|
* Squash some spelling issuesGabor Greif2014-01-261-1/+1
|
* Implement pattern synonymsDr. ERDI Gergo2014-01-201-21/+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>
* Refactor the way shadowing in handled in GHCiSimon Peyton Jones2014-01-031-0/+1
| | | | | | | | | | | | | | | | | | | | | | If you say ghci> import Foo( T ) ghci> data T = MkT ghci> data T = XXX then the second 'data T' should shadow the first. But the qualified Foo.T should still be available. We really weren't handling this correctly at all, resulting in Trac #8639 and #8628 among others This patch: * Add RdrName.extendGlobalRdrEnv, which does shadowing properly * Change HscTypes.icExtendGblRdrEnv (was badly-named icPlusGblRdrEnv) to use the new function * Change RnNames.extendGobalRdrEnvRn to use the new function * Move gresFrom Avails into RdrName * Better pprGlobalRdrEnv function in RdrName
* Suggest TemplateHaskell after encountering a naked top-level expressionPatrick Palka2013-12-051-0/+1
| | | | Helps fix #7396
* A raft of changes driven by Trac #8540Simon Peyton Jones2013-11-221-4/+7
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The root cause of #8450 is that the new Template Haskell story, with the renamer doing more of the work of Template Haskell, wasn't dealing correctly with the keepAlive problem. Consider g = ..blah... f = [| g |] Then f's RHS refers to g's name but not to g, so g was being discarded as dead code. Fixing this sucked me into a deep swamp of understanding how all the moving parts of hte new Template Haskell fit together, leading to a large collection of related changes and better documentation. Specifically: * Instead of putting the TH level of a binder in the LocalRdrEnv, there is now a separate field tcl_th_bndrs :: NameEnv (TopLevelFlag, ThLevel) in the TcLclEnv, which records for each binder a) whether it is syntactically a top-level binder or not b) its TH level This deals uniformly with top-level and non-top-level binders, which was previously dealt with via greviously-delicate meddling with Internal and External Names. Much better. * As a result I could remove the tct_level field of ATcId. * There are consequential changes in TcEnv too, which must also extend the level bindings. Again, more clarity. I renamed TcEnv.tcExtendTcTyThingEnv to tcExtendKindEnv2, since it's only used during kind inference, for (AThing kind) and APromotionErr; and that is relevant to whether we want to extend the tcl_th_bndrs field (no). * I de-crufted the code in RnEnv.extendGlobalRdrEnv, by getting rid of the qual_gre code which said "Seems like 5 times as much work as it deserves!". Instead, RdrName.pickGREs makes the Internal names shadow External ones. * I moved the checkThLocalName cross-stage test to finishHsVar; previously we weren't doing the test at all in the OpApp case! * Quite a few changes (shortening the code) in the cross-stage checking code in TcExpr and RnSplice, notably to move the keepAlive call to the renamer One leftover piece: * In TcEnv I removed tcExtendGhciEnv and refactored tcExtendGlobalTyVars; this is really related to the next commit, but it was too hard to disentangle.
* Tidy up the error messages we get from TH in stage1 (Trac #8312)Simon Peyton Jones2013-11-061-7/+0
| | | | | | Instead of panic-ing we now give a sensible message. There is quite a bit of refactoring here too, removing several #ifdef GHCI things
* Fix Trac #8485.Richard Eisenberg2013-10-291-15/+44
| | | | | | | | | | The problem was that the renamer treated role annotations by looking up the annotated type in the module being compiled. If this check succeeded, it was assumed that the annotated type was being compiled at the same time. But this assumption is false! In GHCi (and Template Haskell), sometimes compilation within one module can be staged. So, now there is a more intricate check for orphan role annotations. This also has the benefit of producing better error messages.
* Add full support for declaration splices.Geoffrey Mainland2013-10-041-1/+6
| | | | | Since declaration splices are now untyped, they can be used anywhere a declaration is valid, including in declaration brackets.
* Change role annotation syntax.Richard Eisenberg2013-09-171-15/+95
| | | | | | | | | This fixes bugs #8185, #8234, and #8246. The new syntax is explained in the comments to #8185, appears in the "Roles" subsection of the manual, and on the [wiki:Roles] wiki page. This change also removes the ability for a role annotation on type synonyms, as noted in #8234.
* Give language pragma suggestions without -XJoachim Breitner2013-09-141-1/+1
| | | | for easier copy'n'paste. This fixes: #3647
* Revise implementation of overlapping type family instances.Richard Eisenberg2013-06-211-10/+20
| | | | | | | | | | | | | | | | | | | This commit changes the syntax and story around overlapping type family instances. Before, we had "unbranched" instances and "branched" instances. Now, we have closed type families and open ones. The behavior of open families is completely unchanged. In particular, coincident overlap of open type family instances still works, despite emails to the contrary. A closed type family is declared like this: > type family F a where > F Int = Bool > F a = Char The equations are tried in order, from top to bottom, subject to certain constraints, as described in the user manual. It is not allowed to declare an instance of a closed family.
* Fix a TODO in the compilerIan Lynagh2013-02-261-1/+2
| | | | AnnProvenance now has Functor, Foldable, Traversable instances.
* Merge branch 'refs/heads/vect-avoid' into vect-avoid-mergeManuel M T Chakravarty2013-02-061-8/+4
|\ | | | | | | | | | | | | | | | | Conflicts: compiler/rename/RnSource.lhs compiler/simplCore/OccurAnal.lhs compiler/vectorise/Vectorise/Exp.hs NB: Merging instead of rebasing for a change. During rebase Git got confused due to the lack of the submodules in my quite old fork.
| * Rewrote vectorisation avoidance (based on the HS paper)Manuel M T Chakravarty2012-12-051-7/+3
| | | | | | | | | | | | | | * Vectorisation avoidance is now the default * Types and values from unvectorised modules are permitted in scalar code * Simplified the VECTORISE pragmas (see http://hackage.haskell.org/trac/ghc/wiki/DataParallel/VectPragma for the spec) * Vectorisation information is now included in the annotated Core AST
* | Remove unused argumentSimon Peyton Jones2013-01-251-11/+5
| |
* | Implement overlapping type family instances.Richard Eisenberg2012-12-211-101/+169
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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.
* | Whitespace only in rename/RnSource.lhsIan Lynagh2012-09-231-306/+297
|/
* Tidy up the treatment of signatures (incl fixity)Simon Peyton Jones2012-05-241-8/+14
| | | | | | This fixes Trac #6120. I've added comments to explain. Turns out there was another lurking bug, also fixed, and tested in (an extended version of) th/T2713.
* Fix scoping of kind variables in instance declarationsSimon Peyton Jones2012-05-221-16/+30
| | | | Fixes Trac #6118
* Refactor LHsTyVarBndrs to fix Trac #6081Simon Peyton Jones2012-05-111-46/+35
| | | | | | | | | | | | | | | This is really a small change, but it touches a lot of files quite significantly. The real goal is to put the implicitly-bound kind variables of a data/class decl in the right place, namely on the LHsTyVarBndrs type, which now looks like data LHsTyVarBndrs name = HsQTvs { hsq_kvs :: [Name] , hsq_tvs :: [LHsTyVarBndr name] } This little change made the type checker neater in a number of ways, but it was fiddly to push through the changes.
* Fix lookup of fixity signatures for type operators (#6027)Paolo Capriotti2012-04-261-2/+2
| | | | | Extend name lookup for fixity declaration to the TcClsName namespace for all reader names, instead of only those in DataName.
* Move free-var info from InstDecl to FamInstDeclSimon Peyton Jones2012-04-201-19/+25
|
* Do SCC on instance declarations (fixes Trac #5715)Simon Peyton Jones2012-04-201-16/+22
| | | | | | | | | | | | | | | | | | The trouble here is that given {-# LANGUAGE DataKinds, TypeFamilies #-} data instance Foo a = Bar (Bar a) we want to get a sensible message that we can't use the promoted 'Bar' constructor until after its definition; it's a staging error. Bud the staging mechanism that we use for vanilla data declarations don't work here. Solution is to perform strongly-connected component analysis on the instance declarations. But that in turn means that we need to track free-variable information on more HsSyn declarations, which is why so many files are touched. All the changes are boiler-platey except the ones in TcInstDcls.
* Allow kind-variable binders in type signaturesSimon Peyton Jones2012-04-131-5/+7
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | This is the last major addition to the kind-polymorphism story, by allowing (Trac #5938) type family F a -- F :: forall k. k -> * data T a -- T :: forall k. k -> * type instance F (T (a :: Maybe k)) = Char The new thing is the explicit 'k' in the type signature on 'a', which itself is inside a type pattern for F. Main changes are: * HsTypes.HsBSig now has a *pair* (kvs, tvs) of binders, the kind variables and the type variables * extractHsTyRdrTyVars returns a pair (kvs, tvs) and the function itself has moved from RdrHsSyn to RnTypes * Quite a bit of fiddling with TcHsType.tcHsPatSigType and tcPatSig which have become a bit simpler. I'm still not satisfied though. There's some consequential fiddling in TcRules too. * Removed the unused HsUtils.collectSigTysFromPats There's a consequential wibble to Haddock too
* Don't crash if there's a malformed instance!Simon Peyton Jones2012-03-301-3/+7
| | | | Fixes Trac #5951
* Make the 'extract' functions to find free type variablesSimon Peyton Jones2012-03-261-2/+7
| | | | | | | of an HsType return RdrNames rather than (Located RdrNames). This means less clutter, and the individual locations are a bit arbitrary if a name occurs more than once.
* Merge branch 'master' of http://darcs.haskell.org//ghcSimon Peyton Jones2012-03-241-2/+2
|\ | | | | | | | | Conflicts: compiler/main/HscStats.lhs
* | Refactor HsDecls.TyClDecl to extract the type HsTyDefn, which is theSimon Peyton Jones2012-03-221-102/+132
|/ | | | | RHS of a data type or type synonym declaration. This can be shared between type declarations and type *instance* declarations.
* Hurrah! This major commit adds support for scoped kind variables,Simon Peyton Jones2012-03-021-202/+153
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | which (finally) fills out the functionality of polymorphic kinds. It also fixes numerous bugs. Main changes are: Renaming stuff ~~~~~~~~~~~~~~ * New type in HsTypes: data HsBndrSig sig = HsBSig sig [Name] which is used for type signatures in patterns, and kind signatures in types. So when you say f (x :: [a]) = x ++ x or data T (f :: k -> *) (x :: *) = MkT (f x) the signatures in both cases are a HsBndrSig. * The [Name] in HsBndrSig records the variables bound by the pattern, that is 'a' in the first example, 'k' in the second, and nothing in the third. The renamer initialises the field. * As a result I was able to get rid of RnHsSyn.extractHsTyNames :: LHsType Name -> NameSet and its friends altogether. Deleted the entire module! This led to some knock-on refactoring; in particular the type renamer now returns the free variables just like the term renamer. Kind-checking types: mainly TcHsType ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ A major change is that instead of kind-checking types in two passes, we now do one. Under the old scheme, the first pass did kind-checking and (hackily) annotated the HsType with the inferred kinds; and the second pass desugared the HsType to a Type. But now that we have kind variables inside types, the first pass (TcHsType.tc_hs_type) can go straight to Type, and zonking will squeeze out any kind unification variables later. This is much nicer, but it was much more fiddly than I had expected. The nastiest corner is this: it's very important that tc_hs_type uses lazy constructors to build the returned type. See Note [Zonking inside the knot] in TcHsType. Type-checking type and class declarations: mainly TcTyClsDecls ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ I did tons of refactoring in TcTyClsDecls. Simpler and nicer now. Typechecking bindings: mainly TcBinds ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ I rejigged (yet again) the handling of type signatures in TcBinds. It's a bit simpler now. The main change is that tcTySigs goes right through to a TcSigInfo in one step; previously it was split into two, part here and part later. Unsafe coercions ~~~~~~~~~~~~~~~~ Usually equality coercions have exactly the same kind on both sides. But we do allow an *unsafe* coercion between Int# and Bool, say, used in case error Bool "flah" of { True -> 3#; False -> 0# } --> (error Bool "flah") |> unsafeCoerce Bool Int# So what is the instantiation of (~#) here? unsafeCoerce Bool Int# :: (~#) ??? Bool Int# I'm using OpenKind here for now, but it's un-satisfying that the lhs and rhs of the ~ don't have precisely the same kind. More minor ~~~~~~~~~~ * HsDecl.TySynonym has its free variables attached, which makes the cycle computation in TcTyDecls.mkSynEdges easier. * Fixed a nasty reversed-comparison bug in FamInstEnv: @@ -490,7 +490,7 @@ lookup_fam_inst_env' match_fun one_sided ie fam tys n_tys = length tys extra_tys = drop arity tys (match_tys, add_extra_tys) - | arity > n_tys = (take arity tys, \res_tys -> res_tys ++ extra_tys) + | arity < n_tys = (take arity tys, \res_tys -> res_tys ++ extra_tys) | otherwise = (tys, \res_tys -> res_tys)
* Implement "value" imports with the CAPIIan Lynagh2012-02-261-2/+2
| | | | | | This allows us to import values (i.e. non-functions) with the CAPI. This means we can access values even if (on some or all platforms) they are simple #defines.
* Remove support for CTYPE pragmas on type synonymsIan Lynagh2012-02-221-2/+2
| | | | | | 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-161-4/+8
| | | | | | | For now, the syntax is type {-# CTYPE "some C type" #-} Foo = ... newtype {-# CTYPE "some C type" #-} Foo = ... data {-# CTYPE "some C type" #-} Foo = ...
* Refactor HsDecls again, to put family instances in InstDeclSimon Peyton Jones2012-02-061-7/+16
| | | | | | | | | | | | | | | | | | | | This continues the clean up of the front end. Since they were first invented, type and data family *instance* decls have been in the TyClDecl data type, even though they always treated separately. This patch takes a step in the right direction * The InstDecl type now includes both class instances and type/data family instances * The hs_tyclds field of HsGroup now never has any family instance declarations in it However a family instance is still a TyClDecl. It should really be a separate type, but that's the next step. All this was provoked by fixing Trac #5792 in the HEAD. (I did a less invasive fix on the branch.)
* Remove getDOpts; use getDynFlags insteadIan Lynagh2012-01-191-1/+1
|
* Fix vectorisation of classesManuel M T Chakravarty2012-01-161-1/+1
| | | | | | - 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
* Implemnt Trac #5712: show method for infix GADT constructorsSimon Peyton Jones2011-12-231-16/+36
| | | | | This is a tiny feature improvement; see the ticket. I have updated the user manual too.
* Allow type signatures in instance decls (Trac #5676)Simon Peyton Jones2011-12-121-15/+23
| | | | | | | | | | | This new feature-ette, enable with -XInstanceSigs, lets you give a type signature in an instance declaration: instance Eq Int where (==) :: Int -> Int -> Bool (==) = ...blah... Scoped type variables work too.
* Fix newtype wrapper for 'PData[s] (Wrap a)' and fix VECTORISE type and ↵Manuel M T Chakravarty2011-11-251-3/+3
| | | | | | | | 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'
* Changes to the kind checkerJose Pedro Magalhaes2011-11-161-2/+1
| | | | | | | | | | | | | We now always check against an expected kind. When we really don't know what kind to expect, we match against a new meta kind variable. Also, we are more explicit about tuple sorts: HsUnboxedTuple -> Produced by the parser HsBoxedTuple -> Certainly a boxed tuple HsConstraintTuple -> Certainly a constraint tuple HsBoxedOrConstraintTuple -> Could be a boxed or a constraint tuple. Produced by the parser only, disappears after type checking
* Add dependencies on all .hs-boot TyCons in rnTyClDeclsJose Pedro Magalhaes2011-11-161-28/+69
|