diff options
| author | Alan Zimmerman <alan.zimm@gmail.com> | 2016-11-03 14:08:10 +0200 | 
|---|---|---|
| committer | Alan Zimmerman <alan.zimm@gmail.com> | 2016-12-07 21:14:28 +0200 | 
| commit | 1dcefaddc52d968b20bb6107d620e1e0c6839970 (patch) | |
| tree | 5f6600b63d773b6d8be00fd1bb09a39d58e494c9 /haddock-api/src/Haddock/Interface | |
| parent | 2bd3429c40419100478545db6a8b2080786ca26d (diff) | |
Match changes in GHC wip/T3384 branch
Diffstat (limited to 'haddock-api/src/Haddock/Interface')
| -rw-r--r-- | haddock-api/src/Haddock/Interface/Create.hs | 10 | ||||
| -rw-r--r-- | haddock-api/src/Haddock/Interface/Rename.hs | 4 | ||||
| -rw-r--r-- | haddock-api/src/Haddock/Interface/Specialize.hs | 16 | 
3 files changed, 15 insertions, 15 deletions
| diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index 2cdc6f8b..4e1a9b3a 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -48,7 +48,7 @@ import Bag  import RdrName  import TcRnTypes  import FastString (concatFS) -import BasicTypes ( StringLiteral(..) ) +import BasicTypes ( StringLiteral(..), SourceText(..) )  import qualified Outputable as O  import HsDecls ( gadtDeclDetails,getConDetails ) @@ -164,7 +164,7 @@ mkAliasMap dflags mRenamedSource =      Just (_,impDecls,_,_) ->        M.fromList $        mapMaybe (\(SrcLoc.L _ impDecl) -> do -        alias <- ideclAs impDecl +        SrcLoc.L _ alias <- ideclAs impDecl          return $            (lookupModuleDyn dflags               (fmap Module.fsToUnitId $ @@ -569,7 +569,7 @@ mkExportItems                    L loc (TyClD cl@ClassDecl{}) -> do                      mdef <- liftGhcToErrMsgGhc $ minimalDef t -                    let sig = maybeToList $ fmap (noLoc . MinimalSig mempty . noLoc . fmap noLoc) mdef +                    let sig = maybeToList $ fmap (noLoc . MinimalSig NoSourceText . noLoc . fmap noLoc) mdef                      return [ mkExportDecl t                        (L loc $ TyClD cl { tcdSigs = sig ++ tcdSigs cl }) docs_ ] @@ -769,7 +769,7 @@ fullModuleContents dflags warnings gre (docMap, argMap, subMap, declMap, instMap          expInst decl l name      mkExportItem (L l (TyClD cl@ClassDecl{ tcdLName = L _ name, tcdSigs = sigs })) = do        mdef <- liftGhcToErrMsgGhc $ minimalDef name -      let sig = maybeToList $ fmap (noLoc . MinimalSig mempty . noLoc . fmap noLoc) mdef +      let sig = maybeToList $ fmap (noLoc . MinimalSig NoSourceText . noLoc . fmap noLoc) mdef        expDecl (L l (TyClD cl { tcdSigs = sig ++ sigs })) l name      mkExportItem decl@(L l d)        | name:_ <- getMainDeclBinder d = expDecl decl l name @@ -839,7 +839,7 @@ extractRecSel nm mdl t tvs (L _ con : rest) =    data_ty      -- | ResTyGADT _ ty <- con_res con = ty      | ConDeclGADT{} <- con = hsib_body $ con_type con -    | otherwise = foldl' (\x y -> noLoc (HsAppTy x y)) (noLoc (HsTyVar (noLoc t))) tvs +    | otherwise = foldl' (\x y -> noLoc (HsAppTy x y)) (noLoc (HsTyVar NotPromoted (noLoc t))) tvs  -- | Keep export items with docs.  pruneExportItems :: [ExportItem Name] -> [ExportItem Name] diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs index fa85ba64..40a10675 100644 --- a/haddock-api/src/Haddock/Interface/Rename.hs +++ b/haddock-api/src/Haddock/Interface/Rename.hs @@ -219,7 +219,7 @@ renameType t = case t of      ltype'    <- renameLType ltype      return (HsQualTy { hst_ctxt = lcontext', hst_body = ltype' }) -  HsTyVar (L l n) -> return . HsTyVar . L l =<< rename n +  HsTyVar ip (L l n) -> return . HsTyVar ip . L l =<< rename n    HsBangTy b ltype -> return . HsBangTy b =<< renameLType ltype    HsAppTy a b -> do @@ -262,7 +262,7 @@ renameType t = case t of    HsRecTy a               -> HsRecTy <$> mapM renameConDeclFieldField a    HsCoreTy a              -> pure (HsCoreTy a) -  HsExplicitListTy  a b   -> HsExplicitListTy  a <$> mapM renameLType b +  HsExplicitListTy i a b  -> HsExplicitListTy i a <$> mapM renameLType b    HsExplicitTupleTy a b   -> HsExplicitTupleTy a <$> mapM renameLType b    HsSpliceTy _ _          -> error "renameType: HsSpliceTy"    HsWildCardTy a          -> HsWildCardTy <$> renameWildCardInfo a diff --git a/haddock-api/src/Haddock/Interface/Specialize.hs b/haddock-api/src/Haddock/Interface/Specialize.hs index 3e0df4e1..28bbf305 100644 --- a/haddock-api/src/Haddock/Interface/Specialize.hs +++ b/haddock-api/src/Haddock/Interface/Specialize.hs @@ -36,7 +36,7 @@ specialize :: (Eq name, Typeable name)  specialize name details =      everywhere $ mkT step    where -    step (HsTyVar (L _ name')) | name == name' = details +    step (HsTyVar _ (L _ name')) | name == name' = details      step typ = typ @@ -123,7 +123,7 @@ sugar =  sugarLists :: NamedThing name => HsType name -> HsType name -sugarLists (HsAppTy (L _ (HsTyVar (L _ name))) ltyp) +sugarLists (HsAppTy (L _ (HsTyVar _ (L _ name))) ltyp)      | isBuiltInSyntax name' && strName == "[]" = HsListTy ltyp    where      name' = getName name @@ -137,7 +137,7 @@ sugarTuples typ =    where      aux apps (HsAppTy (L _ ftyp) atyp) = aux (atyp:apps) ftyp      aux apps (HsParTy (L _ typ')) = aux apps typ' -    aux apps (HsTyVar (L _ name)) +    aux apps (HsTyVar _ (L _ name))          | isBuiltInSyntax name' && suitable = HsTupleTy HsBoxedTuple apps        where          name' = getName name @@ -149,7 +149,7 @@ sugarTuples typ =  sugarOperators :: NamedThing name => HsType name -> HsType name -sugarOperators (HsAppTy (L _ (HsAppTy (L _ (HsTyVar (L l name))) la)) lb) +sugarOperators (HsAppTy (L _ (HsAppTy (L _ (HsTyVar _ (L l name))) la)) lb)      | isSymOcc $ getOccName name' = mkHsOpTy la (L l name) lb      | isBuiltInSyntax name' && getOccString name == "(->)" = HsFunTy la lb    where @@ -224,7 +224,7 @@ freeVariables =      query term ctx = case cast term :: Maybe (HsType name) of          Just (HsForAllTy bndrs _) ->              (Set.empty, Set.union ctx (bndrsNames bndrs)) -        Just (HsTyVar (L _ name)) +        Just (HsTyVar _ (L _ name))              | getName name `Set.member` ctx -> (Set.empty, ctx)              | otherwise -> (Set.singleton $ getNameRep name, ctx)          _ -> (Set.empty, ctx) @@ -267,7 +267,7 @@ renameType (HsQualTy lctxt lt) =    HsQualTy          <$> located renameContext lctxt          <*> renameLType lt -renameType (HsTyVar name) = HsTyVar <$> located renameName name +renameType (HsTyVar ip name) = HsTyVar ip <$> located renameName name  renameType (HsAppTy lf la) = HsAppTy <$> renameLType lf <*> renameLType la  renameType (HsFunTy la lr) = HsFunTy <$> renameLType la <*> renameLType lr  renameType (HsListTy lt) = HsListTy <$> renameLType lt @@ -285,8 +285,8 @@ renameType (HsDocTy lt doc) = HsDocTy <$> renameLType lt <*> pure doc  renameType (HsBangTy bang lt) = HsBangTy bang <$> renameLType lt  renameType t@(HsRecTy _) = pure t  renameType t@(HsCoreTy _) = pure t -renameType (HsExplicitListTy ph ltys) = -    HsExplicitListTy ph <$> renameLTypes ltys +renameType (HsExplicitListTy ip ph ltys) = +    HsExplicitListTy ip ph <$> renameLTypes ltys  renameType (HsExplicitTupleTy phs ltys) =      HsExplicitTupleTy phs <$> renameLTypes ltys  renameType t@(HsTyLit _) = pure t | 
