aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/lang
diff options
context:
space:
mode:
authorEduardo Julian2017-11-27 02:09:04 -0400
committerEduardo Julian2017-11-27 02:09:04 -0400
commitd6a7a133c5c4a734ab45e9497c8e5df749ce383a (patch)
tree040b4df12dd3482fc0bb76f8e0a37126ef34fb34 /stdlib/source/lux/lang
parent6031fc715b4a16b008d6f288c38739d9bb066490 (diff)
- Changed the prefixes of numeric functions.
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/lang/syntax.lux64
-rw-r--r--stdlib/source/lux/lang/type.lux12
-rw-r--r--stdlib/source/lux/lang/type/check.lux20
3 files changed, 48 insertions, 48 deletions
diff --git a/stdlib/source/lux/lang/syntax.lux b/stdlib/source/lux/lang/syntax.lux
index ae20fd9b6..a0d65cc89 100644
--- a/stdlib/source/lux/lang/syntax.lux
+++ b/stdlib/source/lux/lang/syntax.lux
@@ -54,14 +54,14 @@
(-> Cursor (l;Lexer [Cursor Text]))
(p;either (do p;Monad<Parser>
[content (l;many (l;one-of white-space))]
- (wrap [(update@ #;column (n.+ (text;size content)) where)
+ (wrap [(update@ #;column (n/+ (text;size content)) where)
content]))
## New-lines must be handled as a separate case to ensure line
## information is handled properly.
(do p;Monad<Parser>
[content (l;many (l;one-of new-line))]
(wrap [(|> where
- (update@ #;line (n.+ (text;size content)))
+ (update@ #;line (n/+ (text;size content)))
(set@ #;column +0))
content]))
))
@@ -75,7 +75,7 @@
comment (l;some (l;none-of new-line))
_ (l;this new-line)]
(wrap [(|> where
- (update@ #;line n.inc)
+ (update@ #;line n/inc)
(set@ #;column +0))
comment])))
@@ -98,21 +98,21 @@
(do p;Monad<Parser>
[_ (l;this "#(")]
(loop [comment ""
- where (update@ #;column (n.+ +2) where)]
+ where (update@ #;column (n/+ +2) where)]
($_ p;either
## These are normal chunks of commented text.
(do @
[chunk (l;many (l;not comment-bound^))]
(recur (format comment chunk)
(|> where
- (update@ #;column (n.+ (text;size chunk))))))
+ (update@ #;column (n/+ (text;size chunk))))))
## This is a special rule to handle new-lines within
## comments properly.
(do @
[_ (l;this new-line)]
(recur (format comment new-line)
(|> where
- (update@ #;line n.inc)
+ (update@ #;line n/inc)
(set@ #;column +0))))
## This is the rule for handling nested sub-comments.
## Ultimately, the whole comment is just treated as text
@@ -127,7 +127,7 @@
## Finally, this is the rule for closing the comment.
(do @
[_ (l;this ")#")]
- (wrap [(update@ #;column (n.+ +2) where)
+ (wrap [(update@ #;column (n/+ +2) where)
comment]))
))))
@@ -184,7 +184,7 @@
[code (l;between +1 +4 l;hexadecimal)]
(wrap (case (|> code (format "+") (:: number;Hex@Codec<Text,Nat> decode))
(#;Right value)
- [(n.+ +2 (text;size code)) (text;from-code value)]
+ [(n/+ +2 (text;size code)) (text;from-code value)]
_
(undefined))))
@@ -219,7 +219,7 @@
(p;fail error)
(#;Right value)
- (wrap [(update@ #;column (n.+ (text;size chunk)) where)
+ (wrap [(update@ #;column (n/+ (text;size chunk)) where)
[where (<tag> value)]]))))]
[bool #;Bool
@@ -247,19 +247,19 @@
(do @
[normal (l;none-of "\\\"\n")]
(wrap [(|> where
- (update@ #;column n.inc))
+ (update@ #;column n/inc))
normal]))
## Must handle escaped
## chars separately.
(do @
[[chars-consumed char] escaped-char^]
(wrap [(|> where
- (update@ #;column (n.+ chars-consumed)))
+ (update@ #;column (n/+ chars-consumed)))
char]))))
_ (l;this "\"")
#let [char (maybe;assume (text;nth +0 char))]]
(wrap [(|> where'
- (update@ #;column n.inc))
+ (update@ #;column n/inc))
[where (#;Nat char)]])))
(def: (normal-nat where)
@@ -272,7 +272,7 @@
(p;fail error)
(#;Right value)
- (wrap [(update@ #;column (n.+ (text;size chunk)) where)
+ (wrap [(update@ #;column (n/+ (text;size chunk)) where)
[where (#;Nat value)]]))))
(def: #export (nat where)
@@ -298,7 +298,7 @@
(p;fail error)
(#;Right value)
- (wrap [(update@ #;column (n.+ (text;size chunk)) where)
+ (wrap [(update@ #;column (n/+ (text;size chunk)) where)
[where (#;Frac value)]]))))
(def: frac-ratio-fragment
@@ -323,11 +323,11 @@
_ (l;this? "/")
denominator frac-ratio-fragment
_ (p;assert "Denominator cannot be 0."
- (not (f.= 0.0 denominator)))]
+ (not (f/= 0.0 denominator)))]
(wrap (|> numerator
- (f.* (if signed? -1.0 1.0))
- (f./ denominator)))))]
- (wrap [(update@ #;column (n.+ (text;size chunk)) where)
+ (f/* (if signed? -1.0 1.0))
+ (f// denominator)))))]
+ (wrap [(update@ #;column (n/+ (text;size chunk)) where)
[where (#;Frac value)]])))
(def: #export (frac where)
@@ -350,7 +350,7 @@
## as many spaces as necessary to be column-aligned.
## This helps ensure that the formatting on the text in the
## source-code matches the formatting of the Text value.
- #let [offset-column (n.inc (get@ #;column where))]
+ #let [offset-column (n/inc (get@ #;column where))]
[where' text-read] (: (l;Lexer [Cursor Text])
## I must keep track of how much of the
## text body has been read, how far the
@@ -359,7 +359,7 @@
## processing normal text body.
(loop [text-read ""
where (|> where
- (update@ #;column n.inc))
+ (update@ #;column n/inc))
must-have-offset? false]
(p;either (if must-have-offset?
## If I'm at the start of a
@@ -371,7 +371,7 @@
(do @
[offset (l;many (l;one-of " "))
#let [offset-size (text;size offset)]]
- (if (n.>= offset-column offset-size)
+ (if (n/>= offset-column offset-size)
## Any extra offset
## becomes part of the
## text's body.
@@ -381,7 +381,7 @@
product;right
(format text-read))
(|> where
- (update@ #;column (n.+ offset-size)))
+ (update@ #;column (n/+ offset-size)))
false)
(p;fail (format "Each line of a multi-line text must have an appropriate offset!\n"
"Expected: " (%i (nat-to-int offset-column)) " columns.\n"
@@ -392,7 +392,7 @@
[normal (l;many (l;none-of "\\\"\n"))]
(recur (format text-read normal)
(|> where
- (update@ #;column (n.+ (text;size normal))))
+ (update@ #;column (n/+ (text;size normal))))
false))
## Must handle escaped
## chars separately.
@@ -400,13 +400,13 @@
[[chars-consumed char] escaped-char^]
(recur (format text-read char)
(|> where
- (update@ #;column (n.+ chars-consumed)))
+ (update@ #;column (n/+ chars-consumed)))
false))
## The text ends when it
## reaches the right-delimiter.
(do @
[_ (l;this "\"")]
- (wrap [(update@ #;column n.inc where)
+ (wrap [(update@ #;column n/inc where)
text-read]))))
## If a new-line is
## encountered, it gets
@@ -417,7 +417,7 @@
[_ (l;this new-line)]
(recur (format text-read new-line)
(|> where
- (update@ #;line n.inc)
+ (update@ #;line n/inc)
(set@ #;column +0))
true)))))]
(wrap [where'
@@ -448,7 +448,7 @@
## end-delimiter.
where' (left-padding^ where)
_ (l;this <close>)]
- (wrap [(update@ #;column n.inc where')
+ (wrap [(update@ #;column n/inc where')
(sequence;to-list elems)]))))]
(wrap [where'
[where (<tag> elems)]])))]
@@ -483,7 +483,7 @@
(do @
[where' (left-padding^ where)
_ (l;this "}")]
- (wrap [(update@ #;column n.inc where')
+ (wrap [(update@ #;column n/inc where')
(sequence;to-list elems)]))))]
(wrap [where'
[where (#;Record elems)]])))
@@ -535,7 +535,7 @@
[_ (l;this current-module-mark)
def-name ident-part^]
(wrap [[current-module def-name]
- (n.+ +2 (text;size def-name))]))
+ (n/+ +2 (text;size def-name))]))
## If the identifier is prefixed by the mark, but no module
## part, the module is assumed to be "lux" (otherwise known as
## the 'prelude').
@@ -546,7 +546,7 @@
[_ (l;this identifier-separator)
def-name ident-part^]
(wrap [["lux" def-name]
- (n.inc (text;size def-name))]))
+ (n/inc (text;size def-name))]))
## Not all identifiers must be specified with a module part.
## If that part is not provided, the identifier will be created
## with the empty "" text as the module.
@@ -563,7 +563,7 @@
second-part ident-part^]
(wrap [[(|> aliases (dict;get first-part) (maybe;default first-part))
second-part]
- ($_ n.+
+ ($_ n/+
(text;size first-part)
+1
(text;size second-part))]))
@@ -582,7 +582,7 @@
(-> Text Aliases Cursor (l;Lexer [Cursor Code]))
(do p;Monad<Parser>
[[value length] <lexer>]
- (wrap [(update@ #;column (|>. ($_ n.+ <extra> length)) where)
+ (wrap [(update@ #;column (|>. ($_ n/+ <extra> length)) where)
[where (<tag> value)]])))]
[symbol #;Symbol (ident^ current-module aliases) +0]
diff --git a/stdlib/source/lux/lang/type.lux b/stdlib/source/lux/lang/type.lux
index d4a3d7d1b..217320ab2 100644
--- a/stdlib/source/lux/lang/type.lux
+++ b/stdlib/source/lux/lang/type.lux
@@ -48,7 +48,7 @@
(case [x y]
[(#;Primitive xname xparams) (#;Primitive yname yparams)]
(and (text/= xname yname)
- (n.= (list;size yparams) (list;size xparams))
+ (n/= (list;size yparams) (list;size xparams))
(list/fold (;function [[x y] prev] (and prev (= x y)))
true
(list;zip2 xparams yparams)))
@@ -60,7 +60,7 @@
(^template [<tag>]
[(<tag> xid) (<tag> yid)]
- (n.= yid xid))
+ (n/= yid xid))
([#;Var] [#;Ex] [#;Bound])
(^or [(#;Function xleft xright) (#;Function yleft yright)]
@@ -79,7 +79,7 @@
(^or [(#;UnivQ xenv xbody) (#;UnivQ yenv ybody)]
[(#;ExQ xenv xbody) (#;ExQ yenv ybody)])
- (and (n.= (list;size yenv) (list;size xenv))
+ (and (n/= (list;size yenv) (list;size xenv))
(= xbody ybody)
(list/fold (;function [[x y] prev] (and prev (= x y)))
true
@@ -97,7 +97,7 @@
type type]
(case type
(<tag> env sub-type)
- (recur (n.inc num-args) sub-type)
+ (recur (n/inc num-args) sub-type)
_
[num-args type])))]
@@ -323,7 +323,7 @@
(-> Nat Type Type)
(case size
+0 body
- _ (<tag> (list) (<name> (n.dec size) body))))]
+ _ (<tag> (list) (<name> (n/dec size) body))))]
[univ-q #;UnivQ]
[ex-q #;ExQ]
@@ -351,4 +351,4 @@
(-> Nat Type Type)
(case level
+0 elem-type
- _ (#;Primitive "#Array" (list (array (n.dec level) elem-type)))))
+ _ (#;Primitive "#Array" (list (array (n/dec level) elem-type)))))
diff --git a/stdlib/source/lux/lang/type/check.lux b/stdlib/source/lux/lang/type/check.lux
index 086866ddf..9dc1a6565 100644
--- a/stdlib/source/lux/lang/type/check.lux
+++ b/stdlib/source/lux/lang/type/check.lux
@@ -96,7 +96,7 @@
(#;Cons [var-id var-type]
plist')
- (if (n.= id var-id)
+ (if (n/= id var-id)
(#;Some var-type)
(var::get id plist'))
))
@@ -109,7 +109,7 @@
(#;Cons [var-id var-type]
plist')
- (if (n.= id var-id)
+ (if (n/= id var-id)
(#;Cons [var-id value]
plist')
(#;Cons [var-id var-type]
@@ -124,7 +124,7 @@
(#;Cons [var-id var-type]
plist')
- (if (n.= id var-id)
+ (if (n/= id var-id)
plist'
(#;Cons [var-id var-type]
(var::remove id plist')))
@@ -150,7 +150,7 @@
(Check [Nat Type])
(function [context]
(let [id (get@ #;ex-counter context)]
- (#e;Success [(update@ #;ex-counter n.inc context)
+ (#e;Success [(update@ #;ex-counter n/inc context)
[id (#;Ex id)]]))))
(do-template [<name> <outputT> <fail> <succeed>]
@@ -219,7 +219,7 @@
(function [context]
(let [id (get@ #;var-counter context)]
(#e;Success [(|> context
- (update@ #;var-counter n.inc)
+ (update@ #;var-counter n/inc)
(update@ #;var-bindings (var::put id #;None)))
[id (#;Var id)]]))))
@@ -270,7 +270,7 @@
(#;Some (#;Some type))
(case type
(#;Var post)
- (if (n.= id post)
+ (if (n/= id post)
(#e;Success [context output])
(recur post (set;add post output)))
@@ -344,7 +344,7 @@
then)
(do Monad<Check>
[ring (ring id)
- _ (assert "" (n.> +1 (set;size ring)))
+ _ (assert "" (n/> +1 (set;size ring)))
_ (monad;map @ (update type) (set;to-list ring))]
then)
(do Monad<Check>
@@ -368,7 +368,7 @@
(List Assumption)
Var Var
(Check (List Assumption)))
- (if (n.= idE idA)
+ (if (n/= idE idA)
(check/wrap assumptions)
(do Monad<Check>
[ebound (attempt (peek idE))
@@ -576,7 +576,7 @@
[(#;Primitive e-name e-params) (#;Primitive a-name a-params)]
(if (and (text/= e-name a-name)
- (n.= (list;size e-params)
+ (n/= (list;size e-params)
(list;size a-params)))
(do Monad<Check>
[assumptions (monad;fold Monad<Check>
@@ -603,7 +603,7 @@
(check' eO aO assumptions))
[(#;Ex e!id) (#;Ex a!id)]
- (if (n.= e!id a!id)
+ (if (n/= e!id a!id)
(check/wrap assumptions)
(fail ""))