{-# LANGUAGE BangPatterns #-}
module SMR.Core.Step
( Config (..)
, World (..)
, Result (..)
, newWorld
, steps
, step)
where
import SMR.Core.Exp
import SMR.Core.World
import SMR.Prim.Op.Base
import Data.Text (Text)
import Data.Map (Map)
import qualified Data.Map as Map
data Config s p w
= Config
{
configUnderLambdas :: !Bool
, configHeadArgs :: !Bool
, configPrims :: !(Map p (PrimEval s p w))
, configDeclsMac :: !(Map Name (Exp s p)) }
data Result
= ResultDone
| ResultError Text
deriving Show
steps :: (Ord p, Show p)
=> Config s p w
-> World w -> Exp s p
-> IO (Either Text (Exp s p))
steps !config !world !xx
= do erx <- step config world xx
case erx of
Left ResultDone -> return $ Right xx
Left (ResultError err) -> return $ Left err
Right xx' -> steps config world xx'
step :: (Ord p, Show p)
=> Config s p w
-> World w -> Exp s p
-> IO (Either Result (Exp s p))
step !config !world !xx
= case xx of
XRef ref
-> case ref of
RMac n
-> case Map.lookup n (configDeclsMac config) of
Nothing -> return $ Left ResultDone
Just x -> return $ Right x
_ -> return $ Left ResultDone
XVar{}
-> return $ Left ResultDone
XAbs ns1 x2
| configUnderLambdas config
-> do er2' <- step config world x2
case er2' of
Left r2 -> return $ Left r2
Right x2' -> return $ Right $ XAbs ns1 x2'
| otherwise
-> return $ Left ResultDone
XApp xF []
-> return $ Right xF
XApp{}
| Just (xF, xsArgs) <- takeXApps xx
-> do erx <- step (config { configUnderLambdas = False })
world xF
case erx of
Right xF'
-> return $ Right $ makeXApps xF' xsArgs
Left err@(ResultError _)
-> return $ Left err
Left ResultDone
-> case xF of
XRef (RPrm primF) -> stepAppPrm config world primF xsArgs
XAbs nsParam xBody -> stepAppAbs config world nsParam xBody xsArgs
_ | configHeadArgs config
-> do erxArgs <- stepFirstVal config world xsArgs
case erxArgs of
Right xsArgs' -> return $ Right $ makeXApps xF xsArgs'
Left res -> return $ Left res
| otherwise
-> return $ Left ResultDone
| otherwise
-> return $ Left ResultDone
XSub{}
-> case pushHead xx of
Nothing -> return $ Left ResultDone
Just xx' -> return $ Right xx'
XKey KBox _
-> return $ Left ResultDone
XKey KRun x1
-> do erx <- step (config { configUnderLambdas = False
, configHeadArgs = False })
world x1
case erx of
Right x1'
-> return $ Right (XKey KRun x1')
Left err@(ResultError _)
-> return $ Left err
Left ResultDone
-> case x1 of
XKey KBox x11 -> return $ Right x11
_ -> return $ Right x1
stepAppPrm
:: (Ord p, Show p)
=> Config s p w
-> World w -> p -> [Exp s p]
-> IO (Either Result (Exp s p))
stepAppPrm !config !world !prim !xsArgs
= case Map.lookup prim (configPrims config) of
Nothing -> return $ Left ResultDone
Just primEval -> stepPrim config world primEval xsArgs
stepAppAbs
:: (Ord p, Show p)
=> Config s p w
-> World w -> [Param] -> Exp s p -> [Exp s p]
-> IO (Either Result (Exp s p))
stepAppAbs !config !world !psParam !xBody !xsArgs
= do
let arity = length psParam
let args = length xsArgs
let xsArgs_sat = take arity xsArgs
let xsArgs_remain = drop arity xsArgs
let fsParam_sat = map formOfParam psParam
erxs <- stepFirst config world xsArgs_sat fsParam_sat
case erxs of
Right xsArgs_sat'
-> do let xFun = XAbs psParam xBody
return $ Right
$ makeXApps (makeXApps xFun xsArgs_sat') xsArgs_remain
Left err@(ResultError _)
-> return $ Left err
Left ResultDone
| args == arity
-> do let nsParam = map nameOfParam psParam
let snv = snvOfNamesArgs nsParam xsArgs
return $ Right
$ snvApply False snv xBody
| args < arity
-> do let psParam_sat = take args psParam
let nsParam_sat = map nameOfParam psParam_sat
let psParam_remain = drop args psParam
let snv = snvOfNamesArgs nsParam_sat xsArgs_sat
return $ Right
$ makeXApps
(snvApply False snv $ XAbs psParam_remain xBody)
xsArgs_remain
| otherwise
-> do let nsParam = map nameOfParam psParam
let snv = snvOfNamesArgs nsParam xsArgs_sat
return $ Right
$ makeXApps
(snvApply False snv xBody)
xsArgs_remain
stepPrim
:: (Ord p, Show p)
=> Config s p w
-> World w -> PrimEval s p w -> [Exp s p]
-> IO (Either Result (Exp s p))
stepPrim !config !world !pe !xsArgs
| PrimEval _prim _desc csArg eval <- pe
= let
evalArgs [] [] xsArgsDone
= do mr <- eval world (reverse xsArgsDone)
case mr of
Just xResult -> return $ Right xResult
Nothing -> return $ Left ResultDone
evalArgs [] xsArgsRemain xsArgsDone
= do mr <- eval world (reverse xsArgsDone)
case mr of
Just xResult -> return $ Right $ makeXApps xResult xsArgsRemain
Nothing -> return $ Left ResultDone
evalArgs (cArg' : csArg') (xArg' : xsArg') xsArgsDone
| PExp <- cArg'
= evalArgs csArg' xsArg' (xArg' : xsArgsDone)
| otherwise
= do erxArg' <- step (config { configUnderLambdas = False
, configHeadArgs = False })
world xArg'
case erxArg' of
Left err@(ResultError _)
-> return $ Left err
Left ResultDone
-> evalArgs csArg' xsArg' (xArg' : xsArgsDone)
Right xArg''
-> return $ Right
$ makeXApps (XRef (RPrm (primEvalName pe)))
$ (reverse xsArgsDone) ++ (xArg'' : xsArg')
evalArgs _ [] _xsArgsDone
= return $ Left ResultDone
in evalArgs csArg xsArgs []
stepFirstVal
:: (Ord p, Show p)
=> Config s p w
-> World w -> [Exp s p]
-> IO (Either Result [Exp s p])
stepFirstVal !config !world !xx
= stepFirst config world xx (replicate (length xx) PVal)
stepFirst
:: (Ord p, Show p)
=> Config s p w
-> World w -> [Exp s p] -> [Form]
-> IO (Either Result [Exp s p])
stepFirst !config !world !xx !ff
= case (xx, ff) of
([], _)
-> return $ Left ResultDone
(_, [])
-> return $ Left ResultDone
(x1 : xs2, f1 : fs2)
| PExp <- f1
-> do erx <- stepFirst config world xs2 fs2
case erx of
Left r -> return $ Left r
Right xs2' -> return $ Right $ x1 : xs2'
| otherwise
-> do erx1 <- step config world x1
case erx1 of
Left err@(ResultError{})
-> return $ Left err
Left ResultDone
-> do erxs2 <- stepFirst config world xs2 fs2
case erxs2 of
Left r -> return $ Left r
Right xs2' -> return $ Right $ x1 : xs2'
Right x1'
-> return $ Right $ x1' : xs2