Skip to content

Commit

Permalink
Remove support for modules
Browse files Browse the repository at this point in the history
They'll come later
  • Loading branch information
knrafto committed Oct 18, 2013
1 parent ee2280c commit f9cf43d
Show file tree
Hide file tree
Showing 4 changed files with 7 additions and 53 deletions.
15 changes: 1 addition & 14 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -46,22 +46,9 @@ Names may be redefined at any time. A name appearing in an expression refers
to the the latest definition that appears before the expression
(see "Execution").

## Imports

And import statement of the form

import path.to.file;

will inline the file path/to/file.lc, similar to the C preprocessor.
Thus, order of imports can matter in some instances.

The standard prelude (Prelude.lc) is automatically imported before every
file.

## Execution

After all imports are inlined into a single list of declarations, the main
expression is equivalent to
The main expression is equivalent to

let <decls> in main

Expand Down
29 changes: 2 additions & 27 deletions src/Language/BLC/Parse.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,6 @@ module Language.BLC.Parse
Name
, Decl(..)
, Expr(..)
, ModuleName(..)
, Module(..)
-- * Parsing
, parseExpr
) where
Expand All @@ -22,9 +20,7 @@ import qualified Text.Parsec.Token as P
type Name = String

-- | A declaration or import statement.
data Decl
= Decl Name Expr
| Import ModuleName
data Decl = Decl Name Expr
deriving (Eq, Ord, Show, Read)

-- | An expression.
Expand All @@ -37,17 +33,6 @@ data Expr
| StrLit String
deriving (Eq, Ord, Show, Read)

-- | A module name. @Data.Category.File@ is represented as
-- @["Data", "Category", "File"]@.
newtype ModuleName = ModuleName [String]
deriving (Eq, Ord, Show, Read)

-- | A module, as a simple list of declarations.
data Module = Module
{ moduleName :: ModuleName
, moduleDecls :: [Decl]
} deriving (Eq, Ord, Show, Read)

-- | Parse a value from a file name and string, consuming all input.
parseAll :: Parser a -> String -> String -> Either ParseError a
parseAll p = parse (P.whiteSpace lexer *> p <* eof)
Expand All @@ -67,9 +52,6 @@ lexer = P.makeTokenParser emptyDef
nameStart = satisfy $ \c -> not $ isSpace c || c `elem` "\\.#();'\""
nameLetter = satisfy $ \c -> not $ isSpace c || c `elem` "\\.#();"

lexeme :: Parser a -> Parser a
lexeme = P.lexeme lexer

symbol :: String -> Parser String
symbol = P.symbol lexer

Expand Down Expand Up @@ -100,11 +82,4 @@ decls :: Parser [Decl]
decls = sepEndBy1 decl (P.semi lexer)

decl :: Parser Decl
decl = import_ <|> Decl <$> name <* reserved "=" <*> expr

import_ :: Parser Decl
import_ = Import <$ reserved "import" <*> lexeme path
where
path = ModuleName <$> sepBy1 pathSegment (char '.')
pathSegment = many1 pathChar
pathChar = satisfy $ \c -> not $ isSpace c || c `elem` "/."
decl = Decl <$> name <* reserved "=" <*> expr
13 changes: 3 additions & 10 deletions src/Language/BLC/Translate.hs
Original file line number Diff line number Diff line change
@@ -1,22 +1,18 @@
-- | Translating lambda expressions.
module Language.BLC.Translate
( translate
, translateMain
) where

import Data.Map (Map)
import qualified Data.Map as Map

import Language.BLC.Core
import Language.BLC.Encoding
import qualified Language.BLC.Parse as P

type ModuleMap = Map P.ModuleName P.Module

-- | Translate a syntax tree into an expression. Chars are encoded as
-- 8-element lists of Church booleans, and strings are encoded as lists of
-- encoded chars.
translate :: ModuleMap -> P.Expr -> Expr String
translate modules = go
translate :: P.Expr -> Expr String
translate = go
where
go (P.Var a) = Var a
go (P.App f as) = app (go f) (map go as)
Expand All @@ -26,6 +22,3 @@ translate modules = go
go (P.Let ds b) = foldr bind (go b) ds

bind (P.Decl n s) e = App (lam n e) (go s)
bind (P.Import n) e = case Map.lookup n modules of
Just m -> foldr bind e (P.moduleDecls m)
Nothing -> e
3 changes: 1 addition & 2 deletions tests/Tests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,6 @@ import Prelude hiding (notElem)
import Data.Char
import Data.Foldable (notElem)
import Data.Function
import Data.Map as Map (empty)
import Test.QuickCheck
import Test.Tasty
import Test.Tasty.QuickCheck
Expand Down Expand Up @@ -41,7 +40,7 @@ reducible e = reduce e /= e
where
assertParse s = case parseExpr s of
Left _ -> assertFailure ("failed parse: " ++ s) >> undefined
Right e -> return (translate Map.empty e)
Right e -> return (translate e)

parseFail :: String -> Assertion
parseFail s = case parseExpr s of
Expand Down

0 comments on commit f9cf43d

Please sign in to comment.