[commit: haddock] 2.17.3.1-spanfix, alexbiehl-patch-1, ghc-8.0, ghc-8.0-facebook, ghc-head, ghc-head1, haddock-quick, headdock-library-1.4.5, ie_avails, issue-303, issue-475, master, pr-filter-maps, pr/cabal-desc, travis, v2.16, v2.17, v2.17.3, v2.18, wip-located-module-as, wip/D2418, wip/T11080-open-data-kinds, wip/T11258, wip/T11430, wip/T12105, wip/T12105-2, wip/T12942, wip/T13163, wip/T14529, wip/T3384, wip/embelleshed-rdr, wip/new-tree-one-param, wip/rae, wip/remove-frames, wip/remove-frames1, wip/revert-ttg-2017-11-20, wip/ttg-2017-10-13, wip/ttg-2017-10-31, wip/ttg-2017-11-06, wip/ttg2-2017-11-10, wip/ttg3-2017-11-12, wip/ttg4-constraints-2017-11-13, wip/ttg6-unrevert-2017-11-22: Refactor type renamer to rebinding and pure renaming phases. (3f404ba)
git at git.haskell.org
git at git.haskell.org
Tue Nov 28 11:34:49 UTC 2017
- Previous message: [commit: haddock] 2.17.3.1-spanfix, alexbiehl-patch-1, ghc-8.0, ghc-8.0-facebook, ghc-head, ghc-head1, haddock-quick, headdock-library-1.4.5, ie_avails, issue-303, issue-475, master, pr-filter-maps, pr/cabal-desc, travis, v2.16, v2.17, v2.17.3, v2.18, wip-located-module-as, wip/D2418, wip/T11080-open-data-kinds, wip/T11258, wip/T11430, wip/T12105, wip/T12105-2, wip/T12942, wip/T13163, wip/T14529, wip/T3384, wip/embelleshed-rdr, wip/new-tree-one-param, wip/rae, wip/remove-frames, wip/remove-frames1, wip/revert-ttg-2017-11-20, wip/ttg-2017-10-13, wip/ttg-2017-10-31, wip/ttg-2017-11-06, wip/ttg2-2017-11-10, wip/ttg3-2017-11-12, wip/ttg4-constraints-2017-11-13, wip/ttg6-unrevert-2017-11-22: Fix type renamer bug with incorrect names being generated. (08e592e)
- Next message: [commit: haddock] 2.17.3.1-spanfix, alexbiehl-patch-1, ghc-8.0, ghc-8.0-facebook, ghc-head, ghc-head1, haddock-quick, headdock-library-1.4.5, ie_avails, issue-303, issue-475, master, pr-filter-maps, pr/cabal-desc, travis, v2.16, v2.17, v2.17.3, v2.18, wip-located-module-as, wip/D2418, wip/T11080-open-data-kinds, wip/T11258, wip/T11430, wip/T12105, wip/T12105-2, wip/T12942, wip/T13163, wip/T14529, wip/T3384, wip/embelleshed-rdr, wip/new-tree-one-param, wip/rae, wip/remove-frames, wip/remove-frames1, wip/revert-ttg-2017-11-20, wip/ttg-2017-10-13, wip/ttg-2017-10-31, wip/ttg-2017-11-06, wip/ttg2-2017-11-10, wip/ttg3-2017-11-12, wip/ttg4-constraints-2017-11-13, wip/ttg6-unrevert-2017-11-22: Extend instances test case to also test multi-name type signatures. (dbe6f2c)
- Messages sorted by:
[ date ]
[ thread ]
[ subject ]
[ author ]
Repository : ssh://git@git.haskell.org/haddock
On branches: 2.17.3.1-spanfix,alexbiehl-patch-1,ghc-8.0,ghc-8.0-facebook,ghc-head,ghc-head1,haddock-quick,headdock-library-1.4.5,ie_avails,issue-303,issue-475,master,pr-filter-maps,pr/cabal-desc,travis,v2.16,v2.17,v2.17.3,v2.18,wip-located-module-as,wip/D2418,wip/T11080-open-data-kinds,wip/T11258,wip/T11430,wip/T12105,wip/T12105-2,wip/T12942,wip/T13163,wip/T14529,wip/T3384,wip/embelleshed-rdr,wip/new-tree-one-param,wip/rae,wip/remove-frames,wip/remove-frames1,wip/revert-ttg-2017-11-20,wip/ttg-2017-10-13,wip/ttg-2017-10-31,wip/ttg-2017-11-06,wip/ttg2-2017-11-10,wip/ttg3-2017-11-12,wip/ttg4-constraints-2017-11-13,wip/ttg6-unrevert-2017-11-22
Link : http://git.haskell.org/haddock.git/commitdiff/3f404ba3c1b36212ae7507874aefb1e8cc107dd8
>---------------------------------------------------------------
commit 3f404ba3c1b36212ae7507874aefb1e8cc107dd8
Author: Ćukasz Hanuszczak <lukasz.hanuszczak at gmail.com>
Date: Wed Jul 22 18:46:10 2015 +0200
Refactor type renamer to rebinding and pure renaming phases.
>---------------------------------------------------------------
3f404ba3c1b36212ae7507874aefb1e8cc107dd8
.../src/Haddock/Backends/Xhtml/Specialize.hs | 105 ++++++++++++---------
1 file changed, 60 insertions(+), 45 deletions(-)
diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Specialize.hs b/haddock-api/src/Haddock/Backends/Xhtml/Specialize.hs
index 47a96b3..69cd939 100644
--- a/haddock-api/src/Haddock/Backends/Xhtml/Specialize.hs
+++ b/haddock-api/src/Haddock/Backends/Xhtml/Specialize.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE RecordWildCards #-}
module Haddock.Backends.Xhtml.Specialize
@@ -19,7 +20,8 @@ import Name
import FastString
import Control.Monad
-import Control.Monad.Trans.RWS
+import Control.Monad.Trans.Reader
+import Control.Monad.Trans.State
import Data.Data
import qualified Data.List as List
@@ -190,20 +192,26 @@ freeVariables =
-- will fix that type to be visually unambiguous again (making it something
-- like @(a -> c) -> b@).
rename :: SetName name => Set NameRep -> HsType name -> HsType name
-rename fv typ = fst $ evalRWS (renameType typ) fv Map.empty
+rename fv typ = runReader (renameType typ) $ RenameEnv
+ { rneFV = fv
+ , rneCtx = Map.empty
+ }
-- | Renaming monad.
---
--- This is just a simple RWS instance, where /reader/ part consists of names
--- that are initially taken and cannot change, /state/ part is just context
--- with name bindings and /writer/ part is not used.
-type Rename name a = RWS (Set NameRep) () (Map Name name) a
+type Rename name = Reader (RenameEnv name)
+
+-- | Binding generation monad.
+type Rebind name = State (RenameEnv name)
+
+data RenameEnv name = RenameEnv
+ { rneFV :: Set NameRep
+ , rneCtx :: Map Name name
+ }
renameType :: SetName name => HsType name -> Rename name (HsType name)
-renameType (HsForAllTy ex mspan lbndrs lctx lt) = do
- lbndrs' <- renameLTyVarBndrs lbndrs
+renameType (HsForAllTy ex mspan lbndrs lctx lt) = rebind lbndrs $ \lbndrs' ->
HsForAllTy
<$> pure ex
<*> pure mspan
@@ -246,66 +254,73 @@ renameLTypes :: SetName name => [LHsType name] -> Rename name [LHsType name]
renameLTypes = mapM renameLType
-renameContext :: SetName name => HsContext name
- -> Rename name (HsContext name)
+renameContext :: SetName name => HsContext name -> Rename name (HsContext name)
renameContext = renameLTypes
-renameLTyVarBndrs :: SetName name => LHsTyVarBndrs name -> Rename name (LHsTyVarBndrs name)
-renameLTyVarBndrs lbndrs = do
- tys' <- mapM (located renameTyVarBndr) $ hsq_tvs lbndrs
- pure $ lbndrs { hsq_tvs = tys' }
-
-
-renameTyVarBndr :: SetName name => HsTyVarBndr name
- -> Rename name (HsTyVarBndr name)
-renameTyVarBndr (UserTyVar name) =
- UserTyVar <$> renameNameBndr name
-renameTyVarBndr (KindedTyVar name kinds) =
- KindedTyVar <$> located renameNameBndr name <*> pure kinds
-
-
renameLTyOp :: SetName name => LHsTyOp name -> Rename name (LHsTyOp name)
renameLTyOp (wrap, lname) = (,) wrap <$> located renameName lname
-renameNameBndr :: SetName name => name -> Rename name name
-renameNameBndr name = do
- fv <- ask
- env <- get
- case Map.lookup (getName name) env of
- Just name' -> pure name'
- Nothing | getNameRep name `Set.member` fv -> freshName name
- Nothing -> pure name
-
-
renameName :: SetName name => name -> Rename name name
renameName name = do
- env <- get
- pure $ case Map.lookup (getName name) env of
+ RenameEnv { rneCtx = ctx } <- ask
+ pure $ case Map.lookup (getName name) ctx of
Just name' -> name'
Nothing -> name
+rebind :: SetName name
+ => LHsTyVarBndrs name -> (LHsTyVarBndrs name -> Rename name a)
+ -> Rename name a
+rebind lbndrs action = do
+ (lbndrs', env') <- runState (rebindLTyVarBndrs lbndrs) <$> ask
+ local (const env') (action lbndrs')
+
+
+rebindLTyVarBndrs :: SetName name
+ => LHsTyVarBndrs name -> Rebind name (LHsTyVarBndrs name)
+rebindLTyVarBndrs lbndrs = do
+ tys' <- mapM (located rebindTyVarBndr) $ hsq_tvs lbndrs
+ pure $ lbndrs { hsq_tvs = tys' }
+
+
+rebindTyVarBndr :: SetName name
+ => HsTyVarBndr name -> Rebind name (HsTyVarBndr name)
+rebindTyVarBndr (UserTyVar name) =
+ UserTyVar <$> rebindName name
+rebindTyVarBndr (KindedTyVar name kinds) =
+ KindedTyVar <$> located rebindName name <*> pure kinds
+
+
+rebindName :: SetName name => name -> Rebind name name
+rebindName name = do
+ RenameEnv { .. } <- get
+ case Map.lookup (getName name) rneCtx of
+ Just name' -> pure name'
+ Nothing | getNameRep name `Set.member` rneFV -> freshName name
+ Nothing -> pure name
+
+
-- | Generate fresh occurrence name, put it into context and return.
-freshName :: SetName name => name -> Rename name name
+freshName :: SetName name => name -> Rebind name name
freshName name = do
- fv <- ask
- env <- get
- let taken = Set.union fv (Set.fromList . map getNameRep . Map.elems $ env)
- let name' = setInternalNameRep (findFreshName taken occ) name
- put $ Map.insert nname name' env
+ env at RenameEnv { .. } <- get
+ let taken = Set.union rneFV (elems' rneCtx)
+ let name' = setInternalNameRep (findFreshName taken rep) name
+ put $ env { rneCtx = Map.insert nname name' rneCtx }
return name'
where
+ elems' = Set.fromList . map getNameRep . Map.elems
nname = getName name
- occ = getNameRep nname
+ rep = getNameRep nname
findFreshName :: Set NameRep -> NameRep -> NameRep
findFreshName taken =
fromJust . List.find isFresh . alternativeNames
where
- isFresh = not . flip Set.member taken
+ isFresh = not . Set.member taken
alternativeNames :: NameRep -> [NameRep]
- Previous message: [commit: haddock] 2.17.3.1-spanfix, alexbiehl-patch-1, ghc-8.0, ghc-8.0-facebook, ghc-head, ghc-head1, haddock-quick, headdock-library-1.4.5, ie_avails, issue-303, issue-475, master, pr-filter-maps, pr/cabal-desc, travis, v2.16, v2.17, v2.17.3, v2.18, wip-located-module-as, wip/D2418, wip/T11080-open-data-kinds, wip/T11258, wip/T11430, wip/T12105, wip/T12105-2, wip/T12942, wip/T13163, wip/T14529, wip/T3384, wip/embelleshed-rdr, wip/new-tree-one-param, wip/rae, wip/remove-frames, wip/remove-frames1, wip/revert-ttg-2017-11-20, wip/ttg-2017-10-13, wip/ttg-2017-10-31, wip/ttg-2017-11-06, wip/ttg2-2017-11-10, wip/ttg3-2017-11-12, wip/ttg4-constraints-2017-11-13, wip/ttg6-unrevert-2017-11-22: Fix type renamer bug with incorrect names being generated. (08e592e)
- Next message: [commit: haddock] 2.17.3.1-spanfix, alexbiehl-patch-1, ghc-8.0, ghc-8.0-facebook, ghc-head, ghc-head1, haddock-quick, headdock-library-1.4.5, ie_avails, issue-303, issue-475, master, pr-filter-maps, pr/cabal-desc, travis, v2.16, v2.17, v2.17.3, v2.18, wip-located-module-as, wip/D2418, wip/T11080-open-data-kinds, wip/T11258, wip/T11430, wip/T12105, wip/T12105-2, wip/T12942, wip/T13163, wip/T14529, wip/T3384, wip/embelleshed-rdr, wip/new-tree-one-param, wip/rae, wip/remove-frames, wip/remove-frames1, wip/revert-ttg-2017-11-20, wip/ttg-2017-10-13, wip/ttg-2017-10-31, wip/ttg-2017-11-06, wip/ttg2-2017-11-10, wip/ttg3-2017-11-12, wip/ttg4-constraints-2017-11-13, wip/ttg6-unrevert-2017-11-22: Extend instances test case to also test multi-name type signatures. (dbe6f2c)
- Messages sorted by:
[ date ]
[ thread ]
[ subject ]
[ author ]
More information about the ghc-commits
mailing list