diff options
Diffstat (limited to 'stdlib/source/lux/control/parser')
-rw-r--r-- | stdlib/source/lux/control/parser/binary.lux | 9 | ||||
-rw-r--r-- | stdlib/source/lux/control/parser/synthesis.lux | 10 | ||||
-rw-r--r-- | stdlib/source/lux/control/parser/text.lux | 22 | ||||
-rw-r--r-- | stdlib/source/lux/control/parser/type.lux | 34 |
4 files changed, 38 insertions, 37 deletions
diff --git a/stdlib/source/lux/control/parser/binary.lux b/stdlib/source/lux/control/parser/binary.lux index 2912e0a52..fed4370bf 100644 --- a/stdlib/source/lux/control/parser/binary.lux +++ b/stdlib/source/lux/control/parser/binary.lux @@ -9,6 +9,7 @@ [data ["." binary (#+ Binary)] [number + ["n" nat] ["." frac]] [text ["." encoding] @@ -35,7 +36,7 @@ (#try.Success [[end _] output]) (let [length (binary.size input)] - (if (n/= end length) + (if (n.= end length) (#try.Success output) (exception.throw ..binary-was-not-fully-read [length end]))))) @@ -52,7 +53,7 @@ (function (_ [offset binary]) (case (<read> offset binary) (#try.Success data) - (#try.Success [(n/+ <size> offset) binary] data) + (#try.Success [(n.+ <size> offset) binary] data) (#try.Failure error) (#try.Failure error))))] @@ -114,7 +115,7 @@ [size (//@map .nat <bits>)] (function (_ [offset binary]) (do try.monad - [#let [end (n/+ size offset)] + [#let [end (n.+ size offset)] output (binary.slice offset (.dec end) binary)] (wrap [[end binary] output])))))] @@ -150,7 +151,7 @@ valueP} {(Row v) row.empty})] - (if (n/< count index) + (if (n.< count index) (do //.monad [value valueP] (recur (.inc index) diff --git a/stdlib/source/lux/control/parser/synthesis.lux b/stdlib/source/lux/control/parser/synthesis.lux index 784f08698..1b0a38acd 100644 --- a/stdlib/source/lux/control/parser/synthesis.lux +++ b/stdlib/source/lux/control/parser/synthesis.lux @@ -10,8 +10,8 @@ ["." name] [number ["." i64] - ["." frac] - ["." nat]] + ["n" nat] + ["." frac]] ["." text ["%" format (#+ format)]]] [tool @@ -89,8 +89,8 @@ [i64 i64! /.i64 (I64 Any) i64.equivalence] [f64 f64! /.f64 Frac frac.equivalence] [text text! /.text Text text.equivalence] - [local local! /.variable/local Nat nat.equivalence] - [foreign foreign! /.variable/foreign Nat nat.equivalence] + [local local! /.variable/local Nat n.equivalence] + [foreign foreign! /.variable/foreign Nat n.equivalence] [constant constant! /.constant Name name.equivalence] ) @@ -111,7 +111,7 @@ (.function (_ input) (case input (^ (list& (/.function/abstraction [environment actual body]) tail)) - (if (n/= expected actual) + (if (n.= expected actual) (do try.monad [output (..run (list body) parser)] (#try.Success [tail [environment output]])) diff --git a/stdlib/source/lux/control/parser/text.lux b/stdlib/source/lux/control/parser/text.lux index 0e57f02f6..bec295f39 100644 --- a/stdlib/source/lux/control/parser/text.lux +++ b/stdlib/source/lux/control/parser/text.lux @@ -10,7 +10,7 @@ ["." maybe] ["/" text ("#@." monoid)] [number - ["." nat ("#@." decimal)]] + ["n" nat ("#@." decimal)]] [collection ["." list ("#@." fold)]]] [macro @@ -34,13 +34,13 @@ (exception: #export (unconsumed-input {offset Offset} {tape Text}) (exception.report - ["Offset" (nat@encode offset)] - ["Input size" (nat@encode (/.size tape))] + ["Offset" (n@encode offset)] + ["Input size" (n@encode (/.size tape))] ["Remaining input" (remaining offset tape)])) (exception: #export (expected-to-fail {offset Offset} {tape Text}) (exception.report - ["Offset" (nat@encode offset)] + ["Offset" (n@encode offset)] ["Input" (remaining offset tape)])) (exception: #export cannot-parse) @@ -53,7 +53,7 @@ (#try.Failure msg) (#try.Success [[end-offset _] output]) - (if (n/= end-offset (/.size input)) + (if (n.= end-offset (/.size input)) (#try.Success output) (exception.throw ..unconsumed-input [end-offset input])))) @@ -115,7 +115,7 @@ (function (_ [offset tape]) (case (/.index-of' reference offset tape) (#.Some where) - (if (n/= offset where) + (if (n.= offset where) (#try.Success [[("lux i64 +" (/.size reference) offset) tape] []]) (#try.Failure ($_ /@compose "Could not match: " (/.encode reference) " @ " (maybe.assume (/.clip' offset tape))))) @@ -128,7 +128,7 @@ (-> Text (Parser Bit)) (function (_ (^@ input [offset tape])) (case (/.index-of' reference offset tape) - (^multi (#.Some where) (n/= offset where)) + (^multi (#.Some where) (n.= offset where)) (#try.Success [[("lux i64 +" (/.size reference) offset) tape] #1]) @@ -139,7 +139,7 @@ {#.doc "Ensure the parser's input is empty."} (Parser Any) (function (_ (^@ input [offset tape])) - (if (n/= offset (/.size tape)) + (if (n.= offset (/.size tape)) (#try.Success [input []]) (exception.throw ..unconsumed-input input)))) @@ -147,7 +147,7 @@ {#.doc "Ask if the parser's input is empty."} (Parser Bit) (function (_ (^@ input [offset tape])) - (#try.Success [input (n/= offset (/.size tape))]))) + (#try.Success [input (n.= offset (/.size tape))]))) (def: #export peek {#.doc "Lex the next character (without consuming it from the input)."} @@ -173,8 +173,8 @@ [char any #let [char' (maybe.assume (/.nth 0 char))] _ (//.assert ($_ /@compose "Character is not within range: " (/.from-code bottom) "-" (/.from-code top)) - (.and (n/>= bottom char') - (n/<= top char')))] + (.and (n.>= bottom char') + (n.<= top char')))] (wrap char))) (template [<name> <bottom> <top> <desc>] diff --git a/stdlib/source/lux/control/parser/type.lux b/stdlib/source/lux/control/parser/type.lux index 6e42cad87..dc3f101f3 100644 --- a/stdlib/source/lux/control/parser/type.lux +++ b/stdlib/source/lux/control/parser/type.lux @@ -9,7 +9,7 @@ [data ["." name ("#@." codec)] [number - ["." nat ("#@." decimal)]] + ["n" nat ("#@." decimal)]] ["." text ("#@." monoid) ["%" format (#+ format)]] [collection @@ -60,7 +60,7 @@ (type: #export (Parser a) (//.Parser [Env (List Type)] a)) -(def: #export fresh Env (dictionary.new nat.hash)) +(def: #export fresh Env (dictionary.new n.hash)) (def: (run' env types poly) (All [a] (-> Env (List Type) (Parser a) (Try a))) @@ -127,7 +127,7 @@ (def: (label idx) (-> Nat Code) - (code.local-identifier ($_ text@compose "label" text.tab (nat@encode idx)))) + (code.local-identifier ($_ text@compose "label" text.tab (n@encode idx)))) (def: #export (with-extension type poly) (All [a] (-> Type (Parser a) (Parser [Code a]))) @@ -149,7 +149,7 @@ (do //.monad [headT any] (let [members (<flattener> (type.un-name headT))] - (if (n/> 1 (list.size members)) + (if (n.> 1 (list.size members)) (local members poly) (//.fail (exception.construct <exception> headT))))))] @@ -162,7 +162,7 @@ (do //.monad [headT any #let [[num-arg bodyT] (type.flatten-univ-q (type.un-name headT))]] - (if (n/= 0 num-arg) + (if (n.= 0 num-arg) (//.fail (exception.construct not-polymorphic headT)) (wrap [num-arg bodyT])))) @@ -177,19 +177,19 @@ [all-varsL env'] (loop [current-arg 0 env' env all-varsL (: (List Code) (list))] - (if (n/< num-args current-arg) - (if (n/= 0 current-arg) + (if (n.< num-args current-arg) + (if (n.= 0 current-arg) (let [varL (label (inc funcI))] (recur (inc current-arg) (|> env' (dictionary.put funcI [headT funcL]) (dictionary.put (inc funcI) [(#.Parameter (inc funcI)) varL])) (#.Cons varL all-varsL))) - (let [partialI (|> current-arg (n/* 2) (n/+ funcI)) + (let [partialI (|> current-arg (n.* 2) (n.+ funcI)) partial-varI (inc partialI) partial-varL (label partial-varI) partialC (` ((~ funcL) (~+ (|> (list.indices num-args) - (list@map (|>> (n/* 2) inc (n/+ funcI) label)) + (list@map (|>> (n.* 2) inc (n.+ funcI) label)) list.reverse))))] (recur (inc current-arg) (|> env' @@ -208,7 +208,7 @@ (do //.monad [headT any #let [[inputsT outputT] (type.flatten-function (type.un-name headT))]] - (if (n/> 0 (list.size inputsT)) + (if (n.> 0 (list.size inputsT)) (//.and (local inputsT in-poly) (local (list outputT) out-poly)) (//.fail (exception.construct not-function headT))))) @@ -218,7 +218,7 @@ (do //.monad [headT any #let [[funcT paramsT] (type.flatten-application (type.un-name headT))]] - (if (n/= 0 (list.size paramsT)) + (if (n.= 0 (list.size paramsT)) (//.fail (exception.construct not-application headT)) (local (#.Cons funcT paramsT) poly)))) @@ -238,10 +238,10 @@ (def: #export (adjusted-idx env idx) (-> Env Nat Nat) - (let [env-level (n// 2 (dictionary.size env)) - parameter-level (n// 2 idx) - parameter-idx (n/% 2 idx)] - (|> env-level dec (n/- parameter-level) (n/* 2) (n/+ parameter-idx)))) + (let [env-level (n./ 2 (dictionary.size env)) + parameter-level (n./ 2 idx) + parameter-idx (n.% 2 idx)] + (|> env-level dec (n.- parameter-level) (n.* 2) (n.+ parameter-idx)))) (def: #export parameter (Parser Code) @@ -267,7 +267,7 @@ headT any] (case headT (#.Parameter idx) - (if (n/= id (adjusted-idx env idx)) + (if (n.= id (adjusted-idx env idx)) (wrap []) (//.fail (exception.construct wrong-parameter [(#.Parameter id) headT]))) @@ -319,7 +319,7 @@ headT any] (case (type.un-name headT) (^multi (#.Apply (#.Named ["lux" "Nothing"] _) (#.Parameter funcT-idx)) - (n/= 0 (adjusted-idx env funcT-idx)) + (n.= 0 (adjusted-idx env funcT-idx)) [(dictionary.get 0 env) (#.Some [self-type self-call])]) (wrap self-call) |