Skip to content

Commit

Permalink
rename Intermediate Code to Intermediate Representation
Browse files Browse the repository at this point in the history
  • Loading branch information
KMahoney committed Jul 31, 2009
1 parent 55e242f commit 1c4b420
Show file tree
Hide file tree
Showing 7 changed files with 33 additions and 37 deletions.
12 changes: 6 additions & 6 deletions Dochi/Compile.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,17 +9,17 @@ import Control.Monad.Writer
import Control.Monad.State
import Control.Monad.Error

import Dochi.IMC
import Dochi.IR
import Dochi.Parse (AST(..))

data CompileState = CompileState { varList :: [String]
, envList :: [ (String, [String]) ]
, useList :: [String]
}

-- uses a Writer monad to output IC
-- uses a Writer monad to output IR

type Compiler a = WriterT [IC] (StateT CompileState (Either String)) a
type Compiler a = WriterT [IR] (StateT CompileState (Either String)) a


newCompileState = CompileState [] [] []
Expand Down Expand Up @@ -157,13 +157,13 @@ compileAST ast =

runCompiler st action = evalStateT (execWriterT $ action) st

compile :: CompileState -> [AST] -> Either String [IC]
compile :: CompileState -> [AST] -> Either String [IR]
compile st ast = runCompiler st $ mapM_ compileAST ast


-- Compile the AST and pop the captured values from the value stack.

compileScoped :: CompileState -> [AST] -> Either String [IC]
compileScoped :: CompileState -> [AST] -> Either String [IR]
compileScoped st ast = runCompiler st $ do mapM_ compileAST ast
st' <- gets varList
let c = length st'
Expand All @@ -176,6 +176,6 @@ compileScoped st ast = runCompiler st $ do mapM_ compileAST ast
envCompile :: [(String, [String])] -- ^ environment
-> [String] -- ^ list of useable modules
-> [AST] -- ^ Syntax tree to compile
-> Either String [IC] -- ^ Returns intermediate code
-> Either String [IR] -- ^ Returns intermediate code

envCompile e u = compileScoped (CompileState [] e u)
2 changes: 1 addition & 1 deletion Dochi/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ module Dochi.Core ( prettyprint
, coreState
) where

import Dochi.IMC
import Dochi.IR
import Dochi.Interpreter

import Data.List (intercalate, intersperse)
Expand Down
26 changes: 11 additions & 15 deletions Dochi/IMC.hs → Dochi/IR.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Dochi.IMC where
module Dochi.IR where

import qualified Data.Map as M
import Data.Dynamic
Expand All @@ -8,36 +8,32 @@ import Data.Dynamic
instance Eq Dynamic where _ == _ = False
instance Ord Dynamic where _ < _ = False


-- |Intermediate Representation
--
-- Captured values are pushed to a separate stack with VarPush
-- and referenced with VarIndex. At the end of the scope they are
-- pushed off the stack with EndScope. The rest are fairly
-- self-explanatory.

data Value = VWord String
| VKeyword String
| VInteger Integer
| VString String
| VChar Char
| VQuot [IC]
| VClosure [Value] [IC]
| VQuot [IR]
| VClosure [Value] [IR]
| VBool Bool
| VCons Value Value
| VTable (M.Map Value Value)
| VDyn Dynamic
deriving (Show, Eq, Ord)



-- |Intermediate Code
--
-- Captured values are pushed to a separate stack with VarPush
-- and referenced with VarIndex. At the end of the scope they are
-- pushed off the stack with EndScope. The rest are fairly
-- self-explanatory.

data IC = CallWord String String
data IR = CallWord String String
| FnCall
| PushValue Value
| PopValue
| VarPush String
| EndScope Integer
| VarIndex Integer
| MakeClosure [Int] [IC]
| MakeClosure [Int] [IR]
deriving (Show, Eq, Ord)
12 changes: 6 additions & 6 deletions Dochi/Interpreter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ import Control.Monad.State
import Control.Monad.Error
import Data.Foldable (foldrM)

import Dochi.IMC
import Dochi.IR
import Dochi.Parse (AST, ChiModuleAST, modName, modDefs, modUses)
import qualified Dochi.Parse as P
import Dochi.Compile (envCompile)
Expand Down Expand Up @@ -138,7 +138,7 @@ callword m w = do

where hidden = ["core", "list", "table"]

makeclosure :: [Int] -> [IC] -> Chi ()
makeclosure :: [Int] -> [IR] -> Chi ()
makeclosure refs code = do
v <- gets vars
pushstack $ VClosure (map (v !!) refs) code
Expand All @@ -152,9 +152,9 @@ fncall = do
runCode code
_ -> chiError $ "Cannot call value " ++ show a ++ "."

-- run IC code in Chi monad (IO with state)
-- run IR code in Chi monad (IO with state)

runCode :: [IC] -> Chi ()
runCode :: [IR] -> Chi ()
runCode [] = return ()

runCode (instr:code) = do
Expand All @@ -176,7 +176,7 @@ runCode (instr:code) = do

defWord :: String -- ^ Module name
-> String -- ^ Word name
-> [IC] -- ^ Intermediate code of new word
-> [IR] -- ^ Intermediate code of new word
-> ChiState -- ^ Initial state
-> ChiState -- ^ New state

Expand Down Expand Up @@ -205,6 +205,6 @@ runWord m name st = case M.lookup m (env st) of

-- |Run intermediate code in the provided state

runDochi :: ChiState -> [IC] -> IO ChiState
runDochi :: ChiState -> [IR] -> IO ChiState
runDochi st code = do (a, s) <- runStateT (runCode code) st
return s
8 changes: 4 additions & 4 deletions Dochi/REPL.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ import Dochi.Interpreter (ChiState(..), defWord, runDochi, environment)
import Dochi.Core (prettyprint)


data Options = Options { showIC :: Bool
data Options = Options { showIR :: Bool
, showAST :: Bool
, current :: String
, using :: [String]
Expand All @@ -31,7 +31,7 @@ debugAST opts ast = when (showAST opts) $ do putStrLn $ "AST: "
mapM_ (putStrLn . (" "++) . show) ast


debugIC opts ic = when (showIC opts) $ do putStrLn $ "IC: "
debugIR opts ic = when (showIR opts) $ do putStrLn $ "IR: "
mapM_ (putStrLn . (" "++) . show) ic


Expand All @@ -44,7 +44,7 @@ runLine opts st ast = do
Left err -> do putStrLn $ "Compile Error: " ++ err
return st

Right ic -> do debugIC opts ic
Right ic -> do debugIR opts ic
st' <- runDochi st ic
when (not . null $ stack st') $ putStrLn $ "\ESC[31mstack>\ESC[0m " ++ (prettystack st')
newline
Expand Down Expand Up @@ -92,7 +92,7 @@ interactive opts st = do
debugAST opts ast
case (envCompile (environment st) (current opts:using opts) ast) of
Left err -> putStrLn $ "Compile Error: " ++ err
Right ic -> do debugIC opts ic
Right ic -> do debugIR opts ic
interactive opts $ defWord (current opts) name ic st

Right (IMod name) -> do
Expand Down
8 changes: 4 additions & 4 deletions Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,18 +12,18 @@ import qualified Dochi.REPL as R

data Options = Options { repl :: Bool
, showAST :: Bool
, showIC :: Bool
, showIR :: Bool
}

defaultOptions = Options { repl = False
, showAST = False
, showIC = False
, showIR = False
}

options :: [OptDescr (Options -> Options)]
options = [ Option ['i'] ["interactive"] (NoArg (\o -> o {repl=True})) "Interactive REPL"
, Option [] ["ast"] (NoArg (\o -> o {showAST=True})) "Display Parse Output"
, Option [] ["debug"] (NoArg (\o -> o {showIC=True})) "Display Intermediate Code"
, Option [] ["debug"] (NoArg (\o -> o {showIR=True})) "Display Intermediate Code"
]

getopts :: [String] -> IO (Options, [String])
Expand All @@ -48,7 +48,7 @@ main = do
case opts of

Options {repl = True} -> do st <- compileFiles initialState files
R.runREPL R.Options { R.showIC = showIC opts, R.showAST = showAST opts, R.current = "user", R.using = [] } st
R.runREPL R.Options { R.showIR = showIR opts, R.showAST = showAST opts, R.current = "user", R.using = [] } st

_ -> handleError $ withFiles files runFiles

2 changes: 1 addition & 1 deletion dochi.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ library
Dochi.Interpreter
Dochi.Util
Dochi.Core
Dochi.IMC
Dochi.IR
Dochi.Parse
Dochi.REPL
Dochi.Compile
Expand Down

0 comments on commit 1c4b420

Please sign in to comment.