{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
module GHC.HsToCore (
deSugar, deSugarExpr
) where
#include "HsVersions.h"
import GHC.Prelude
import GHC.Driver.Session
import GHC.Driver.Config
import GHC.Driver.Env
import GHC.Driver.Backend
import GHC.Hs
import GHC.HsToCore.Usage
import GHC.HsToCore.Monad
import GHC.HsToCore.Expr
import GHC.HsToCore.Binds
import GHC.HsToCore.Foreign.Decl
import GHC.HsToCore.Coverage
import GHC.HsToCore.Docs
import GHC.Tc.Types
import GHC.Tc.Utils.Monad ( finalSafeMode, fixSafeInstances )
import GHC.Tc.Module ( runTcInteractive )
import GHC.Core.Type
import GHC.Core.TyCon ( tyConDataCons )
import GHC.Core
import GHC.Core.FVs ( exprsSomeFreeVarsList )
import GHC.Core.SimpleOpt ( simpleOptPgm, simpleOptExpr )
import GHC.Core.Utils
import GHC.Core.Unfold.Make
import GHC.Core.Ppr
import GHC.Core.Coercion
import GHC.Core.DataCon ( dataConWrapId )
import GHC.Core.Make
import GHC.Core.Rules
import GHC.Core.Opt.Monad ( CoreToDo(..) )
import GHC.Core.Lint ( endPassIO )
import GHC.Builtin.Names
import GHC.Builtin.Types.Prim
import GHC.Builtin.Types
import GHC.Data.FastString
import GHC.Data.OrdList
import GHC.Utils.Error
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Utils.Misc
import GHC.Utils.Monad
import GHC.Utils.Logger
import GHC.Types.Id
import GHC.Types.Id.Info
import GHC.Types.ForeignStubs
import GHC.Types.Avail
import GHC.Types.Basic
import GHC.Types.Var.Set
import GHC.Types.SrcLoc
import GHC.Types.SourceFile
import GHC.Types.TypeEnv
import GHC.Types.Name
import GHC.Types.Name.Set
import GHC.Types.Name.Env
import GHC.Types.Name.Ppr
import GHC.Types.HpcInfo
import GHC.Unit
import GHC.Unit.Module.ModGuts
import GHC.Unit.Module.ModIface
import Data.List (partition)
import Data.IORef
import Control.Monad( when )
import GHC.Driver.Plugins ( LoadedPlugin(..) )
deSugar :: HscEnv -> ModLocation -> TcGblEnv -> IO (Messages DecoratedSDoc, Maybe ModGuts)
deSugar :: HscEnv
-> ModLocation
-> TcGblEnv
-> IO (Messages DecoratedSDoc, Maybe ModGuts)
deSugar HscEnv
hsc_env
ModLocation
mod_loc
tcg_env :: TcGblEnv
tcg_env@(TcGblEnv { tcg_mod :: TcGblEnv -> Module
tcg_mod = Module
id_mod,
tcg_semantic_mod :: TcGblEnv -> Module
tcg_semantic_mod = Module
mod,
tcg_src :: TcGblEnv -> HscSource
tcg_src = HscSource
hsc_src,
tcg_type_env :: TcGblEnv -> TypeEnv
tcg_type_env = TypeEnv
type_env,
tcg_imports :: TcGblEnv -> ImportAvails
tcg_imports = ImportAvails
imports,
tcg_exports :: TcGblEnv -> [AvailInfo]
tcg_exports = [AvailInfo]
exports,
tcg_keep :: TcGblEnv -> TcRef NameSet
tcg_keep = TcRef NameSet
keep_var,
tcg_th_splice_used :: TcGblEnv -> TcRef Bool
tcg_th_splice_used = TcRef Bool
tc_splice_used,
tcg_rdr_env :: TcGblEnv -> GlobalRdrEnv
tcg_rdr_env = GlobalRdrEnv
rdr_env,
tcg_fix_env :: TcGblEnv -> FixityEnv
tcg_fix_env = FixityEnv
fix_env,
tcg_inst_env :: TcGblEnv -> InstEnv
tcg_inst_env = InstEnv
inst_env,
tcg_fam_inst_env :: TcGblEnv -> FamInstEnv
tcg_fam_inst_env = FamInstEnv
fam_inst_env,
tcg_merged :: TcGblEnv -> [(Module, Fingerprint)]
tcg_merged = [(Module, Fingerprint)]
merged,
tcg_warns :: TcGblEnv -> Warnings
tcg_warns = Warnings
warns,
tcg_anns :: TcGblEnv -> [Annotation]
tcg_anns = [Annotation]
anns,
tcg_binds :: TcGblEnv -> LHsBinds GhcTc
tcg_binds = LHsBinds GhcTc
binds,
tcg_imp_specs :: TcGblEnv -> [LTcSpecPrag]
tcg_imp_specs = [LTcSpecPrag]
imp_specs,
tcg_dependent_files :: TcGblEnv -> TcRef [FilePath]
tcg_dependent_files = TcRef [FilePath]
dependent_files,
tcg_ev_binds :: TcGblEnv -> Bag EvBind
tcg_ev_binds = Bag EvBind
ev_binds,
tcg_th_foreign_files :: TcGblEnv -> TcRef [(ForeignSrcLang, FilePath)]
tcg_th_foreign_files = TcRef [(ForeignSrcLang, FilePath)]
th_foreign_files_var,
tcg_fords :: TcGblEnv -> [LForeignDecl GhcTc]
tcg_fords = [LForeignDecl GhcTc]
fords,
tcg_rules :: TcGblEnv -> [LRuleDecl GhcTc]
tcg_rules = [LRuleDecl GhcTc]
rules,
tcg_patsyns :: TcGblEnv -> [PatSyn]
tcg_patsyns = [PatSyn]
patsyns,
tcg_tcs :: TcGblEnv -> [TyCon]
tcg_tcs = [TyCon]
tcs,
tcg_insts :: TcGblEnv -> [ClsInst]
tcg_insts = [ClsInst]
insts,
tcg_fam_insts :: TcGblEnv -> [FamInst]
tcg_fam_insts = [FamInst]
fam_insts,
tcg_hpc :: TcGblEnv -> Bool
tcg_hpc = Bool
other_hpc_info,
tcg_complete_matches :: TcGblEnv -> CompleteMatches
tcg_complete_matches = CompleteMatches
complete_matches
})
= do { let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
print_unqual :: PrintUnqualified
print_unqual = UnitEnv -> GlobalRdrEnv -> PrintUnqualified
mkPrintUnqualified (HscEnv -> UnitEnv
hsc_unit_env HscEnv
hsc_env) GlobalRdrEnv
rdr_env
; forall (m :: * -> *) a.
MonadIO m =>
Logger -> DynFlags -> SDoc -> (a -> ()) -> m a -> m a
withTiming Logger
logger DynFlags
dflags
(FilePath -> SDoc
text FilePath
"Desugar"SDoc -> SDoc -> SDoc
<+>SDoc -> SDoc
brackets (forall a. Outputable a => a -> SDoc
ppr Module
mod))
(forall a b. a -> b -> a
const ()) forall a b. (a -> b) -> a -> b
$
do {
; let export_set :: NameSet
export_set = [AvailInfo] -> NameSet
availsToNameSet [AvailInfo]
exports
bcknd :: Backend
bcknd = DynFlags -> Backend
backend DynFlags
dflags
hpcInfo :: HpcInfo
hpcInfo = Bool -> HpcInfo
emptyHpcInfo Bool
other_hpc_info
; (Bag (GenLocated SrcSpanAnnA (HsBindLR GhcTc GhcTc))
binds_cvr, HpcInfo
ds_hpc_info, Maybe ModBreaks
modBreaks)
<- if Bool -> Bool
not (HscSource -> Bool
isHsBootOrSig HscSource
hsc_src)
then HscEnv
-> Module
-> ModLocation
-> NameSet
-> [TyCon]
-> LHsBinds GhcTc
-> IO (LHsBinds GhcTc, HpcInfo, Maybe ModBreaks)
addTicksToBinds HscEnv
hsc_env Module
mod ModLocation
mod_loc
NameSet
export_set (TypeEnv -> [TyCon]
typeEnvTyCons TypeEnv
type_env) LHsBinds GhcTc
binds
else forall (m :: * -> *) a. Monad m => a -> m a
return (LHsBinds GhcTc
binds, HpcInfo
hpcInfo, forall a. Maybe a
Nothing)
; (Messages DecoratedSDoc
msgs, Maybe ([CoreBind], OrdList Binding, [CoreRule], ForeignStubs)
mb_res) <- forall a.
HscEnv -> TcGblEnv -> DsM a -> IO (Messages DecoratedSDoc, Maybe a)
initDs HscEnv
hsc_env TcGblEnv
tcg_env forall a b. (a -> b) -> a -> b
$
do { [CoreBind]
ds_ev_binds <- Bag EvBind -> DsM [CoreBind]
dsEvBinds Bag EvBind
ev_binds
; OrdList Binding
core_prs <- LHsBinds GhcTc -> DsM (OrdList Binding)
dsTopLHsBinds Bag (GenLocated SrcSpanAnnA (HsBindLR GhcTc GhcTc))
binds_cvr
; OrdList Binding
core_prs <- OrdList Binding -> DsM (OrdList Binding)
patchMagicDefns OrdList Binding
core_prs
; (OrdList Binding
spec_prs, [CoreRule]
spec_rules) <- [LTcSpecPrag] -> DsM (OrdList Binding, [CoreRule])
dsImpSpecs [LTcSpecPrag]
imp_specs
; (ForeignStubs
ds_fords, OrdList Binding
foreign_prs) <- [LForeignDecl GhcTc] -> DsM (ForeignStubs, OrdList Binding)
dsForeigns [LForeignDecl GhcTc]
fords
; [CoreRule]
ds_rules <- forall (m :: * -> *) a b.
Applicative m =>
(a -> m (Maybe b)) -> [a] -> m [b]
mapMaybeM LRuleDecl GhcTc -> DsM (Maybe CoreRule)
dsRule [LRuleDecl GhcTc]
rules
; let hpc_init :: CStub
hpc_init
| GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_Hpc DynFlags
dflags = DynFlags -> Module -> HpcInfo -> CStub
hpcInitCode (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) Module
mod HpcInfo
ds_hpc_info
| Bool
otherwise = forall a. Monoid a => a
mempty
; forall (m :: * -> *) a. Monad m => a -> m a
return ( [CoreBind]
ds_ev_binds
, OrdList Binding
foreign_prs forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Binding
core_prs forall a. OrdList a -> OrdList a -> OrdList a
`appOL` OrdList Binding
spec_prs
, [CoreRule]
spec_rules forall a. [a] -> [a] -> [a]
++ [CoreRule]
ds_rules
, ForeignStubs
ds_fords ForeignStubs -> CStub -> ForeignStubs
`appendStubC` CStub
hpc_init) }
; case Maybe ([CoreBind], OrdList Binding, [CoreRule], ForeignStubs)
mb_res of {
Maybe ([CoreBind], OrdList Binding, [CoreRule], ForeignStubs)
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return (Messages DecoratedSDoc
msgs, forall a. Maybe a
Nothing) ;
Just ([CoreBind]
ds_ev_binds, OrdList Binding
all_prs, [CoreRule]
all_rules, ForeignStubs
ds_fords) ->
do {
NameSet
keep_alive <- forall a. IORef a -> IO a
readIORef TcRef NameSet
keep_var
; let ([CoreRule]
rules_for_locals, [CoreRule]
rules_for_imps) = forall a. (a -> Bool) -> [a] -> ([a], [a])
partition CoreRule -> Bool
isLocalRule [CoreRule]
all_rules
final_prs :: [Binding]
final_prs = forall t.
Backend
-> NameSet -> NameSet -> [CoreRule] -> [(Id, t)] -> [(Id, t)]
addExportFlagsAndRules Backend
bcknd NameSet
export_set NameSet
keep_alive
[CoreRule]
rules_for_locals (forall a. OrdList a -> [a]
fromOL OrdList Binding
all_prs)
final_pgm :: [CoreBind]
final_pgm = [CoreBind] -> [Binding] -> [CoreBind]
combineEvBinds [CoreBind]
ds_ev_binds [Binding]
final_prs
; HscEnv
-> PrintUnqualified
-> CoreToDo
-> [CoreBind]
-> [CoreRule]
-> IO ()
endPassIO HscEnv
hsc_env PrintUnqualified
print_unqual CoreToDo
CoreDesugar [CoreBind]
final_pgm [CoreRule]
rules_for_imps
; let simpl_opts :: SimpleOpts
simpl_opts = DynFlags -> SimpleOpts
initSimpleOpts DynFlags
dflags
; let ([CoreBind]
ds_binds, [CoreRule]
ds_rules_for_imps, [CoreBind]
occ_anald_binds)
= SimpleOpts
-> Module
-> [CoreBind]
-> [CoreRule]
-> ([CoreBind], [CoreRule], [CoreBind])
simpleOptPgm SimpleOpts
simpl_opts Module
mod [CoreBind]
final_pgm [CoreRule]
rules_for_imps
; Logger
-> DynFlags -> DumpFlag -> FilePath -> DumpFormat -> SDoc -> IO ()
dumpIfSet_dyn Logger
logger DynFlags
dflags DumpFlag
Opt_D_dump_occur_anal FilePath
"Occurrence analysis"
DumpFormat
FormatCore (forall b. OutputableBndr b => [Bind b] -> SDoc
pprCoreBindings [CoreBind]
occ_anald_binds SDoc -> SDoc -> SDoc
$$ [CoreRule] -> SDoc
pprRules [CoreRule]
ds_rules_for_imps )
; HscEnv
-> PrintUnqualified
-> CoreToDo
-> [CoreBind]
-> [CoreRule]
-> IO ()
endPassIO HscEnv
hsc_env PrintUnqualified
print_unqual CoreToDo
CoreDesugarOpt [CoreBind]
ds_binds [CoreRule]
ds_rules_for_imps
; let used_names :: NameSet
used_names = TcGblEnv -> NameSet
mkUsedNames TcGblEnv
tcg_env
pluginModules :: [ModIface]
pluginModules = forall a b. (a -> b) -> [a] -> [b]
map LoadedPlugin -> ModIface
lpModule (HscEnv -> [LoadedPlugin]
hsc_plugins HscEnv
hsc_env)
home_unit :: HomeUnit
home_unit = HscEnv -> HomeUnit
hsc_home_unit HscEnv
hsc_env
; Dependencies
deps <- UnitId -> [Module] -> TcGblEnv -> IO Dependencies
mkDependencies (forall u. GenHomeUnit u -> UnitId
homeUnitId HomeUnit
home_unit)
(forall a b. (a -> b) -> [a] -> [b]
map forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module [ModIface]
pluginModules) TcGblEnv
tcg_env
; Bool
used_th <- forall a. IORef a -> IO a
readIORef TcRef Bool
tc_splice_used
; [FilePath]
dep_files <- forall a. IORef a -> IO a
readIORef TcRef [FilePath]
dependent_files
; SafeHaskellMode
safe_mode <- DynFlags -> TcGblEnv -> IO SafeHaskellMode
finalSafeMode DynFlags
dflags TcGblEnv
tcg_env
; [Usage]
usages <- HscEnv
-> Module
-> ImportedMods
-> NameSet
-> [FilePath]
-> [(Module, Fingerprint)]
-> [ModIface]
-> IO [Usage]
mkUsageInfo HscEnv
hsc_env Module
mod (ImportAvails -> ImportedMods
imp_mods ImportAvails
imports) NameSet
used_names
[FilePath]
dep_files [(Module, Fingerprint)]
merged [ModIface]
pluginModules
; MASSERT( id_mod == mod )
; [(ForeignSrcLang, FilePath)]
foreign_files <- forall a. IORef a -> IO a
readIORef TcRef [(ForeignSrcLang, FilePath)]
th_foreign_files_var
; (Maybe HsDocString
doc_hdr, DeclDocMap
decl_docs, ArgDocMap
arg_docs) <- forall (m :: * -> *).
MonadIO m =>
TcGblEnv -> m (Maybe HsDocString, DeclDocMap, ArgDocMap)
extractDocs TcGblEnv
tcg_env
; let mod_guts :: ModGuts
mod_guts = ModGuts {
mg_module :: Module
mg_module = Module
mod,
mg_hsc_src :: HscSource
mg_hsc_src = HscSource
hsc_src,
mg_loc :: SrcSpan
mg_loc = ModLocation -> SrcSpan
mkFileSrcSpan ModLocation
mod_loc,
mg_exports :: [AvailInfo]
mg_exports = [AvailInfo]
exports,
mg_usages :: [Usage]
mg_usages = [Usage]
usages,
mg_deps :: Dependencies
mg_deps = Dependencies
deps,
mg_used_th :: Bool
mg_used_th = Bool
used_th,
mg_rdr_env :: GlobalRdrEnv
mg_rdr_env = GlobalRdrEnv
rdr_env,
mg_fix_env :: FixityEnv
mg_fix_env = FixityEnv
fix_env,
mg_warns :: Warnings
mg_warns = Warnings
warns,
mg_anns :: [Annotation]
mg_anns = [Annotation]
anns,
mg_tcs :: [TyCon]
mg_tcs = [TyCon]
tcs,
mg_insts :: [ClsInst]
mg_insts = SafeHaskellMode -> [ClsInst] -> [ClsInst]
fixSafeInstances SafeHaskellMode
safe_mode [ClsInst]
insts,
mg_fam_insts :: [FamInst]
mg_fam_insts = [FamInst]
fam_insts,
mg_inst_env :: InstEnv
mg_inst_env = InstEnv
inst_env,
mg_fam_inst_env :: FamInstEnv
mg_fam_inst_env = FamInstEnv
fam_inst_env,
mg_patsyns :: [PatSyn]
mg_patsyns = [PatSyn]
patsyns,
mg_rules :: [CoreRule]
mg_rules = [CoreRule]
ds_rules_for_imps,
mg_binds :: [CoreBind]
mg_binds = [CoreBind]
ds_binds,
mg_foreign :: ForeignStubs
mg_foreign = ForeignStubs
ds_fords,
mg_foreign_files :: [(ForeignSrcLang, FilePath)]
mg_foreign_files = [(ForeignSrcLang, FilePath)]
foreign_files,
mg_hpc_info :: HpcInfo
mg_hpc_info = HpcInfo
ds_hpc_info,
mg_modBreaks :: Maybe ModBreaks
mg_modBreaks = Maybe ModBreaks
modBreaks,
mg_safe_haskell :: SafeHaskellMode
mg_safe_haskell = SafeHaskellMode
safe_mode,
mg_trust_pkg :: Bool
mg_trust_pkg = ImportAvails -> Bool
imp_trust_own_pkg ImportAvails
imports,
mg_complete_matches :: CompleteMatches
mg_complete_matches = CompleteMatches
complete_matches,
mg_doc_hdr :: Maybe HsDocString
mg_doc_hdr = Maybe HsDocString
doc_hdr,
mg_decl_docs :: DeclDocMap
mg_decl_docs = DeclDocMap
decl_docs,
mg_arg_docs :: ArgDocMap
mg_arg_docs = ArgDocMap
arg_docs
}
; forall (m :: * -> *) a. Monad m => a -> m a
return (Messages DecoratedSDoc
msgs, forall a. a -> Maybe a
Just ModGuts
mod_guts)
}}}}
mkFileSrcSpan :: ModLocation -> SrcSpan
mkFileSrcSpan :: ModLocation -> SrcSpan
mkFileSrcSpan ModLocation
mod_loc
= case ModLocation -> Maybe FilePath
ml_hs_file ModLocation
mod_loc of
Just FilePath
file_path -> FastString -> SrcSpan
mkGeneralSrcSpan (FilePath -> FastString
mkFastString FilePath
file_path)
Maybe FilePath
Nothing -> SrcSpan
interactiveSrcSpan
dsImpSpecs :: [LTcSpecPrag] -> DsM (OrdList (Id,CoreExpr), [CoreRule])
dsImpSpecs :: [LTcSpecPrag] -> DsM (OrdList Binding, [CoreRule])
dsImpSpecs [LTcSpecPrag]
imp_specs
= do { [(OrdList Binding, CoreRule)]
spec_prs <- forall (m :: * -> *) a b.
Applicative m =>
(a -> m (Maybe b)) -> [a] -> m [b]
mapMaybeM (Maybe CoreExpr
-> LTcSpecPrag -> DsM (Maybe (OrdList Binding, CoreRule))
dsSpec forall a. Maybe a
Nothing) [LTcSpecPrag]
imp_specs
; let ([OrdList Binding]
spec_binds, [CoreRule]
spec_rules) = forall a b. [(a, b)] -> ([a], [b])
unzip [(OrdList Binding, CoreRule)]
spec_prs
; forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. [OrdList a] -> OrdList a
concatOL [OrdList Binding]
spec_binds, [CoreRule]
spec_rules) }
combineEvBinds :: [CoreBind] -> [(Id,CoreExpr)] -> [CoreBind]
combineEvBinds :: [CoreBind] -> [Binding] -> [CoreBind]
combineEvBinds [] [Binding]
val_prs
= [forall b. [(b, Expr b)] -> Bind b
Rec [Binding]
val_prs]
combineEvBinds (NonRec Id
b CoreExpr
r : [CoreBind]
bs) [Binding]
val_prs
| Id -> Bool
isId Id
b = [CoreBind] -> [Binding] -> [CoreBind]
combineEvBinds [CoreBind]
bs ((Id
b,CoreExpr
r)forall a. a -> [a] -> [a]
:[Binding]
val_prs)
| Bool
otherwise = forall b. b -> Expr b -> Bind b
NonRec Id
b CoreExpr
r forall a. a -> [a] -> [a]
: [CoreBind] -> [Binding] -> [CoreBind]
combineEvBinds [CoreBind]
bs [Binding]
val_prs
combineEvBinds (Rec [Binding]
prs : [CoreBind]
bs) [Binding]
val_prs
= [CoreBind] -> [Binding] -> [CoreBind]
combineEvBinds [CoreBind]
bs ([Binding]
prs forall a. [a] -> [a] -> [a]
++ [Binding]
val_prs)
deSugarExpr :: HscEnv -> LHsExpr GhcTc -> IO (Messages DecoratedSDoc, Maybe CoreExpr)
deSugarExpr :: HscEnv
-> LHsExpr GhcTc -> IO (Messages DecoratedSDoc, Maybe CoreExpr)
deSugarExpr HscEnv
hsc_env LHsExpr GhcTc
tc_expr = do
let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
let logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
Logger -> DynFlags -> FilePath -> IO ()
showPass Logger
logger DynFlags
dflags FilePath
"Desugar"
(Messages DecoratedSDoc
msgs, Maybe CoreExpr
mb_core_expr) <- forall a. HscEnv -> TcRn a -> IO (Messages DecoratedSDoc, Maybe a)
runTcInteractive HscEnv
hsc_env forall a b. (a -> b) -> a -> b
$ forall a. DsM a -> TcM a
initDsTc forall a b. (a -> b) -> a -> b
$
LHsExpr GhcTc -> DsM CoreExpr
dsLExpr LHsExpr GhcTc
tc_expr
case Maybe CoreExpr
mb_core_expr of
Maybe CoreExpr
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just CoreExpr
expr -> Logger
-> DynFlags -> DumpFlag -> FilePath -> DumpFormat -> SDoc -> IO ()
dumpIfSet_dyn Logger
logger DynFlags
dflags DumpFlag
Opt_D_dump_ds FilePath
"Desugared"
DumpFormat
FormatCore (forall b. OutputableBndr b => Expr b -> SDoc
pprCoreExpr CoreExpr
expr)
forall (m :: * -> *) a. Monad m => a -> m a
return (Messages DecoratedSDoc
msgs, Maybe CoreExpr
mb_core_expr)
addExportFlagsAndRules
:: Backend -> NameSet -> NameSet -> [CoreRule]
-> [(Id, t)] -> [(Id, t)]
addExportFlagsAndRules :: forall t.
Backend
-> NameSet -> NameSet -> [CoreRule] -> [(Id, t)] -> [(Id, t)]
addExportFlagsAndRules Backend
bcknd NameSet
exports NameSet
keep_alive [CoreRule]
rules [(Id, t)]
prs
= forall a c b. (a -> c) -> [(a, b)] -> [(c, b)]
mapFst Id -> Id
add_one [(Id, t)]
prs
where
add_one :: Id -> Id
add_one Id
bndr = Name -> Id -> Id
add_rules Name
name (Name -> Id -> Id
add_export Name
name Id
bndr)
where
name :: Name
name = Id -> Name
idName Id
bndr
add_rules :: Name -> Id -> Id
add_rules Name
name Id
bndr
| Just [CoreRule]
rules <- forall a. NameEnv a -> Name -> Maybe a
lookupNameEnv RuleBase
rule_base Name
name
= Id
bndr Id -> [CoreRule] -> Id
`addIdSpecialisations` [CoreRule]
rules
| Bool
otherwise
= Id
bndr
rule_base :: RuleBase
rule_base = RuleBase -> [CoreRule] -> RuleBase
extendRuleBaseList RuleBase
emptyRuleBase [CoreRule]
rules
add_export :: Name -> Id -> Id
add_export Name
name Id
bndr
| Name -> Bool
dont_discard Name
name = Id -> Id
setIdExported Id
bndr
| Bool
otherwise = Id
bndr
dont_discard :: Name -> Bool
dont_discard :: Name -> Bool
dont_discard Name
name = Name -> Bool
is_exported Name
name
Bool -> Bool -> Bool
|| Name
name Name -> NameSet -> Bool
`elemNameSet` NameSet
keep_alive
is_exported :: Name -> Bool
is_exported :: Name -> Bool
is_exported | Backend -> Bool
backendRetainsAllBindings Backend
bcknd = Name -> Bool
isExternalName
| Bool
otherwise = (Name -> NameSet -> Bool
`elemNameSet` NameSet
exports)
dsRule :: LRuleDecl GhcTc -> DsM (Maybe CoreRule)
dsRule :: LRuleDecl GhcTc -> DsM (Maybe CoreRule)
dsRule (L SrcSpanAnnA
loc (HsRule { rd_name :: forall pass. RuleDecl pass -> XRec pass (SourceText, FastString)
rd_name = XRec GhcTc (SourceText, FastString)
name
, rd_act :: forall pass. RuleDecl pass -> Activation
rd_act = Activation
rule_act
, rd_tmvs :: forall pass. RuleDecl pass -> [LRuleBndr pass]
rd_tmvs = [LRuleBndr GhcTc]
vars
, rd_lhs :: forall pass. RuleDecl pass -> XRec pass (HsExpr pass)
rd_lhs = LHsExpr GhcTc
lhs
, rd_rhs :: forall pass. RuleDecl pass -> XRec pass (HsExpr pass)
rd_rhs = LHsExpr GhcTc
rhs }))
= forall a. SrcSpan -> DsM a -> DsM a
putSrcSpanDs (forall a. SrcSpanAnn' a -> SrcSpan
locA SrcSpanAnnA
loc) forall a b. (a -> b) -> a -> b
$
do { let bndrs' :: [Id]
bndrs' = [Id
var | L SrcSpan
_ (RuleBndr XCRuleBndr GhcTc
_ (L SrcSpanAnnN
_ Id
var)) <- [LRuleBndr GhcTc]
vars]
; CoreExpr
lhs' <- forall gbl lcl a.
GeneralFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
unsetGOptM GeneralFlag
Opt_EnableRewriteRules forall a b. (a -> b) -> a -> b
$
forall gbl lcl a.
WarningFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
unsetWOptM WarningFlag
Opt_WarnIdentities forall a b. (a -> b) -> a -> b
$
LHsExpr GhcTc -> DsM CoreExpr
dsLExpr LHsExpr GhcTc
lhs
; CoreExpr
rhs' <- LHsExpr GhcTc -> DsM CoreExpr
dsLExpr LHsExpr GhcTc
rhs
; Module
this_mod <- forall (m :: * -> *). HasModule m => m Module
getModule
; ([Id]
bndrs'', CoreExpr
lhs'', CoreExpr
rhs'') <- [Id] -> CoreExpr -> CoreExpr -> DsM ([Id], CoreExpr, CoreExpr)
unfold_coerce [Id]
bndrs' CoreExpr
lhs' CoreExpr
rhs'
; DynFlags
dflags <- forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
; case DynFlags -> [Id] -> CoreExpr -> Either SDoc ([Id], Id, [CoreExpr])
decomposeRuleLhs DynFlags
dflags [Id]
bndrs'' CoreExpr
lhs'' of {
Left SDoc
msg -> do { WarnReason -> SDoc -> DsM ()
warnDs WarnReason
NoReason SDoc
msg; forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing } ;
Right ([Id]
final_bndrs, Id
fn_id, [CoreExpr]
args) -> do
{ let is_local :: Bool
is_local = Id -> Bool
isLocalId Id
fn_id
fn_name :: Name
fn_name = Id -> Name
idName Id
fn_id
simpl_opts :: SimpleOpts
simpl_opts = DynFlags -> SimpleOpts
initSimpleOpts DynFlags
dflags
final_rhs :: CoreExpr
final_rhs = HasDebugCallStack => SimpleOpts -> CoreExpr -> CoreExpr
simpleOptExpr SimpleOpts
simpl_opts CoreExpr
rhs''
rule_name :: FastString
rule_name = forall a b. (a, b) -> b
snd (forall l e. GenLocated l e -> e
unLoc XRec GhcTc (SourceText, FastString)
name)
final_bndrs_set :: VarSet
final_bndrs_set = [Id] -> VarSet
mkVarSet [Id]
final_bndrs
arg_ids :: [Id]
arg_ids = forall a. (a -> Bool) -> [a] -> [a]
filterOut (Id -> VarSet -> Bool
`elemVarSet` VarSet
final_bndrs_set) forall a b. (a -> b) -> a -> b
$
(Id -> Bool) -> [CoreExpr] -> [Id]
exprsSomeFreeVarsList Id -> Bool
isId [CoreExpr]
args
; CoreRule
rule <- Module
-> Bool
-> FastString
-> Activation
-> Name
-> [Id]
-> [CoreExpr]
-> CoreExpr
-> DsM CoreRule
dsMkUserRule Module
this_mod Bool
is_local
FastString
rule_name Activation
rule_act Name
fn_name [Id]
final_bndrs [CoreExpr]
args
CoreExpr
final_rhs
; forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (WarningFlag -> DynFlags -> Bool
wopt WarningFlag
Opt_WarnInlineRuleShadowing DynFlags
dflags) forall a b. (a -> b) -> a -> b
$
FastString -> Activation -> Id -> [Id] -> DsM ()
warnRuleShadowing FastString
rule_name Activation
rule_act Id
fn_id [Id]
arg_ids
; forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just CoreRule
rule)
} } }
warnRuleShadowing :: RuleName -> Activation -> Id -> [Id] -> DsM ()
warnRuleShadowing :: FastString -> Activation -> Id -> [Id] -> DsM ()
warnRuleShadowing FastString
rule_name Activation
rule_act Id
fn_id [Id]
arg_ids
= do { Bool -> Id -> DsM ()
check Bool
False Id
fn_id
; forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Bool -> Id -> DsM ()
check Bool
True) [Id]
arg_ids }
where
check :: Bool -> Id -> DsM ()
check Bool
check_rules_too Id
lhs_id
| Id -> Bool
isLocalId Id
lhs_id Bool -> Bool -> Bool
|| Unfolding -> Bool
canUnfold (Id -> Unfolding
idUnfolding Id
lhs_id)
, Id -> Activation
idInlineActivation Id
lhs_id Activation -> Activation -> Bool
`competesWith` Activation
rule_act
= WarnReason -> SDoc -> DsM ()
warnDs (WarningFlag -> WarnReason
Reason WarningFlag
Opt_WarnInlineRuleShadowing)
([SDoc] -> SDoc
vcat [ SDoc -> Int -> SDoc -> SDoc
hang (FilePath -> SDoc
text FilePath
"Rule" SDoc -> SDoc -> SDoc
<+> FastString -> SDoc
pprRuleName FastString
rule_name
SDoc -> SDoc -> SDoc
<+> FilePath -> SDoc
text FilePath
"may never fire")
Int
2 (FilePath -> SDoc
text FilePath
"because" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (forall a. Outputable a => a -> SDoc
ppr Id
lhs_id)
SDoc -> SDoc -> SDoc
<+> FilePath -> SDoc
text FilePath
"might inline first")
, FilePath -> SDoc
text FilePath
"Probable fix: add an INLINE[n] or NOINLINE[n] pragma for"
SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (forall a. Outputable a => a -> SDoc
ppr Id
lhs_id)
, SDoc -> SDoc
whenPprDebug (forall a. Outputable a => a -> SDoc
ppr (Id -> Activation
idInlineActivation Id
lhs_id) SDoc -> SDoc -> SDoc
$$ forall a. Outputable a => a -> SDoc
ppr Activation
rule_act) ])
| Bool
check_rules_too
, CoreRule
bad_rule : [CoreRule]
_ <- Id -> [CoreRule]
get_bad_rules Id
lhs_id
= WarnReason -> SDoc -> DsM ()
warnDs (WarningFlag -> WarnReason
Reason WarningFlag
Opt_WarnInlineRuleShadowing)
([SDoc] -> SDoc
vcat [ SDoc -> Int -> SDoc -> SDoc
hang (FilePath -> SDoc
text FilePath
"Rule" SDoc -> SDoc -> SDoc
<+> FastString -> SDoc
pprRuleName FastString
rule_name
SDoc -> SDoc -> SDoc
<+> FilePath -> SDoc
text FilePath
"may never fire")
Int
2 (FilePath -> SDoc
text FilePath
"because rule" SDoc -> SDoc -> SDoc
<+> FastString -> SDoc
pprRuleName (CoreRule -> FastString
ruleName CoreRule
bad_rule)
SDoc -> SDoc -> SDoc
<+> FilePath -> SDoc
text FilePath
"for"SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (forall a. Outputable a => a -> SDoc
ppr Id
lhs_id)
SDoc -> SDoc -> SDoc
<+> FilePath -> SDoc
text FilePath
"might fire first")
, FilePath -> SDoc
text FilePath
"Probable fix: add phase [n] or [~n] to the competing rule"
, SDoc -> SDoc
whenPprDebug (forall a. Outputable a => a -> SDoc
ppr CoreRule
bad_rule) ])
| Bool
otherwise
= forall (m :: * -> *) a. Monad m => a -> m a
return ()
get_bad_rules :: Id -> [CoreRule]
get_bad_rules Id
lhs_id
= [ CoreRule
rule | CoreRule
rule <- Id -> [CoreRule]
idCoreRules Id
lhs_id
, CoreRule -> Activation
ruleActivation CoreRule
rule Activation -> Activation -> Bool
`competesWith` Activation
rule_act ]
unfold_coerce :: [Id] -> CoreExpr -> CoreExpr -> DsM ([Var], CoreExpr, CoreExpr)
unfold_coerce :: [Id] -> CoreExpr -> CoreExpr -> DsM ([Id], CoreExpr, CoreExpr)
unfold_coerce [Id]
bndrs CoreExpr
lhs CoreExpr
rhs = do
([Id]
bndrs', CoreExpr -> CoreExpr
wrap) <- [Id] -> DsM ([Id], CoreExpr -> CoreExpr)
go [Id]
bndrs
forall (m :: * -> *) a. Monad m => a -> m a
return ([Id]
bndrs', CoreExpr -> CoreExpr
wrap CoreExpr
lhs, CoreExpr -> CoreExpr
wrap CoreExpr
rhs)
where
go :: [Id] -> DsM ([Id], CoreExpr -> CoreExpr)
go :: [Id] -> DsM ([Id], CoreExpr -> CoreExpr)
go [] = forall (m :: * -> *) a. Monad m => a -> m a
return ([], forall a. a -> a
id)
go (Id
v:[Id]
vs)
| Just (TyCon
tc, [Type
k, Type
t1, Type
t2]) <- HasDebugCallStack => Type -> Maybe (TyCon, [Type])
splitTyConApp_maybe (Id -> Type
idType Id
v)
, TyCon
tc forall a. Uniquable a => a -> Unique -> Bool
`hasKey` Unique
coercibleTyConKey = do
Unique
u <- forall gbl lcl. TcRnIf gbl lcl Unique
newUnique
let ty' :: Type
ty' = TyCon -> [Type] -> Type
mkTyConApp TyCon
eqReprPrimTyCon [Type
k, Type
k, Type
t1, Type
t2]
v' :: Id
v' = Name -> Type -> Id
mkLocalCoVar
((OccName -> OccName) -> Unique -> Name -> Name
mkDerivedInternalName OccName -> OccName
mkRepEqOcc Unique
u (forall a. NamedThing a => a -> Name
getName Id
v)) Type
ty'
box :: CoreExpr
box = forall b. Id -> Expr b
Var (DataCon -> Id
dataConWrapId DataCon
coercibleDataCon) forall b. Expr b -> [Type] -> Expr b
`mkTyApps`
[Type
k, Type
t1, Type
t2] forall b. Expr b -> Expr b -> Expr b
`App`
forall b. Coercion -> Expr b
Coercion (Id -> Coercion
mkCoVarCo Id
v')
([Id]
bndrs, CoreExpr -> CoreExpr
wrap) <- [Id] -> DsM ([Id], CoreExpr -> CoreExpr)
go [Id]
vs
forall (m :: * -> *) a. Monad m => a -> m a
return (Id
v'forall a. a -> [a] -> [a]
:[Id]
bndrs, CoreBind -> CoreExpr -> CoreExpr
mkCoreLet (forall b. b -> Expr b -> Bind b
NonRec Id
v CoreExpr
box) forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoreExpr -> CoreExpr
wrap)
| Bool
otherwise = do
([Id]
bndrs,CoreExpr -> CoreExpr
wrap) <- [Id] -> DsM ([Id], CoreExpr -> CoreExpr)
go [Id]
vs
forall (m :: * -> *) a. Monad m => a -> m a
return (Id
vforall a. a -> [a] -> [a]
:[Id]
bndrs, CoreExpr -> CoreExpr
wrap)
patchMagicDefns :: OrdList (Id,CoreExpr)
-> DsM (OrdList (Id,CoreExpr))
patchMagicDefns :: OrdList Binding -> DsM (OrdList Binding)
patchMagicDefns OrdList Binding
pairs
= do { Module
this_mod <- forall (m :: * -> *). HasModule m => m Module
getModule
; if Module
this_mod Module -> ModuleSet -> Bool
`elemModuleSet` ModuleSet
magicDefnModules
then forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Binding -> DsM Binding
patchMagicDefn OrdList Binding
pairs
else forall (m :: * -> *) a. Monad m => a -> m a
return OrdList Binding
pairs }
patchMagicDefn :: (Id, CoreExpr) -> DsM (Id, CoreExpr)
patchMagicDefn :: Binding -> DsM Binding
patchMagicDefn orig_pair :: Binding
orig_pair@(Id
orig_id, CoreExpr
orig_rhs)
| Just Id -> CoreExpr -> DsM Binding
mk_magic_pair <- forall a. NameEnv a -> Name -> Maybe a
lookupNameEnv NameEnv (Id -> CoreExpr -> DsM Binding)
magicDefnsEnv (forall a. NamedThing a => a -> Name
getName Id
orig_id)
= do { magic_pair :: Binding
magic_pair@(Id
magic_id, CoreExpr
_) <- Id -> CoreExpr -> DsM Binding
mk_magic_pair Id
orig_id CoreExpr
orig_rhs
; MASSERT( getUnique magic_id == getUnique orig_id )
; MASSERT( varType magic_id `eqType` varType orig_id )
; forall (m :: * -> *) a. Monad m => a -> m a
return Binding
magic_pair }
| Bool
otherwise
= forall (m :: * -> *) a. Monad m => a -> m a
return Binding
orig_pair
magicDefns :: [(Name, Id -> CoreExpr
-> DsM (Id, CoreExpr)
)]
magicDefns :: [(Name, Id -> CoreExpr -> DsM Binding)]
magicDefns = [ (Name
unsafeCoercePrimName, Id -> CoreExpr -> DsM Binding
mkUnsafeCoercePrimPair) ]
magicDefnsEnv :: NameEnv (Id -> CoreExpr -> DsM (Id, CoreExpr))
magicDefnsEnv :: NameEnv (Id -> CoreExpr -> DsM Binding)
magicDefnsEnv = forall a. [(Name, a)] -> NameEnv a
mkNameEnv [(Name, Id -> CoreExpr -> DsM Binding)]
magicDefns
magicDefnModules :: ModuleSet
magicDefnModules :: ModuleSet
magicDefnModules = [Module] -> ModuleSet
mkModuleSet forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (HasDebugCallStack => Name -> Module
nameModule forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NamedThing a => a -> Name
getName forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) [(Name, Id -> CoreExpr -> DsM Binding)]
magicDefns
mkUnsafeCoercePrimPair :: Id -> CoreExpr -> DsM (Id, CoreExpr)
mkUnsafeCoercePrimPair :: Id -> CoreExpr -> DsM Binding
mkUnsafeCoercePrimPair Id
_old_id CoreExpr
old_expr
= do { Id
unsafe_equality_proof_id <- Name -> DsM Id
dsLookupGlobalId Name
unsafeEqualityProofName
; TyCon
unsafe_equality_tc <- Name -> DsM TyCon
dsLookupTyCon Name
unsafeEqualityTyConName
; let [DataCon
unsafe_refl_data_con] = TyCon -> [DataCon]
tyConDataCons TyCon
unsafe_equality_tc
rhs :: CoreExpr
rhs = forall b. [b] -> Expr b -> Expr b
mkLams [ Id
runtimeRep1TyVar, Id
runtimeRep2TyVar
, Id
openAlphaTyVar, Id
openBetaTyVar
, Id
x ] forall a b. (a -> b) -> a -> b
$
CoreExpr -> Id -> AltCon -> [Id] -> CoreExpr -> CoreExpr
mkSingleAltCase CoreExpr
scrut1
(Type -> Type -> Id
mkWildValBinder Type
Many Type
scrut1_ty)
(DataCon -> AltCon
DataAlt DataCon
unsafe_refl_data_con)
[Id
rr_cv] forall a b. (a -> b) -> a -> b
$
CoreExpr -> Id -> AltCon -> [Id] -> CoreExpr -> CoreExpr
mkSingleAltCase CoreExpr
scrut2
(Type -> Type -> Id
mkWildValBinder Type
Many Type
scrut2_ty)
(DataCon -> AltCon
DataAlt DataCon
unsafe_refl_data_con)
[Id
ab_cv] forall a b. (a -> b) -> a -> b
$
forall b. Id -> Expr b
Var Id
x CoreExpr -> Coercion -> CoreExpr
`mkCast` Coercion
x_co
[Id
x, Id
rr_cv, Id
ab_cv] = [Type] -> [Id]
mkTemplateLocals
[ Type
openAlphaTy
, Type
rr_cv_ty
, Type
ab_cv_ty
]
unsafe_equality :: Type -> Type -> Type -> (CoreExpr, Type, Type)
unsafe_equality Type
k Type
a Type
b
= ( forall b. Expr b -> [Type] -> Expr b
mkTyApps (forall b. Id -> Expr b
Var Id
unsafe_equality_proof_id) [Type
k,Type
b,Type
a]
, TyCon -> [Type] -> Type
mkTyConApp TyCon
unsafe_equality_tc [Type
k,Type
b,Type
a]
, Type -> Type -> Type -> Type -> Type
mkHeteroPrimEqPred Type
k Type
k Type
a Type
b
)
(CoreExpr
scrut1, Type
scrut1_ty, Type
rr_cv_ty) = Type -> Type -> Type -> (CoreExpr, Type, Type)
unsafe_equality Type
runtimeRepTy
Type
runtimeRep1Ty
Type
runtimeRep2Ty
(CoreExpr
scrut2, Type
scrut2_ty, Type
ab_cv_ty) = Type -> Type -> Type -> (CoreExpr, Type, Type)
unsafe_equality (Type -> Type
tYPE Type
runtimeRep2Ty)
(Type
openAlphaTy Type -> Coercion -> Type
`mkCastTy` Coercion
alpha_co)
Type
openBetaTy
alpha_co :: Coercion
alpha_co = HasDebugCallStack => Role -> TyCon -> [Coercion] -> Coercion
mkTyConAppCo Role
Nominal TyCon
tYPETyCon [Id -> Coercion
mkCoVarCo Id
rr_cv]
x_co :: Coercion
x_co = Role -> Type -> MCoercionN -> Coercion
mkGReflCo Role
Representational Type
openAlphaTy (Coercion -> MCoercionN
MCo Coercion
alpha_co) Coercion -> Coercion -> Coercion
`mkTransCo`
HasDebugCallStack => Coercion -> Coercion
mkSubCo (Id -> Coercion
mkCoVarCo Id
ab_cv)
info :: IdInfo
info = IdInfo
noCafIdInfo IdInfo -> InlinePragma -> IdInfo
`setInlinePragInfo` InlinePragma
alwaysInlinePragma
IdInfo -> Unfolding -> IdInfo
`setUnfoldingInfo` CoreExpr -> Unfolding
mkCompulsoryUnfolding' CoreExpr
rhs
ty :: Type
ty = [Id] -> Type -> Type
mkSpecForAllTys [ Id
runtimeRep1TyVar, Id
runtimeRep2TyVar
, Id
openAlphaTyVar, Id
openBetaTyVar ] forall a b. (a -> b) -> a -> b
$
Type -> Type -> Type
mkVisFunTyMany Type
openAlphaTy Type
openBetaTy
id :: Id
id = Name -> Type -> Id
mkExportedVanillaId Name
unsafeCoercePrimName Type
ty Id -> IdInfo -> Id
`setIdInfo` IdInfo
info
; forall (m :: * -> *) a. Monad m => a -> m a
return (Id
id, CoreExpr
old_expr) }