@@ -231,39 +231,25 @@ let
231231 f = div' n d ;
232232 in n - f * d ;
233233
234- # TODO: Properly accept fractional exponents.
234+ is_nan = n : n != n ;
235+ inf = ( builtins . fromTOML "a = inf" ) . a ;
236+
235237 power = x : n :
236238 if n == 0.5
237239 then square_root x # heuristic for square_root function
238- else if builtins . floor n == 0
239- then 1
240- else if n < 0
241- then power ( 1 / x ) ( - n )
242- else x * power x ( n - 1 ) ;
243-
244- # Credit to:
245- # https://github.com/xddxdd/nix-math
246- square_root =
247- let
248- epsilon = power ( 0.1 ) 10 ;
249- fabs =
250- x :
251- if x < 0
252- then 0 - x
253- else x ;
254- in
255- x :
256- let
257- helper = tmp : let
258- value = ( tmp + 1.0 * x / tmp ) / 2 ;
259- in
260- if ( fabs ( value - tmp ) ) < epsilon
261- then value
262- else helper value ;
263- in
264- if x < epsilon
265- then 0
266- else helper ( 1.0 * x ) ;
240+ else if is_nan x
241+ then x
242+ else if is_nan n
243+ then n
244+ else if n == inf
245+ then n
246+ else if n == - inf
247+ then 0
248+ else if x == inf || x == - inf
249+ then x
250+ else math . pow x n ;
251+
252+ square_root = math . sqrt ;
267253
268254 # No global seed to change, so there isn't much we can do.
269255 random_uniform = { } : 0.646355926896028 ;
@@ -855,6 +841,203 @@ let
855841 let
856842 result = byteArrayToUtf8String array ;
857843 in if builtins . isNull result then Error Nil else Ok result ;
844+
845+ # nix-math (credit to xddxdd)
846+ # https://github.com/xddxdd/nix-math/commit/f75dc262fc441391b4d19306b7f233bbb4fc3b3a
847+ math =
848+ rec {
849+ inherit ( builtins ) floor ceil ;
850+
851+ pi = 3.14159265358979323846264338327950288 ;
852+ e = 2.718281828459045235360287471352 ;
853+ epsilon = _pow_int ( 0.1 ) 10 ;
854+
855+ sum = builtins . foldl' builtins . add 0 ;
856+ multiply = builtins . foldl' builtins . mul 1 ;
857+
858+ # Absolute value of `x`
859+ abs = x : if x < 0 then 0 - x else x ;
860+
861+ # Absolute value of `x`
862+ fabs = abs ;
863+
864+ # Returns `a` to the power of `b`. **Only supports integer for `b`!**
865+ # Internal use only. Users should use `_pow_int`, which supports floating point exponentials.
866+ _pow_int = x : times : multiply ( builtins . genList ( _ : x ) times x ) ;
867+
868+ # Create a list of numbers from `min` (inclusive) to `max` (exclusive), adding `step` each time.
869+ arange =
870+ min : max : step :
871+ let
872+ count = floor ( ( max - min ) / step ) ;
873+ in
874+ builtins . genList ( i : min + step * i ) count ;
875+
876+ # Create a list of numbers from `min` (inclusive) to `max` (inclusive), adding `step` each time.
877+ arange2 =
878+ min : max : step :
879+ arange min ( max + step ) step ;
880+
881+ # Calculate x^0*poly[0] + x^1*poly[1] + ... + x^n*poly[n]
882+ polynomial =
883+ x : poly :
884+ let
885+ step = i : ( _pow_int x i ) * ( builtins . elemAt poly i ) ;
886+ in
887+ sum ( builtins . genList step ( builtins . length poly ) ) ;
888+
889+ parseFloat = builtins . fromJSON ;
890+
891+ int = x : if x < 0 then - int ( 0 - x ) else builtins . floor x ;
892+
893+ hasFraction =
894+ x :
895+ let
896+ splitted = builtins . splitString "." ( builtins . toString x ) ;
897+ in
898+ builtins . length splitted >= 2
899+ &&
900+ builtins . length (
901+ builtins . filter ( ch : ch != "0" ) ( builtins . stringToCharacters ( builtins . elemAt splitted 1 ) )
902+ ) > 0 ;
903+
904+ # Divide `a` by `b` with no remainder.
905+ div =
906+ a : b :
907+ let
908+ divideExactly = ! ( hasFraction ( 1.0 * a / b ) ) ;
909+ offset = if divideExactly then 0 else ( 0 - 1 ) ;
910+ in
911+ if b < 0 then
912+ offset - div a ( 0 - b )
913+ else if a < 0 then
914+ offset - div ( 0 - a ) b
915+ else
916+ floor ( 1.0 * a / b ) ;
917+
918+ # Modulos of dividing `a` by `b`.
919+ mod =
920+ a : b :
921+ if b < 0 then
922+ 0 - mod ( 0 - a ) ( 0 - b )
923+ else if a < 0 then
924+ mod ( b - mod ( 0 - a ) b ) b
925+ else
926+ a - b * ( div a b ) ;
927+
928+ # Returns factorial of `x`. `x` is an integer, `x >= 0`.
929+ factorial = x : multiply ( builtins . genList ( i : i + 1 ) 1 ) ; # info omitted 1 x);
930+
931+ # Trigonometric function. Takes radian as input.
932+ # Taylor series: for x >= 0, sin(x) = x - x^3/3! + x^5/5! - ...
933+ sin =
934+ x :
935+ let
936+ x' = mod ( 1.0 * x ) ( 2 * pi ) ;
937+ step = i : ( _pow_int ( 0 - 1 ) ( i - 1 ) ) * multiply ( builtins . genList ( j : x' / ( j + 1 ) ) ( i * 2 - 1 ) ) ;
938+ helper =
939+ tmp : i :
940+ let
941+ value = step i ;
942+ in
943+ if ( fabs value ) < epsilon then tmp else helper ( tmp + value ) ( i + 1 ) ;
944+ in
945+ if x < 0 then - sin ( 0 - x ) else helper 0 1 ;
946+
947+ # Trigonometric function. Takes radian as input.
948+ cos = x : sin ( 0.5 * pi - x ) ;
949+
950+ # Trigonometric function. Takes radian as input.
951+ tan = x : ( sin x ) / ( cos x ) ;
952+
953+ # Arctangent function. Polynomial approximation.
954+ atan =
955+ x :
956+ let
957+ poly = builtins . fromJSON "[-3.45783607234591e-15, 0.99999999999744, 5.257304414192212e-10, -0.33333336391488594, 8.433269318729302e-07, 0.1999866363777591, 0.00013446991236889277, -0.14376659407790288, 0.00426000182788111, 0.097197156521193, 0.030912220117352136, -0.133167493353323, 0.020663690408239177, 0.11398478735740854, -0.06791459641806276, -0.06663597903061667, 0.11580255232044795, -0.07215375057397233, 0.022284945086684438, -0.0028573630133916046]" ;
958+ in
959+ if x < 0 then
960+ - atan ( 0 - x )
961+ else if x > 1 then
962+ pi / 2 - atan ( 1 / x )
963+ else
964+ polynomial x poly ;
965+
966+ # Exponential function. Polynomial approximation.
967+ # (https://github.com/nadavrot/fast_log)
968+ exp =
969+ x :
970+ let
971+ x_int = int x ;
972+ x_decimal = x - x_int ;
973+ decimal_poly = builtins . fromJSON "[0.9999999999999997, 0.9999999999999494, 0.5000000000013429, 0.16666666664916754, 0.04166666680065545, 0.008333332669176907, 0.001388891142716621, 0.00019840730702746657, 2.481076351588151e-05, 2.744709498016379e-06, 2.846575263734758e-07, 2.0215584670370862e-08, 3.542885385105854e-09]" ;
974+ in
975+ if x < 0 then 1 / ( exp ( 0 - x ) ) else ( _pow_int e x_int ) * ( polynomial x_decimal decimal_poly ) ;
976+
977+ # Logarithmetic function. Takes radian as input.
978+ # Taylor series: for 1 <= x <= 1.9, ln(x) = (x-1)/1 - (x-1)^2/2 + (x-1)^3/3
979+ # (https://en.wikipedia.org/wiki/Logarithm#Taylor_series)
980+ # For x >= 1.9, ln(x) = 2 * ln(sqrt(x))
981+ # For 0 < x < 1, ln(x) = -ln(1/x)
982+ #
983+ # Although Taylor series applies to 0 <= x <= 2, calculation outside
984+ # 1 <= x <= 1.9 is very slow and may cause max-call-depth exceeded
985+ ln =
986+ x :
987+ let
988+ step = i : ( _pow_int ( 0 - 1 ) ( i - 1 ) ) * ( _pow_int ( 1.0 * x - 1.0 ) i ) / i ;
989+ helper =
990+ tmp : i :
991+ let
992+ value = step i ;
993+ in
994+ if ( fabs value ) < epsilon then tmp else helper ( tmp + value ) ( i + 1 ) ;
995+ in
996+ if x <= 0 then
997+ throw "ln(x<=0) returns invalid value"
998+ else if x < 1 then
999+ - ln ( 1 / x )
1000+ else if x > 1.9 then
1001+ 2 * ( ln ( sqrt x ) )
1002+ else
1003+ helper 0 1 ;
1004+
1005+ # Power function that supports float.
1006+ # pow(x, y) = exp(y * ln(x)), plus a few edge cases.
1007+ pow =
1008+ x : times :
1009+ let
1010+ is_int_times = abs ( times - int times ) < epsilon ;
1011+ in
1012+ if is_int_times then
1013+ _pow_int x ( int times )
1014+ else if x == 0 then
1015+ 0
1016+ else if x < 0 then
1017+ throw "Calculating power of negative base and decimal exponential is not supported"
1018+ else
1019+ exp ( times * ln x ) ;
1020+
1021+ log = base : x : ( ln x ) / ( ln base ) ;
1022+ log2 = log 2 ;
1023+ log10 = log 10 ;
1024+
1025+ # Degrees to radian.
1026+ deg2rad = x : x * pi / 180 ;
1027+
1028+ # Square root of `x`. `x >= 0`.
1029+ sqrt =
1030+ x :
1031+ let
1032+ helper =
1033+ tmp :
1034+ let
1035+ value = ( tmp + 1.0 * x / tmp ) / 2 ;
1036+ in
1037+ if ( fabs ( value - tmp ) ) < epsilon then value else helper value ;
1038+ in
1039+ if x < epsilon then 0 else helper ( 1.0 * x ) ;
1040+ } ;
8581041in
8591042 {
8601043 inherit
0 commit comments