-- | This module implements interface renaming, which is
-- used to rewrite interface files on the fly when we
-- are doing indefinite typechecking and need instantiations
-- of modules which do not necessarily exist yet.

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 -- a bit vexing

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 <- IO (Either (Messages TcRnMessage) a)
-> IOEnv (Env TcGblEnv TcLclEnv) (Either (Messages TcRnMessage) a)
forall a. IO a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either (Messages TcRnMessage) a)
 -> IOEnv (Env TcGblEnv TcLclEnv) (Either (Messages TcRnMessage) a))
-> IO (Either (Messages TcRnMessage) a)
-> IOEnv (Env TcGblEnv TcLclEnv) (Either (Messages TcRnMessage) a)
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
            TcM a
forall env a. IOEnv env a
failM
        Right a
x -> a -> TcM a
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
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 <- TcRnIf TcGblEnv TcLclEnv HscEnv
forall gbl lcl. TcRnIf gbl lcl HscEnv
getTopEnv
    IO (Either (Messages TcRnMessage) ModIface) -> TcM ModIface
forall a. IO (Either (Messages TcRnMessage) a) -> TcM a
tcRnMsgMaybe (IO (Either (Messages TcRnMessage) ModIface) -> TcM ModIface)
-> IO (Either (Messages TcRnMessage) ModIface) -> TcM ModIface
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 <- TcRnIf TcGblEnv TcLclEnv HscEnv
forall gbl lcl. TcRnIf gbl lcl HscEnv
getTopEnv
    IO (Either (Messages TcRnMessage) [AvailInfo]) -> TcM [AvailInfo]
forall a. IO (Either (Messages TcRnMessage) a) -> TcM a
tcRnMsgMaybe (IO (Either (Messages TcRnMessage) [AvailInfo]) -> TcM [AvailInfo])
-> IO (Either (Messages TcRnMessage) [AvailInfo])
-> TcM [AvailInfo]
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 <- (ShIfEnv -> IORef (Messages TcRnMessage))
-> IOEnv (Env ShIfEnv ()) ShIfEnv
-> IOEnv (Env ShIfEnv ()) (IORef (Messages TcRnMessage))
forall a b.
(a -> b) -> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShIfEnv -> IORef (Messages TcRnMessage)
sh_if_errs IOEnv (Env ShIfEnv ()) ShIfEnv
forall gbl lcl. TcRnIf gbl lcl gbl
getGblEnv
    Messages TcRnMessage
errs <- IORef (Messages TcRnMessage)
-> TcRnIf ShIfEnv () (Messages TcRnMessage)
forall a gbl lcl. TcRef a -> TcRnIf gbl lcl a
readTcRef IORef (Messages TcRnMessage)
errs_var
    -- TODO: maybe associate this with a source location?
    let msg :: MsgEnvelope TcRnMessage
msg = SrcSpan -> TcRnMessage -> MsgEnvelope TcRnMessage
forall e. Diagnostic e => SrcSpan -> e -> MsgEnvelope e
mkPlainErrorMsgEnvelope SrcSpan
noSrcSpan TcRnMessage
tcRnMessage
    IORef (Messages TcRnMessage)
-> Messages TcRnMessage -> TcRnIf ShIfEnv () ()
forall a gbl lcl. TcRef a -> a -> TcRnIf gbl lcl ()
writeTcRef IORef (Messages TcRnMessage)
errs_var (MsgEnvelope TcRnMessage
msg MsgEnvelope TcRnMessage
-> Messages TcRnMessage -> Messages TcRnMessage
forall e. MsgEnvelope e -> Messages e -> Messages e
`addMessage` Messages TcRnMessage
errs)
    ShIfM a
forall env a. IOEnv env a
failM

-- | What we have is a generalized ModIface, which corresponds to
-- a module that looks like p[A=\<A>]:B.  We need a *specific* ModIface, e.g.
-- p[A=q():A]:B (or maybe even p[A=\<B>]:B) which we load
-- up (either to merge it, or to just use during typechecking).
--
-- Suppose we have:
--
--  p[A=\<A>]:M  ==>  p[A=q():A]:M
--
-- Substitute all occurrences of \<A> with q():A (renameHoleModule).
-- Then, for any Name of form {A.T}, replace the Name with
-- the Name according to the exports of the implementing module.
-- This works even for p[A=\<B>]:M, since we just read in the
-- exports of B.hi, which is assumed to be ready now.
--
-- This function takes an optional 'NameShape', which can be used
-- to further refine the identities in this interface: suppose
-- we read a declaration for {H.T} but we actually know that this
-- should be Foo.T; then we'll also rename this (this is used
-- when loading an interface to merge it into a requirement.)
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 =
    HscEnv
-> ModIface
-> [(ModuleName, Module)]
-> Maybe NameShape
-> ShIfM ModIface
-> IO (Either (Messages TcRnMessage) ModIface)
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 ModIface -> IO (Either (Messages TcRnMessage) ModIface))
-> ShIfM ModIface -> IO (Either (Messages TcRnMessage) ModIface)
forall a b. (a -> b) -> a -> b
$ do
        Module
mod <- Rename Module
rnModule (ModIface -> Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module ModIface
iface)
        Maybe Module
sig_of <- case ModIface -> Maybe Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe Module
mi_sig_of ModIface
iface of
                    Maybe Module
Nothing -> Maybe Module -> IOEnv (Env ShIfEnv ()) (Maybe Module)
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Module
forall a. Maybe a
Nothing
                    Just Module
x  -> (Module -> Maybe Module)
-> IOEnv (Env ShIfEnv ()) Module
-> IOEnv (Env ShIfEnv ()) (Maybe Module)
forall a b.
(a -> b) -> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Module -> Maybe Module
forall a. a -> Maybe a
Just (Rename Module
rnModule Module
x)
        [AvailInfo]
exports <- (AvailInfo -> IOEnv (Env ShIfEnv ()) AvailInfo)
-> [AvailInfo] -> IOEnv (Env ShIfEnv ()) [AvailInfo]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM AvailInfo -> IOEnv (Env ShIfEnv ()) AvailInfo
rnAvailInfo (ModIface -> [AvailInfo]
forall (phase :: ModIfacePhase). ModIface_ phase -> [AvailInfo]
mi_exports ModIface
iface)
        [(Fingerprint, IfaceDecl)]
decls <- ((Fingerprint, IfaceDecl)
 -> IOEnv (Env ShIfEnv ()) (Fingerprint, IfaceDecl))
-> [(Fingerprint, IfaceDecl)]
-> IOEnv (Env ShIfEnv ()) [(Fingerprint, IfaceDecl)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Fingerprint, IfaceDecl)
-> IOEnv (Env ShIfEnv ()) (Fingerprint, IfaceDecl)
rnIfaceDecl' (ModIface -> [IfaceDeclExts 'ModIfaceFinal]
forall (phase :: ModIfacePhase).
ModIface_ phase -> [IfaceDeclExts phase]
mi_decls ModIface
iface)
        [IfaceClsInst]
insts <- (IfaceClsInst -> IOEnv (Env ShIfEnv ()) IfaceClsInst)
-> [IfaceClsInst] -> IOEnv (Env ShIfEnv ()) [IfaceClsInst]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM IfaceClsInst -> IOEnv (Env ShIfEnv ()) IfaceClsInst
rnIfaceClsInst (ModIface -> [IfaceClsInst]
forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceClsInst]
mi_insts ModIface
iface)
        [IfaceFamInst]
fams <- (IfaceFamInst -> IOEnv (Env ShIfEnv ()) IfaceFamInst)
-> [IfaceFamInst] -> IOEnv (Env ShIfEnv ()) [IfaceFamInst]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM IfaceFamInst -> IOEnv (Env ShIfEnv ()) IfaceFamInst
rnIfaceFamInst (ModIface -> [IfaceFamInst]
forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceFamInst]
mi_fam_insts ModIface
iface)
        Dependencies
deps <- Rename Dependencies
rnDependencies (ModIface -> Dependencies
forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps ModIface
iface)
        -- TODO:
        -- mi_rules
        ModIface -> ShIfM ModIface
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return ModIface
iface { mi_module = mod
                     , mi_sig_of = sig_of
                     , mi_insts = insts
                     , mi_fam_insts = fams
                     , mi_exports = exports
                     , mi_decls = decls
                     , mi_deps = deps }

-- | Rename just the exports of a 'ModIface'.  Useful when we're doing
-- shaping prior to signature merging.
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
    = HscEnv
-> ModIface
-> [(ModuleName, Module)]
-> Maybe NameShape
-> IOEnv (Env ShIfEnv ()) [AvailInfo]
-> IO (Either (Messages TcRnMessage) [AvailInfo])
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
forall a. Maybe a
Nothing
    (IOEnv (Env ShIfEnv ()) [AvailInfo]
 -> IO (Either (Messages TcRnMessage) [AvailInfo]))
-> IOEnv (Env ShIfEnv ()) [AvailInfo]
-> IO (Either (Messages TcRnMessage) [AvailInfo])
forall a b. (a -> b) -> a -> b
$ (AvailInfo -> IOEnv (Env ShIfEnv ()) AvailInfo)
-> [AvailInfo] -> IOEnv (Env ShIfEnv ()) [AvailInfo]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM AvailInfo -> IOEnv (Env ShIfEnv ()) AvailInfo
rnAvailInfo (ModIface -> [AvailInfo]
forall (phase :: ModIfacePhase). ModIface_ phase -> [AvailInfo]
mi_exports ModIface
iface)

rnDependencies :: Rename Dependencies
rnDependencies :: Rename Dependencies
rnDependencies Dependencies
deps0 = do
    Dependencies
deps1  <- Dependencies
-> ([Module] -> IOEnv (Env ShIfEnv ()) [Module])
-> ShIfM Dependencies
forall (m :: * -> *).
Monad m =>
Dependencies -> ([Module] -> m [Module]) -> m Dependencies
dep_orphs_update Dependencies
deps0 ((Dependencies -> [Module])
-> [Module] -> IOEnv (Env ShIfEnv ()) [Module]
rnDepModules Dependencies -> [Module]
dep_orphs)
    Dependencies
-> ([Module] -> IOEnv (Env ShIfEnv ()) [Module])
-> ShIfM Dependencies
forall (m :: * -> *).
Monad m =>
Dependencies -> ([Module] -> m [Module]) -> m Dependencies
dep_finsts_update Dependencies
deps1 ((Dependencies -> [Module])
-> [Module] -> IOEnv (Env ShIfEnv ()) [Module]
rnDepModules Dependencies -> [Module]
dep_finsts)

rnDepModules :: (Dependencies -> [Module]) -> [Module] -> ShIfM [Module]
rnDepModules :: (Dependencies -> [Module])
-> [Module] -> IOEnv (Env ShIfEnv ()) [Module]
rnDepModules Dependencies -> [Module]
sel [Module]
mods = do
    HscEnv
hsc_env <- TcRnIf ShIfEnv () HscEnv
forall gbl lcl. TcRnIf gbl lcl HscEnv
getTopEnv
    ShHoleSubst
hmap <- ShIfM ShHoleSubst
getHoleSubst
    -- NB: It's not necessary to test if we're doing signature renaming,
    -- because ModIface will never contain module reference for itself
    -- in these dependencies.
    ([[Module]] -> [Module])
-> IOEnv (Env ShIfEnv ()) [[Module]]
-> IOEnv (Env ShIfEnv ()) [Module]
forall a b.
(a -> b) -> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Module] -> [Module]
forall a. Ord a => [a] -> [a]
nubSort ([Module] -> [Module])
-> ([[Module]] -> [Module]) -> [[Module]] -> [Module]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Module]] -> [Module]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat) (IOEnv (Env ShIfEnv ()) [[Module]]
 -> IOEnv (Env ShIfEnv ()) [Module])
-> ((Module -> IOEnv (Env ShIfEnv ()) [Module])
    -> IOEnv (Env ShIfEnv ()) [[Module]])
-> (Module -> IOEnv (Env ShIfEnv ()) [Module])
-> IOEnv (Env ShIfEnv ()) [Module]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Module]
-> (Module -> IOEnv (Env ShIfEnv ()) [Module])
-> IOEnv (Env ShIfEnv ()) [[Module]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
T.forM [Module]
mods ((Module -> IOEnv (Env ShIfEnv ()) [Module])
 -> IOEnv (Env ShIfEnv ()) [Module])
-> (Module -> IOEnv (Env ShIfEnv ()) [Module])
-> IOEnv (Env ShIfEnv ()) [Module]
forall a b. (a -> b) -> a -> b
$ \Module
mod -> do
        -- For holes, its necessary to "see through" the instantiation
        -- of the hole to get accurate family instance dependencies.
        -- For example, if B imports <A>, and <A> is instantiated with
        -- F, we must grab and include all of the dep_finsts from
        -- F to have an accurate transitive dep_finsts list.
        --
        -- However, we MUST NOT do this for regular modules.
        -- First, for efficiency reasons, doing this
        -- bloats the dep_finsts list, because we *already* had
        -- those modules in the list (it wasn't a hole module, after
        -- all). But there's a second, more important correctness
        -- consideration: we perform module renaming when running
        -- --abi-hash.  In this case, GHC's contract to the user is that
        -- it will NOT go and read out interfaces of any dependencies
        -- (https://github.com/haskell/cabal/issues/3633); the point of
        -- --abi-hash is just to get a hash of the on-disk interfaces
        -- for this *specific* package.  If we go off and tug on the
        -- interface for /everything/ in dep_finsts, we're gonna have a
        -- bad time.  (It's safe to do this for hole modules, though,
        -- because the hmap for --abi-hash is always trivial, so the
        -- interface we request is local.  Though, maybe we ought
        -- not to do it in this case either...)
        --
        -- This mistake was bug #15594.
        let mod' :: Module
mod' = UnitState -> ShHoleSubst -> Module -> Module
renameHoleModule ((() :: Constraint) => HscEnv -> UnitState
HscEnv -> UnitState
hsc_units HscEnv
hsc_env) ShHoleSubst
hmap Module
mod
        if Module -> Bool
forall u. GenModule (GenUnit u) -> Bool
isHoleModule Module
mod
          then do ModIface
iface <- IO ModIface -> ShIfM ModIface
forall a. IO a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ModIface -> ShIfM ModIface)
-> (IfG ModIface -> IO ModIface) -> IfG ModIface -> ShIfM ModIface
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SDoc -> HscEnv -> IfG ModIface -> IO ModIface
forall a. SDoc -> HscEnv -> IfG a -> IO a
initIfaceCheck (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"rnDepModule") HscEnv
hsc_env
                                  (IfG ModIface -> ShIfM ModIface) -> IfG ModIface -> ShIfM ModIface
forall a b. (a -> b) -> a -> b
$ SDoc -> Module -> IfG ModIface
forall lcl. SDoc -> Module -> IfM lcl ModIface
loadSysInterface (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"rnDepModule") Module
mod'
                  [Module] -> IOEnv (Env ShIfEnv ()) [Module]
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Module
mod' Module -> [Module] -> [Module]
forall a. a -> [a] -> [a]
: Dependencies -> [Module]
sel (ModIface -> Dependencies
forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps ModIface
iface))
          else [Module] -> IOEnv (Env ShIfEnv ()) [Module]
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return [Module
mod']

{-
************************************************************************
*                                                                      *
                        ModIface substitution
*                                                                      *
************************************************************************
-}

-- | Run a computation in the 'ShIfM' monad.
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 <- Messages TcRnMessage -> IO (IORef (Messages TcRnMessage))
forall a. a -> IO (IORef a)
newIORef Messages TcRnMessage
forall e. Messages e
emptyMessages
    let hsubst :: ShHoleSubst
hsubst = [(ModuleName, Module)] -> ShHoleSubst
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 ((() :: Constraint) => HscEnv -> UnitState
HscEnv -> UnitState
hsc_units HscEnv
hsc_env) ShHoleSubst
hsubst
        env :: ShIfEnv
env = ShIfEnv {
            sh_if_module :: Module
sh_if_module = Module -> Module
rn_mod (ModIface -> Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module ModIface
iface),
            sh_if_semantic_module :: Module
sh_if_semantic_module = Module -> Module
rn_mod (ModIface -> Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_semantic_module ModIface
iface),
            sh_if_hole_subst :: ShHoleSubst
sh_if_hole_subst = [(ModuleName, Module)] -> ShHoleSubst
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
        }
    -- Modeled off of 'initTc'
    Either IOEnvFailure a
res <- Char
-> HscEnv
-> ShIfEnv
-> ()
-> TcRnIf ShIfEnv () (Either IOEnvFailure a)
-> IO (Either IOEnvFailure a)
forall gbl lcl a.
Char -> HscEnv -> gbl -> lcl -> TcRnIf gbl lcl a -> IO a
initTcRnIf Char
'c' HscEnv
hsc_env ShIfEnv
env () (TcRnIf ShIfEnv () (Either IOEnvFailure a)
 -> IO (Either IOEnvFailure a))
-> TcRnIf ShIfEnv () (Either IOEnvFailure a)
-> IO (Either IOEnvFailure a)
forall a b. (a -> b) -> a -> b
$ ShIfM a -> TcRnIf ShIfEnv () (Either IOEnvFailure a)
forall env r. IOEnv env r -> IOEnv env (Either IOEnvFailure r)
tryM ShIfM a
do_this
    Messages TcRnMessage
msgs <- IORef (Messages TcRnMessage) -> IO (Messages TcRnMessage)
forall a. IORef a -> IO a
readIORef IORef (Messages TcRnMessage)
errs_var
    case Either IOEnvFailure a
res of
        Left IOEnvFailure
_                               -> Either (Messages TcRnMessage) a
-> IO (Either (Messages TcRnMessage) a)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Messages TcRnMessage -> Either (Messages TcRnMessage) a
forall a b. a -> Either a b
Left Messages TcRnMessage
msgs)
        Right a
r | Bool -> Bool
not (Messages TcRnMessage -> Bool
forall e. Messages e -> Bool
isEmptyMessages Messages TcRnMessage
msgs) -> Either (Messages TcRnMessage) a
-> IO (Either (Messages TcRnMessage) a)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Messages TcRnMessage -> Either (Messages TcRnMessage) a
forall a b. a -> Either a b
Left Messages TcRnMessage
msgs)
                | Bool
otherwise                  -> Either (Messages TcRnMessage) a
-> IO (Either (Messages TcRnMessage) a)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Either (Messages TcRnMessage) a
forall a b. b -> Either a b
Right a
r)

-- | Environment for 'ShIfM' monads.
data ShIfEnv = ShIfEnv {
        -- What we are renaming the ModIface to.  It assumed that
        -- the original mi_module of the ModIface is
        -- @generalizeModule (mi_module iface)@.
        ShIfEnv -> Module
sh_if_module :: Module,
        -- The semantic module that we are renaming to
        ShIfEnv -> Module
sh_if_semantic_module :: Module,
        -- Cached hole substitution, e.g.
        -- @sh_if_hole_subst == listToUFM . unitIdInsts . moduleUnit . sh_if_module@
        ShIfEnv -> ShHoleSubst
sh_if_hole_subst :: ShHoleSubst,
        -- An optional name substitution to be applied when renaming
        -- the names in the interface.  If this is 'Nothing', then
        -- we just load the target interface and look at the export
        -- list to determine the renaming.
        ShIfEnv -> Maybe NameShape
sh_if_shape :: Maybe NameShape,
        -- Mutable reference to keep track of diagnostics (similar to 'tcl_errs')
        ShIfEnv -> IORef (Messages TcRnMessage)
sh_if_errs :: IORef (Messages TcRnMessage)
    }

getHoleSubst :: ShIfM ShHoleSubst
getHoleSubst :: ShIfM ShHoleSubst
getHoleSubst = (ShIfEnv -> ShHoleSubst)
-> IOEnv (Env ShIfEnv ()) ShIfEnv -> ShIfM ShHoleSubst
forall a b.
(a -> b) -> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShIfEnv -> ShHoleSubst
sh_if_hole_subst IOEnv (Env ShIfEnv ()) ShIfEnv
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 <- (() :: Constraint) => HscEnv -> UnitState
HscEnv -> UnitState
hsc_units (HscEnv -> UnitState)
-> TcRnIf ShIfEnv () HscEnv -> IOEnv (Env ShIfEnv ()) UnitState
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TcRnIf ShIfEnv () HscEnv
forall gbl lcl. TcRnIf gbl lcl HscEnv
getTopEnv
    Rename Module
forall a. a -> IOEnv (Env ShIfEnv ()) a
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 :: AvailInfo -> IOEnv (Env ShIfEnv ()) AvailInfo
rnAvailInfo (Avail GreName
c) = GreName -> AvailInfo
Avail (GreName -> AvailInfo)
-> IOEnv (Env ShIfEnv ()) GreName
-> IOEnv (Env ShIfEnv ()) AvailInfo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename GreName
rnGreName GreName
c
rnAvailInfo (AvailTC IfaceTopBndr
n [GreName]
ns) = do
    -- Why don't we rnIfaceGlobal the availName itself?  It may not
    -- actually be exported by the module it putatively is from, in
    -- which case we won't be able to tell what the name actually
    -- is.  But for the availNames they MUST be exported, so they
    -- will rename fine.
    [GreName]
ns' <- Rename GreName -> [GreName] -> IOEnv (Env ShIfEnv ()) [GreName]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Rename GreName
rnGreName [GreName]
ns
    case [GreName]
ns' of
        [] -> String -> IOEnv (Env ShIfEnv ()) AvailInfo
forall a. HasCallStack => String -> a
panic String
"rnAvailInfoEmpty AvailInfo"
        (GreName
rep:[GreName]
rest) -> Bool
-> SDoc
-> IOEnv (Env ShIfEnv ()) AvailInfo
-> IOEnv (Env ShIfEnv ()) AvailInfo
forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr ((GreName -> Bool) -> [GreName] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ((Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
== GreName -> Module
childModule GreName
rep) (Module -> Bool) -> (GreName -> Module) -> GreName -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GreName -> Module
childModule) [GreName]
rest)
                                (GreName -> SDoc
forall a. Outputable a => a -> SDoc
ppr GreName
rep SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hcat ((GreName -> SDoc) -> [GreName] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map GreName -> SDoc
forall a. Outputable a => a -> SDoc
ppr [GreName]
rest)) (IOEnv (Env ShIfEnv ()) AvailInfo
 -> IOEnv (Env ShIfEnv ()) AvailInfo)
-> IOEnv (Env ShIfEnv ()) AvailInfo
-> IOEnv (Env ShIfEnv ()) AvailInfo
forall a b. (a -> b) -> a -> b
$ do
                         IfaceTopBndr
n' <- Maybe Module -> IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
forall m n. Maybe Module -> IfaceTopBndr -> TcRnIf m n IfaceTopBndr
setNameModule (Module -> Maybe Module
forall a. a -> Maybe a
Just (GreName -> Module
childModule GreName
rep)) IfaceTopBndr
n
                         AvailInfo -> IOEnv (Env ShIfEnv ()) AvailInfo
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return (IfaceTopBndr -> [GreName] -> AvailInfo
AvailTC IfaceTopBndr
n' [GreName]
ns')
  where
    childModule :: GreName -> Module
childModule = (() :: Constraint) => IfaceTopBndr -> Module
IfaceTopBndr -> Module
nameModule (IfaceTopBndr -> Module)
-> (GreName -> IfaceTopBndr) -> GreName -> Module
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 (IfaceTopBndr -> GreName)
-> TcRnIf ShIfEnv () IfaceTopBndr -> IOEnv (Env ShIfEnv ()) GreName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceGlobal IfaceTopBndr
n
rnGreName (FieldGreName FieldLabel
fl) = FieldLabel -> GreName
FieldGreName  (FieldLabel -> GreName)
-> IOEnv (Env ShIfEnv ()) FieldLabel
-> IOEnv (Env ShIfEnv ()) GreName
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 -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceGlobal (FieldLabel -> IfaceTopBndr
flSelector FieldLabel
fl)
    Rename FieldLabel
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return (FieldLabel
fl { flSelector = sel' })




-- | The key function.  This gets called on every Name embedded
-- inside a ModIface.  Our job is to take a Name from some
-- generalized unit ID p[A=\<A>, B=\<B>], and change
-- it to the correct name for a (partially) instantiated unit
-- ID, e.g. p[A=q[]:A, B=\<B>].
--
-- There are two important things to do:
--
-- If a hole is substituted with a real module implementation,
-- we need to look at that actual implementation to determine what
-- the true identity of this name should be.  We'll do this by
-- loading that module's interface and looking at the mi_exports.
--
-- However, there is one special exception: when we are loading
-- the interface of a requirement.  In this case, we may not have
-- the "implementing" interface, because we are reading this
-- interface precisely to "merge it in".
--
--     External case:
--         p[A=\<B>]:A (and thisUnitId is something else)
--     We are loading this in order to determine B.hi!  So
--     don't load B.hi to find the exports.
--
--     Local case:
--         p[A=\<A>]:A (and thisUnitId is p[A=\<A>])
--     This should not happen, because the rename is not necessary
--     in this case, but if it does we shouldn't load A.hi!
--
-- Compare me with 'tcIfaceGlobal'!

-- In effect, this function needs compute the name substitution on the
-- fly.  What it has is the name that we would like to substitute.
-- If the name is not a hole name {M.x} (e.g. isHoleModule) then
-- no renaming can take place (although the inner hole structure must
-- be updated to account for the hole module renaming.)
rnIfaceGlobal :: Name -> ShIfM Name
rnIfaceGlobal :: IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceGlobal IfaceTopBndr
n = do
    HscEnv
hsc_env <- TcRnIf ShIfEnv () HscEnv
forall gbl lcl. TcRnIf gbl lcl HscEnv
getTopEnv
    let unit_state :: UnitState
unit_state = (() :: Constraint) => HscEnv -> UnitState
HscEnv -> UnitState
hsc_units HscEnv
hsc_env
        home_unit :: HomeUnit
home_unit  = HscEnv -> HomeUnit
hsc_home_unit HscEnv
hsc_env
    Module
iface_semantic_mod <- (ShIfEnv -> Module)
-> IOEnv (Env ShIfEnv ()) ShIfEnv -> IOEnv (Env ShIfEnv ()) Module
forall a b.
(a -> b) -> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShIfEnv -> Module
sh_if_semantic_module IOEnv (Env ShIfEnv ()) ShIfEnv
forall gbl lcl. TcRnIf gbl lcl gbl
getGblEnv
    Maybe NameShape
mb_nsubst <- (ShIfEnv -> Maybe NameShape)
-> IOEnv (Env ShIfEnv ()) ShIfEnv
-> IOEnv (Env ShIfEnv ()) (Maybe NameShape)
forall a b.
(a -> b) -> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShIfEnv -> Maybe NameShape
sh_if_shape IOEnv (Env ShIfEnv ()) ShIfEnv
forall gbl lcl. TcRnIf gbl lcl gbl
getGblEnv
    ShHoleSubst
hmap <- ShIfM ShHoleSubst
getHoleSubst
    let m :: Module
m = (() :: Constraint) => IfaceTopBndr -> Module
IfaceTopBndr -> Module
nameModule IfaceTopBndr
n
        m' :: Module
m' = UnitState -> ShHoleSubst -> Module -> Module
renameHoleModule UnitState
unit_state ShHoleSubst
hmap Module
m
    case () of
       -- Did we encounter {A.T} while renaming p[A=<B>]:A? If so,
       -- do NOT assume B.hi is available.
       -- In this case, rename {A.T} to {B.T} but don't look up exports.
     ()
_ | Module
m' Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
== Module
iface_semantic_mod
       , Module -> Bool
forall u. GenModule (GenUnit u) -> Bool
isHoleModule Module
m'
      -- NB: this could be Nothing for computeExports, we have
      -- nothing to say.
      -> do IfaceTopBndr
n' <- Maybe Module -> IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
forall m n. Maybe Module -> IfaceTopBndr -> TcRnIf m n IfaceTopBndr
setNameModule (Module -> Maybe Module
forall a. a -> Maybe a
Just Module
m') IfaceTopBndr
n
            case Maybe NameShape
mb_nsubst of
                Maybe NameShape
Nothing -> IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
forall a. a -> IOEnv (Env ShIfEnv ()) a
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
                        -- TODO: would love to have context
                        -- TODO: This will give an unpleasant message if n'
                        -- is a constructor; then we'll suggest adding T
                        -- but it won't work.
                        Maybe IfaceTopBndr
Nothing ->
                          TcRnMessage -> TcRnIf ShIfEnv () IfaceTopBndr
forall a. TcRnMessage -> ShIfM a
failWithRn (TcRnMessage -> TcRnIf ShIfEnv () IfaceTopBndr)
-> TcRnMessage -> TcRnIf ShIfEnv () IfaceTopBndr
forall a b. (a -> b) -> a -> b
$ IfaceTopBndr -> TcRnMessage
TcRnIdNotExportedFromLocalSig IfaceTopBndr
n'
                        Just IfaceTopBndr
n'' -> IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceTopBndr
n''
       -- Fastpath: we are renaming p[H=<H>]:A.T, in which case the
       -- export list is irrelevant.
       | Bool -> Bool
not (Module -> Bool
forall u. GenModule (GenUnit u) -> Bool
isHoleModule Module
m)
      -> Maybe Module -> IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
forall m n. Maybe Module -> IfaceTopBndr -> TcRnIf m n IfaceTopBndr
setNameModule (Module -> Maybe Module
forall a. a -> Maybe a
Just Module
m') IfaceTopBndr
n
       -- The substitution was from <A> to p[]:A.
       -- But this does not mean {A.T} goes to p[]:A.T:
       -- p[]:A may reexport T from somewhere else.  Do the name
       -- substitution.  Furthermore, we need
       -- to make sure we pick the accurate name NOW,
       -- or we might accidentally reject a merge.
       | Bool
otherwise
      -> do -- Make sure we look up the local interface if substitution
            -- went from <A> to <B>.
            let m'' :: Module
m'' = if Module -> Bool
forall u. GenModule (GenUnit u) -> Bool
isHoleModule Module
m'
                        -- Pull out the local guy!!
                        then HomeUnit -> ModuleName -> Module
mkHomeModule HomeUnit
home_unit (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
m')
                        else Module
m'
            ModIface
iface <- IO ModIface -> ShIfM ModIface
forall a. IO a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ModIface -> ShIfM ModIface)
-> (IfG ModIface -> IO ModIface) -> IfG ModIface -> ShIfM ModIface
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SDoc -> HscEnv -> IfG ModIface -> IO ModIface
forall a. SDoc -> HscEnv -> IfG a -> IO a
initIfaceCheck (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"rnIfaceGlobal") HscEnv
hsc_env
                            (IfG ModIface -> ShIfM ModIface) -> IfG ModIface -> ShIfM ModIface
forall a b. (a -> b) -> a -> b
$ SDoc -> Module -> IfG ModIface
forall lcl. SDoc -> Module -> IfM lcl ModIface
loadSysInterface (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"rnIfaceGlobal") Module
m''
            let nsubst :: NameShape
nsubst = ModuleName -> [AvailInfo] -> NameShape
mkNameShape (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
m) (ModIface -> [AvailInfo]
forall (phase :: ModIfacePhase). ModIface_ phase -> [AvailInfo]
mi_exports ModIface
iface)
            case NameShape -> IfaceTopBndr -> Maybe IfaceTopBndr
maybeSubstNameShape NameShape
nsubst IfaceTopBndr
n of
                -- NB: report m' because it's more user-friendly
                Maybe IfaceTopBndr
Nothing -> TcRnMessage -> TcRnIf ShIfEnv () IfaceTopBndr
forall a. TcRnMessage -> ShIfM a
failWithRn (TcRnMessage -> TcRnIf ShIfEnv () IfaceTopBndr)
-> TcRnMessage -> TcRnIf ShIfEnv () IfaceTopBndr
forall a b. (a -> b) -> a -> b
$ IfaceTopBndr -> Module -> TcRnMessage
TcRnIdNotExportedFromModuleSig IfaceTopBndr
n Module
m'
                Just IfaceTopBndr
n' -> IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceTopBndr
n'

-- | Rename an implicit name, e.g., a DFun or coercion axiom.
-- Here is where we ensure that DFuns have the correct module as described in
-- Note [rnIfaceNeverExported].
rnIfaceNeverExported :: Name -> ShIfM Name
rnIfaceNeverExported :: IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceNeverExported IfaceTopBndr
name = do
    ShHoleSubst
hmap <- ShIfM ShHoleSubst
getHoleSubst
    UnitState
unit_state <- (() :: Constraint) => HscEnv -> UnitState
HscEnv -> UnitState
hsc_units (HscEnv -> UnitState)
-> TcRnIf ShIfEnv () HscEnv -> IOEnv (Env ShIfEnv ()) UnitState
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TcRnIf ShIfEnv () HscEnv
forall gbl lcl. TcRnIf gbl lcl HscEnv
getTopEnv
    Module
iface_semantic_mod <- (ShIfEnv -> Module)
-> IOEnv (Env ShIfEnv ()) ShIfEnv -> IOEnv (Env ShIfEnv ()) Module
forall a b.
(a -> b) -> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShIfEnv -> Module
sh_if_semantic_module IOEnv (Env ShIfEnv ()) ShIfEnv
forall gbl lcl. TcRnIf gbl lcl gbl
getGblEnv
    let m :: Module
m = UnitState -> ShHoleSubst -> Module -> Module
renameHoleModule UnitState
unit_state ShHoleSubst
hmap (Module -> Module) -> Module -> Module
forall a b. (a -> b) -> a -> b
$ (() :: Constraint) => IfaceTopBndr -> Module
IfaceTopBndr -> Module
nameModule IfaceTopBndr
name
    -- Doublecheck that this DFun/coercion axiom was, indeed, locally defined.
    Bool -> SDoc -> TcRnIf ShIfEnv () ()
forall (m :: * -> *).
(HasCallStack, Applicative m) =>
Bool -> SDoc -> m ()
massertPpr (Module
iface_semantic_mod Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
== Module
m) (Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
iface_semantic_mod SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
m)
    Maybe Module -> IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
forall m n. Maybe Module -> IfaceTopBndr -> TcRnIf m n IfaceTopBndr
setNameModule (Module -> Maybe Module
forall a. a -> Maybe a
Just Module
m) IfaceTopBndr
name

-- Note [rnIfaceNeverExported]
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~
-- For the high-level overview, see
-- Note [Handling never-exported TyThings under Backpack]
--
-- When we see a reference to an entity that was defined in a signature,
-- 'rnIfaceGlobal' relies on the identifier in question being part of the
-- exports of the implementing 'ModIface', so that we can use the exports to
-- decide how to rename the identifier.  Unfortunately, references to 'DFun's
-- and 'CoAxiom's will run into trouble under this strategy, because they are
-- never exported.
--
-- Let us consider first what should happen in the absence of promotion.  In
-- this setting, a reference to a 'DFun' or a 'CoAxiom' can only occur inside
-- the signature *that is defining it* (as there are no Core terms in
-- typechecked-only interface files, there's no way for a reference to occur
-- besides from the defining 'ClsInst' or closed type family).  Thus,
-- it doesn't really matter what names we give the DFun/CoAxiom, as long
-- as it's consistent between the declaration site and the use site.
--
-- We have to make sure that these bogus names don't get propagated,
-- but it is fine: see Note [Signature merging DFuns] for the fixups
-- to the names we do before writing out the merged interface.
-- (It's even easier for instantiation, since the DFuns all get
-- dropped entirely; the instances are reexported implicitly.)
--
-- Unfortunately, this strategy is not enough in the presence of promotion
-- (see bug #13149), where modules which import the signature may make
-- reference to their coercions.  It's not altogether clear how to
-- fix this case, but it is definitely a bug!

-- PILES AND PILES OF BOILERPLATE

-- | Rename an 'IfaceClsInst', with special handling for an associated
-- dictionary function.
rnIfaceClsInst :: Rename IfaceClsInst
rnIfaceClsInst :: IfaceClsInst -> IOEnv (Env ShIfEnv ()) IfaceClsInst
rnIfaceClsInst IfaceClsInst
cls_inst = do
    IfaceTopBndr
n <- IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceGlobal (IfaceClsInst -> IfaceTopBndr
ifInstCls IfaceClsInst
cls_inst)
    [Maybe IfaceTyCon]
tys <- (Maybe IfaceTyCon -> IOEnv (Env ShIfEnv ()) (Maybe IfaceTyCon))
-> [Maybe IfaceTyCon] -> IOEnv (Env ShIfEnv ()) [Maybe IfaceTyCon]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Maybe IfaceTyCon -> IOEnv (Env ShIfEnv ()) (Maybe IfaceTyCon)
rnRoughMatchTyCon (IfaceClsInst -> [Maybe IfaceTyCon]
ifInstTys IfaceClsInst
cls_inst)

    IfaceTopBndr
dfun <- IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceNeverExported (IfaceClsInst -> IfaceTopBndr
ifDFun IfaceClsInst
cls_inst)
    IfaceClsInst -> IOEnv (Env ShIfEnv ()) IfaceClsInst
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceClsInst
cls_inst { ifInstCls = n
                    , ifInstTys = tys
                    , ifDFun = dfun
                    }

rnRoughMatchTyCon :: Rename (Maybe IfaceTyCon)
rnRoughMatchTyCon :: Maybe IfaceTyCon -> IOEnv (Env ShIfEnv ()) (Maybe IfaceTyCon)
rnRoughMatchTyCon Maybe IfaceTyCon
Nothing = Maybe IfaceTyCon -> IOEnv (Env ShIfEnv ()) (Maybe IfaceTyCon)
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe IfaceTyCon
forall a. Maybe a
Nothing
rnRoughMatchTyCon (Just IfaceTyCon
tc) = IfaceTyCon -> Maybe IfaceTyCon
forall a. a -> Maybe a
Just (IfaceTyCon -> Maybe IfaceTyCon)
-> IOEnv (Env ShIfEnv ()) IfaceTyCon
-> IOEnv (Env ShIfEnv ()) (Maybe IfaceTyCon)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceTyCon
rnIfaceTyCon IfaceTyCon
tc

rnIfaceFamInst :: Rename IfaceFamInst
rnIfaceFamInst :: IfaceFamInst -> IOEnv (Env ShIfEnv ()) IfaceFamInst
rnIfaceFamInst IfaceFamInst
d = do
    IfaceTopBndr
fam <- IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceGlobal (IfaceFamInst -> IfaceTopBndr
ifFamInstFam IfaceFamInst
d)
    [Maybe IfaceTyCon]
tys <- (Maybe IfaceTyCon -> IOEnv (Env ShIfEnv ()) (Maybe IfaceTyCon))
-> [Maybe IfaceTyCon] -> IOEnv (Env ShIfEnv ()) [Maybe IfaceTyCon]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Maybe IfaceTyCon -> IOEnv (Env ShIfEnv ()) (Maybe IfaceTyCon)
rnRoughMatchTyCon (IfaceFamInst -> [Maybe IfaceTyCon]
ifFamInstTys IfaceFamInst
d)
    IfaceTopBndr
axiom <- IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceGlobal (IfaceFamInst -> IfaceTopBndr
ifFamInstAxiom IfaceFamInst
d)
    IfaceFamInst -> IOEnv (Env ShIfEnv ()) IfaceFamInst
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceFamInst
d { ifFamInstFam = fam, ifFamInstTys = tys, ifFamInstAxiom = axiom }

rnIfaceDecl' :: Rename (Fingerprint, IfaceDecl)
rnIfaceDecl' :: (Fingerprint, IfaceDecl)
-> IOEnv (Env ShIfEnv ()) (Fingerprint, IfaceDecl)
rnIfaceDecl' (Fingerprint
fp, IfaceDecl
decl) = (,) Fingerprint
fp (IfaceDecl -> (Fingerprint, IfaceDecl))
-> IOEnv (Env ShIfEnv ()) IfaceDecl
-> IOEnv (Env ShIfEnv ()) (Fingerprint, IfaceDecl)
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 -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceNeverExported (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d)
                      IfaceIdDetails
_ | OccName -> Bool
isDefaultMethodOcc (IfaceTopBndr -> OccName
forall name. HasOccName name => name -> OccName
occName (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d))
                        -> IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceNeverExported (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d)
                      -- Typeable bindings. See Note [Grand plan for Typeable].
                      IfaceIdDetails
_ | OccName -> Bool
isTypeableBindOcc (IfaceTopBndr -> OccName
forall name. HasOccName name => name -> OccName
occName (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d))
                        -> IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceNeverExported (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d)
                        | Bool
otherwise -> IfaceTopBndr -> TcRnIf ShIfEnv () 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)
            Rename IfaceDecl
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName = name
                     , ifType = ty
                     , ifIdDetails = details
                     , ifIdInfo = info
                     }
rnIfaceDecl d :: IfaceDecl
d@IfaceData{} = do
            IfaceTopBndr
name <- IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceGlobal (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d)
            [IfaceTyConBinder]
binders <- (IfaceTyConBinder -> IOEnv (Env ShIfEnv ()) IfaceTyConBinder)
-> [IfaceTyConBinder] -> IOEnv (Env ShIfEnv ()) [IfaceTyConBinder]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM IfaceTyConBinder -> IOEnv (Env ShIfEnv ()) IfaceTyConBinder
rnIfaceTyConBinder (IfaceDecl -> [IfaceTyConBinder]
ifBinders IfaceDecl
d)
            [IfaceType]
ctxt <- Rename IfaceType
-> [IfaceType] -> IOEnv (Env ShIfEnv ()) [IfaceType]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [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)
            Rename IfaceDecl
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName = name
                     , ifBinders = binders
                     , ifCtxt = ctxt
                     , ifCons = cons
                     , ifResKind = res_kind
                     , ifParent = parent
                     }
rnIfaceDecl d :: IfaceDecl
d@IfaceSynonym{} = do
            IfaceTopBndr
name <- IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceGlobal (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d)
            [IfaceTyConBinder]
binders <- (IfaceTyConBinder -> IOEnv (Env ShIfEnv ()) IfaceTyConBinder)
-> [IfaceTyConBinder] -> IOEnv (Env ShIfEnv ()) [IfaceTyConBinder]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM IfaceTyConBinder -> IOEnv (Env ShIfEnv ()) 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)
            Rename IfaceDecl
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName = name
                     , ifBinders = binders
                     , ifResKind = syn_kind
                     , ifSynRhs = syn_rhs
                     }
rnIfaceDecl d :: IfaceDecl
d@IfaceFamily{} = do
            IfaceTopBndr
name <- IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceGlobal (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d)
            [IfaceTyConBinder]
binders <- (IfaceTyConBinder -> IOEnv (Env ShIfEnv ()) IfaceTyConBinder)
-> [IfaceTyConBinder] -> IOEnv (Env ShIfEnv ()) [IfaceTyConBinder]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM IfaceTyConBinder -> IOEnv (Env ShIfEnv ()) 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)
            Rename IfaceDecl
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName = name
                     , ifBinders = binders
                     , ifResKind = fam_kind
                     , ifFamFlav = fam_flav
                     }
rnIfaceDecl d :: IfaceDecl
d@IfaceClass{} = do
            IfaceTopBndr
name <- IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceGlobal (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d)
            [IfaceTyConBinder]
binders <- (IfaceTyConBinder -> IOEnv (Env ShIfEnv ()) IfaceTyConBinder)
-> [IfaceTyConBinder] -> IOEnv (Env ShIfEnv ()) [IfaceTyConBinder]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM IfaceTyConBinder -> IOEnv (Env ShIfEnv ()) IfaceTyConBinder
rnIfaceTyConBinder (IfaceDecl -> [IfaceTyConBinder]
ifBinders IfaceDecl
d)
            IfaceClassBody
body <- Rename IfaceClassBody
rnIfaceClassBody (IfaceDecl -> IfaceClassBody
ifBody IfaceDecl
d)
            Rename IfaceDecl
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName    = name
                     , ifBinders = binders
                     , ifBody    = body
                     }
rnIfaceDecl d :: IfaceDecl
d@IfaceAxiom{} = do
            IfaceTopBndr
name <- IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceNeverExported (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d)
            IfaceTyCon
tycon <- Rename IfaceTyCon
rnIfaceTyCon (IfaceDecl -> IfaceTyCon
ifTyCon IfaceDecl
d)
            [IfaceAxBranch]
ax_branches <- (IfaceAxBranch -> IOEnv (Env ShIfEnv ()) IfaceAxBranch)
-> [IfaceAxBranch] -> IOEnv (Env ShIfEnv ()) [IfaceAxBranch]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM IfaceAxBranch -> IOEnv (Env ShIfEnv ()) IfaceAxBranch
rnIfaceAxBranch (IfaceDecl -> [IfaceAxBranch]
ifAxBranches IfaceDecl
d)
            Rename IfaceDecl
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName = name
                     , ifTyCon = tycon
                     , ifAxBranches = ax_branches
                     }
rnIfaceDecl d :: IfaceDecl
d@IfacePatSyn{} =  do
            IfaceTopBndr
name <- IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceGlobal (IfaceDecl -> IfaceTopBndr
ifName IfaceDecl
d)
            let rnPat :: (IfaceTopBndr, a) -> IOEnv (Env ShIfEnv ()) (IfaceTopBndr, a)
rnPat (IfaceTopBndr
n, a
b) = (,) (IfaceTopBndr -> a -> (IfaceTopBndr, a))
-> TcRnIf ShIfEnv () IfaceTopBndr
-> IOEnv (Env ShIfEnv ()) (a -> (IfaceTopBndr, a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceGlobal IfaceTopBndr
n IOEnv (Env ShIfEnv ()) (a -> (IfaceTopBndr, a))
-> IOEnv (Env ShIfEnv ()) a
-> IOEnv (Env ShIfEnv ()) (IfaceTopBndr, a)
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> IOEnv (Env ShIfEnv ()) a
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
b
            (IfaceTopBndr, Bool)
pat_matcher <- (IfaceTopBndr, Bool) -> IOEnv (Env ShIfEnv ()) (IfaceTopBndr, Bool)
forall {a}.
(IfaceTopBndr, a) -> IOEnv (Env ShIfEnv ()) (IfaceTopBndr, a)
rnPat (IfaceDecl -> (IfaceTopBndr, Bool)
ifPatMatcher IfaceDecl
d)
            Maybe (IfaceTopBndr, Bool)
pat_builder <- ((IfaceTopBndr, Bool)
 -> IOEnv (Env ShIfEnv ()) (IfaceTopBndr, Bool))
-> Maybe (IfaceTopBndr, Bool)
-> IOEnv (Env ShIfEnv ()) (Maybe (IfaceTopBndr, Bool))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Maybe a -> f (Maybe b)
T.traverse (IfaceTopBndr, Bool) -> IOEnv (Env ShIfEnv ()) (IfaceTopBndr, Bool)
forall {a}.
(IfaceTopBndr, a) -> IOEnv (Env ShIfEnv ()) (IfaceTopBndr, a)
rnPat (IfaceDecl -> Maybe (IfaceTopBndr, Bool)
ifPatBuilder IfaceDecl
d)
            [VarBndr IfaceBndr Specificity]
pat_univ_bndrs <- (VarBndr IfaceBndr Specificity
 -> IOEnv (Env ShIfEnv ()) (VarBndr IfaceBndr Specificity))
-> [VarBndr IfaceBndr Specificity]
-> IOEnv (Env ShIfEnv ()) [VarBndr IfaceBndr Specificity]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM VarBndr IfaceBndr Specificity
-> IOEnv (Env ShIfEnv ()) (VarBndr IfaceBndr Specificity)
forall flag. Rename (VarBndr IfaceBndr flag)
rnIfaceForAllBndr (IfaceDecl -> [VarBndr IfaceBndr Specificity]
ifPatUnivBndrs IfaceDecl
d)
            [VarBndr IfaceBndr Specificity]
pat_ex_bndrs <- (VarBndr IfaceBndr Specificity
 -> IOEnv (Env ShIfEnv ()) (VarBndr IfaceBndr Specificity))
-> [VarBndr IfaceBndr Specificity]
-> IOEnv (Env ShIfEnv ()) [VarBndr IfaceBndr Specificity]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM VarBndr IfaceBndr Specificity
-> IOEnv (Env ShIfEnv ()) (VarBndr IfaceBndr Specificity)
forall flag. Rename (VarBndr IfaceBndr flag)
rnIfaceForAllBndr (IfaceDecl -> [VarBndr IfaceBndr Specificity]
ifPatExBndrs IfaceDecl
d)
            [IfaceType]
pat_prov_ctxt <- Rename IfaceType
-> [IfaceType] -> IOEnv (Env ShIfEnv ()) [IfaceType]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Rename IfaceType
rnIfaceType (IfaceDecl -> [IfaceType]
ifPatProvCtxt IfaceDecl
d)
            [IfaceType]
pat_req_ctxt <- Rename IfaceType
-> [IfaceType] -> IOEnv (Env ShIfEnv ()) [IfaceType]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Rename IfaceType
rnIfaceType (IfaceDecl -> [IfaceType]
ifPatReqCtxt IfaceDecl
d)
            [IfaceType]
pat_args <- Rename IfaceType
-> [IfaceType] -> IOEnv (Env ShIfEnv ()) [IfaceType]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Rename IfaceType
rnIfaceType (IfaceDecl -> [IfaceType]
ifPatArgs IfaceDecl
d)
            IfaceType
pat_ty <- Rename IfaceType
rnIfaceType (IfaceDecl -> IfaceType
ifPatTy IfaceDecl
d)
            Rename IfaceDecl
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName = name
                     , ifPatMatcher = pat_matcher
                     , ifPatBuilder = pat_builder
                     , ifPatUnivBndrs = pat_univ_bndrs
                     , ifPatExBndrs = pat_ex_bndrs
                     , ifPatProvCtxt = pat_prov_ctxt
                     , ifPatReqCtxt = pat_req_ctxt
                     , ifPatArgs = pat_args
                     , ifPatTy = pat_ty
                     }

rnIfaceClassBody :: Rename IfaceClassBody
rnIfaceClassBody :: Rename IfaceClassBody
rnIfaceClassBody IfaceClassBody
IfAbstractClass = Rename IfaceClassBody
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceClassBody
IfAbstractClass
rnIfaceClassBody d :: IfaceClassBody
d@IfConcreteClass{} = do
    [IfaceType]
ctxt <- Rename IfaceType
-> [IfaceType] -> IOEnv (Env ShIfEnv ()) [IfaceType]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Rename IfaceType
rnIfaceType (IfaceClassBody -> [IfaceType]
ifClassCtxt IfaceClassBody
d)
    [IfaceAT]
ats <- (IfaceAT -> IOEnv (Env ShIfEnv ()) IfaceAT)
-> [IfaceAT] -> IOEnv (Env ShIfEnv ()) [IfaceAT]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM IfaceAT -> IOEnv (Env ShIfEnv ()) IfaceAT
rnIfaceAT (IfaceClassBody -> [IfaceAT]
ifATs IfaceClassBody
d)
    [IfaceClassOp]
sigs <- (IfaceClassOp -> IOEnv (Env ShIfEnv ()) IfaceClassOp)
-> [IfaceClassOp] -> IOEnv (Env ShIfEnv ()) [IfaceClassOp]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM IfaceClassOp -> IOEnv (Env ShIfEnv ()) IfaceClassOp
rnIfaceClassOp (IfaceClassBody -> [IfaceClassOp]
ifSigs IfaceClassBody
d)
    Rename IfaceClassBody
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceClassBody
d { ifClassCtxt = ctxt, ifATs = ats, ifSigs = sigs }

rnIfaceFamTyConFlav :: Rename IfaceFamTyConFlav
rnIfaceFamTyConFlav :: Rename IfaceFamTyConFlav
rnIfaceFamTyConFlav (IfaceClosedSynFamilyTyCon (Just (IfaceTopBndr
n, [IfaceAxBranch]
axs)))
    = Maybe (IfaceTopBndr, [IfaceAxBranch]) -> IfaceFamTyConFlav
IfaceClosedSynFamilyTyCon (Maybe (IfaceTopBndr, [IfaceAxBranch]) -> IfaceFamTyConFlav)
-> ((IfaceTopBndr, [IfaceAxBranch])
    -> Maybe (IfaceTopBndr, [IfaceAxBranch]))
-> (IfaceTopBndr, [IfaceAxBranch])
-> IfaceFamTyConFlav
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IfaceTopBndr, [IfaceAxBranch])
-> Maybe (IfaceTopBndr, [IfaceAxBranch])
forall a. a -> Maybe a
Just ((IfaceTopBndr, [IfaceAxBranch]) -> IfaceFamTyConFlav)
-> IOEnv (Env ShIfEnv ()) (IfaceTopBndr, [IfaceAxBranch])
-> IOEnv (Env ShIfEnv ()) IfaceFamTyConFlav
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((,) (IfaceTopBndr
 -> [IfaceAxBranch] -> (IfaceTopBndr, [IfaceAxBranch]))
-> TcRnIf ShIfEnv () IfaceTopBndr
-> IOEnv
     (Env ShIfEnv ())
     ([IfaceAxBranch] -> (IfaceTopBndr, [IfaceAxBranch]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceNeverExported IfaceTopBndr
n
                                                IOEnv
  (Env ShIfEnv ())
  ([IfaceAxBranch] -> (IfaceTopBndr, [IfaceAxBranch]))
-> IOEnv (Env ShIfEnv ()) [IfaceAxBranch]
-> IOEnv (Env ShIfEnv ()) (IfaceTopBndr, [IfaceAxBranch])
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (IfaceAxBranch -> IOEnv (Env ShIfEnv ()) IfaceAxBranch)
-> [IfaceAxBranch] -> IOEnv (Env ShIfEnv ()) [IfaceAxBranch]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM IfaceAxBranch -> IOEnv (Env ShIfEnv ()) IfaceAxBranch
rnIfaceAxBranch [IfaceAxBranch]
axs)
rnIfaceFamTyConFlav IfaceFamTyConFlav
flav = Rename IfaceFamTyConFlav
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceFamTyConFlav
flav

rnIfaceAT :: Rename IfaceAT
rnIfaceAT :: IfaceAT -> IOEnv (Env ShIfEnv ()) IfaceAT
rnIfaceAT (IfaceAT IfaceDecl
decl Maybe IfaceType
mb_ty)
    = IfaceDecl -> Maybe IfaceType -> IfaceAT
IfaceAT (IfaceDecl -> Maybe IfaceType -> IfaceAT)
-> IOEnv (Env ShIfEnv ()) IfaceDecl
-> IOEnv (Env ShIfEnv ()) (Maybe IfaceType -> IfaceAT)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceDecl
rnIfaceDecl IfaceDecl
decl IOEnv (Env ShIfEnv ()) (Maybe IfaceType -> IfaceAT)
-> IOEnv (Env ShIfEnv ()) (Maybe IfaceType)
-> IOEnv (Env ShIfEnv ()) IfaceAT
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceType
-> Maybe IfaceType -> IOEnv (Env ShIfEnv ()) (Maybe IfaceType)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Maybe a -> f (Maybe 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 (IfaceTopBndr -> IfaceTyCon -> IfaceAppArgs -> IfaceTyConParent)
-> TcRnIf ShIfEnv () IfaceTopBndr
-> IOEnv
     (Env ShIfEnv ()) (IfaceTyCon -> IfaceAppArgs -> IfaceTyConParent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceGlobal IfaceTopBndr
n
                     IOEnv
  (Env ShIfEnv ()) (IfaceTyCon -> IfaceAppArgs -> IfaceTyConParent)
-> IOEnv (Env ShIfEnv ()) IfaceTyCon
-> IOEnv (Env ShIfEnv ()) (IfaceAppArgs -> IfaceTyConParent)
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceTyCon
rnIfaceTyCon IfaceTyCon
tc
                     IOEnv (Env ShIfEnv ()) (IfaceAppArgs -> IfaceTyConParent)
-> IOEnv (Env ShIfEnv ()) IfaceAppArgs
-> IOEnv (Env ShIfEnv ()) IfaceTyConParent
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceAppArgs
rnIfaceAppArgs IfaceAppArgs
args
rnIfaceTyConParent IfaceTyConParent
IfNoParent = Rename IfaceTyConParent
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceTyConParent
IfNoParent

rnIfaceConDecls :: Rename IfaceConDecls
rnIfaceConDecls :: Rename IfaceConDecls
rnIfaceConDecls (IfDataTyCon Bool
type_data [IfaceConDecl]
ds)
    = Bool -> [IfaceConDecl] -> IfaceConDecls
IfDataTyCon Bool
type_data ([IfaceConDecl] -> IfaceConDecls)
-> IOEnv (Env ShIfEnv ()) [IfaceConDecl]
-> IOEnv (Env ShIfEnv ()) IfaceConDecls
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (IfaceConDecl -> IOEnv (Env ShIfEnv ()) IfaceConDecl)
-> [IfaceConDecl] -> IOEnv (Env ShIfEnv ()) [IfaceConDecl]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM IfaceConDecl -> IOEnv (Env ShIfEnv ()) IfaceConDecl
rnIfaceConDecl [IfaceConDecl]
ds
rnIfaceConDecls (IfNewTyCon IfaceConDecl
d) = IfaceConDecl -> IfaceConDecls
IfNewTyCon (IfaceConDecl -> IfaceConDecls)
-> IOEnv (Env ShIfEnv ()) IfaceConDecl
-> IOEnv (Env ShIfEnv ()) IfaceConDecls
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceConDecl -> IOEnv (Env ShIfEnv ()) IfaceConDecl
rnIfaceConDecl IfaceConDecl
d
rnIfaceConDecls IfaceConDecls
IfAbstractTyCon = Rename IfaceConDecls
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceConDecls
IfAbstractTyCon

rnIfaceConDecl :: Rename IfaceConDecl
rnIfaceConDecl :: IfaceConDecl -> IOEnv (Env ShIfEnv ()) IfaceConDecl
rnIfaceConDecl IfaceConDecl
d = do
    IfaceTopBndr
con_name <- IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceGlobal (IfaceConDecl -> IfaceTopBndr
ifConName IfaceConDecl
d)
    [IfaceBndr]
con_ex_tvs <- (IfaceBndr -> IOEnv (Env ShIfEnv ()) IfaceBndr)
-> [IfaceBndr] -> IOEnv (Env ShIfEnv ()) [IfaceBndr]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM IfaceBndr -> IOEnv (Env ShIfEnv ()) IfaceBndr
rnIfaceBndr (IfaceConDecl -> [IfaceBndr]
ifConExTCvs IfaceConDecl
d)
    [VarBndr IfaceBndr Specificity]
con_user_tvbs <- (VarBndr IfaceBndr Specificity
 -> IOEnv (Env ShIfEnv ()) (VarBndr IfaceBndr Specificity))
-> [VarBndr IfaceBndr Specificity]
-> IOEnv (Env ShIfEnv ()) [VarBndr IfaceBndr Specificity]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM VarBndr IfaceBndr Specificity
-> IOEnv (Env ShIfEnv ()) (VarBndr IfaceBndr Specificity)
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 (IfaceType -> (a, IfaceType))
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) (a, IfaceType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
t
    [(IfLclName, IfaceType)]
con_eq_spec <- ((IfLclName, IfaceType)
 -> IOEnv (Env ShIfEnv ()) (IfLclName, IfaceType))
-> [(IfLclName, IfaceType)]
-> IOEnv (Env ShIfEnv ()) [(IfLclName, IfaceType)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (IfLclName, IfaceType)
-> IOEnv (Env ShIfEnv ()) (IfLclName, IfaceType)
forall {a}. (a, IfaceType) -> IOEnv (Env ShIfEnv ()) (a, IfaceType)
rnIfConEqSpec (IfaceConDecl -> [(IfLclName, IfaceType)]
ifConEqSpec IfaceConDecl
d)
    [IfaceType]
con_ctxt <- Rename IfaceType
-> [IfaceType] -> IOEnv (Env ShIfEnv ()) [IfaceType]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Rename IfaceType
rnIfaceType (IfaceConDecl -> [IfaceType]
ifConCtxt IfaceConDecl
d)
    [(IfaceType, IfaceType)]
con_arg_tys <- ((IfaceType, IfaceType)
 -> IOEnv (Env ShIfEnv ()) (IfaceType, IfaceType))
-> [(IfaceType, IfaceType)]
-> IOEnv (Env ShIfEnv ()) [(IfaceType, IfaceType)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (IfaceType, IfaceType)
-> IOEnv (Env ShIfEnv ()) (IfaceType, IfaceType)
rnIfaceScaledType (IfaceConDecl -> [(IfaceType, IfaceType)]
ifConArgTys IfaceConDecl
d)
    [FieldLabel]
con_fields <- Rename FieldLabel
-> [FieldLabel] -> IOEnv (Env ShIfEnv ()) [FieldLabel]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Rename FieldLabel
rnFieldLabel (IfaceConDecl -> [FieldLabel]
ifConFields IfaceConDecl
d)
    let rnIfaceBang :: IfaceBang -> IOEnv (Env ShIfEnv ()) IfaceBang
rnIfaceBang (IfUnpackCo IfaceCoercion
co) = IfaceCoercion -> IfaceBang
IfUnpackCo (IfaceCoercion -> IfaceBang)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) IfaceBang
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co
        rnIfaceBang IfaceBang
bang = IfaceBang -> IOEnv (Env ShIfEnv ()) IfaceBang
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceBang
bang
    [IfaceBang]
con_stricts <- (IfaceBang -> IOEnv (Env ShIfEnv ()) IfaceBang)
-> [IfaceBang] -> IOEnv (Env ShIfEnv ()) [IfaceBang]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM IfaceBang -> IOEnv (Env ShIfEnv ()) IfaceBang
rnIfaceBang (IfaceConDecl -> [IfaceBang]
ifConStricts IfaceConDecl
d)
    IfaceConDecl -> IOEnv (Env ShIfEnv ()) IfaceConDecl
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceConDecl
d { ifConName = con_name
             , ifConExTCvs = con_ex_tvs
             , ifConUserTvBinders = con_user_tvbs
             , ifConEqSpec = con_eq_spec
             , ifConCtxt = con_ctxt
             , ifConArgTys = con_arg_tys
             , ifConFields = con_fields
             , ifConStricts = con_stricts
             }

rnIfaceClassOp :: Rename IfaceClassOp
rnIfaceClassOp :: IfaceClassOp -> IOEnv (Env ShIfEnv ()) IfaceClassOp
rnIfaceClassOp (IfaceClassOp IfaceTopBndr
n IfaceType
ty Maybe (DefMethSpec IfaceType)
dm) =
    IfaceTopBndr
-> IfaceType -> Maybe (DefMethSpec IfaceType) -> IfaceClassOp
IfaceClassOp (IfaceTopBndr
 -> IfaceType -> Maybe (DefMethSpec IfaceType) -> IfaceClassOp)
-> TcRnIf ShIfEnv () IfaceTopBndr
-> IOEnv
     (Env ShIfEnv ())
     (IfaceType -> Maybe (DefMethSpec IfaceType) -> IfaceClassOp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceGlobal IfaceTopBndr
n
                 IOEnv
  (Env ShIfEnv ())
  (IfaceType -> Maybe (DefMethSpec IfaceType) -> IfaceClassOp)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv
     (Env ShIfEnv ()) (Maybe (DefMethSpec IfaceType) -> IfaceClassOp)
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceType
rnIfaceType IfaceType
ty
                 IOEnv
  (Env ShIfEnv ()) (Maybe (DefMethSpec IfaceType) -> IfaceClassOp)
-> IOEnv (Env ShIfEnv ()) (Maybe (DefMethSpec IfaceType))
-> IOEnv (Env ShIfEnv ()) IfaceClassOp
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
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)) = DefMethSpec IfaceType -> Maybe (DefMethSpec IfaceType)
forall a. a -> Maybe a
Just (DefMethSpec IfaceType -> Maybe (DefMethSpec IfaceType))
-> (IfaceType -> DefMethSpec IfaceType)
-> IfaceType
-> Maybe (DefMethSpec IfaceType)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IfaceType -> DefMethSpec IfaceType
forall ty. ty -> DefMethSpec ty
GenericDM (IfaceType -> Maybe (DefMethSpec IfaceType))
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) (Maybe (DefMethSpec IfaceType))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
ty
rnMaybeDefMethSpec Maybe (DefMethSpec IfaceType)
mb = Rename (Maybe (DefMethSpec IfaceType))
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (DefMethSpec IfaceType)
mb

rnIfaceAxBranch :: Rename IfaceAxBranch
rnIfaceAxBranch :: IfaceAxBranch -> IOEnv (Env ShIfEnv ()) IfaceAxBranch
rnIfaceAxBranch IfaceAxBranch
d = do
    [(IfLclName, IfaceType)]
ty_vars <- ((IfLclName, IfaceType)
 -> IOEnv (Env ShIfEnv ()) (IfLclName, IfaceType))
-> [(IfLclName, IfaceType)]
-> IOEnv (Env ShIfEnv ()) [(IfLclName, IfaceType)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (IfLclName, IfaceType)
-> IOEnv (Env ShIfEnv ()) (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)
    IfaceAxBranch -> IOEnv (Env ShIfEnv ()) IfaceAxBranch
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceAxBranch
d { ifaxbTyVars = ty_vars
             , ifaxbLHS = lhs
             , ifaxbRHS = rhs }

rnIfaceIdInfo :: Rename IfaceIdInfo
rnIfaceIdInfo :: Rename IfaceIdInfo
rnIfaceIdInfo = (IfaceInfoItem -> IOEnv (Env ShIfEnv ()) IfaceInfoItem)
-> Rename IfaceIdInfo
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM IfaceInfoItem -> IOEnv (Env ShIfEnv ()) IfaceInfoItem
rnIfaceInfoItem

rnIfaceInfoItem :: Rename IfaceInfoItem
rnIfaceInfoItem :: IfaceInfoItem -> IOEnv (Env ShIfEnv ()) IfaceInfoItem
rnIfaceInfoItem (HsUnfold Bool
lb IfaceUnfolding
if_unf)
    = Bool -> IfaceUnfolding -> IfaceInfoItem
HsUnfold Bool
lb (IfaceUnfolding -> IfaceInfoItem)
-> IOEnv (Env ShIfEnv ()) IfaceUnfolding
-> IOEnv (Env ShIfEnv ()) IfaceInfoItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceUnfolding
rnIfaceUnfolding IfaceUnfolding
if_unf
rnIfaceInfoItem IfaceInfoItem
i
    = IfaceInfoItem -> IOEnv (Env ShIfEnv ()) IfaceInfoItem
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceInfoItem
i

rnIfaceUnfolding :: Rename IfaceUnfolding
rnIfaceUnfolding :: Rename IfaceUnfolding
rnIfaceUnfolding (IfCoreUnfold UnfoldingSource
src IfUnfoldingCache
cache IfGuidance
guide IfaceExpr
if_expr)
    = UnfoldingSource
-> IfUnfoldingCache -> IfGuidance -> IfaceExpr -> IfaceUnfolding
IfCoreUnfold UnfoldingSource
src IfUnfoldingCache
cache IfGuidance
guide (IfaceExpr -> IfaceUnfolding)
-> IOEnv (Env ShIfEnv ()) IfaceExpr
-> IOEnv (Env ShIfEnv ()) IfaceUnfolding
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 ([IfaceBndr] -> [IfaceExpr] -> IfaceUnfolding)
-> IOEnv (Env ShIfEnv ()) [IfaceBndr]
-> IOEnv (Env ShIfEnv ()) ([IfaceExpr] -> IfaceUnfolding)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IfaceBndr] -> IOEnv (Env ShIfEnv ()) [IfaceBndr]
rnIfaceBndrs [IfaceBndr]
bs IOEnv (Env ShIfEnv ()) ([IfaceExpr] -> IfaceUnfolding)
-> IOEnv (Env ShIfEnv ()) [IfaceExpr]
-> IOEnv (Env ShIfEnv ()) IfaceUnfolding
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceExpr
-> [IfaceExpr] -> IOEnv (Env ShIfEnv ()) [IfaceExpr]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Rename IfaceExpr
rnIfaceExpr [IfaceExpr]
ops

rnIfaceExpr :: Rename IfaceExpr
rnIfaceExpr :: Rename IfaceExpr
rnIfaceExpr (IfaceLcl IfLclName
name) = Rename IfaceExpr
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IfLclName -> IfaceExpr
IfaceLcl IfLclName
name)
rnIfaceExpr (IfaceExt IfaceTopBndr
gbl) = IfaceTopBndr -> IfaceExpr
IfaceExt (IfaceTopBndr -> IfaceExpr)
-> TcRnIf ShIfEnv () IfaceTopBndr
-> IOEnv (Env ShIfEnv ()) IfaceExpr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceGlobal IfaceTopBndr
gbl
rnIfaceExpr (IfaceType IfaceType
ty) = IfaceType -> IfaceExpr
IfaceType (IfaceType -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) IfaceExpr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
ty
rnIfaceExpr (IfaceCo IfaceCoercion
co) = IfaceCoercion -> IfaceExpr
IfaceCo (IfaceCoercion -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) IfaceExpr
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 ([IfaceExpr] -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) [IfaceExpr]
-> IOEnv (Env ShIfEnv ()) IfaceExpr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [IfaceExpr] -> IOEnv (Env ShIfEnv ()) [IfaceExpr]
rnIfaceExprs [IfaceExpr]
args
rnIfaceExpr (IfaceLam IfaceLamBndr
lam_bndr IfaceExpr
expr)
    = IfaceLamBndr -> IfaceExpr -> IfaceExpr
IfaceLam (IfaceLamBndr -> IfaceExpr -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) IfaceLamBndr
-> IOEnv (Env ShIfEnv ()) (IfaceExpr -> IfaceExpr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceLamBndr
rnIfaceLamBndr IfaceLamBndr
lam_bndr IOEnv (Env ShIfEnv ()) (IfaceExpr -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) IfaceExpr
-> IOEnv (Env ShIfEnv ()) IfaceExpr
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
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 (IfaceExpr -> IfaceExpr -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) IfaceExpr
-> IOEnv (Env ShIfEnv ()) (IfaceExpr -> IfaceExpr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceExpr
rnIfaceExpr IfaceExpr
fun IOEnv (Env ShIfEnv ()) (IfaceExpr -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) IfaceExpr
-> IOEnv (Env ShIfEnv ()) IfaceExpr
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
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 (IfaceExpr -> IfLclName -> [IfaceAlt] -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) IfaceExpr
-> IOEnv (Env ShIfEnv ()) (IfLclName -> [IfaceAlt] -> IfaceExpr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceExpr
rnIfaceExpr IfaceExpr
scrut
                IOEnv (Env ShIfEnv ()) (IfLclName -> [IfaceAlt] -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) IfLclName
-> IOEnv (Env ShIfEnv ()) ([IfaceAlt] -> IfaceExpr)
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IfLclName -> IOEnv (Env ShIfEnv ()) IfLclName
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure IfLclName
case_bndr
                IOEnv (Env ShIfEnv ()) ([IfaceAlt] -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) [IfaceAlt]
-> IOEnv (Env ShIfEnv ()) IfaceExpr
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (IfaceAlt -> IOEnv (Env ShIfEnv ()) IfaceAlt)
-> [IfaceAlt] -> IOEnv (Env ShIfEnv ()) [IfaceAlt]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM IfaceAlt -> IOEnv (Env ShIfEnv ()) IfaceAlt
rnIfaceAlt [IfaceAlt]
alts
rnIfaceExpr (IfaceECase IfaceExpr
scrut IfaceType
ty)
    = IfaceExpr -> IfaceType -> IfaceExpr
IfaceECase (IfaceExpr -> IfaceType -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) IfaceExpr
-> IOEnv (Env ShIfEnv ()) (IfaceType -> IfaceExpr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceExpr
rnIfaceExpr IfaceExpr
scrut IOEnv (Env ShIfEnv ()) (IfaceType -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) IfaceExpr
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
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)
    = IfaceBindingX IfaceExpr IfaceLetBndr -> IfaceExpr -> IfaceExpr
IfaceLet (IfaceBindingX IfaceExpr IfaceLetBndr -> IfaceExpr -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) (IfaceBindingX IfaceExpr IfaceLetBndr)
-> IOEnv (Env ShIfEnv ()) (IfaceExpr -> IfaceExpr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (IfaceLetBndr -> IfaceExpr -> IfaceBindingX IfaceExpr IfaceLetBndr
forall r b. b -> r -> IfaceBindingX r b
IfaceNonRec (IfaceLetBndr -> IfaceExpr -> IfaceBindingX IfaceExpr IfaceLetBndr)
-> IOEnv (Env ShIfEnv ()) IfaceLetBndr
-> IOEnv
     (Env ShIfEnv ())
     (IfaceExpr -> IfaceBindingX IfaceExpr IfaceLetBndr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceLetBndr
rnIfaceLetBndr IfaceLetBndr
bndr IOEnv
  (Env ShIfEnv ())
  (IfaceExpr -> IfaceBindingX IfaceExpr IfaceLetBndr)
-> IOEnv (Env ShIfEnv ()) IfaceExpr
-> IOEnv (Env ShIfEnv ()) (IfaceBindingX IfaceExpr IfaceLetBndr)
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceExpr
rnIfaceExpr IfaceExpr
rhs)
               IOEnv (Env ShIfEnv ()) (IfaceExpr -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) IfaceExpr
-> IOEnv (Env ShIfEnv ()) IfaceExpr
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
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)
    = IfaceBindingX IfaceExpr IfaceLetBndr -> IfaceExpr -> IfaceExpr
IfaceLet (IfaceBindingX IfaceExpr IfaceLetBndr -> IfaceExpr -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) (IfaceBindingX IfaceExpr IfaceLetBndr)
-> IOEnv (Env ShIfEnv ()) (IfaceExpr -> IfaceExpr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([(IfaceLetBndr, IfaceExpr)] -> IfaceBindingX IfaceExpr IfaceLetBndr
forall r b. [(b, r)] -> IfaceBindingX r b
IfaceRec ([(IfaceLetBndr, IfaceExpr)]
 -> IfaceBindingX IfaceExpr IfaceLetBndr)
-> IOEnv (Env ShIfEnv ()) [(IfaceLetBndr, IfaceExpr)]
-> IOEnv (Env ShIfEnv ()) (IfaceBindingX IfaceExpr IfaceLetBndr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((IfaceLetBndr, IfaceExpr)
 -> IOEnv (Env ShIfEnv ()) (IfaceLetBndr, IfaceExpr))
-> [(IfaceLetBndr, IfaceExpr)]
-> IOEnv (Env ShIfEnv ()) [(IfaceLetBndr, IfaceExpr)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (\(IfaceLetBndr
bndr, IfaceExpr
rhs) ->
                                        (,) (IfaceLetBndr -> IfaceExpr -> (IfaceLetBndr, IfaceExpr))
-> IOEnv (Env ShIfEnv ()) IfaceLetBndr
-> IOEnv (Env ShIfEnv ()) (IfaceExpr -> (IfaceLetBndr, IfaceExpr))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceLetBndr
rnIfaceLetBndr IfaceLetBndr
bndr
                                            IOEnv (Env ShIfEnv ()) (IfaceExpr -> (IfaceLetBndr, IfaceExpr))
-> IOEnv (Env ShIfEnv ()) IfaceExpr
-> IOEnv (Env ShIfEnv ()) (IfaceLetBndr, IfaceExpr)
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceExpr
rnIfaceExpr IfaceExpr
rhs) [(IfaceLetBndr, IfaceExpr)]
pairs)
               IOEnv (Env ShIfEnv ()) (IfaceExpr -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) IfaceExpr
-> IOEnv (Env ShIfEnv ()) IfaceExpr
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
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 (IfaceExpr -> IfaceCoercion -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) IfaceExpr
-> IOEnv (Env ShIfEnv ()) (IfaceCoercion -> IfaceExpr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceExpr
rnIfaceExpr IfaceExpr
expr IOEnv (Env ShIfEnv ()) (IfaceCoercion -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) IfaceExpr
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co
rnIfaceExpr (IfaceLit Literal
lit)           = Rename IfaceExpr
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Literal -> IfaceExpr
IfaceLit Literal
lit)
rnIfaceExpr (IfaceLitRubbish TypeOrConstraint
tc IfaceType
rep) = TypeOrConstraint -> IfaceType -> IfaceExpr
IfaceLitRubbish TypeOrConstraint
tc (IfaceType -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) IfaceExpr
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 (IfaceType -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) IfaceExpr
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 (IfaceExpr -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) IfaceExpr
-> IOEnv (Env ShIfEnv ()) IfaceExpr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceExpr
rnIfaceExpr IfaceExpr
expr

rnIfaceBndrs :: Rename [IfaceBndr]
rnIfaceBndrs :: [IfaceBndr] -> IOEnv (Env ShIfEnv ()) [IfaceBndr]
rnIfaceBndrs = (IfaceBndr -> IOEnv (Env ShIfEnv ()) IfaceBndr)
-> [IfaceBndr] -> IOEnv (Env ShIfEnv ()) [IfaceBndr]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM IfaceBndr -> IOEnv (Env ShIfEnv ()) IfaceBndr
rnIfaceBndr

rnIfaceBndr :: Rename IfaceBndr
rnIfaceBndr :: IfaceBndr -> IOEnv (Env ShIfEnv ()) IfaceBndr
rnIfaceBndr (IfaceIdBndr (IfaceType
w, IfLclName
fs, IfaceType
ty)) = (IfaceType, IfLclName, IfaceType) -> IfaceBndr
IfaceIdBndr ((IfaceType, IfLclName, IfaceType) -> IfaceBndr)
-> IOEnv (Env ShIfEnv ()) (IfaceType, IfLclName, IfaceType)
-> IOEnv (Env ShIfEnv ()) IfaceBndr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((,,) IfaceType
w IfLclName
fs (IfaceType -> (IfaceType, IfLclName, IfaceType))
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) (IfaceType, IfLclName, IfaceType)
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 ((IfLclName, IfaceType) -> IfaceBndr)
-> IOEnv (Env ShIfEnv ()) (IfLclName, IfaceType)
-> IOEnv (Env ShIfEnv ()) IfaceBndr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (IfLclName, IfaceType)
-> IOEnv (Env ShIfEnv ()) (IfLclName, IfaceType)
rnIfaceTvBndr (IfLclName, IfaceType)
tv_bndr

rnIfaceTvBndr :: Rename IfaceTvBndr
rnIfaceTvBndr :: (IfLclName, IfaceType)
-> IOEnv (Env ShIfEnv ()) (IfLclName, IfaceType)
rnIfaceTvBndr (IfLclName
fs, IfaceType
kind) = (,) IfLclName
fs (IfaceType -> (IfLclName, IfaceType))
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) (IfLclName, IfaceType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
kind

rnIfaceTyConBinder :: Rename IfaceTyConBinder
rnIfaceTyConBinder :: IfaceTyConBinder -> IOEnv (Env ShIfEnv ()) IfaceTyConBinder
rnIfaceTyConBinder (Bndr IfaceBndr
tv TyConBndrVis
vis) = IfaceBndr -> TyConBndrVis -> IfaceTyConBinder
forall var argf. var -> argf -> VarBndr var argf
Bndr (IfaceBndr -> TyConBndrVis -> IfaceTyConBinder)
-> IOEnv (Env ShIfEnv ()) IfaceBndr
-> IOEnv (Env ShIfEnv ()) (TyConBndrVis -> IfaceTyConBinder)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceBndr -> IOEnv (Env ShIfEnv ()) IfaceBndr
rnIfaceBndr IfaceBndr
tv IOEnv (Env ShIfEnv ()) (TyConBndrVis -> IfaceTyConBinder)
-> IOEnv (Env ShIfEnv ()) TyConBndrVis
-> IOEnv (Env ShIfEnv ()) IfaceTyConBinder
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> TyConBndrVis -> IOEnv (Env ShIfEnv ()) TyConBndrVis
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TyConBndrVis
vis

rnIfaceAlt :: Rename IfaceAlt
rnIfaceAlt :: IfaceAlt -> IOEnv (Env ShIfEnv ()) IfaceAlt
rnIfaceAlt (IfaceAlt IfaceConAlt
conalt [IfLclName]
names IfaceExpr
rhs)
     = IfaceConAlt -> [IfLclName] -> IfaceExpr -> IfaceAlt
IfaceAlt (IfaceConAlt -> [IfLclName] -> IfaceExpr -> IfaceAlt)
-> IOEnv (Env ShIfEnv ()) IfaceConAlt
-> IOEnv (Env ShIfEnv ()) ([IfLclName] -> IfaceExpr -> IfaceAlt)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceConAlt
rnIfaceConAlt IfaceConAlt
conalt IOEnv (Env ShIfEnv ()) ([IfLclName] -> IfaceExpr -> IfaceAlt)
-> IOEnv (Env ShIfEnv ()) [IfLclName]
-> IOEnv (Env ShIfEnv ()) (IfaceExpr -> IfaceAlt)
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [IfLclName] -> IOEnv (Env ShIfEnv ()) [IfLclName]
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [IfLclName]
names IOEnv (Env ShIfEnv ()) (IfaceExpr -> IfaceAlt)
-> IOEnv (Env ShIfEnv ()) IfaceExpr
-> IOEnv (Env ShIfEnv ()) IfaceAlt
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
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 (IfaceTopBndr -> IfaceConAlt)
-> TcRnIf ShIfEnv () IfaceTopBndr
-> IOEnv (Env ShIfEnv ()) IfaceConAlt
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceGlobal IfaceTopBndr
data_occ
rnIfaceConAlt IfaceConAlt
alt = Rename IfaceConAlt
forall a. a -> IOEnv (Env ShIfEnv ()) a
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 (IfaceType -> IfaceIdInfo -> IfaceJoinInfo -> IfaceLetBndr)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv
     (Env ShIfEnv ()) (IfaceIdInfo -> IfaceJoinInfo -> IfaceLetBndr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
ty IOEnv
  (Env ShIfEnv ()) (IfaceIdInfo -> IfaceJoinInfo -> IfaceLetBndr)
-> IOEnv (Env ShIfEnv ()) IfaceIdInfo
-> IOEnv (Env ShIfEnv ()) (IfaceJoinInfo -> IfaceLetBndr)
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceIdInfo
rnIfaceIdInfo IfaceIdInfo
info IOEnv (Env ShIfEnv ()) (IfaceJoinInfo -> IfaceLetBndr)
-> IOEnv (Env ShIfEnv ()) IfaceJoinInfo
-> IOEnv (Env ShIfEnv ()) IfaceLetBndr
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IfaceJoinInfo -> IOEnv (Env ShIfEnv ()) IfaceJoinInfo
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceJoinInfo
jpi

rnIfaceLamBndr :: Rename IfaceLamBndr
rnIfaceLamBndr :: Rename IfaceLamBndr
rnIfaceLamBndr (IfaceBndr
bndr, IfaceOneShot
oneshot) = (,) (IfaceBndr -> IfaceOneShot -> IfaceLamBndr)
-> IOEnv (Env ShIfEnv ()) IfaceBndr
-> IOEnv (Env ShIfEnv ()) (IfaceOneShot -> IfaceLamBndr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceBndr -> IOEnv (Env ShIfEnv ()) IfaceBndr
rnIfaceBndr IfaceBndr
bndr IOEnv (Env ShIfEnv ()) (IfaceOneShot -> IfaceLamBndr)
-> IOEnv (Env ShIfEnv ()) IfaceOneShot
-> IOEnv (Env ShIfEnv ()) IfaceLamBndr
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IfaceOneShot -> IOEnv (Env ShIfEnv ()) IfaceOneShot
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceOneShot
oneshot

rnIfaceMCo :: Rename IfaceMCoercion
rnIfaceMCo :: Rename IfaceMCoercion
rnIfaceMCo IfaceMCoercion
IfaceMRefl    = Rename IfaceMCoercion
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceMCoercion
IfaceMRefl
rnIfaceMCo (IfaceMCo IfaceCoercion
co) = IfaceCoercion -> IfaceMCoercion
IfaceMCo (IfaceCoercion -> IfaceMCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) IfaceMCoercion
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 (IfaceType -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
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 (IfaceType -> IfaceMCoercion -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) (IfaceMCoercion -> IfaceCoercion)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
ty IOEnv (Env ShIfEnv ()) (IfaceMCoercion -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceMCoercion
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
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 (IfaceCoercion -> IfaceCoercion -> IfaceCoercion -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv
     (Env ShIfEnv ()) (IfaceCoercion -> IfaceCoercion -> IfaceCoercion)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
w IOEnv
  (Env ShIfEnv ()) (IfaceCoercion -> IfaceCoercion -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) (IfaceCoercion -> IfaceCoercion)
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co1 IOEnv (Env ShIfEnv ()) (IfaceCoercion -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
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 (IfaceTyCon -> [IfaceCoercion] -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceTyCon
-> IOEnv (Env ShIfEnv ()) ([IfaceCoercion] -> IfaceCoercion)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceTyCon
rnIfaceTyCon IfaceTyCon
tc IOEnv (Env ShIfEnv ()) ([IfaceCoercion] -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) [IfaceCoercion]
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
-> [IfaceCoercion] -> IOEnv (Env ShIfEnv ()) [IfaceCoercion]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Rename IfaceCoercion
rnIfaceCo [IfaceCoercion]
cos
rnIfaceCo (IfaceAppCo IfaceCoercion
co1 IfaceCoercion
co2)
    = IfaceCoercion -> IfaceCoercion -> IfaceCoercion
IfaceAppCo (IfaceCoercion -> IfaceCoercion -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) (IfaceCoercion -> IfaceCoercion)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co1 IOEnv (Env ShIfEnv ()) (IfaceCoercion -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
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 (IfaceBndr -> IfaceCoercion -> IfaceCoercion -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceBndr
-> IOEnv
     (Env ShIfEnv ()) (IfaceCoercion -> IfaceCoercion -> IfaceCoercion)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceBndr -> IOEnv (Env ShIfEnv ()) IfaceBndr
rnIfaceBndr IfaceBndr
bndr IOEnv
  (Env ShIfEnv ()) (IfaceCoercion -> IfaceCoercion -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) (IfaceCoercion -> IfaceCoercion)
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co1 IOEnv (Env ShIfEnv ()) (IfaceCoercion -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co2
rnIfaceCo (IfaceFreeCoVar CoVar
c) = Rename IfaceCoercion
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CoVar -> IfaceCoercion
IfaceFreeCoVar CoVar
c)
rnIfaceCo (IfaceCoVarCo IfLclName
lcl) = IfLclName -> IfaceCoercion
IfaceCoVarCo (IfLclName -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfLclName
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfLclName -> IOEnv (Env ShIfEnv ()) IfLclName
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure IfLclName
lcl
rnIfaceCo (IfaceHoleCo CoVar
lcl)  = CoVar -> IfaceCoercion
IfaceHoleCo  (CoVar -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) CoVar
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CoVar -> IOEnv (Env ShIfEnv ()) CoVar
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure CoVar
lcl
rnIfaceCo (IfaceAxiomInstCo IfaceTopBndr
n BranchIndex
i [IfaceCoercion]
cs)
    = IfaceTopBndr -> BranchIndex -> [IfaceCoercion] -> IfaceCoercion
IfaceAxiomInstCo (IfaceTopBndr -> BranchIndex -> [IfaceCoercion] -> IfaceCoercion)
-> TcRnIf ShIfEnv () IfaceTopBndr
-> IOEnv
     (Env ShIfEnv ()) (BranchIndex -> [IfaceCoercion] -> IfaceCoercion)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceGlobal IfaceTopBndr
n IOEnv
  (Env ShIfEnv ()) (BranchIndex -> [IfaceCoercion] -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) BranchIndex
-> IOEnv (Env ShIfEnv ()) ([IfaceCoercion] -> IfaceCoercion)
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BranchIndex -> IOEnv (Env ShIfEnv ()) BranchIndex
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure BranchIndex
i IOEnv (Env ShIfEnv ()) ([IfaceCoercion] -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) [IfaceCoercion]
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
-> [IfaceCoercion] -> IOEnv (Env ShIfEnv ()) [IfaceCoercion]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [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 (IfaceType -> IfaceType -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) (IfaceType -> IfaceCoercion)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
t1 IOEnv (Env ShIfEnv ()) (IfaceType -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
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 (IfaceCoercion -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
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 (IfaceCoercion -> IfaceCoercion -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) (IfaceCoercion -> IfaceCoercion)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
c1 IOEnv (Env ShIfEnv ()) (IfaceCoercion -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
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 (IfaceCoercion -> IfaceCoercion -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) (IfaceCoercion -> IfaceCoercion)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
c1 IOEnv (Env ShIfEnv ()) (IfaceCoercion -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
c2
rnIfaceCo (IfaceSelCo CoSel
d IfaceCoercion
c) = CoSel -> IfaceCoercion -> IfaceCoercion
IfaceSelCo CoSel
d (IfaceCoercion -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
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 (IfaceCoercion -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
c
rnIfaceCo (IfaceSubCo IfaceCoercion
c) = IfaceCoercion -> IfaceCoercion
IfaceSubCo (IfaceCoercion -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
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 ([IfaceCoercion] -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) [IfaceCoercion]
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceCoercion
-> [IfaceCoercion] -> IOEnv (Env ShIfEnv ()) [IfaceCoercion]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Rename IfaceCoercion
rnIfaceCo [IfaceCoercion]
cos
rnIfaceCo (IfaceKindCo IfaceCoercion
c) = IfaceCoercion -> IfaceCoercion
IfaceKindCo (IfaceCoercion -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
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 (IfaceTopBndr -> IfaceTyConInfo -> IfaceTyCon)
-> TcRnIf ShIfEnv () IfaceTopBndr
-> IOEnv (Env ShIfEnv ()) (IfaceTyConInfo -> IfaceTyCon)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceTopBndr -> TcRnIf ShIfEnv () IfaceTopBndr
rnIfaceGlobal IfaceTopBndr
n IOEnv (Env ShIfEnv ()) (IfaceTyConInfo -> IfaceTyCon)
-> IOEnv (Env ShIfEnv ()) IfaceTyConInfo
-> IOEnv (Env ShIfEnv ()) IfaceTyCon
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IfaceTyConInfo -> IOEnv (Env ShIfEnv ()) IfaceTyConInfo
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceTyConInfo
info

rnIfaceExprs :: Rename [IfaceExpr]
rnIfaceExprs :: [IfaceExpr] -> IOEnv (Env ShIfEnv ()) [IfaceExpr]
rnIfaceExprs = Rename IfaceExpr
-> [IfaceExpr] -> IOEnv (Env ShIfEnv ()) [IfaceExpr]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Rename IfaceExpr
rnIfaceExpr

rnIfaceIdDetails :: Rename IfaceIdDetails
rnIfaceIdDetails :: Rename IfaceIdDetails
rnIfaceIdDetails (IfRecSelId (Left IfaceTyCon
tc) Bool
b) = Either IfaceTyCon IfaceDecl -> Bool -> IfaceIdDetails
IfRecSelId (Either IfaceTyCon IfaceDecl -> Bool -> IfaceIdDetails)
-> IOEnv (Env ShIfEnv ()) (Either IfaceTyCon IfaceDecl)
-> IOEnv (Env ShIfEnv ()) (Bool -> IfaceIdDetails)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (IfaceTyCon -> Either IfaceTyCon IfaceDecl)
-> IOEnv (Env ShIfEnv ()) IfaceTyCon
-> IOEnv (Env ShIfEnv ()) (Either IfaceTyCon IfaceDecl)
forall a b.
(a -> b) -> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IfaceTyCon -> Either IfaceTyCon IfaceDecl
forall a b. a -> Either a b
Left (Rename IfaceTyCon
rnIfaceTyCon IfaceTyCon
tc) IOEnv (Env ShIfEnv ()) (Bool -> IfaceIdDetails)
-> IOEnv (Env ShIfEnv ()) Bool
-> IOEnv (Env ShIfEnv ()) IfaceIdDetails
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Bool -> IOEnv (Env ShIfEnv ()) Bool
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
b
rnIfaceIdDetails (IfRecSelId (Right IfaceDecl
decl) Bool
b) = Either IfaceTyCon IfaceDecl -> Bool -> IfaceIdDetails
IfRecSelId (Either IfaceTyCon IfaceDecl -> Bool -> IfaceIdDetails)
-> IOEnv (Env ShIfEnv ()) (Either IfaceTyCon IfaceDecl)
-> IOEnv (Env ShIfEnv ()) (Bool -> IfaceIdDetails)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (IfaceDecl -> Either IfaceTyCon IfaceDecl)
-> IOEnv (Env ShIfEnv ()) IfaceDecl
-> IOEnv (Env ShIfEnv ()) (Either IfaceTyCon IfaceDecl)
forall a b.
(a -> b) -> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IfaceDecl -> Either IfaceTyCon IfaceDecl
forall a b. b -> Either a b
Right (Rename IfaceDecl
rnIfaceDecl IfaceDecl
decl) IOEnv (Env ShIfEnv ()) (Bool -> IfaceIdDetails)
-> IOEnv (Env ShIfEnv ()) Bool
-> IOEnv (Env ShIfEnv ()) IfaceIdDetails
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Bool -> IOEnv (Env ShIfEnv ()) Bool
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
b
rnIfaceIdDetails IfaceIdDetails
details = Rename IfaceIdDetails
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceIdDetails
details

rnIfaceType :: Rename IfaceType
rnIfaceType :: Rename IfaceType
rnIfaceType (IfaceFreeTyVar CoVar
n) = Rename IfaceType
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CoVar -> IfaceType
IfaceFreeTyVar CoVar
n)
rnIfaceType (IfaceTyVar   IfLclName
n)   = Rename IfaceType
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IfLclName -> IfaceType
IfaceTyVar IfLclName
n)
rnIfaceType (IfaceAppTy IfaceType
t1 IfaceAppArgs
t2)
    = IfaceType -> IfaceAppArgs -> IfaceType
IfaceAppTy (IfaceType -> IfaceAppArgs -> IfaceType)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) (IfaceAppArgs -> IfaceType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
t1 IOEnv (Env ShIfEnv ()) (IfaceAppArgs -> IfaceType)
-> IOEnv (Env ShIfEnv ()) IfaceAppArgs
-> IOEnv (Env ShIfEnv ()) IfaceType
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceAppArgs
rnIfaceAppArgs IfaceAppArgs
t2
rnIfaceType (IfaceLitTy IfaceTyLit
l)         = Rename IfaceType
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (m :: * -> *) a. Monad m => a -> m a
return (IfaceTyLit -> IfaceType
IfaceLitTy IfaceTyLit
l)
rnIfaceType (IfaceFunTy FunTyFlag
af IfaceType
w IfaceType
t1 IfaceType
t2)
    = FunTyFlag -> IfaceType -> IfaceType -> IfaceType -> IfaceType
IfaceFunTy FunTyFlag
af (IfaceType -> IfaceType -> IfaceType -> IfaceType)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) (IfaceType -> IfaceType -> IfaceType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
w IOEnv (Env ShIfEnv ()) (IfaceType -> IfaceType -> IfaceType)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) (IfaceType -> IfaceType)
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceType
rnIfaceType IfaceType
t1 IOEnv (Env ShIfEnv ()) (IfaceType -> IfaceType)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) IfaceType
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
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 (IfaceAppArgs -> IfaceType)
-> IOEnv (Env ShIfEnv ()) IfaceAppArgs
-> IOEnv (Env ShIfEnv ()) IfaceType
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 (IfaceTyCon -> IfaceAppArgs -> IfaceType)
-> IOEnv (Env ShIfEnv ()) IfaceTyCon
-> IOEnv (Env ShIfEnv ()) (IfaceAppArgs -> IfaceType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceTyCon
rnIfaceTyCon IfaceTyCon
tc IOEnv (Env ShIfEnv ()) (IfaceAppArgs -> IfaceType)
-> IOEnv (Env ShIfEnv ()) IfaceAppArgs
-> IOEnv (Env ShIfEnv ()) IfaceType
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
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 (IfaceForAllBndr -> IfaceType -> IfaceType)
-> IOEnv (Env ShIfEnv ()) IfaceForAllBndr
-> IOEnv (Env ShIfEnv ()) (IfaceType -> IfaceType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceForAllBndr
forall flag. Rename (VarBndr IfaceBndr flag)
rnIfaceForAllBndr IfaceForAllBndr
tv IOEnv (Env ShIfEnv ()) (IfaceType -> IfaceType)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) IfaceType
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
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 (IfaceCoercion -> IfaceType)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) IfaceType
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 (IfaceType -> IfaceCoercion -> IfaceType)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) (IfaceCoercion -> IfaceType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
ty IOEnv (Env ShIfEnv ()) (IfaceCoercion -> IfaceType)
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
-> IOEnv (Env ShIfEnv ()) IfaceType
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co

rnIfaceScaledType :: Rename (IfaceMult, IfaceType)
rnIfaceScaledType :: (IfaceType, IfaceType)
-> IOEnv (Env ShIfEnv ()) (IfaceType, IfaceType)
rnIfaceScaledType (IfaceType
m, IfaceType
t) = (,) (IfaceType -> IfaceType -> (IfaceType, IfaceType))
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) (IfaceType -> (IfaceType, IfaceType))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
m IOEnv (Env ShIfEnv ()) (IfaceType -> (IfaceType, IfaceType))
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) (IfaceType, IfaceType)
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
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) = IfaceBndr -> flag -> VarBndr IfaceBndr flag
forall var argf. var -> argf -> VarBndr var argf
Bndr (IfaceBndr -> flag -> VarBndr IfaceBndr flag)
-> IOEnv (Env ShIfEnv ()) IfaceBndr
-> IOEnv (Env ShIfEnv ()) (flag -> VarBndr IfaceBndr flag)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceBndr -> IOEnv (Env ShIfEnv ()) IfaceBndr
rnIfaceBndr IfaceBndr
tv IOEnv (Env ShIfEnv ()) (flag -> VarBndr IfaceBndr flag)
-> IOEnv (Env ShIfEnv ()) flag
-> IOEnv (Env ShIfEnv ()) (VarBndr IfaceBndr flag)
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> flag -> IOEnv (Env ShIfEnv ()) flag
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure flag
vis

rnIfaceAppArgs :: Rename IfaceAppArgs
rnIfaceAppArgs :: Rename IfaceAppArgs
rnIfaceAppArgs (IA_Arg IfaceType
t ForAllTyFlag
a IfaceAppArgs
ts) = IfaceType -> ForAllTyFlag -> IfaceAppArgs -> IfaceAppArgs
IA_Arg (IfaceType -> ForAllTyFlag -> IfaceAppArgs -> IfaceAppArgs)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv
     (Env ShIfEnv ()) (ForAllTyFlag -> IfaceAppArgs -> IfaceAppArgs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
t IOEnv
  (Env ShIfEnv ()) (ForAllTyFlag -> IfaceAppArgs -> IfaceAppArgs)
-> IOEnv (Env ShIfEnv ()) ForAllTyFlag
-> IOEnv (Env ShIfEnv ()) (IfaceAppArgs -> IfaceAppArgs)
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ForAllTyFlag -> IOEnv (Env ShIfEnv ()) ForAllTyFlag
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ForAllTyFlag
a
                                        IOEnv (Env ShIfEnv ()) (IfaceAppArgs -> IfaceAppArgs)
-> IOEnv (Env ShIfEnv ()) IfaceAppArgs
-> IOEnv (Env ShIfEnv ()) IfaceAppArgs
forall a b.
IOEnv (Env ShIfEnv ()) (a -> b)
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceAppArgs
rnIfaceAppArgs IfaceAppArgs
ts
rnIfaceAppArgs IfaceAppArgs
IA_Nil = Rename IfaceAppArgs
forall a. a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceAppArgs
IA_Nil