{-# LANGUAGE CPP, DeriveFunctor, ViewPatterns #-}
module TidyPgm (
mkBootModDetailsTc, tidyProgram
) where
#include "HsVersions.h"
import GhcPrelude
import TcRnTypes
import DynFlags
import CoreSyn
import CoreUnfold
import CoreFVs
import CoreTidy
import CoreMonad
import CorePrep
import CoreUtils (rhsIsStatic)
import CoreStats (coreBindsStats, CoreStats(..))
import CoreSeq (seqBinds)
import CoreLint
import Literal
import Rules
import PatSyn
import ConLike
import CoreArity ( exprArity, exprBotStrictness_maybe )
import StaticPtrTable
import VarEnv
import VarSet
import Var
import Id
import MkId ( mkDictSelRhs )
import IdInfo
import InstEnv
import Type ( tidyTopType )
import Demand ( appIsBottom, isTopSig, isBottomingSig )
import BasicTypes
import Name hiding (varName)
import NameSet
import NameCache
import Avail
import IfaceEnv
import TcEnv
import TcRnMonad
import DataCon
import TyCon
import Class
import Module
import Packages( isDllName )
import HscTypes
import Maybes
import UniqSupply
import Outputable
import Util( filterOut )
import qualified ErrUtils as Err
import Control.Monad
import Data.Function
import Data.List ( sortBy, mapAccumL )
import Data.IORef ( atomicModifyIORef' )
mkBootModDetailsTc :: HscEnv -> TcGblEnv -> IO ModDetails
mkBootModDetailsTc :: HscEnv -> TcGblEnv -> IO ModDetails
mkBootModDetailsTc HscEnv
hsc_env
TcGblEnv{ tcg_exports :: TcGblEnv -> [AvailInfo]
tcg_exports = [AvailInfo]
exports,
tcg_type_env :: TcGblEnv -> TypeEnv
tcg_type_env = TypeEnv
type_env,
tcg_tcs :: TcGblEnv -> [TyCon]
tcg_tcs = [TyCon]
tcs,
tcg_patsyns :: TcGblEnv -> [PatSyn]
tcg_patsyns = [PatSyn]
pat_syns,
tcg_insts :: TcGblEnv -> [ClsInst]
tcg_insts = [ClsInst]
insts,
tcg_fam_insts :: TcGblEnv -> [FamInst]
tcg_fam_insts = [FamInst]
fam_insts,
tcg_complete_matches :: TcGblEnv -> [CompleteMatch]
tcg_complete_matches = [CompleteMatch]
complete_sigs,
tcg_mod :: TcGblEnv -> Module
tcg_mod = Module
this_mod
}
=
DynFlags
-> SDoc -> (ModDetails -> ()) -> IO ModDetails -> IO ModDetails
forall (m :: * -> *) a.
MonadIO m =>
DynFlags -> SDoc -> (a -> ()) -> m a -> m a
Err.withTiming DynFlags
dflags
(String -> SDoc
text String
"CoreTidy"SDoc -> SDoc -> SDoc
<+>SDoc -> SDoc
brackets (Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
this_mod))
(() -> ModDetails -> ()
forall a b. a -> b -> a
const ()) (IO ModDetails -> IO ModDetails) -> IO ModDetails -> IO ModDetails
forall a b. (a -> b) -> a -> b
$
ModDetails -> IO ModDetails
forall (m :: * -> *) a. Monad m => a -> m a
return (ModDetails :: [AvailInfo]
-> TypeEnv
-> [ClsInst]
-> [FamInst]
-> [CoreRule]
-> [Annotation]
-> [CompleteMatch]
-> ModDetails
ModDetails { md_types :: TypeEnv
md_types = TypeEnv
type_env'
, md_insts :: [ClsInst]
md_insts = [ClsInst]
insts'
, md_fam_insts :: [FamInst]
md_fam_insts = [FamInst]
fam_insts
, md_rules :: [CoreRule]
md_rules = []
, md_anns :: [Annotation]
md_anns = []
, md_exports :: [AvailInfo]
md_exports = [AvailInfo]
exports
, md_complete_sigs :: [CompleteMatch]
md_complete_sigs = [CompleteMatch]
complete_sigs
})
where
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
final_ids :: [Id]
final_ids = [ Id -> Id
globaliseAndTidyBootId Id
id
| Id
id <- TypeEnv -> [Id]
typeEnvIds TypeEnv
type_env
, Id -> Bool
keep_it Id
id ]
final_tcs :: [TyCon]
final_tcs = (TyCon -> Bool) -> [TyCon] -> [TyCon]
forall a. (a -> Bool) -> [a] -> [a]
filterOut (Name -> Bool
isWiredInName (Name -> Bool) -> (TyCon -> Name) -> TyCon -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TyCon -> Name
forall a. NamedThing a => a -> Name
getName) [TyCon]
tcs
type_env1 :: TypeEnv
type_env1 = [Id] -> [TyCon] -> [FamInst] -> TypeEnv
typeEnvFromEntities [Id]
final_ids [TyCon]
final_tcs [FamInst]
fam_insts
insts' :: [ClsInst]
insts' = TypeEnv -> [ClsInst] -> [ClsInst]
mkFinalClsInsts TypeEnv
type_env1 [ClsInst]
insts
pat_syns' :: [PatSyn]
pat_syns' = TypeEnv -> [PatSyn] -> [PatSyn]
mkFinalPatSyns TypeEnv
type_env1 [PatSyn]
pat_syns
type_env' :: TypeEnv
type_env' = [PatSyn] -> TypeEnv -> TypeEnv
extendTypeEnvWithPatSyns [PatSyn]
pat_syns' TypeEnv
type_env1
keep_it :: Id -> Bool
keep_it Id
id | Name -> Bool
isWiredInName Name
id_name = Bool
False
| Id -> Bool
isExportedId Id
id = Bool
True
| Name
id_name Name -> NameSet -> Bool
`elemNameSet` NameSet
exp_names = Bool
True
| Bool
otherwise = Bool
False
where
id_name :: Name
id_name = Id -> Name
idName Id
id
exp_names :: NameSet
exp_names = [AvailInfo] -> NameSet
availsToNameSet [AvailInfo]
exports
lookupFinalId :: TypeEnv -> Id -> Id
lookupFinalId :: TypeEnv -> Id -> Id
lookupFinalId TypeEnv
type_env Id
id
= case TypeEnv -> Name -> Maybe TyThing
lookupTypeEnv TypeEnv
type_env (Id -> Name
idName Id
id) of
Just (AnId Id
id') -> Id
id'
Maybe TyThing
_ -> String -> SDoc -> Id
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"lookup_final_id" (Id -> SDoc
forall a. Outputable a => a -> SDoc
ppr Id
id)
mkFinalClsInsts :: TypeEnv -> [ClsInst] -> [ClsInst]
mkFinalClsInsts :: TypeEnv -> [ClsInst] -> [ClsInst]
mkFinalClsInsts TypeEnv
env = (ClsInst -> ClsInst) -> [ClsInst] -> [ClsInst]
forall a b. (a -> b) -> [a] -> [b]
map ((Id -> Id) -> ClsInst -> ClsInst
updateClsInstDFun (TypeEnv -> Id -> Id
lookupFinalId TypeEnv
env))
mkFinalPatSyns :: TypeEnv -> [PatSyn] -> [PatSyn]
mkFinalPatSyns :: TypeEnv -> [PatSyn] -> [PatSyn]
mkFinalPatSyns TypeEnv
env = (PatSyn -> PatSyn) -> [PatSyn] -> [PatSyn]
forall a b. (a -> b) -> [a] -> [b]
map ((Id -> Id) -> PatSyn -> PatSyn
updatePatSynIds (TypeEnv -> Id -> Id
lookupFinalId TypeEnv
env))
extendTypeEnvWithPatSyns :: [PatSyn] -> TypeEnv -> TypeEnv
extendTypeEnvWithPatSyns :: [PatSyn] -> TypeEnv -> TypeEnv
extendTypeEnvWithPatSyns [PatSyn]
tidy_patsyns TypeEnv
type_env
= TypeEnv -> [TyThing] -> TypeEnv
extendTypeEnvList TypeEnv
type_env [ConLike -> TyThing
AConLike (PatSyn -> ConLike
PatSynCon PatSyn
ps) | PatSyn
ps <- [PatSyn]
tidy_patsyns ]
globaliseAndTidyBootId :: Id -> Id
globaliseAndTidyBootId :: Id -> Id
globaliseAndTidyBootId Id
id
= Id -> Id
globaliseId Id
id Id -> Type -> Id
`setIdType` Type -> Type
tidyTopType (Id -> Type
idType Id
id)
Id -> Unfolding -> Id
`setIdUnfolding` Unfolding
BootUnfolding
tidyProgram :: HscEnv -> ModGuts -> IO (CgGuts, ModDetails)
tidyProgram :: HscEnv -> ModGuts -> IO (CgGuts, ModDetails)
tidyProgram HscEnv
hsc_env (ModGuts { mg_module :: ModGuts -> Module
mg_module = Module
mod
, mg_exports :: ModGuts -> [AvailInfo]
mg_exports = [AvailInfo]
exports
, mg_rdr_env :: ModGuts -> GlobalRdrEnv
mg_rdr_env = GlobalRdrEnv
rdr_env
, mg_tcs :: ModGuts -> [TyCon]
mg_tcs = [TyCon]
tcs
, mg_insts :: ModGuts -> [ClsInst]
mg_insts = [ClsInst]
cls_insts
, mg_fam_insts :: ModGuts -> [FamInst]
mg_fam_insts = [FamInst]
fam_insts
, mg_binds :: ModGuts -> CoreProgram
mg_binds = CoreProgram
binds
, mg_patsyns :: ModGuts -> [PatSyn]
mg_patsyns = [PatSyn]
patsyns
, mg_rules :: ModGuts -> [CoreRule]
mg_rules = [CoreRule]
imp_rules
, mg_anns :: ModGuts -> [Annotation]
mg_anns = [Annotation]
anns
, mg_complete_sigs :: ModGuts -> [CompleteMatch]
mg_complete_sigs = [CompleteMatch]
complete_sigs
, mg_deps :: ModGuts -> Dependencies
mg_deps = Dependencies
deps
, mg_foreign :: ModGuts -> ForeignStubs
mg_foreign = ForeignStubs
foreign_stubs
, mg_foreign_files :: ModGuts -> [(ForeignSrcLang, String)]
mg_foreign_files = [(ForeignSrcLang, String)]
foreign_files
, mg_hpc_info :: ModGuts -> HpcInfo
mg_hpc_info = HpcInfo
hpc_info
, mg_modBreaks :: ModGuts -> Maybe ModBreaks
mg_modBreaks = Maybe ModBreaks
modBreaks
})
= DynFlags
-> SDoc
-> ((CgGuts, ModDetails) -> ())
-> IO (CgGuts, ModDetails)
-> IO (CgGuts, ModDetails)
forall (m :: * -> *) a.
MonadIO m =>
DynFlags -> SDoc -> (a -> ()) -> m a -> m a
Err.withTiming DynFlags
dflags
(String -> SDoc
text String
"CoreTidy"SDoc -> SDoc -> SDoc
<+>SDoc -> SDoc
brackets (Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
mod))
(() -> (CgGuts, ModDetails) -> ()
forall a b. a -> b -> a
const ()) (IO (CgGuts, ModDetails) -> IO (CgGuts, ModDetails))
-> IO (CgGuts, ModDetails) -> IO (CgGuts, ModDetails)
forall a b. (a -> b) -> a -> b
$
do { let { omit_prags :: Bool
omit_prags = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_OmitInterfacePragmas DynFlags
dflags
; expose_all :: Bool
expose_all = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_ExposeAllUnfoldings DynFlags
dflags
; print_unqual :: PrintUnqualified
print_unqual = DynFlags -> GlobalRdrEnv -> PrintUnqualified
mkPrintUnqualified DynFlags
dflags GlobalRdrEnv
rdr_env
; implicit_binds :: CoreProgram
implicit_binds = (TyCon -> CoreProgram) -> [TyCon] -> CoreProgram
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TyCon -> CoreProgram
getImplicitBinds [TyCon]
tcs
}
; (UnfoldEnv
unfold_env, TidyOccEnv
tidy_occ_env)
<- HscEnv
-> Module
-> Bool
-> Bool
-> CoreProgram
-> CoreProgram
-> [CoreRule]
-> IO (UnfoldEnv, TidyOccEnv)
chooseExternalIds HscEnv
hsc_env Module
mod Bool
omit_prags Bool
expose_all
CoreProgram
binds CoreProgram
implicit_binds [CoreRule]
imp_rules
; let { (CoreProgram
trimmed_binds, [CoreRule]
trimmed_rules)
= Bool
-> CoreProgram
-> [CoreRule]
-> UnfoldEnv
-> (CoreProgram, [CoreRule])
findExternalRules Bool
omit_prags CoreProgram
binds [CoreRule]
imp_rules UnfoldEnv
unfold_env }
; (TidyEnv
tidy_env, CoreProgram
tidy_binds)
<- HscEnv
-> Module
-> UnfoldEnv
-> TidyOccEnv
-> CoreProgram
-> IO (TidyEnv, CoreProgram)
tidyTopBinds HscEnv
hsc_env Module
mod UnfoldEnv
unfold_env TidyOccEnv
tidy_occ_env CoreProgram
trimmed_binds
; ([SptEntry]
spt_entries, CoreProgram
tidy_binds') <-
HscEnv -> Module -> CoreProgram -> IO ([SptEntry], CoreProgram)
sptCreateStaticBinds HscEnv
hsc_env Module
mod CoreProgram
tidy_binds
; let { spt_init_code :: SDoc
spt_init_code = Module -> [SptEntry] -> SDoc
sptModuleInitCode Module
mod [SptEntry]
spt_entries
; add_spt_init_code :: ForeignStubs -> ForeignStubs
add_spt_init_code =
case DynFlags -> HscTarget
hscTarget DynFlags
dflags of
HscTarget
HscInterpreted -> ForeignStubs -> ForeignStubs
forall a. a -> a
id
HscTarget
_ -> (ForeignStubs -> SDoc -> ForeignStubs
`appendStubC` SDoc
spt_init_code)
; final_ids :: [Id]
final_ids = [ if Bool
omit_prags then Id -> Id
trimId Id
id else Id
id
| Id
id <- CoreProgram -> [Id]
forall b. [Bind b] -> [b]
bindersOfBinds CoreProgram
tidy_binds
, Name -> Bool
isExternalName (Id -> Name
idName Id
id)
, Bool -> Bool
not (Name -> Bool
isWiredInName (Id -> Name
forall a. NamedThing a => a -> Name
getName Id
id))
]
; final_tcs :: [TyCon]
final_tcs = (TyCon -> Bool) -> [TyCon] -> [TyCon]
forall a. (a -> Bool) -> [a] -> [a]
filterOut (Name -> Bool
isWiredInName (Name -> Bool) -> (TyCon -> Name) -> TyCon -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TyCon -> Name
forall a. NamedThing a => a -> Name
getName) [TyCon]
tcs
; type_env :: TypeEnv
type_env = [Id] -> [TyCon] -> [FamInst] -> TypeEnv
typeEnvFromEntities [Id]
final_ids [TyCon]
final_tcs [FamInst]
fam_insts
; tidy_cls_insts :: [ClsInst]
tidy_cls_insts = TypeEnv -> [ClsInst] -> [ClsInst]
mkFinalClsInsts TypeEnv
type_env [ClsInst]
cls_insts
; tidy_patsyns :: [PatSyn]
tidy_patsyns = TypeEnv -> [PatSyn] -> [PatSyn]
mkFinalPatSyns TypeEnv
type_env [PatSyn]
patsyns
; tidy_type_env :: TypeEnv
tidy_type_env = [PatSyn] -> TypeEnv -> TypeEnv
extendTypeEnvWithPatSyns [PatSyn]
tidy_patsyns TypeEnv
type_env
; tidy_rules :: [CoreRule]
tidy_rules = TidyEnv -> [CoreRule] -> [CoreRule]
tidyRules TidyEnv
tidy_env [CoreRule]
trimmed_rules
;
all_tidy_binds :: CoreProgram
all_tidy_binds = CoreProgram
implicit_binds CoreProgram -> CoreProgram -> CoreProgram
forall a. [a] -> [a] -> [a]
++ CoreProgram
tidy_binds'
; alg_tycons :: [TyCon]
alg_tycons = (TyCon -> Bool) -> [TyCon] -> [TyCon]
forall a. (a -> Bool) -> [a] -> [a]
filter TyCon -> Bool
isAlgTyCon [TyCon]
tcs
}
; HscEnv
-> PrintUnqualified
-> CoreToDo
-> CoreProgram
-> [CoreRule]
-> IO ()
endPassIO HscEnv
hsc_env PrintUnqualified
print_unqual CoreToDo
CoreTidy CoreProgram
all_tidy_binds [CoreRule]
tidy_rules
; Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (DumpFlag -> DynFlags -> Bool
dopt DumpFlag
Opt_D_dump_simpl DynFlags
dflags) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
DynFlags -> DumpFlag -> String -> SDoc -> IO ()
Err.dumpIfSet_dyn DynFlags
dflags DumpFlag
Opt_D_dump_rules
(DynFlags -> SDoc -> String
showSDoc DynFlags
dflags (CoreToDo -> SDoc
forall a. Outputable a => a -> SDoc
ppr CoreToDo
CoreTidy SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"rules"))
(DynFlags -> [CoreRule] -> SDoc
pprRulesForUser DynFlags
dflags [CoreRule]
tidy_rules)
; let cs :: CoreStats
cs = CoreProgram -> CoreStats
coreBindsStats CoreProgram
tidy_binds
; DynFlags -> DumpFlag -> String -> SDoc -> IO ()
Err.dumpIfSet_dyn DynFlags
dflags DumpFlag
Opt_D_dump_core_stats String
"Core Stats"
(String -> SDoc
text String
"Tidy size (terms,types,coercions)"
SDoc -> SDoc -> SDoc
<+> ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Module -> ModuleName
moduleName Module
mod) SDoc -> SDoc -> SDoc
<> SDoc
colon
SDoc -> SDoc -> SDoc
<+> Int -> SDoc
int (CoreStats -> Int
cs_tm CoreStats
cs)
SDoc -> SDoc -> SDoc
<+> Int -> SDoc
int (CoreStats -> Int
cs_ty CoreStats
cs)
SDoc -> SDoc -> SDoc
<+> Int -> SDoc
int (CoreStats -> Int
cs_co CoreStats
cs) )
; (CgGuts, ModDetails) -> IO (CgGuts, ModDetails)
forall (m :: * -> *) a. Monad m => a -> m a
return (CgGuts :: Module
-> [TyCon]
-> CoreProgram
-> ForeignStubs
-> [(ForeignSrcLang, String)]
-> [InstalledUnitId]
-> HpcInfo
-> Maybe ModBreaks
-> [SptEntry]
-> CgGuts
CgGuts { cg_module :: Module
cg_module = Module
mod,
cg_tycons :: [TyCon]
cg_tycons = [TyCon]
alg_tycons,
cg_binds :: CoreProgram
cg_binds = CoreProgram
all_tidy_binds,
cg_foreign :: ForeignStubs
cg_foreign = ForeignStubs -> ForeignStubs
add_spt_init_code ForeignStubs
foreign_stubs,
cg_foreign_files :: [(ForeignSrcLang, String)]
cg_foreign_files = [(ForeignSrcLang, String)]
foreign_files,
cg_dep_pkgs :: [InstalledUnitId]
cg_dep_pkgs = ((InstalledUnitId, Bool) -> InstalledUnitId)
-> [(InstalledUnitId, Bool)] -> [InstalledUnitId]
forall a b. (a -> b) -> [a] -> [b]
map (InstalledUnitId, Bool) -> InstalledUnitId
forall a b. (a, b) -> a
fst ([(InstalledUnitId, Bool)] -> [InstalledUnitId])
-> [(InstalledUnitId, Bool)] -> [InstalledUnitId]
forall a b. (a -> b) -> a -> b
$ Dependencies -> [(InstalledUnitId, Bool)]
dep_pkgs Dependencies
deps,
cg_hpc_info :: HpcInfo
cg_hpc_info = HpcInfo
hpc_info,
cg_modBreaks :: Maybe ModBreaks
cg_modBreaks = Maybe ModBreaks
modBreaks,
cg_spt_entries :: [SptEntry]
cg_spt_entries = [SptEntry]
spt_entries },
ModDetails :: [AvailInfo]
-> TypeEnv
-> [ClsInst]
-> [FamInst]
-> [CoreRule]
-> [Annotation]
-> [CompleteMatch]
-> ModDetails
ModDetails { md_types :: TypeEnv
md_types = TypeEnv
tidy_type_env,
md_rules :: [CoreRule]
md_rules = [CoreRule]
tidy_rules,
md_insts :: [ClsInst]
md_insts = [ClsInst]
tidy_cls_insts,
md_fam_insts :: [FamInst]
md_fam_insts = [FamInst]
fam_insts,
md_exports :: [AvailInfo]
md_exports = [AvailInfo]
exports,
md_anns :: [Annotation]
md_anns = [Annotation]
anns,
md_complete_sigs :: [CompleteMatch]
md_complete_sigs = [CompleteMatch]
complete_sigs
})
}
where
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
trimId :: Id -> Id
trimId :: Id -> Id
trimId Id
id
| Bool -> Bool
not (Id -> Bool
isImplicitId Id
id)
= Id
id Id -> IdInfo -> Id
`setIdInfo` IdInfo
vanillaIdInfo
| Bool
otherwise
= Id
id
getImplicitBinds :: TyCon -> [CoreBind]
getImplicitBinds :: TyCon -> CoreProgram
getImplicitBinds TyCon
tc = CoreProgram
cls_binds CoreProgram -> CoreProgram -> CoreProgram
forall a. [a] -> [a] -> [a]
++ TyCon -> CoreProgram
getTyConImplicitBinds TyCon
tc
where
cls_binds :: CoreProgram
cls_binds = CoreProgram -> (Class -> CoreProgram) -> Maybe Class -> CoreProgram
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] Class -> CoreProgram
getClassImplicitBinds (TyCon -> Maybe Class
tyConClass_maybe TyCon
tc)
getTyConImplicitBinds :: TyCon -> [CoreBind]
getTyConImplicitBinds :: TyCon -> CoreProgram
getTyConImplicitBinds TyCon
tc
| TyCon -> Bool
isNewTyCon TyCon
tc = []
| Bool
otherwise = (Id -> CoreBind) -> [Id] -> CoreProgram
forall a b. (a -> b) -> [a] -> [b]
map Id -> CoreBind
get_defn ((DataCon -> Maybe Id) -> [DataCon] -> [Id]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DataCon -> Maybe Id
dataConWrapId_maybe (TyCon -> [DataCon]
tyConDataCons TyCon
tc))
getClassImplicitBinds :: Class -> [CoreBind]
getClassImplicitBinds :: Class -> CoreProgram
getClassImplicitBinds Class
cls
= [ Id -> Expr Id -> CoreBind
forall b. b -> Expr b -> Bind b
NonRec Id
op (Class -> Int -> Expr Id
mkDictSelRhs Class
cls Int
val_index)
| (Id
op, Int
val_index) <- Class -> [Id]
classAllSelIds Class
cls [Id] -> [Int] -> [(Id, Int)]
forall a b. [a] -> [b] -> [(a, b)]
`zip` [Int
0..] ]
get_defn :: Id -> CoreBind
get_defn :: Id -> CoreBind
get_defn Id
id = Id -> Expr Id -> CoreBind
forall b. b -> Expr b -> Bind b
NonRec Id
id (Unfolding -> Expr Id
unfoldingTemplate (Id -> Unfolding
realIdUnfolding Id
id))
type UnfoldEnv = IdEnv (Name, Bool )
chooseExternalIds :: HscEnv
-> Module
-> Bool -> Bool
-> [CoreBind]
-> [CoreBind]
-> [CoreRule]
-> IO (UnfoldEnv, TidyOccEnv)
chooseExternalIds :: HscEnv
-> Module
-> Bool
-> Bool
-> CoreProgram
-> CoreProgram
-> [CoreRule]
-> IO (UnfoldEnv, TidyOccEnv)
chooseExternalIds HscEnv
hsc_env Module
mod Bool
omit_prags Bool
expose_all CoreProgram
binds CoreProgram
implicit_binds [CoreRule]
imp_id_rules
= do { (UnfoldEnv
unfold_env1,TidyOccEnv
occ_env1) <- [(Id, Id)] -> UnfoldEnv -> TidyOccEnv -> IO (UnfoldEnv, TidyOccEnv)
search [(Id, Id)]
init_work_list UnfoldEnv
forall a. VarEnv a
emptyVarEnv TidyOccEnv
init_occ_env
; let internal_ids :: [Id]
internal_ids = (Id -> Bool) -> [Id] -> [Id]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Id -> Bool) -> Id -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Id -> UnfoldEnv -> Bool
forall a. Id -> VarEnv a -> Bool
`elemVarEnv` UnfoldEnv
unfold_env1)) [Id]
binders
; [Id] -> UnfoldEnv -> TidyOccEnv -> IO (UnfoldEnv, TidyOccEnv)
tidy_internal [Id]
internal_ids UnfoldEnv
unfold_env1 TidyOccEnv
occ_env1 }
where
nc_var :: IORef NameCache
nc_var = HscEnv -> IORef NameCache
hsc_NC HscEnv
hsc_env
init_work_list :: [(Id, Id)]
init_work_list = [Id] -> [Id] -> [(Id, Id)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Id]
init_ext_ids [Id]
init_ext_ids
init_ext_ids :: [Id]
init_ext_ids = (Id -> Id -> Ordering) -> [Id] -> [Id]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (OccName -> OccName -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (OccName -> OccName -> Ordering)
-> (Id -> OccName) -> Id -> Id -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Id -> OccName
forall a. NamedThing a => a -> OccName
getOccName) ([Id] -> [Id]) -> [Id] -> [Id]
forall a b. (a -> b) -> a -> b
$ (Id -> Bool) -> [Id] -> [Id]
forall a. (a -> Bool) -> [a] -> [a]
filter Id -> Bool
is_external [Id]
binders
is_external :: Id -> Bool
is_external Id
id = Id -> Bool
isExportedId Id
id Bool -> Bool -> Bool
|| Id
id Id -> VarSet -> Bool
`elemVarSet` VarSet
rule_rhs_vars
rule_rhs_vars :: VarSet
rule_rhs_vars = (CoreRule -> VarSet) -> [CoreRule] -> VarSet
forall a. (a -> VarSet) -> [a] -> VarSet
mapUnionVarSet CoreRule -> VarSet
ruleRhsFreeVars [CoreRule]
imp_id_rules
binders :: [Id]
binders = ((Id, Expr Id) -> Id) -> [(Id, Expr Id)] -> [Id]
forall a b. (a -> b) -> [a] -> [b]
map (Id, Expr Id) -> Id
forall a b. (a, b) -> a
fst ([(Id, Expr Id)] -> [Id]) -> [(Id, Expr Id)] -> [Id]
forall a b. (a -> b) -> a -> b
$ CoreProgram -> [(Id, Expr Id)]
forall b. [Bind b] -> [(b, Expr b)]
flattenBinds CoreProgram
binds
implicit_binders :: [Id]
implicit_binders = CoreProgram -> [Id]
forall b. [Bind b] -> [b]
bindersOfBinds CoreProgram
implicit_binds
binder_set :: VarSet
binder_set = [Id] -> VarSet
mkVarSet [Id]
binders
avoids :: [OccName]
avoids = [Name -> OccName
forall a. NamedThing a => a -> OccName
getOccName Name
name | Id
bndr <- [Id]
binders [Id] -> [Id] -> [Id]
forall a. [a] -> [a] -> [a]
++ [Id]
implicit_binders,
let name :: Name
name = Id -> Name
idName Id
bndr,
Name -> Bool
isExternalName Name
name ]
init_occ_env :: TidyOccEnv
init_occ_env = [OccName] -> TidyOccEnv
initTidyOccEnv [OccName]
avoids
search :: [(Id,Id)]
-> UnfoldEnv
-> TidyOccEnv
-> IO (UnfoldEnv, TidyOccEnv)
search :: [(Id, Id)] -> UnfoldEnv -> TidyOccEnv -> IO (UnfoldEnv, TidyOccEnv)
search [] UnfoldEnv
unfold_env TidyOccEnv
occ_env = (UnfoldEnv, TidyOccEnv) -> IO (UnfoldEnv, TidyOccEnv)
forall (m :: * -> *) a. Monad m => a -> m a
return (UnfoldEnv
unfold_env, TidyOccEnv
occ_env)
search ((Id
idocc,Id
referrer) : [(Id, Id)]
rest) UnfoldEnv
unfold_env TidyOccEnv
occ_env
| Id
idocc Id -> UnfoldEnv -> Bool
forall a. Id -> VarEnv a -> Bool
`elemVarEnv` UnfoldEnv
unfold_env = [(Id, Id)] -> UnfoldEnv -> TidyOccEnv -> IO (UnfoldEnv, TidyOccEnv)
search [(Id, Id)]
rest UnfoldEnv
unfold_env TidyOccEnv
occ_env
| Bool
otherwise = do
(TidyOccEnv
occ_env', Name
name') <- Module
-> IORef NameCache
-> Maybe Id
-> TidyOccEnv
-> Id
-> IO (TidyOccEnv, Name)
tidyTopName Module
mod IORef NameCache
nc_var (Id -> Maybe Id
forall a. a -> Maybe a
Just Id
referrer) TidyOccEnv
occ_env Id
idocc
let
([Id]
new_ids, Bool
show_unfold)
| Bool
omit_prags = ([], Bool
False)
| Bool
otherwise = Bool -> Id -> ([Id], Bool)
addExternal Bool
expose_all Id
refined_id
refined_id :: Id
refined_id = case VarSet -> Id -> Maybe Id
lookupVarSet VarSet
binder_set Id
idocc of
Just Id
id -> Id
id
Maybe Id
Nothing -> WARN( True, ppr idocc ) idocc
unfold_env' :: UnfoldEnv
unfold_env' = UnfoldEnv -> Id -> (Name, Bool) -> UnfoldEnv
forall a. VarEnv a -> Id -> a -> VarEnv a
extendVarEnv UnfoldEnv
unfold_env Id
idocc (Name
name',Bool
show_unfold)
referrer' :: Id
referrer' | Id -> Bool
isExportedId Id
refined_id = Id
refined_id
| Bool
otherwise = Id
referrer
[(Id, Id)] -> UnfoldEnv -> TidyOccEnv -> IO (UnfoldEnv, TidyOccEnv)
search ([Id] -> [Id] -> [(Id, Id)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Id]
new_ids (Id -> [Id]
forall a. a -> [a]
repeat Id
referrer') [(Id, Id)] -> [(Id, Id)] -> [(Id, Id)]
forall a. [a] -> [a] -> [a]
++ [(Id, Id)]
rest) UnfoldEnv
unfold_env' TidyOccEnv
occ_env'
tidy_internal :: [Id] -> UnfoldEnv -> TidyOccEnv
-> IO (UnfoldEnv, TidyOccEnv)
tidy_internal :: [Id] -> UnfoldEnv -> TidyOccEnv -> IO (UnfoldEnv, TidyOccEnv)
tidy_internal [] UnfoldEnv
unfold_env TidyOccEnv
occ_env = (UnfoldEnv, TidyOccEnv) -> IO (UnfoldEnv, TidyOccEnv)
forall (m :: * -> *) a. Monad m => a -> m a
return (UnfoldEnv
unfold_env,TidyOccEnv
occ_env)
tidy_internal (Id
id:[Id]
ids) UnfoldEnv
unfold_env TidyOccEnv
occ_env = do
(TidyOccEnv
occ_env', Name
name') <- Module
-> IORef NameCache
-> Maybe Id
-> TidyOccEnv
-> Id
-> IO (TidyOccEnv, Name)
tidyTopName Module
mod IORef NameCache
nc_var Maybe Id
forall a. Maybe a
Nothing TidyOccEnv
occ_env Id
id
let unfold_env' :: UnfoldEnv
unfold_env' = UnfoldEnv -> Id -> (Name, Bool) -> UnfoldEnv
forall a. VarEnv a -> Id -> a -> VarEnv a
extendVarEnv UnfoldEnv
unfold_env Id
id (Name
name',Bool
False)
[Id] -> UnfoldEnv -> TidyOccEnv -> IO (UnfoldEnv, TidyOccEnv)
tidy_internal [Id]
ids UnfoldEnv
unfold_env' TidyOccEnv
occ_env'
addExternal :: Bool -> Id -> ([Id], Bool)
addExternal :: Bool -> Id -> ([Id], Bool)
addExternal Bool
expose_all Id
id = ([Id]
new_needed_ids, Bool
show_unfold)
where
new_needed_ids :: [Id]
new_needed_ids = Bool -> Id -> [Id]
bndrFvsInOrder Bool
show_unfold Id
id
idinfo :: IdInfo
idinfo = HasDebugCallStack => Id -> IdInfo
Id -> IdInfo
idInfo Id
id
show_unfold :: Bool
show_unfold = Unfolding -> Bool
show_unfolding (IdInfo -> Unfolding
unfoldingInfo IdInfo
idinfo)
never_active :: Bool
never_active = Activation -> Bool
isNeverActive (InlinePragma -> Activation
inlinePragmaActivation (IdInfo -> InlinePragma
inlinePragInfo IdInfo
idinfo))
loop_breaker :: Bool
loop_breaker = OccInfo -> Bool
isStrongLoopBreaker (IdInfo -> OccInfo
occInfo IdInfo
idinfo)
bottoming_fn :: Bool
bottoming_fn = StrictSig -> Bool
isBottomingSig (IdInfo -> StrictSig
strictnessInfo IdInfo
idinfo)
show_unfolding :: Unfolding -> Bool
show_unfolding (CoreUnfolding { uf_src :: Unfolding -> UnfoldingSource
uf_src = UnfoldingSource
src, uf_guidance :: Unfolding -> UnfoldingGuidance
uf_guidance = UnfoldingGuidance
guidance })
= Bool
expose_all
Bool -> Bool -> Bool
|| UnfoldingSource -> Bool
isStableSource UnfoldingSource
src
Bool -> Bool -> Bool
|| Bool -> Bool
not (Bool
bottoming_fn
Bool -> Bool -> Bool
|| Bool
never_active
Bool -> Bool -> Bool
|| Bool
loop_breaker
Bool -> Bool -> Bool
|| UnfoldingGuidance -> Bool
neverUnfoldGuidance UnfoldingGuidance
guidance)
show_unfolding (DFunUnfolding {}) = Bool
True
show_unfolding Unfolding
_ = Bool
False
bndrFvsInOrder :: Bool -> Id -> [Id]
bndrFvsInOrder :: Bool -> Id -> [Id]
bndrFvsInOrder Bool
show_unfold Id
id
= DFFV () -> [Id]
run (Bool -> Id -> DFFV ()
dffvLetBndr Bool
show_unfold Id
id)
run :: DFFV () -> [Id]
run :: DFFV () -> [Id]
run (DFFV VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), ())
m) = case VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), ())
m VarSet
emptyVarSet (VarSet
emptyVarSet, []) of
((VarSet
_,[Id]
ids),()
_) -> [Id]
ids
newtype DFFV a
= DFFV (VarSet
-> (VarSet, [Var])
-> ((VarSet,[Var]),a))
deriving (a -> DFFV b -> DFFV a
(a -> b) -> DFFV a -> DFFV b
(forall a b. (a -> b) -> DFFV a -> DFFV b)
-> (forall a b. a -> DFFV b -> DFFV a) -> Functor DFFV
forall a b. a -> DFFV b -> DFFV a
forall a b. (a -> b) -> DFFV a -> DFFV b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> DFFV b -> DFFV a
$c<$ :: forall a b. a -> DFFV b -> DFFV a
fmap :: (a -> b) -> DFFV a -> DFFV b
$cfmap :: forall a b. (a -> b) -> DFFV a -> DFFV b
Functor)
instance Applicative DFFV where
pure :: a -> DFFV a
pure a
a = (VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), a)) -> DFFV a
forall a.
(VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), a)) -> DFFV a
DFFV ((VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), a)) -> DFFV a)
-> (VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), a)) -> DFFV a
forall a b. (a -> b) -> a -> b
$ \VarSet
_ (VarSet, [Id])
st -> ((VarSet, [Id])
st, a
a)
<*> :: DFFV (a -> b) -> DFFV a -> DFFV b
(<*>) = DFFV (a -> b) -> DFFV a -> DFFV b
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
ap
instance Monad DFFV where
(DFFV VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), a)
m) >>= :: DFFV a -> (a -> DFFV b) -> DFFV b
>>= a -> DFFV b
k = (VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), b)) -> DFFV b
forall a.
(VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), a)) -> DFFV a
DFFV ((VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), b)) -> DFFV b)
-> (VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), b)) -> DFFV b
forall a b. (a -> b) -> a -> b
$ \VarSet
env (VarSet, [Id])
st ->
case VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), a)
m VarSet
env (VarSet, [Id])
st of
((VarSet, [Id])
st',a
a) -> case a -> DFFV b
k a
a of
DFFV VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), b)
f -> VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), b)
f VarSet
env (VarSet, [Id])
st'
extendScope :: Var -> DFFV a -> DFFV a
extendScope :: Id -> DFFV a -> DFFV a
extendScope Id
v (DFFV VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), a)
f) = (VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), a)) -> DFFV a
forall a.
(VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), a)) -> DFFV a
DFFV (\VarSet
env (VarSet, [Id])
st -> VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), a)
f (VarSet -> Id -> VarSet
extendVarSet VarSet
env Id
v) (VarSet, [Id])
st)
extendScopeList :: [Var] -> DFFV a -> DFFV a
extendScopeList :: [Id] -> DFFV a -> DFFV a
extendScopeList [Id]
vs (DFFV VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), a)
f) = (VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), a)) -> DFFV a
forall a.
(VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), a)) -> DFFV a
DFFV (\VarSet
env (VarSet, [Id])
st -> VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), a)
f (VarSet -> [Id] -> VarSet
extendVarSetList VarSet
env [Id]
vs) (VarSet, [Id])
st)
insert :: Var -> DFFV ()
insert :: Id -> DFFV ()
insert Id
v = (VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), ())) -> DFFV ()
forall a.
(VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), a)) -> DFFV a
DFFV ((VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), ())) -> DFFV ())
-> (VarSet -> (VarSet, [Id]) -> ((VarSet, [Id]), ())) -> DFFV ()
forall a b. (a -> b) -> a -> b
$ \ VarSet
env (VarSet
set, [Id]
ids) ->
let keep_me :: Bool
keep_me = Id -> Bool
isLocalId Id
v Bool -> Bool -> Bool
&&
Bool -> Bool
not (Id
v Id -> VarSet -> Bool
`elemVarSet` VarSet
env) Bool -> Bool -> Bool
&&
Bool -> Bool
not (Id
v Id -> VarSet -> Bool
`elemVarSet` VarSet
set)
in if Bool
keep_me
then ((VarSet -> Id -> VarSet
extendVarSet VarSet
set Id
v, Id
vId -> [Id] -> [Id]
forall a. a -> [a] -> [a]
:[Id]
ids), ())
else ((VarSet
set, [Id]
ids), ())
dffvExpr :: CoreExpr -> DFFV ()
dffvExpr :: Expr Id -> DFFV ()
dffvExpr (Var Id
v) = Id -> DFFV ()
insert Id
v
dffvExpr (App Expr Id
e1 Expr Id
e2) = Expr Id -> DFFV ()
dffvExpr Expr Id
e1 DFFV () -> DFFV () -> DFFV ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Expr Id -> DFFV ()
dffvExpr Expr Id
e2
dffvExpr (Lam Id
v Expr Id
e) = Id -> DFFV () -> DFFV ()
forall a. Id -> DFFV a -> DFFV a
extendScope Id
v (Expr Id -> DFFV ()
dffvExpr Expr Id
e)
dffvExpr (Tick (Breakpoint Int
_ [Id]
ids) Expr Id
e) = (Id -> DFFV ()) -> [Id] -> DFFV ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Id -> DFFV ()
insert [Id]
ids DFFV () -> DFFV () -> DFFV ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Expr Id -> DFFV ()
dffvExpr Expr Id
e
dffvExpr (Tick Tickish Id
_other Expr Id
e) = Expr Id -> DFFV ()
dffvExpr Expr Id
e
dffvExpr (Cast Expr Id
e Coercion
_) = Expr Id -> DFFV ()
dffvExpr Expr Id
e
dffvExpr (Let (NonRec Id
x Expr Id
r) Expr Id
e) = (Id, Expr Id) -> DFFV ()
dffvBind (Id
x,Expr Id
r) DFFV () -> DFFV () -> DFFV ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Id -> DFFV () -> DFFV ()
forall a. Id -> DFFV a -> DFFV a
extendScope Id
x (Expr Id -> DFFV ()
dffvExpr Expr Id
e)
dffvExpr (Let (Rec [(Id, Expr Id)]
prs) Expr Id
e) = [Id] -> DFFV () -> DFFV ()
forall a. [Id] -> DFFV a -> DFFV a
extendScopeList (((Id, Expr Id) -> Id) -> [(Id, Expr Id)] -> [Id]
forall a b. (a -> b) -> [a] -> [b]
map (Id, Expr Id) -> Id
forall a b. (a, b) -> a
fst [(Id, Expr Id)]
prs) (DFFV () -> DFFV ()) -> DFFV () -> DFFV ()
forall a b. (a -> b) -> a -> b
$
(((Id, Expr Id) -> DFFV ()) -> [(Id, Expr Id)] -> DFFV ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Id, Expr Id) -> DFFV ()
dffvBind [(Id, Expr Id)]
prs DFFV () -> DFFV () -> DFFV ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Expr Id -> DFFV ()
dffvExpr Expr Id
e)
dffvExpr (Case Expr Id
e Id
b Type
_ [Alt Id]
as) = Expr Id -> DFFV ()
dffvExpr Expr Id
e DFFV () -> DFFV () -> DFFV ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Id -> DFFV () -> DFFV ()
forall a. Id -> DFFV a -> DFFV a
extendScope Id
b ((Alt Id -> DFFV ()) -> [Alt Id] -> DFFV ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Alt Id -> DFFV ()
forall t. (t, [Id], Expr Id) -> DFFV ()
dffvAlt [Alt Id]
as)
dffvExpr Expr Id
_other = () -> DFFV ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
dffvAlt :: (t, [Var], CoreExpr) -> DFFV ()
dffvAlt :: (t, [Id], Expr Id) -> DFFV ()
dffvAlt (t
_,[Id]
xs,Expr Id
r) = [Id] -> DFFV () -> DFFV ()
forall a. [Id] -> DFFV a -> DFFV a
extendScopeList [Id]
xs (Expr Id -> DFFV ()
dffvExpr Expr Id
r)
dffvBind :: (Id, CoreExpr) -> DFFV ()
dffvBind :: (Id, Expr Id) -> DFFV ()
dffvBind(Id
x,Expr Id
r)
| Bool -> Bool
not (Id -> Bool
isId Id
x) = Expr Id -> DFFV ()
dffvExpr Expr Id
r
| Bool
otherwise = Bool -> Id -> DFFV ()
dffvLetBndr Bool
False Id
x DFFV () -> DFFV () -> DFFV ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Expr Id -> DFFV ()
dffvExpr Expr Id
r
dffvLetBndr :: Bool -> Id -> DFFV ()
dffvLetBndr :: Bool -> Id -> DFFV ()
dffvLetBndr Bool
vanilla_unfold Id
id
= do { Unfolding -> DFFV ()
go_unf (IdInfo -> Unfolding
unfoldingInfo IdInfo
idinfo)
; (CoreRule -> DFFV ()) -> [CoreRule] -> DFFV ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ CoreRule -> DFFV ()
go_rule (RuleInfo -> [CoreRule]
ruleInfoRules (IdInfo -> RuleInfo
ruleInfo IdInfo
idinfo)) }
where
idinfo :: IdInfo
idinfo = HasDebugCallStack => Id -> IdInfo
Id -> IdInfo
idInfo Id
id
go_unf :: Unfolding -> DFFV ()
go_unf (CoreUnfolding { uf_tmpl :: Unfolding -> Expr Id
uf_tmpl = Expr Id
rhs, uf_src :: Unfolding -> UnfoldingSource
uf_src = UnfoldingSource
src })
= case UnfoldingSource
src of
UnfoldingSource
InlineRhs | Bool
vanilla_unfold -> Expr Id -> DFFV ()
dffvExpr Expr Id
rhs
| Bool
otherwise -> () -> DFFV ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
UnfoldingSource
_ -> Expr Id -> DFFV ()
dffvExpr Expr Id
rhs
go_unf (DFunUnfolding { df_bndrs :: Unfolding -> [Id]
df_bndrs = [Id]
bndrs, df_args :: Unfolding -> [Expr Id]
df_args = [Expr Id]
args })
= [Id] -> DFFV () -> DFFV ()
forall a. [Id] -> DFFV a -> DFFV a
extendScopeList [Id]
bndrs (DFFV () -> DFFV ()) -> DFFV () -> DFFV ()
forall a b. (a -> b) -> a -> b
$ (Expr Id -> DFFV ()) -> [Expr Id] -> DFFV ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Expr Id -> DFFV ()
dffvExpr [Expr Id]
args
go_unf Unfolding
_ = () -> DFFV ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
go_rule :: CoreRule -> DFFV ()
go_rule (BuiltinRule {}) = () -> DFFV ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
go_rule (Rule { ru_bndrs :: CoreRule -> [Id]
ru_bndrs = [Id]
bndrs, ru_rhs :: CoreRule -> Expr Id
ru_rhs = Expr Id
rhs })
= [Id] -> DFFV () -> DFFV ()
forall a. [Id] -> DFFV a -> DFFV a
extendScopeList [Id]
bndrs (Expr Id -> DFFV ()
dffvExpr Expr Id
rhs)
findExternalRules :: Bool
-> [CoreBind]
-> [CoreRule]
-> UnfoldEnv
-> ([CoreBind], [CoreRule])
findExternalRules :: Bool
-> CoreProgram
-> [CoreRule]
-> UnfoldEnv
-> (CoreProgram, [CoreRule])
findExternalRules Bool
omit_prags CoreProgram
binds [CoreRule]
imp_id_rules UnfoldEnv
unfold_env
= (CoreProgram
trimmed_binds, (CoreRule -> Bool) -> [CoreRule] -> [CoreRule]
forall a. (a -> Bool) -> [a] -> [a]
filter CoreRule -> Bool
keep_rule [CoreRule]
all_rules)
where
imp_rules :: [CoreRule]
imp_rules = (CoreRule -> Bool) -> [CoreRule] -> [CoreRule]
forall a. (a -> Bool) -> [a] -> [a]
filter CoreRule -> Bool
expose_rule [CoreRule]
imp_id_rules
imp_user_rule_fvs :: VarSet
imp_user_rule_fvs = (CoreRule -> VarSet) -> [CoreRule] -> VarSet
forall a. (a -> VarSet) -> [a] -> VarSet
mapUnionVarSet CoreRule -> VarSet
user_rule_rhs_fvs [CoreRule]
imp_rules
user_rule_rhs_fvs :: CoreRule -> VarSet
user_rule_rhs_fvs CoreRule
rule | CoreRule -> Bool
isAutoRule CoreRule
rule = VarSet
emptyVarSet
| Bool
otherwise = CoreRule -> VarSet
ruleRhsFreeVars CoreRule
rule
(CoreProgram
trimmed_binds, VarSet
local_bndrs, VarSet
_, [CoreRule]
all_rules) = CoreProgram -> (CoreProgram, VarSet, VarSet, [CoreRule])
trim_binds CoreProgram
binds
keep_rule :: CoreRule -> Bool
keep_rule CoreRule
rule = CoreRule -> VarSet
ruleFreeVars CoreRule
rule VarSet -> VarSet -> Bool
`subVarSet` VarSet
local_bndrs
expose_rule :: CoreRule -> Bool
expose_rule CoreRule
rule
| Bool
omit_prags = Bool
False
| Bool
otherwise = (Id -> Bool) -> [Id] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Id -> Bool
is_external_id (CoreRule -> [Id]
ruleLhsFreeIdsList CoreRule
rule)
is_external_id :: Id -> Bool
is_external_id Id
id = case UnfoldEnv -> Id -> Maybe (Name, Bool)
forall a. VarEnv a -> Id -> Maybe a
lookupVarEnv UnfoldEnv
unfold_env Id
id of
Just (Name
name, Bool
_) -> Name -> Bool
isExternalName Name
name
Maybe (Name, Bool)
Nothing -> Bool
False
trim_binds :: [CoreBind]
-> ( [CoreBind]
, VarSet
, VarSet
, [CoreRule])
trim_binds :: CoreProgram -> (CoreProgram, VarSet, VarSet, [CoreRule])
trim_binds []
= ([], VarSet
emptyVarSet, VarSet
imp_user_rule_fvs, [CoreRule]
imp_rules)
trim_binds (CoreBind
bind:CoreProgram
binds)
| (Id -> Bool) -> [Id] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Id -> Bool
needed [Id]
bndrs
= ( CoreBind
bind CoreBind -> CoreProgram -> CoreProgram
forall a. a -> [a] -> [a]
: CoreProgram
binds', VarSet
bndr_set', VarSet
needed_fvs', [CoreRule]
local_rules [CoreRule] -> [CoreRule] -> [CoreRule]
forall a. [a] -> [a] -> [a]
++ [CoreRule]
rules )
| Bool
otherwise
= (CoreProgram, VarSet, VarSet, [CoreRule])
stuff
where
stuff :: (CoreProgram, VarSet, VarSet, [CoreRule])
stuff@(CoreProgram
binds', VarSet
bndr_set, VarSet
needed_fvs, [CoreRule]
rules)
= CoreProgram -> (CoreProgram, VarSet, VarSet, [CoreRule])
trim_binds CoreProgram
binds
needed :: Id -> Bool
needed Id
bndr = Id -> Bool
isExportedId Id
bndr Bool -> Bool -> Bool
|| Id
bndr Id -> VarSet -> Bool
`elemVarSet` VarSet
needed_fvs
bndrs :: [Id]
bndrs = CoreBind -> [Id]
forall b. Bind b -> [b]
bindersOf CoreBind
bind
rhss :: [Expr Id]
rhss = CoreBind -> [Expr Id]
forall b. Bind b -> [Expr b]
rhssOfBind CoreBind
bind
bndr_set' :: VarSet
bndr_set' = VarSet
bndr_set VarSet -> [Id] -> VarSet
`extendVarSetList` [Id]
bndrs
needed_fvs' :: VarSet
needed_fvs' = VarSet
needed_fvs VarSet -> VarSet -> VarSet
`unionVarSet`
(Id -> VarSet) -> [Id] -> VarSet
forall a. (a -> VarSet) -> [a] -> VarSet
mapUnionVarSet Id -> VarSet
idUnfoldingVars [Id]
bndrs VarSet -> VarSet -> VarSet
`unionVarSet`
(Expr Id -> VarSet) -> [Expr Id] -> VarSet
forall a. (a -> VarSet) -> [a] -> VarSet
mapUnionVarSet Expr Id -> VarSet
exprFreeVars [Expr Id]
rhss VarSet -> VarSet -> VarSet
`unionVarSet`
(CoreRule -> VarSet) -> [CoreRule] -> VarSet
forall a. (a -> VarSet) -> [a] -> VarSet
mapUnionVarSet CoreRule -> VarSet
user_rule_rhs_fvs [CoreRule]
local_rules
local_rules :: [CoreRule]
local_rules = [ CoreRule
rule
| Id
id <- [Id]
bndrs
, Id -> Bool
is_external_id Id
id
, CoreRule
rule <- Id -> [CoreRule]
idCoreRules Id
id
, CoreRule -> Bool
expose_rule CoreRule
rule ]
tidyTopName :: Module -> IORef NameCache -> Maybe Id -> TidyOccEnv
-> Id -> IO (TidyOccEnv, Name)
tidyTopName :: Module
-> IORef NameCache
-> Maybe Id
-> TidyOccEnv
-> Id
-> IO (TidyOccEnv, Name)
tidyTopName Module
mod IORef NameCache
nc_var Maybe Id
maybe_ref TidyOccEnv
occ_env Id
id
| Bool
global Bool -> Bool -> Bool
&& Bool
internal = (TidyOccEnv, Name) -> IO (TidyOccEnv, Name)
forall (m :: * -> *) a. Monad m => a -> m a
return (TidyOccEnv
occ_env, Name -> Name
localiseName Name
name)
| Bool
global Bool -> Bool -> Bool
&& Bool
external = (TidyOccEnv, Name) -> IO (TidyOccEnv, Name)
forall (m :: * -> *) a. Monad m => a -> m a
return (TidyOccEnv
occ_env, Name
name)
| Bool
local Bool -> Bool -> Bool
&& Bool
internal = do { Name
new_local_name <- IORef NameCache -> (NameCache -> (NameCache, Name)) -> IO Name
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef NameCache
nc_var NameCache -> (NameCache, Name)
mk_new_local
; (TidyOccEnv, Name) -> IO (TidyOccEnv, Name)
forall (m :: * -> *) a. Monad m => a -> m a
return (TidyOccEnv
occ_env', Name
new_local_name) }
| Bool
local Bool -> Bool -> Bool
&& Bool
external = do { Name
new_external_name <- IORef NameCache -> (NameCache -> (NameCache, Name)) -> IO Name
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef NameCache
nc_var NameCache -> (NameCache, Name)
mk_new_external
; (TidyOccEnv, Name) -> IO (TidyOccEnv, Name)
forall (m :: * -> *) a. Monad m => a -> m a
return (TidyOccEnv
occ_env', Name
new_external_name) }
| Bool
otherwise = String -> IO (TidyOccEnv, Name)
forall a. String -> a
panic String
"tidyTopName"
where
name :: Name
name = Id -> Name
idName Id
id
external :: Bool
external = Maybe Id -> Bool
forall a. Maybe a -> Bool
isJust Maybe Id
maybe_ref
global :: Bool
global = Name -> Bool
isExternalName Name
name
local :: Bool
local = Bool -> Bool
not Bool
global
internal :: Bool
internal = Bool -> Bool
not Bool
external
loc :: SrcSpan
loc = Name -> SrcSpan
nameSrcSpan Name
name
old_occ :: OccName
old_occ = Name -> OccName
nameOccName Name
name
new_occ :: OccName
new_occ | Just Id
ref <- Maybe Id
maybe_ref
, Id
ref Id -> Id -> Bool
forall a. Eq a => a -> a -> Bool
/= Id
id
= NameSpace -> String -> OccName
mkOccName (OccName -> NameSpace
occNameSpace OccName
old_occ) (String -> OccName) -> String -> OccName
forall a b. (a -> b) -> a -> b
$
let
ref_str :: String
ref_str = OccName -> String
occNameString (Id -> OccName
forall a. NamedThing a => a -> OccName
getOccName Id
ref)
occ_str :: String
occ_str = OccName -> String
occNameString OccName
old_occ
in
case String
occ_str of
Char
'$':Char
'w':String
_ -> String
occ_str
String
_other | Name -> Bool
isSystemName Name
name -> String
ref_str
| Bool
otherwise -> String
ref_str String -> String -> String
forall a. [a] -> [a] -> [a]
++ Char
'_' Char -> String -> String
forall a. a -> [a] -> [a]
: String
occ_str
| Bool
otherwise = OccName
old_occ
(TidyOccEnv
occ_env', OccName
occ') = TidyOccEnv -> OccName -> (TidyOccEnv, OccName)
tidyOccName TidyOccEnv
occ_env OccName
new_occ
mk_new_local :: NameCache -> (NameCache, Name)
mk_new_local NameCache
nc = (NameCache
nc { nsUniqs :: UniqSupply
nsUniqs = UniqSupply
us }, Unique -> OccName -> SrcSpan -> Name
mkInternalName Unique
uniq OccName
occ' SrcSpan
loc)
where
(Unique
uniq, UniqSupply
us) = UniqSupply -> (Unique, UniqSupply)
takeUniqFromSupply (NameCache -> UniqSupply
nsUniqs NameCache
nc)
mk_new_external :: NameCache -> (NameCache, Name)
mk_new_external NameCache
nc = NameCache -> Module -> OccName -> SrcSpan -> (NameCache, Name)
allocateGlobalBinder NameCache
nc Module
mod OccName
occ' SrcSpan
loc
tidyTopBinds :: HscEnv
-> Module
-> UnfoldEnv
-> TidyOccEnv
-> CoreProgram
-> IO (TidyEnv, CoreProgram)
tidyTopBinds :: HscEnv
-> Module
-> UnfoldEnv
-> TidyOccEnv
-> CoreProgram
-> IO (TidyEnv, CoreProgram)
tidyTopBinds HscEnv
hsc_env Module
this_mod UnfoldEnv
unfold_env TidyOccEnv
init_occ_env CoreProgram
binds
= do Id
mkIntegerId <- DynFlags -> HscEnv -> IO Id
lookupMkIntegerName DynFlags
dflags HscEnv
hsc_env
Id
mkNaturalId <- DynFlags -> HscEnv -> IO Id
lookupMkNaturalName DynFlags
dflags HscEnv
hsc_env
Maybe DataCon
integerSDataCon <- DynFlags -> HscEnv -> IO (Maybe DataCon)
lookupIntegerSDataConName DynFlags
dflags HscEnv
hsc_env
Maybe DataCon
naturalSDataCon <- DynFlags -> HscEnv -> IO (Maybe DataCon)
lookupNaturalSDataConName DynFlags
dflags HscEnv
hsc_env
let cvt_literal :: LitNumType -> Integer -> Maybe (Expr Id)
cvt_literal LitNumType
nt Integer
i = case LitNumType
nt of
LitNumType
LitNumInteger -> Expr Id -> Maybe (Expr Id)
forall a. a -> Maybe a
Just (DynFlags -> Id -> Maybe DataCon -> Integer -> Expr Id
cvtLitInteger DynFlags
dflags Id
mkIntegerId Maybe DataCon
integerSDataCon Integer
i)
LitNumType
LitNumNatural -> Expr Id -> Maybe (Expr Id)
forall a. a -> Maybe a
Just (DynFlags -> Id -> Maybe DataCon -> Integer -> Expr Id
cvtLitNatural DynFlags
dflags Id
mkNaturalId Maybe DataCon
naturalSDataCon Integer
i)
LitNumType
_ -> Maybe (Expr Id)
forall a. Maybe a
Nothing
result :: (TidyEnv, CoreProgram)
result = (LitNumType -> Integer -> Maybe (Expr Id))
-> TidyEnv -> CoreProgram -> (TidyEnv, CoreProgram)
forall (t :: * -> *).
Traversable t =>
(LitNumType -> Integer -> Maybe (Expr Id))
-> TidyEnv -> t CoreBind -> (TidyEnv, t CoreBind)
tidy LitNumType -> Integer -> Maybe (Expr Id)
cvt_literal TidyEnv
forall a. (TidyOccEnv, VarEnv a)
init_env CoreProgram
binds
CoreProgram -> ()
seqBinds ((TidyEnv, CoreProgram) -> CoreProgram
forall a b. (a, b) -> b
snd (TidyEnv, CoreProgram)
result) () -> IO (TidyEnv, CoreProgram) -> IO (TidyEnv, CoreProgram)
`seq` (TidyEnv, CoreProgram) -> IO (TidyEnv, CoreProgram)
forall (m :: * -> *) a. Monad m => a -> m a
return (TidyEnv, CoreProgram)
result
where
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
init_env :: (TidyOccEnv, VarEnv a)
init_env = (TidyOccEnv
init_occ_env, VarEnv a
forall a. VarEnv a
emptyVarEnv)
tidy :: (LitNumType -> Integer -> Maybe (Expr Id))
-> TidyEnv -> t CoreBind -> (TidyEnv, t CoreBind)
tidy LitNumType -> Integer -> Maybe (Expr Id)
cvt_literal = (TidyEnv -> CoreBind -> (TidyEnv, CoreBind))
-> TidyEnv -> t CoreBind -> (TidyEnv, t CoreBind)
forall (t :: * -> *) a b c.
Traversable t =>
(a -> b -> (a, c)) -> a -> t b -> (a, t c)
mapAccumL (DynFlags
-> Module
-> (LitNumType -> Integer -> Maybe (Expr Id))
-> UnfoldEnv
-> TidyEnv
-> CoreBind
-> (TidyEnv, CoreBind)
tidyTopBind DynFlags
dflags Module
this_mod LitNumType -> Integer -> Maybe (Expr Id)
cvt_literal UnfoldEnv
unfold_env)
tidyTopBind :: DynFlags
-> Module
-> (LitNumType -> Integer -> Maybe CoreExpr)
-> UnfoldEnv
-> TidyEnv
-> CoreBind
-> (TidyEnv, CoreBind)
tidyTopBind :: DynFlags
-> Module
-> (LitNumType -> Integer -> Maybe (Expr Id))
-> UnfoldEnv
-> TidyEnv
-> CoreBind
-> (TidyEnv, CoreBind)
tidyTopBind DynFlags
dflags Module
this_mod LitNumType -> Integer -> Maybe (Expr Id)
cvt_literal UnfoldEnv
unfold_env
(TidyOccEnv
occ_env,VarEnv Id
subst1) (NonRec Id
bndr Expr Id
rhs)
= (TidyEnv
tidy_env2, Id -> Expr Id -> CoreBind
forall b. b -> Expr b -> Bind b
NonRec Id
bndr' Expr Id
rhs')
where
Just (Name
name',Bool
show_unfold) = UnfoldEnv -> Id -> Maybe (Name, Bool)
forall a. VarEnv a -> Id -> Maybe a
lookupVarEnv UnfoldEnv
unfold_env Id
bndr
caf_info :: CafInfo
caf_info = DynFlags -> Module -> CafRefEnv -> Int -> Expr Id -> CafInfo
hasCafRefs DynFlags
dflags Module
this_mod
(VarEnv Id
subst1, LitNumType -> Integer -> Maybe (Expr Id)
cvt_literal)
(Id -> Int
idArity Id
bndr) Expr Id
rhs
(Id
bndr', Expr Id
rhs') = DynFlags
-> Bool
-> TidyEnv
-> CafInfo
-> Name
-> (Id, Expr Id)
-> (Id, Expr Id)
tidyTopPair DynFlags
dflags Bool
show_unfold TidyEnv
tidy_env2 CafInfo
caf_info Name
name'
(Id
bndr, Expr Id
rhs)
subst2 :: VarEnv Id
subst2 = VarEnv Id -> Id -> Id -> VarEnv Id
forall a. VarEnv a -> Id -> a -> VarEnv a
extendVarEnv VarEnv Id
subst1 Id
bndr Id
bndr'
tidy_env2 :: TidyEnv
tidy_env2 = (TidyOccEnv
occ_env, VarEnv Id
subst2)
tidyTopBind DynFlags
dflags Module
this_mod LitNumType -> Integer -> Maybe (Expr Id)
cvt_literal UnfoldEnv
unfold_env
(TidyOccEnv
occ_env, VarEnv Id
subst1) (Rec [(Id, Expr Id)]
prs)
= (TidyEnv
tidy_env2, [(Id, Expr Id)] -> CoreBind
forall b. [(b, Expr b)] -> Bind b
Rec [(Id, Expr Id)]
prs')
where
prs' :: [(Id, Expr Id)]
prs' = [ DynFlags
-> Bool
-> TidyEnv
-> CafInfo
-> Name
-> (Id, Expr Id)
-> (Id, Expr Id)
tidyTopPair DynFlags
dflags Bool
show_unfold TidyEnv
tidy_env2 CafInfo
caf_info Name
name' (Id
id,Expr Id
rhs)
| (Id
id,Expr Id
rhs) <- [(Id, Expr Id)]
prs,
let (Name
name',Bool
show_unfold) =
String -> Maybe (Name, Bool) -> (Name, Bool)
forall a. HasCallStack => String -> Maybe a -> a
expectJust String
"tidyTopBind" (Maybe (Name, Bool) -> (Name, Bool))
-> Maybe (Name, Bool) -> (Name, Bool)
forall a b. (a -> b) -> a -> b
$ UnfoldEnv -> Id -> Maybe (Name, Bool)
forall a. VarEnv a -> Id -> Maybe a
lookupVarEnv UnfoldEnv
unfold_env Id
id
]
subst2 :: VarEnv Id
subst2 = VarEnv Id -> [(Id, Id)] -> VarEnv Id
forall a. VarEnv a -> [(Id, a)] -> VarEnv a
extendVarEnvList VarEnv Id
subst1 ([Id]
bndrs [Id] -> [Id] -> [(Id, Id)]
forall a b. [a] -> [b] -> [(a, b)]
`zip` ((Id, Expr Id) -> Id) -> [(Id, Expr Id)] -> [Id]
forall a b. (a -> b) -> [a] -> [b]
map (Id, Expr Id) -> Id
forall a b. (a, b) -> a
fst [(Id, Expr Id)]
prs')
tidy_env2 :: TidyEnv
tidy_env2 = (TidyOccEnv
occ_env, VarEnv Id
subst2)
bndrs :: [Id]
bndrs = ((Id, Expr Id) -> Id) -> [(Id, Expr Id)] -> [Id]
forall a b. (a -> b) -> [a] -> [b]
map (Id, Expr Id) -> Id
forall a b. (a, b) -> a
fst [(Id, Expr Id)]
prs
caf_info :: CafInfo
caf_info
| [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
or [ CafInfo -> Bool
mayHaveCafRefs (DynFlags -> Module -> CafRefEnv -> Int -> Expr Id -> CafInfo
hasCafRefs DynFlags
dflags Module
this_mod
(VarEnv Id
subst1, LitNumType -> Integer -> Maybe (Expr Id)
cvt_literal)
(Id -> Int
idArity Id
bndr) Expr Id
rhs)
| (Id
bndr,Expr Id
rhs) <- [(Id, Expr Id)]
prs ] = CafInfo
MayHaveCafRefs
| Bool
otherwise = CafInfo
NoCafRefs
tidyTopPair :: DynFlags
-> Bool
-> TidyEnv
-> CafInfo
-> Name
-> (Id, CoreExpr)
-> (Id, CoreExpr)
tidyTopPair :: DynFlags
-> Bool
-> TidyEnv
-> CafInfo
-> Name
-> (Id, Expr Id)
-> (Id, Expr Id)
tidyTopPair DynFlags
dflags Bool
show_unfold TidyEnv
rhs_tidy_env CafInfo
caf_info Name
name' (Id
bndr, Expr Id
rhs)
= (Id
bndr1, Expr Id
rhs1)
where
bndr1 :: Id
bndr1 = IdDetails -> Name -> Type -> IdInfo -> Id
mkGlobalId IdDetails
details Name
name' Type
ty' IdInfo
idinfo'
details :: IdDetails
details = Id -> IdDetails
idDetails Id
bndr
ty' :: Type
ty' = Type -> Type
tidyTopType (Id -> Type
idType Id
bndr)
rhs1 :: Expr Id
rhs1 = TidyEnv -> Expr Id -> Expr Id
tidyExpr TidyEnv
rhs_tidy_env Expr Id
rhs
idinfo' :: IdInfo
idinfo' = DynFlags
-> TidyEnv
-> Name
-> Expr Id
-> Expr Id
-> IdInfo
-> Bool
-> CafInfo
-> IdInfo
tidyTopIdInfo DynFlags
dflags TidyEnv
rhs_tidy_env Name
name' Expr Id
rhs Expr Id
rhs1 (HasDebugCallStack => Id -> IdInfo
Id -> IdInfo
idInfo Id
bndr)
Bool
show_unfold CafInfo
caf_info
tidyTopIdInfo :: DynFlags -> TidyEnv -> Name -> CoreExpr -> CoreExpr
-> IdInfo -> Bool -> CafInfo -> IdInfo
tidyTopIdInfo :: DynFlags
-> TidyEnv
-> Name
-> Expr Id
-> Expr Id
-> IdInfo
-> Bool
-> CafInfo
-> IdInfo
tidyTopIdInfo DynFlags
dflags TidyEnv
rhs_tidy_env Name
name Expr Id
orig_rhs Expr Id
tidy_rhs IdInfo
idinfo Bool
show_unfold CafInfo
caf_info
| Bool -> Bool
not Bool
is_external
= IdInfo
vanillaIdInfo
IdInfo -> CafInfo -> IdInfo
`setCafInfo` CafInfo
caf_info
IdInfo -> Int -> IdInfo
`setArityInfo` Int
arity
IdInfo -> StrictSig -> IdInfo
`setStrictnessInfo` StrictSig
final_sig
IdInfo -> Unfolding -> IdInfo
`setUnfoldingInfo` Unfolding
minimal_unfold_info
| Bool
otherwise
= IdInfo
vanillaIdInfo
IdInfo -> CafInfo -> IdInfo
`setCafInfo` CafInfo
caf_info
IdInfo -> Int -> IdInfo
`setArityInfo` Int
arity
IdInfo -> StrictSig -> IdInfo
`setStrictnessInfo` StrictSig
final_sig
IdInfo -> OccInfo -> IdInfo
`setOccInfo` OccInfo
robust_occ_info
IdInfo -> InlinePragma -> IdInfo
`setInlinePragInfo` (IdInfo -> InlinePragma
inlinePragInfo IdInfo
idinfo)
IdInfo -> Unfolding -> IdInfo
`setUnfoldingInfo` Unfolding
unfold_info
where
is_external :: Bool
is_external = Name -> Bool
isExternalName Name
name
robust_occ_info :: OccInfo
robust_occ_info = OccInfo -> OccInfo
zapFragileOcc (IdInfo -> OccInfo
occInfo IdInfo
idinfo)
mb_bot_str :: Maybe (Int, StrictSig)
mb_bot_str = Expr Id -> Maybe (Int, StrictSig)
exprBotStrictness_maybe Expr Id
orig_rhs
sig :: StrictSig
sig = IdInfo -> StrictSig
strictnessInfo IdInfo
idinfo
final_sig :: StrictSig
final_sig | Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ StrictSig -> Bool
isTopSig StrictSig
sig
= WARN( _bottom_hidden sig , ppr name ) sig
| Just (Int
_, StrictSig
nsig) <- Maybe (Int, StrictSig)
mb_bot_str = StrictSig
nsig
| Bool
otherwise = StrictSig
sig
_bottom_hidden :: StrictSig -> Bool
_bottom_hidden StrictSig
id_sig = case Maybe (Int, StrictSig)
mb_bot_str of
Maybe (Int, StrictSig)
Nothing -> Bool
False
Just (Int
arity, StrictSig
_) -> Bool -> Bool
not (StrictSig -> Int -> Bool
appIsBottom StrictSig
id_sig Int
arity)
unf_info :: Unfolding
unf_info = IdInfo -> Unfolding
unfoldingInfo IdInfo
idinfo
unfold_info :: Unfolding
unfold_info | Bool
show_unfold = TidyEnv -> Unfolding -> Unfolding -> Unfolding
tidyUnfolding TidyEnv
rhs_tidy_env Unfolding
unf_info Unfolding
unf_from_rhs
| Bool
otherwise = Unfolding
minimal_unfold_info
minimal_unfold_info :: Unfolding
minimal_unfold_info = Unfolding -> Unfolding
zapUnfolding Unfolding
unf_info
unf_from_rhs :: Unfolding
unf_from_rhs = DynFlags -> Bool -> Expr Id -> Unfolding
mkTopUnfolding DynFlags
dflags Bool
is_bot Expr Id
tidy_rhs
is_bot :: Bool
is_bot = StrictSig -> Bool
isBottomingSig StrictSig
final_sig
arity :: Int
arity = Expr Id -> Int
exprArity Expr Id
orig_rhs
type CafRefEnv = (VarEnv Id, LitNumType -> Integer -> Maybe CoreExpr)
hasCafRefs :: DynFlags -> Module
-> CafRefEnv -> Arity -> CoreExpr
-> CafInfo
hasCafRefs :: DynFlags -> Module -> CafRefEnv -> Int -> Expr Id -> CafInfo
hasCafRefs DynFlags
dflags Module
this_mod (VarEnv Id
subst, LitNumType -> Integer -> Maybe (Expr Id)
cvt_literal) Int
arity Expr Id
expr
| Bool
is_caf Bool -> Bool -> Bool
|| Bool
mentions_cafs = CafInfo
MayHaveCafRefs
| Bool
otherwise = CafInfo
NoCafRefs
where
mentions_cafs :: Bool
mentions_cafs = Expr Id -> Bool
forall a. Expr a -> Bool
cafRefsE Expr Id
expr
is_dynamic_name :: Name -> Bool
is_dynamic_name = DynFlags -> Module -> Name -> Bool
isDllName DynFlags
dflags Module
this_mod
is_caf :: Bool
is_caf = Bool -> Bool
not (Int
arity Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 Bool -> Bool -> Bool
|| Platform
-> (Name -> Bool)
-> (LitNumType -> Integer -> Maybe (Expr Id))
-> Expr Id
-> Bool
rhsIsStatic (DynFlags -> Platform
targetPlatform DynFlags
dflags) Name -> Bool
is_dynamic_name
LitNumType -> Integer -> Maybe (Expr Id)
cvt_literal Expr Id
expr)
cafRefsE :: Expr a -> Bool
cafRefsE :: Expr a -> Bool
cafRefsE (Var Id
id) = Id -> Bool
cafRefsV Id
id
cafRefsE (Lit Literal
lit) = Literal -> Bool
cafRefsL Literal
lit
cafRefsE (App Expr a
f Expr a
a) = Expr a -> Bool
forall a. Expr a -> Bool
cafRefsE Expr a
f Bool -> Bool -> Bool
|| Expr a -> Bool
forall a. Expr a -> Bool
cafRefsE Expr a
a
cafRefsE (Lam a
_ Expr a
e) = Expr a -> Bool
forall a. Expr a -> Bool
cafRefsE Expr a
e
cafRefsE (Let Bind a
b Expr a
e) = [Expr a] -> Bool
forall a. [Expr a] -> Bool
cafRefsEs (Bind a -> [Expr a]
forall b. Bind b -> [Expr b]
rhssOfBind Bind a
b) Bool -> Bool -> Bool
|| Expr a -> Bool
forall a. Expr a -> Bool
cafRefsE Expr a
e
cafRefsE (Case Expr a
e a
_ Type
_ [Alt a]
alts) = Expr a -> Bool
forall a. Expr a -> Bool
cafRefsE Expr a
e Bool -> Bool -> Bool
|| [Expr a] -> Bool
forall a. [Expr a] -> Bool
cafRefsEs ([Alt a] -> [Expr a]
forall b. [Alt b] -> [Expr b]
rhssOfAlts [Alt a]
alts)
cafRefsE (Tick Tickish Id
_n Expr a
e) = Expr a -> Bool
forall a. Expr a -> Bool
cafRefsE Expr a
e
cafRefsE (Cast Expr a
e Coercion
_co) = Expr a -> Bool
forall a. Expr a -> Bool
cafRefsE Expr a
e
cafRefsE (Type Type
_) = Bool
False
cafRefsE (Coercion Coercion
_) = Bool
False
cafRefsEs :: [Expr a] -> Bool
cafRefsEs :: [Expr a] -> Bool
cafRefsEs [] = Bool
False
cafRefsEs (Expr a
e:[Expr a]
es) = Expr a -> Bool
forall a. Expr a -> Bool
cafRefsE Expr a
e Bool -> Bool -> Bool
|| [Expr a] -> Bool
forall a. [Expr a] -> Bool
cafRefsEs [Expr a]
es
cafRefsL :: Literal -> Bool
cafRefsL :: Literal -> Bool
cafRefsL (LitNumber LitNumType
nt Integer
i Type
_) = case LitNumType -> Integer -> Maybe (Expr Id)
cvt_literal LitNumType
nt Integer
i of
Just Expr Id
e -> Expr Id -> Bool
forall a. Expr a -> Bool
cafRefsE Expr Id
e
Maybe (Expr Id)
Nothing -> Bool
False
cafRefsL Literal
_ = Bool
False
cafRefsV :: Id -> Bool
cafRefsV :: Id -> Bool
cafRefsV Id
id
| Bool -> Bool
not (Id -> Bool
isLocalId Id
id) = CafInfo -> Bool
mayHaveCafRefs (Id -> CafInfo
idCafInfo Id
id)
| Just Id
id' <- VarEnv Id -> Id -> Maybe Id
forall a. VarEnv a -> Id -> Maybe a
lookupVarEnv VarEnv Id
subst Id
id = CafInfo -> Bool
mayHaveCafRefs (Id -> CafInfo
idCafInfo Id
id')
| Bool
otherwise = Bool
False