From 506f614402192bd7b6a9a608e925a01b373b2bdc Mon Sep 17 00:00:00 2001
From: Doug Wilson
Date: Sun, 28 May 2017 05:54:53 +1200
Subject: Improve Syb code (#621)
Specialize.hs and Ast.hs are modified to have their Syb code not recurse into
Name or Id in HsSyn types.
Specialize.hs is refactored to have fewer calls to Syb functions.
Syb.hs has some foldl calls replaced with foldl' calls.
There is still a lot of performance on the floor of Ast.hs. The RenamedSource
is traversed many times, and lookupBySpan is very inefficient. everywhereBut and
lookupBySpan dominate the runtime whenever --hyperlinked-source is passed.
---
haddock-api/src/Haddock/Interface/Specialize.hs | 58 ++++++++++---------------
1 file changed, 23 insertions(+), 35 deletions(-)
(limited to 'haddock-api/src/Haddock/Interface/Specialize.hs')
diff --git a/haddock-api/src/Haddock/Interface/Specialize.hs b/haddock-api/src/Haddock/Interface/Specialize.hs
index 28bbf305..8c28cd5a 100644
--- a/haddock-api/src/Haddock/Interface/Specialize.hs
+++ b/haddock-api/src/Haddock/Interface/Specialize.hs
@@ -1,9 +1,9 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE RecordWildCards #-}
-
module Haddock.Interface.Specialize
( specializeInstHead
) where
@@ -27,73 +27,66 @@ import Data.Map (Map)
import qualified Data.Map as Map
import Data.Set (Set)
import qualified Data.Set as Set
-
-
--- | Instantiate all occurrences of given name with particular type.
-specialize :: (Eq name, Typeable name)
- => Data a
- => name -> HsType name -> a -> a
-specialize name details =
- everywhere $ mkT step
- where
- step (HsTyVar _ (L _ name')) | name == name' = details
- step typ = typ
-
+import Data.Foldable
-- | Instantiate all occurrences of given names with corresponding types.
---
--- It is just a convenience function wrapping 'specialize' that supports more
--- that one specialization.
-specialize' :: (Eq name, Typeable name)
+specialize :: forall name a. (Ord name, DataId name, NamedThing name)
=> Data a
=> [(name, HsType name)] -> a -> a
-specialize' = flip $ foldr (uncurry specialize)
+specialize specs = go
+ where
+ go :: forall x. Data x => x -> x
+ go = everywhereButType @name $ mkT $ sugar . specialize_ty_var
+ specialize_ty_var (HsTyVar _ (L _ name'))
+ | Just t <- Map.lookup name' spec_map = t
+ specialize_ty_var typ = typ
+ -- This is a tricky recursive definition that is guaranteed to terminate
+ -- because a type binder cannot be instantiated with a type that depends
+ -- on that binder. i.e. @a -> Maybe a@ is invalid
+ spec_map = Map.fromList [ (n, go t) | (n, t) <- specs]
-- | Instantiate given binders with corresponding types.
--
-- Again, it is just a convenience function around 'specialize'. Note that
-- length of type list should be the same as the number of binders.
-specializeTyVarBndrs :: (Eq name, DataId name)
+specializeTyVarBndrs :: (Ord name, DataId name, NamedThing name)
=> Data a
=> LHsQTyVars name -> [HsType name]
-> a -> a
specializeTyVarBndrs bndrs typs =
- specialize' $ zip bndrs' typs
+ specialize $ zip bndrs' typs
where
bndrs' = map (bname . unLoc) . hsq_explicit $ bndrs
bname (UserTyVar (L _ name)) = name
bname (KindedTyVar (L _ name) _) = name
-specializePseudoFamilyDecl :: (Eq name, DataId name)
+specializePseudoFamilyDecl :: (Ord name, DataId name, NamedThing name)
=> LHsQTyVars name -> [HsType name]
-> PseudoFamilyDecl name
-> PseudoFamilyDecl name
specializePseudoFamilyDecl bndrs typs decl =
- decl { pfdTyVars = map specializeTyVars (pfdTyVars decl) }
- where
- specializeTyVars = specializeTyVarBndrs bndrs typs
-
+ decl {pfdTyVars = map (specializeTyVarBndrs bndrs typs) (pfdTyVars decl)}
-specializeSig :: forall name . (Eq name, DataId name, SetName name)
+specializeSig :: forall name . (Ord name, DataId name, SetName name, NamedThing name)
=> LHsQTyVars name -> [HsType name]
-> Sig name
-> Sig name
specializeSig bndrs typs (TypeSig lnames typ) =
- TypeSig lnames (typ { hswc_body = (hswc_body typ) { hsib_body = noLoc typ'}})
+ TypeSig lnames (typ {hswc_body = (hswc_body typ) {hsib_body = noLoc typ'}})
where
true_type :: HsType name
true_type = unLoc (hsSigWcType typ)
typ' :: HsType name
- typ' = rename fv . sugar $ specializeTyVarBndrs bndrs typs true_type
+ typ' = rename fv $ specializeTyVarBndrs bndrs typs true_type
fv = foldr Set.union Set.empty . map freeVariables $ typs
specializeSig _ _ sig = sig
-- | Make all details of instance head (signatures, associated types)
-- specialized to that particular instance type.
-specializeInstHead :: (Eq name, DataId name, SetName name)
+specializeInstHead :: (Ord name, DataId name, SetName name, NamedThing name)
=> InstHead name -> InstHead name
specializeInstHead ihd@InstHead { ihdInstType = clsi@ClassInst { .. }, .. } =
ihd { ihdInstType = instType' }
@@ -115,12 +108,7 @@ specializeInstHead ihd = ihd
-- and @(a, b, c)@.
sugar :: forall name. (NamedThing name, DataId name)
=> HsType name -> HsType name
-sugar =
- everywhere $ mkT step
- where
- step :: HsType name -> HsType name
- step = sugarOperators . sugarTuples . sugarLists
-
+sugar = sugarOperators . sugarTuples . sugarLists
sugarLists :: NamedThing name => HsType name -> HsType name
sugarLists (HsAppTy (L _ (HsTyVar _ (L _ name))) ltyp)
--
cgit v1.2.3
From fdf1b017b07e12769a7ca605b41dc76842838855 Mon Sep 17 00:00:00 2001
From: Alex Biehl
Date: Tue, 30 May 2017 19:02:12 +0200
Subject: Make haddock-library and haddock-api warning free (#626)
---
haddock-api/src/Haddock.hs | 12 ++++++------
haddock-api/src/Haddock/GhcUtils.hs | 4 ----
haddock-api/src/Haddock/Interface/Specialize.hs | 1 -
haddock-library/src/Documentation/Haddock/Types.hs | 4 +++-
4 files changed, 9 insertions(+), 12 deletions(-)
(limited to 'haddock-api/src/Haddock/Interface/Specialize.hs')
diff --git a/haddock-api/src/Haddock.hs b/haddock-api/src/Haddock.hs
index f0e7e6c7..57ea5fea 100644
--- a/haddock-api/src/Haddock.hs
+++ b/haddock-api/src/Haddock.hs
@@ -398,12 +398,12 @@ withGhc' libDir flags ghcActs = runGhc (Just libDir) $ do
ghcLink = NoLink
}
let dynflags'' = updOptLevel 0 $ gopt_unset dynflags' Opt_SplitObjs
- defaultCleanupHandler dynflags'' $ do
- -- ignore the following return-value, which is a list of packages
- -- that may need to be re-linked: Haddock doesn't do any
- -- dynamic or static linking at all!
- _ <- setSessionDynFlags dynflags''
- ghcActs dynflags''
+
+ -- ignore the following return-value, which is a list of packages
+ -- that may need to be re-linked: Haddock doesn't do any
+ -- dynamic or static linking at all!
+ _ <- setSessionDynFlags dynflags''
+ ghcActs dynflags''
where
parseGhcFlags :: MonadIO m => DynFlags -> m DynFlags
parseGhcFlags dynflags = do
diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs
index c8e5ea8b..dcc1d834 100644
--- a/haddock-api/src/Haddock/GhcUtils.hs
+++ b/haddock-api/src/Haddock/GhcUtils.hs
@@ -17,17 +17,13 @@ module Haddock.GhcUtils where
import Control.Arrow
-import Data.Function
import Exception
import Outputable
import Name
import Lexeme
import Module
-import RdrName (GlobalRdrEnv)
-import GhcMonad (withSession)
import HscTypes
-import UniqFM
import GHC
import Class
diff --git a/haddock-api/src/Haddock/Interface/Specialize.hs b/haddock-api/src/Haddock/Interface/Specialize.hs
index 8c28cd5a..da8c3e7b 100644
--- a/haddock-api/src/Haddock/Interface/Specialize.hs
+++ b/haddock-api/src/Haddock/Interface/Specialize.hs
@@ -27,7 +27,6 @@ import Data.Map (Map)
import qualified Data.Map as Map
import Data.Set (Set)
import qualified Data.Set as Set
-import Data.Foldable
-- | Instantiate all occurrences of given names with corresponding types.
specialize :: forall name a. (Ord name, DataId name, NamedThing name)
diff --git a/haddock-library/src/Documentation/Haddock/Types.hs b/haddock-library/src/Documentation/Haddock/Types.hs
index 4d5bb68a..660878ff 100644
--- a/haddock-library/src/Documentation/Haddock/Types.hs
+++ b/haddock-library/src/Documentation/Haddock/Types.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE DeriveFunctor, DeriveFoldable, DeriveTraversable #-}
+{-# LANGUAGE CPP, DeriveFunctor, DeriveFoldable, DeriveTraversable #-}
-- |
-- Module : Documentation.Haddock.Types
@@ -14,8 +14,10 @@
-- Exposes documentation data types used for (some) of Haddock.
module Documentation.Haddock.Types where
+#if !MIN_VERSION_base(4,8,0)
import Data.Foldable
import Data.Traversable
+#endif
-- | With the advent of 'Version', we may want to start attaching more
-- meta-data to comments. We make a structure for this ahead of time
--
cgit v1.2.3
From 4d765e3cd0a735f9a7e8d13fb6633f9ee534fbfb Mon Sep 17 00:00:00 2001
From: Moritz Drexl
Date: Sat, 5 Aug 2017 16:44:40 +0200
Subject: Fix renaming after instance signature specializing (#660)
* rework rename
* Add regression test for Bug 613
* update tests
* update changelog
---
CHANGES.md | 2 +
haddock-api/src/Haddock/Interface/Specialize.hs | 132 +++++-------
html-test/ref/Bug613.html | 260 ++++++++++++++++++++++++
html-test/ref/Instances.html | 178 ++++++++--------
html-test/src/Bug613.hs | 16 ++
5 files changed, 418 insertions(+), 170 deletions(-)
create mode 100644 html-test/ref/Bug613.html
create mode 100644 html-test/src/Bug613.hs
(limited to 'haddock-api/src/Haddock/Interface/Specialize.hs')
diff --git a/CHANGES.md b/CHANGES.md
index bf60817a..5050339d 100644
--- a/CHANGES.md
+++ b/CHANGES.md
@@ -2,6 +2,8 @@
* to be released
+ * Fix renaming of type variables after specializing instance method signatures (#613)
+
* Move markup related data types to haddock-library
## Changes in version 2.18.1
diff --git a/haddock-api/src/Haddock/Interface/Specialize.hs b/haddock-api/src/Haddock/Interface/Specialize.hs
index da8c3e7b..84168151 100644
--- a/haddock-api/src/Haddock/Interface/Specialize.hs
+++ b/haddock-api/src/Haddock/Interface/Specialize.hs
@@ -17,7 +17,6 @@ import Name
import FastString
import Control.Monad
-import Control.Monad.Trans.Reader
import Control.Monad.Trans.State
import Data.Data
@@ -204,7 +203,7 @@ setInternalOccName occ name =
-- | Compute set of free variables of given type.
freeVariables :: forall name. (NamedThing name, DataId name)
- => HsType name -> Set NameRep
+ => HsType name -> Set Name
freeVariables =
everythingWithState Set.empty Set.union query
where
@@ -213,7 +212,7 @@ freeVariables =
(Set.empty, Set.union ctx (bndrsNames bndrs))
Just (HsTyVar _ (L _ name))
| getName name `Set.member` ctx -> (Set.empty, ctx)
- | otherwise -> (Set.singleton $ getNameRep name, ctx)
+ | otherwise -> (Set.singleton $ getName name, ctx)
_ -> (Set.empty, ctx)
bndrsNames = Set.fromList . map (getName . tyVarName . unLoc)
@@ -225,33 +224,36 @@ freeVariables =
-- @(a -> b)@ we get @(a -> b) -> b@ where first occurrence of @b@ refers to
-- different type variable than latter one. Applying 'rename' function
-- 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 = runReader (renameType typ) $ RenameEnv
- { rneFV = fv
- , rneCtx = Map.empty
- }
-
+-- like @(a -> b0) -> b@).
+rename :: (Eq name, DataId name, SetName name)
+ => Set Name -> HsType name -> HsType name
+rename fv typ = evalState (renameType typ) env
+ where
+ env = RenameEnv
+ { rneHeadFVs = Map.fromList . map mkPair . Set.toList $ fv
+ , rneSigFVs = Set.map getNameRep $ freeVariables typ
+ , rneCtx = Map.empty
+ }
+ mkPair name = (getNameRep name, name)
-- | Renaming monad.
-type Rename name = Reader (RenameEnv name)
-
--- | Binding generation monad.
-type Rebind name = State (RenameEnv name)
+type Rename name = State (RenameEnv name)
data RenameEnv name = RenameEnv
- { rneFV :: Set NameRep
- , rneCtx :: Map Name name
- }
+ { rneHeadFVs :: Map NameRep Name
+ , rneSigFVs :: Set NameRep
+ , rneCtx :: Map Name name
+ }
-renameType :: SetName name => HsType name -> Rename name (HsType name)
-renameType (HsForAllTy bndrs lt) = rebind bndrs $ \bndrs' ->
+renameType :: (Eq name, SetName name)
+ => HsType name -> Rename name (HsType name)
+renameType (HsForAllTy bndrs lt) =
HsForAllTy
- <$> pure bndrs'
+ <$> mapM (located renameBinder) bndrs
<*> renameLType lt
renameType (HsQualTy lctxt lt) =
- HsQualTy
+ HsQualTy
<$> located renameContext lctxt
<*> renameLType lt
renameType (HsTyVar ip name) = HsTyVar ip <$> located renameName name
@@ -281,85 +283,61 @@ renameType (HsWildCardTy wc) = pure (HsWildCardTy wc)
renameType (HsAppsTy _) = error "HsAppsTy: Only used before renaming"
-renameLType :: SetName name => LHsType name -> Rename name (LHsType name)
+renameLType :: (Eq name, SetName name)
+ => LHsType name -> Rename name (LHsType name)
renameLType = located renameType
-renameLTypes :: SetName name => [LHsType name] -> Rename name [LHsType name]
+renameLTypes :: (Eq name, SetName name)
+ => [LHsType name] -> Rename name [LHsType name]
renameLTypes = mapM renameLType
-renameContext :: SetName name => HsContext name -> Rename name (HsContext name)
+renameContext :: (Eq name, SetName name)
+ => HsContext name -> Rename name (HsContext name)
renameContext = renameLTypes
-{-
-renameLTyOp :: SetName name => LHsTyOp name -> Rename name (LHsTyOp name)
-renameLTyOp (wrap, lname) = (,) wrap <$> located renameName lname
--}
-
-
-renameName :: SetName name => name -> Rename name name
-renameName name = do
- RenameEnv { rneCtx = ctx } <- ask
- pure $ fromMaybe name (Map.lookup (getName name) ctx)
-
-
-rebind :: SetName name
- => [LHsTyVarBndr name] -> ([LHsTyVarBndr 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
- => [LHsTyVarBndr name] -> Rebind name [LHsTyVarBndr name]
-rebindLTyVarBndrs lbndrs = mapM (located rebindTyVarBndr) lbndrs
+renameBinder :: (Eq name, SetName name)
+ => HsTyVarBndr name -> Rename name (HsTyVarBndr name)
+renameBinder (UserTyVar lname) = UserTyVar <$> located renameName lname
+renameBinder (KindedTyVar lname lkind) =
+ KindedTyVar <$> located renameName lname <*> located renameType lkind
-rebindTyVarBndr :: SetName name
- => HsTyVarBndr name -> Rebind name (HsTyVarBndr name)
-rebindTyVarBndr (UserTyVar (L l name)) =
- UserTyVar . L l <$> rebindName name
-rebindTyVarBndr (KindedTyVar name kinds) =
- KindedTyVar <$> located rebindName name <*> pure kinds
-
-
-rebindName :: SetName name => name -> Rebind name name
-rebindName name = do
+-- | Core renaming logic.
+renameName :: (Eq name, SetName name) => name -> Rename name name
+renameName name = do
RenameEnv { .. } <- get
- taken <- takenNames
case Map.lookup (getName name) rneCtx of
- Just name' -> pure name'
- Nothing | getNameRep name `Set.member` taken -> freshName name
- Nothing -> reuseName name
+ Nothing
+ | Just headTv <- Map.lookup (getNameRep name) rneHeadFVs
+ , headTv /= getName name -> freshName name
+ Just name' -> return name'
+ _ -> return name
-- | Generate fresh occurrence name, put it into context and return.
-freshName :: SetName name => name -> Rebind name name
+freshName :: SetName name => name -> Rename name name
freshName name = do
- env@RenameEnv { .. } <- get
taken <- takenNames
let name' = setInternalNameRep (findFreshName taken rep) name
- put $ env { rneCtx = Map.insert nname name' rneCtx }
+ modify $ \rne -> rne
+ { rneCtx = Map.insert (getName name) name' (rneCtx rne) }
return name'
where
nname = getName name
rep = getNameRep nname
-reuseName :: SetName name => name -> Rebind name name
-reuseName name = do
- env@RenameEnv { .. } <- get
- put $ env { rneCtx = Map.insert (getName name) name rneCtx }
- return name
-
-
-takenNames :: NamedThing name => Rebind name (Set NameRep)
+takenNames :: NamedThing name => Rename name (Set NameRep)
takenNames = do
RenameEnv { .. } <- get
- return $ Set.union rneFV (ctxElems rneCtx)
+ return $ headReps rneHeadFVs `Set.union`
+ rneSigFVs `Set.union`
+ ctxElems rneCtx
where
+ headReps = Set.fromList . Map.keys
ctxElems = Set.fromList . map getNameRep . Map.elems
@@ -371,15 +349,7 @@ findFreshName taken =
alternativeNames :: NameRep -> [NameRep]
-alternativeNames name
- | [_] <- nameRepString name = letterNames ++ alternativeNames' name
- where
- letterNames = map (stringNameRep . pure) ['a'..'z']
-alternativeNames name = alternativeNames' name
-
-
-alternativeNames' :: NameRep -> [NameRep]
-alternativeNames' name =
+alternativeNames name =
[ stringNameRep $ str ++ show i | i :: Int <- [0..] ]
where
str = nameRepString name
diff --git a/html-test/ref/Bug613.html b/html-test/ref/Bug613.html
new file mode 100644
index 00000000..924f37d4
--- /dev/null
+++ b/html-test/ref/Bug613.html
@@ -0,0 +1,260 @@
+Bug613 Documentation class Functor f where #
Minimal complete definition
fmap
Methods
fmap :: (a -> b) -> f a -> f b #
data ThreeVars a0 a b #
Phantom type a0 is added to block the first renaming from a to a0. This ensures that the renamer doesn't create a new conflict
\ No newline at end of file
diff --git a/html-test/ref/Instances.html b/html-test/ref/Instances.html
index b014e8df..c9ca6f82 100644
--- a/html-test/ref/Instances.html
+++ b/html-test/ref/Instances.html
@@ -102,9 +102,9 @@ window.onload = function () {pageLoad();};
><~~ Int ) -> a -> a ) -> a0 -> a <~~ a a0 #
<~~ (a <~~ a)) -> a0)) -> Int -> a <~~ Either a Int -> a -> -> a0 -> Either a a a a0 #
Either a (Either a a) -> a a0) -> Int -> Either foo :: (f a, Int ) -> a -> (f a, a) ) -> a0 -> (f a, a0) #
foo' :: (f a, (f a, a)) -> :: (f a, (f a, a0)) -> Int -> (f a, (f a, Int <~~ Int ) -> a -> a ) -> a0 -> a <~~ a a0 #
<~~ (a <~~ a)) -> a0)) -> Int -> a <~~ foo :: (a, a, Int ) -> a -> (a, a, a) ) -> a0 -> (a, a, a0) #
foo' :: (a, a, (a, a, a)) -> :: (a, a, (a, a, a0)) -> Int -> (a, a, (a, a, Int Quux a b Int -> a -> -> a0 -> Quux a b a a b a0 #
Quux a b (Quux a b a) -> a b a0) -> Int -> Quux LiftedRep) a Int -> a -> ( -> a0 -> ( LiftedRep -> LiftedRep ) a a ) a a0 #
LiftedRep -> LiftedRep ) a a) -> ) a a0) -> Int -> (LiftedRep
bar' :: (a, b, (a, b, (a, b, a))) -> (a, b, (a, b, (a, b, b))) :: (a, b, (a, b, (a, b, a))) -> (a, b, (a, b, (a, b, b0))) #
bar0 :: ((a, b, (a, b, a)), (a, b, (a, b, a))) -> ((a, b, b), (a, b, c)) :: ((a, b, (a, b, a)), (a, b, (a, b, a))) -> ((a, b, b0), (a, b, c)) #
bar1 :: ((a, b, (a, b, a)), (a, b, (a, b, a))) -> ((a, b, b), (a, b, c)) :: ((a, b, (a, b, a)), (a, b, (a, b, a))) -> ((a, b, b0), (a, b, c)) #
Quux a c (Quux a c b)) a c b0)) # Quux a b c)) -> (Quux a c b, a c b0, Quux a c c) a c c0) #
Quux a b c)) -> (Quux a c b, a c b0, Quux a c c) a c c0) #
forall a. a -> a) -> (b, forall a. a -> [c]) -> (b, c) c0. c0 -> [c]) -> (b, c1) # forall b. (forall a. a -> [c]) -> c) -> b. b -> [c]) -> c0) -> forall a. a -> b c1. c1 -> b #
baz :: (a -> b) -> (forall c. c -> c) -> (b, a0. a0 -> a0) -> (b0, forall c. c -> a -> b) -> (b, c) c. c -> a -> b) -> (b0, c) # baz' :: b -> ( :: b0 -> (forall c. c -> a -> b) -> ( b1. b1 -> a -> b) -> (forall c. c -> a -> b) -> [(b, a -> b)] b2. b2 -> a -> b) -> [(b0, a -> b)] #
baz'' :: b -> ( :: b0 -> (forall c. ( b1. (forall d. d -> a -> b) -> c) -> b2. b2 -> a -> b) -> c) -> forall c. c -> b c. c -> b0 #
baz :: (a, b, c) -> (forall d. d -> d) -> (b, a0. a0 -> a0) -> (b0, forall d. d -> (a, b, c)) -> (b, c) c0. c0 -> (a, b, c)) -> (b0, c1) # baz' :: b -> ( :: b0 -> (forall d. d -> (a, b, c)) -> ( b1. b1 -> (a, b, c)) -> (forall d. d -> (a, b, c)) -> [(b, (a, b, c))] b2. b2 -> (a, b, c)) -> [(b0, (a, b, c))] #
baz'' :: b -> ( :: b0 -> (forall d. ( b1. (forall e. e -> (a, b, c)) -> c) -> b2. b2 -> (a, b, c)) -> c0) -> forall d. d -> b c1. c1 -> b0 #
Quux a b c -> (forall d. d -> d) -> (b, a0. a0 -> a0) -> (b0, forall d. d -> c0. c0 -> Quux a b c) -> (b, c) a b c) -> (b0, c1) # baz' :: b -> ( :: b0 -> (forall d. d -> b1. b1 -> Quux a b c) -> (forall d. d -> b2. b2 -> Quux a b c) -> [(b, a b c) -> [(b0, Quux a b c)] # baz'' :: b -> ( :: b0 -> (forall d. ( b1. (forall e. e -> b2. b2 -> Quux a b c) -> c) -> a b c) -> c0) -> forall d. d -> b c1. c1 -> b0 #
baz :: (a, [b], b, a) -> (forall c. c -> c) -> (b, a0. a0 -> a0) -> (b0, forall c. c -> (a, [b], b, a)) -> (b, c) c. c -> (a, [b], b, a)) -> (b0, c) #
baz' :: b -> ( :: b0 -> (forall c. c -> (a, [b], b, a)) -> ( b1. b1 -> (a, [b], b, a)) -> (forall c. c -> (a, [b], b, a)) -> [(b, (a, [b], b, a))] b2. b2 -> (a, [b], b, a)) -> [(b0, (a, [b], b, a))] #
baz'' :: b -> ( :: b0 -> (forall c. ( b1. (forall d. d -> (a, [b], b, a)) -> c) -> b2. b2 -> (a, [b], b, a)) -> c) -> forall c. c -> b c. c -> b0 #
Quux a b Int -> a -> -> a0 -> Quux a b a a b a0 # Quux a b (Quux a b a) -> a b a0) -> Int -> Quux Quux a c (Quux a c b)) a c b0)) #
Quux a b c)) -> (Quux a c b, a c b0, Quux a c c) a c c0) #
Quux a b c)) -> (Quux a c b, a c b0, Quux a c c) a c c0) #
Quux a b c -> (forall d. d -> d) -> (b, a0. a0 -> a0) -> (b0, forall d. d -> c0. c0 -> Quux a b c) -> (b, c) a b c) -> (b0, c1) # baz' :: b -> ( :: b0 -> (forall d. d -> b1. b1 -> Quux a b c) -> (forall d. d -> b2. b2 -> Quux a b c) -> [(b, a b c) -> [(b0, Quux a b c)] # baz'' :: b -> ( :: b0 -> (forall d. ( b1. (forall e. e -> b2. b2 -> Quux a b c) -> c) -> a b c) -> c0) -> forall d. d -> b c1. c1 -> b0 #
b) -> f a -> f b
+
+instance Functor (Either a) where
+ fmap _ (Left x) = Left x
+ fmap f (Right y) = Right (f y)
+
+-- | Phantom type a0 is added to block the first renaming from a to a0. This ensures that the renamer doesn't create a new conflict
+data ThreeVars a0 a b = ThreeVars a b
+
+instance Functor (ThreeVars a0 a) where
+ fmap f (ThreeVars a b) = ThreeVars a (f b)
--
cgit v1.2.3