summary refs log tree commit diff stats
path: root/tests/stdlib/tmath.nim
blob: 8ddb09bf58a36d1f0210795141160f971e0c06e1 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
pre { line-height: 125%; }
td.linenos .normal { color: inherit; background-color: transparent; padding-left: 5px; padding-right: 5px; }
span.linenos { color: inherit; background-color: transparent; padding-left: 5px; padding-right: 5px; }
td.linenos .special { color: #000000; background-color: #ffffc0; padding-left: 5px; padding-right: 5px; }
span.linenos.special { color: #000000; background-color: #ffffc0; padding-left: 5px; padding-right: 5px; }
.highlight .hll { background-color: #ffffcc }
.highlight .c { color: #888888 } /* Comment */
.highlight .err { color: #a61717; background-color: #e3d2d2 } /* Error */
.highlight .k { color: #008800; font-weight: bold } /* Keyword */
.highlight .ch { color: #888888 } /* Comment.Hashbang */
.highlight .cm { color: #888888 } /* Comment.Multiline */
.highlight .cp { color: #cc0000; font-weight: bold } /* Comment.Preproc */
.highlight .cpf { color: #888888 } /* Comment.PreprocFile */
.highlight .c1 { color: #888888 } /* Comment.Single */
.highlight .cs { color: #cc0000; font-weight: bold; background-color: #fff0f0 } /* Comment.Special */
.highlight .gd { color: #000000; background-color: #ffdddd } /* Generic.Deleted */
.highlight .ge { font-style: italic } /* Generic.Emph */
.highlight .ges { font-weight: bold; font-style: italic } /* Generic.EmphStrong */
.highlight .gr { color: #aa0000 } /* Generic.Error */
.highlight .gh { color: #333333 } /* Generic.Heading */
.highlight .gi { color: #000000; background-color: #ddffdd } /* Generic.Inserted */
.highlight .go { color: #888888 } /* Generic.Output */
.highlight .gp { color: #555555 } /* Generic.Prompt */
.highlight .gs { font-weight: bold } /* Generic.Strong */
.highlight .gu { color: #666666 } /* Generic.Subheading */
.highlight .gt { color: #aa0000 } /* Generic.Traceback */
.highlight .kc { color: #008800; font-weight: bold } /* Keyword.Constant */
.highlight .kd { color: #008800; font-weight: bold } /* Keyword.Declaration */
.highlight .kn { color: #008800; font-weight: bold } /* Keyword.Namespace */
.highlight .kp { color: #008800 } /* Keyword.Pseudo */
.highlight .kr { color: #008800; font-weight: bold } /* Keyword.Reserved */
.highlight .kt { color: #888888; font-weight: bold } /* Keyword.Type */
.highlight .m { color: #0000DD; font-weight: bold } /* Literal.Number */
.highlight .s { color: #dd2200; background-color: #fff0f0 } /* Literal.String */
.highlight .na { color: #336699 } /* Name.Attribute */
.highlight .nb { color: #003388 } /* Name.Builtin */
.highlight .nc { color: #bb0066; font-weight: bold } /* Name.Class */
.highlight .no { color: #003366; font-weight: bold } /* Name.Constant */
.highlight .nd { color: #555555 } /* Name.Decorator */
.highlight .ne { color: #bb0066; font-weight: bold } /* Name.Exception */
.highlight .nf { color: #0066bb; font-weight: bold } /* Name.Function */
.highlight .nl { color: #336699; font-style: italic } /* Name.Label */
.highlight .nn { color: #bb0066; font-weight: bold } /* Name.Namespace */
.highlight .py { color: #336699; font-weight: bold } /* Name.Property */
.highlight .nt { color: #bb0066; font-weight: bold } /* Name.Tag */
.highlight .nv { color: #336699 } /* Name.Variable */
.highlight .ow { color: #008800 } /* Operator.Word */
.highlight .w { color: #bbbbbb } /* Text.Whitespace */
.highlight .mb { color: #0000DD; font-weight: bold } /* Literal.Number.Bin */
.highlight .mf { color: #0000DD; font-weight: bold } /* Literal.Number.Float */
.highlight .mh { color: #0000DD; font-weight: bold } /* Literal.Number.Hex */
.highlight .mi { color: #0000DD; font-weight: bold } /* Literal.Number.Integer */
.highlight .mo { color: #0000DD; font-weight: bold } /* Literal.Number.Oct */
.highlight .sa { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Affix */
.highlight .sb { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Backtick */
.highlight .sc { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Char */
.highlight .dl { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Delimiter */
.highlight .sd { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Doc */
.highlight .s2 { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Double */
.highlight .se { color: #0044dd; background-color: #fff0f0 } /* Literal.String.Escape */
.highlight .sh { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Heredoc */
.highlight .si { color: #3333bb; background-color: #fff0f0 } /* Literal.String.Interpol */
.highlight .sx { color: #22bb22; background-color: #f0fff0 } /* Literal.String.Other */
.highlight .sr { color: #008800; background-color: #fff0ff } /* Literal.String.Regex */
.highlight .s1 { color: #dd2200; background-color: #fff0f0 } /* Literal.String.Single */
.highlight .ss { color: #aa6600; background-color: #fff0f0 } /* Literal.String.Symbol */
.highlight .bp { color: #003388 } /* Name.Builtin.Pseudo */
.highlight .fm { color: #0066bb; font-weight: bold } /* Name.Function.Magic */
.highlight .vc { color: #336699 } /* Name.Variable.Class */
.highlight .vg { color: #dd7700 } /* Name.Variable.Global */
.highlight .vi { color: #3333bb } /* Name.Variable.Instance */
.highlight .vm { color: #336699 } /* Name.Variable.Magic */
.highlight .il { color: #0000DD; font-weight: bold } /* Literal.Number.Integer.Long */
# Copyright (C) 2009, 2010  Roman Zimbelmann <romanz@lavabit.com>
#
# This program is free software: you can redistribute it and/or modify
# it under the terms of the GNU General Public License as published by
# the Free Software Foundation, either version 3 of the License, or
# (at your option) any later version.
#
# This program is distributed in the hope that it will be useful,
# but WITHOUT ANY WARRANTY; without even the implied warranty of
# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
# GNU General Public License for more details.
#
# You should have received a copy of the GNU General Public License
# along with this program.  If not, see <http://www.gnu.org/licenses/>.

"""This package includes container-objects which are
used to manage stored data
"""
from ranger.container.history import History
from .keymap import KeyMap, KeyManager
from .keybuffer import KeyBuffer
from .bo
discard """
  targets: "c cpp js"
  matrix:"; -d:danger; --mm:refc"
"""

# xxx: there should be a test with `-d:nimTmathCase2 -d:danger --passc:-ffast-math`,
# but it requires disabling certain lines with `when not defined(nimTmathCase2)`

import std/math
import std/assertions


# Function for approximate comparison of floats
proc `==~`(x, y: float): bool = abs(x - y) < 1e-9


template main() =
  block:
    when not defined(js):
      # check for no side effect annotation
      proc mySqrt(num: float): float {.noSideEffect.} =
        # xxx unused
        sqrt(num)

      # check gamma function
      doAssert gamma(5.0) == 24.0 # 4!
      doAssert almostEqual(gamma(0.5), sqrt(PI))
      doAssert almostEqual(gamma(-0.5), -2 * sqrt(PI))
      doAssert lgamma(1.0) == 0.0 # ln(1.0) == 0.0
      doAssert almostEqual(lgamma(0.5), 0.5 * ln(PI))
      doAssert erf(6.0) > erf(5.0)
      doAssert erfc(6.0) < erfc(5.0)

  block: # sgn() tests
    doAssert sgn(1'i8) == 1
    doAssert sgn(1'i16) == 1
    doAssert sgn(1'i32) == 1
    doAssert sgn(1'i64) == 1
    doAssert sgn(1'u8) == 1
    doAssert sgn(1'u16) == 1
    doAssert sgn(1'u32) == 1
    doAssert sgn(1'u64) == 1
    doAssert sgn(-12342.8844'f32) == -1
    doAssert sgn(123.9834'f64) == 1
    doAssert sgn(0'i32) == 0
    doAssert sgn(0'f32) == 0
    doAssert sgn(-0.0'f64) == 0
    doAssert sgn(NegInf) == -1
    doAssert sgn(Inf) == 1
    doAssert sgn(NaN) == 0

  block: # fac() tests
    when nimvm: discard
    else:
      try:
        discard fac(-1)
      except AssertionDefect:
        discard

    doAssert fac(0) == 1
    doAssert fac(1) == 1
    doAssert fac(2) == 2
    doAssert fac(3) == 6
    doAssert fac(4) == 24
    doAssert fac(5) == 120

  block: # floorMod/floorDiv
    doAssert floorDiv(8, 3) == 2
    doAssert floorMod(8, 3) == 2

    doAssert floorDiv(8, -3) == -3
    doAssert floorMod(8, -3) == -1

    doAssert floorDiv(-8, 3) == -3
    doAssert floorMod(-8, 3) == 1

    doAssert floorDiv(-8, -3) == 2
    doAssert floorMod(-8, -3) == -2

    doAssert floorMod(8.0, -3.0) == -1.0
    doAssert floorMod(-8.5, 3.0) == 0.5

  block: # euclDiv/euclMod
    doAssert euclDiv(8, 3) == 2
    doAssert euclMod(8, 3) == 2

    doAssert euclDiv(8, -3) == -2
    doAssert euclMod(8, -3) == 2

    doAssert euclDiv(-8, 3) == -3
    doAssert euclMod(-8, 3) == 1

    doAssert euclDiv(-8, -3) == 3
    doAssert euclMod(-8, -3) == 1

    doAssert euclMod(8.0, -3.0) == 2.0
    doAssert euclMod(-8.5, 3.0) == 0.5

    doAssert euclDiv(9, 3) == 3
    doAssert euclMod(9, 3) == 0

    doAssert euclDiv(9, -3) == -3
    doAssert euclMod(9, -3) == 0

    doAssert euclDiv(-9, 3) == -3
    doAssert euclMod(-9, 3) == 0

    doAssert euclDiv(-9, -3) == 3
    doAssert euclMod(-9, -3) == 0

  block: # ceilDiv
    doAssert ceilDiv(8,  3) ==  3
    doAssert ceilDiv(8,  4) ==  2
    doAssert ceilDiv(8,  5) ==  2
    doAssert ceilDiv(11, 3) ==  4
    doAssert ceilDiv(12, 3) ==  4
    doAssert ceilDiv(13, 3) ==  5
    doAssert ceilDiv(41, 7) ==  6
    doAssert ceilDiv(0,  1) ==  0
    doAssert ceilDiv(1,  1) ==  1
    doAssert ceilDiv(1,  2) ==  1
    doAssert ceilDiv(2,  1) ==  2
    doAssert ceilDiv(2,  2) ==  1
    doAssert ceilDiv(0, high(int)) == 0
    doAssert ceilDiv(1, high(int)) == 1
    doAssert ceilDiv(0, high(int) - 1) == 0
    doAssert ceilDiv(1, high(int) - 1) == 1
    doAssert ceilDiv(high(int) div 2, high(int) div 2 + 1) == 1
    doAssert ceilDiv(high(int) div 2, high(int) div 2 + 2) == 1
    doAssert ceilDiv(high(int) div 2 + 1, high(int) div 2) == 2
    doAssert ceilDiv(high(int) div 2 + 2, high(int) div 2) == 2
    doAssert ceilDiv(high(int) div 2 + 1, high(int) div 2 + 1) == 1
    doAssert ceilDiv(high(int), 1) == high(int)
    doAssert ceilDiv(high(int) - 1, 1) == high(int) - 1
    doAssert ceilDiv(high(int) - 1, 2) == high(int) div 2
    doAssert ceilDiv(high(int) - 1, high(int)) == 1
    doAssert ceilDiv(high(int) - 1, high(int) - 1) == 1
    doAssert ceilDiv(high(int) - 1, high(int) - 2) == 2
    doAssert ceilDiv(high(int), high(int)) == 1
    doAssert ceilDiv(high(int), high(int) - 1) == 2
    doAssert ceilDiv(255'u8,  1'u8) == 255'u8
    doAssert ceilDiv(254'u8,  2'u8) == 127'u8
    when not defined(danger):
      doAssertRaises(AssertionDefect): discard ceilDiv(41,  0)
      doAssertRaises(AssertionDefect): discard ceilDiv(41, -1)
      doAssertRaises(AssertionDefect): discard ceilDiv(-1,  1)
      doAssertRaises(AssertionDefect): discard ceilDiv(-1, -1)
      doAssertRaises(AssertionDefect): discard ceilDiv(254'u8, 3'u8)
      doAssertRaises(AssertionDefect): discard ceilDiv(255'u8, 2'u8)

  block: # splitDecimal() tests
    doAssert splitDecimal(54.674).intpart == 54.0
    doAssert splitDecimal(54.674).floatpart ==~ 0.674
    doAssert splitDecimal(-693.4356).intpart == -693.0
    doAssert splitDecimal(-693.4356).floatpart ==~ -0.4356
    doAssert splitDecimal(0.0).intpart == 0.0
    doAssert splitDecimal(0.0).floatpart == 0.0

  block: # trunc tests for vcc
    doAssert trunc(-1.1) == -1
    doAssert trunc(1.1) == 1
    doAssert trunc(-0.1) == -0
    doAssert trunc(0.1) == 0

    # special case
    doAssert classify(trunc(1e1000000)) == fcInf
    doAssert classify(trunc(-1e1000000)) == fcNegInf
    when not defined(nimTmathCase2):
      doAssert classify(trunc(0.0/0.0)) == fcNan
    doAssert classify(trunc(0.0)) == fcZero

    # trick the compiler to produce signed zero
    let
      f_neg_one = -1.0
      f_zero = 0.0
      f_nan = f_zero / f_zero

    doAssert classify(trunc(f_neg_one*f_zero)) == fcNegZero

    doAssert trunc(-1.1'f32) == -1
    doAssert trunc(1.1'f32) == 1
    doAssert trunc(-0.1'f32) == -0
    doAssert trunc(0.1'f32) == 0
    doAssert classify(trunc(1e1000000'f32)) == fcInf
    doAssert classify(trunc(-1e1000000'f32)) == fcNegInf
    when not defined(nimTmathCase2):
      doAssert classify(trunc(f_nan.float32)) == fcNan
    doAssert classify(trunc(0.0'f32)) == fcZero

  block: # log
    doAssert log(4.0, 3.0) ==~ ln(4.0) / ln(3.0)
    doAssert log2(8.0'f64) == 3.0'f64
    doAssert log2(4.0'f64) == 2.0'f64
    doAssert log2(2.0'f64) == 1.0'f64
    doAssert log2(1.0'f64) == 0.0'f64
    doAssert classify(log2(0.0'f64)) == fcNegInf

    doAssert log2(8.0'f32) == 3.0'f32
    doAssert log2(4.0'f32) == 2.0'f32
    doAssert log2(2.0'f32) == 1.0'f32
    doAssert log2(1.0'f32) == 0.0'f32
    doAssert classify(log2(0.0'f32)) == fcNegInf

  block: # cumsum
    block: # cumsum int seq return
      let counts = [1, 2, 3, 4]
      doAssert counts.cumsummed == @[1, 3, 6, 10]
      let empty: seq[int] = @[]
      doAssert empty.cumsummed == @[]

    block: # cumsum float seq return
      let counts = [1.0, 2.0, 3.0, 4.0]
      doAssert counts.cumsummed == @[1.0, 3.0, 6.0, 10.0]
      let empty: seq[float] = @[]
      doAssert empty.cumsummed == @[]

    block: # cumsum int in-place
      var counts = [1, 2, 3, 4]
      counts.cumsum
      doAssert counts == [1, 3, 6, 10]
      var empty: seq[int] = @[]
      empty.cumsum
      doAssert empty == @[]

    block: # cumsum float in-place
      var counts = [1.0, 2.0, 3.0, 4.0]
      counts.cumsum
      doAssert counts == [1.0, 3.0, 6.0, 10.0]
      var empty: seq[float] = @[]
      empty.cumsum
      doAssert empty == @[]

  block: # ^ compiles for valid types
    doAssert: compiles(5 ^ 2)
    doAssert: compiles(5.5 ^ 2)
    doAssert: compiles(5.5 ^ 2.int8)
    doAssert: compiles(5.5 ^ 2.uint)
    doAssert: compiles(5.5 ^ 2.uint8)
    doAssert: not compiles(5.5 ^ 2.2)

  block: # isNaN
    doAssert NaN.isNaN
    doAssert not Inf.isNaN
    doAssert isNaN(Inf - Inf)
    doAssert not isNaN(0.0)
    doAssert not isNaN(3.1415926)
    doAssert not isNaN(0'f32)

  block: # signbit
    doAssert not signbit(0.0)
    doAssert signbit(-0.0)
    doAssert signbit(-0.1)
    doAssert not signbit(0.1)

    doAssert not signbit(Inf)
    doAssert signbit(-Inf)
    doAssert not signbit(NaN)

    let x1 = NaN
    let x2 = -NaN
    let x3 = -x1

    doAssert isNaN(x1)
    doAssert isNaN(x2)
    doAssert isNaN(x3)
    doAssert not signbit(x1)
    doAssert signbit(x2)
    doAssert signbit(x3)

  block: # copySign
    doAssert copySign(10.0, 1.0) == 10.0
    doAssert copySign(10.0, -1.0) == -10.0
    doAssert copySign(-10.0, -1.0) == -10.0
    doAssert copySign(-10.0, 1.0) == 10.0
    doAssert copySign(float(10), -1.0) == -10.0

    doAssert copySign(10.0'f64, 1.0) == 10.0
    doAssert copySign(10.0'f64, -1.0) == -10.0
    doAssert copySign(-10.0'f64, -1.0) == -10.0
    doAssert copySign(-10.0'f64, 1.0) == 10.0
    doAssert copySign(10'f64, -1.0) == -10.0

    doAssert copySign(10.0'f32, 1.0) == 10.0
    doAssert copySign(10.0'f32, -1.0) == -10.0
    doAssert copySign(-10.0'f32, -1.0) == -10.0
    doAssert copySign(-10.0'f32, 1.0) == 10.0
    doAssert copySign(10'f32, -1.0) == -10.0

    doAssert copySign(Inf, -1.0) == -Inf
    doAssert copySign(-Inf, 1.0) == Inf
    doAssert copySign(Inf, 1.0) == Inf
    doAssert copySign(-Inf, -1.0) == -Inf
    doAssert copySign(Inf, 0.0) == Inf
    doAssert copySign(Inf, -0.0) == -Inf
    doAssert copySign(-Inf, 0.0) == Inf
    doAssert copySign(-Inf, -0.0) == -Inf
    doAssert copySign(1.0, -0.0) == -1.0
    doAssert copySign(0.0, -0.0) == -0.0
    doAssert copySign(-1.0, 0.0) == 1.0
    doAssert copySign(10.0, 0.0) == 10.0
    doAssert copySign(-1.0, NaN) == 1.0
    doAssert copySign(10.0, NaN) == 10.0

    doAssert copySign(NaN, NaN).isNaN
    doAssert copySign(-NaN, NaN).isNaN
    doAssert copySign(NaN, -NaN).isNaN
    doAssert copySign(-NaN, -NaN).isNaN
    doAssert copySign(NaN, 0.0).isNaN
    doAssert copySign(NaN, -0.0).isNaN
    doAssert copySign(-NaN, 0.0).isNaN
    doAssert copySign(-NaN, -0.0).isNaN

    doAssert copySign(-1.0, NaN) == 1.0
    doAssert copySign(-1.0, -NaN) == -1.0
    doAssert copySign(1.0, copySign(NaN, -1.0)) == -1.0

  block: # almostEqual
    doAssert almostEqual(3.141592653589793, 3.1415926535897936)
    doAssert almostEqual(1.6777215e7'f32, 1.6777216e7'f32)
    doAssert almostEqual(Inf, Inf)
    doAssert almostEqual(-Inf, -Inf)
    doAssert not almostEqual(Inf, -Inf)
    doAssert not almostEqual(-Inf, Inf)
    doAssert not almostEqual(Inf, NaN)
    doAssert not almostEqual(NaN, NaN)

  block: # round
    block: # Round to 0 decimal places
      doAssert round(54.652) == 55.0
      doAssert round(54.352) == 54.0
      doAssert round(-54.652) == -55.0
      doAssert round(-54.352) == -54.0
      doAssert round(0.0) == 0.0
      doAssert 1 / round(0.0) == Inf
      doAssert 1 / round(-0.0) == -Inf
      doAssert round(Inf) == Inf
      doAssert round(-Inf) == -Inf
      doAssert round(NaN).isNaN
      doAssert round(-NaN).isNaN
      doAssert round(-0.5) == -1.0
      doAssert round(0.5) == 1.0
      doAssert round(-1.5) == -2.0
      doAssert round(1.5) == 2.0
      doAssert round(-2.5) == -3.0
      doAssert round(2.5) == 3.0
      doAssert round(2.5'f32) == 3.0'f32
      doAssert round(2.5'f64) == 3.0'f64

    block: # func round*[T: float32|float64](x: T, places: int): T
      doAssert round(54.345, 0) == 54.0
      template fn(x) =
        doAssert round(x, 2).almostEqual 54.35
        doAssert round(x, 2).almostEqual 54.35
        doAssert round(x, -1).almostEqual 50.0
        doAssert round(x, -2).almostEqual 100.0
        doAssert round(x, -3).almostEqual 0.0
      fn(54.346)
      fn(54.346'f32)

  block: # abs
    doAssert 1.0 / abs(-0.0) == Inf
    doAssert 1.0 / abs(0.0) == Inf
    doAssert -1.0 / abs(-0.0) == -Inf
    doAssert -1.0 / abs(0.0) == -Inf
    doAssert abs(0.0) == 0.0
    doAssert abs(0.0'f32) == 0.0'f32

    doAssert abs(Inf) == Inf
    doAssert abs(-Inf) == Inf
    doAssert abs(NaN).isNaN
    doAssert abs(-NaN).isNaN

  block: # classify
    doAssert classify(0.3) == fcNormal
    doAssert classify(-0.3) == fcNormal
    doAssert classify(5.0e-324) == fcSubnormal
    doAssert classify(-5.0e-324) == fcSubnormal
    doAssert classify(0.0) == fcZero
    doAssert classify(-0.0) == fcNegZero
    doAssert classify(NaN) == fcNan
    doAssert classify(0.3 / 0.0) == fcInf
    doAssert classify(Inf) == fcInf
    doAssert classify(-0.3 / 0.0) == fcNegInf
    doAssert classify(-Inf) == fcNegInf

  block: # sum
    let empty: seq[int] = @[]
    doAssert sum(empty) == 0
    doAssert sum([1, 2, 3, 4]) == 10
    doAssert sum([-4, 3, 5]) == 4

  block: # prod
    let empty: seq[int] = @[]
    doAssert prod(empty) == 1
    doAssert prod([1, 2, 3, 4]) == 24
    doAssert prod([-4, 3, 5]) == -60
    doAssert almostEqual(prod([1.5, 3.4]), 5.1)
    let x: seq[float] = @[]
    doAssert prod(x) == 1.0

  block: # clamp range
    doAssert clamp(10, 1..5) == 5
    doAssert clamp(3, 1..5) == 3
    doAssert clamp(5, 1..5) == 5
    doAssert clamp(42.0, 1.0 .. 3.1415926535) == 3.1415926535
    doAssert clamp(NaN, 1.0 .. 2.0).isNaN
    doAssert clamp(-Inf, -Inf .. -1.0) == -Inf
    type A = enum a0, a1, a2, a3, a4, a5
    doAssert a1.clamp(a2..a4) == a2
    doAssert clamp((3, 0), (1, 0) .. (2, 9)) == (2, 9)

  block: # edge cases
    doAssert sqrt(-4.0).isNaN

    doAssert ln(0.0) == -Inf
    doAssert ln(-0.0) == -Inf
    doAssert ln(-12.0).isNaN

    doAssert log10(0.0) == -Inf
    doAssert log10(-0.0) == -Inf
    doAssert log10(-12.0).isNaN

    doAssert log2(0.0) == -Inf
    doAssert log2(-0.0) == -Inf
    doAssert log2(-12.0).isNaN

    when nimvm: discard
    else:
      doAssert frexp(0.0) == (0.0, 0)
      doAssert frexp(-0.0) == (-0.0, 0)
      doAssert classify(frexp(-0.0)[0]) == fcNegZero

    when not defined(js):
      doAssert gamma(0.0) == Inf
      doAssert gamma(-0.0) == -Inf
      doAssert gamma(-1.0).isNaN

      doAssert lgamma(0.0) == Inf
      doAssert lgamma(-0.0) == Inf
      doAssert lgamma(-1.0) == Inf


static: main()
main()