Apoorv Ingle pushed to branch wip/ani/ctorig-stuff at Glasgow Haskell Compiler / GHC

Commits:

4 changed files:

Changes:

  • compiler/GHC/Tc/Errors.hs
    ... ... @@ -24,6 +24,10 @@ import GHC.Driver.Config.Diagnostic
    24 24
     
    
    25 25
     import GHC.Rename.Unbound
    
    26 26
     
    
    27
    +import Language.Haskell.Syntax (DotFieldOcc (..))
    
    28
    +import Language.Haskell.Syntax.Basic (FieldLabelString (..))
    
    29
    +import GHC.Hs.Expr (SrcCodeOrigin (..), HsExpr (..))
    
    30
    +
    
    27 31
     import GHC.Tc.Types
    
    28 32
     import GHC.Tc.Utils.Monad
    
    29 33
     import GHC.Tc.Errors.Types
    
    ... ... @@ -2349,7 +2353,7 @@ mk_dict_err ctxt (item, (matches, pot_unifiers, unsafe_overlapped))
    2349 2353
           isNothing (lookupLocalRdrOcc lcl_env occ_name)
    
    2350 2354
     
    
    2351 2355
         record_field = case orig of
    
    2352
    -      GetFieldOrigin name -> Just (mkVarOccFS name)
    
    2356
    +      ExpansionOrigin (OrigExpr (HsGetField _ _ (L _ name))) -> Just (mkVarOccFS (field_label $ unLoc $ dfoLabel name))
    
    2353 2357
           _                   -> Nothing
    
    2354 2358
     
    
    2355 2359
     {- Note [Report candidate instances]
    

  • compiler/GHC/Tc/Types/Origin.hs
    ... ... @@ -788,7 +788,8 @@ lexprCtOrigin (L _ e) = exprCtOrigin e
    788 788
     
    
    789 789
     exprCtOrigin :: HsExpr GhcRn -> CtOrigin
    
    790 790
     exprCtOrigin (HsVar _ (L _ (WithUserRdr _ name))) = OccurrenceOf name
    
    791
    -exprCtOrigin (HsGetField _ _ (L _ f)) = GetFieldOrigin (field_label $ unLoc $ dfoLabel f)
    
    791
    +exprCtOrigin e@(HsGetField _ _ (L _ _)) = ExpansionOrigin (OrigExpr e)
    
    792
    +                                        -- GetFieldOrigin (field_label $ unLoc $ dfoLabel f)
    
    792 793
     exprCtOrigin (HsOverLabel _ l)  = OverLabelOrigin l
    
    793 794
     exprCtOrigin (ExplicitList {})    = ListOrigin
    
    794 795
     exprCtOrigin (HsIPVar _ ip)       = IPOccOrigin ip
    
    ... ... @@ -1081,6 +1082,7 @@ pprCtO (ImpedanceMatching {}) = text "combining required constraints"
    1081 1082
     pprCtO (NonLinearPatternOrigin _ pat) = hsep [text "a non-linear pattern" <+> quotes (ppr pat)]
    
    1082 1083
     pprCtO (ExpansionOrigin (OrigPat p)) = hsep [text "a pattern" <+> quotes (ppr p)]
    
    1083 1084
     pprCtO (ExpansionOrigin (OrigStmt{})) = text "a do statement"
    
    1085
    +pprCtO (ExpansionOrigin (OrigExpr (HsGetField _ _ (L _ f)))) = hsep [text "selecting the field", quotes (ppr f)]
    
    1084 1086
     pprCtO (ExpansionOrigin (OrigExpr e)) = text "an expression" <+> ppr e
    
    1085 1087
     pprCtO (ExpectedFunTySyntaxOp{}) = text "a rebindable syntax operator"
    
    1086 1088
     pprCtO (ExpectedFunTyViewPat{}) = text "a view pattern"
    

  • compiler/GHC/Tc/Utils/Unify.hs
    ... ... @@ -174,7 +174,7 @@ matchActualFunTy herald mb_thing err_info fun_ty
    174 174
     
    
    175 175
         go (FunTy { ft_af = af, ft_mult = w, ft_arg = arg_ty, ft_res = res_ty })
    
    176 176
           = assert (isVisibleFunArg af) $
    
    177
    -      do { hasFixedRuntimeRep_syntactic (FRRExpectedFunTy herald 1) arg_ty
    
    177
    +      do { hasFixedRuntimeRep_syntactic (FRRExpectedFunTy (updatePositionCtOrigin 1 herald) 1) arg_ty
    
    178 178
              ; return (idHsWrapper, Scaled w arg_ty, res_ty) }
    
    179 179
     
    
    180 180
         go ty@(TyVarTy tv)
    
    ... ... @@ -852,7 +852,7 @@ matchExpectedFunTys herald ctx arity (Check top_ty) thing_inside
    852 852
                                        , ft_arg = arg_ty, ft_res = res_ty })
    
    853 853
           = assert (isVisibleFunArg af) $
    
    854 854
             do { let arg_pos = arity - n_req + 1   -- 1 for the first argument etc
    
    855
    -           ; (arg_co, arg_ty) <- hasFixedRuntimeRep (FRRExpectedFunTy herald arg_pos) arg_ty
    
    855
    +           ; (arg_co, arg_ty) <- hasFixedRuntimeRep (FRRExpectedFunTy (updatePositionCtOrigin arg_pos herald) arg_pos) arg_ty
    
    856 856
                ; (wrap_res, result) <- check (n_req - 1)
    
    857 857
                                              (mkCheckExpFunPatTy (Scaled mult arg_ty) : rev_pat_tys)
    
    858 858
                                              res_ty
    

  • compiler/hie.yaml
    1
    +# This is a IDE configuration file which tells IDEs such as `ghcide` how
    
    2
    +# to set up a GHC API session for this project.
    
    3
    +#
    
    4
    +# To use it in windows systems replace the config with
    
    5
    +# cradle: {bios: {program: "./hadrian/hie-bios.bat"}}
    
    6
    +#
    
    7
    +# The format is documented here - https://github.com/mpickering/hie-bios
    
    8
    +cradle: {bios: {program: "./hadrian/hie-bios",
    
    9
    +		with-ghc: "~/.ghcup/bin/ghc"}}