{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
module RnModIface(
    rnModIface,
    rnModExports,
    tcRnModIface,
    tcRnModExports,
    ) where
#include "HsVersions.h"
import GhcPrelude
import SrcLoc
import Outputable
import HscTypes
import Module
import UniqFM
import Avail
import IfaceSyn
import FieldLabel
import Var
import ErrUtils
import Name
import TcRnMonad
import Util
import Fingerprint
import BasicTypes
import {-# SOURCE #-} LoadIface
import DynFlags
import qualified Data.Traversable as T
import Bag
import Data.IORef
import NameShape
import IfaceEnv
tcRnMsgMaybe :: IO (Either ErrorMessages a) -> TcM a
tcRnMsgMaybe :: IO (Either ErrorMessages a) -> TcM a
tcRnMsgMaybe IO (Either ErrorMessages a)
do_this = do
    Either ErrorMessages a
r <- IO (Either ErrorMessages a)
-> IOEnv (Env TcGblEnv TcLclEnv) (Either ErrorMessages a)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either ErrorMessages a)
 -> IOEnv (Env TcGblEnv TcLclEnv) (Either ErrorMessages a))
-> IO (Either ErrorMessages a)
-> IOEnv (Env TcGblEnv TcLclEnv) (Either ErrorMessages a)
forall a b. (a -> b) -> a -> b
$ IO (Either ErrorMessages a)
do_this
    case Either ErrorMessages a
r of
        Left ErrorMessages
errs -> do
            Messages -> TcRn ()
addMessages (ErrorMessages
forall a. Bag a
emptyBag, ErrorMessages
errs)
            TcM a
forall env a. IOEnv env a
failM
        Right a
x -> a -> TcM 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 ErrorMessages ModIface) -> TcM ModIface
forall a. IO (Either ErrorMessages a) -> TcM a
tcRnMsgMaybe (IO (Either ErrorMessages ModIface) -> TcM ModIface)
-> IO (Either ErrorMessages ModIface) -> TcM ModIface
forall a b. (a -> b) -> a -> b
$ HscEnv
-> [(ModuleName, Module)]
-> Maybe NameShape
-> ModIface
-> IO (Either ErrorMessages 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 ErrorMessages [AvailInfo]) -> TcM [AvailInfo]
forall a. IO (Either ErrorMessages a) -> TcM a
tcRnMsgMaybe (IO (Either ErrorMessages [AvailInfo]) -> TcM [AvailInfo])
-> IO (Either ErrorMessages [AvailInfo]) -> TcM [AvailInfo]
forall a b. (a -> b) -> a -> b
$ HscEnv
-> [(ModuleName, Module)]
-> ModIface
-> IO (Either ErrorMessages [AvailInfo])
rnModExports HscEnv
hsc_env [(ModuleName, Module)]
x ModIface
y
failWithRn :: SDoc -> ShIfM a
failWithRn :: SDoc -> ShIfM a
failWithRn SDoc
doc = do
    IORef ErrorMessages
errs_var <- (ShIfEnv -> IORef ErrorMessages)
-> IOEnv (Env ShIfEnv ()) ShIfEnv
-> IOEnv (Env ShIfEnv ()) (IORef ErrorMessages)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShIfEnv -> IORef ErrorMessages
sh_if_errs IOEnv (Env ShIfEnv ()) ShIfEnv
forall gbl lcl. TcRnIf gbl lcl gbl
getGblEnv
    DynFlags
dflags <- IOEnv (Env ShIfEnv ()) DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
    ErrorMessages
errs <- IORef ErrorMessages -> TcRnIf ShIfEnv () ErrorMessages
forall a gbl lcl. TcRef a -> TcRnIf gbl lcl a
readTcRef IORef ErrorMessages
errs_var
    
    IORef ErrorMessages -> ErrorMessages -> TcRnIf ShIfEnv () ()
forall a gbl lcl. TcRef a -> a -> TcRnIf gbl lcl ()
writeTcRef IORef ErrorMessages
errs_var (ErrorMessages
errs ErrorMessages -> ErrMsg -> ErrorMessages
forall a. Bag a -> a -> Bag a
`snocBag` DynFlags -> SrcSpan -> SDoc -> ErrMsg
mkPlainErrMsg DynFlags
dflags SrcSpan
noSrcSpan SDoc
doc)
    ShIfM a
forall env a. IOEnv env a
failM
rnModIface :: HscEnv -> [(ModuleName, Module)] -> Maybe NameShape
           -> ModIface -> IO (Either ErrorMessages ModIface)
rnModIface :: HscEnv
-> [(ModuleName, Module)]
-> Maybe NameShape
-> ModIface
-> IO (Either ErrorMessages ModIface)
rnModIface HscEnv
hsc_env [(ModuleName, Module)]
insts Maybe NameShape
nsubst ModIface
iface = do
    HscEnv
-> ModIface
-> [(ModuleName, Module)]
-> Maybe NameShape
-> ShIfM ModIface
-> IO (Either ErrorMessages ModIface)
forall a.
HscEnv
-> ModIface
-> [(ModuleName, Module)]
-> Maybe NameShape
-> ShIfM a
-> IO (Either ErrorMessages a)
initRnIface HscEnv
hsc_env ModIface
iface [(ModuleName, Module)]
insts Maybe NameShape
nsubst (ShIfM ModIface -> IO (Either ErrorMessages ModIface))
-> ShIfM ModIface -> IO (Either ErrorMessages 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 (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 (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)
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)
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)
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)
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)
        
        
        ModIface -> ShIfM ModIface
forall (m :: * -> *) a. Monad m => a -> m a
return ModIface
iface { mi_module :: Module
mi_module = Module
mod
                     , mi_sig_of :: Maybe Module
mi_sig_of = Maybe Module
sig_of
                     , mi_insts :: [IfaceClsInst]
mi_insts = [IfaceClsInst]
insts
                     , mi_fam_insts :: [IfaceFamInst]
mi_fam_insts = [IfaceFamInst]
fams
                     , mi_exports :: [AvailInfo]
mi_exports = [AvailInfo]
exports
                     , mi_decls :: [IfaceDeclExts 'ModIfaceFinal]
mi_decls = [(Fingerprint, IfaceDecl)]
[IfaceDeclExts 'ModIfaceFinal]
decls
                     , mi_deps :: Dependencies
mi_deps = Dependencies
deps }
rnModExports :: HscEnv -> [(ModuleName, Module)] -> ModIface -> IO (Either ErrorMessages [AvailInfo])
rnModExports :: HscEnv
-> [(ModuleName, Module)]
-> ModIface
-> IO (Either ErrorMessages [AvailInfo])
rnModExports HscEnv
hsc_env [(ModuleName, Module)]
insts ModIface
iface
    = HscEnv
-> ModIface
-> [(ModuleName, Module)]
-> Maybe NameShape
-> IOEnv (Env ShIfEnv ()) [AvailInfo]
-> IO (Either ErrorMessages [AvailInfo])
forall a.
HscEnv
-> ModIface
-> [(ModuleName, Module)]
-> Maybe NameShape
-> ShIfM a
-> IO (Either ErrorMessages a)
initRnIface HscEnv
hsc_env ModIface
iface [(ModuleName, Module)]
insts Maybe NameShape
forall a. Maybe a
Nothing
    (IOEnv (Env ShIfEnv ()) [AvailInfo]
 -> IO (Either ErrorMessages [AvailInfo]))
-> IOEnv (Env ShIfEnv ()) [AvailInfo]
-> IO (Either ErrorMessages [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)
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
deps = do
    [Module]
orphs  <- (Dependencies -> [Module]) -> Dependencies -> ShIfM [Module]
rnDepModules Dependencies -> [Module]
dep_orphs Dependencies
deps
    [Module]
finsts <- (Dependencies -> [Module]) -> Dependencies -> ShIfM [Module]
rnDepModules Dependencies -> [Module]
dep_finsts Dependencies
deps
    Rename Dependencies
forall (m :: * -> *) a. Monad m => a -> m a
return Dependencies
deps { dep_orphs :: [Module]
dep_orphs = [Module]
orphs, dep_finsts :: [Module]
dep_finsts = [Module]
finsts }
rnDepModules :: (Dependencies -> [Module]) -> Dependencies -> ShIfM [Module]
rnDepModules :: (Dependencies -> [Module]) -> Dependencies -> ShIfM [Module]
rnDepModules Dependencies -> [Module]
sel Dependencies
deps = do
    HscEnv
hsc_env <- TcRnIf ShIfEnv () HscEnv
forall gbl lcl. TcRnIf gbl lcl HscEnv
getTopEnv
    ShHoleSubst
hmap <- ShIfM ShHoleSubst
getHoleSubst
    
    
    
    ([[Module]] -> [Module])
-> IOEnv (Env ShIfEnv ()) [[Module]] -> ShIfM [Module]
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]] -> ShIfM [Module])
-> ((Module -> ShIfM [Module])
    -> IOEnv (Env ShIfEnv ()) [[Module]])
-> (Module -> ShIfM [Module])
-> ShIfM [Module]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Module]
-> (Module -> ShIfM [Module]) -> IOEnv (Env ShIfEnv ()) [[Module]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
T.forM (Dependencies -> [Module]
sel Dependencies
deps) ((Module -> ShIfM [Module]) -> ShIfM [Module])
-> (Module -> ShIfM [Module]) -> ShIfM [Module]
forall a b. (a -> b) -> a -> b
$ \Module
mod -> do
        DynFlags
dflags <- IOEnv (Env ShIfEnv ()) DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        let mod' :: Module
mod' = DynFlags -> ShHoleSubst -> Module -> Module
renameHoleModule DynFlags
dflags ShHoleSubst
hmap Module
mod
        if Module -> Bool
isHoleModule Module
mod
          then do ModIface
iface <- IO ModIface -> ShIfM ModIface
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
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
text String
"rnDepModule") Module
mod'
                  [Module] -> ShIfM [Module]
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] -> ShIfM [Module]
forall (m :: * -> *) a. Monad m => a -> m a
return [Module
mod']
initRnIface :: HscEnv -> ModIface -> [(ModuleName, Module)] -> Maybe NameShape
            -> ShIfM a -> IO (Either ErrorMessages a)
initRnIface :: HscEnv
-> ModIface
-> [(ModuleName, Module)]
-> Maybe NameShape
-> ShIfM a
-> IO (Either ErrorMessages a)
initRnIface HscEnv
hsc_env ModIface
iface [(ModuleName, Module)]
insts Maybe NameShape
nsubst ShIfM a
do_this = do
    IORef ErrorMessages
errs_var <- ErrorMessages -> IO (IORef ErrorMessages)
forall a. a -> IO (IORef a)
newIORef ErrorMessages
forall a. Bag a
emptyBag
    let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
        hsubst :: ShHoleSubst
hsubst = [(ModuleName, Module)] -> ShHoleSubst
forall key elt. Uniquable key => [(key, elt)] -> UniqFM elt
listToUFM [(ModuleName, Module)]
insts
        rn_mod :: Module -> Module
rn_mod = DynFlags -> ShHoleSubst -> Module -> Module
renameHoleModule DynFlags
dflags ShHoleSubst
hsubst
        env :: ShIfEnv
env = ShIfEnv :: Module
-> Module
-> ShHoleSubst
-> Maybe NameShape
-> IORef ErrorMessages
-> ShIfEnv
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 elt
listToUFM [(ModuleName, Module)]
insts,
            sh_if_shape :: Maybe NameShape
sh_if_shape = Maybe NameShape
nsubst,
            sh_if_errs :: IORef ErrorMessages
sh_if_errs = IORef ErrorMessages
errs_var
        }
    
    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
    ErrorMessages
msgs <- IORef ErrorMessages -> IO ErrorMessages
forall a. IORef a -> IO a
readIORef IORef ErrorMessages
errs_var
    case Either IOEnvFailure a
res of
        Left IOEnvFailure
_                          -> Either ErrorMessages a -> IO (Either ErrorMessages a)
forall (m :: * -> *) a. Monad m => a -> m a
return (ErrorMessages -> Either ErrorMessages a
forall a b. a -> Either a b
Left ErrorMessages
msgs)
        Right a
r | Bool -> Bool
not (ErrorMessages -> Bool
forall a. Bag a -> Bool
isEmptyBag ErrorMessages
msgs) -> Either ErrorMessages a -> IO (Either ErrorMessages a)
forall (m :: * -> *) a. Monad m => a -> m a
return (ErrorMessages -> Either ErrorMessages a
forall a b. a -> Either a b
Left ErrorMessages
msgs)
                | Bool
otherwise             -> Either ErrorMessages a -> IO (Either ErrorMessages a)
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Either ErrorMessages a
forall a b. b -> Either a b
Right a
r)
data ShIfEnv = ShIfEnv {
        
        
        
        ShIfEnv -> Module
sh_if_module :: Module,
        
        ShIfEnv -> Module
sh_if_semantic_module :: Module,
        
        
        ShIfEnv -> ShHoleSubst
sh_if_hole_subst :: ShHoleSubst,
        
        
        
        
        ShIfEnv -> Maybe NameShape
sh_if_shape :: Maybe NameShape,
        
        ShIfEnv -> IORef ErrorMessages
sh_if_errs :: IORef ErrorMessages
    }
getHoleSubst :: ShIfM ShHoleSubst
getHoleSubst :: ShIfM ShHoleSubst
getHoleSubst = (ShIfEnv -> ShHoleSubst)
-> IOEnv (Env ShIfEnv ()) ShIfEnv -> ShIfM ShHoleSubst
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
    DynFlags
dflags <- IOEnv (Env ShIfEnv ()) DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
    Rename Module
forall (m :: * -> *) a. Monad m => a -> m a
return (DynFlags -> ShHoleSubst -> Module -> Module
renameHoleModule DynFlags
dflags ShHoleSubst
hmap Module
mod)
rnAvailInfo :: Rename AvailInfo
rnAvailInfo :: AvailInfo -> IOEnv (Env ShIfEnv ()) AvailInfo
rnAvailInfo (Avail Name
n) = Name -> AvailInfo
Avail (Name -> AvailInfo)
-> IOEnv (Env ShIfEnv ()) Name -> IOEnv (Env ShIfEnv ()) AvailInfo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal Name
n
rnAvailInfo (AvailTC Name
n [Name]
ns [FieldLabel]
fs) = do
    
    
    
    
    
    [Name]
ns' <- (Name -> IOEnv (Env ShIfEnv ()) Name)
-> [Name] -> IOEnv (Env ShIfEnv ()) [Name]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal [Name]
ns
    [FieldLabel]
fs' <- (FieldLabel -> IOEnv (Env ShIfEnv ()) FieldLabel)
-> [FieldLabel] -> IOEnv (Env ShIfEnv ()) [FieldLabel]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM FieldLabel -> IOEnv (Env ShIfEnv ()) FieldLabel
rnFieldLabel [FieldLabel]
fs
    case [Name]
ns' [Name] -> [Name] -> [Name]
forall a. [a] -> [a] -> [a]
++ (FieldLabel -> Name) -> [FieldLabel] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map FieldLabel -> Name
forall a. FieldLbl a -> a
flSelector [FieldLabel]
fs' of
        [] -> String -> IOEnv (Env ShIfEnv ()) AvailInfo
forall a. String -> a
panic String
"rnAvailInfoEmpty AvailInfo"
        (Name
rep:[Name]
rest) -> ASSERT2( all ((== nameModule rep) . nameModule) rest, ppr rep $$ hcat (map ppr rest) ) do
                         n' <- setNameModule (Just (nameModule rep)) n
                         return (AvailTC n' ns' fs')
rnFieldLabel :: Rename FieldLabel
rnFieldLabel :: FieldLabel -> IOEnv (Env ShIfEnv ()) FieldLabel
rnFieldLabel (FieldLabel FieldLabelString
l Bool
b Name
sel) = do
    Name
sel' <- Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal Name
sel
    FieldLabel -> IOEnv (Env ShIfEnv ()) FieldLabel
forall (m :: * -> *) a. Monad m => a -> m a
return (FieldLabelString -> Bool -> Name -> FieldLabel
forall a. FieldLabelString -> Bool -> a -> FieldLbl a
FieldLabel FieldLabelString
l Bool
b Name
sel')
rnIfaceGlobal :: Name -> ShIfM Name
rnIfaceGlobal :: Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal Name
n = do
    HscEnv
hsc_env <- TcRnIf ShIfEnv () HscEnv
forall gbl lcl. TcRnIf gbl lcl HscEnv
getTopEnv
    let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
    Module
iface_semantic_mod <- (ShIfEnv -> Module)
-> IOEnv (Env ShIfEnv ()) ShIfEnv -> IOEnv (Env ShIfEnv ()) Module
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 (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 = HasDebugCallStack => Name -> Module
Name -> Module
nameModule Name
n
        m' :: Module
m' = DynFlags -> ShHoleSubst -> Module -> Module
renameHoleModule DynFlags
dflags ShHoleSubst
hmap Module
m
    case () of
       
       
       
     ()
_ | Module
m' Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
== Module
iface_semantic_mod
       , Module -> Bool
isHoleModule Module
m'
      
      
      -> do Name
n' <- Maybe Module -> Name -> IOEnv (Env ShIfEnv ()) Name
forall m n. Maybe Module -> Name -> TcRnIf m n Name
setNameModule (Module -> Maybe Module
forall a. a -> Maybe a
Just Module
m') Name
n
            case Maybe NameShape
mb_nsubst of
                Maybe NameShape
Nothing -> Name -> IOEnv (Env ShIfEnv ()) Name
forall (m :: * -> *) a. Monad m => a -> m a
return Name
n'
                Just NameShape
nsubst ->
                    case NameShape -> Name -> Maybe Name
maybeSubstNameShape NameShape
nsubst Name
n' of
                        
                        
                        
                        
                        Maybe Name
Nothing -> SDoc -> IOEnv (Env ShIfEnv ()) Name
forall a. SDoc -> ShIfM a
failWithRn (SDoc -> IOEnv (Env ShIfEnv ()) Name)
-> SDoc -> IOEnv (Env ShIfEnv ()) Name
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
vcat [
                            String -> SDoc
text String
"The identifier" SDoc -> SDoc -> SDoc
<+> OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Name -> OccName
forall name. HasOccName name => name -> OccName
occName Name
n') SDoc -> SDoc -> SDoc
<+>
                                String -> SDoc
text String
"does not exist in the local signature.",
                            SDoc -> SDoc
parens (String -> SDoc
text String
"Try adding it to the export list of the hsig file.")
                            ]
                        Just Name
n'' -> Name -> IOEnv (Env ShIfEnv ()) Name
forall (m :: * -> *) a. Monad m => a -> m a
return Name
n''
       
       
       | Bool -> Bool
not (Module -> Bool
isHoleModule Module
m)
      -> Maybe Module -> Name -> IOEnv (Env ShIfEnv ()) Name
forall m n. Maybe Module -> Name -> TcRnIf m n Name
setNameModule (Module -> Maybe Module
forall a. a -> Maybe a
Just Module
m') Name
n
       
       
       
       
       
       
       | Bool
otherwise
      -> do 
            
            let m'' :: Module
m'' = if Module -> Bool
isHoleModule Module
m'
                        
                        then UnitId -> ModuleName -> Module
mkModule (DynFlags -> UnitId
thisPackage DynFlags
dflags) (Module -> ModuleName
moduleName Module
m')
                        else Module
m'
            ModIface
iface <- IO ModIface -> ShIfM ModIface
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
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
text String
"rnIfaceGlobal") Module
m''
            let nsubst :: NameShape
nsubst = ModuleName -> [AvailInfo] -> NameShape
mkNameShape (Module -> ModuleName
moduleName Module
m) (ModIface -> [AvailInfo]
forall (phase :: ModIfacePhase). ModIface_ phase -> [AvailInfo]
mi_exports ModIface
iface)
            case NameShape -> Name -> Maybe Name
maybeSubstNameShape NameShape
nsubst Name
n of
                Maybe Name
Nothing -> SDoc -> IOEnv (Env ShIfEnv ()) Name
forall a. SDoc -> ShIfM a
failWithRn (SDoc -> IOEnv (Env ShIfEnv ()) Name)
-> SDoc -> IOEnv (Env ShIfEnv ()) Name
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
vcat [
                    String -> SDoc
text String
"The identifier" SDoc -> SDoc -> SDoc
<+> OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Name -> OccName
forall name. HasOccName name => name -> OccName
occName Name
n) SDoc -> SDoc -> SDoc
<+>
                        
                        String -> SDoc
text String
"does not exist in the signature for" SDoc -> SDoc -> SDoc
<+> Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
m',
                    SDoc -> SDoc
parens (String -> SDoc
text String
"Try adding it to the export list in that hsig file.")
                    ]
                Just Name
n' -> Name -> IOEnv (Env ShIfEnv ()) Name
forall (m :: * -> *) a. Monad m => a -> m a
return Name
n'
rnIfaceNeverExported :: Name -> ShIfM Name
rnIfaceNeverExported :: Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceNeverExported Name
name = do
    ShHoleSubst
hmap <- ShIfM ShHoleSubst
getHoleSubst
    DynFlags
dflags <- IOEnv (Env ShIfEnv ()) DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
    Module
iface_semantic_mod <- (ShIfEnv -> Module)
-> IOEnv (Env ShIfEnv ()) ShIfEnv -> IOEnv (Env ShIfEnv ()) Module
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 = DynFlags -> ShHoleSubst -> Module -> Module
renameHoleModule DynFlags
dflags ShHoleSubst
hmap (Module -> Module) -> Module -> Module
forall a b. (a -> b) -> a -> b
$ HasDebugCallStack => Name -> Module
Name -> Module
nameModule Name
name
    
    MASSERT2( iface_semantic_mod == m, ppr iface_semantic_mod <+> ppr m )
    Maybe Module -> Name -> IOEnv (Env ShIfEnv ()) Name
forall m n. Maybe Module -> Name -> TcRnIf m n Name
setNameModule (Module -> Maybe Module
forall a. a -> Maybe a
Just Module
m) Name
name
rnIfaceClsInst :: Rename IfaceClsInst
rnIfaceClsInst :: IfaceClsInst -> IOEnv (Env ShIfEnv ()) IfaceClsInst
rnIfaceClsInst IfaceClsInst
cls_inst = do
    Name
n <- Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal (IfaceClsInst -> Name
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)
mapM Maybe IfaceTyCon -> IOEnv (Env ShIfEnv ()) (Maybe IfaceTyCon)
rnMaybeIfaceTyCon (IfaceClsInst -> [Maybe IfaceTyCon]
ifInstTys IfaceClsInst
cls_inst)
    Name
dfun <- Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceNeverExported (IfaceClsInst -> Name
ifDFun IfaceClsInst
cls_inst)
    IfaceClsInst -> IOEnv (Env ShIfEnv ()) IfaceClsInst
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceClsInst
cls_inst { ifInstCls :: Name
ifInstCls = Name
n
                    , ifInstTys :: [Maybe IfaceTyCon]
ifInstTys = [Maybe IfaceTyCon]
tys
                    , ifDFun :: Name
ifDFun = Name
dfun
                    }
rnMaybeIfaceTyCon :: Rename (Maybe IfaceTyCon)
rnMaybeIfaceTyCon :: Maybe IfaceTyCon -> IOEnv (Env ShIfEnv ()) (Maybe IfaceTyCon)
rnMaybeIfaceTyCon Maybe IfaceTyCon
Nothing = Maybe IfaceTyCon -> IOEnv (Env ShIfEnv ()) (Maybe IfaceTyCon)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe IfaceTyCon
forall a. Maybe a
Nothing
rnMaybeIfaceTyCon (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
    Name
fam <- Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal (IfaceFamInst -> Name
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)
mapM Maybe IfaceTyCon -> IOEnv (Env ShIfEnv ()) (Maybe IfaceTyCon)
rnMaybeIfaceTyCon (IfaceFamInst -> [Maybe IfaceTyCon]
ifFamInstTys IfaceFamInst
d)
    Name
axiom <- Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal (IfaceFamInst -> Name
ifFamInstAxiom IfaceFamInst
d)
    IfaceFamInst -> IOEnv (Env ShIfEnv ()) IfaceFamInst
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceFamInst
d { ifFamInstFam :: Name
ifFamInstFam = Name
fam, ifFamInstTys :: [Maybe IfaceTyCon]
ifFamInstTys = [Maybe IfaceTyCon]
tys, ifFamInstAxiom :: Name
ifFamInstAxiom = Name
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
            Name
name <- case IfaceDecl -> IfaceIdDetails
ifIdDetails IfaceDecl
d of
                      IfaceIdDetails
IfDFunId -> Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceNeverExported (IfaceDecl -> Name
ifName IfaceDecl
d)
                      IfaceIdDetails
_ | OccName -> Bool
isDefaultMethodOcc (Name -> OccName
forall name. HasOccName name => name -> OccName
occName (IfaceDecl -> Name
ifName IfaceDecl
d))
                        -> Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceNeverExported (IfaceDecl -> Name
ifName IfaceDecl
d)
                      
                      IfaceIdDetails
_ | OccName -> Bool
isTypeableBindOcc (Name -> OccName
forall name. HasOccName name => name -> OccName
occName (IfaceDecl -> Name
ifName IfaceDecl
d))
                        -> Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceNeverExported (IfaceDecl -> Name
ifName IfaceDecl
d)
                        | Bool
otherwise -> Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal (IfaceDecl -> Name
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 (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName :: Name
ifName = Name
name
                     , ifType :: IfaceType
ifType = IfaceType
ty
                     , ifIdDetails :: IfaceIdDetails
ifIdDetails = IfaceIdDetails
details
                     , ifIdInfo :: IfaceIdInfo
ifIdInfo = IfaceIdInfo
info
                     }
rnIfaceDecl d :: IfaceDecl
d@IfaceData{} = do
            Name
name <- Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal (IfaceDecl -> Name
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)
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)
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 (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName :: Name
ifName = Name
name
                     , ifBinders :: [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
binders
                     , ifCtxt :: [IfaceType]
ifCtxt = [IfaceType]
ctxt
                     , ifCons :: IfaceConDecls
ifCons = IfaceConDecls
cons
                     , ifResKind :: IfaceType
ifResKind = IfaceType
res_kind
                     , ifParent :: IfaceTyConParent
ifParent = IfaceTyConParent
parent
                     }
rnIfaceDecl d :: IfaceDecl
d@IfaceSynonym{} = do
            Name
name <- Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal (IfaceDecl -> Name
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)
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 (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName :: Name
ifName = Name
name
                     , ifBinders :: [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
binders
                     , ifResKind :: IfaceType
ifResKind = IfaceType
syn_kind
                     , ifSynRhs :: IfaceType
ifSynRhs = IfaceType
syn_rhs
                     }
rnIfaceDecl d :: IfaceDecl
d@IfaceFamily{} = do
            Name
name <- Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal (IfaceDecl -> Name
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)
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 (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName :: Name
ifName = Name
name
                     , ifBinders :: [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
binders
                     , ifResKind :: IfaceType
ifResKind = IfaceType
fam_kind
                     , ifFamFlav :: IfaceFamTyConFlav
ifFamFlav = IfaceFamTyConFlav
fam_flav
                     }
rnIfaceDecl d :: IfaceDecl
d@IfaceClass{} = do
            Name
name <- Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal (IfaceDecl -> Name
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)
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 (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName :: Name
ifName    = Name
name
                     , ifBinders :: [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
binders
                     , ifBody :: IfaceClassBody
ifBody    = IfaceClassBody
body
                     }
rnIfaceDecl d :: IfaceDecl
d@IfaceAxiom{} = do
            Name
name <- Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceNeverExported (IfaceDecl -> Name
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)
mapM IfaceAxBranch -> IOEnv (Env ShIfEnv ()) IfaceAxBranch
rnIfaceAxBranch (IfaceDecl -> [IfaceAxBranch]
ifAxBranches IfaceDecl
d)
            Rename IfaceDecl
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName :: Name
ifName = Name
name
                     , ifTyCon :: IfaceTyCon
ifTyCon = IfaceTyCon
tycon
                     , ifAxBranches :: [IfaceAxBranch]
ifAxBranches = [IfaceAxBranch]
ax_branches
                     }
rnIfaceDecl d :: IfaceDecl
d@IfacePatSyn{} =  do
            Name
name <- Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal (IfaceDecl -> Name
ifName IfaceDecl
d)
            let rnPat :: (Name, a) -> IOEnv (Env ShIfEnv ()) (Name, a)
rnPat (Name
n, a
b) = (,) (Name -> a -> (Name, a))
-> IOEnv (Env ShIfEnv ()) Name
-> IOEnv (Env ShIfEnv ()) (a -> (Name, a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal Name
n IOEnv (Env ShIfEnv ()) (a -> (Name, a))
-> IOEnv (Env ShIfEnv ()) a -> IOEnv (Env ShIfEnv ()) (Name, a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> IOEnv (Env ShIfEnv ()) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
b
            (Name, Bool)
pat_matcher <- (Name, Bool) -> IOEnv (Env ShIfEnv ()) (Name, Bool)
forall a. (Name, a) -> IOEnv (Env ShIfEnv ()) (Name, a)
rnPat (IfaceDecl -> (Name, Bool)
ifPatMatcher IfaceDecl
d)
            Maybe (Name, Bool)
pat_builder <- ((Name, Bool) -> IOEnv (Env ShIfEnv ()) (Name, Bool))
-> Maybe (Name, Bool)
-> IOEnv (Env ShIfEnv ()) (Maybe (Name, Bool))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
T.traverse (Name, Bool) -> IOEnv (Env ShIfEnv ()) (Name, Bool)
forall a. (Name, a) -> IOEnv (Env ShIfEnv ()) (Name, a)
rnPat (IfaceDecl -> Maybe (Name, Bool)
ifPatBuilder IfaceDecl
d)
            [IfaceForAllBndr]
pat_univ_bndrs <- (IfaceForAllBndr -> IOEnv (Env ShIfEnv ()) IfaceForAllBndr)
-> [IfaceForAllBndr] -> IOEnv (Env ShIfEnv ()) [IfaceForAllBndr]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM IfaceForAllBndr -> IOEnv (Env ShIfEnv ()) IfaceForAllBndr
rnIfaceForAllBndr (IfaceDecl -> [IfaceForAllBndr]
ifPatUnivBndrs IfaceDecl
d)
            [IfaceForAllBndr]
pat_ex_bndrs <- (IfaceForAllBndr -> IOEnv (Env ShIfEnv ()) IfaceForAllBndr)
-> [IfaceForAllBndr] -> IOEnv (Env ShIfEnv ()) [IfaceForAllBndr]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM IfaceForAllBndr -> IOEnv (Env ShIfEnv ()) IfaceForAllBndr
rnIfaceForAllBndr (IfaceDecl -> [IfaceForAllBndr]
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)
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)
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)
mapM Rename IfaceType
rnIfaceType (IfaceDecl -> [IfaceType]
ifPatArgs IfaceDecl
d)
            IfaceType
pat_ty <- Rename IfaceType
rnIfaceType (IfaceDecl -> IfaceType
ifPatTy IfaceDecl
d)
            Rename IfaceDecl
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceDecl
d { ifName :: Name
ifName = Name
name
                     , ifPatMatcher :: (Name, Bool)
ifPatMatcher = (Name, Bool)
pat_matcher
                     , ifPatBuilder :: Maybe (Name, Bool)
ifPatBuilder = Maybe (Name, Bool)
pat_builder
                     , ifPatUnivBndrs :: [IfaceForAllBndr]
ifPatUnivBndrs = [IfaceForAllBndr]
pat_univ_bndrs
                     , ifPatExBndrs :: [IfaceForAllBndr]
ifPatExBndrs = [IfaceForAllBndr]
pat_ex_bndrs
                     , ifPatProvCtxt :: [IfaceType]
ifPatProvCtxt = [IfaceType]
pat_prov_ctxt
                     , ifPatReqCtxt :: [IfaceType]
ifPatReqCtxt = [IfaceType]
pat_req_ctxt
                     , ifPatArgs :: [IfaceType]
ifPatArgs = [IfaceType]
pat_args
                     , ifPatTy :: IfaceType
ifPatTy = IfaceType
pat_ty
                     }
rnIfaceClassBody :: Rename IfaceClassBody
rnIfaceClassBody :: Rename IfaceClassBody
rnIfaceClassBody IfaceClassBody
IfAbstractClass = Rename IfaceClassBody
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)
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)
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)
mapM IfaceClassOp -> IOEnv (Env ShIfEnv ()) IfaceClassOp
rnIfaceClassOp (IfaceClassBody -> [IfaceClassOp]
ifSigs IfaceClassBody
d)
    Rename IfaceClassBody
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceClassBody
d { ifClassCtxt :: [IfaceType]
ifClassCtxt = [IfaceType]
ctxt, ifATs :: [IfaceAT]
ifATs = [IfaceAT]
ats, ifSigs :: [IfaceClassOp]
ifSigs = [IfaceClassOp]
sigs }
rnIfaceFamTyConFlav :: Rename IfaceFamTyConFlav
rnIfaceFamTyConFlav :: Rename IfaceFamTyConFlav
rnIfaceFamTyConFlav (IfaceClosedSynFamilyTyCon (Just (Name
n, [IfaceAxBranch]
axs)))
    = Maybe (Name, [IfaceAxBranch]) -> IfaceFamTyConFlav
IfaceClosedSynFamilyTyCon (Maybe (Name, [IfaceAxBranch]) -> IfaceFamTyConFlav)
-> ((Name, [IfaceAxBranch]) -> Maybe (Name, [IfaceAxBranch]))
-> (Name, [IfaceAxBranch])
-> IfaceFamTyConFlav
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Name, [IfaceAxBranch]) -> Maybe (Name, [IfaceAxBranch])
forall a. a -> Maybe a
Just ((Name, [IfaceAxBranch]) -> IfaceFamTyConFlav)
-> IOEnv (Env ShIfEnv ()) (Name, [IfaceAxBranch])
-> IOEnv (Env ShIfEnv ()) IfaceFamTyConFlav
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((,) (Name -> [IfaceAxBranch] -> (Name, [IfaceAxBranch]))
-> IOEnv (Env ShIfEnv ()) Name
-> IOEnv
     (Env ShIfEnv ()) ([IfaceAxBranch] -> (Name, [IfaceAxBranch]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceNeverExported Name
n
                                                IOEnv (Env ShIfEnv ()) ([IfaceAxBranch] -> (Name, [IfaceAxBranch]))
-> IOEnv (Env ShIfEnv ()) [IfaceAxBranch]
-> IOEnv (Env ShIfEnv ()) (Name, [IfaceAxBranch])
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)
mapM IfaceAxBranch -> IOEnv (Env ShIfEnv ()) IfaceAxBranch
rnIfaceAxBranch [IfaceAxBranch]
axs)
rnIfaceFamTyConFlav IfaceFamTyConFlav
flav = Rename IfaceFamTyConFlav
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 (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)
T.traverse Rename IfaceType
rnIfaceType Maybe IfaceType
mb_ty
rnIfaceTyConParent :: Rename IfaceTyConParent
rnIfaceTyConParent :: Rename IfaceTyConParent
rnIfaceTyConParent (IfDataInstance Name
n IfaceTyCon
tc IfaceAppArgs
args)
    = Name -> IfaceTyCon -> IfaceAppArgs -> IfaceTyConParent
IfDataInstance (Name -> IfaceTyCon -> IfaceAppArgs -> IfaceTyConParent)
-> IOEnv (Env ShIfEnv ()) Name
-> IOEnv
     (Env ShIfEnv ()) (IfaceTyCon -> IfaceAppArgs -> IfaceTyConParent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal Name
n
                     IOEnv
  (Env ShIfEnv ()) (IfaceTyCon -> IfaceAppArgs -> IfaceTyConParent)
-> IOEnv (Env ShIfEnv ()) IfaceTyCon
-> IOEnv (Env ShIfEnv ()) (IfaceAppArgs -> IfaceTyConParent)
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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceAppArgs
rnIfaceAppArgs IfaceAppArgs
args
rnIfaceTyConParent IfaceTyConParent
IfNoParent = Rename IfaceTyConParent
forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceTyConParent
IfNoParent
rnIfaceConDecls :: Rename IfaceConDecls
rnIfaceConDecls :: Rename IfaceConDecls
rnIfaceConDecls (IfDataTyCon [IfaceConDecl]
ds)
    = [IfaceConDecl] -> IfaceConDecls
IfDataTyCon ([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)
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 (f :: * -> *) a. Applicative f => a -> f a
pure IfaceConDecls
IfAbstractTyCon
rnIfaceConDecl :: Rename IfaceConDecl
rnIfaceConDecl :: IfaceConDecl -> IOEnv (Env ShIfEnv ()) IfaceConDecl
rnIfaceConDecl IfaceConDecl
d = do
    Name
con_name <- Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal (IfaceConDecl -> Name
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)
mapM IfaceBndr -> IOEnv (Env ShIfEnv ()) IfaceBndr
rnIfaceBndr (IfaceConDecl -> [IfaceBndr]
ifConExTCvs IfaceConDecl
d)
    [IfaceForAllBndr]
con_user_tvbs <- (IfaceForAllBndr -> IOEnv (Env ShIfEnv ()) IfaceForAllBndr)
-> [IfaceForAllBndr] -> IOEnv (Env ShIfEnv ()) [IfaceForAllBndr]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM IfaceForAllBndr -> IOEnv (Env ShIfEnv ()) IfaceForAllBndr
rnIfaceForAllBndr (IfaceConDecl -> [IfaceForAllBndr]
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
    [(FieldLabelString, IfaceType)]
con_eq_spec <- ((FieldLabelString, IfaceType)
 -> IOEnv (Env ShIfEnv ()) (FieldLabelString, IfaceType))
-> [(FieldLabelString, IfaceType)]
-> IOEnv (Env ShIfEnv ()) [(FieldLabelString, IfaceType)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (FieldLabelString, IfaceType)
-> IOEnv (Env ShIfEnv ()) (FieldLabelString, IfaceType)
forall a. (a, IfaceType) -> IOEnv (Env ShIfEnv ()) (a, IfaceType)
rnIfConEqSpec (IfaceConDecl -> [(FieldLabelString, 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)
mapM Rename IfaceType
rnIfaceType (IfaceConDecl -> [IfaceType]
ifConCtxt IfaceConDecl
d)
    [IfaceType]
con_arg_tys <- Rename IfaceType
-> [IfaceType] -> IOEnv (Env ShIfEnv ()) [IfaceType]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Rename IfaceType
rnIfaceType (IfaceConDecl -> [IfaceType]
ifConArgTys IfaceConDecl
d)
    [FieldLabel]
con_fields <- (FieldLabel -> IOEnv (Env ShIfEnv ()) FieldLabel)
-> [FieldLabel] -> IOEnv (Env ShIfEnv ()) [FieldLabel]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM FieldLabel -> IOEnv (Env ShIfEnv ()) 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 (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)
mapM IfaceBang -> IOEnv (Env ShIfEnv ()) IfaceBang
rnIfaceBang (IfaceConDecl -> [IfaceBang]
ifConStricts IfaceConDecl
d)
    IfaceConDecl -> IOEnv (Env ShIfEnv ()) IfaceConDecl
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceConDecl
d { ifConName :: Name
ifConName = Name
con_name
             , ifConExTCvs :: [IfaceBndr]
ifConExTCvs = [IfaceBndr]
con_ex_tvs
             , ifConUserTvBinders :: [IfaceForAllBndr]
ifConUserTvBinders = [IfaceForAllBndr]
con_user_tvbs
             , ifConEqSpec :: [(FieldLabelString, IfaceType)]
ifConEqSpec = [(FieldLabelString, IfaceType)]
con_eq_spec
             , ifConCtxt :: [IfaceType]
ifConCtxt = [IfaceType]
con_ctxt
             , ifConArgTys :: [IfaceType]
ifConArgTys = [IfaceType]
con_arg_tys
             , ifConFields :: [FieldLabel]
ifConFields = [FieldLabel]
con_fields
             , ifConStricts :: [IfaceBang]
ifConStricts = [IfaceBang]
con_stricts
             }
rnIfaceClassOp :: Rename IfaceClassOp
rnIfaceClassOp :: IfaceClassOp -> IOEnv (Env ShIfEnv ()) IfaceClassOp
rnIfaceClassOp (IfaceClassOp Name
n IfaceType
ty Maybe (DefMethSpec IfaceType)
dm) =
    Name -> IfaceType -> Maybe (DefMethSpec IfaceType) -> IfaceClassOp
IfaceClassOp (Name
 -> IfaceType -> Maybe (DefMethSpec IfaceType) -> IfaceClassOp)
-> IOEnv (Env ShIfEnv ()) Name
-> IOEnv
     (Env ShIfEnv ())
     (IfaceType -> Maybe (DefMethSpec IfaceType) -> IfaceClassOp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal Name
n
                 IOEnv
  (Env ShIfEnv ())
  (IfaceType -> Maybe (DefMethSpec IfaceType) -> IfaceClassOp)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv
     (Env ShIfEnv ()) (Maybe (DefMethSpec IfaceType) -> IfaceClassOp)
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 (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 (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
    [(FieldLabelString, IfaceType)]
ty_vars <- ((FieldLabelString, IfaceType)
 -> IOEnv (Env ShIfEnv ()) (FieldLabelString, IfaceType))
-> [(FieldLabelString, IfaceType)]
-> IOEnv (Env ShIfEnv ()) [(FieldLabelString, IfaceType)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (FieldLabelString, IfaceType)
-> IOEnv (Env ShIfEnv ()) (FieldLabelString, IfaceType)
rnIfaceTvBndr (IfaceAxBranch -> [(FieldLabelString, 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 (m :: * -> *) a. Monad m => a -> m a
return IfaceAxBranch
d { ifaxbTyVars :: [(FieldLabelString, IfaceType)]
ifaxbTyVars = [(FieldLabelString, IfaceType)]
ty_vars
             , ifaxbLHS :: IfaceAppArgs
ifaxbLHS = IfaceAppArgs
lhs
             , ifaxbRHS :: IfaceType
ifaxbRHS = IfaceType
rhs }
rnIfaceIdInfo :: Rename IfaceIdInfo
rnIfaceIdInfo :: Rename IfaceIdInfo
rnIfaceIdInfo IfaceIdInfo
NoInfo = Rename IfaceIdInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceIdInfo
NoInfo
rnIfaceIdInfo (HasInfo [IfaceInfoItem]
is) = [IfaceInfoItem] -> IfaceIdInfo
HasInfo ([IfaceInfoItem] -> IfaceIdInfo)
-> IOEnv (Env ShIfEnv ()) [IfaceInfoItem]
-> IOEnv (Env ShIfEnv ()) IfaceIdInfo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (IfaceInfoItem -> IOEnv (Env ShIfEnv ()) IfaceInfoItem)
-> [IfaceInfoItem] -> IOEnv (Env ShIfEnv ()) [IfaceInfoItem]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM IfaceInfoItem -> IOEnv (Env ShIfEnv ()) IfaceInfoItem
rnIfaceInfoItem [IfaceInfoItem]
is
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 (f :: * -> *) a. Applicative f => a -> f a
pure IfaceInfoItem
i
rnIfaceUnfolding :: Rename IfaceUnfolding
rnIfaceUnfolding :: Rename IfaceUnfolding
rnIfaceUnfolding (IfCoreUnfold Bool
stable IfaceExpr
if_expr)
    = Bool -> IfaceExpr -> IfaceUnfolding
IfCoreUnfold Bool
stable (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 (IfCompulsory IfaceExpr
if_expr)
    = IfaceExpr -> IfaceUnfolding
IfCompulsory (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 (IfInlineRule Int
arity Bool
unsat_ok Bool
boring_ok IfaceExpr
if_expr)
    = Int -> Bool -> Bool -> IfaceExpr -> IfaceUnfolding
IfInlineRule Int
arity Bool
unsat_ok Bool
boring_ok (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 (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)
mapM Rename IfaceExpr
rnIfaceExpr [IfaceExpr]
ops
rnIfaceExpr :: Rename IfaceExpr
rnIfaceExpr :: Rename IfaceExpr
rnIfaceExpr (IfaceLcl FieldLabelString
name) = Rename IfaceExpr
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FieldLabelString -> IfaceExpr
IfaceLcl FieldLabelString
name)
rnIfaceExpr (IfaceExt Name
gbl) = Name -> IfaceExpr
IfaceExt (Name -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) Name -> IOEnv (Env ShIfEnv ()) IfaceExpr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal Name
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 (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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceExpr
rnIfaceExpr IfaceExpr
arg
rnIfaceExpr (IfaceCase IfaceExpr
scrut FieldLabelString
case_bndr [IfaceAlt]
alts)
    = IfaceExpr -> FieldLabelString -> [IfaceAlt] -> IfaceExpr
IfaceCase (IfaceExpr -> FieldLabelString -> [IfaceAlt] -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) IfaceExpr
-> IOEnv
     (Env ShIfEnv ()) (FieldLabelString -> [IfaceAlt] -> IfaceExpr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceExpr
rnIfaceExpr IfaceExpr
scrut
                IOEnv
  (Env ShIfEnv ()) (FieldLabelString -> [IfaceAlt] -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) FieldLabelString
-> IOEnv (Env ShIfEnv ()) ([IfaceAlt] -> IfaceExpr)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldLabelString -> IOEnv (Env ShIfEnv ()) FieldLabelString
forall (f :: * -> *) a. Applicative f => a -> f a
pure FieldLabelString
case_bndr
                IOEnv (Env ShIfEnv ()) ([IfaceAlt] -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) [IfaceAlt]
-> IOEnv (Env ShIfEnv ()) IfaceExpr
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)
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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceType
rnIfaceType IfaceType
ty
rnIfaceExpr (IfaceLet (IfaceNonRec IfaceLetBndr
bndr IfaceExpr
rhs) IfaceExpr
body)
    = IfaceBinding -> IfaceExpr -> IfaceExpr
IfaceLet (IfaceBinding -> IfaceExpr -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) IfaceBinding
-> IOEnv (Env ShIfEnv ()) (IfaceExpr -> IfaceExpr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (IfaceLetBndr -> IfaceExpr -> IfaceBinding
IfaceNonRec (IfaceLetBndr -> IfaceExpr -> IfaceBinding)
-> IOEnv (Env ShIfEnv ()) IfaceLetBndr
-> IOEnv (Env ShIfEnv ()) (IfaceExpr -> IfaceBinding)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceLetBndr
rnIfaceLetBndr IfaceLetBndr
bndr IOEnv (Env ShIfEnv ()) (IfaceExpr -> IfaceBinding)
-> IOEnv (Env ShIfEnv ()) IfaceExpr
-> IOEnv (Env ShIfEnv ()) IfaceBinding
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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceExpr
rnIfaceExpr IfaceExpr
body
rnIfaceExpr (IfaceLet (IfaceRec [(IfaceLetBndr, IfaceExpr)]
pairs) IfaceExpr
body)
    = IfaceBinding -> IfaceExpr -> IfaceExpr
IfaceLet (IfaceBinding -> IfaceExpr -> IfaceExpr)
-> IOEnv (Env ShIfEnv ()) IfaceBinding
-> IOEnv (Env ShIfEnv ()) (IfaceExpr -> IfaceExpr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([(IfaceLetBndr, IfaceExpr)] -> IfaceBinding
IfaceRec ([(IfaceLetBndr, IfaceExpr)] -> IfaceBinding)
-> IOEnv (Env ShIfEnv ()) [(IfaceLetBndr, IfaceExpr)]
-> IOEnv (Env ShIfEnv ()) IfaceBinding
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)
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 (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 (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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co
rnIfaceExpr (IfaceLit Literal
lit) = Rename IfaceExpr
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Literal -> IfaceExpr
IfaceLit Literal
lit)
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)
mapM IfaceBndr -> IOEnv (Env ShIfEnv ()) IfaceBndr
rnIfaceBndr
rnIfaceBndr :: Rename IfaceBndr
rnIfaceBndr :: IfaceBndr -> IOEnv (Env ShIfEnv ()) IfaceBndr
rnIfaceBndr (IfaceIdBndr (FieldLabelString
fs, IfaceType
ty)) = (FieldLabelString, IfaceType) -> IfaceBndr
IfaceIdBndr ((FieldLabelString, IfaceType) -> IfaceBndr)
-> IOEnv (Env ShIfEnv ()) (FieldLabelString, IfaceType)
-> IOEnv (Env ShIfEnv ()) IfaceBndr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((,) FieldLabelString
fs (IfaceType -> (FieldLabelString, IfaceType))
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) (FieldLabelString, IfaceType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
ty)
rnIfaceBndr (IfaceTvBndr (FieldLabelString, IfaceType)
tv_bndr) = (FieldLabelString, IfaceType) -> IfaceBndr
IfaceTvBndr ((FieldLabelString, IfaceType) -> IfaceBndr)
-> IOEnv (Env ShIfEnv ()) (FieldLabelString, IfaceType)
-> IOEnv (Env ShIfEnv ()) IfaceBndr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (FieldLabelString, IfaceType)
-> IOEnv (Env ShIfEnv ()) (FieldLabelString, IfaceType)
rnIfaceTvBndr (FieldLabelString, IfaceType)
tv_bndr
rnIfaceTvBndr :: Rename IfaceTvBndr
rnIfaceTvBndr :: (FieldLabelString, IfaceType)
-> IOEnv (Env ShIfEnv ()) (FieldLabelString, IfaceType)
rnIfaceTvBndr (FieldLabelString
fs, IfaceType
kind) = (,) FieldLabelString
fs (IfaceType -> (FieldLabelString, IfaceType))
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) (FieldLabelString, 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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> TyConBndrVis -> IOEnv (Env ShIfEnv ()) TyConBndrVis
forall (f :: * -> *) a. Applicative f => a -> f a
pure TyConBndrVis
vis
rnIfaceAlt :: Rename IfaceAlt
rnIfaceAlt :: IfaceAlt -> IOEnv (Env ShIfEnv ()) IfaceAlt
rnIfaceAlt (IfaceConAlt
conalt, [FieldLabelString]
names, IfaceExpr
rhs)
     = (,,) (IfaceConAlt -> [FieldLabelString] -> IfaceExpr -> IfaceAlt)
-> IOEnv (Env ShIfEnv ()) IfaceConAlt
-> IOEnv
     (Env ShIfEnv ()) ([FieldLabelString] -> IfaceExpr -> IfaceAlt)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceConAlt
rnIfaceConAlt IfaceConAlt
conalt IOEnv
  (Env ShIfEnv ()) ([FieldLabelString] -> IfaceExpr -> IfaceAlt)
-> IOEnv (Env ShIfEnv ()) [FieldLabelString]
-> IOEnv (Env ShIfEnv ()) (IfaceExpr -> IfaceAlt)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [FieldLabelString] -> IOEnv (Env ShIfEnv ()) [FieldLabelString]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [FieldLabelString]
names IOEnv (Env ShIfEnv ()) (IfaceExpr -> IfaceAlt)
-> IOEnv (Env ShIfEnv ()) IfaceExpr
-> IOEnv (Env ShIfEnv ()) IfaceAlt
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 Name
data_occ) = Name -> IfaceConAlt
IfaceDataAlt (Name -> IfaceConAlt)
-> IOEnv (Env ShIfEnv ()) Name
-> IOEnv (Env ShIfEnv ()) IfaceConAlt
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal Name
data_occ
rnIfaceConAlt IfaceConAlt
alt = Rename IfaceConAlt
forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceConAlt
alt
rnIfaceLetBndr :: Rename IfaceLetBndr
rnIfaceLetBndr :: Rename IfaceLetBndr
rnIfaceLetBndr (IfLetBndr FieldLabelString
fs IfaceType
ty IfaceIdInfo
info IfaceJoinInfo
jpi)
    = FieldLabelString
-> IfaceType -> IfaceIdInfo -> IfaceJoinInfo -> IfaceLetBndr
IfLetBndr FieldLabelString
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 (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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IfaceJoinInfo -> IOEnv (Env ShIfEnv ()) IfaceJoinInfo
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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IfaceOneShot -> IOEnv (Env ShIfEnv ()) IfaceOneShot
forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceOneShot
oneshot
rnIfaceMCo :: Rename IfaceMCoercion
rnIfaceMCo :: Rename IfaceMCoercion
rnIfaceMCo IfaceMCoercion
IfaceMRefl    = Rename IfaceMCoercion
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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceMCoercion
rnIfaceMCo IfaceMCoercion
mco
rnIfaceCo (IfaceFunCo Role
role IfaceCoercion
co1 IfaceCoercion
co2)
    = Role -> IfaceCoercion -> IfaceCoercion -> IfaceCoercion
IfaceFunCo Role
role (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 (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 (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)
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 (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 (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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co2
rnIfaceCo (IfaceFreeCoVar CoVar
c) = Rename IfaceCoercion
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CoVar -> IfaceCoercion
IfaceFreeCoVar CoVar
c)
rnIfaceCo (IfaceCoVarCo FieldLabelString
lcl) = FieldLabelString -> IfaceCoercion
IfaceCoVarCo (FieldLabelString -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) FieldLabelString
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FieldLabelString -> IOEnv (Env ShIfEnv ()) FieldLabelString
forall (f :: * -> *) a. Applicative f => a -> f a
pure FieldLabelString
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 (f :: * -> *) a. Applicative f => a -> f a
pure CoVar
lcl
rnIfaceCo (IfaceAxiomInstCo Name
n Int
i [IfaceCoercion]
cs)
    = Name -> Int -> [IfaceCoercion] -> IfaceCoercion
IfaceAxiomInstCo (Name -> Int -> [IfaceCoercion] -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) Name
-> IOEnv (Env ShIfEnv ()) (Int -> [IfaceCoercion] -> IfaceCoercion)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal Name
n IOEnv (Env ShIfEnv ()) (Int -> [IfaceCoercion] -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) Int
-> IOEnv (Env ShIfEnv ()) ([IfaceCoercion] -> IfaceCoercion)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> IOEnv (Env ShIfEnv ()) Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
i IOEnv (Env ShIfEnv ()) ([IfaceCoercion] -> IfaceCoercion)
-> IOEnv (Env ShIfEnv ()) [IfaceCoercion]
-> IOEnv (Env ShIfEnv ()) IfaceCoercion
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)
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 (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 (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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
c2
rnIfaceCo (IfaceNthCo Int
d IfaceCoercion
c) = Int -> IfaceCoercion -> IfaceCoercion
IfaceNthCo Int
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 FieldLabelString
ax [IfaceCoercion]
cos)
    = FieldLabelString -> [IfaceCoercion] -> IfaceCoercion
IfaceAxiomRuleCo FieldLabelString
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)
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 Name
n IfaceTyConInfo
info)
    = Name -> IfaceTyConInfo -> IfaceTyCon
IfaceTyCon (Name -> IfaceTyConInfo -> IfaceTyCon)
-> IOEnv (Env ShIfEnv ()) Name
-> IOEnv (Env ShIfEnv ()) (IfaceTyConInfo -> IfaceTyCon)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name -> IOEnv (Env ShIfEnv ()) Name
rnIfaceGlobal Name
n IOEnv (Env ShIfEnv ()) (IfaceTyConInfo -> IfaceTyCon)
-> IOEnv (Env ShIfEnv ()) IfaceTyConInfo
-> IOEnv (Env ShIfEnv ()) IfaceTyCon
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IfaceTyConInfo -> IOEnv (Env ShIfEnv ()) IfaceTyConInfo
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)
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 (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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Bool -> IOEnv (Env ShIfEnv ()) Bool
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 (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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Bool -> IOEnv (Env ShIfEnv ()) Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
b
rnIfaceIdDetails IfaceIdDetails
details = Rename IfaceIdDetails
forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceIdDetails
details
rnIfaceType :: Rename IfaceType
rnIfaceType :: Rename IfaceType
rnIfaceType (IfaceFreeTyVar CoVar
n) = Rename IfaceType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CoVar -> IfaceType
IfaceFreeTyVar CoVar
n)
rnIfaceType (IfaceTyVar   FieldLabelString
n)   = Rename IfaceType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FieldLabelString -> IfaceType
IfaceTyVar FieldLabelString
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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceAppArgs
rnIfaceAppArgs IfaceAppArgs
t2
rnIfaceType (IfaceLitTy IfaceTyLit
l)         = Rename IfaceType
forall (m :: * -> *) a. Monad m => a -> m a
return (IfaceTyLit -> IfaceType
IfaceLitTy IfaceTyLit
l)
rnIfaceType (IfaceFunTy AnonArgFlag
af IfaceType
t1 IfaceType
t2)
    = AnonArgFlag -> IfaceType -> IfaceType -> IfaceType
IfaceFunTy AnonArgFlag
af (IfaceType -> IfaceType -> IfaceType)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) (IfaceType -> IfaceType)
forall (f :: * -> *) a b. Functor 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 (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 (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
<$> IfaceForAllBndr -> IOEnv (Env ShIfEnv ()) IfaceForAllBndr
rnIfaceForAllBndr IfaceForAllBndr
tv IOEnv (Env ShIfEnv ()) (IfaceType -> IfaceType)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) IfaceType
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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Rename IfaceCoercion
rnIfaceCo IfaceCoercion
co
rnIfaceForAllBndr :: Rename IfaceForAllBndr
rnIfaceForAllBndr :: IfaceForAllBndr -> IOEnv (Env ShIfEnv ()) IfaceForAllBndr
rnIfaceForAllBndr (Bndr IfaceBndr
tv ArgFlag
vis) = IfaceBndr -> ArgFlag -> IfaceForAllBndr
forall var argf. var -> argf -> VarBndr var argf
Bndr (IfaceBndr -> ArgFlag -> IfaceForAllBndr)
-> IOEnv (Env ShIfEnv ()) IfaceBndr
-> IOEnv (Env ShIfEnv ()) (ArgFlag -> IfaceForAllBndr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IfaceBndr -> IOEnv (Env ShIfEnv ()) IfaceBndr
rnIfaceBndr IfaceBndr
tv IOEnv (Env ShIfEnv ()) (ArgFlag -> IfaceForAllBndr)
-> IOEnv (Env ShIfEnv ()) ArgFlag
-> IOEnv (Env ShIfEnv ()) IfaceForAllBndr
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ArgFlag -> IOEnv (Env ShIfEnv ()) ArgFlag
forall (f :: * -> *) a. Applicative f => a -> f a
pure ArgFlag
vis
rnIfaceAppArgs :: Rename IfaceAppArgs
rnIfaceAppArgs :: Rename IfaceAppArgs
rnIfaceAppArgs (IA_Arg IfaceType
t ArgFlag
a IfaceAppArgs
ts) = IfaceType -> ArgFlag -> IfaceAppArgs -> IfaceAppArgs
IA_Arg (IfaceType -> ArgFlag -> IfaceAppArgs -> IfaceAppArgs)
-> IOEnv (Env ShIfEnv ()) IfaceType
-> IOEnv (Env ShIfEnv ()) (ArgFlag -> IfaceAppArgs -> IfaceAppArgs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Rename IfaceType
rnIfaceType IfaceType
t IOEnv (Env ShIfEnv ()) (ArgFlag -> IfaceAppArgs -> IfaceAppArgs)
-> IOEnv (Env ShIfEnv ()) ArgFlag
-> IOEnv (Env ShIfEnv ()) (IfaceAppArgs -> IfaceAppArgs)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ArgFlag -> IOEnv (Env ShIfEnv ()) ArgFlag
forall (f :: * -> *) a. Applicative f => a -> f a
pure ArgFlag
a
                                        IOEnv (Env ShIfEnv ()) (IfaceAppArgs -> IfaceAppArgs)
-> IOEnv (Env ShIfEnv ()) IfaceAppArgs
-> IOEnv (Env ShIfEnv ()) IfaceAppArgs
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 (f :: * -> *) a. Applicative f => a -> f a
pure IfaceAppArgs
IA_Nil