Skip to content
This repository was archived by the owner on Aug 3, 2024. It is now read-only.

Commit 1d657cf

Browse files
alanzbgamari
authored andcommitted
Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled
(cherry picked from commit a7d1d8e)
1 parent 20098c8 commit 1d657cf

File tree

6 files changed

+20
-17
lines changed

6 files changed

+20
-17
lines changed

haddock-api/src/Haddock/Backends/Hoogle.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,7 @@ import Haddock.Utils hiding (out)
2727

2828
import GHC
2929
import GHC.Utils.Outputable as Outputable
30+
import GHC.Parser.Annotation (IsUnicodeSyntax(..))
3031

3132
import Data.Char
3233
import Data.List
@@ -245,7 +246,7 @@ ppCtor dflags dat subdocs con@ConDeclH98 {}
245246
[out dflags (map (extFieldOcc . unLoc) $ cd_fld_names r) `typeSig` [resType, cd_fld_type r]]
246247
| r <- map unLoc recs]
247248

248-
funs = foldr1 (\x y -> reL $ HsFunTy noExtField HsUnrestrictedArrow x y)
249+
funs = foldr1 (\x y -> reL $ HsFunTy noExtField (HsUnrestrictedArrow NormalSyntax) x y)
249250
apps = foldl1 (\x y -> reL $ HsAppTy noExtField x y)
250251

251252
typeSig nm flds = operator nm ++ " :: " ++ outHsType dflags (unL $ funs flds)

haddock-api/src/Haddock/Convert.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -52,6 +52,7 @@ import GHC.Utils.Outputable ( assertPanic )
5252
import GHC.Types.Var
5353
import GHC.Types.Var.Set
5454
import GHC.Types.SrcLoc
55+
import GHC.Parser.Annotation (IsUnicodeSyntax(..))
5556

5657
import Haddock.Types
5758
import Haddock.Interface.Specialize
@@ -769,9 +770,9 @@ noKindTyVars _ _ = emptyVarSet
769770

770771
synifyMult :: [TyVar] -> Mult -> HsArrow GhcRn
771772
synifyMult vs t = case t of
772-
One -> HsLinearArrow
773-
Many -> HsUnrestrictedArrow
774-
ty -> HsExplicitMult (synifyType WithinType vs ty)
773+
One -> HsLinearArrow NormalSyntax
774+
Many -> HsUnrestrictedArrow NormalSyntax
775+
ty -> HsExplicitMult NormalSyntax (synifyType WithinType vs ty)
775776

776777

777778

haddock-api/src/Haddock/GhcUtils.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,7 @@ import GHC.Types.Var.Env ( TyVarEnv, extendVarEnv, elemVarEnv, emptyVarEnv )
4242
import GHC.Core.TyCo.Rep ( Type(..) )
4343
import GHC.Core.Type ( isRuntimeRepVar )
4444
import GHC.Builtin.Types( liftedRepDataConTyCon )
45+
import GHC.Parser.Annotation (IsUnicodeSyntax(..))
4546

4647
import GHC.Data.StringBuffer ( StringBuffer )
4748
import qualified GHC.Data.StringBuffer as S
@@ -165,13 +166,13 @@ getGADTConType (ConDeclGADT { con_forall = L _ has_forall
165166
| otherwise
166167
= tau_ty
167168

168-
-- tau_ty :: LHsType DocNameI
169+
-- tau_ty :: LHsType DocNameI
169170
tau_ty = case args of
170171
RecCon flds -> mkFunTy (noLoc (HsRecTy noExtField (unLoc flds))) res_ty
171172
PrefixCon pos_args -> foldr mkFunTy res_ty (map hsScaledThing pos_args)
172173
InfixCon arg1 arg2 -> (hsScaledThing arg1) `mkFunTy` ((hsScaledThing arg2) `mkFunTy` res_ty)
173174

174-
mkFunTy a b = noLoc (HsFunTy noExtField HsUnrestrictedArrow a b)
175+
mkFunTy a b = noLoc (HsFunTy noExtField (HsUnrestrictedArrow NormalSyntax) a b)
175176

176177
getGADTConType (ConDeclH98 {}) = panic "getGADTConType"
177178
-- Should only be called on ConDeclGADT
@@ -227,7 +228,7 @@ getGADTConTypeG (ConDeclGADT { con_forall = L _ has_forall
227228
InfixCon arg1 arg2 -> (hsScaledThing arg1) `mkFunTy` ((hsScaledThing arg2) `mkFunTy` res_ty)
228229

229230
-- mkFunTy :: LHsType DocNameI -> LHsType DocNameI -> LHsType DocNameI
230-
mkFunTy a b = noLoc (HsFunTy noExtField HsUnrestrictedArrow a b)
231+
mkFunTy a b = noLoc (HsFunTy noExtField (HsUnrestrictedArrow NormalSyntax) a b)
231232

232233
getGADTConTypeG (ConDeclH98 {}) = panic "getGADTConTypeG"
233234
-- Should only be called on ConDeclGADT

haddock-api/src/Haddock/Interface/Create.hs

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -56,8 +56,7 @@ import GHC.Data.FastString ( unpackFS, bytesFS )
5656
import GHC.Types.Basic ( StringLiteral(..), SourceText(..), PromotionFlag(..) )
5757
import qualified GHC.Utils.Outputable as O
5858
import GHC.HsToCore.Docs hiding (mkMaps)
59-
60-
import GHC.Core.Multiplicity
59+
import GHC.Parser.Annotation (IsUnicodeSyntax(..))
6160

6261

6362
-- | Use a 'TypecheckedModule' to produce an 'Interface'.
@@ -958,8 +957,8 @@ extractPatternSyn nm t tvs cons =
958957
typ'' = noLoc (HsQualTy noExtField (noLoc []) typ')
959958
in PatSynSig noExtField [noLoc nm] (mkEmptyImplicitBndrs typ'')
960959

961-
longArrow :: (XFunTy name ~ NoExtField) => [LHsType name] -> LHsType name -> LHsType name
962-
longArrow inputs output = foldr (\x y -> noLoc (HsFunTy noExtField HsUnrestrictedArrow x y)) output inputs
960+
longArrow :: [LHsType GhcRn] -> LHsType GhcRn -> LHsType GhcRn
961+
longArrow inputs output = foldr (\x y -> noLoc (HsFunTy noExtField (HsUnrestrictedArrow NormalSyntax) x y)) output inputs
963962

964963
data_ty con
965964
| ConDeclGADT{} <- con = con_res_ty con
@@ -976,7 +975,7 @@ extractRecSel _ _ _ [] = error "extractRecSel: selector not found"
976975
extractRecSel nm t tvs (L _ con : rest) =
977976
case getConArgs con of
978977
RecCon (L _ fields) | ((l,L _ (ConDeclField _ _nn ty _)) : _) <- matching_fields fields ->
979-
L l (TypeSig noExtField [noLoc nm] (mkEmptySigWcType (noLoc (HsFunTy noExtField HsUnrestrictedArrow data_ty (getBangType ty)))))
978+
L l (TypeSig noExtField [noLoc nm] (mkEmptySigWcType (noLoc (HsFunTy noExtField (HsUnrestrictedArrow NormalSyntax) data_ty (getBangType ty)))))
980979
_ -> extractRecSel nm t tvs rest
981980
where
982981
matching_fields :: [LConDeclField GhcRn] -> [(SrcSpan, LConDeclField GhcRn)]

haddock-api/src/Haddock/Interface/Rename.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -223,9 +223,9 @@ renameMaybeInjectivityAnn :: Maybe (LInjectivityAnn GhcRn)
223223
renameMaybeInjectivityAnn = traverse renameInjectivityAnn
224224

225225
renameArrow :: HsArrow GhcRn -> RnM (HsArrow DocNameI)
226-
renameArrow HsUnrestrictedArrow = return HsUnrestrictedArrow
227-
renameArrow HsLinearArrow = return HsLinearArrow
228-
renameArrow (HsExplicitMult p) = HsExplicitMult <$> renameLType p
226+
renameArrow (HsUnrestrictedArrow u) = return (HsUnrestrictedArrow u)
227+
renameArrow (HsLinearArrow u) = return (HsLinearArrow u)
228+
renameArrow (HsExplicitMult u p) = HsExplicitMult u <$> renameLType p
229229

230230
renameType :: HsType GhcRn -> RnM (HsType DocNameI)
231231
renameType t = case t of

haddock-api/src/Haddock/Interface/Specialize.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ import GHC.Types.Name
1717
import GHC.Data.FastString
1818
import GHC.Builtin.Types.Prim ( funTyConName )
1919
import GHC.Builtin.Types ( listTyConName, unrestrictedFunTyConName )
20+
import GHC.Parser.Annotation (IsUnicodeSyntax(..))
2021

2122
import Control.Monad
2223
import Control.Monad.Trans.State
@@ -136,7 +137,7 @@ sugarTuples typ =
136137
sugarOperators :: NamedThing (IdP (GhcPass p)) => HsType (GhcPass p) -> HsType (GhcPass p)
137138
sugarOperators (HsAppTy _ (L _ (HsAppTy _ (L _ (HsTyVar _ _ (L l name))) la)) lb)
138139
| isSymOcc $ getOccName name' = mkHsOpTy la (L l name) lb
139-
| unrestrictedFunTyConName == name' = HsFunTy noExtField HsUnrestrictedArrow la lb
140+
| unrestrictedFunTyConName == name' = HsFunTy noExtField (HsUnrestrictedArrow NormalSyntax) la lb
140141
where
141142
name' = getName name
142143
sugarOperators typ = typ
@@ -282,7 +283,7 @@ renameType t@(HsTyLit _ _) = pure t
282283
renameType (HsWildCardTy wc) = pure (HsWildCardTy wc)
283284

284285
renameHsArrow :: HsArrow GhcRn -> Rename (IdP GhcRn) (HsArrow GhcRn)
285-
renameHsArrow (HsExplicitMult p) = HsExplicitMult <$> renameLType p
286+
renameHsArrow (HsExplicitMult u p) = HsExplicitMult u <$> renameLType p
286287
renameHsArrow mult = pure mult
287288

288289

0 commit comments

Comments
 (0)