{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
module GHC.Iface.Rename (
rnModIface,
rnModExports,
tcRnModIface,
tcRnModExports,
) where
import GHC.Prelude
import GHC.Driver.Env
import GHC.Tc.Utils.Monad
import GHC.Iface.Syntax
import GHC.Iface.Env
import {-# SOURCE #-} GHC.Iface.Load
import GHC.Unit
import GHC.Unit.Module.ModIface
import GHC.Unit.Module.Deps
import GHC.Tc.Errors.Types
import GHC.Types.SrcLoc
import GHC.Types.Unique.FM
import GHC.Types.Avail
import GHC.Types.Error
import GHC.Types.FieldLabel
import GHC.Types.Var
import GHC.Types.Basic
import GHC.Types.Name
import GHC.Types.Name.Shape
import GHC.Utils.Outputable
import GHC.Utils.Misc
import GHC.Utils.Error
import GHC.Utils.Fingerprint
import GHC.Utils.Panic
import qualified Data.Traversable as T
import Data.IORef
tcRnMsgMaybe :: IO (Either (Messages TcRnMessage) a) -> TcM a
tcRnMsgMaybe :: forall a. IO (Either (Messages TcRnMessage) a) -> TcM a
tcRnMsgMaybe IO (Either (Messages TcRnMessage) a)
do_this = do
Either (Messages TcRnMessage) a
r <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ IO (Either (Messages TcRnMessage) a)
do_this
case Either (Messages TcRnMessage) a
r of
Left Messages TcRnMessage
msgs -> do
Messages TcRnMessage -> TcRn ()
addMessages Messages TcRnMessage
msgs
forall env a. IOEnv env a
failM
Right a
x -> forall (m :: * -> *) a. Monad m => a -> m a
return a
x
tcRnModIface :: [(ModuleName, Module)] -> Maybe NameShape -> ModIface -> TcM ModIface
tcRnModIface :: [(ModuleName, Module)]
-> Maybe NameShape -> ModIface -> TcM ModIface
tcRnModIface [(ModuleName, Module)]
x Maybe NameShape
y ModIface
z = do
HscEnv
hsc_env <- forall gbl lcl. TcRnIf gbl lcl HscEnv
getTopEnv
forall a. IO (Either (Messages TcRnMessage) a) -> TcM a
tcRnMsgMaybe forall a b. (a -> b) -> a -> b
$ HscEnv
-> [(ModuleName, Module)]
-> Maybe NameShape
-> ModIface
-> IO (Either (Messages TcRnMessage) ModIface)
rnModIface HscEnv
hsc_env [(ModuleName, Module)]
x Maybe NameShape
y ModIface
z
tcRnModExports :: [(ModuleName, Module)] -> ModIface -> TcM [AvailInfo]
tcRnModExports :: [(ModuleName, Module)] -> ModIface -> TcM [AvailInfo]
tcRnModExports [(ModuleName, Module)]
x ModIface
y = do
HscEnv
hsc_env <- forall gbl lcl. TcRnIf gbl lcl HscEnv
getTopEnv
forall a. IO (Either (Messages TcRnMessage) a) -> TcM a
tcRnMsgMaybe forall a b. (a -> b) -> a -> b
$ HscEnv
-> [(ModuleName, Module)]
-> ModIface
-> IO (Either (Messages TcRnMessage) [AvailInfo])
rnModExports HscEnv
hsc_env [(ModuleName, Module)]
x ModIface
y
failWithRn :: TcRnMessage -> ShIfM a
failWithRn :: forall a. TcRnMessage -> ShIfM a
failWithRn TcRnMessage
tcRnMessage = do
IORef (Messages TcRnMessage)
errs_var <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShIfEnv -> IORef (Messages TcRnMessage)
sh_if_errs forall gbl lcl. TcRnIf gbl lcl gbl
getGblEnv
Messages TcRnMessage
errs <- forall a gbl lcl. TcRef a -> TcRnIf gbl lcl a
readTcRef IORef (Messages TcRnMessage)
errs_var
let msg :: MsgEnvelope TcRnMessage
msg = forall e. Diagnostic e => SrcSpan -> e -> MsgEnvelope e
mkPlainErrorMsgEnvelope SrcSpan
noSrcSpan TcRnMessage
tcRnMessage
forall a gbl lcl. TcRef a -> a -> TcRnIf gbl lcl ()
writeTcRef IORef (Messages TcRnMessage)
errs_var (MsgEnvelope TcRnMessage
msg forall e. MsgEnvelope e -> Messages e -> Messages e
`addMessage` Messages TcRnMessage
errs)
forall env a. IOEnv env a
failM
rnModIface :: HscEnv -> [(ModuleName, Module)] -> Maybe NameShape
-> ModIface -> IO (Either (Messages TcRnMessage) ModIface)
rnModIface :: HscEnv
-> [(ModuleName, Module)]
-> Maybe NameShape
-> ModIface
-> IO (Either (Messages TcRnMessage) ModIface)
rnModIface HscEnv
hsc_env [(ModuleName, Module)]
insts Maybe NameShape
nsubst ModIface
iface =
forall a.
HscEnv
-> ModIface
-> [(ModuleName, Module)]
-> Maybe NameShape
-> ShIfM a
-> IO (Either (Messages TcRnMessage) a)
initRnIface HscEnv
hsc_env ModIface
iface [(ModuleName, Module)]
insts Maybe NameShape
nsubst forall a b. (a -> b) -> a -> b
$ do
Module
mod <- Rename Module
rnModule (forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module ModIface
iface)
Maybe Module
sig_of <- case forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe Module
mi_sig_of ModIface
iface of
Maybe Module
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
Just Module
x -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Maybe a
Just (Rename Module
rnModule Module
x)
[AvailInfo]
exports <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename AvailInfo
rnAvailInfo (forall (phase :: ModIfacePhase). ModIface_ phase -> [AvailInfo]
mi_exports ModIface
iface)
[(Fingerprint, IfaceDecl)]
decls <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename (Fingerprint, IfaceDecl)
rnIfaceDecl' (forall (phase :: ModIfacePhase).
ModIface_ phase -> [IfaceDeclExts phase]
mi_decls ModIface
iface)
[IfaceClsInst]
insts <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceClsInst
rnIfaceClsInst (forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceClsInst]
mi_insts ModIface
iface)
[IfaceFamInst]
fams <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceFamInst
rnIfaceFamInst (forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceFamInst]
mi_fam_insts ModIface
iface)
Dependencies
deps <- Rename Dependencies
rnDependencies (forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps ModIface
iface)
forall (m :: * -> *) a. Monad m => a -> m a
return ModIface
iface { mi_module :: Module
mi_module = Module
mod
, mi_sig_of :: Maybe Module
mi_sig_of = Maybe Module
sig_of
, mi_insts :: [IfaceClsInst]
mi_insts = [IfaceClsInst]
insts
, mi_fam_insts :: [IfaceFamInst]
mi_fam_insts = [IfaceFamInst]
fams
, mi_exports :: [AvailInfo]
mi_exports = [AvailInfo]
exports
, mi_decls :: [IfaceDeclExts 'ModIfaceFinal]
mi_decls = [(Fingerprint, IfaceDecl)]
decls
, mi_deps :: Dependencies
mi_deps = Dependencies
deps }
rnModExports :: HscEnv -> [(ModuleName, Module)] -> ModIface -> IO (Either (Messages TcRnMessage) [AvailInfo])
rnModExports :: HscEnv
-> [(ModuleName, Module)]
-> ModIface
-> IO (Either (Messages TcRnMessage) [AvailInfo])
rnModExports HscEnv
hsc_env [(ModuleName, Module)]
insts ModIface
iface
= forall a.
HscEnv
-> ModIface
-> [(ModuleName, Module)]
-> Maybe NameShape
-> ShIfM a
-> IO (Either (Messages TcRnMessage) a)
initRnIface HscEnv
hsc_env ModIface
iface [(ModuleName, Module)]
insts forall a. Maybe a
Nothing
forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename AvailInfo
rnAvailInfo (forall (phase :: ModIfacePhase). ModIface_ phase -> [AvailInfo]
mi_exports ModIface
iface)
rnDependencies :: Rename Dependencies
rnDependencies :: Rename Dependencies
rnDependencies Dependencies
deps0 = do
Dependencies
deps1 <- forall (m :: * -> *).
Monad m =>
Dependencies -> ([Module] -> m [Module]) -> m Dependencies
dep_orphs_update Dependencies
deps0 ((Dependencies -> [Module]) -> [Module] -> ShIfM [Module]
rnDepModules Dependencies -> [Module]
dep_orphs)
forall (m :: * -> *).
Monad m =>
Dependencies -> ([Module] -> m [Module]) -> m Dependencies
dep_finsts_update Dependencies
deps1 ((Dependencies -> [Module]) -> [Module] -> ShIfM [Module]
rnDepModules Dependencies -> [Module]
dep_finsts)
rnDepModules :: (Dependencies -> [Module]) -> [Module] -> ShIfM [Module]
rnDepModules :: (Dependencies -> [Module]) -> [Module] -> ShIfM [Module]
rnDepModules Dependencies -> [Module]
sel [Module]
mods = do
HscEnv
hsc_env <- forall gbl lcl. TcRnIf gbl lcl HscEnv
getTopEnv
ShHoleSubst
hmap <- ShIfM ShHoleSubst
getHoleSubst
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. Ord a => [a] -> [a]
nubSort forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
T.forM [Module]
mods forall a b. (a -> b) -> a -> b
$ \Module
mod -> do
let mod' :: Module
mod' = UnitState -> ShHoleSubst -> Module -> Module
renameHoleModule (HasDebugCallStack => HscEnv -> UnitState
hsc_units HscEnv
hsc_env) ShHoleSubst
hmap Module
mod
if forall u. GenModule (GenUnit u) -> Bool
isHoleModule Module
mod
then do ModIface
iface <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. SDoc -> HscEnv -> IfG a -> IO a
initIfaceCheck (String -> SDoc
text String
"rnDepModule") HscEnv
hsc_env
forall a b. (a -> b) -> a -> b
$ forall lcl. SDoc -> Module -> IfM lcl ModIface
loadSysInterface (String -> SDoc
text String
"rnDepModule") Module
mod'
forall (m :: * -> *) a. Monad m => a -> m a
return (Module
mod' forall a. a -> [a] -> [a]
: Dependencies -> [Module]
sel (forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps ModIface
iface))
else forall (m :: * -> *) a. Monad m => a -> m a
return [Module
mod']
initRnIface :: HscEnv -> ModIface -> [(ModuleName, Module)] -> Maybe NameShape
-> ShIfM a -> IO (Either (Messages TcRnMessage) a)
initRnIface :: forall a.
HscEnv
-> ModIface
-> [(ModuleName, Module)]
-> Maybe NameShape
-> ShIfM a
-> IO (Either (Messages TcRnMessage) a)
initRnIface HscEnv
hsc_env ModIface
iface [(ModuleName, Module)]
insts Maybe NameShape
nsubst ShIfM a
do_this = do
IORef (Messages TcRnMessage)
errs_var <- forall a. a -> IO (IORef a)
newIORef forall e. Messages e
emptyMessages
let hsubst :: ShHoleSubst
hsubst = forall key elt. Uniquable key => [(key, elt)] -> UniqFM key elt
listToUFM [(ModuleName, Module)]
insts
rn_mod :: Module -> Module
rn_mod = UnitState -> ShHoleSubst -> Module -> Module
renameHoleModule (HasDebugCallStack => HscEnv -> UnitState
hsc_units HscEnv
hsc_env) ShHoleSubst
hsubst
env :: ShIfEnv
env = ShIfEnv {
sh_if_module :: Module
sh_if_module = Module -> Module
rn_mod (forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module ModIface
iface),
sh_if_semantic_module :: Module
sh_if_semantic_module = Module -> Module
rn_mod (forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_semantic_module ModIface
iface),
sh_if_hole_subst :: ShHoleSubst
sh_if_hole_subst = forall key elt. Uniquable key => [(key, elt)] -> UniqFM key elt
listToUFM [(ModuleName, Module)]
insts,
sh_if_shape :: Maybe NameShape
sh_if_shape = Maybe NameShape
nsubst,
sh_if_errs :: IORef (Messages TcRnMessage)
sh_if_errs = IORef (Messages TcRnMessage)
errs_var
}
Either IOEnvFailure a
res <- forall gbl lcl a.
Char -> HscEnv -> gbl -> lcl -> TcRnIf gbl lcl a -> IO a
initTcRnIf Char
'c' HscEnv
hsc_env ShIfEnv
env () forall a b. (a -> b) -> a -> b
$ forall env r. IOEnv env r -> IOEnv env (Either IOEnvFailure r)
tryM ShIfM a
do_this
Messages TcRnMessage
msgs <- forall a. IORef a -> IO a
readIORef IORef (Messages TcRnMessage)
errs_var
case Either IOEnvFailure a
res of
Left IOEnvFailure
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. a -> Either a b
Left Messages TcRnMessage
msgs)
Right a
r | Bool -> Bool
not (forall e. Messages e -> Bool
isEmptyMessages Messages TcRnMessage
msgs) -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. a -> Either a b
Left Messages TcRnMessage
msgs)
| Bool
otherwise -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. b -> Either a b
Right a
r)
data ShIfEnv = ShIfEnv {
ShIfEnv -> Module
sh_if_module :: Module,
ShIfEnv -> Module
sh_if_semantic_module :: Module,
ShIfEnv -> ShHoleSubst
sh_if_hole_subst :: ShHoleSubst,
ShIfEnv -> Maybe NameShape
sh_if_shape :: Maybe NameShape,
ShIfEnv -> IORef (Messages TcRnMessage)
sh_if_errs :: IORef (Messages TcRnMessage)
}
getHoleSubst :: ShIfM ShHoleSubst
getHoleSubst :: ShIfM ShHoleSubst
getHoleSubst = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShIfEnv -> ShHoleSubst
sh_if_hole_subst forall gbl lcl. TcRnIf gbl lcl gbl
getGblEnv
type ShIfM = TcRnIf ShIfEnv ()
type Rename a = a -> ShIfM a
rnModule :: Rename Module
rnModule :: Rename Module
rnModule Module
mod = do
ShHoleSubst
hmap <- ShIfM ShHoleSubst
getHoleSubst
UnitState
unit_state <- HasDebugCallStack => HscEnv -> UnitState
hsc_units forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall gbl lcl. TcRnIf gbl lcl HscEnv
getTopEnv
forall (m :: * -> *) a. Monad m => a -> m a
return (UnitState -> ShHoleSubst -> Module -> Module
renameHoleModule UnitState
unit_state ShHoleSubst
hmap Module
mod)
rnAvailInfo :: Rename AvailInfo
rnAvailInfo :: Rename AvailInfo
rnAvailInfo (Avail GreName
c) = GreName -> AvailInfo
Avail forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename GreName
rnGreName GreName
c
rnAvailInfo (AvailTC IfaceTopBndr
n [GreName]
ns) = do
[GreName]
ns' <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename GreName
rnGreName [GreName]
ns
case [GreName]
ns' of
[] -> forall a. String -> a
panic String
"rnAvailInfoEmpty AvailInfo"
(GreName
rep:[GreName]
rest) -> forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ((forall a. Eq a => a -> a -> Bool
== GreName -> Module
childModule GreName
rep) forall b c a. (b -> c) -> (a -> b) -> a -> c
. GreName -> Module
childModule) [GreName]
rest)
(forall a. Outputable a => a -> SDoc
ppr GreName
rep SDoc -> SDoc -> SDoc
$$ [SDoc] -> SDoc
hcat (forall a b. (a -> b) -> [a] -> [b]
map forall a. Outputable a => a -> SDoc
ppr [GreName]
rest)) forall a b. (a -> b) -> a -> b
$ do
IfaceTopBndr
n' <- forall m n. Maybe Module -> IfaceTopBndr -> TcRnIf m n IfaceTopBndr
setNameModule (forall a. a -> Maybe a
Just (GreName -> Module
childModule GreName
rep)) IfaceTopBndr
n
forall (m :: * -> *) a. Monad m => a -> m a
return (IfaceTopBndr -> [GreName] -> AvailInfo
AvailTC IfaceTopBndr
n' [GreName]
ns')
where
childModule :: GreName -> Module
childModule = HasDebugCallStack => IfaceTopBndr -> Module
nameModule forall b c a. (b -> c) -> (a -> b) -> a -> c
. GreName -> IfaceTopBndr
greNameMangledName
rnGreName :: Rename GreName
rnGreName :: Rename GreName
rnGreName (NormalGreName IfaceTopBndr
n) = IfaceTopBndr -> GreName
NormalGreName forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceGlobal IfaceTopBndr
n
rnGreName (FieldGreName FieldLabel
fl) = FieldLabel -> GreName
FieldGreName forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename FieldLabel
rnFieldLabel FieldLabel
fl
rnFieldLabel :: Rename FieldLabel
rnFieldLabel :: Rename FieldLabel
rnFieldLabel FieldLabel
fl = do
IfaceTopBndr
sel' <- IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceGlobal (FieldLabel -> IfaceTopBndr
flSelector FieldLabel
fl)
forall (m :: * -> *) a. Monad m => a -> m a
return (FieldLabel
fl { flSelector :: IfaceTopBndr
flSelector = IfaceTopBndr
sel' })
rnIfaceGlobal :: Name -> ShIfM Name
rnIfaceGlobal :: IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceGlobal IfaceTopBndr
n = do
HscEnv
hsc_env <- forall gbl lcl. TcRnIf gbl lcl HscEnv
getTopEnv
let unit_state :: UnitState
unit_state = HasDebugCallStack => HscEnv -> UnitState
hsc_units HscEnv
hsc_env
home_unit :: HomeUnit
home_unit = HscEnv -> HomeUnit
hsc_home_unit HscEnv
hsc_env
Module
iface_semantic_mod <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShIfEnv -> Module
sh_if_semantic_module forall gbl lcl. TcRnIf gbl lcl gbl
getGblEnv
Maybe NameShape
mb_nsubst <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShIfEnv -> Maybe NameShape
sh_if_shape forall gbl lcl. TcRnIf gbl lcl gbl
getGblEnv
ShHoleSubst
hmap <- ShIfM ShHoleSubst
getHoleSubst
let m :: Module
m = HasDebugCallStack => IfaceTopBndr -> Module
nameModule IfaceTopBndr
n
m' :: Module
m' = UnitState -> ShHoleSubst -> Module -> Module
renameHoleModule UnitState
unit_state ShHoleSubst
hmap Module
m
case () of
()
_ | Module
m' forall a. Eq a => a -> a -> Bool
== Module
iface_semantic_mod
, forall u. GenModule (GenUnit u) -> Bool
isHoleModule Module
m'
-> do IfaceTopBndr
n' <- forall m n. Maybe Module -> IfaceTopBndr -> TcRnIf m n IfaceTopBndr
setNameModule (forall a. a -> Maybe a
Just Module
m') IfaceTopBndr
n
case Maybe NameShape
mb_nsubst of
Maybe NameShape
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return IfaceTopBndr
n'
Just NameShape
nsubst ->
case NameShape -> IfaceTopBndr -> Maybe IfaceTopBndr
maybeSubstNameShape NameShape
nsubst IfaceTopBndr
n' of
Maybe IfaceTopBndr
Nothing ->
forall a. TcRnMessage -> ShIfM a
failWithRn forall a b. (a -> b) -> a -> b
$ IfaceTopBndr -> TcRnMessage
TcRnIdNotExportedFromLocalSig IfaceTopBndr
n'
Just IfaceTopBndr
n'' -> forall (m :: * -> *) a. Monad m => a -> m a
return IfaceTopBndr
n''
| Bool -> Bool
not (forall u. GenModule (GenUnit u) -> Bool
isHoleModule Module
m)
-> forall m n. Maybe Module -> IfaceTopBndr -> TcRnIf m n IfaceTopBndr
setNameModule (forall a. a -> Maybe a
Just Module
m') IfaceTopBndr
n
| Bool
otherwise
-> do
let m'' :: Module
m'' = if forall u. GenModule (GenUnit u) -> Bool
isHoleModule Module
m'
then HomeUnit -> ModuleName -> Module
mkHomeModule HomeUnit
home_unit (forall unit. GenModule unit -> ModuleName
moduleName Module
m')
else Module
m'
ModIface
iface <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. SDoc -> HscEnv -> IfG a -> IO a
initIfaceCheck (String -> SDoc
text String
"rnIfaceGlobal") HscEnv
hsc_env
forall a b. (a -> b) -> a -> b
$ forall lcl. SDoc -> Module -> IfM lcl ModIface
loadSysInterface (String -> SDoc
text String
"rnIfaceGlobal") Module
m''
let nsubst :: NameShape
nsubst = ModuleName -> [AvailInfo] -> NameShape
mkNameShape (forall unit. GenModule unit -> ModuleName
moduleName Module
m) (forall (phase :: ModIfacePhase). ModIface_ phase -> [AvailInfo]
mi_exports ModIface
iface)
case NameShape -> IfaceTopBndr -> Maybe IfaceTopBndr
maybeSubstNameShape NameShape
nsubst IfaceTopBndr
n of
Maybe IfaceTopBndr
Nothing -> forall a. TcRnMessage -> ShIfM a
failWithRn forall a b. (a -> b) -> a -> b
$ IfaceTopBndr -> Module -> TcRnMessage
TcRnIdNotExportedFromModuleSig IfaceTopBndr
n Module
m'
Just IfaceTopBndr
n' -> forall (m :: * -> *) a. Monad m => a -> m a
return IfaceTopBndr
n'
rnIfaceNeverExported :: Name -> ShIfM Name
rnIfaceNeverExported :: IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceNeverExported IfaceTopBndr
name = do
ShHoleSubst
hmap <- ShIfM ShHoleSubst
getHoleSubst
UnitState
unit_state <- HasDebugCallStack => HscEnv -> UnitState
hsc_units forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall gbl lcl. TcRnIf gbl lcl HscEnv
getTopEnv
Module
iface_semantic_mod <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShIfEnv -> Module
sh_if_semantic_module forall gbl lcl. TcRnIf gbl lcl gbl
getGblEnv
let m :: Module
m = UnitState -> ShHoleSubst -> Module -> Module
renameHoleModule UnitState
unit_state ShHoleSubst
hmap forall a b. (a -> b) -> a -> b
$ HasDebugCallStack => IfaceTopBndr -> Module
nameModule IfaceTopBndr
name
forall (m :: * -> *).
(HasCallStack, Applicative m) =>
Bool -> SDoc -> m ()
massertPpr (Module
iface_semantic_mod forall a. Eq a => a -> a -> Bool
== Module
m) (forall a. Outputable a => a -> SDoc
ppr Module
iface_semantic_mod SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Module
m)
forall m n. Maybe Module -> IfaceTopBndr -> TcRnIf m n IfaceTopBndr
setNameModule (forall a. a -> Maybe a
Just Module
m) IfaceTopBndr
name
rnIfaceClsInst :: Rename IfaceClsInst
rnIfaceClsInst :: Rename IfaceClsInst
rnIfaceClsInst IfaceClsInst
cls_inst = do
IfaceTopBndr
n <- IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceGlobal (IfaceClsInst -> IfaceTopBndr
ifInstCls IfaceClsInst
cls_inst)
[Maybe IfaceTyCon]
tys <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename (Maybe IfaceTyCon)
rnRoughMatchTyCon (IfaceClsInst -> [Maybe IfaceTyCon]
ifInstTys IfaceClsInst
cls_inst)
IfaceTopBndr
dfun <- IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceNeverExported (IfaceClsInst -> IfaceTopBndr
ifDFun IfaceClsInst
cls_inst)
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceClsInst
cls_inst { ifInstCls :: IfaceTopBndr
ifInstCls = IfaceTopBndr
n
, ifInstTys :: [Maybe IfaceTyCon]
ifInstTys = [Maybe IfaceTyCon]
tys
, ifDFun :: IfaceTopBndr
ifDFun = IfaceTopBndr
dfun
}
rnRoughMatchTyCon :: Rename (Maybe IfaceTyCon)
rnRoughMatchTyCon :: Rename (Maybe IfaceTyCon)
rnRoughMatchTyCon Maybe IfaceTyCon
Nothing = forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
rnRoughMatchTyCon (Just IfaceTyCon
tc) = forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceTyCon
rnIfaceTyCon IfaceTyCon
tc
rnIfaceFamInst :: Rename IfaceFamInst
rnIfaceFamInst :: Rename IfaceFamInst
rnIfaceFamInst IfaceFamInst
d = do
IfaceTopBndr
fam <- IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceGlobal (IfaceFamInst -> IfaceTopBndr
ifFamInstFam IfaceFamInst
d)
[Maybe IfaceTyCon]
tys <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename (Maybe IfaceTyCon)
rnRoughMatchTyCon (IfaceFamInst -> [Maybe IfaceTyCon]
ifFamInstTys IfaceFamInst
d)
IfaceTopBndr
axiom <- IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceGlobal (IfaceFamInst -> IfaceTopBndr
ifFamInstAxiom IfaceFamInst
d)
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceFamInst
d { ifFamInstFam :: IfaceTopBndr
ifFamInstFam = IfaceTopBndr
fam, ifFamInstTys :: [Maybe IfaceTyCon]
ifFamInstTys = [Maybe IfaceTyCon]
tys, ifFamInstAxiom :: IfaceTopBndr
ifFamInstAxiom = IfaceTopBndr
axiom }
rnIfaceDecl' :: Rename (Fingerprint, IfaceDecl)
rnIfaceDecl' :: Rename (Fingerprint, IfaceDecl)
rnIfaceDecl' (Fingerprint
fp, IfaceDecl
decl) = (,) Fingerprint
fp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceDecl
rnIfaceDecl IfaceDecl
decl
rnIfaceDecl :: Rename IfaceDecl
rnIfaceDecl :: Rename IfaceDecl
rnIfaceDecl d :: IfaceDecl
d@IfaceId{} = do
IfaceTopBndr
name <- case IfaceDecl -> IfaceIdDetails
ifIdDetails IfaceDecl
d of
IfaceIdDetails
IfDFunId -> IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceNeverExported (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d)
IfaceIdDetails
_ | OccName -> Bool
isDefaultMethodOcc (forall name. HasOccName name => name -> OccName
occName (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d))
-> IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceNeverExported (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d)
IfaceIdDetails
_ | OccName -> Bool
isTypeableBindOcc (forall name. HasOccName name => name -> OccName
occName (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d))
-> IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceNeverExported (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d)
| Bool
otherwise -> IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceGlobal (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d)
IfaceType
ty <- Rename IfaceType
rnIfaceType (IfaceDecl -> IfaceType
ifType IfaceDecl
d)
IfaceIdDetails
details <- Rename IfaceIdDetails
rnIfaceIdDetails (IfaceDecl -> IfaceIdDetails
ifIdDetails IfaceDecl
d)
IfaceIdInfo
info <- Rename IfaceIdInfo
rnIfaceIdInfo (IfaceDecl -> IfaceIdInfo
ifIdInfo IfaceDecl
d)
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName :: IfaceTopBndr
ifName = IfaceTopBndr
name
, ifType :: IfaceType
ifType = IfaceType
ty
, ifIdDetails :: IfaceIdDetails
ifIdDetails = IfaceIdDetails
details
, ifIdInfo :: IfaceIdInfo
ifIdInfo = IfaceIdInfo
info
}
rnIfaceDecl d :: IfaceDecl
d@IfaceData{} = do
IfaceTopBndr
name <- IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceGlobal (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d)
[IfaceTyConBinder]
binders <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceTyConBinder
rnIfaceTyConBinder (IfaceDecl -> [IfaceTyConBinder]
ifBinders IfaceDecl
d)
[IfaceType]
ctxt <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceType
rnIfaceType (IfaceDecl -> [IfaceType]
ifCtxt IfaceDecl
d)
IfaceConDecls
cons <- Rename IfaceConDecls
rnIfaceConDecls (IfaceDecl -> IfaceConDecls
ifCons IfaceDecl
d)
IfaceType
res_kind <- Rename IfaceType
rnIfaceType (IfaceDecl -> IfaceType
ifResKind IfaceDecl
d)
IfaceTyConParent
parent <- Rename IfaceTyConParent
rnIfaceTyConParent (IfaceDecl -> IfaceTyConParent
ifParent IfaceDecl
d)
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName :: IfaceTopBndr
ifName = IfaceTopBndr
name
, ifBinders :: [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
binders
, ifCtxt :: [IfaceType]
ifCtxt = [IfaceType]
ctxt
, ifCons :: IfaceConDecls
ifCons = IfaceConDecls
cons
, ifResKind :: IfaceType
ifResKind = IfaceType
res_kind
, ifParent :: IfaceTyConParent
ifParent = IfaceTyConParent
parent
}
rnIfaceDecl d :: IfaceDecl
d@IfaceSynonym{} = do
IfaceTopBndr
name <- IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceGlobal (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d)
[IfaceTyConBinder]
binders <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceTyConBinder
rnIfaceTyConBinder (IfaceDecl -> [IfaceTyConBinder]
ifBinders IfaceDecl
d)
IfaceType
syn_kind <- Rename IfaceType
rnIfaceType (IfaceDecl -> IfaceType
ifResKind IfaceDecl
d)
IfaceType
syn_rhs <- Rename IfaceType
rnIfaceType (IfaceDecl -> IfaceType
ifSynRhs IfaceDecl
d)
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName :: IfaceTopBndr
ifName = IfaceTopBndr
name
, ifBinders :: [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
binders
, ifResKind :: IfaceType
ifResKind = IfaceType
syn_kind
, ifSynRhs :: IfaceType
ifSynRhs = IfaceType
syn_rhs
}
rnIfaceDecl d :: IfaceDecl
d@IfaceFamily{} = do
IfaceTopBndr
name <- IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceGlobal (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d)
[IfaceTyConBinder]
binders <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceTyConBinder
rnIfaceTyConBinder (IfaceDecl -> [IfaceTyConBinder]
ifBinders IfaceDecl
d)
IfaceType
fam_kind <- Rename IfaceType
rnIfaceType (IfaceDecl -> IfaceType
ifResKind IfaceDecl
d)
IfaceFamTyConFlav
fam_flav <- Rename IfaceFamTyConFlav
rnIfaceFamTyConFlav (IfaceDecl -> IfaceFamTyConFlav
ifFamFlav IfaceDecl
d)
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName :: IfaceTopBndr
ifName = IfaceTopBndr
name
, ifBinders :: [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
binders
, ifResKind :: IfaceType
ifResKind = IfaceType
fam_kind
, ifFamFlav :: IfaceFamTyConFlav
ifFamFlav = IfaceFamTyConFlav
fam_flav
}
rnIfaceDecl d :: IfaceDecl
d@IfaceClass{} = do
IfaceTopBndr
name <- IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceGlobal (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d)
[IfaceTyConBinder]
binders <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceTyConBinder
rnIfaceTyConBinder (IfaceDecl -> [IfaceTyConBinder]
ifBinders IfaceDecl
d)
IfaceClassBody
body <- Rename IfaceClassBody
rnIfaceClassBody (IfaceDecl -> IfaceClassBody
ifBody IfaceDecl
d)
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName :: IfaceTopBndr
ifName = IfaceTopBndr
name
, ifBinders :: [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
binders
, ifBody :: IfaceClassBody
ifBody = IfaceClassBody
body
}
rnIfaceDecl d :: IfaceDecl
d@IfaceAxiom{} = do
IfaceTopBndr
name <- IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceNeverExported (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d)
IfaceTyCon
tycon <- Rename IfaceTyCon
rnIfaceTyCon (IfaceDecl -> IfaceTyCon
ifTyCon IfaceDecl
d)
[IfaceAxBranch]
ax_branches <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceAxBranch
rnIfaceAxBranch (IfaceDecl -> [IfaceAxBranch]
ifAxBranches IfaceDecl
d)
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName :: IfaceTopBndr
ifName = IfaceTopBndr
name
, ifTyCon :: IfaceTyCon
ifTyCon = IfaceTyCon
tycon
, ifAxBranches :: [IfaceAxBranch]
ifAxBranches = [IfaceAxBranch]
ax_branches
}
rnIfaceDecl d :: IfaceDecl
d@IfacePatSyn{} = do
IfaceTopBndr
name <- IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceGlobal (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d)
let rnPat :: (IfaceTopBndr, a) -> IOEnv (Env ShIfEnv ()) (IfaceTopBndr, a)
rnPat (IfaceTopBndr
n, a
b) = (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceGlobal IfaceTopBndr
n forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure a
b
(IfaceTopBndr, Bool)
pat_matcher <- forall {a}.
(IfaceTopBndr, a) -> IOEnv (Env ShIfEnv ()) (IfaceTopBndr, a)
rnPat (IfaceDecl -> (IfaceTopBndr, Bool)
ifPatMatcher IfaceDecl
d)
Maybe (IfaceTopBndr, Bool)
pat_builder <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
T.traverse forall {a}.
(IfaceTopBndr, a) -> IOEnv (Env ShIfEnv ()) (IfaceTopBndr, a)
rnPat (IfaceDecl -> Maybe (IfaceTopBndr, Bool)
ifPatBuilder IfaceDecl
d)
[VarBndr IfaceBndr Specificity]
pat_univ_bndrs <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall flag. Rename (VarBndr IfaceBndr flag)
rnIfaceForAllBndr (IfaceDecl -> [VarBndr IfaceBndr Specificity]
ifPatUnivBndrs IfaceDecl
d)
[VarBndr IfaceBndr Specificity]
pat_ex_bndrs <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall flag. Rename (VarBndr IfaceBndr flag)
rnIfaceForAllBndr (IfaceDecl -> [VarBndr IfaceBndr Specificity]
ifPatExBndrs IfaceDecl
d)
[IfaceType]
pat_prov_ctxt <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceType
rnIfaceType (IfaceDecl -> [IfaceType]
ifPatProvCtxt IfaceDecl
d)
[IfaceType]
pat_req_ctxt <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceType
rnIfaceType (IfaceDecl -> [IfaceType]
ifPatReqCtxt IfaceDecl
d)
[IfaceType]
pat_args <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceType
rnIfaceType (IfaceDecl -> [IfaceType]
ifPatArgs IfaceDecl
d)
IfaceType
pat_ty <- Rename IfaceType
rnIfaceType (IfaceDecl -> IfaceType
ifPatTy IfaceDecl
d)
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName :: IfaceTopBndr
ifName = IfaceTopBndr
name
, ifPatMatcher :: (IfaceTopBndr, Bool)
ifPatMatcher = (IfaceTopBndr, Bool)
pat_matcher
, ifPatBuilder :: Maybe (IfaceTopBndr, Bool)
ifPatBuilder = Maybe (IfaceTopBndr, Bool)
pat_builder
, ifPatUnivBndrs :: [VarBndr IfaceBndr Specificity]
ifPatUnivBndrs = [VarBndr IfaceBndr Specificity]
pat_univ_bndrs
, ifPatExBndrs :: [VarBndr IfaceBndr Specificity]
ifPatExBndrs = [VarBndr IfaceBndr Specificity]
pat_ex_bndrs
, ifPatProvCtxt :: [IfaceType]
ifPatProvCtxt = [IfaceType]
pat_prov_ctxt
, ifPatReqCtxt :: [IfaceType]
ifPatReqCtxt = [IfaceType]
pat_req_ctxt
, ifPatArgs :: [IfaceType]
ifPatArgs = [IfaceType]
pat_args
, ifPatTy :: IfaceType
ifPatTy = IfaceType
pat_ty
}
rnIfaceClassBody :: Rename IfaceClassBody
rnIfaceClassBody :: Rename IfaceClassBody
rnIfaceClassBody IfaceClassBody
IfAbstractClass = forall (m :: * -> *) a. Monad m => a -> m a
return IfaceClassBody
IfAbstractClass
rnIfaceClassBody d :: IfaceClassBody
d@IfConcreteClass{} = do
[IfaceType]
ctxt <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceType
rnIfaceType (IfaceClassBody -> [IfaceType]
ifClassCtxt IfaceClassBody
d)
[IfaceAT]
ats <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceAT
rnIfaceAT (IfaceClassBody -> [IfaceAT]
ifATs IfaceClassBody
d)
[IfaceClassOp]
sigs <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceClassOp
rnIfaceClassOp (IfaceClassBody -> [IfaceClassOp]
ifSigs IfaceClassBody
d)
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceClassBody
d { ifClassCtxt :: [IfaceType]
ifClassCtxt = [IfaceType]
ctxt, ifATs :: [IfaceAT]
ifATs = [IfaceAT]
ats, ifSigs :: [IfaceClassOp]
ifSigs = [IfaceClassOp]
sigs }
rnIfaceFamTyConFlav :: Rename IfaceFamTyConFlav
rnIfaceFamTyConFlav :: Rename IfaceFamTyConFlav
rnIfaceFamTyConFlav (IfaceClosedSynFamilyTyCon (Just (IfaceTopBndr
n, [IfaceAxBranch]
axs)))
= Maybe (IfaceTopBndr, [IfaceAxBranch]) -> IfaceFamTyConFlav
IfaceClosedSynFamilyTyCon forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceNeverExported IfaceTopBndr
n
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceAxBranch
rnIfaceAxBranch [IfaceAxBranch]
axs)
rnIfaceFamTyConFlav IfaceFamTyConFlav
flav = forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceFamTyConFlav
flav
rnIfaceAT :: Rename IfaceAT
rnIfaceAT :: Rename IfaceAT
rnIfaceAT (IfaceAT IfaceDecl
decl Maybe IfaceType
mb_ty)
= IfaceDecl -> Maybe IfaceType -> IfaceAT
IfaceAT forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceDecl
rnIfaceDecl IfaceDecl
decl forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
T.traverse Rename IfaceType
rnIfaceType Maybe IfaceType
mb_ty
rnIfaceTyConParent :: Rename IfaceTyConParent
rnIfaceTyConParent :: Rename IfaceTyConParent
rnIfaceTyConParent (IfDataInstance IfaceTopBndr
n IfaceTyCon
tc IfaceAppArgs
args)
= IfaceTopBndr -> IfaceTyCon -> IfaceAppArgs -> IfaceTyConParent
IfDataInstance forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceGlobal IfaceTopBndr
n
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceTyCon
rnIfaceTyCon IfaceTyCon
tc
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceAppArgs
rnIfaceAppArgs IfaceAppArgs
args
rnIfaceTyConParent IfaceTyConParent
IfNoParent = forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceTyConParent
IfNoParent
rnIfaceConDecls :: Rename IfaceConDecls
rnIfaceConDecls :: Rename IfaceConDecls
rnIfaceConDecls (IfDataTyCon [IfaceConDecl]
ds)
= [IfaceConDecl] -> IfaceConDecls
IfDataTyCon forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceConDecl
rnIfaceConDecl [IfaceConDecl]
ds
rnIfaceConDecls (IfNewTyCon IfaceConDecl
d) = IfaceConDecl -> IfaceConDecls
IfNewTyCon forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceConDecl
rnIfaceConDecl IfaceConDecl
d
rnIfaceConDecls IfaceConDecls
IfAbstractTyCon = forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceConDecls
IfAbstractTyCon
rnIfaceConDecl :: Rename IfaceConDecl
rnIfaceConDecl :: Rename IfaceConDecl
rnIfaceConDecl IfaceConDecl
d = do
IfaceTopBndr
con_name <- IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceGlobal (IfaceConDecl -> IfaceTopBndr
ifConName IfaceConDecl
d)
[IfaceBndr]
con_ex_tvs <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceBndr
rnIfaceBndr (IfaceConDecl -> [IfaceBndr]
ifConExTCvs IfaceConDecl
d)
[VarBndr IfaceBndr Specificity]
con_user_tvbs <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall flag. Rename (VarBndr IfaceBndr flag)
rnIfaceForAllBndr (IfaceConDecl -> [VarBndr IfaceBndr Specificity]
ifConUserTvBinders IfaceConDecl
d)
let rnIfConEqSpec :: (a, IfaceType) -> IOEnv (Env ShIfEnv ()) (a, IfaceType)
rnIfConEqSpec (a
n,IfaceType
t) = (,) a
n forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
t
[(IfLclName, IfaceType)]
con_eq_spec <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall {a}. (a, IfaceType) -> IOEnv (Env ShIfEnv ()) (a, IfaceType)
rnIfConEqSpec (IfaceConDecl -> [(IfLclName, IfaceType)]
ifConEqSpec IfaceConDecl
d)
[IfaceType]
con_ctxt <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceType
rnIfaceType (IfaceConDecl -> [IfaceType]
ifConCtxt IfaceConDecl
d)
[(IfaceType, IfaceType)]
con_arg_tys <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename (IfaceType, IfaceType)
rnIfaceScaledType (IfaceConDecl -> [(IfaceType, IfaceType)]
ifConArgTys IfaceConDecl
d)
[FieldLabel]
con_fields <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename FieldLabel
rnFieldLabel (IfaceConDecl -> [FieldLabel]
ifConFields IfaceConDecl
d)
let rnIfaceBang :: IfaceBang -> IOEnv (Env ShIfEnv ()) IfaceBang
rnIfaceBang (IfUnpackCo IfaceCoercion
co) = IfaceCoercion -> IfaceBang
IfUnpackCo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co
rnIfaceBang IfaceBang
bang = forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceBang
bang
[IfaceBang]
con_stricts <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM IfaceBang -> IOEnv (Env ShIfEnv ()) IfaceBang
rnIfaceBang (IfaceConDecl -> [IfaceBang]
ifConStricts IfaceConDecl
d)
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceConDecl
d { ifConName :: IfaceTopBndr
ifConName = IfaceTopBndr
con_name
, ifConExTCvs :: [IfaceBndr]
ifConExTCvs = [IfaceBndr]
con_ex_tvs
, ifConUserTvBinders :: [VarBndr IfaceBndr Specificity]
ifConUserTvBinders = [VarBndr IfaceBndr Specificity]
con_user_tvbs
, ifConEqSpec :: [(IfLclName, IfaceType)]
ifConEqSpec = [(IfLclName, IfaceType)]
con_eq_spec
, ifConCtxt :: [IfaceType]
ifConCtxt = [IfaceType]
con_ctxt
, ifConArgTys :: [(IfaceType, IfaceType)]
ifConArgTys = [(IfaceType, IfaceType)]
con_arg_tys
, ifConFields :: [FieldLabel]
ifConFields = [FieldLabel]
con_fields
, ifConStricts :: [IfaceBang]
ifConStricts = [IfaceBang]
con_stricts
}
rnIfaceClassOp :: Rename IfaceClassOp
rnIfaceClassOp :: Rename IfaceClassOp
rnIfaceClassOp (IfaceClassOp IfaceTopBndr
n IfaceType
ty Maybe (DefMethSpec IfaceType)
dm) =
IfaceTopBndr
-> IfaceType -> Maybe (DefMethSpec IfaceType) -> IfaceClassOp
IfaceClassOp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceGlobal IfaceTopBndr
n
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceType
rnIfaceType IfaceType
ty
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename (Maybe (DefMethSpec IfaceType))
rnMaybeDefMethSpec Maybe (DefMethSpec IfaceType)
dm
rnMaybeDefMethSpec :: Rename (Maybe (DefMethSpec IfaceType))
rnMaybeDefMethSpec :: Rename (Maybe (DefMethSpec IfaceType))
rnMaybeDefMethSpec (Just (GenericDM IfaceType
ty)) = forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall ty. ty -> DefMethSpec ty
GenericDM forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
ty
rnMaybeDefMethSpec Maybe (DefMethSpec IfaceType)
mb = forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (DefMethSpec IfaceType)
mb
rnIfaceAxBranch :: Rename IfaceAxBranch
rnIfaceAxBranch :: Rename IfaceAxBranch
rnIfaceAxBranch IfaceAxBranch
d = do
[(IfLclName, IfaceType)]
ty_vars <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename (IfLclName, IfaceType)
rnIfaceTvBndr (IfaceAxBranch -> [(IfLclName, IfaceType)]
ifaxbTyVars IfaceAxBranch
d)
IfaceAppArgs
lhs <- Rename IfaceAppArgs
rnIfaceAppArgs (IfaceAxBranch -> IfaceAppArgs
ifaxbLHS IfaceAxBranch
d)
IfaceType
rhs <- Rename IfaceType
rnIfaceType (IfaceAxBranch -> IfaceType
ifaxbRHS IfaceAxBranch
d)
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceAxBranch
d { ifaxbTyVars :: [(IfLclName, IfaceType)]
ifaxbTyVars = [(IfLclName, IfaceType)]
ty_vars
, ifaxbLHS :: IfaceAppArgs
ifaxbLHS = IfaceAppArgs
lhs
, ifaxbRHS :: IfaceType
ifaxbRHS = IfaceType
rhs }
rnIfaceIdInfo :: Rename IfaceIdInfo
rnIfaceIdInfo :: Rename IfaceIdInfo
rnIfaceIdInfo = forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceInfoItem
rnIfaceInfoItem
rnIfaceInfoItem :: Rename IfaceInfoItem
rnIfaceInfoItem :: Rename IfaceInfoItem
rnIfaceInfoItem (HsUnfold Bool
lb IfaceUnfolding
if_unf)
= Bool -> IfaceUnfolding -> IfaceInfoItem
HsUnfold Bool
lb forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceUnfolding
rnIfaceUnfolding IfaceUnfolding
if_unf
rnIfaceInfoItem IfaceInfoItem
i
= forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceInfoItem
i
rnIfaceUnfolding :: Rename IfaceUnfolding
rnIfaceUnfolding :: Rename IfaceUnfolding
rnIfaceUnfolding (IfCoreUnfold Bool
stable IfUnfoldingCache
cache IfaceExpr
if_expr)
= Bool -> IfUnfoldingCache -> IfaceExpr -> IfaceUnfolding
IfCoreUnfold Bool
stable IfUnfoldingCache
cache forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceExpr
rnIfaceExpr IfaceExpr
if_expr
rnIfaceUnfolding (IfCompulsory IfaceExpr
if_expr)
= IfaceExpr -> IfaceUnfolding
IfCompulsory forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceExpr
rnIfaceExpr IfaceExpr
if_expr
rnIfaceUnfolding (IfInlineRule Arity
arity Bool
unsat_ok Bool
boring_ok IfaceExpr
if_expr)
= Arity -> Bool -> Bool -> IfaceExpr -> IfaceUnfolding
IfInlineRule Arity
arity Bool
unsat_ok Bool
boring_ok forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceExpr
rnIfaceExpr IfaceExpr
if_expr
rnIfaceUnfolding (IfDFunUnfold [IfaceBndr]
bs [IfaceExpr]
ops)
= [IfaceBndr] -> [IfaceExpr] -> IfaceUnfolding
IfDFunUnfold forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename [IfaceBndr]
rnIfaceBndrs [IfaceBndr]
bs forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceExpr
rnIfaceExpr [IfaceExpr]
ops
rnIfaceExpr :: Rename IfaceExpr
rnIfaceExpr :: Rename IfaceExpr
rnIfaceExpr (IfaceLcl IfLclName
name) = forall (f :: * -> *) a. Applicative f => a -> f a
pure (IfLclName -> IfaceExpr
IfaceLcl IfLclName
name)
rnIfaceExpr (IfaceExt IfaceTopBndr
gbl) = IfaceTopBndr -> IfaceExpr
IfaceExt forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceGlobal IfaceTopBndr
gbl
rnIfaceExpr (IfaceType IfaceType
ty) = IfaceType -> IfaceExpr
IfaceType forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
ty
rnIfaceExpr (IfaceCo IfaceCoercion
co) = IfaceCoercion -> IfaceExpr
IfaceCo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co
rnIfaceExpr (IfaceTuple TupleSort
sort [IfaceExpr]
args) = TupleSort -> [IfaceExpr] -> IfaceExpr
IfaceTuple TupleSort
sort forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename [IfaceExpr]
rnIfaceExprs [IfaceExpr]
args
rnIfaceExpr (IfaceLam IfaceLamBndr
lam_bndr IfaceExpr
expr)
= IfaceLamBndr -> IfaceExpr -> IfaceExpr
IfaceLam forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceLamBndr
rnIfaceLamBndr IfaceLamBndr
lam_bndr forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceExpr
rnIfaceExpr IfaceExpr
expr
rnIfaceExpr (IfaceApp IfaceExpr
fun IfaceExpr
arg)
= IfaceExpr -> IfaceExpr -> IfaceExpr
IfaceApp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceExpr
rnIfaceExpr IfaceExpr
fun forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceExpr
rnIfaceExpr IfaceExpr
arg
rnIfaceExpr (IfaceCase IfaceExpr
scrut IfLclName
case_bndr [IfaceAlt]
alts)
= IfaceExpr -> IfLclName -> [IfaceAlt] -> IfaceExpr
IfaceCase forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceExpr
rnIfaceExpr IfaceExpr
scrut
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure IfLclName
case_bndr
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceAlt
rnIfaceAlt [IfaceAlt]
alts
rnIfaceExpr (IfaceECase IfaceExpr
scrut IfaceType
ty)
= IfaceExpr -> IfaceType -> IfaceExpr
IfaceECase forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceExpr
rnIfaceExpr IfaceExpr
scrut forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceType
rnIfaceType IfaceType
ty
rnIfaceExpr (IfaceLet (IfaceNonRec IfaceLetBndr
bndr IfaceExpr
rhs) IfaceExpr
body)
= IfaceBinding -> IfaceExpr -> IfaceExpr
IfaceLet forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (IfaceLetBndr -> IfaceExpr -> IfaceBinding
IfaceNonRec forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceLetBndr
rnIfaceLetBndr IfaceLetBndr
bndr forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceExpr
rnIfaceExpr IfaceExpr
rhs)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceExpr
rnIfaceExpr IfaceExpr
body
rnIfaceExpr (IfaceLet (IfaceRec [(IfaceLetBndr, IfaceExpr)]
pairs) IfaceExpr
body)
= IfaceBinding -> IfaceExpr -> IfaceExpr
IfaceLet forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([(IfaceLetBndr, IfaceExpr)] -> IfaceBinding
IfaceRec forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (\(IfaceLetBndr
bndr, IfaceExpr
rhs) ->
(,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceLetBndr
rnIfaceLetBndr IfaceLetBndr
bndr
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceExpr
rnIfaceExpr IfaceExpr
rhs) [(IfaceLetBndr, IfaceExpr)]
pairs)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceExpr
rnIfaceExpr IfaceExpr
body
rnIfaceExpr (IfaceCast IfaceExpr
expr IfaceCoercion
co)
= IfaceExpr -> IfaceCoercion -> IfaceExpr
IfaceCast forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceExpr
rnIfaceExpr IfaceExpr
expr forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co
rnIfaceExpr (IfaceLit Literal
lit) = forall (f :: * -> *) a. Applicative f => a -> f a
pure (Literal -> IfaceExpr
IfaceLit Literal
lit)
rnIfaceExpr (IfaceLitRubbish IfaceType
rep) = IfaceType -> IfaceExpr
IfaceLitRubbish forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
rep
rnIfaceExpr (IfaceFCall ForeignCall
cc IfaceType
ty) = ForeignCall -> IfaceType -> IfaceExpr
IfaceFCall ForeignCall
cc forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
ty
rnIfaceExpr (IfaceTick IfaceTickish
tickish IfaceExpr
expr) = IfaceTickish -> IfaceExpr -> IfaceExpr
IfaceTick IfaceTickish
tickish forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceExpr
rnIfaceExpr IfaceExpr
expr
rnIfaceBndrs :: Rename [IfaceBndr]
rnIfaceBndrs :: Rename [IfaceBndr]
rnIfaceBndrs = forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceBndr
rnIfaceBndr
rnIfaceBndr :: Rename IfaceBndr
rnIfaceBndr :: Rename IfaceBndr
rnIfaceBndr (IfaceIdBndr (IfaceType
w, IfLclName
fs, IfaceType
ty)) = (IfaceType, IfLclName, IfaceType) -> IfaceBndr
IfaceIdBndr forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((,,) IfaceType
w IfLclName
fs forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
ty)
rnIfaceBndr (IfaceTvBndr (IfLclName, IfaceType)
tv_bndr) = (IfLclName, IfaceType) -> IfaceBndr
IfaceTvBndr forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename (IfLclName, IfaceType)
rnIfaceTvBndr (IfLclName, IfaceType)
tv_bndr
rnIfaceTvBndr :: Rename IfaceTvBndr
rnIfaceTvBndr :: Rename (IfLclName, IfaceType)
rnIfaceTvBndr (IfLclName
fs, IfaceType
kind) = (,) IfLclName
fs forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
kind
rnIfaceTyConBinder :: Rename IfaceTyConBinder
rnIfaceTyConBinder :: Rename IfaceTyConBinder
rnIfaceTyConBinder (Bndr IfaceBndr
tv TyConBndrVis
vis) = forall var argf. var -> argf -> VarBndr var argf
Bndr forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceBndr
rnIfaceBndr IfaceBndr
tv forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure TyConBndrVis
vis
rnIfaceAlt :: Rename IfaceAlt
rnIfaceAlt :: Rename IfaceAlt
rnIfaceAlt (IfaceAlt IfaceConAlt
conalt [IfLclName]
names IfaceExpr
rhs)
= IfaceConAlt -> [IfLclName] -> IfaceExpr -> IfaceAlt
IfaceAlt forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceConAlt
rnIfaceConAlt IfaceConAlt
conalt forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure [IfLclName]
names forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceExpr
rnIfaceExpr IfaceExpr
rhs
rnIfaceConAlt :: Rename IfaceConAlt
rnIfaceConAlt :: Rename IfaceConAlt
rnIfaceConAlt (IfaceDataAlt IfaceTopBndr
data_occ) = IfaceTopBndr -> IfaceConAlt
IfaceDataAlt forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceGlobal IfaceTopBndr
data_occ
rnIfaceConAlt IfaceConAlt
alt = forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceConAlt
alt
rnIfaceLetBndr :: Rename IfaceLetBndr
rnIfaceLetBndr :: Rename IfaceLetBndr
rnIfaceLetBndr (IfLetBndr IfLclName
fs IfaceType
ty IfaceIdInfo
info IfaceJoinInfo
jpi)
= IfLclName
-> IfaceType -> IfaceIdInfo -> IfaceJoinInfo -> IfaceLetBndr
IfLetBndr IfLclName
fs forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
ty forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceIdInfo
rnIfaceIdInfo IfaceIdInfo
info forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceJoinInfo
jpi
rnIfaceLamBndr :: Rename IfaceLamBndr
rnIfaceLamBndr :: Rename IfaceLamBndr
rnIfaceLamBndr (IfaceBndr
bndr, IfaceOneShot
oneshot) = (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceBndr
rnIfaceBndr IfaceBndr
bndr forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceOneShot
oneshot
rnIfaceMCo :: Rename IfaceMCoercion
rnIfaceMCo :: Rename IfaceMCoercion
rnIfaceMCo IfaceMCoercion
IfaceMRefl = forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceMCoercion
IfaceMRefl
rnIfaceMCo (IfaceMCo IfaceCoercion
co) = IfaceCoercion -> IfaceMCoercion
IfaceMCo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co
rnIfaceCo :: Rename IfaceCoercion
rnIfaceCo :: Rename IfaceCoercion
rnIfaceCo (IfaceReflCo IfaceType
ty) = IfaceType -> IfaceCoercion
IfaceReflCo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
ty
rnIfaceCo (IfaceGReflCo Role
role IfaceType
ty IfaceMCoercion
mco)
= Role -> IfaceType -> IfaceMCoercion -> IfaceCoercion
IfaceGReflCo Role
role forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
ty forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceMCoercion
rnIfaceMCo IfaceMCoercion
mco
rnIfaceCo (IfaceFunCo Role
role IfaceCoercion
w IfaceCoercion
co1 IfaceCoercion
co2)
= Role
-> IfaceCoercion -> IfaceCoercion -> IfaceCoercion -> IfaceCoercion
IfaceFunCo Role
role forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
w forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co1 forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co2
rnIfaceCo (IfaceTyConAppCo Role
role IfaceTyCon
tc [IfaceCoercion]
cos)
= Role -> IfaceTyCon -> [IfaceCoercion] -> IfaceCoercion
IfaceTyConAppCo Role
role forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceTyCon
rnIfaceTyCon IfaceTyCon
tc forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceCoercion
rnIfaceCo [IfaceCoercion]
cos
rnIfaceCo (IfaceAppCo IfaceCoercion
co1 IfaceCoercion
co2)
= IfaceCoercion -> IfaceCoercion -> IfaceCoercion
IfaceAppCo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co1 forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co2
rnIfaceCo (IfaceForAllCo IfaceBndr
bndr IfaceCoercion
co1 IfaceCoercion
co2)
= IfaceBndr -> IfaceCoercion -> IfaceCoercion -> IfaceCoercion
IfaceForAllCo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceBndr
rnIfaceBndr IfaceBndr
bndr forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co1 forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co2
rnIfaceCo (IfaceFreeCoVar CoVar
c) = forall (f :: * -> *) a. Applicative f => a -> f a
pure (CoVar -> IfaceCoercion
IfaceFreeCoVar CoVar
c)
rnIfaceCo (IfaceCoVarCo IfLclName
lcl) = IfLclName -> IfaceCoercion
IfaceCoVarCo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure IfLclName
lcl
rnIfaceCo (IfaceHoleCo CoVar
lcl) = CoVar -> IfaceCoercion
IfaceHoleCo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure CoVar
lcl
rnIfaceCo (IfaceAxiomInstCo IfaceTopBndr
n Arity
i [IfaceCoercion]
cs)
= IfaceTopBndr -> Arity -> [IfaceCoercion] -> IfaceCoercion
IfaceAxiomInstCo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceGlobal IfaceTopBndr
n forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure Arity
i forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceCoercion
rnIfaceCo [IfaceCoercion]
cs
rnIfaceCo (IfaceUnivCo IfaceUnivCoProv
s Role
r IfaceType
t1 IfaceType
t2)
= IfaceUnivCoProv -> Role -> IfaceType -> IfaceType -> IfaceCoercion
IfaceUnivCo IfaceUnivCoProv
s Role
r forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
t1 forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceType
rnIfaceType IfaceType
t2
rnIfaceCo (IfaceSymCo IfaceCoercion
c)
= IfaceCoercion -> IfaceCoercion
IfaceSymCo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
c
rnIfaceCo (IfaceTransCo IfaceCoercion
c1 IfaceCoercion
c2)
= IfaceCoercion -> IfaceCoercion -> IfaceCoercion
IfaceTransCo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
c1 forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
c2
rnIfaceCo (IfaceInstCo IfaceCoercion
c1 IfaceCoercion
c2)
= IfaceCoercion -> IfaceCoercion -> IfaceCoercion
IfaceInstCo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
c1 forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
c2
rnIfaceCo (IfaceNthCo Arity
d IfaceCoercion
c) = Arity -> IfaceCoercion -> IfaceCoercion
IfaceNthCo Arity
d forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
c
rnIfaceCo (IfaceLRCo LeftOrRight
lr IfaceCoercion
c) = LeftOrRight -> IfaceCoercion -> IfaceCoercion
IfaceLRCo LeftOrRight
lr forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
c
rnIfaceCo (IfaceSubCo IfaceCoercion
c) = IfaceCoercion -> IfaceCoercion
IfaceSubCo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
c
rnIfaceCo (IfaceAxiomRuleCo IfLclName
ax [IfaceCoercion]
cos)
= IfLclName -> [IfaceCoercion] -> IfaceCoercion
IfaceAxiomRuleCo IfLclName
ax forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceCoercion
rnIfaceCo [IfaceCoercion]
cos
rnIfaceCo (IfaceKindCo IfaceCoercion
c) = IfaceCoercion -> IfaceCoercion
IfaceKindCo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
c
rnIfaceTyCon :: Rename IfaceTyCon
rnIfaceTyCon :: Rename IfaceTyCon
rnIfaceTyCon (IfaceTyCon IfaceTopBndr
n IfaceTyConInfo
info)
= IfaceTopBndr -> IfaceTyConInfo -> IfaceTyCon
IfaceTyCon forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceTopBndr -> ShIfM IfaceTopBndr
rnIfaceGlobal IfaceTopBndr
n forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceTyConInfo
info
rnIfaceExprs :: Rename [IfaceExpr]
rnIfaceExprs :: Rename [IfaceExpr]
rnIfaceExprs = forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceExpr
rnIfaceExpr
rnIfaceIdDetails :: Rename IfaceIdDetails
rnIfaceIdDetails :: Rename IfaceIdDetails
rnIfaceIdDetails (IfRecSelId (Left IfaceTyCon
tc) Bool
b) = Either IfaceTyCon IfaceDecl -> Bool -> IfaceIdDetails
IfRecSelId forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. a -> Either a b
Left (Rename IfaceTyCon
rnIfaceTyCon IfaceTyCon
tc) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
b
rnIfaceIdDetails (IfRecSelId (Right IfaceDecl
decl) Bool
b) = Either IfaceTyCon IfaceDecl -> Bool -> IfaceIdDetails
IfRecSelId forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. b -> Either a b
Right (Rename IfaceDecl
rnIfaceDecl IfaceDecl
decl) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
b
rnIfaceIdDetails IfaceIdDetails
details = forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceIdDetails
details
rnIfaceType :: Rename IfaceType
rnIfaceType :: Rename IfaceType
rnIfaceType (IfaceFreeTyVar CoVar
n) = forall (f :: * -> *) a. Applicative f => a -> f a
pure (CoVar -> IfaceType
IfaceFreeTyVar CoVar
n)
rnIfaceType (IfaceTyVar IfLclName
n) = forall (f :: * -> *) a. Applicative f => a -> f a
pure (IfLclName -> IfaceType
IfaceTyVar IfLclName
n)
rnIfaceType (IfaceAppTy IfaceType
t1 IfaceAppArgs
t2)
= IfaceType -> IfaceAppArgs -> IfaceType
IfaceAppTy forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
t1 forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceAppArgs
rnIfaceAppArgs IfaceAppArgs
t2
rnIfaceType (IfaceLitTy IfaceTyLit
l) = forall (m :: * -> *) a. Monad m => a -> m a
return (IfaceTyLit -> IfaceType
IfaceLitTy IfaceTyLit
l)
rnIfaceType (IfaceFunTy AnonArgFlag
af IfaceType
w IfaceType
t1 IfaceType
t2)
= AnonArgFlag -> IfaceType -> IfaceType -> IfaceType -> IfaceType
IfaceFunTy AnonArgFlag
af forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
w forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceType
rnIfaceType IfaceType
t1 forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceType
rnIfaceType IfaceType
t2
rnIfaceType (IfaceTupleTy TupleSort
s PromotionFlag
i IfaceAppArgs
tks)
= TupleSort -> PromotionFlag -> IfaceAppArgs -> IfaceType
IfaceTupleTy TupleSort
s PromotionFlag
i forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceAppArgs
rnIfaceAppArgs IfaceAppArgs
tks
rnIfaceType (IfaceTyConApp IfaceTyCon
tc IfaceAppArgs
tks)
= IfaceTyCon -> IfaceAppArgs -> IfaceType
IfaceTyConApp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceTyCon
rnIfaceTyCon IfaceTyCon
tc forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceAppArgs
rnIfaceAppArgs IfaceAppArgs
tks
rnIfaceType (IfaceForAllTy IfaceForAllBndr
tv IfaceType
t)
= IfaceForAllBndr -> IfaceType -> IfaceType
IfaceForAllTy forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall flag. Rename (VarBndr IfaceBndr flag)
rnIfaceForAllBndr IfaceForAllBndr
tv forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceType
rnIfaceType IfaceType
t
rnIfaceType (IfaceCoercionTy IfaceCoercion
co)
= IfaceCoercion -> IfaceType
IfaceCoercionTy forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co
rnIfaceType (IfaceCastTy IfaceType
ty IfaceCoercion
co)
= IfaceType -> IfaceCoercion -> IfaceType
IfaceCastTy forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
ty forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co
rnIfaceScaledType :: Rename (IfaceMult, IfaceType)
rnIfaceScaledType :: Rename (IfaceType, IfaceType)
rnIfaceScaledType (IfaceType
m, IfaceType
t) = (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
m forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceType
rnIfaceType IfaceType
t
rnIfaceForAllBndr :: Rename (VarBndr IfaceBndr flag)
rnIfaceForAllBndr :: forall flag. Rename (VarBndr IfaceBndr flag)
rnIfaceForAllBndr (Bndr IfaceBndr
tv flag
vis) = forall var argf. var -> argf -> VarBndr var argf
Bndr forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceBndr
rnIfaceBndr IfaceBndr
tv forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure flag
vis
rnIfaceAppArgs :: Rename IfaceAppArgs
rnIfaceAppArgs :: Rename IfaceAppArgs
rnIfaceAppArgs (IA_Arg IfaceType
t ArgFlag
a IfaceAppArgs
ts) = IfaceType -> ArgFlag -> IfaceAppArgs -> IfaceAppArgs
IA_Arg forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
t forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure ArgFlag
a
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceAppArgs
rnIfaceAppArgs IfaceAppArgs
ts
rnIfaceAppArgs IfaceAppArgs
IA_Nil = forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceAppArgs
IA_Nil