aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/math/random.lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/lux/math/random.lux')
-rw-r--r--stdlib/source/lux/math/random.lux100
1 files changed, 50 insertions, 50 deletions
diff --git a/stdlib/source/lux/math/random.lux b/stdlib/source/lux/math/random.lux
index e8b552b1c..e3c7fd751 100644
--- a/stdlib/source/lux/math/random.lux
+++ b/stdlib/source/lux/math/random.lux
@@ -1,4 +1,4 @@
-(;module: {#;doc "Pseudo-random number generation (PRNG) algorithms."}
+(.module: {#.doc "Pseudo-random number generation (PRNG) algorithms."}
[lux #- list]
(lux (control [functor #+ Functor]
[applicative #+ Applicative]
@@ -21,11 +21,11 @@
))
(type: #export #rec PRNG
- {#;doc "An abstract way to represent any PRNG."}
+ {#.doc "An abstract way to represent any PRNG."}
(-> Unit [PRNG Nat]))
(type: #export (Random a)
- {#;doc "A producer of random values based on a PRNG."}
+ {#.doc "A producer of random values based on a PRNG."}
(-> PRNG [PRNG a]))
(struct: #export _ (Functor Random)
@@ -56,7 +56,7 @@
(fa state')))))
(def: #export (filter pred gen)
- {#;doc "Retries the generator until the output satisfies a predicate."}
+ {#.doc "Retries the generator until the output satisfies a predicate."}
(All [a] (-> (-> a Bool) (Random a) (Random a)))
(do Monad<Random>
[sample gen]
@@ -69,7 +69,7 @@
(function [prng]
(let [[prng left] (prng [])
[prng right] (prng [])]
- [prng (n/+ (bit;shift-left +32 left)
+ [prng (n/+ (bit.shift-left +32 left)
right)])))
(def: #export int
@@ -77,20 +77,20 @@
(function [prng]
(let [[prng left] (prng [])
[prng right] (prng [])]
- [prng (nat-to-int (n/+ (bit;shift-left +32 left)
+ [prng (nat-to-int (n/+ (bit.shift-left +32 left)
right))])))
(def: #export bool
(Random Bool)
(function [prng]
(let [[prng output] (prng [])]
- [prng (|> output (bit;and +1) (n/= +1))])))
+ [prng (|> output (bit.and +1) (n/= +1))])))
(def: (bits n)
(-> Nat (Random Nat))
(function [prng]
(let [[prng output] (prng [])]
- [prng (bit;shift-right (n/- n +64) output)])))
+ [prng (bit.shift-right (n/- n +64) output)])))
(def: #export frac
(Random Frac)
@@ -98,10 +98,10 @@
[left (bits +26)
right (bits +27)]
(wrap (|> right
- (n/+ (bit;shift-left +27 left))
+ (n/+ (bit.shift-left +27 left))
nat-to-int
int-to-frac
- (f// (|> +1 (bit;shift-left +53) nat-to-int int-to-frac))))))
+ (f// (|> +1 (bit.shift-left +53) nat-to-int int-to-frac))))))
(def: #export deg
(Random Deg)
@@ -114,7 +114,7 @@
(do Monad<Random>
[x char-gen
xs (text' char-gen (n/dec size))]
- (wrap (text/compose (text;from-code x) xs)))))
+ (wrap (text/compose (text.from-code x) xs)))))
(type: Char-Range [Nat Nat])
@@ -137,13 +137,13 @@
(-> Char-Range Nat Bool)
(and (n/>= from char) (n/<= to char)))
-(def: unicode-ceiling (n/inc (product;right CJK-Compatibility-Ideographs-Supplement)))
+(def: unicode-ceiling (n/inc (product.right CJK-Compatibility-Ideographs-Supplement)))
(def: #export unicode
(Random Nat)
- (|> ;;nat
+ (|> ..nat
(:: Monad<Random> map (n/% unicode-ceiling))
- (;;filter (function [raw]
+ (..filter (function [raw]
## From "Basic Latin" to "Syriac"
(or (n/<= (hex "+074F") raw)
(within? Thaana raw)
@@ -208,12 +208,12 @@
right <gen>]
(wrap (<ctor> left right))))]
- [ratio r;Ratio r;ratio nat]
- [complex c;Complex c;complex frac]
+ [ratio r.Ratio r.ratio nat]
+ [complex c.Complex c.complex frac]
)
(def: #export (seq left right)
- {#;doc "Sequencing combinator."}
+ {#.doc "Sequencing combinator."}
(All [a b] (-> (Random a) (Random b) (Random [a b])))
(do Monad<Random>
[=left left
@@ -221,7 +221,7 @@
(wrap [=left =right])))
(def: #export (alt left right)
- {#;doc "Heterogeneous alternative combinator."}
+ {#.doc "Heterogeneous alternative combinator."}
(All [a b] (-> (Random a) (Random b) (Random (| a b))))
(do Monad<Random>
[? bool]
@@ -234,7 +234,7 @@
(wrap (+1 =right))))))
(def: #export (either left right)
- {#;doc "Homogeneous alternative combinator."}
+ {#.doc "Homogeneous alternative combinator."}
(All [a] (-> (Random a) (Random a) (Random a)))
(do Monad<Random>
[? bool]
@@ -243,7 +243,7 @@
right)))
(def: #export (rec gen)
- {#;doc "A combinator for producing recursive random generators."}
+ {#.doc "A combinator for producing recursive random generators."}
(All [a] (-> (-> (Random a) (Random a)) (Random a)))
(function [state]
(let [gen' (gen (rec gen))]
@@ -256,8 +256,8 @@
(if some?
(do @
[value value-gen]
- (wrap (#;Some value)))
- (wrap #;None))))
+ (wrap (#.Some value)))
+ (wrap #.None))))
(do-template [<name> <type> <zero> <plus>]
[(def: #export (<name> size value-gen)
@@ -269,8 +269,8 @@
(wrap (<plus> x xs)))
(:: Monad<Random> wrap <zero>)))]
- [list List (;list) #;Cons]
- [sequence Sequence sequence;empty sequence;add]
+ [list List (.list) #.Cons]
+ [sequence Sequence sequence.empty sequence.add]
)
(do-template [<name> <type> <ctor>]
@@ -280,9 +280,9 @@
[values (list size value-gen)]
(wrap (|> values <ctor>))))]
- [array Array array;from-list]
- [queue Queue queue;from-list]
- [stack Stack (list/fold stack;push stack;empty)]
+ [array Array array.from-list]
+ [queue Queue queue.from-list]
+ [stack Stack (list/fold stack.push stack.empty)]
)
(def: #export (set Hash<a> size value-gen)
@@ -293,11 +293,11 @@
(loop [_ []]
(do @
[x value-gen
- #let [xs+ (set;add x xs)]]
- (if (n/= size (set;size xs+))
+ #let [xs+ (set.add x xs)]]
+ (if (n/= size (set.size xs+))
(wrap xs+)
(recur [])))))
- (:: Monad<Random> wrap (set;new Hash<a>))))
+ (:: Monad<Random> wrap (set.new Hash<a>))))
(def: #export (dict Hash<a> size key-gen value-gen)
(All [k v] (-> (Hash k) Nat (Random k) (Random v) (Random (Dict k v))))
@@ -308,11 +308,11 @@
(do @
[k key-gen
v value-gen
- #let [kv+ (dict;put k v kv)]]
- (if (n/= size (dict;size kv+))
+ #let [kv+ (dict.put k v kv)]]
+ (if (n/= size (dict.size kv+))
(wrap kv+)
(recur [])))))
- (:: Monad<Random> wrap (dict;new Hash<a>))))
+ (:: Monad<Random> wrap (dict.new Hash<a>))))
(def: #export (run prng calc)
(All [a] (-> PRNG (Random a) [PRNG a]))
@@ -321,49 +321,49 @@
(def: pcg-32-magic-mult Nat +6364136223846793005)
(def: #export (pcg-32 [inc seed])
- {#;doc "An implementation of the PCG32 algorithm.
+ {#.doc "An implementation of the PCG32 algorithm.
For more information, please see: http://www.pcg-random.org/"}
(-> [Nat Nat] PRNG)
(function [_]
(let [seed' (|> seed (n/* pcg-32-magic-mult) (n/+ inc))
- xor-shifted (|> seed (bit;shift-right +18) (bit;xor seed) (bit;shift-right +27))
- rot (|> seed (bit;shift-right +59))]
- [(pcg-32 [inc seed']) (bit;rotate-right rot xor-shifted)]
+ xor-shifted (|> seed (bit.shift-right +18) (bit.xor seed) (bit.shift-right +27))
+ rot (|> seed (bit.shift-right +59))]
+ [(pcg-32 [inc seed']) (bit.rotate-right rot xor-shifted)]
)))
(def: #export (xoroshiro-128+ [s0 s1])
- {#;doc "An implementation of the Xoroshiro128+ algorithm.
+ {#.doc "An implementation of the Xoroshiro128+ algorithm.
For more information, please see: http://xoroshiro.di.unimi.it/"}
(-> [Nat Nat] PRNG)
(function [_]
(let [result (n/+ s0 s1)
- s01 (bit;xor s0 s1)
- s0' (|> (bit;rotate-left +55 s0)
- (bit;xor s01)
- (bit;xor (bit;shift-left +14 s01)))
- s1' (bit;rotate-left +36 s01)]
+ s01 (bit.xor s0 s1)
+ s0' (|> (bit.rotate-left +55 s0)
+ (bit.xor s01)
+ (bit.xor (bit.shift-left +14 s01)))
+ s1' (bit.rotate-left +36 s01)]
[(xoroshiro-128+ [s0' s1']) result])
))
(def: (swap from to vec)
(All [a] (-> Nat Nat (Sequence a) (Sequence a)))
(|> vec
- (sequence;put to (maybe;assume (sequence;nth from vec)))
- (sequence;put from (maybe;assume (sequence;nth to vec)))))
+ (sequence.put to (maybe.assume (sequence.nth from vec)))
+ (sequence.put from (maybe.assume (sequence.nth to vec)))))
(def: #export (shuffle seed sequence)
- {#;doc "Shuffle a sequence randomly based on a seed value."}
+ {#.doc "Shuffle a sequence randomly based on a seed value."}
(All [a] (-> Nat (Sequence a) (Sequence a)))
- (let [_size (sequence;size sequence)
- _shuffle (monad;fold Monad<Random>
+ (let [_size (sequence.size sequence)
+ _shuffle (monad.fold Monad<Random>
(function [idx vec]
(do Monad<Random>
[rand nat]
(wrap (swap idx (n/% _size rand) vec))))
sequence
- (list;n/range +0 (n/dec _size)))]
+ (list.n/range +0 (n/dec _size)))]
(|> _shuffle
(run (pcg-32 [+123 seed]))
- product;right)))
+ product.right)))