-
Notifications
You must be signed in to change notification settings - Fork 2
/
Copy pathRepl.hs
146 lines (116 loc) · 4.76 KB
/
Repl.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
{-|
Module : Repl
Description : The Read-Eval-Print-Loop for SOL.
Copyright : (c) Luke Geeson, 2019
License : GPL-3
Maintainer : [email protected]
Stability : stable
Portability : POSIX
The "Repl" module provides the Read-eval-print-loop for SOL.
This is the top level interface between the user and the interpreter.
-}
module Repl where
-- SOL Imports.
import SOL
import Parser
-- Tool Imports.
import qualified System.IO as IO (hFlush, stdout)
import qualified Data.Map.Lazy as M
-- | Top level repl function
replMain :: IO ()
replMain = do
putStrLn "Welcome to the SOL REPL"
putStrLn "Type some terms or press Enter to leave."
repl M.empty
-- | Stores variables from let expressions at runtime
-- terms are stored in left
-- types are stored in right
type Environment = M.Map String (Either SOLTerm T)
-- | REPL loop, takes input reduces and prints result, or exits out
repl :: Environment -> IO ()
repl env = do putStr "> "
IO.hFlush IO.stdout
s <- getLine
if Prelude.null s
then putStrLn "Goodbye."
else do {parseTerm s env; repl env}
-- | Helper function parses the term as either a Let expression or a raw term.
-- Let expressions update the environment with new variables, using any existing
-- variables in scope. For a raw term, evaluation is attempted after substituting
-- in bound terms from the environment.
parseTerm :: String -> Environment -> IO ()
parseTerm s env
| head s == '\'' = printReductions s env
| head s == 't' = printType s
| otherwise = case apply (pLet +++ pTypeLet +++ pTerm) s of
[(("", Left t),"")] -> -- reducing a term
case typeof' t' of
Just _ -> putStrLn . prependTerm t' $ reduce t'
_ -> cannotType $ show t'
where t' = formatTerm t env
[((v,Left t),"")] -> -- let expression
case typeof' t' of
Just _ -> do putStrLn $ "Saved term: " ++ show t'
repl $ M.insert v (Left t') env
_ -> cannotType s
where t' = formatTerm t env
[((v,Right t),"")] -> do putStrLn $ "Saved type: " ++ show t'
repl $ M.insert v (Right t') env
where t' = formatType t env
_ -> cannotParse s
-- | Helper function to print the reduction steps of a term
printReductions :: String -> Environment -> IO ()
printReductions s env
= let prepend x = prependReductions x $ reductions x
in case apply term (tail s) of
(x:_) -> if null $ snd x
then case typeof' x' of
Just _ -> mapM_ putStrLn $ prepend x'
_ -> cannotType $ tail s
else cannotParse s
where x' = formatTerm (fst x) env
_ -> cannotParse s
-- | Helper function to print the type of a term
printType :: String -> IO ()
printType s = case apply term $ tail s of
(x:_) -> if null $ snd x
then case typeof' $ fst x of
Just y -> print y
_ -> cannotType $ tail s
else cannotParse s
_ -> cannotParse s
-- | Takes a term and context and substitutes env terms
-- into all free occurrences in the term
formatTerm :: SOLTerm -> Environment -> SOLTerm
formatTerm t1 env = foldl
(\t (v,t2) -> case t2 of
Left t2 ->
if v `elem` vars t
then substitute t (Var v, t2)
else t
Right t2 ->
if v `elem` typeVarsInTerm t
then tSubUnder t (TVar v, t2)
else t) t1 $ M.assocs env
-- | Takes a type and context and substitutes env terms
-- all free occurrences in the term
formatType :: T -> Environment -> T
formatType t1 env = foldl
(\t (v,t2) -> case t2 of
Right t2 -> if v `elem` typeVars t1
then typeSub t (TVar v, t2)
else t
_ -> t) t1 $ M.assocs env
-- | Function prepends ~> arrows or prints existing term if no reds occur
prependReductions :: SOLTerm -> [SOLTerm] -> [String]
prependReductions x xs = if null xs then ["= "++show x] else
map (\x -> "~> " ++ show x) xs
-- | Function prepends reduction ops for one multi-step reduction
prependTerm :: SOLTerm -> SOLTerm -> String
prependTerm x y = if x == y then "= " ++ show x else "~>* " ++ show y
-- | Error message for parse failure
cannotParse :: String -> IO ()
cannotParse s = putStrLn $ (++) "Cannot Parse Term: " s
-- | Error message for typing failure
cannotType :: String -> IO ()
cannotType s = putStrLn $ (++) "Cannot Type Term: " s