aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/data
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/lux/data')
-rw-r--r--stdlib/source/lux/data/bool.lux5
-rw-r--r--stdlib/source/lux/data/coll/array.lux2
-rw-r--r--stdlib/source/lux/data/coll/list.lux28
-rw-r--r--stdlib/source/lux/data/coll/ordered/set.lux2
-rw-r--r--stdlib/source/lux/data/ident.lux16
-rw-r--r--stdlib/source/lux/data/number.lux2
-rw-r--r--stdlib/source/lux/data/text.lux4
-rw-r--r--stdlib/source/lux/data/text/regex.lux122
-rw-r--r--stdlib/source/lux/data/trace.lux15
9 files changed, 99 insertions, 97 deletions
diff --git a/stdlib/source/lux/data/bool.lux b/stdlib/source/lux/data/bool.lux
index c5b345ce1..e737c6118 100644
--- a/stdlib/source/lux/data/bool.lux
+++ b/stdlib/source/lux/data/bool.lux
@@ -3,7 +3,8 @@
(lux (control [monoid #+ Monoid]
[eq #+ Eq]
hash
- codec)))
+ [codec #+ Codec])
+ function))
## [Structures]
(struct: #export _ (Eq Bool)
@@ -46,4 +47,4 @@
{#;doc "Generates the complement of a predicate.
That is a predicate that returns the oposite of the original predicate."}
(All [a] (-> (-> a Bool) (-> a Bool)))
- (. not))
+ (compose not))
diff --git a/stdlib/source/lux/data/coll/array.lux b/stdlib/source/lux/data/coll/array.lux
index 1eeb1342c..ac15bfe9d 100644
--- a/stdlib/source/lux/data/coll/array.lux
+++ b/stdlib/source/lux/data/coll/array.lux
@@ -1,6 +1,6 @@
(;module:
lux
- (lux (control monoid
+ (lux (control [monoid #+ Monoid]
[functor #+ Functor]
[eq #+ Eq]
fold)
diff --git a/stdlib/source/lux/data/coll/list.lux b/stdlib/source/lux/data/coll/list.lux
index 6de9eeaa2..28deea034 100644
--- a/stdlib/source/lux/data/coll/list.lux
+++ b/stdlib/source/lux/data/coll/list.lux
@@ -1,12 +1,12 @@
(;module:
lux
(lux (control [monoid #+ Monoid]
- ["F" functor]
- ["A" applicative]
- ["M" monad #+ do Monad]
+ [functor #+ Functor]
+ [applicative #+ Applicative]
+ [monad #+ do Monad]
[eq #+ Eq]
[fold])
- (data [number "Nat/" Codec<Text,Nat>]
+ (data [number "nat/" Codec<Text,Nat>]
bool
[product])))
@@ -260,7 +260,7 @@
(open Monoid<List>)
-(struct: #export _ (F;Functor List)
+(struct: #export _ (Functor List)
(def: (map f ma)
(case ma
#;Nil #;Nil
@@ -268,7 +268,7 @@
(open Functor<List>)
-(struct: #export _ (A;Applicative List)
+(struct: #export _ (Applicative List)
(def: functor Functor<List>)
(def: (wrap a)
@@ -358,7 +358,7 @@
(if (n/> +0 num-lists)
(let [(^open) Functor<List>
indices (n/range +0 (n/dec num-lists))
- type-vars (: (List Code) (map (. symbol$ Nat/encode) indices))
+ type-vars (: (List Code) (map (|>> nat/encode symbol$) indices))
zip-type (` (All [(~@ type-vars)]
(-> (~@ (map (: (-> Code Code) (function [var] (` (List (~ var)))))
type-vars))
@@ -366,7 +366,7 @@
vars+lists (|> indices
(map n/inc)
(map (function [idx]
- (let [base (Nat/encode idx)]
+ (let [base (nat/encode idx)]
[(symbol$ base)
(symbol$ ("lux text concat" base "'"))]))))
pattern (` [(~@ (map (function [[v vs]] (` (#;Cons (~ v) (~ vs))))
@@ -404,7 +404,7 @@
indices (n/range +0 (n/dec num-lists))
g!return-type (symbol$ "\treturn-type\t")
g!func (symbol$ "\tfunc\t")
- type-vars (: (List Code) (map (. symbol$ Nat/encode) indices))
+ type-vars (: (List Code) (map (|>> nat/encode symbol$) indices))
zip-type (` (All [(~@ type-vars) (~ g!return-type)]
(-> (-> (~@ type-vars) (~ g!return-type))
(~@ (map (: (-> Code Code) (function [var] (` (List (~ var)))))
@@ -413,7 +413,7 @@
vars+lists (|> indices
(map n/inc)
(map (function [idx]
- (let [base (Nat/encode idx)]
+ (let [base (nat/encode idx)]
[(symbol$ base)
(symbol$ ("lux text concat" base "'"))]))))
pattern (` [(~@ (map (function [[v vs]] (` (#;Cons (~ v) (~ vs))))
@@ -478,19 +478,19 @@
(struct: #export (ListT Monad<M>)
(All [M] (-> (Monad M) (Monad (All [a] (M (List a))))))
- (def: applicative (A;compose (get@ #M;applicative Monad<M>) Applicative<List>))
+ (def: applicative (applicative;compose (get@ #monad;applicative Monad<M>) Applicative<List>))
(def: (join MlMla)
(do Monad<M>
[lMla MlMla
lla (: (($ +0) (List (List ($ +1))))
- (M;seq @ lMla))
- ## lla (M;seq @ lMla)
+ (monad;seq @ lMla))
+ ## lla (monad;seq @ lMla)
]
(wrap (concat lla)))))
(def: #export (lift Monad<M>)
(All [M a] (-> (Monad M) (-> (M a) (M (List a)))))
- (M;lift Monad<M> (:: Monad<List> wrap)))
+ (monad;lift Monad<M> (:: Monad<List> wrap)))
(def: (enumerate' idx xs)
(All [a] (-> Nat (List a) (List [Nat a])))
diff --git a/stdlib/source/lux/data/coll/ordered/set.lux b/stdlib/source/lux/data/coll/ordered/set.lux
index 376624033..a8f5ed45d 100644
--- a/stdlib/source/lux/data/coll/ordered/set.lux
+++ b/stdlib/source/lux/data/coll/ordered/set.lux
@@ -69,7 +69,7 @@
(def: #export (difference param subject)
(All [a] (-> (Set a) (Set a) (Set a)))
(|> (to-list subject)
- (list;filter (. not (member? param)))
+ (list;filter (|>> (member? param) not))
(from-list (get@ #d;order subject))))
(def: #export (sub? super sub)
diff --git a/stdlib/source/lux/data/ident.lux b/stdlib/source/lux/data/ident.lux
index 24fe97221..57e742433 100644
--- a/stdlib/source/lux/data/ident.lux
+++ b/stdlib/source/lux/data/ident.lux
@@ -1,9 +1,9 @@
(;module:
lux
(lux (control [eq #+ Eq]
- codec
+ [codec #+ Codec]
hash)
- (data [text "Text/" Monoid<Text> Eq<Text>])))
+ (data [text "text/" Monoid<Text> Eq<Text>])))
## [Types]
## (type: Ident
@@ -22,18 +22,18 @@
## [Structures]
(struct: #export _ (Eq Ident)
(def: (= [xmodule xname] [ymodule yname])
- (and (Text/= xmodule ymodule)
- (Text/= xname yname))))
+ (and (text/= xmodule ymodule)
+ (text/= xname yname))))
(struct: #export _ (Codec Text Ident)
(def: (encode [module name])
(case module
"" name
- _ ($_ Text/compose module ";" name)))
+ _ ($_ text/compose module ";" name)))
(def: (decode input)
- (if (Text/= "" input)
- (#;Left (Text/compose "Invalid format for Ident: " input))
+ (if (text/= "" input)
+ (#;Left (text/compose "Invalid format for Ident: " input))
(case (text;split-all-with ";" input)
(^ (list name))
(#;Right ["" name])
@@ -42,7 +42,7 @@
(#;Right [module name])
_
- (#;Left (Text/compose "Invalid format for Ident: " input))))))
+ (#;Left (text/compose "Invalid format for Ident: " input))))))
(struct: #export _ (Hash Ident)
(def: eq Eq<Ident>)
diff --git a/stdlib/source/lux/data/number.lux b/stdlib/source/lux/data/number.lux
index 8e330e9d5..de8ba5242 100644
--- a/stdlib/source/lux/data/number.lux
+++ b/stdlib/source/lux/data/number.lux
@@ -7,7 +7,7 @@
[order]
enum
interval
- codec)
+ [codec #+ Codec])
(data ["e" error]
[maybe]
[bit])))
diff --git a/stdlib/source/lux/data/text.lux b/stdlib/source/lux/data/text.lux
index 534901e98..bf05df201 100644
--- a/stdlib/source/lux/data/text.lux
+++ b/stdlib/source/lux/data/text.lux
@@ -3,8 +3,8 @@
(lux (control [monoid #+ Monoid]
[eq #+ Eq]
[order]
- ["M" monad #+ do Monad]
- codec
+ [monad #+ do Monad]
+ [codec #+ Codec]
hash)
(data (coll [list])
[maybe])))
diff --git a/stdlib/source/lux/data/text/regex.lux b/stdlib/source/lux/data/text/regex.lux
index 37cb091ee..4dccf7855 100644
--- a/stdlib/source/lux/data/text/regex.lux
+++ b/stdlib/source/lux/data/text/regex.lux
@@ -5,11 +5,11 @@
(data [text]
["l" text/lexer]
text/format
- [number "Int/" Codec<Text,Int>]
+ [number "int/" Codec<Text,Int>]
[product]
- ["E" error]
+ ["e" error]
[maybe]
- (coll [list "L/" Fold<List> Monad<List>]))
+ (coll [list "list/" Fold<List> Monad<List>]))
[macro #- run]
(macro [code]
["s" syntax #+ syntax:])))
@@ -112,10 +112,10 @@
[_ (wrap [])
init re-user-class^'
rest (p;some (p;after (l;this "&&") (l;enclosed ["[" "]"] re-user-class^')))]
- (wrap (L/fold (function [refinement base]
- (` (refine^ (~ refinement) (~ base))))
- init
- rest))))
+ (wrap (list/fold (function [refinement base]
+ (` (refine^ (~ refinement) (~ base))))
+ init
+ rest))))
(def: #hidden blank^
(l;Lexer Text)
@@ -188,7 +188,7 @@
(p;either (do p;Monad<Parser>
[_ (l;this "\\")
id number^]
- (wrap (` (;;copy (~ (code;symbol ["" (Int/encode (nat-to-int id))]))))))
+ (wrap (` (;;copy (~ (code;symbol ["" (int/encode (nat-to-int id))]))))))
(do p;Monad<Parser>
[_ (l;this "\\k<")
captured-name identifier-part^
@@ -253,7 +253,7 @@
(re-quantified^ current-module)
(re-simple^ current-module)))
-(def: #hidden _Text/compose_
+(def: #hidden _text/compose_
(-> Text Text Text)
(:: text;Monoid<Text> compose))
@@ -271,44 +271,44 @@
(re-scoped^ current-module)))
#let [g!total (code;symbol ["" "0total"])
g!temp (code;symbol ["" "0temp"])
- [_ names steps] (L/fold (: (-> (Either Code [Re-Group Code])
- [Int (List Code) (List (List Code))]
- [Int (List Code) (List (List Code))])
- (function [part [idx names steps]]
- (case part
- (^or (#E;Error complex) (#E;Success [#Non-Capturing complex]))
- [idx
- names
- (list& (list g!temp complex
- (' #let) (` [(~ g!total) (_Text/compose_ (~ g!total) (~ g!temp))]))
- steps)]
-
- (#E;Success [(#Capturing [?name num-captures]) scoped])
- (let [[idx! name!] (case ?name
- (#;Some _name)
- [idx (code;symbol ["" _name])]
-
- #;None
- [(i/inc idx) (code;symbol ["" (Int/encode idx)])])
- access (if (n/> +0 num-captures)
- (` (product;left (~ name!)))
- name!)]
- [idx!
- (list& name! names)
- (list& (list name! scoped
- (' #let) (` [(~ g!total) (_Text/compose_ (~ g!total) (~ access))]))
- steps)])
- )))
- [0
- (: (List Code) (list))
- (: (List (List Code)) (list))]
- parts)]]
+ [_ names steps] (list/fold (: (-> (Either Code [Re-Group Code])
+ [Int (List Code) (List (List Code))]
+ [Int (List Code) (List (List Code))])
+ (function [part [idx names steps]]
+ (case part
+ (^or (#e;Error complex) (#e;Success [#Non-Capturing complex]))
+ [idx
+ names
+ (list& (list g!temp complex
+ (' #let) (` [(~ g!total) (_text/compose_ (~ g!total) (~ g!temp))]))
+ steps)]
+
+ (#e;Success [(#Capturing [?name num-captures]) scoped])
+ (let [[idx! name!] (case ?name
+ (#;Some _name)
+ [idx (code;symbol ["" _name])]
+
+ #;None
+ [(i/inc idx) (code;symbol ["" (int/encode idx)])])
+ access (if (n/> +0 num-captures)
+ (` (product;left (~ name!)))
+ name!)]
+ [idx!
+ (list& name! names)
+ (list& (list name! scoped
+ (' #let) (` [(~ g!total) (_text/compose_ (~ g!total) (~ access))]))
+ steps)])
+ )))
+ [0
+ (: (List Code) (list))
+ (: (List (List Code)) (list))]
+ parts)]]
(wrap [(if capturing?
(list;size names)
+0)
(` (do p;Monad<Parser>
[(~ (' #let)) [(~ g!total) ""]
- (~@ (|> steps list;reverse L/join))]
+ (~@ (|> steps list;reverse list/join))]
((~ (' wrap)) [(~ g!total) (~@ (list;reverse names))])))])
))
@@ -320,31 +320,31 @@
(All [l r] (-> (l;Lexer [Text l]) (l;Lexer [Text r]) (l;Lexer [Text (| l r)])))
(function [input]
(case (left input)
- (#E;Success [input' [lt lv]])
- (#E;Success [input' [lt (+0 lv)]])
+ (#e;Success [input' [lt lv]])
+ (#e;Success [input' [lt (+0 lv)]])
- (#E;Error _)
+ (#e;Error _)
(case (right input)
- (#E;Success [input' [rt rv]])
- (#E;Success [input' [rt (+1 rv)]])
+ (#e;Success [input' [rt rv]])
+ (#e;Success [input' [rt (+1 rv)]])
- (#E;Error error)
- (#E;Error error)))))
+ (#e;Error error)
+ (#e;Error error)))))
(def: #hidden (|||_^ left right)
(All [l r] (-> (l;Lexer [Text l]) (l;Lexer [Text r]) (l;Lexer Text)))
(function [input]
(case (left input)
- (#E;Success [input' [lt lv]])
- (#E;Success [input' lt])
+ (#e;Success [input' [lt lv]])
+ (#e;Success [input' lt])
- (#E;Error _)
+ (#e;Error _)
(case (right input)
- (#E;Success [input' [rt rv]])
- (#E;Success [input' rt])
+ (#e;Success [input' [rt rv]])
+ (#e;Success [input' rt])
- (#E;Error error)
- (#E;Error error)))))
+ (#e;Error error)
+ (#e;Error error)))))
(def: (prep-alternative [num-captures alt])
(-> [Nat Code] Code)
@@ -366,8 +366,8 @@
(` |||_^))]]
(if (list;empty? tail)
(wrap head)
- (wrap [(L/fold n/max (product;left head) (L/map product;left tail))
- (` ($_ (~ g!op) (~ (prep-alternative head)) (~@ (L/map prep-alternative tail))))]))))
+ (wrap [(list/fold n/max (product;left head) (list/map product;left tail))
+ (` ($_ (~ g!op) (~ (prep-alternative head)) (~@ (list/map prep-alternative tail))))]))))
(def: (re-scoped^ current-module)
(-> Text (l;Lexer [Re-Group Code]))
@@ -462,11 +462,11 @@
(case (|> (regex^ current-module)
(p;before l;end)
(l;run pattern))
- (#E;Error error)
+ (#e;Error error)
(macro;fail (format "Error while parsing regular-expression:\n"
error))
- (#E;Success regex)
+ (#e;Success regex)
(wrap (list regex))
)))
@@ -488,7 +488,7 @@
[g!temp (macro;gensym "temp")]
(wrap (list& (` (^multi (~ g!temp)
[(l;run (~ g!temp) (regex (~ (code;text pattern))))
- (#E;Success (~ (maybe;default g!temp
+ (#e;Success (~ (maybe;default g!temp
bindings)))]))
body
branches))))
diff --git a/stdlib/source/lux/data/trace.lux b/stdlib/source/lux/data/trace.lux
index acb059dc0..d34ab0a0a 100644
--- a/stdlib/source/lux/data/trace.lux
+++ b/stdlib/source/lux/data/trace.lux
@@ -1,23 +1,24 @@
(;module:
lux
- (lux (control ["m" monoid]
- ["F" functor]
- comonad)))
+ (lux (control [monoid #+ Monoid]
+ [functor #+ Functor]
+ comonad)
+ function))
(type: #export (Trace t a)
- {#monoid (m;Monoid t)
+ {#monoid (Monoid t)
#trace (-> t a)})
-(struct: #export Functor<Trace> (All [t] (F;Functor (Trace t)))
+(struct: #export Functor<Trace> (All [t] (Functor (Trace t)))
(def: (map f fa)
- (update@ #trace (. f) fa)))
+ (update@ #trace (compose f) fa)))
(struct: #export CoMonad<Trace> (All [t] (CoMonad (Trace t)))
(def: functor Functor<Trace>)
(def: (unwrap wa)
((get@ #trace wa)
- (get@ [#monoid #m;identity] wa)))
+ (get@ [#monoid #monoid;identity] wa)))
(def: (split wa)
(let [monoid (get@ #monoid wa)]