Skip to content

Commit

Permalink
r28760@phanatique: nelhage | 2007-12-20 21:21:10 -0800
Browse files Browse the repository at this point in the history
 move Expression into its own module


git-svn-id: svn+ssh://lunatique.mit.edu/data/svn/flnv/trunk@28 e7f7c2cb-1e20-0410-8c26-a6ba679ee1f5
  • Loading branch information
nelhage committed Jul 25, 2008
1 parent 1aef566 commit 713f774
Show file tree
Hide file tree
Showing 5 changed files with 35 additions and 40 deletions.
5 changes: 3 additions & 2 deletions FLNV/AST.hs
@@ -1,13 +1,14 @@
module FLNV.AST where

import FLNV.Error
import FLNV.Parser (Expression(..))
import FLNV.Expression
import Control.Monad

-- An AST is approximately an Expression, but it makes special forms
-- and calls explicit. Syntax checking occurs during the translation
-- from Expression to AST
data AST = Lambda [String] AST
data AST = Define String Expression
| Lambda [String] AST
| If AST AST AST
| Apply AST [AST]
| AString String
Expand Down
6 changes: 4 additions & 2 deletions FLNV/Error.hs
Expand Up @@ -5,14 +5,16 @@ import Text.ParserCombinators.Parsec (ParseError)
import Control.Monad.Error (throwError, MonadError)
import qualified Control.Monad.Error as E

import {-# SOURCE #-} FLNV.Parser (Expression)
import FLNV.Expression

data Error = Error String
| ReadErr ParseError
| SyntaxError String Expression
| InternalError String
| Undefined String
| DuplicateBinding String
deriving Show

instance E.Error Error where
noMsg = Error "An error has occurred"
strMsg = Error

26 changes: 26 additions & 0 deletions FLNV/Expression.hs
@@ -0,0 +1,26 @@
module FLNV.Expression (Expression(..)) where

data Expression = Symbol String
| Number Integer
| String String
| Bool Bool
| Cons Expression Expression
| Nil
deriving (Eq)

instance Show Expression where
show (Symbol s) = s
show (Number n) = show n
show (String s) = '"' : s ++ "\""
show (Bool True) = "#t"
show (Bool False) = "#f"
show c@(Cons a b) = "(" ++ showListInner c ++ ")"
show Nil = "()"

showListInner :: Expression -> String
showListInner (Cons a b@(Cons _ _)) = show a ++ " " ++ showListInner b
showListInner (Cons a Nil) = show a
showListInner (Cons a b) = show a ++ " . " ++ showListInner b
showListInner Nil = ""
showListInner x = show x

27 changes: 2 additions & 25 deletions FLNV/Parser.hs
@@ -1,33 +1,10 @@
module FLNV.Parser (Expression(..), readExpr) where
module FLNV.Parser (readExpr) where

import FLNV.Expression
import FLNV.Error
import Control.Monad
import Text.ParserCombinators.Parsec hiding (newline)

data Expression = Symbol String
| Number Integer
| String String
| Bool Bool
| Cons Expression Expression
| Nil
deriving (Eq)

instance Show Expression where
show (Symbol s) = s
show (Number n) = show n
show (String s) = '"' : s ++ "\""
show (Bool True) = "#t"
show (Bool False) = "#f"
show c@(Cons a b) = "(" ++ showListInner c ++ ")"
show Nil = "()"

showListInner :: Expression -> String
showListInner (Cons a b@(Cons _ _)) = show a ++ " " ++ showListInner b
showListInner (Cons a Nil) = show a
showListInner (Cons a b) = show a ++ " . " ++ showListInner b
showListInner Nil = ""
showListInner x = show x

readExpr :: (MonadError Error m) => String -> m Expression
readExpr s = case parse sExpression "scheme" s of
Left err -> throwError $ ReadErr err
Expand Down
11 changes: 0 additions & 11 deletions FLNV/Parser.hs-boot

This file was deleted.

0 comments on commit 713f774

Please sign in to comment.