Clean up and list SKI conversion fix
This commit is contained in:
88
src/Eval.hs
88
src/Eval.hs
@ -62,27 +62,39 @@ evalAST env term
|
||||
elimLambda :: TricuAST -> TricuAST
|
||||
elimLambda = go
|
||||
where
|
||||
-- η-reduction
|
||||
go (SLambda [v] (SApp f (SVar x)))
|
||||
| v == x && not (isFree v f) = elimLambda f
|
||||
-- Triage optimization
|
||||
go (SLambda [a] (SLambda [b] (SLambda [c] body)))
|
||||
| body == triageBody = _TRIAGE
|
||||
where
|
||||
triageBody =
|
||||
SApp (SApp TLeaf (SApp (SApp TLeaf (SVar a)) (SVar b))) (SVar c)
|
||||
-- Composition optimization
|
||||
go (SLambda [f] (SLambda [g] (SLambda [x] body)))
|
||||
| body == SApp (SVar f) (SApp (SVar g) (SVar x)) = _B
|
||||
-- General elimination
|
||||
go (SLambda [v] (SList xs))
|
||||
= elimLambda (SLambda [v] (foldr wrapTLeaf TLeaf xs))
|
||||
where wrapTLeaf m r = SApp (SApp TLeaf m) r
|
||||
go (SLambda (v:vs) body)
|
||||
| null vs = toSKI v (elimLambda body)
|
||||
| otherwise = elimLambda (SLambda [v] (SLambda vs body))
|
||||
go (SApp f g) = SApp (elimLambda f) (elimLambda g)
|
||||
go x = x
|
||||
go term
|
||||
| etaReduction term = elimLambda $ etaReduceResult term
|
||||
| triagePattern term = _TRI
|
||||
| composePattern term = _B
|
||||
| lambdaList term = elimLambda $ lambdaListResult term
|
||||
| nestedLambda term = nestedLambdaResult term
|
||||
| application term = applicationResult term
|
||||
| otherwise = term
|
||||
|
||||
etaReduction (SLambda [v] (SApp f (SVar x))) = v == x && not (isFree v f)
|
||||
etaReduction _ = False
|
||||
etaReduceResult (SLambda [_] (SApp f _)) = f
|
||||
|
||||
triagePattern (SLambda [a] (SLambda [b] (SLambda [c] body))) = body == triageBody a b c
|
||||
triagePattern _ = False
|
||||
|
||||
composePattern (SLambda [f] (SLambda [g] (SLambda [x] body))) = body == composeBody f g x
|
||||
composePattern _ = False
|
||||
|
||||
lambdaList (SLambda [_] (SList _)) = True
|
||||
lambdaList _ = False
|
||||
lambdaListResult (SLambda [v] (SList xs)) = SLambda [v] (foldr wrapTLeaf TLeaf xs)
|
||||
wrapTLeaf m r = SApp (SApp TLeaf m) r
|
||||
|
||||
nestedLambda (SLambda (_:_) _) = True
|
||||
nestedLambda _ = False
|
||||
nestedLambdaResult (SLambda (v:vs) body)
|
||||
| null vs = toSKI v (elimLambda body)
|
||||
| otherwise = elimLambda (SLambda [v] (SLambda vs body))
|
||||
|
||||
application (SApp _ _) = True
|
||||
application _ = False
|
||||
applicationResult (SApp f g) = SApp (elimLambda f) (elimLambda g)
|
||||
|
||||
toSKI x (SVar y)
|
||||
| x == y = _I
|
||||
@ -90,30 +102,38 @@ elimLambda = go
|
||||
toSKI x t@(SApp n u)
|
||||
| not (isFree x t) = SApp _K t
|
||||
| otherwise = SApp (SApp _S (toSKI x n)) (toSKI x u)
|
||||
toSKI x (SList xs)
|
||||
| not (isFree x (SList xs)) = SApp _K (SList xs)
|
||||
| otherwise = SList (map (toSKI x) xs)
|
||||
toSKI x t
|
||||
| not (isFree x t) = SApp _K t
|
||||
| otherwise = errorWithoutStackTrace "Unhandled toSKI conversion"
|
||||
|
||||
_S = parseSingle "t (t (t t t)) t"
|
||||
_K = parseSingle "t t"
|
||||
_I = parseSingle "t (t (t t)) t"
|
||||
_B = parseSingle "t (t (t t (t (t (t t t)) t))) (t t)"
|
||||
_TRIAGE = parseSingle "t (t (t t (t (t (t t t))))) t"
|
||||
-- Combinators and special forms
|
||||
_S = parseSingle "t (t (t t t)) t"
|
||||
_K = parseSingle "t t"
|
||||
_I = parseSingle "t (t (t t)) t"
|
||||
_B = parseSingle "t (t (t t (t (t (t t t)) t))) (t t)"
|
||||
_TRI = parseSingle "t (t (t t (t (t (t t t))))) t"
|
||||
|
||||
-- Pattern bodies
|
||||
triageBody a b c = SApp (SApp TLeaf (SApp (SApp TLeaf (SVar a)) (SVar b))) (SVar c)
|
||||
composeBody f g x = SApp (SVar f) (SApp (SVar g) (SVar x))
|
||||
|
||||
isFree :: String -> TricuAST -> Bool
|
||||
isFree x = Set.member x . freeVars
|
||||
|
||||
freeVars :: TricuAST -> Set.Set String
|
||||
freeVars (SVar v ) = Set.singleton v
|
||||
freeVars (SInt _ ) = Set.empty
|
||||
freeVars (SStr _ ) = Set.empty
|
||||
freeVars (SList s ) = foldMap freeVars s
|
||||
freeVars (SLambda v b ) = foldr Set.delete (freeVars b) v
|
||||
freeVars (SApp f a ) = freeVars f <> freeVars a
|
||||
freeVars TLeaf = Set.empty
|
||||
freeVars (TFork l r ) = freeVars l <> freeVars r
|
||||
freeVars (SDef _ _ b) = freeVars b
|
||||
freeVars (TStem t ) = freeVars t
|
||||
freeVars (TFork l r ) = freeVars l <> freeVars r
|
||||
freeVars (SLambda v b ) = foldr Set.delete (freeVars b) v
|
||||
freeVars (SInt _ ) = Set.empty
|
||||
freeVars (SStr _ ) = Set.empty
|
||||
freeVars TLeaf = Set.empty
|
||||
freeVars _ = Set.empty
|
||||
|
||||
reorderDefs :: Env -> [TricuAST] -> [TricuAST]
|
||||
@ -131,7 +151,7 @@ reorderDefs env defs
|
||||
graph = buildDepGraph defsOnly
|
||||
sortedDefs = sortDeps graph
|
||||
defMap = Map.fromList [(name, def) | def@(SDef name _ _) <- defsOnly]
|
||||
orderedDefs = map (\name -> defMap Map.! name) sortedDefs
|
||||
orderedDefs = map (defMap Map.!) sortedDefs
|
||||
|
||||
freeVarsDefs = foldMap snd defsWithFreeVars
|
||||
freeVarsOthers = foldMap freeVars others
|
||||
@ -139,8 +159,8 @@ reorderDefs env defs
|
||||
validNames = Set.fromList defNames `Set.union` Set.fromList (Map.keys env)
|
||||
missingDeps = Set.toList (allFreeVars `Set.difference` validNames)
|
||||
|
||||
isDef (SDef _ _ _) = True
|
||||
isDef _ = False
|
||||
isDef SDef {} = True
|
||||
isDef _ = False
|
||||
|
||||
buildDepGraph :: [TricuAST] -> Map.Map String (Set.Set String)
|
||||
buildDepGraph topDefs
|
||||
|
53
src/Main.hs
53
src/Main.hs
@ -63,18 +63,17 @@ main = do
|
||||
case args of
|
||||
Repl -> do
|
||||
putStrLn "Welcome to the tricu REPL"
|
||||
putStrLn "You can exit with `CTRL+D` or the `!exit` command.`"
|
||||
putStrLn "You may exit with `CTRL+D` or the `!exit` command."
|
||||
putStrLn "Try typing `!` with tab completion for more commands."
|
||||
repl Map.empty
|
||||
Evaluate { file = filePaths, form = form } -> do
|
||||
result <- case filePaths of
|
||||
[] -> do
|
||||
t <- getContents
|
||||
pure $ runTricu t
|
||||
[] -> runTricuT <$> getContents
|
||||
(filePath:restFilePaths) -> do
|
||||
initialEnv <- evaluateFile filePath
|
||||
finalEnv <- foldM evaluateFileWithContext initialEnv restFilePaths
|
||||
pure $ mainResult finalEnv
|
||||
let fRes = formatResult form result
|
||||
let fRes = formatT form result
|
||||
putStr fRes
|
||||
TDecode { file = filePaths } -> do
|
||||
value <- case filePaths of
|
||||
@ -82,8 +81,48 @@ main = do
|
||||
(filePath:_) -> readFile filePath
|
||||
putStrLn $ decodeResult $ result $ evalTricu Map.empty $ parseTricu value
|
||||
|
||||
runTricu :: String -> T
|
||||
runTricu input =
|
||||
-- Simple interfaces
|
||||
|
||||
runTricu :: String -> String
|
||||
runTricu = formatT TreeCalculus . runTricuT
|
||||
|
||||
runTricuT :: String -> T
|
||||
runTricuT input =
|
||||
let asts = parseTricu input
|
||||
finalEnv = evalTricu Map.empty asts
|
||||
in result finalEnv
|
||||
|
||||
runTricuEnv :: Env -> String -> String
|
||||
runTricuEnv env = formatT TreeCalculus . runTricuTEnv env
|
||||
|
||||
runTricuTEnv :: Env -> String -> T
|
||||
runTricuTEnv env input =
|
||||
let asts = parseTricu input
|
||||
finalEnv = evalTricu env asts
|
||||
in result finalEnv
|
||||
|
||||
runTricuWithEnvT :: String -> (Env, T)
|
||||
runTricuWithEnvT input =
|
||||
let asts = parseTricu input
|
||||
finalEnv = evalTricu Map.empty asts
|
||||
in (finalEnv, result finalEnv)
|
||||
|
||||
runTricuWithEnv :: String -> (Env, String)
|
||||
runTricuWithEnv input =
|
||||
let asts = parseTricu input
|
||||
finalEnv = evalTricu Map.empty asts
|
||||
res = result finalEnv
|
||||
in (finalEnv, formatT TreeCalculus res)
|
||||
|
||||
runTricuEnvWithEnvT :: Env -> String -> (Env, T)
|
||||
runTricuEnvWithEnvT env input =
|
||||
let asts = parseTricu input
|
||||
finalEnv = evalTricu env asts
|
||||
in (finalEnv, result finalEnv)
|
||||
|
||||
runTricuEnvWithEnv :: Env -> String -> (Env, String)
|
||||
runTricuEnvWithEnv env input =
|
||||
let asts = parseTricu input
|
||||
finalEnv = evalTricu env asts
|
||||
res = result finalEnv
|
||||
in (finalEnv, formatT TreeCalculus res)
|
@ -152,7 +152,7 @@ repl env = runInputT settings (withInterrupt (loop env Decode))
|
||||
newEnv = evalTricu env asts
|
||||
case Map.lookup "!result" newEnv of
|
||||
Just r -> do
|
||||
putStrLn $ "tricu > " ++ formatResult form r
|
||||
putStrLn $ "tricu > " ++ formatT form r
|
||||
Nothing -> pure ()
|
||||
return newEnv
|
||||
|
||||
@ -182,7 +182,7 @@ repl env = runInputT settings (withInterrupt (loop env Decode))
|
||||
liftIO $ writeFile filepath ""
|
||||
outputStrLn "File created..."
|
||||
forM_ definitions $ \(name, value) -> do
|
||||
let content = name ++ " = " ++ formatResult TreeCalculus value ++ "\n"
|
||||
let content = name ++ " = " ++ formatT TreeCalculus value ++ "\n"
|
||||
outputStrLn $ "Writing definition: " ++ name ++ " with length " ++ show (length content)
|
||||
liftIO $ appendFile filepath content
|
||||
outputStrLn $ "Saved " ++ show (length definitions) ++ " definitions to " ++ p
|
||||
|
@ -15,7 +15,7 @@ data T = Leaf | Stem T | Fork T T
|
||||
-- Abstract Syntax Tree for tricu
|
||||
data TricuAST
|
||||
= SVar String
|
||||
| SInt Int
|
||||
| SInt Integer
|
||||
| SStr String
|
||||
| SList [TricuAST]
|
||||
| SDef String [String] TricuAST
|
||||
@ -33,7 +33,7 @@ data LToken
|
||||
= LKeywordT
|
||||
| LIdentifier String
|
||||
| LNamespace String
|
||||
| LIntegerLiteral Int
|
||||
| LIntegerLiteral Integer
|
||||
| LStringLiteral String
|
||||
| LAssign
|
||||
| LColon
|
||||
@ -84,9 +84,9 @@ _not = Fork (Fork _true (Fork Leaf _false)) Leaf
|
||||
|
||||
-- Marshalling
|
||||
ofString :: String -> T
|
||||
ofString str = ofList $ map (ofNumber . fromEnum) str
|
||||
ofString str = ofList $ map (ofNumber . toInteger . fromEnum) str
|
||||
|
||||
ofNumber :: Int -> T
|
||||
ofNumber :: Integer -> T
|
||||
ofNumber 0 = Leaf
|
||||
ofNumber n =
|
||||
Fork
|
||||
@ -96,7 +96,7 @@ ofNumber n =
|
||||
ofList :: [T] -> T
|
||||
ofList = foldr Fork Leaf
|
||||
|
||||
toNumber :: T -> Either String Int
|
||||
toNumber :: T -> Either String Integer
|
||||
toNumber Leaf = Right 0
|
||||
toNumber (Fork Leaf rest) = case toNumber rest of
|
||||
Right n -> Right (2 * n)
|
||||
@ -108,7 +108,7 @@ toNumber _ = Left "Invalid Tree Calculus number"
|
||||
|
||||
toString :: T -> Either String String
|
||||
toString tc = case toList tc of
|
||||
Right list -> traverse (fmap toEnum . toNumber) list
|
||||
Right list -> traverse (fmap (toEnum . fromInteger) . toNumber) list
|
||||
Left err -> Left "Invalid Tree Calculus string"
|
||||
|
||||
toList :: T -> Either String [T]
|
||||
@ -119,13 +119,13 @@ toList (Fork x rest) = case toList rest of
|
||||
toList _ = Left "Invalid Tree Calculus list"
|
||||
|
||||
-- Outputs
|
||||
formatResult :: EvaluatedForm -> T -> String
|
||||
formatResult TreeCalculus = toSimpleT . show
|
||||
formatResult FSL = show
|
||||
formatResult AST = show . toAST
|
||||
formatResult Ternary = toTernaryString
|
||||
formatResult Ascii = toAscii
|
||||
formatResult Decode = decodeResult
|
||||
formatT :: EvaluatedForm -> T -> String
|
||||
formatT TreeCalculus = toSimpleT . show
|
||||
formatT FSL = show
|
||||
formatT AST = show . toAST
|
||||
formatT Ternary = toTernaryString
|
||||
formatT Ascii = toAscii
|
||||
formatT Decode = decodeResult
|
||||
|
||||
toSimpleT :: String -> String
|
||||
toSimpleT s = T.unpack
|
||||
@ -166,7 +166,7 @@ decodeResult tc =
|
||||
(_, _, Right n) -> show n
|
||||
(_, Right xs@(_:_), _) -> "[" ++ intercalate ", " (map decodeResult xs) ++ "]"
|
||||
(_, Right [], _) -> "[]"
|
||||
_ -> formatResult TreeCalculus tc
|
||||
_ -> formatT TreeCalculus tc
|
||||
where
|
||||
isCommonChar c =
|
||||
let n = fromEnum c
|
||||
|
Reference in New Issue
Block a user