Skip to content
  • Simon Peyton Jones's avatar
    Type vs Constraint: finally nailed · 778c6adc
    Simon Peyton Jones authored and Simon Peyton Jones's avatar Simon Peyton Jones committed
    This big patch addresses the rats-nest of issues that have plagued
    us for years, about the relationship between Type and Constraint.
    See #11715/#21623.
    
    The main payload of the patch is:
    * To introduce CONSTRAINT :: RuntimeRep -> Type
    * To make TYPE and CONSTRAINT distinct throughout the compiler
    
    Two overview Notes in GHC.Builtin.Types.Prim
    
    * Note [TYPE and CONSTRAINT]
    
    * Note [Type and Constraint are not apart]
      This is the main complication.
    
    The specifics
    
    * New primitive types (GHC.Builtin.Types.Prim)
      - CONSTRAINT
      - ctArrowTyCon (=>)
      - tcArrowTyCon (-=>)
      - ccArrowTyCon (==>)
      - funTyCon     FUN     -- Not new
      See Note [Function type constructors and FunTy]
      and Note [TYPE and CONSTRAINT]
    
    * GHC.Builtin.Types:
      - New type Constraint = CONSTRAINT LiftedRep
      - I also stopped nonEmptyTyCon being built-in; it only needs to be wired-in
    
    * Exploit the fact that Type and Constraint are distinct throughout GHC
      - Get rid of tcView in favour of coreView.
      - Many tcXX functions become XX functions.
        e.g. tcGetCastedTyVar --> getCastedTyVar
    
    * Kill off Note [ForAllTy and typechecker equality], in (old)
      GHC.Tc.Solver.Canonical.  It said that typechecker-equality should ignore
      the specified/inferred distinction when comparein two ForAllTys.  But
      that wsa only weakly supported and (worse) implies that we need a separate
      typechecker equality, different from core equality. No no no.
    
    * GHC.Core.TyCon: kill off FunTyCon in data TyCon.  There was no need for it,
      and anyway now we have four of them!
    
    * GHC.Core.TyCo.Rep: add two FunTyFlags to FunCo
      See Note [FunCo] in that module.
    
    * GHC.Core.Type.  Lots and lots of changes driven by adding CONSTRAINT.
      The key new function is sORTKind_maybe; most other changes are built
      on top of that.
    
      See also `funTyConAppTy_maybe` and `tyConAppFun_maybe`.
    
    * Fix a longstanding bug in GHC.Core.Type.typeKind, and Core Lint, in
      kinding ForAllTys.  See new tules (FORALL1) and (FORALL2) in GHC.Core.Type.
      (The bug was that before (forall (cv::t1 ~# t2). blah), where
      blah::TYPE IntRep, would get kind (TYPE IntRep), but it should be
      (TYPE LiftedRep).  See Note [Kinding rules for types] in GHC.Core.Type.
    
    * GHC.Core.TyCo.Compare is a new module in which we do eqType and cmpType.
      Of course, no tcEqType any more.
    
    * GHC.Core.TyCo.FVs. I moved some free-var-like function into this module:
      tyConsOfType, visVarsOfType, and occCheckExpand.  Refactoring only.
    
    * GHC.Builtin.Types.  Compiletely re-engineer boxingDataCon_maybe to
      have one for each /RuntimeRep/, rather than one for each /Type/.
      This dramatically widens the range of types we can auto-box.
      See Note [Boxing constructors] in GHC.Builtin.Types
      The boxing types themselves are declared in library ghc-prim:GHC.Types.
    
      GHC.Core.Make.  Re-engineer the treatment of "big" tuples (mkBigCoreVarTup
      etc) GHC.Core.Make, so that it auto-boxes unboxed values and (crucially)
      types of kind Constraint. That allows the desugaring for arrows to work;
      it gathers up free variables (including dictionaries) into tuples.
      See  Note [Big tuples] in GHC.Core.Make.
    
      There is still work to do here: #22336. But things are better than
      before.
    
    * GHC.Core.Make.  We need two absent-error Ids, aBSENT_ERROR_ID for types of
      kind Type, and aBSENT_CONSTRAINT_ERROR_ID for vaues of kind Constraint.
      Ditto noInlineId vs noInlieConstraintId in GHC.Types.Id.Make;
      see Note [inlineId magic].
    
    * GHC.Core.TyCo.Rep. Completely refactor the NthCo coercion.  It is now called
      SelCo, and its fields are much more descriptive than the single Int we used to
      have.  A great improvement.  See Note [SelCo] in GHC.Core.TyCo.Rep.
    
    * GHC.Core.RoughMap.roughMatchTyConName.  Collapse TYPE and CONSTRAINT to
      a single TyCon, so that the rough-map does not distinguish them.
    
    * GHC.Core.DataCon
      - Mainly just improve documentation
    
    * Some significant renamings:
      GHC.Core.Multiplicity: Many -->  ManyTy (easier to grep for)
                             One  -->  OneTy
      GHC.Core.TyCo.Rep TyCoBinder      -->   GHC.Core.Var.PiTyBinder
      GHC.Core.Var      TyCoVarBinder   -->   ForAllTyBinder
                        AnonArgFlag     -->   FunTyFlag
                        ArgFlag         -->   ForAllTyFlag
      GHC.Core.TyCon    TyConTyCoBinder --> TyConPiTyBinder
      Many functions are renamed in consequence
      e.g. isinvisibleArgFlag becomes isInvisibleForAllTyFlag, etc
    
    * I refactored FunTyFlag (was AnonArgFlag) into a simple, flat data type
        data FunTyFlag
          = FTF_T_T           -- (->)  Type -> Type
          | FTF_T_C           -- (-=>) Type -> Constraint
          | FTF_C_T           -- (=>)  Constraint -> Type
          | FTF_C_C           -- (==>) Constraint -> Constraint
    
    * GHC.Tc.Errors.Ppr.  Some significant refactoring in the TypeEqMisMatch case
      of pprMismatchMsg.
    
    * I made the tyConUnique field of TyCon strict, because I
      saw code with lots of silly eval's.  That revealed that
      GHC.Settings.Constants.mAX_SUM_SIZE can only be 63, because
      we pack the sum tag into a 6-bit field.  (Lurking bug squashed.)
    
    Fixes
    * #21530
    
    Updates haddock submodule slightly.
    
    Performance changes
    ~~~~~~~~~~~~~~~~~~~
    I was worried that compile times would get worse, but after
    some careful profiling we are down to a geometric mean 0.1%
    increase in allocation (in perf/compiler).  That seems fine.
    
    There is a big runtime improvement in T10359
    
    Metric Decrease:
        LargeRecord
        MultiLayerModulesTH_OneShot
        T13386
        T13719
    Metric Increase:
        T8095
    778c6adc