module Language.PureScript.CoreImp.Optimizer.MagicDo (magicDoEffect, magicDoEff, magicDoST, inlineST) where
import Prelude.Compat
import Protolude (ordNub)
import Data.Maybe (fromJust, isJust)
import Data.Text (Text)
import Language.PureScript.CoreImp.AST
import Language.PureScript.CoreImp.Optimizer.Common
import Language.PureScript.PSString (mkString)
import qualified Language.PureScript.Constants as C
magicDoEff :: AST -> AST
magicDoEff = magicDo C.eff C.effDictionaries
magicDoEffect :: AST -> AST
magicDoEffect = magicDo C.effect C.effectDictionaries
magicDoST :: AST -> AST
magicDoST = magicDo C.st C.stDictionaries
magicDo :: Text -> C.EffectDictionaries -> AST -> AST
magicDo effectModule C.EffectDictionaries{..} = everywhereTopDown convert
where
fnName = "__do"
convert :: AST -> AST
convert (App _ (App _ pure' [val]) []) | isPure pure' = val
convert (App _ (App _ bind [m]) [Function s1 Nothing [] (Block s2 js)]) | isDiscard bind =
Function s1 (Just fnName) [] $ Block s2 (App s2 m [] : map applyReturns js )
convert (App _ (App _ bind [m]) [Function s1 Nothing [arg] (Block s2 js)]) | isBind bind =
Function s1 (Just fnName) [] $ Block s2 (VariableIntroduction s2 arg (Just (App s2 m [])) : map applyReturns js)
convert (App s1 (App _ f [arg]) []) | isEffFunc edUntil f =
App s1 (Function s1 Nothing [] (Block s1 [ While s1 (Unary s1 Not (App s1 arg [])) (Block s1 []), Return s1 $ ObjectLiteral s1 []])) []
convert (App _ (App _ (App s1 f [arg1]) [arg2]) []) | isEffFunc edWhile f =
App s1 (Function s1 Nothing [] (Block s1 [ While s1 (App s1 arg1 []) (Block s1 [ App s1 arg2 [] ]), Return s1 $ ObjectLiteral s1 []])) []
convert (Return _ (App _ (Function _ (Just ident) [] body) [])) | ident == fnName = body
convert (App _ (App s1 (Function s2 Nothing [] (Block ss body)) []) []) =
App s1 (Function s2 Nothing [] (Block ss (applyReturns `fmap` body))) []
convert other = other
isBind (App _ fn [dict]) | isDict (effectModule, edBindDict) dict && isBindPoly fn = True
isBind _ = False
isDiscard (App _ (App _ fn [dict1]) [dict2])
| isDict (C.controlBind, C.discardUnitDictionary) dict1 &&
isDict (effectModule, edBindDict) dict2 &&
isDiscardPoly fn = True
isDiscard _ = False
isPure (App _ fn [dict]) | isDict (effectModule, edApplicativeDict) dict && isPurePoly fn = True
isPure _ = False
isBindPoly = isDict (C.controlBind, C.bind)
isPurePoly = isDict (C.controlApplicative, C.pure')
isDiscardPoly = isDict (C.controlBind, C.discard)
isEffFunc name (Indexer _ (StringLiteral _ name') (Var _ eff)) = eff == effectModule && name == name'
isEffFunc _ _ = False
applyReturns :: AST -> AST
applyReturns (Return ss ret) = Return ss (App ss ret [])
applyReturns (Block ss jss) = Block ss (map applyReturns jss)
applyReturns (While ss cond js) = While ss cond (applyReturns js)
applyReturns (For ss v lo hi js) = For ss v lo hi (applyReturns js)
applyReturns (ForIn ss v xs js) = ForIn ss v xs (applyReturns js)
applyReturns (IfElse ss cond t f) = IfElse ss cond (applyReturns t) (applyReturns `fmap` f)
applyReturns other = other
inlineST :: AST -> AST
inlineST = everywhere convertBlock
where
convertBlock (App s1 f [arg]) | isSTFunc C.runST f =
let refs = ordNub . findSTRefsIn $ arg
usages = findAllSTUsagesIn arg
allUsagesAreLocalVars = all (\u -> let v = toVar u in isJust v && fromJust v `elem` refs) usages
localVarsDoNotEscape = all (\r -> length (r `appearingIn` arg) == length (filter (\u -> let v = toVar u in v == Just r) usages)) refs
in App s1 (everywhere (convert (allUsagesAreLocalVars && localVarsDoNotEscape)) arg) []
convertBlock other = other
convert agg (App s1 f [arg]) | isSTFunc C.newSTRef f =
Function s1 Nothing [] (Block s1 [Return s1 $ if agg then arg else ObjectLiteral s1 [(mkString C.stRefValue, arg)]])
convert agg (App _ (App s1 f [ref]) []) | isSTFunc C.readSTRef f =
if agg then ref else Indexer s1 (StringLiteral s1 C.stRefValue) ref
convert agg (App _ (App _ (App s1 f [arg]) [ref]) []) | isSTFunc C.writeSTRef f =
if agg then Assignment s1 ref arg else Assignment s1 (Indexer s1 (StringLiteral s1 C.stRefValue) ref) arg
convert agg (App _ (App _ (App s1 f [func]) [ref]) []) | isSTFunc C.modifySTRef f =
if agg then Assignment s1 ref (App s1 func [ref]) else Assignment s1 (Indexer s1 (StringLiteral s1 C.stRefValue) ref) (App s1 func [Indexer s1 (StringLiteral s1 C.stRefValue) ref])
convert _ other = other
isSTFunc name (Indexer _ (StringLiteral _ name') (Var _ st)) = st == C.st && name == name'
isSTFunc _ _ = False
findSTRefsIn = everything (++) isSTRef
where
isSTRef (VariableIntroduction _ ident (Just (App _ (App _ f [_]) []))) | isSTFunc C.newSTRef f = [ident]
isSTRef _ = []
findAllSTUsagesIn = everything (++) isSTUsage
where
isSTUsage (App _ (App _ f [ref]) []) | isSTFunc C.readSTRef f = [ref]
isSTUsage (App _ (App _ (App _ f [_]) [ref]) []) | isSTFunc C.writeSTRef f || isSTFunc C.modifySTRef f = [ref]
isSTUsage _ = []
appearingIn ref = everything (++) isVar
where
isVar e@(Var _ v) | v == ref = [e]
isVar _ = []
toVar (Var _ v) = Just v
toVar _ = Nothing