Skip to content

Commit

Permalink
Merge pull request #53 from nLatt/22-implement-an-interactive-mode-fo…
Browse files Browse the repository at this point in the history
…r-the-scheme-interpreter

[Fix] add patterns matching
  • Loading branch information
audetuczapski authored Feb 6, 2023
2 parents efcce68 + 1589965 commit 2302283
Show file tree
Hide file tree
Showing 2 changed files with 58 additions and 23 deletions.
35 changes: 12 additions & 23 deletions lib/Exec/InteractivePrompt.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module Exec.InteractivePrompt where

import Data.List ()
import Data.List (isInfixOf)
import Exec.Eval
import Exec.Registry
import Parsing.Ast (parseExprList)
Expand All @@ -15,33 +15,27 @@ import System.IO (hFlush, stdout)
countChar :: Char -> String -> Int
countChar char = length . filter (== char)

-- Function that checks the occurance between '(' and ')'.
-- Returns a boolean
occurenceBrackets :: Int -> Int -> Bool
occurenceBrackets num_open num_close = num_open == num_close && num_open /= 0

recurse :: [String] -> Int -> Int -> IO String
recurse inputs 0 close = print "Open with a bracket." >> getInput [] 0
recurse inputs _ _
| "\ESC" `isInfixOf` last inputs = exitSuccess
recurse inputs open close
| open == close = return $ concat inputs
| otherwise = getInput inputs (open - close)

printprompt :: Int -> IO ()
printprompt 0 = putStr "> " >> hFlush stdout
printprompt _ = putStr " " >> hFlush stdout

-- Recursive function that receives input
-- Reads input, triggers program exit, terminates after good format, recursive if bad
getInput :: [String] -> Int -> IO String
getInput inputs openBrackets = do
if openBrackets == 0
then putStr "> "
else putStr " "
hFlush stdout
printprompt openBrackets
input <- getLine
if input == "\ESC"
then exitSuccess
else do
let num_open = countChar '(' input
let num_close = countChar ')' input

recurse (inputs <> [input ++ "\n"]) (openBrackets + num_open) num_close
let num_open = countChar '(' input
let num_close = countChar ')' input
recurse (inputs <> [input ++ "\n"]) (openBrackets + num_open) num_close

loop :: Registry -> IO ()
loop reg = do
Expand All @@ -60,9 +54,4 @@ interactiveMode = do
-- Run
loop emptyRegistry

return ()

-- Fonction main
-- Affiche entrée "input"bon au format
-- get the return of the "checkBrackets" function
-- which gives the correct test format with true occurance '(' == ')'
return ()
46 changes: 46 additions & 0 deletions lib/Exec/Main.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,46 @@
module Main where

-- Our modules
import Parsing
import Parsing.Token
import Parsing.Cpt
import Parsing.Ast
import Parsing.Args
import System.Console.GetOpt
import Exec

import System.Environment
import System.Exit
import Data.Maybe (fromMaybe)

getFileName :: [String] -> Maybe FilePath -> String
getFileName [] b = fromMaybe "stdin" b
getFileName (x:xs) b = x

runFile :: String -> IO ()
runFile filename = do
-- Tokenize
tokens <- tokenizeFile filename

-- Parse CPT
let cpt = parseTokenList tokens

-- Parse AST
let ast = parseExprList cpt

-- Run
run ast

return ()


main :: IO ()
main = do
-- Parsing arguments
(res, fls) <- getArgs >>= parse

let fileName = getFileName fls (file res)
print ("Execute file: " ++ fileName)
if (==) fileName "stdin"
then exitSuccess -- interactive
else runFile fileName -- normal

0 comments on commit 2302283

Please sign in to comment.