From 9e2f1e76f2c8df01ed7687d934c3210fcf676bd6 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Thu, 16 Jun 2022 00:48:19 -0400 Subject: De-sigil-ification: suffix : [Part 13] --- stdlib/source/parser/lux/data/binary.lux | 58 ++++++++-------- stdlib/source/parser/lux/data/text.lux | 80 +++++++++++----------- .../lux/tool/compiler/language/lux/analysis.lux | 16 ++--- .../lux/tool/compiler/language/lux/synthesis.lux | 18 ++--- 4 files changed, 86 insertions(+), 86 deletions(-) (limited to 'stdlib/source/parser') diff --git a/stdlib/source/parser/lux/data/binary.lux b/stdlib/source/parser/lux/data/binary.lux index d09eeba86..117f07a34 100644 --- a/stdlib/source/parser/lux/data/binary.lux +++ b/stdlib/source/parser/lux/data/binary.lux @@ -44,7 +44,7 @@ "Bytes read" (%.nat bytes_read))) (with_template [ ] - [(def: + [(def (template ( ) [( )]))] @@ -53,7 +53,7 @@ [n#- "lux i64 -"] ) -(def: .public (result parser input) +(def .public (result parser input) (All (_ a) (-> (Parser a) Binary (Try a))) (case (parser [0 input]) {try.#Success [[end _] output]} @@ -65,17 +65,17 @@ failure (as_expected failure))) -(def: .public end? +(def .public end? (Parser Bit) (function (_ (^.let input [offset data])) {try.#Success [input (n#= offset (/.size data))]})) -(def: .public offset +(def .public offset (Parser Offset) (function (_ (^.let input [offset data])) {try.#Success [input offset]})) -(def: .public remaining +(def .public remaining (Parser Nat) (function (_ (^.let input [offset data])) {try.#Success [input (n#- offset (/.size data))]})) @@ -83,10 +83,10 @@ (type: .public Size Nat) -(def: .public size_8 Size 1) -(def: .public size_16 Size (n.* 2 size_8)) -(def: .public size_32 Size (n.* 2 size_16)) -(def: .public size_64 Size (n.* 2 size_32)) +(def .public size_8 Size 1) +(def .public size_16 Size (n.* 2 size_8)) +(def .public size_32 Size (n.* 2 size_16)) +(def .public size_64 Size (n.* 2 size_32)) (exception: .public (range_out_of_bounds [length Nat start Nat @@ -97,7 +97,7 @@ "Range end" (%.nat end))) (with_template [ ] - [(def: .public + [(def .public (Parser I64) (function (_ [start binary]) (let [end (n#+ start)] @@ -114,14 +114,14 @@ ) (with_template [ ] - [(def: .public (Parser ) ..bits_64)] + [(def .public (Parser ) ..bits_64)] [nat Nat] [int Int] [rev Rev] ) -(def: .public frac +(def .public frac (Parser Frac) (//#each frac.of_bits ..bits_64)) @@ -131,7 +131,7 @@ "Tag range" (%.nat range) "Tag value" (%.nat byte))) -(def: !variant +(def !variant (template (!variant +) [(do [! //.monad] [flag (is (Parser Nat) @@ -144,18 +144,18 @@ _ (//.lifted (exception.except ..invalid_tag [(template.amount [+]) flag])))))])) -(def: .public (or left right) +(def .public (or left right) (All (_ l r) (-> (Parser l) (Parser r) (Parser (Or l r)))) (!variant [[0 [.#Left] left] [1 [.#Right] right]])) -(def: .public (rec body) +(def .public (rec body) (All (_ a) (-> (-> (Parser a) (Parser a)) (Parser a))) (function (_ input) (let [parser (body (rec body))] (parser input)))) -(def: .public any +(def .public any (Parser Any) (//#in [])) @@ -164,7 +164,7 @@ "Expected values" "either 0 or 1" "Actual value" (%.nat value))) -(def: .public bit +(def .public bit (Parser Bit) (do //.monad [value (is (Parser Nat) @@ -174,7 +174,7 @@ 1 (in #1) _ (//.lifted (exception.except ..not_a_bit [value]))))) -(def: .public (segment size) +(def .public (segment size) (-> Nat (Parser Binary)) (case size 0 (//#in (/.empty 0)) @@ -188,7 +188,7 @@ {try.#Success})))))) (with_template [ ] - [(`` (def: .public + [(`` (def .public (Parser Binary) (do //.monad [size (//#each (|>> .nat) )] @@ -201,7 +201,7 @@ ) (with_template [ ] - [(`` (def: .public + [(`` (def .public (Parser Text) (do //.monad [utf8 ] @@ -213,10 +213,10 @@ [64 utf8_64 ..binary_64] ) -(def: .public text ..utf8_64) +(def .public text ..utf8_64) (with_template [ ] - [(def: .public ( valueP) + [(def .public ( valueP) (All (_ v) (-> (Parser v) (Parser (Sequence v)))) (do //.monad [amount (is (Parser Nat) @@ -240,11 +240,11 @@ [64 sequence_64 ..bits_64] ) -(def: .public maybe +(def .public maybe (All (_ a) (-> (Parser a) (Parser (Maybe a)))) (..or ..any)) -(def: .public (list value) +(def .public (list value) (All (_ a) (-> (Parser a) (Parser (List a)))) (..rec (|>> (//.and value) @@ -252,7 +252,7 @@ (exception: .public set_elements_are_not_unique) -(def: .public (set hash value) +(def .public (set hash value) (All (_ a) (-> (Hash a) (Parser a) (Parser (Set a)))) (do //.monad [raw (..list value) @@ -262,11 +262,11 @@ (set.size output)))] (in output))) -(def: .public symbol +(def .public symbol (Parser Symbol) (//.and ..text ..text)) -(def: .public type +(def .public type (Parser Type) (..rec (function (_ type) @@ -285,11 +285,11 @@ [9 [.#Apply] pair] [10 [.#Named] (//.and ..symbol type)]]))))) -(def: .public location +(def .public location (Parser Location) (all //.and ..text ..nat ..nat)) -(def: .public code +(def .public code (Parser Code) (..rec (function (_ again) diff --git a/stdlib/source/parser/lux/data/text.lux b/stdlib/source/parser/lux/data/text.lux index e02733f77..b6d86b35a 100644 --- a/stdlib/source/parser/lux/data/text.lux +++ b/stdlib/source/parser/lux/data/text.lux @@ -24,7 +24,7 @@ (type: .public Offset Nat) -(def: beginning +(def beginning Offset 0) @@ -39,7 +39,7 @@ [#basis Offset #distance Offset])) -(def: .public (slice parser) +(def .public (slice parser) (-> (Parser Slice) (Parser Text)) (do //.monad [[basis distance] parser] @@ -51,7 +51,7 @@ {.#None} (exception.except ..cannot_slice []))))) -(def: (left_over offset tape) +(def (left_over offset tape) (-> Offset Text Text) (|> tape (/.clip_since offset) maybe.trusted)) @@ -68,7 +68,7 @@ "Offset" (n#encoded offset) "Input" (..left_over offset tape))) -(def: .public (result parser input) +(def .public (result parser input) (All (_ a) (-> (Parser a) Text (Try a))) (case (parser [..beginning input]) {try.#Failure msg} @@ -79,12 +79,12 @@ {try.#Success output} (exception.except ..unconsumed_input [end_offset input])))) -(def: .public offset +(def .public offset (Parser Offset) (function (_ (^.let input [offset tape])) {try.#Success [input offset]})) -(def: (with_slices parser) +(def (with_slices parser) (-> (Parser (List Slice)) (Parser Slice)) (do //.monad [offset ..offset @@ -96,7 +96,7 @@ #distance 0] slices)))) -(def: .public any +(def .public any (Parser Text) (function (_ [offset tape]) (case (/.char offset tape) @@ -106,7 +106,7 @@ _ (exception.except ..cannot_parse [])))) -(def: .public any! +(def .public any! (Parser Slice) (function (_ [offset tape]) (case (/.char offset tape) @@ -119,7 +119,7 @@ (exception.except ..cannot_slice [])))) (with_template [ ] - [(`` (def: .public ( parser) + [(`` (def .public ( parser) (All (_ a) (-> (Parser a) (Parser ))) (function (_ input) (case (parser input) @@ -137,7 +137,7 @@ (exception.report "Reference" (/.format reference))) -(def: .public (this reference) +(def .public (this reference) (-> Text (Parser Any)) (function (_ [offset tape]) (case (/.index_since offset reference tape) @@ -150,14 +150,14 @@ _ (exception.except ..cannot_match [reference])))) -(def: .public end +(def .public end (Parser Any) (function (_ (^.let input [offset tape])) (if (n.= offset (/.size tape)) {try.#Success [input []]} (exception.except ..unconsumed_input input)))) -(def: .public next +(def .public next (Parser Text) (function (_ (^.let input [offset tape])) (case (/.char offset tape) @@ -167,12 +167,12 @@ _ (exception.except ..cannot_parse [])))) -(def: .public remaining +(def .public remaining (Parser Text) (function (_ (^.let input [offset tape])) {try.#Success [input (..left_over offset tape)]})) -(def: .public (range bottom top) +(def .public (range bottom top) (-> Nat Nat (Parser Text)) (do //.monad [char any @@ -182,7 +182,7 @@ (n.<= top char')))] (in char))) -(def: .public (range! bottom top) +(def .public (range! bottom top) (-> Nat Nat (Parser Slice)) (do //.monad [it ..any! @@ -194,11 +194,11 @@ (in it))) (with_template [ ] - [(def: .public + [(def .public (Parser Text) (..range (char ) (char ))) - (def: .public + (def .public (Parser Slice) (..range! (char ) (char )))] @@ -208,20 +208,20 @@ ["0" "7" octal octal!] ) -(def: .public alpha (Parser Text) (//.either ..lower ..upper)) -(def: .public alpha! (Parser Slice) (//.either ..lower! ..upper!)) +(def .public alpha (Parser Text) (//.either ..lower ..upper)) +(def .public alpha! (Parser Slice) (//.either ..lower! ..upper!)) -(def: .public alpha_num (Parser Text) (//.either ..alpha ..decimal)) -(def: .public alpha_num! (Parser Slice) (//.either ..alpha! ..decimal!)) +(def .public alpha_num (Parser Text) (//.either ..alpha ..decimal)) +(def .public alpha_num! (Parser Slice) (//.either ..alpha! ..decimal!)) -(def: .public hexadecimal +(def .public hexadecimal (Parser Text) (all //.either ..decimal (..range (char "a") (char "f")) (..range (char "A") (char "F")))) -(def: .public hexadecimal! +(def .public hexadecimal! (Parser Slice) (all //.either ..decimal! @@ -240,7 +240,7 @@ ) (with_template [ ] - [(def: .public ( options) + [(def .public ( options) (-> Text (Parser Text)) (function (_ [offset tape]) (case (/.char offset tape) @@ -258,7 +258,7 @@ ) (with_template [ ] - [(def: .public ( options) + [(def .public ( options) (-> Text (Parser Slice)) (function (_ [offset tape]) (case (/.char offset tape) @@ -281,7 +281,7 @@ (exception.report "Character" (/.format (/.of_char character)))) -(def: .public (satisfies parser) +(def .public (satisfies parser) (-> (-> Char Bit) (Parser Text)) (function (_ [offset tape]) (case (/.char offset tape) @@ -293,7 +293,7 @@ _ (exception.except ..cannot_parse [])))) -(def: .public (satisfies! parser) +(def .public (satisfies! parser) (-> (-> Char Bit) (Parser Slice)) (function (_ [offset tape]) (case (/.char offset tape) @@ -306,22 +306,22 @@ _ (exception.except ..cannot_parse [])))) -(def: .public space +(def .public space (Parser Text) (..satisfies /.space?)) -(def: .public space! +(def .public space! (Parser Slice) (..satisfies! /.space?)) -(def: .public (and left right) +(def .public (and left right) (-> (Parser Text) (Parser Text) (Parser Text)) (do //.monad [=left left =right right] (in (all /#composite =left =right)))) -(def: .public (and! left right) +(def .public (and! left right) (-> (Parser Slice) (Parser Slice) (Parser Slice)) (do //.monad [(open "left[0]") left @@ -329,7 +329,7 @@ (in [left#basis ("lux i64 +" left#distance right#distance)]))) (with_template [ ] - [(def: .public ( parser) + [(def .public ( parser) (-> (Parser Text) (Parser Text)) (|> parser (at //.monad each /.together)))] @@ -338,7 +338,7 @@ ) (with_template [ ] - [(def: .public ( parser) + [(def .public ( parser) (-> (Parser Slice) (Parser Slice)) (with_slices ( parser)))] @@ -347,7 +347,7 @@ ) (with_template [ ] - [(def: .public ( amount parser) + [(def .public ( amount parser) (-> Nat (Parser Text) (Parser Text)) (|> parser ( amount) @@ -359,7 +359,7 @@ ) (with_template [ ] - [(def: .public ( amount parser) + [(def .public ( amount parser) (-> Nat (Parser Slice) (Parser Slice)) (with_slices ( amount parser)))] @@ -369,24 +369,24 @@ [at_least! //.at_least "at least"] ) -(def: .public (between minimum additional parser) +(def .public (between minimum additional parser) (-> Nat Nat (Parser Text) (Parser Text)) (|> parser (//.between minimum additional) (at //.monad each /.together))) -(def: .public (between! minimum additional parser) +(def .public (between! minimum additional parser) (-> Nat Nat (Parser Slice) (Parser Slice)) (with_slices (//.between minimum additional parser))) -(def: .public (enclosed [start end] parser) +(def .public (enclosed [start end] parser) (All (_ a) (-> [Text Text] (Parser a) (Parser a))) (|> parser (//.before (this end)) (//.after (this start)))) -(def: .public (local local_input parser) +(def .public (local local_input parser) (All (_ a) (-> Text (Parser a) (Parser a))) (function (_ real_input) (case (..result parser local_input) @@ -396,7 +396,7 @@ {try.#Success value} {try.#Success [real_input value]}))) -(def: .public (then structured text) +(def .public (then structured text) (All (_ s a) (-> (Parser a) (//.Parser s Text) diff --git a/stdlib/source/parser/lux/tool/compiler/language/lux/analysis.lux b/stdlib/source/parser/lux/tool/compiler/language/lux/analysis.lux index 3a298ba27..eb2695e96 100644 --- a/stdlib/source/parser/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/parser/lux/tool/compiler/language/lux/analysis.lux @@ -31,7 +31,7 @@ [variable (.only)]]]]]] ["/" \\library (.only Environment Analysis)]) -(def: (remaining_inputs asts) +(def (remaining_inputs asts) (-> (List Analysis) Text) (format text.new_line "Remaining input: " (|> asts @@ -49,7 +49,7 @@ (type: .public Parser (//.Parser (List Analysis))) -(def: .public (result parser input) +(def .public (result parser input) (All (_ a) (-> (Parser a) (List Analysis) (Try a))) (case (parser input) {try.#Failure error} @@ -61,7 +61,7 @@ {try.#Success [unconsumed _]} (exception.except ..unconsumed_input unconsumed))) -(def: .public any +(def .public any (Parser Analysis) (function (_ input) (case input @@ -71,7 +71,7 @@ {.#Item [head tail]} {try.#Success [tail head]}))) -(def: .public end +(def .public end (Parser Any) (function (_ tokens) (case tokens @@ -79,7 +79,7 @@ _ {try.#Failure (format "Expected list of tokens to be empty!" (remaining_inputs tokens))}))) -(def: .public end? +(def .public end? (Parser Bit) (function (_ tokens) {try.#Success [tokens (case tokens @@ -87,7 +87,7 @@ _ false)]})) (with_template [ ] - [(`` (these (def: .public + [(`` (these (def .public (Parser ) (function (_ input) (case input @@ -97,7 +97,7 @@ _ (exception.except ..cannot_parse input)))) - (def: .public ( expected) + (def .public ( expected) (-> (Parser Any)) (function (_ input) (case input @@ -120,7 +120,7 @@ [constant this_constant /.constant Symbol symbol.equivalence] ) -(def: .public (tuple parser) +(def .public (tuple parser) (All (_ a) (-> (Parser a) (Parser a))) (function (_ input) (case input diff --git a/stdlib/source/parser/lux/tool/compiler/language/lux/synthesis.lux b/stdlib/source/parser/lux/tool/compiler/language/lux/synthesis.lux index c6537531f..535e03cc0 100644 --- a/stdlib/source/parser/lux/tool/compiler/language/lux/synthesis.lux +++ b/stdlib/source/parser/lux/tool/compiler/language/lux/synthesis.lux @@ -54,7 +54,7 @@ (type: .public Parser (//.Parser (List Synthesis))) -(def: .public (result parser input) +(def .public (result parser input) (All (_ a) (-> (Parser a) (List Synthesis) (Try a))) (case (parser input) {try.#Failure error} @@ -66,7 +66,7 @@ {try.#Success [unconsumed _]} (exception.except ..unconsumed_input unconsumed))) -(def: .public any +(def .public any (Parser Synthesis) (.function (_ input) (case input @@ -76,14 +76,14 @@ {.#Item [head tail]} {try.#Success [tail head]}))) -(def: .public end +(def .public end (Parser Any) (.function (_ tokens) (case tokens {.#End} {try.#Success [tokens []]} _ (exception.except ..expected_empty_input [tokens])))) -(def: .public end? +(def .public end? (Parser Bit) (.function (_ tokens) {try.#Success [tokens (case tokens @@ -91,7 +91,7 @@ _ false)]})) (with_template [ ] - [(`` (def: .public + [(`` (def .public (Parser ) (.function (_ input) (case input @@ -101,7 +101,7 @@ _ (exception.except ..cannot_parse input))))) - (`` (def: .public ( expected) + (`` (def .public ( expected) (-> (Parser Any)) (.function (_ input) (case input @@ -122,7 +122,7 @@ [constant this_constant /.constant Symbol symbol.equivalence] ) -(def: .public (tuple parser) +(def .public (tuple parser) (All (_ a) (-> (Parser a) (Parser a))) (.function (_ input) (case input @@ -134,7 +134,7 @@ _ (exception.except ..cannot_parse input)))) -(def: .public (function expected parser) +(def .public (function expected parser) (All (_ a) (-> Arity (Parser a) (Parser [(Environment Synthesis) a]))) (.function (_ input) (case input @@ -148,7 +148,7 @@ _ (exception.except ..cannot_parse input)))) -(def: .public (loop init_parsers iteration_parser) +(def .public (loop init_parsers iteration_parser) (All (_ a b) (-> (Parser a) (Parser b) (Parser [Register a b]))) (.function (_ input) (case input -- cgit v1.2.3