{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
module GHC.Core.Opt.Arity
( manifestArity, joinRhsArity, exprArity, typeArity
, exprEtaExpandArity, findRhsArity, etaExpand
, etaExpandToJoinPoint, etaExpandToJoinPointRule
, exprBotStrictness_maybe
)
where
#include "HsVersions.h"
import GHC.Prelude
import GHC.Core
import GHC.Core.FVs
import GHC.Core.Utils
import GHC.Core.Subst
import GHC.Types.Demand
import GHC.Types.Var
import GHC.Types.Var.Env
import GHC.Types.Id
import GHC.Core.Type as Type
import GHC.Core.TyCon ( initRecTc, checkRecTc )
import GHC.Core.Predicate ( isDictTy )
import GHC.Core.Coercion as Coercion
import GHC.Types.Basic
import GHC.Types.Unique
import GHC.Driver.Session ( DynFlags, GeneralFlag(..), gopt )
import GHC.Utils.Outputable
import GHC.Data.FastString
import GHC.Utils.Misc ( debugIsOn )
manifestArity :: CoreExpr -> Arity
manifestArity :: CoreExpr -> JoinArity
manifestArity (Lam Id
v CoreExpr
e) | Id -> Bool
isId Id
v = JoinArity
1 JoinArity -> JoinArity -> JoinArity
forall a. Num a => a -> a -> a
External instance of the constraint type Num JoinArity
+ CoreExpr -> JoinArity
manifestArity CoreExpr
e
| Bool
otherwise = CoreExpr -> JoinArity
manifestArity CoreExpr
e
manifestArity (Tick Tickish Id
t CoreExpr
e) | Bool -> Bool
not (Tickish Id -> Bool
forall id. Tickish id -> Bool
tickishIsCode Tickish Id
t) = CoreExpr -> JoinArity
manifestArity CoreExpr
e
manifestArity (Cast CoreExpr
e Coercion
_) = CoreExpr -> JoinArity
manifestArity CoreExpr
e
manifestArity CoreExpr
_ = JoinArity
0
joinRhsArity :: CoreExpr -> JoinArity
joinRhsArity :: CoreExpr -> JoinArity
joinRhsArity (Lam Id
_ CoreExpr
e) = JoinArity
1 JoinArity -> JoinArity -> JoinArity
forall a. Num a => a -> a -> a
External instance of the constraint type Num JoinArity
+ CoreExpr -> JoinArity
joinRhsArity CoreExpr
e
joinRhsArity CoreExpr
_ = JoinArity
0
exprArity :: CoreExpr -> Arity
exprArity :: CoreExpr -> JoinArity
exprArity CoreExpr
e = CoreExpr -> JoinArity
go CoreExpr
e
where
go :: CoreExpr -> JoinArity
go (Var Id
v) = Id -> JoinArity
idArity Id
v
go (Lam Id
x CoreExpr
e) | Id -> Bool
isId Id
x = CoreExpr -> JoinArity
go CoreExpr
e JoinArity -> JoinArity -> JoinArity
forall a. Num a => a -> a -> a
External instance of the constraint type Num JoinArity
+ JoinArity
1
| Bool
otherwise = CoreExpr -> JoinArity
go CoreExpr
e
go (Tick Tickish Id
t CoreExpr
e) | Bool -> Bool
not (Tickish Id -> Bool
forall id. Tickish id -> Bool
tickishIsCode Tickish Id
t) = CoreExpr -> JoinArity
go CoreExpr
e
go (Cast CoreExpr
e Coercion
co) = JoinArity -> Type -> JoinArity
trim_arity (CoreExpr -> JoinArity
go CoreExpr
e) (Coercion -> Type
coercionRKind Coercion
co)
go (App CoreExpr
e (Type Type
_)) = CoreExpr -> JoinArity
go CoreExpr
e
go (App CoreExpr
f CoreExpr
a) | CoreExpr -> Bool
exprIsTrivial CoreExpr
a = (CoreExpr -> JoinArity
go CoreExpr
f JoinArity -> JoinArity -> JoinArity
forall a. Num a => a -> a -> a
External instance of the constraint type Num JoinArity
- JoinArity
1) JoinArity -> JoinArity -> JoinArity
forall a. Ord a => a -> a -> a
External instance of the constraint type Ord JoinArity
`max` JoinArity
0
go CoreExpr
_ = JoinArity
0
trim_arity :: Arity -> Type -> Arity
trim_arity :: JoinArity -> Type -> JoinArity
trim_arity JoinArity
arity Type
ty = JoinArity
arity JoinArity -> JoinArity -> JoinArity
forall a. Ord a => a -> a -> a
External instance of the constraint type Ord JoinArity
`min` [OneShotInfo] -> JoinArity
forall (t :: * -> *) a. Foldable t => t a -> JoinArity
External instance of the constraint type Foldable []
length (Type -> [OneShotInfo]
typeArity Type
ty)
typeArity :: Type -> [OneShotInfo]
typeArity :: Type -> [OneShotInfo]
typeArity Type
ty
= RecTcChecker -> Type -> [OneShotInfo]
go RecTcChecker
initRecTc Type
ty
where
go :: RecTcChecker -> Type -> [OneShotInfo]
go RecTcChecker
rec_nts Type
ty
| Just (Id
_, Type
ty') <- Type -> Maybe (Id, Type)
splitForAllTy_maybe Type
ty
= RecTcChecker -> Type -> [OneShotInfo]
go RecTcChecker
rec_nts Type
ty'
| Just (Type
arg,Type
res) <- Type -> Maybe (Type, Type)
splitFunTy_maybe Type
ty
= Type -> OneShotInfo
typeOneShot Type
arg OneShotInfo -> [OneShotInfo] -> [OneShotInfo]
forall a. a -> [a] -> [a]
: RecTcChecker -> Type -> [OneShotInfo]
go RecTcChecker
rec_nts Type
res
| Just (TyCon
tc,[Type]
tys) <- HasDebugCallStack => Type -> Maybe (TyCon, [Type])
Type -> Maybe (TyCon, [Type])
External instance of the constraint type HasDebugCallStack
splitTyConApp_maybe Type
ty
, Just (Type
ty', Coercion
_) <- TyCon -> [Type] -> Maybe (Type, Coercion)
instNewTyCon_maybe TyCon
tc [Type]
tys
, Just RecTcChecker
rec_nts' <- RecTcChecker -> TyCon -> Maybe RecTcChecker
checkRecTc RecTcChecker
rec_nts TyCon
tc
= RecTcChecker -> Type -> [OneShotInfo]
go RecTcChecker
rec_nts' Type
ty'
| Bool
otherwise
= []
exprBotStrictness_maybe :: CoreExpr -> Maybe (Arity, StrictSig)
exprBotStrictness_maybe :: CoreExpr -> Maybe (JoinArity, StrictSig)
exprBotStrictness_maybe CoreExpr
e
= case ArityType -> Maybe JoinArity
getBotArity (ArityEnv -> CoreExpr -> ArityType
arityType ArityEnv
env CoreExpr
e) of
Maybe JoinArity
Nothing -> Maybe (JoinArity, StrictSig)
forall a. Maybe a
Nothing
Just JoinArity
ar -> (JoinArity, StrictSig) -> Maybe (JoinArity, StrictSig)
forall a. a -> Maybe a
Just (JoinArity
ar, JoinArity -> StrictSig
sig JoinArity
ar)
where
env :: ArityEnv
env = AE :: CheapFun -> Bool -> ArityEnv
AE { ae_ped_bot :: Bool
ae_ped_bot = Bool
True, ae_cheap_fn :: CheapFun
ae_cheap_fn = \ CoreExpr
_ Maybe Type
_ -> Bool
False }
sig :: JoinArity -> StrictSig
sig JoinArity
ar = [Demand] -> Divergence -> StrictSig
mkClosedStrictSig (JoinArity -> Demand -> [Demand]
forall a. JoinArity -> a -> [a]
replicate JoinArity
ar Demand
topDmd) Divergence
botDiv
data ArityType = ATop [OneShotInfo] | ABot Arity
instance Outputable ArityType where
ppr :: ArityType -> SDoc
ppr (ATop [OneShotInfo]
os) = String -> SDoc
text String
"ATop" SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
parens (JoinArity -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable JoinArity
ppr ([OneShotInfo] -> JoinArity
forall (t :: * -> *) a. Foldable t => t a -> JoinArity
External instance of the constraint type Foldable []
length [OneShotInfo]
os))
ppr (ABot JoinArity
n) = String -> SDoc
text String
"ABot" SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
parens (JoinArity -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable JoinArity
ppr JoinArity
n)
vanillaArityType :: ArityType
vanillaArityType :: ArityType
vanillaArityType = [OneShotInfo] -> ArityType
ATop []
exprEtaExpandArity :: DynFlags -> CoreExpr -> Arity
exprEtaExpandArity :: DynFlags -> CoreExpr -> JoinArity
exprEtaExpandArity DynFlags
dflags CoreExpr
e
= case (ArityEnv -> CoreExpr -> ArityType
arityType ArityEnv
env CoreExpr
e) of
ATop [OneShotInfo]
oss -> [OneShotInfo] -> JoinArity
forall (t :: * -> *) a. Foldable t => t a -> JoinArity
External instance of the constraint type Foldable []
length [OneShotInfo]
oss
ABot JoinArity
n -> JoinArity
n
where
env :: ArityEnv
env = AE :: CheapFun -> Bool -> ArityEnv
AE { ae_cheap_fn :: CheapFun
ae_cheap_fn = DynFlags -> CheapAppFun -> CheapFun
mk_cheap_fn DynFlags
dflags CheapAppFun
isCheapApp
, ae_ped_bot :: Bool
ae_ped_bot = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_PedanticBottoms DynFlags
dflags }
getBotArity :: ArityType -> Maybe Arity
getBotArity :: ArityType -> Maybe JoinArity
getBotArity (ABot JoinArity
n) = JoinArity -> Maybe JoinArity
forall a. a -> Maybe a
Just JoinArity
n
getBotArity ArityType
_ = Maybe JoinArity
forall a. Maybe a
Nothing
mk_cheap_fn :: DynFlags -> CheapAppFun -> CheapFun
mk_cheap_fn :: DynFlags -> CheapAppFun -> CheapFun
mk_cheap_fn DynFlags
dflags CheapAppFun
cheap_app
| Bool -> Bool
not (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_DictsCheap DynFlags
dflags)
= \CoreExpr
e Maybe Type
_ -> CheapAppFun -> CoreExpr -> Bool
exprIsCheapX CheapAppFun
cheap_app CoreExpr
e
| Bool
otherwise
= \CoreExpr
e Maybe Type
mb_ty -> CheapAppFun -> CoreExpr -> Bool
exprIsCheapX CheapAppFun
cheap_app CoreExpr
e
Bool -> Bool -> Bool
|| case Maybe Type
mb_ty of
Maybe Type
Nothing -> Bool
False
Just Type
ty -> Type -> Bool
isDictTy Type
ty
findRhsArity :: DynFlags -> Id -> CoreExpr -> Arity -> (Arity, Bool)
findRhsArity :: DynFlags -> Id -> CoreExpr -> JoinArity -> (JoinArity, Bool)
findRhsArity DynFlags
dflags Id
bndr CoreExpr
rhs JoinArity
old_arity
= (JoinArity, Bool) -> (JoinArity, Bool)
go (CheapAppFun -> (JoinArity, Bool)
get_arity CheapAppFun
init_cheap_app)
where
is_lam :: Bool
is_lam = CoreExpr -> Bool
has_lam CoreExpr
rhs
has_lam :: CoreExpr -> Bool
has_lam (Tick Tickish Id
_ CoreExpr
e) = CoreExpr -> Bool
has_lam CoreExpr
e
has_lam (Lam Id
b CoreExpr
e) = Id -> Bool
isId Id
b Bool -> Bool -> Bool
|| CoreExpr -> Bool
has_lam CoreExpr
e
has_lam CoreExpr
_ = Bool
False
init_cheap_app :: CheapAppFun
init_cheap_app :: CheapAppFun
init_cheap_app Id
fn JoinArity
n_val_args
| Id
fn Id -> Id -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Id
== Id
bndr = Bool
True
| Bool
otherwise = CheapAppFun
isCheapApp Id
fn JoinArity
n_val_args
go :: (Arity, Bool) -> (Arity, Bool)
go :: (JoinArity, Bool) -> (JoinArity, Bool)
go cur_info :: (JoinArity, Bool)
cur_info@(JoinArity
cur_arity, Bool
_)
| JoinArity
cur_arity JoinArity -> JoinArity -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord JoinArity
<= JoinArity
old_arity = (JoinArity, Bool)
cur_info
| JoinArity
new_arity JoinArity -> JoinArity -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq JoinArity
== JoinArity
cur_arity = (JoinArity, Bool)
cur_info
| Bool
otherwise = ASSERT( new_arity < cur_arity )
#if defined(DEBUG)
pprTrace "Exciting arity"
(vcat [ ppr bndr <+> ppr cur_arity <+> ppr new_arity
, ppr rhs])
#endif
(JoinArity, Bool) -> (JoinArity, Bool)
go (JoinArity, Bool)
new_info
where
new_info :: (JoinArity, Bool)
new_info@(JoinArity
new_arity, Bool
_) = CheapAppFun -> (JoinArity, Bool)
get_arity CheapAppFun
cheap_app
cheap_app :: CheapAppFun
cheap_app :: CheapAppFun
cheap_app Id
fn JoinArity
n_val_args
| Id
fn Id -> Id -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Id
== Id
bndr = JoinArity
n_val_args JoinArity -> JoinArity -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord JoinArity
< JoinArity
cur_arity
| Bool
otherwise = CheapAppFun
isCheapApp Id
fn JoinArity
n_val_args
get_arity :: CheapAppFun -> (Arity, Bool)
get_arity :: CheapAppFun -> (JoinArity, Bool)
get_arity CheapAppFun
cheap_app
= case (ArityEnv -> CoreExpr -> ArityType
arityType ArityEnv
env CoreExpr
rhs) of
ABot JoinArity
n -> (JoinArity
n, Bool
True)
ATop (OneShotInfo
os:[OneShotInfo]
oss) | OneShotInfo -> Bool
isOneShotInfo OneShotInfo
os Bool -> Bool -> Bool
|| Bool
is_lam
-> (JoinArity
1 JoinArity -> JoinArity -> JoinArity
forall a. Num a => a -> a -> a
External instance of the constraint type Num JoinArity
+ [OneShotInfo] -> JoinArity
forall (t :: * -> *) a. Foldable t => t a -> JoinArity
External instance of the constraint type Foldable []
length [OneShotInfo]
oss, Bool
False)
ATop [OneShotInfo]
_ -> (JoinArity
0, Bool
False)
where
env :: ArityEnv
env = AE :: CheapFun -> Bool -> ArityEnv
AE { ae_cheap_fn :: CheapFun
ae_cheap_fn = DynFlags -> CheapAppFun -> CheapFun
mk_cheap_fn DynFlags
dflags CheapAppFun
cheap_app
, ae_ped_bot :: Bool
ae_ped_bot = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_PedanticBottoms DynFlags
dflags }
arityLam :: Id -> ArityType -> ArityType
arityLam :: Id -> ArityType -> ArityType
arityLam Id
id (ATop [OneShotInfo]
as) = [OneShotInfo] -> ArityType
ATop (Id -> OneShotInfo
idStateHackOneShotInfo Id
id OneShotInfo -> [OneShotInfo] -> [OneShotInfo]
forall a. a -> [a] -> [a]
: [OneShotInfo]
as)
arityLam Id
_ (ABot JoinArity
n) = JoinArity -> ArityType
ABot (JoinArity
nJoinArity -> JoinArity -> JoinArity
forall a. Num a => a -> a -> a
External instance of the constraint type Num JoinArity
+JoinArity
1)
floatIn :: Bool -> ArityType -> ArityType
floatIn :: Bool -> ArityType -> ArityType
floatIn Bool
_ (ABot JoinArity
n) = JoinArity -> ArityType
ABot JoinArity
n
floatIn Bool
True (ATop [OneShotInfo]
as) = [OneShotInfo] -> ArityType
ATop [OneShotInfo]
as
floatIn Bool
False (ATop [OneShotInfo]
as) = [OneShotInfo] -> ArityType
ATop ((OneShotInfo -> Bool) -> [OneShotInfo] -> [OneShotInfo]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile OneShotInfo -> Bool
isOneShotInfo [OneShotInfo]
as)
arityApp :: ArityType -> Bool -> ArityType
arityApp :: ArityType -> Bool -> ArityType
arityApp (ABot JoinArity
0) Bool
_ = JoinArity -> ArityType
ABot JoinArity
0
arityApp (ABot JoinArity
n) Bool
_ = JoinArity -> ArityType
ABot (JoinArity
nJoinArity -> JoinArity -> JoinArity
forall a. Num a => a -> a -> a
External instance of the constraint type Num JoinArity
-JoinArity
1)
arityApp (ATop []) Bool
_ = [OneShotInfo] -> ArityType
ATop []
arityApp (ATop (OneShotInfo
_:[OneShotInfo]
as)) Bool
cheap = Bool -> ArityType -> ArityType
floatIn Bool
cheap ([OneShotInfo] -> ArityType
ATop [OneShotInfo]
as)
andArityType :: ArityType -> ArityType -> ArityType
andArityType :: ArityType -> ArityType -> ArityType
andArityType (ABot JoinArity
n1) (ABot JoinArity
n2) = JoinArity -> ArityType
ABot (JoinArity
n1 JoinArity -> JoinArity -> JoinArity
forall a. Ord a => a -> a -> a
External instance of the constraint type Ord JoinArity
`max` JoinArity
n2)
andArityType (ATop [OneShotInfo]
as) (ABot JoinArity
_) = [OneShotInfo] -> ArityType
ATop [OneShotInfo]
as
andArityType (ABot JoinArity
_) (ATop [OneShotInfo]
bs) = [OneShotInfo] -> ArityType
ATop [OneShotInfo]
bs
andArityType (ATop [OneShotInfo]
as) (ATop [OneShotInfo]
bs) = [OneShotInfo] -> ArityType
ATop ([OneShotInfo]
as [OneShotInfo] -> [OneShotInfo] -> [OneShotInfo]
`combine` [OneShotInfo]
bs)
where
combine :: [OneShotInfo] -> [OneShotInfo] -> [OneShotInfo]
combine (OneShotInfo
a:[OneShotInfo]
as) (OneShotInfo
b:[OneShotInfo]
bs) = (OneShotInfo
a OneShotInfo -> OneShotInfo -> OneShotInfo
`bestOneShot` OneShotInfo
b) OneShotInfo -> [OneShotInfo] -> [OneShotInfo]
forall a. a -> [a] -> [a]
: [OneShotInfo] -> [OneShotInfo] -> [OneShotInfo]
combine [OneShotInfo]
as [OneShotInfo]
bs
combine [] [OneShotInfo]
bs = (OneShotInfo -> Bool) -> [OneShotInfo] -> [OneShotInfo]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile OneShotInfo -> Bool
isOneShotInfo [OneShotInfo]
bs
combine [OneShotInfo]
as [] = (OneShotInfo -> Bool) -> [OneShotInfo] -> [OneShotInfo]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile OneShotInfo -> Bool
isOneShotInfo [OneShotInfo]
as
type CheapFun = CoreExpr -> Maybe Type -> Bool
data ArityEnv
= AE { ArityEnv -> CheapFun
ae_cheap_fn :: CheapFun
, ArityEnv -> Bool
ae_ped_bot :: Bool
}
arityType :: ArityEnv -> CoreExpr -> ArityType
arityType :: ArityEnv -> CoreExpr -> ArityType
arityType ArityEnv
env (Cast CoreExpr
e Coercion
co)
= case ArityEnv -> CoreExpr -> ArityType
arityType ArityEnv
env CoreExpr
e of
ATop [OneShotInfo]
os -> [OneShotInfo] -> ArityType
ATop (JoinArity -> [OneShotInfo] -> [OneShotInfo]
forall a. JoinArity -> [a] -> [a]
take JoinArity
co_arity [OneShotInfo]
os)
ABot JoinArity
n | JoinArity
co_arity JoinArity -> JoinArity -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord JoinArity
< JoinArity
n -> [OneShotInfo] -> ArityType
ATop (JoinArity -> OneShotInfo -> [OneShotInfo]
forall a. JoinArity -> a -> [a]
replicate JoinArity
co_arity OneShotInfo
noOneShotInfo)
| Bool
otherwise -> JoinArity -> ArityType
ABot JoinArity
n
where
co_arity :: JoinArity
co_arity = [OneShotInfo] -> JoinArity
forall (t :: * -> *) a. Foldable t => t a -> JoinArity
External instance of the constraint type Foldable []
length (Type -> [OneShotInfo]
typeArity (Coercion -> Type
coercionRKind Coercion
co))
arityType ArityEnv
_ (Var Id
v)
| StrictSig
strict_sig <- Id -> StrictSig
idStrictness Id
v
, Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ StrictSig -> Bool
isTopSig StrictSig
strict_sig
, ([Demand]
ds, Divergence
res) <- StrictSig -> ([Demand], Divergence)
splitStrictSig StrictSig
strict_sig
, let arity :: JoinArity
arity = [Demand] -> JoinArity
forall (t :: * -> *) a. Foldable t => t a -> JoinArity
External instance of the constraint type Foldable []
length [Demand]
ds
= if Divergence -> Bool
isDeadEndDiv Divergence
res then JoinArity -> ArityType
ABot JoinArity
arity
else [OneShotInfo] -> ArityType
ATop (JoinArity -> [OneShotInfo] -> [OneShotInfo]
forall a. JoinArity -> [a] -> [a]
take JoinArity
arity [OneShotInfo]
one_shots)
| Bool
otherwise
= [OneShotInfo] -> ArityType
ATop (JoinArity -> [OneShotInfo] -> [OneShotInfo]
forall a. JoinArity -> [a] -> [a]
take (Id -> JoinArity
idArity Id
v) [OneShotInfo]
one_shots)
where
one_shots :: [OneShotInfo]
one_shots :: [OneShotInfo]
one_shots = Type -> [OneShotInfo]
typeArity (Id -> Type
idType Id
v)
arityType ArityEnv
env (Lam Id
x CoreExpr
e)
| Id -> Bool
isId Id
x = Id -> ArityType -> ArityType
arityLam Id
x (ArityEnv -> CoreExpr -> ArityType
arityType ArityEnv
env CoreExpr
e)
| Bool
otherwise = ArityEnv -> CoreExpr -> ArityType
arityType ArityEnv
env CoreExpr
e
arityType ArityEnv
env (App CoreExpr
fun (Type Type
_))
= ArityEnv -> CoreExpr -> ArityType
arityType ArityEnv
env CoreExpr
fun
arityType ArityEnv
env (App CoreExpr
fun CoreExpr
arg )
= ArityType -> Bool -> ArityType
arityApp (ArityEnv -> CoreExpr -> ArityType
arityType ArityEnv
env CoreExpr
fun) (ArityEnv -> CheapFun
ae_cheap_fn ArityEnv
env CoreExpr
arg Maybe Type
forall a. Maybe a
Nothing)
arityType ArityEnv
env (Case CoreExpr
scrut Id
_ Type
_ [Alt Id]
alts)
| CoreExpr -> Bool
exprIsDeadEnd CoreExpr
scrut Bool -> Bool -> Bool
|| [Alt Id] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null [Alt Id]
alts
= JoinArity -> ArityType
ABot JoinArity
0
| Bool
otherwise
= case ArityType
alts_type of
ABot JoinArity
n | JoinArity
nJoinArity -> JoinArity -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord JoinArity
>JoinArity
0 -> [OneShotInfo] -> ArityType
ATop []
| Bool
otherwise -> JoinArity -> ArityType
ABot JoinArity
0
ATop [OneShotInfo]
as | Bool -> Bool
not (ArityEnv -> Bool
ae_ped_bot ArityEnv
env)
, ArityEnv -> CheapFun
ae_cheap_fn ArityEnv
env CoreExpr
scrut Maybe Type
forall a. Maybe a
Nothing -> [OneShotInfo] -> ArityType
ATop [OneShotInfo]
as
| CoreExpr -> Bool
exprOkForSpeculation CoreExpr
scrut -> [OneShotInfo] -> ArityType
ATop [OneShotInfo]
as
| Bool
otherwise -> [OneShotInfo] -> ArityType
ATop ((OneShotInfo -> Bool) -> [OneShotInfo] -> [OneShotInfo]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile OneShotInfo -> Bool
isOneShotInfo [OneShotInfo]
as)
where
alts_type :: ArityType
alts_type = (ArityType -> ArityType -> ArityType) -> [ArityType] -> ArityType
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
External instance of the constraint type Foldable []
foldr1 ArityType -> ArityType -> ArityType
andArityType [ArityEnv -> CoreExpr -> ArityType
arityType ArityEnv
env CoreExpr
rhs | (AltCon
_,[Id]
_,CoreExpr
rhs) <- [Alt Id]
alts]
arityType ArityEnv
env (Let Bind Id
b CoreExpr
e)
= Bool -> ArityType -> ArityType
floatIn (Bind Id -> Bool
cheap_bind Bind Id
b) (ArityEnv -> CoreExpr -> ArityType
arityType ArityEnv
env CoreExpr
e)
where
cheap_bind :: Bind Id -> Bool
cheap_bind (NonRec Id
b CoreExpr
e) = (Id, CoreExpr) -> Bool
is_cheap (Id
b,CoreExpr
e)
cheap_bind (Rec [(Id, CoreExpr)]
prs) = ((Id, CoreExpr) -> Bool) -> [(Id, CoreExpr)] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
External instance of the constraint type Foldable []
all (Id, CoreExpr) -> Bool
is_cheap [(Id, CoreExpr)]
prs
is_cheap :: (Id, CoreExpr) -> Bool
is_cheap (Id
b,CoreExpr
e) = ArityEnv -> CheapFun
ae_cheap_fn ArityEnv
env CoreExpr
e (Type -> Maybe Type
forall a. a -> Maybe a
Just (Id -> Type
idType Id
b))
arityType ArityEnv
env (Tick Tickish Id
t CoreExpr
e)
| Bool -> Bool
not (Tickish Id -> Bool
forall id. Tickish id -> Bool
tickishIsCode Tickish Id
t) = ArityEnv -> CoreExpr -> ArityType
arityType ArityEnv
env CoreExpr
e
arityType ArityEnv
_ CoreExpr
_ = ArityType
vanillaArityType
etaExpand :: Arity
-> CoreExpr
-> CoreExpr
etaExpand :: JoinArity -> CoreExpr -> CoreExpr
etaExpand JoinArity
n CoreExpr
orig_expr
= JoinArity -> CoreExpr -> CoreExpr
go JoinArity
n CoreExpr
orig_expr
where
go :: JoinArity -> CoreExpr -> CoreExpr
go JoinArity
0 CoreExpr
expr = CoreExpr
expr
go JoinArity
n (Lam Id
v CoreExpr
body) | Id -> Bool
isTyVar Id
v = Id -> CoreExpr -> CoreExpr
forall b. b -> Expr b -> Expr b
Lam Id
v (JoinArity -> CoreExpr -> CoreExpr
go JoinArity
n CoreExpr
body)
| Bool
otherwise = Id -> CoreExpr -> CoreExpr
forall b. b -> Expr b -> Expr b
Lam Id
v (JoinArity -> CoreExpr -> CoreExpr
go (JoinArity
nJoinArity -> JoinArity -> JoinArity
forall a. Num a => a -> a -> a
External instance of the constraint type Num JoinArity
-JoinArity
1) CoreExpr
body)
go JoinArity
n (Cast CoreExpr
expr Coercion
co) = CoreExpr -> Coercion -> CoreExpr
forall b. Expr b -> Coercion -> Expr b
Cast (JoinArity -> CoreExpr -> CoreExpr
go JoinArity
n CoreExpr
expr) Coercion
co
go JoinArity
n CoreExpr
expr
=
CoreExpr -> CoreExpr
retick (CoreExpr -> CoreExpr) -> CoreExpr -> CoreExpr
forall a b. (a -> b) -> a -> b
$ [EtaInfo] -> CoreExpr -> CoreExpr
etaInfoAbs [EtaInfo]
etas (Subst -> CoreExpr -> [EtaInfo] -> CoreExpr
etaInfoApp Subst
subst' CoreExpr
sexpr [EtaInfo]
etas)
where
in_scope :: InScopeSet
in_scope = VarSet -> InScopeSet
mkInScopeSet (CoreExpr -> VarSet
exprFreeVars CoreExpr
expr)
(InScopeSet
in_scope', [EtaInfo]
etas) = JoinArity -> SDoc -> InScopeSet -> Type -> (InScopeSet, [EtaInfo])
mkEtaWW JoinArity
n (CoreExpr -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall b. OutputableBndr b => Outputable (Expr b)
External instance of the constraint type OutputableBndr Id
ppr CoreExpr
orig_expr) InScopeSet
in_scope (CoreExpr -> Type
exprType CoreExpr
expr)
subst' :: Subst
subst' = InScopeSet -> Subst
mkEmptySubst InScopeSet
in_scope'
(CoreExpr
expr', [CoreExpr]
args) = CoreExpr -> (CoreExpr, [CoreExpr])
forall b. Expr b -> (Expr b, [Expr b])
collectArgs CoreExpr
expr
([Tickish Id]
ticks, CoreExpr
expr'') = (Tickish Id -> Bool) -> CoreExpr -> ([Tickish Id], CoreExpr)
forall b. (Tickish Id -> Bool) -> Expr b -> ([Tickish Id], Expr b)
stripTicksTop Tickish Id -> Bool
forall id. Tickish id -> Bool
tickishFloatable CoreExpr
expr'
sexpr :: CoreExpr
sexpr = (CoreExpr -> CoreExpr -> CoreExpr)
-> CoreExpr -> [CoreExpr] -> CoreExpr
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldl' CoreExpr -> CoreExpr -> CoreExpr
forall b. Expr b -> Expr b -> Expr b
App CoreExpr
expr'' [CoreExpr]
args
retick :: CoreExpr -> CoreExpr
retick CoreExpr
expr = (Tickish Id -> CoreExpr -> CoreExpr)
-> CoreExpr -> [Tickish Id] -> CoreExpr
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldr Tickish Id -> CoreExpr -> CoreExpr
mkTick CoreExpr
expr [Tickish Id]
ticks
data EtaInfo = EtaVar Var
| EtaCo Coercion
instance Outputable EtaInfo where
ppr :: EtaInfo -> SDoc
ppr (EtaVar Id
v) = String -> SDoc
text String
"EtaVar" SDoc -> SDoc -> SDoc
<+> Id -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Id
ppr Id
v
ppr (EtaCo Coercion
co) = String -> SDoc
text String
"EtaCo" SDoc -> SDoc -> SDoc
<+> Coercion -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Coercion
ppr Coercion
co
pushCoercion :: Coercion -> [EtaInfo] -> [EtaInfo]
pushCoercion :: Coercion -> [EtaInfo] -> [EtaInfo]
pushCoercion Coercion
co1 (EtaCo Coercion
co2 : [EtaInfo]
eis)
| Coercion -> Bool
isReflCo Coercion
co = [EtaInfo]
eis
| Bool
otherwise = Coercion -> EtaInfo
EtaCo Coercion
co EtaInfo -> [EtaInfo] -> [EtaInfo]
forall a. a -> [a] -> [a]
: [EtaInfo]
eis
where
co :: Coercion
co = Coercion
co1 Coercion -> Coercion -> Coercion
`mkTransCo` Coercion
co2
pushCoercion Coercion
co [EtaInfo]
eis = Coercion -> EtaInfo
EtaCo Coercion
co EtaInfo -> [EtaInfo] -> [EtaInfo]
forall a. a -> [a] -> [a]
: [EtaInfo]
eis
etaInfoAbs :: [EtaInfo] -> CoreExpr -> CoreExpr
etaInfoAbs :: [EtaInfo] -> CoreExpr -> CoreExpr
etaInfoAbs [] CoreExpr
expr = CoreExpr
expr
etaInfoAbs (EtaVar Id
v : [EtaInfo]
eis) CoreExpr
expr = Id -> CoreExpr -> CoreExpr
forall b. b -> Expr b -> Expr b
Lam Id
v ([EtaInfo] -> CoreExpr -> CoreExpr
etaInfoAbs [EtaInfo]
eis CoreExpr
expr)
etaInfoAbs (EtaCo Coercion
co : [EtaInfo]
eis) CoreExpr
expr = CoreExpr -> Coercion -> CoreExpr
forall b. Expr b -> Coercion -> Expr b
Cast ([EtaInfo] -> CoreExpr -> CoreExpr
etaInfoAbs [EtaInfo]
eis CoreExpr
expr) (Coercion -> Coercion
mkSymCo Coercion
co)
etaInfoApp :: Subst -> CoreExpr -> [EtaInfo] -> CoreExpr
etaInfoApp :: Subst -> CoreExpr -> [EtaInfo] -> CoreExpr
etaInfoApp Subst
subst (Lam Id
v1 CoreExpr
e) (EtaVar Id
v2 : [EtaInfo]
eis)
= Subst -> CoreExpr -> [EtaInfo] -> CoreExpr
etaInfoApp (Subst -> Id -> Id -> Subst
GHC.Core.Subst.extendSubstWithVar Subst
subst Id
v1 Id
v2) CoreExpr
e [EtaInfo]
eis
etaInfoApp Subst
subst (Cast CoreExpr
e Coercion
co1) [EtaInfo]
eis
= Subst -> CoreExpr -> [EtaInfo] -> CoreExpr
etaInfoApp Subst
subst CoreExpr
e (Coercion -> [EtaInfo] -> [EtaInfo]
pushCoercion Coercion
co' [EtaInfo]
eis)
where
co' :: Coercion
co' = HasCallStack => Subst -> Coercion -> Coercion
Subst -> Coercion -> Coercion
GHC.Core.Subst.substCo Subst
subst Coercion
co1
etaInfoApp Subst
subst (Case CoreExpr
e Id
b Type
ty [Alt Id]
alts) [EtaInfo]
eis
= CoreExpr -> Id -> Type -> [Alt Id] -> CoreExpr
forall b. Expr b -> b -> Type -> [Alt b] -> Expr b
Case (Subst -> CoreExpr -> CoreExpr
subst_expr Subst
subst CoreExpr
e) Id
b1 Type
ty' [Alt Id]
alts'
where
(Subst
subst1, Id
b1) = Subst -> Id -> (Subst, Id)
substBndr Subst
subst Id
b
alts' :: [Alt Id]
alts' = (Alt Id -> Alt Id) -> [Alt Id] -> [Alt Id]
forall a b. (a -> b) -> [a] -> [b]
map Alt Id -> Alt Id
forall {a}. (a, [Id], CoreExpr) -> (a, [Id], CoreExpr)
subst_alt [Alt Id]
alts
ty' :: Type
ty' = Type -> [EtaInfo] -> Type
etaInfoAppTy (Subst -> Type -> Type
GHC.Core.Subst.substTy Subst
subst Type
ty) [EtaInfo]
eis
subst_alt :: (a, [Id], CoreExpr) -> (a, [Id], CoreExpr)
subst_alt (a
con, [Id]
bs, CoreExpr
rhs) = (a
con, [Id]
bs', Subst -> CoreExpr -> [EtaInfo] -> CoreExpr
etaInfoApp Subst
subst2 CoreExpr
rhs [EtaInfo]
eis)
where
(Subst
subst2,[Id]
bs') = Subst -> [Id] -> (Subst, [Id])
substBndrs Subst
subst1 [Id]
bs
etaInfoApp Subst
subst (Let Bind Id
b CoreExpr
e) [EtaInfo]
eis
| Bool -> Bool
not (Bind Id -> Bool
isJoinBind Bind Id
b)
= Bind Id -> CoreExpr -> CoreExpr
forall b. Bind b -> Expr b -> Expr b
Let Bind Id
b' (Subst -> CoreExpr -> [EtaInfo] -> CoreExpr
etaInfoApp Subst
subst' CoreExpr
e [EtaInfo]
eis)
where
(Subst
subst', Bind Id
b') = Subst -> Bind Id -> (Subst, Bind Id)
substBindSC Subst
subst Bind Id
b
etaInfoApp Subst
subst (Tick Tickish Id
t CoreExpr
e) [EtaInfo]
eis
= Tickish Id -> CoreExpr -> CoreExpr
forall b. Tickish Id -> Expr b -> Expr b
Tick (Subst -> Tickish Id -> Tickish Id
substTickish Subst
subst Tickish Id
t) (Subst -> CoreExpr -> [EtaInfo] -> CoreExpr
etaInfoApp Subst
subst CoreExpr
e [EtaInfo]
eis)
etaInfoApp Subst
subst CoreExpr
expr [EtaInfo]
_
| (Var Id
fun, [CoreExpr]
_) <- CoreExpr -> (CoreExpr, [CoreExpr])
forall b. Expr b -> (Expr b, [Expr b])
collectArgs CoreExpr
expr
, Var Id
fun' <- SDoc -> Subst -> Id -> CoreExpr
lookupIdSubst (String -> SDoc
text String
"etaInfoApp" SDoc -> SDoc -> SDoc
<+> Id -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Id
ppr Id
fun) Subst
subst Id
fun
, Id -> Bool
isJoinId Id
fun'
= Subst -> CoreExpr -> CoreExpr
subst_expr Subst
subst CoreExpr
expr
etaInfoApp Subst
subst CoreExpr
e [EtaInfo]
eis
= CoreExpr -> [EtaInfo] -> CoreExpr
forall {b}. Expr b -> [EtaInfo] -> Expr b
go (Subst -> CoreExpr -> CoreExpr
subst_expr Subst
subst CoreExpr
e) [EtaInfo]
eis
where
go :: Expr b -> [EtaInfo] -> Expr b
go Expr b
e [] = Expr b
e
go Expr b
e (EtaVar Id
v : [EtaInfo]
eis) = Expr b -> [EtaInfo] -> Expr b
go (Expr b -> Expr b -> Expr b
forall b. Expr b -> Expr b -> Expr b
App Expr b
e (Id -> Expr b
forall b. Id -> Expr b
varToCoreExpr Id
v)) [EtaInfo]
eis
go Expr b
e (EtaCo Coercion
co : [EtaInfo]
eis) = Expr b -> [EtaInfo] -> Expr b
go (Expr b -> Coercion -> Expr b
forall b. Expr b -> Coercion -> Expr b
Cast Expr b
e Coercion
co) [EtaInfo]
eis
etaInfoAppTy :: Type -> [EtaInfo] -> Type
etaInfoAppTy :: Type -> [EtaInfo] -> Type
etaInfoAppTy Type
ty [] = Type
ty
etaInfoAppTy Type
ty (EtaVar Id
v : [EtaInfo]
eis) = Type -> [EtaInfo] -> Type
etaInfoAppTy (Type -> CoreExpr -> Type
applyTypeToArg Type
ty (Id -> CoreExpr
forall b. Id -> Expr b
varToCoreExpr Id
v)) [EtaInfo]
eis
etaInfoAppTy Type
_ (EtaCo Coercion
co : [EtaInfo]
eis) = Type -> [EtaInfo] -> Type
etaInfoAppTy (Coercion -> Type
coercionRKind Coercion
co) [EtaInfo]
eis
mkEtaWW
:: Arity
-> SDoc
-> InScopeSet
-> Type
-> (InScopeSet, [EtaInfo])
mkEtaWW :: JoinArity -> SDoc -> InScopeSet -> Type -> (InScopeSet, [EtaInfo])
mkEtaWW JoinArity
orig_n SDoc
ppr_orig_expr InScopeSet
in_scope Type
orig_ty
= JoinArity
-> TCvSubst -> Type -> [EtaInfo] -> (InScopeSet, [EtaInfo])
go JoinArity
orig_n TCvSubst
empty_subst Type
orig_ty []
where
empty_subst :: TCvSubst
empty_subst = InScopeSet -> TCvSubst
mkEmptyTCvSubst InScopeSet
in_scope
go :: Arity
-> TCvSubst -> Type
-> [EtaInfo]
-> (InScopeSet, [EtaInfo])
go :: JoinArity
-> TCvSubst -> Type -> [EtaInfo] -> (InScopeSet, [EtaInfo])
go JoinArity
n TCvSubst
subst Type
ty [EtaInfo]
eis
| JoinArity
n JoinArity -> JoinArity -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq JoinArity
== JoinArity
0
= (TCvSubst -> InScopeSet
getTCvInScope TCvSubst
subst, [EtaInfo] -> [EtaInfo]
forall a. [a] -> [a]
reverse [EtaInfo]
eis)
| Just (Id
tcv,Type
ty') <- Type -> Maybe (Id, Type)
splitForAllTy_maybe Type
ty
, let (TCvSubst
subst', Id
tcv') = HasCallStack => TCvSubst -> Id -> (TCvSubst, Id)
TCvSubst -> Id -> (TCvSubst, Id)
Type.substVarBndr TCvSubst
subst Id
tcv
= let ((TCvSubst
n_subst, Id
n_tcv), JoinArity
n_n)
| Id -> Bool
isTyVar Id
tcv = ((TCvSubst
subst', Id
tcv'), JoinArity
n)
| Bool
otherwise = (JoinArity -> TCvSubst -> Type -> (TCvSubst, Id)
freshEtaId JoinArity
n TCvSubst
subst' (Id -> Type
varType Id
tcv'), JoinArity
nJoinArity -> JoinArity -> JoinArity
forall a. Num a => a -> a -> a
External instance of the constraint type Num JoinArity
-JoinArity
1)
in JoinArity
-> TCvSubst -> Type -> [EtaInfo] -> (InScopeSet, [EtaInfo])
go JoinArity
n_n TCvSubst
n_subst Type
ty' (Id -> EtaInfo
EtaVar Id
n_tcv EtaInfo -> [EtaInfo] -> [EtaInfo]
forall a. a -> [a] -> [a]
: [EtaInfo]
eis)
| Just (Type
arg_ty, Type
res_ty) <- Type -> Maybe (Type, Type)
splitFunTy_maybe Type
ty
, Bool -> Bool
not (Type -> Bool
isTypeLevPoly Type
arg_ty)
, let (TCvSubst
subst', Id
eta_id') = JoinArity -> TCvSubst -> Type -> (TCvSubst, Id)
freshEtaId JoinArity
n TCvSubst
subst Type
arg_ty
= JoinArity
-> TCvSubst -> Type -> [EtaInfo] -> (InScopeSet, [EtaInfo])
go (JoinArity
nJoinArity -> JoinArity -> JoinArity
forall a. Num a => a -> a -> a
External instance of the constraint type Num JoinArity
-JoinArity
1) TCvSubst
subst' Type
res_ty (Id -> EtaInfo
EtaVar Id
eta_id' EtaInfo -> [EtaInfo] -> [EtaInfo]
forall a. a -> [a] -> [a]
: [EtaInfo]
eis)
| Just (Coercion
co, Type
ty') <- Type -> Maybe (Coercion, Type)
topNormaliseNewType_maybe Type
ty
, let co' :: Coercion
co' = HasCallStack => TCvSubst -> Coercion -> Coercion
TCvSubst -> Coercion -> Coercion
Coercion.substCo TCvSubst
subst Coercion
co
= JoinArity
-> TCvSubst -> Type -> [EtaInfo] -> (InScopeSet, [EtaInfo])
go JoinArity
n TCvSubst
subst Type
ty' (Coercion -> [EtaInfo] -> [EtaInfo]
pushCoercion Coercion
co' [EtaInfo]
eis)
| Bool
otherwise
= WARN( True, (ppr orig_n <+> ppr orig_ty) $$ ppr_orig_expr )
(TCvSubst -> InScopeSet
getTCvInScope TCvSubst
subst, [EtaInfo] -> [EtaInfo]
forall a. [a] -> [a]
reverse [EtaInfo]
eis)
subst_expr :: Subst -> CoreExpr -> CoreExpr
subst_expr :: Subst -> CoreExpr -> CoreExpr
subst_expr = SDoc -> Subst -> CoreExpr -> CoreExpr
substExpr (String -> SDoc
text String
"GHC.Core.Opt.Arity:substExpr")
etaExpandToJoinPoint :: JoinArity -> CoreExpr -> ([CoreBndr], CoreExpr)
etaExpandToJoinPoint :: JoinArity -> CoreExpr -> ([Id], CoreExpr)
etaExpandToJoinPoint JoinArity
join_arity CoreExpr
expr
= JoinArity -> [Id] -> CoreExpr -> ([Id], CoreExpr)
go JoinArity
join_arity [] CoreExpr
expr
where
go :: JoinArity -> [Id] -> CoreExpr -> ([Id], CoreExpr)
go JoinArity
0 [Id]
rev_bs CoreExpr
e = ([Id] -> [Id]
forall a. [a] -> [a]
reverse [Id]
rev_bs, CoreExpr
e)
go JoinArity
n [Id]
rev_bs (Lam Id
b CoreExpr
e) = JoinArity -> [Id] -> CoreExpr -> ([Id], CoreExpr)
go (JoinArity
nJoinArity -> JoinArity -> JoinArity
forall a. Num a => a -> a -> a
External instance of the constraint type Num JoinArity
-JoinArity
1) (Id
b Id -> [Id] -> [Id]
forall a. a -> [a] -> [a]
: [Id]
rev_bs) CoreExpr
e
go JoinArity
n [Id]
rev_bs CoreExpr
e = case JoinArity -> CoreExpr -> ([Id], CoreExpr)
etaBodyForJoinPoint JoinArity
n CoreExpr
e of
([Id]
bs, CoreExpr
e') -> ([Id] -> [Id]
forall a. [a] -> [a]
reverse [Id]
rev_bs [Id] -> [Id] -> [Id]
forall a. [a] -> [a] -> [a]
++ [Id]
bs, CoreExpr
e')
etaExpandToJoinPointRule :: JoinArity -> CoreRule -> CoreRule
etaExpandToJoinPointRule :: JoinArity -> CoreRule -> CoreRule
etaExpandToJoinPointRule JoinArity
_ rule :: CoreRule
rule@(BuiltinRule {})
= WARN(True, (sep [text "Can't eta-expand built-in rule:", ppr rule]))
CoreRule
rule
etaExpandToJoinPointRule JoinArity
join_arity rule :: CoreRule
rule@(Rule { ru_bndrs :: CoreRule -> [Id]
ru_bndrs = [Id]
bndrs, ru_rhs :: CoreRule -> CoreExpr
ru_rhs = CoreExpr
rhs
, ru_args :: CoreRule -> [CoreExpr]
ru_args = [CoreExpr]
args })
| JoinArity
need_args JoinArity -> JoinArity -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq JoinArity
== JoinArity
0
= CoreRule
rule
| JoinArity
need_args JoinArity -> JoinArity -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord JoinArity
< JoinArity
0
= String -> SDoc -> CoreRule
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"etaExpandToJoinPointRule" (JoinArity -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable JoinArity
ppr JoinArity
join_arity SDoc -> SDoc -> SDoc
$$ CoreRule -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable CoreRule
ppr CoreRule
rule)
| Bool
otherwise
= CoreRule
rule { ru_bndrs :: [Id]
ru_bndrs = [Id]
bndrs [Id] -> [Id] -> [Id]
forall a. [a] -> [a] -> [a]
++ [Id]
new_bndrs, ru_args :: [CoreExpr]
ru_args = [CoreExpr]
args [CoreExpr] -> [CoreExpr] -> [CoreExpr]
forall a. [a] -> [a] -> [a]
++ [CoreExpr]
forall {b}. [Expr b]
new_args
, ru_rhs :: CoreExpr
ru_rhs = CoreExpr
new_rhs }
where
need_args :: JoinArity
need_args = JoinArity
join_arity JoinArity -> JoinArity -> JoinArity
forall a. Num a => a -> a -> a
External instance of the constraint type Num JoinArity
- [CoreExpr] -> JoinArity
forall (t :: * -> *) a. Foldable t => t a -> JoinArity
External instance of the constraint type Foldable []
length [CoreExpr]
args
([Id]
new_bndrs, CoreExpr
new_rhs) = JoinArity -> CoreExpr -> ([Id], CoreExpr)
etaBodyForJoinPoint JoinArity
need_args CoreExpr
rhs
new_args :: [Expr b]
new_args = [Id] -> [Expr b]
forall b. [Id] -> [Expr b]
varsToCoreExprs [Id]
new_bndrs
etaBodyForJoinPoint :: Int -> CoreExpr -> ([CoreBndr], CoreExpr)
etaBodyForJoinPoint :: JoinArity -> CoreExpr -> ([Id], CoreExpr)
etaBodyForJoinPoint JoinArity
need_args CoreExpr
body
= JoinArity
-> Type -> TCvSubst -> [Id] -> CoreExpr -> ([Id], CoreExpr)
forall {b}.
JoinArity -> Type -> TCvSubst -> [Id] -> Expr b -> ([Id], Expr b)
go JoinArity
need_args (CoreExpr -> Type
exprType CoreExpr
body) (CoreExpr -> TCvSubst
init_subst CoreExpr
body) [] CoreExpr
body
where
go :: JoinArity -> Type -> TCvSubst -> [Id] -> Expr b -> ([Id], Expr b)
go JoinArity
0 Type
_ TCvSubst
_ [Id]
rev_bs Expr b
e
= ([Id] -> [Id]
forall a. [a] -> [a]
reverse [Id]
rev_bs, Expr b
e)
go JoinArity
n Type
ty TCvSubst
subst [Id]
rev_bs Expr b
e
| Just (Id
tv, Type
res_ty) <- Type -> Maybe (Id, Type)
splitForAllTy_maybe Type
ty
, let (TCvSubst
subst', Id
tv') = HasCallStack => TCvSubst -> Id -> (TCvSubst, Id)
TCvSubst -> Id -> (TCvSubst, Id)
Type.substVarBndr TCvSubst
subst Id
tv
= JoinArity -> Type -> TCvSubst -> [Id] -> Expr b -> ([Id], Expr b)
go (JoinArity
nJoinArity -> JoinArity -> JoinArity
forall a. Num a => a -> a -> a
External instance of the constraint type Num JoinArity
-JoinArity
1) Type
res_ty TCvSubst
subst' (Id
tv' Id -> [Id] -> [Id]
forall a. a -> [a] -> [a]
: [Id]
rev_bs) (Expr b
e Expr b -> Expr b -> Expr b
forall b. Expr b -> Expr b -> Expr b
`App` Id -> Expr b
forall b. Id -> Expr b
varToCoreExpr Id
tv')
| Just (Type
arg_ty, Type
res_ty) <- Type -> Maybe (Type, Type)
splitFunTy_maybe Type
ty
, let (TCvSubst
subst', Id
b) = JoinArity -> TCvSubst -> Type -> (TCvSubst, Id)
freshEtaId JoinArity
n TCvSubst
subst Type
arg_ty
= JoinArity -> Type -> TCvSubst -> [Id] -> Expr b -> ([Id], Expr b)
go (JoinArity
nJoinArity -> JoinArity -> JoinArity
forall a. Num a => a -> a -> a
External instance of the constraint type Num JoinArity
-JoinArity
1) Type
res_ty TCvSubst
subst' (Id
b Id -> [Id] -> [Id]
forall a. a -> [a] -> [a]
: [Id]
rev_bs) (Expr b
e Expr b -> Expr b -> Expr b
forall b. Expr b -> Expr b -> Expr b
`App` Id -> Expr b
forall b. Id -> Expr b
Var Id
b)
| Bool
otherwise
= String -> SDoc -> ([Id], Expr b)
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"etaBodyForJoinPoint" (SDoc -> ([Id], Expr b)) -> SDoc -> ([Id], Expr b)
forall a b. (a -> b) -> a -> b
$ JoinArity -> SDoc
int JoinArity
need_args SDoc -> SDoc -> SDoc
$$
CoreExpr -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall b. OutputableBndr b => Outputable (Expr b)
External instance of the constraint type OutputableBndr Id
ppr CoreExpr
body SDoc -> SDoc -> SDoc
$$ Type -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Type
ppr (CoreExpr -> Type
exprType CoreExpr
body)
init_subst :: CoreExpr -> TCvSubst
init_subst CoreExpr
e = InScopeSet -> TCvSubst
mkEmptyTCvSubst (VarSet -> InScopeSet
mkInScopeSet (CoreExpr -> VarSet
exprFreeVars CoreExpr
e))
freshEtaId :: Int -> TCvSubst -> Type -> (TCvSubst, Id)
freshEtaId :: JoinArity -> TCvSubst -> Type -> (TCvSubst, Id)
freshEtaId JoinArity
n TCvSubst
subst Type
ty
= (TCvSubst
subst', Id
eta_id')
where
ty' :: Type
ty' = TCvSubst -> Type -> Type
Type.substTyUnchecked TCvSubst
subst Type
ty
eta_id' :: Id
eta_id' = InScopeSet -> Id -> Id
uniqAway (TCvSubst -> InScopeSet
getTCvInScope TCvSubst
subst) (Id -> Id) -> Id -> Id
forall a b. (a -> b) -> a -> b
$
FastString -> Unique -> Type -> Id
mkSysLocalOrCoVar (String -> FastString
fsLit String
"eta") (JoinArity -> Unique
mkBuiltinUnique JoinArity
n) Type
ty'
subst' :: TCvSubst
subst' = TCvSubst -> Id -> TCvSubst
extendTCvInScope TCvSubst
subst Id
eta_id'