Checkpoint some existing changes.

This commit is contained in:
2023-04-10 21:24:07 -07:00
parent 6e7a7c7d04
commit 5c294850a8
6 changed files with 130 additions and 80 deletions

View File

@@ -107,7 +107,6 @@ letExpr = do
scope <- term
pure $ Let alts scope
-- Let <$ keyword "let" <*> ident <* keyword "=" <*> term <* keyword "in" <*> term
where
letAssign : Parser (Name,Term)
letAssign = do
@@ -127,7 +126,7 @@ lamExpr = do
keyword "\\"
commit
name <- pPattern
keyword "."
keyword "=>"
scope <- term
pure $ Lam name scope
@@ -150,25 +149,33 @@ caseExpr = do
alts <- startBlock $ someSame $ caseAlt
pure $ Case sc alts
term = defer $ \_ =>
caseExpr
<|> letExpr
<|> lamExpr
<|> parseOp
-- And top level stuff
optional : Parser a -> Parser (Maybe a)
optional pa = Just <$> pa <|> pure Nothing
export
parseSig : Parser Decl
parseSig = TypeSig <$> ident <* keyword ":" <*> term
parseImport : Parser Decl
parseImport = DImport <$ keyword "import" <*> ident
-- Do we do pattern stuff now? or just name = lambda?
export
parseDef : Parser Decl
parseDef = Def <$> ident <* keyword "=" <*> term
export
parseDecl : Parser Decl
parseDecl = parseSig <|> parseDef
parseDecl = parseImport <|> parseSig <|> parseDef
export
parseMod : Parser Module
@@ -176,7 +183,7 @@ parseMod = do
keyword "module"
name <- ident
-- probably should be manySame, and we want to start with col -1
-- if we enforce blocks indent
-- if we enforce blocks indent more than parent
decls <- startBlock $ someSame $ parseDecl
pure $ MkModule name [] decls

View File

@@ -44,6 +44,7 @@ parse pa toks = case runP pa toks False (0,0) of
OK a [] _ => Right a
OK a ts _ => Left "Extra toks \{show ts}"
-- I think I want to drop the typeclasses for v1
export
fail : String -> Parser a
@@ -147,11 +148,9 @@ indented (P p) = P $ \toks,com,(l,c) => case toks of
in if tc > c || tl == l then p toks com (l,c)
else Fail (E "unexpected outdent") toks com
export
token' : Kind -> Parser String
token' k = pred (\t => t.val.kind == k) "Expected a \{show k}"
token' k = pred (\t => t.val.kind == k) "Expected a \{show k} token"
export

View File

@@ -10,10 +10,12 @@ data Kind
| Number
| Symbol
| Space
| Comment
-- not doing Layout.idr
| LBrace
| Semi
| RBrace
| EOI
export
Show Kind where
@@ -26,6 +28,8 @@ Show Kind where
show LBrace = "LBrace"
show Semi = "Semi"
show RBrace = "RBrace"
show Comment = "Comment"
show EOI = "EOI"
export
Eq Kind where

View File

@@ -8,7 +8,7 @@ keywords : List String
keywords = ["let", "in", "where", "case", "of", "data"]
specialOps : List String
specialOps = ["->", ":"]
specialOps = ["->", ":", "=>"]
checkKW : String -> Token Kind
checkKW s = if elem s keywords then Tok Keyword s else Tok Ident s
@@ -19,20 +19,12 @@ isOpChar c = c `elem` (unpack ":!#$%&*+./<=>?@\\^|-~")
opChar : Lexer
opChar = pred isOpChar
-- so Text.Lexer.Core.lex is broken
-- tmap : TokenMap (Token Kind)
-- tmap = [
-- (alpha <+> many alphaNum, checkKW),
-- (some digit, Tok Number),
-- (some opChar, \s => Tok Oper s),
-- (lineComment (exact "--"), Tok Space),
-- (symbol, Tok Symbol),
-- (spaces, Tok Space)
-- ]
identMore : Lexer
identMore = alphaNum <|> exact "."
rawTokens : Tokenizer (Token Kind)
rawTokens
= match (alpha <+> many alphaNum) checkKW
= match (alpha <+> many identMore) checkKW
<|> match (some digit) (Tok Number)
<|> match (some opChar) (\s => Tok Oper s)
<|> match (lineComment (exact "--")) (Tok Space)
@@ -46,5 +38,3 @@ notSpace _ = True
export
tokenise : String -> List BTok
tokenise = filter notSpace . fst . lex rawTokens