From 3b80f40384a8af8770a7c4f1be8b334ceb950a27 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Tue, 8 May 2018 23:07:21 -0400 Subject: - Improved the way Bool values are parsed. --- stdlib/source/lux/lang/syntax.lux | 50 +++++++++++++++++---------------------- 1 file changed, 22 insertions(+), 28 deletions(-) (limited to 'stdlib/source') diff --git a/stdlib/source/lux/lang/syntax.lux b/stdlib/source/lux/lang/syntax.lux index d30436533..6c7236f76 100644 --- a/stdlib/source/lux/lang/syntax.lux +++ b/stdlib/source/lux/lang/syntax.lux @@ -29,8 +29,7 @@ (lux (control monad ["p" parser "p/" Monad] ["ex" exception #+ exception:]) - (data [bool] - ["e" error] + (data ["e" error] [number] [product] [maybe] @@ -205,10 +204,6 @@ (l.seq l.decimal (l.some rich-digit))) -(def: (marker^ token) - (-> Text (l.Lexer Text)) - (p.after (l.this token) (p/wrap token))) - (do-template [ ] [(def: #export ( where) (-> Cursor (l.Lexer [Cursor Code])) @@ -222,10 +217,6 @@ (wrap [(update@ #.column (n/+ (text.size chunk)) where) [where ( value)]]))))] - [bool #.Bool - (p.either (marker^ "true") (marker^ "false")) - bool.Codec] - [int #.Int (l.seq (p.default "" (l.one-of "-")) rich-digits^) @@ -570,24 +561,28 @@ (wrap [["" first-part] (text.size first-part)]))))) -## The only (syntactic) difference between a symbol and a tag (both -## being identifiers), is that tags must be prefixed with a hash-sign -## (i.e. #). -## Semantically, though, they are very different, with symbols being -## used to refer to module definitions and local variables, while tags -## provide the compiler with information related to data-structure -## construction and de-structuring (during pattern-matching). -(do-template [ ] - [(def: #export ( current-module aliases where) - (-> Text Aliases Cursor (l.Lexer [Cursor Code])) - (do p.Monad - [[value length] ] - (wrap [(update@ #.column (|>> ($_ n/+ length)) where) - [where ( value)]])))] +(def: #export (tag current-module aliases where) + (-> Text Aliases Cursor (l.Lexer [Cursor Code])) + (do p.Monad + [[value length] (p.after (l.this "#") + (ident^ current-module aliases))] + (wrap [(update@ #.column (|>> ($_ n/+ +1 length)) where) + [where (#.Tag value)]]))) - [symbol #.Symbol (ident^ current-module aliases) +0] - [tag #.Tag (p.after (l.this "#") (ident^ current-module aliases)) +1] - ) +(def: #export (symbol current-module aliases where) + (-> Text Aliases Cursor (l.Lexer [Cursor Code])) + (do p.Monad + [[value length] (ident^ current-module aliases)] + (wrap [(update@ #.column (|>> (n/+ length)) where) + [where (case value + (^template [ ] + ["" ] + (#.Bool )) + (["true" true] + ["false" false]) + + _ + (#.Symbol value))]]))) (exception: #export (end-of-file {module Text}) module) @@ -607,7 +602,6 @@ (form where ast') (tuple where ast') (record where ast') - (bool where) (nat where) (frac where) (int where) -- cgit v1.2.3