summary refs log tree commit diff stats
path: root/tests/stdlib/tos.nim
blob: 23fa4d098a6e8b2e1428be7287b050575a861be7 (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
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
discard """
  output: '''
All:
__really_obscure_dir_name/are.x
__really_obscure_dir_name/created
__really_obscure_dir_name/dirs
__really_obscure_dir_name/files.q
__really_obscure_dir_name/some
__really_obscure_dir_name/test
__really_obscure_dir_name/testing.r
__really_obscure_dir_name/these.txt
Files:
__really_obscure_dir_name/are.x
__really_obscure_dir_name/files.q
__really_obscure_dir_name/testing.r
__really_obscure_dir_name/these.txt
Dirs:
__really_obscure_dir_name/created
__really_obscure_dir_name/dirs
__really_obscure_dir_name/some
__really_obscure_dir_name/test
Raises
Raises
'''
"""
# test os path creation, iteration, and deletion

import os, strutils, pathnorm

block fileOperations:
  let files = @["these.txt", "are.x", "testing.r", "files.q"]
  let dirs = @["some", "created", "test", "dirs"]

  let dname = "__really_obscure_dir_name"

  createDir(dname)
  doAssert dirExists(dname)

  # Test creating files and dirs
  for dir in dirs:
    createDir(dname/dir)
    doAssert dirExists(dname/dir)

  for file in files:
    let fh = open(dname/file, fmReadWrite)
    fh.close()
    doAssert fileExists(dname/file)

  echo "All:"

  template norm(x): untyped =
    (when defined(windows): x.replace('\\', '/') else: x)

  for path in walkPattern(dname/"*"):
    echo path.norm

  echo "Files:"

  for path in walkFiles(dname/"*"):
    echo path.norm

  echo "Dirs:"

  for path in walkDirs(dname/"*"):
    echo path.norm

  # Test removal of files dirs
  for dir in dirs:
    removeDir(dname/dir)
    doAssert: not dirExists(dname/dir)

  for file in files:
    removeFile(dname/file)
    doAssert: not fileExists(dname/file)

  removeDir(dname)
  doAssert: not dirExists(dname)

  # createDir should create recursive directories
  createDir(dirs[0] / dirs[1])
  doAssert dirExists(dirs[0] / dirs[1]) # true
  removeDir(dirs[0])

  # createDir should properly handle trailing separator
  createDir(dname / "")
  doAssert dirExists(dname) # true
  removeDir(dname)

  # createDir should raise IOError if the path exists
  # and is not a directory
  open(dname, fmWrite).close
  try:
    createDir(dname)
  except IOError:
    echo "Raises"
  removeFile(dname)

  # removeFile should not remove directory
  createDir(dname)
  try:
    removeFile(dname)
  except OSError:
    echo "Raises"
  removeDir(dname)

  # test copyDir:
  createDir("a/b")
  open("a/b/file.txt", fmWrite).close
  createDir("a/b/c")
  open("a/b/c/fileC.txt", fmWrite).close

  copyDir("a", "../dest/a")
  removeDir("a")

  doAssert dirExists("../dest/a/b")
  doAssert fileExists("../dest/a/b/file.txt")

  doAssert fileExists("../dest/a/b/c/fileC.txt")
  removeDir("../dest")

  # test copyDir:
  # if separator at the end of a path
  createDir("a/b")
  open("a/file.txt", fmWrite).close

  copyDir("a/", "../dest/a/")
  removeDir("a")

  doAssert dirExists("../dest/a/b")
  doAssert fileExists("../dest/a/file.txt")
  removeDir("../dest")

import times
block modificationTime:
  # Test get/set modification times
  # Should support at least microsecond resolution
  let tm = fromUnix(0) + 100.microseconds
  writeFile("a", "")
  setLastModificationTime("a", tm)

  when defined(macosx):
    doAssert true
  else:
    doAssert getLastModificationTime("a") == tm
  removeFile("a")

block walkDirRec:
  createDir("walkdir_test/a/b")
  open("walkdir_test/a/b/file_1", fmWrite).close()
  open("walkdir_test/a/file_2", fmWrite).close()

  for p in walkDirRec("walkdir_test"):
    doAssert p.fileExists
    doAssert p.startsWith("walkdir_test")

  var s: seq[string]
  for p in walkDirRec("walkdir_test", {pcFile}, {pcDir}, relative=true):
    s.add(p)

  doAssert s.len == 2
  doAssert "a" / "b" / "file_1" in s
  doAssert "a" / "file_2" in s

  removeDir("walkdir_test")

when not defined(windows):
  block walkDirRelative:
    createDir("walkdir_test")
    createSymlink(".", "walkdir_test/c")
    for k, p in walkDir("walkdir_test", true):
      doAssert k == pcLinkToDir
    removeDir("walkdir_test")

block normalizedPath:
  doAssert normalizedPath("") == ""
  block relative:
    doAssert normalizedPath(".") == "."
    doAssert normalizedPath("foo/..") == "."
    doAssert normalizedPath("foo//../bar/.") == "bar"
    doAssert normalizedPath("..") == ".."
    doAssert normalizedPath("../") == ".."
    doAssert normalizedPath("../..") == unixToNativePath"../.."
    doAssert normalizedPath("../a/..") == ".."
    doAssert normalizedPath("../a/../") == ".."
    doAssert normalizedPath("./") == "."

  block absolute:
    doAssert normalizedPath("/") == unixToNativePath"/"
    doAssert normalizedPath("/.") == unixToNativePath"/"
    doAssert normalizedPath("/..") == unixToNativePath"/.."
    doAssert normalizedPath("/../") == unixToNativePath"/.."
    doAssert normalizedPath("/../..") == unixToNativePath"/../.."
    doAssert normalizedPath("/../../") == unixToNativePath"/../.."
    doAssert normalizedPath("/../../../") == unixToNativePath"/../../.."
    doAssert normalizedPath("/a/b/../../foo") == unixToNativePath"/foo"
    doAssert normalizedPath("/a/b/../../../foo") == unixToNativePath"/../foo"
    doAssert normalizedPath("/./") == unixToNativePath"/"
    doAssert normalizedPath("//") == unixToNativePath"/"
    doAssert normalizedPath("///") == unixToNativePath"/"
    doAssert normalizedPath("/a//b") == unixToNativePath"/a/b"
    doAssert normalizedPath("/a///b") == unixToNativePath"/a/b"
    doAssert normalizedPath("/a/b/c/..") == unixToNativePath"/a/b"
    doAssert normalizedPath("/a/b/c/../") == unixToNativePath"/a/b"

block isHidden:
  when defined(posix):
    doAssert ".foo.txt".isHidden
    doAssert "bar/.foo.ext".isHidden
    doAssert: not "bar".isHidden
    doAssert: not "foo/".isHidden
    # Corner cases: paths are not normalized when determining `isHidden`
    doAssert: not ".foo/.".isHidden
    doAssert: not ".foo/..".isHidden

block absolutePath:
  doAssertRaises(ValueError): discard absolutePath("a", "b")
  doAssert absolutePath("a") == getCurrentDir() / "a"
  doAssert absolutePath("a", "/b") == "/b" / "a"
  when defined(Posix):
    doAssert absolutePath("a", "/b/") == "/b" / "a"
    doAssert absolutePath("a", "/b/c") == "/b/c" / "a"
    doAssert absolutePath("/a", "b/") == "/a"

block splitFile:
  doAssert splitFile("") == ("", "", "")
  doAssert splitFile("abc/") == ("abc", "", "")
  doAssert splitFile("/") == ("/", "", "")
  doAssert splitFile("./abc") == (".", "abc", "")
  doAssert splitFile(".txt") == ("", ".txt", "")
  doAssert splitFile("abc/.txt") == ("abc", ".txt", "")
  doAssert splitFile("abc") == ("", "abc", "")
  doAssert splitFile("abc.txt") == ("", "abc", ".txt")
  doAssert splitFile("/abc.txt") == ("/", "abc", ".txt")
  doAssert splitFile("/foo/abc.txt") == ("/foo", "abc", ".txt")
  doAssert splitFile("/foo/abc.txt.gz") == ("/foo", "abc.txt", ".gz")
  doAssert splitFile(".") == ("", ".", "")
  doAssert splitFile("abc/.") == ("abc", ".", "")
  doAssert splitFile("..") == ("", "..", "")
  doAssert splitFile("a/..") == ("a", "..", "")

# execShellCmd is tested in tosproc

block ospaths:
  doAssert unixToNativePath("") == ""
  doAssert unixToNativePath(".") == $CurDir
  doAssert unixToNativePath("..") == $ParDir
  doAssert isAbsolute(unixToNativePath("/"))
  doAssert isAbsolute(unixToNativePath("/", "a"))
  doAssert isAbsolute(unixToNativePath("/a"))
  doAssert isAbsolute(unixToNativePath("/a", "a"))
  doAssert isAbsolute(unixToNativePath("/a/b"))
  doAssert isAbsolute(unixToNativePath("/a/b", "a"))
  doAssert unixToNativePath("a/b") == joinPath("a", "b")

  when defined(macos):
    doAssert unixToNativePath("./") == ":"
    doAssert unixToNativePath("./abc") == ":abc"
    doAssert unixToNativePath("../abc") == "::abc"
    doAssert unixToNativePath("../../abc") == ":::abc"
    doAssert unixToNativePath("/abc", "a") == "abc"
    doAssert unixToNativePath("/abc/def", "a") == "abc:def"
  elif doslikeFileSystem:
    doAssert unixToNativePath("./") == ".\\"
    doAssert unixToNativePath("./abc") == ".\\abc"
    doAssert unixToNativePath("../abc") == "..\\abc"
    doAssert unixToNativePath("../../abc") == "..\\..\\abc"
    doAssert unixToNativePath("/abc", "a") == "a:\\abc"
    doAssert unixToNativePath("/abc/def", "a") == "a:\\abc\\def"
  else:
    #Tests for unix
    doAssert unixToNativePath("./") == "./"
    doAssert unixToNativePath("./abc") == "./abc"
    doAssert unixToNativePath("../abc") == "../abc"
    doAssert unixToNativePath("../../abc") == "../../abc"
    doAssert unixToNativePath("/abc", "a") == "/abc"
    doAssert unixToNativePath("/abc/def", "a") == "/abc/def"

  block extractFilenameTest:
    doAssert extractFilename("") == ""
    when defined(posix):
      doAssert extractFilename("foo/bar") == "bar"
      doAssert extractFilename("foo/bar.txt") == "bar.txt"
      doAssert extractFilename("foo/") == ""
      doAssert extractFilename("/") == ""
    when doslikeFileSystem:
      doAssert extractFilename(r"foo\bar") == "bar"
      doAssert extractFilename(r"foo\bar.txt") == "bar.txt"
      doAssert extractFilename(r"foo\") == ""
      doAssert extractFilename(r"C:\") == ""

  block lastPathPartTest:
    doAssert lastPathPart("") == ""
    when defined(posix):
      doAssert lastPathPart("foo/bar.txt") == "bar.txt"
      doAssert lastPathPart("foo/") == "foo"
      doAssert lastPathPart("/") == ""
    when doslikeFileSystem:
      doAssert lastPathPart(r"foo\bar.txt") == "bar.txt"
      doAssert lastPathPart(r"foo\") == "foo"

  template canon(x): untyped = normalizePath(x, '/')
  doAssert canon"/foo/../bar" == "/bar"
  doAssert canon"foo/../bar" == "bar"

  doAssert canon"/f/../bar///" == "/bar"
  doAssert canon"f/..////bar" == "bar"

  doAssert canon"../bar" == "../bar"
  doAssert canon"/../bar" == "/../bar"

  doAssert canon("foo/../../bar/") == "../bar"
  doAssert canon("./bla/blob/") == "bla/blob"
  doAssert canon(".hiddenFile") == ".hiddenFile"
  doAssert canon("./bla/../../blob/./zoo.nim") == "../blob/zoo.nim"

  doAssert canon("C:/file/to/this/long") == "C:/file/to/this/long"
  doAssert canon("") == ""
  doAssert canon("foobar") == "foobar"
  doAssert canon("f/////////") == "f"

  doAssert relativePath("/foo/bar//baz.nim", "/foo", '/') == "bar/baz.nim"
  doAssert normalizePath("./foo//bar/../baz", '/') == "foo/baz"

  doAssert relativePath("/Users/me/bar/z.nim", "/Users/other/bad", '/') == "../../me/bar/z.nim"

  doAssert relativePath("/Users/me/bar/z.nim", "/Users/other", '/') == "../me/bar/z.nim"
  doAssert relativePath("/Users///me/bar//z.nim", "//Users/", '/') == "me/bar/z.nim"
  doAssert relativePath("/Users/me/bar/z.nim", "/Users/me", '/') == "bar/z.nim"
  doAssert relativePath("", "/users/moo", '/') == ""
  doAssert relativePath("foo", "", '/') == "foo"

  doAssert joinPath("usr", "") == unixToNativePath"usr/"
  doAssert joinPath("", "lib") == "lib"
  doAssert joinPath("", "/lib") == unixToNativePath"/lib"
  doAssert joinPath("usr/", "/lib") == unixToNativePath"usr/lib"
> n.sons[2] # symmetrical: if b.kind notin ordIntLit: swap(a, b) if b.kind in ordIntLit: let x = b.intVal|+|1 if (x and -x) == x and x >= 0: result = makeRange(a.typ, 0, b.intVal) of mModU: let a = n.sons[1] let b = n.sons[2] if a.kind in ordIntLit: if b.intVal >= 0: result = makeRange(a.typ, 0, b.intVal-1) else: result = makeRange(a.typ, b.intVal+1, 0) of mModI: # so ... if you ever wondered about modulo's signedness; this defines it: let a = n.sons[1] let b = n.sons[2] if b.kind in {nkIntLit..nkUInt64Lit}: if b.intVal >= 0: result = makeRange(a.typ, -(b.intVal-1), b.intVal-1) else: result = makeRange(a.typ, b.intVal+1, -(b.intVal+1)) of mDivI, mDivU: binaryOp(`|div|`) of mMinI: commutativeOp(min) of mMaxI: commutativeOp(max) else: discard discard """ mShlI, mShrI, mAddF64, mSubF64, mMulF64, mDivF64, mMaxF64, mMinF64 """ proc evalIs(n, a: PNode): PNode = # XXX: This should use the standard isOpImpl internalAssert a.kind == nkSym and a.sym.kind == skType internalAssert n.sonsLen == 3 and n[2].kind in {nkStrLit..nkTripleStrLit, nkType} let t1 = a.sym.typ if n[2].kind in {nkStrLit..nkTripleStrLit}: case n[2].strVal.normalize of "closure": let t = skipTypes(t1, abstractRange) result = newIntNode(nkIntLit, ord(t.kind == tyProc and t.callConv == ccClosure and tfIterator notin t.flags)) of "iterator": let t = skipTypes(t1, abstractRange) result = newIntNode(nkIntLit, ord(t.kind == tyProc and t.callConv == ccClosure and tfIterator in t.flags)) else: discard else: # XXX semexprs.isOpImpl is slightly different and requires a context. yay. let t2 = n[2].typ var match = sameType(t1, t2) result = newIntNode(nkIntLit, ord(match)) result.typ = n.typ proc evalOp(m: TMagic, n, a, b, c: PNode): PNode = # b and c may be nil result = nil case m of mOrd: result = newIntNodeT(getOrdValue(a), n) of mChr: result = newIntNodeT(getInt(a), n) of mUnaryMinusI, mUnaryMinusI64: result = newIntNodeT(- getInt(a), n) of mUnaryMinusF64: result = newFloatNodeT(- getFloat(a), n) of mNot: result = newIntNodeT(1 - getInt(a), n) of mCard: result = newIntNodeT(nimsets.cardSet(a), n) of mBitnotI: result = newIntNodeT(not getInt(a), n) of mLengthArray: result = newIntNodeT(lengthOrd(a.typ), n) of mLengthSeq, mLengthOpenArray, mXLenSeq, mLengthStr, mXLenStr: if a.kind == nkNilLit: result = newIntNodeT(0, n) elif a.kind in {nkStrLit..nkTripleStrLit}: result = newIntNodeT(len a.strVal, n) else: result = newIntNodeT(sonsLen(a), n) # BUGFIX of mUnaryPlusI, mUnaryPlusF64: result = a # throw `+` away of mToFloat, mToBiggestFloat: result = newFloatNodeT(toFloat(int(getInt(a))), n) of mToInt, mToBiggestInt: result = newIntNodeT(system.toInt(getFloat(a)), n) of mAbsF64: result = newFloatNodeT(abs(getFloat(a)), n) of mAbsI: if getInt(a) >= 0: result = a else: result = newIntNodeT(- getInt(a), n) of mZe8ToI, mZe8ToI64, mZe16ToI, mZe16ToI64, mZe32ToI64, mZeIToI64: # byte(-128) = 1...1..1000_0000'64 --> 0...0..1000_0000'64 result = newIntNodeT(getInt(a) and (`shl`(1, getSize(a.typ) * 8) - 1), n) of mToU8: result = newIntNodeT(getInt(a) and 0x000000FF, n) of mToU16: result = newIntNodeT(getInt(a) and 0x0000FFFF, n) of mToU32: result = newIntNodeT(getInt(a) and 0x00000000FFFFFFFF'i64, n) of mUnaryLt: result = newIntNodeT(getOrdValue(a) |-| 1, n) of mSucc: result = newIntNodeT(getOrdValue(a) |+| getInt(b), n) of mPred: result = newIntNodeT(getOrdValue(a) |-| getInt(b), n) of mAddI: result = newIntNodeT(getInt(a) |+| getInt(b), n) of mSubI: result = newIntNodeT(getInt(a) |-| getInt(b), n) of mMulI: result = newIntNodeT(getInt(a) |*| getInt(b), n) of mMinI: if getInt(a) > getInt(b): result = newIntNodeT(getInt(b), n) else: result = newIntNodeT(getInt(a), n) of mMaxI: if getInt(a) > getInt(b): result = newIntNodeT(getInt(a), n) else: result = newIntNodeT(getInt(b), n) of mShlI: case skipTypes(n.typ, abstractRange).kind of tyInt8: result = newIntNodeT(int8(getInt(a)) shl int8(getInt(b)), n) of tyInt16: result = newIntNodeT(int16(getInt(a)) shl int16(getInt(b)), n) of tyInt32: result = newIntNodeT(int32(getInt(a)) shl int32(getInt(b)), n) of tyInt64, tyInt, tyUInt..tyUInt64: result = newIntNodeT(`shl`(getInt(a), getInt(b)), n) else: internalError(n.info, "constant folding for shl") of mShrI: case skipTypes(n.typ, abstractRange).kind of tyInt8: result = newIntNodeT(int8(getInt(a)) shr int8(getInt(b)), n) of tyInt16: result = newIntNodeT(int16(getInt(a)) shr int16(getInt(b)), n) of tyInt32: result = newIntNodeT(int32(getInt(a)) shr int32(getInt(b)), n) of tyInt64, tyInt, tyUInt..tyUInt64: result = newIntNodeT(`shr`(getInt(a), getInt(b)), n) else: internalError(n.info, "constant folding for shr") of mDivI: let y = getInt(b) if y != 0: result = newIntNodeT(`|div|`(getInt(a), y), n) of mModI: let y = getInt(b) if y != 0: result = newIntNodeT(`|mod|`(getInt(a), y), n) of mAddF64: result = newFloatNodeT(getFloat(a) + getFloat(b), n) of mSubF64: result = newFloatNodeT(getFloat(a) - getFloat(b), n) of mMulF64: result = newFloatNodeT(getFloat(a) * getFloat(b), n) of mDivF64: if getFloat(b) == 0.0: if getFloat(a) == 0.0: result = newFloatNodeT(NaN, n) else: result = newFloatNodeT(Inf, n) else: result = newFloatNodeT(getFloat(a) / getFloat(b), n) of mMaxF64: if getFloat(a) > getFloat(b): result = newFloatNodeT(getFloat(a), n) else: result = newFloatNodeT(getFloat(b), n) of mMinF64: if getFloat(a) > getFloat(b): result = newFloatNodeT(getFloat(b), n) else: result = newFloatNodeT(getFloat(a), n) of mIsNil: result = newIntNodeT(ord(a.kind == nkNilLit), n) of mLtI, mLtB, mLtEnum, mLtCh: result = newIntNodeT(ord(getOrdValue(a) < getOrdValue(b)), n) of mLeI, mLeB, mLeEnum, mLeCh: result = newIntNodeT(ord(getOrdValue(a) <= getOrdValue(b)), n) of mEqI, mEqB, mEqEnum, mEqCh: result = newIntNodeT(ord(getOrdValue(a) == getOrdValue(b)), n) of mLtF64: result = newIntNodeT(ord(getFloat(a) < getFloat(b)), n) of mLeF64: result = newIntNodeT(ord(getFloat(a) <= getFloat(b)), n) of mEqF64: result = newIntNodeT(ord(getFloat(a) == getFloat(b)), n) of mLtStr: result = newIntNodeT(ord(getStr(a) < getStr(b)), n) of mLeStr: result = newIntNodeT(ord(getStr(a) <= getStr(b)), n) of mEqStr: result = newIntNodeT(ord(getStr(a) == getStr(b)), n) of mLtU, mLtU64: result = newIntNodeT(ord(`<%`(getOrdValue(a), getOrdValue(b))), n) of mLeU, mLeU64: result = newIntNodeT(ord(`<=%`(getOrdValue(a), getOrdValue(b))), n) of mBitandI, mAnd: result = newIntNodeT(a.getInt and b.getInt, n) of mBitorI, mOr: result = newIntNodeT(getInt(a) or getInt(b), n) of mBitxorI, mXor: result = newIntNodeT(a.getInt xor b.getInt, n) of mAddU: result = newIntNodeT(`+%`(getInt(a), getInt(b)), n) of mSubU: result = newIntNodeT(`-%`(getInt(a), getInt(b)), n) of mMulU: result = newIntNodeT(`*%`(getInt(a), getInt(b)), n) of mModU: let y = getInt(b) if y != 0: result = newIntNodeT(`%%`(getInt(a), y), n) of mDivU: let y = getInt(b) if y != 0: result = newIntNodeT(`/%`(getInt(a), y), n) of mLeSet: result = newIntNodeT(ord(containsSets(a, b)), n) of mEqSet: result = newIntNodeT(ord(equalSets(a, b)), n) of mLtSet: result = newIntNodeT(ord(containsSets(a, b) and not equalSets(a, b)), n) of mMulSet: result = nimsets.intersectSets(a, b) result.info = n.info of mPlusSet: result = nimsets.unionSets(a, b) result.info = n.info of mMinusSet: result = nimsets.diffSets(a, b) result.info = n.info of mSymDiffSet: result = nimsets.symdiffSets(a, b) result.info = n.info of mConStrStr: result = newStrNodeT(getStrOrChar(a) & getStrOrChar(b), n) of mInSet: result = newIntNodeT(ord(inSet(a, b)), n) of mRepr: # BUGFIX: we cannot eval mRepr here for reasons that I forgot. discard of mIntToStr, mInt64ToStr: result = newStrNodeT($(getOrdValue(a)), n) of mBoolToStr: if getOrdValue(a) == 0: result = newStrNodeT("false", n) else: result = newStrNodeT("true", n) of mCopyStr: result = newStrNodeT(substr(getStr(a), int(getOrdValue(b))), n) of mCopyStrLast: result = newStrNodeT(substr(getStr(a), int(getOrdValue(b)), int(getOrdValue(c))), n) of mFloatToStr: result = newStrNodeT($getFloat(a), n) of mCStrToStr, mCharToStr: if a.kind == nkBracket: var s = "" for b in a.sons: s.add b.getStrOrChar result = newStrNodeT(s, n) else: result = newStrNodeT(getStrOrChar(a), n) of mStrToStr: result = a of mEnumToStr: result = newStrNodeT(ordinalValToString(a), n) of mArrToSeq: result = copyTree(a) result.typ = n.typ of mCompileOption: result = newIntNodeT(ord(commands.testCompileOption(a.getStr, n.info)), n) of mCompileOptionArg: result = newIntNodeT(ord( testCompileOptionArg(getStr(a), getStr(b), n.info)), n) of mEqProc: result = newIntNodeT(ord( exprStructuralEquivalent(a, b, strictSymEquality=true)), n) else: discard proc getConstIfExpr(c: PSym, n: PNode): PNode = result = nil for i in countup(0, sonsLen(n) - 1): var it = n.sons[i] if it.len == 2: var e = getConstExpr(c, it.sons[0]) if e == nil: return nil if getOrdValue(e) != 0: if result == nil: result = getConstExpr(c, it.sons[1]) if result == nil: return elif it.len == 1: if result == nil: result = getConstExpr(c, it.sons[0]) else: internalError(it.info, "getConstIfExpr()") proc partialAndExpr(c: PSym, n: PNode): PNode = # partial evaluation result = n var a = getConstExpr(c, n.sons[1]) var b = getConstExpr(c, n.sons[2]) if a != nil: if getInt(a) == 0: result = a elif b != nil: result = b else: result = n.sons[2] elif b != nil: if getInt(b) == 0: result = b else: result = n.sons[1] proc partialOrExpr(c: PSym, n: PNode): PNode = # partial evaluation result = n var a = getConstExpr(c, n.sons[1]) var b = getConstExpr(c, n.sons[2]) if a != nil: if getInt(a) != 0: result = a elif b != nil: result = b else: result = n.sons[2] elif b != nil: if getInt(b) != 0: result = b else: result = n.sons[1] proc leValueConv(a, b: PNode): bool = result = false case a.kind of nkCharLit..nkUInt64Lit: case b.kind of nkCharLit..nkUInt64Lit: result = a.intVal <= b.intVal of nkFloatLit..nkFloat128Lit: result = a.intVal <= round(b.floatVal).int else: internalError(a.info, "leValueConv") of nkFloatLit..nkFloat128Lit: case b.kind of nkFloatLit..nkFloat128Lit: result = a.floatVal <= b.floatVal of nkCharLit..nkUInt64Lit: result = a.floatVal <= toFloat(int(b.intVal)) else: internalError(a.info, "leValueConv") else: internalError(a.info, "leValueConv") proc magicCall(m: PSym, n: PNode): PNode = if sonsLen(n) <= 1: return var s = n.sons[0].sym var a = getConstExpr(m, n.sons[1]) var b, c: PNode if a == nil: return if sonsLen(n) > 2: b = getConstExpr(m, n.sons[2]) if b == nil: return if sonsLen(n) > 3: c = getConstExpr(m, n.sons[3]) if c == nil: return result = evalOp(s.magic, n, a, b, c) proc getAppType(n: PNode): PNode = if gGlobalOptions.contains(optGenDynLib): result = newStrNodeT("lib", n) elif gGlobalOptions.contains(optGenStaticLib): result = newStrNodeT("staticlib", n) elif gGlobalOptions.contains(optGenGuiApp): result = newStrNodeT("gui", n) else: result = newStrNodeT("console", n) proc rangeCheck(n: PNode, value: BiggestInt) = if value < firstOrd(n.typ) or value > lastOrd(n.typ): localError(n.info, errGenerated, "cannot convert " & $value & " to " & typeToString(n.typ)) proc foldConv*(n, a: PNode; check = false): PNode = # XXX range checks? case skipTypes(n.typ, abstractRange).kind of tyInt..tyInt64, tyUInt..tyUInt64: case skipTypes(a.typ, abstractRange).kind of tyFloat..tyFloat64: result = newIntNodeT(int(getFloat(a)), n) of tyChar: result = newIntNodeT(getOrdValue(a), n) else: result = a result.typ = n.typ if check: rangeCheck(n, result.intVal) of tyFloat..tyFloat64: case skipTypes(a.typ, abstractRange).kind of tyInt..tyInt64, tyEnum, tyBool, tyChar: result = newFloatNodeT(toBiggestFloat(getOrdValue(a)), n) else: result = a result.typ = n.typ of tyOpenArray, tyVarargs, tyProc: discard else: result = a result.typ = n.typ proc getArrayConstr(m: PSym, n: PNode): PNode = if n.kind == nkBracket: result = n else: result = getConstExpr(m, n) if result == nil: result = n proc foldArrayAccess(m: PSym, n: PNode): PNode = var x = getConstExpr(m, n.sons[0]) if x == nil or x.typ.skipTypes({tyGenericInst}).kind == tyTypeDesc: return var y = getConstExpr(m, n.sons[1]) if y == nil: return var idx = getOrdValue(y) case x.kind of nkPar: if idx >= 0 and idx < sonsLen(x): result = x.sons[int(idx)] if result.kind == nkExprColonExpr: result = result.sons[1] else: localError(n.info, errIndexOutOfBounds) of nkBracket: idx = idx - x.typ.firstOrd if idx >= 0 and idx < x.len: result = x.sons[int(idx)] else: localError(n.info, errIndexOutOfBounds) of nkStrLit..nkTripleStrLit: result = newNodeIT(nkCharLit, x.info, n.typ) if idx >= 0 and idx < len(x.strVal): result.intVal = ord(x.strVal[int(idx)]) elif idx == len(x.strVal): discard else: localError(n.info, errIndexOutOfBounds) else: discard proc foldFieldAccess(m: PSym, n: PNode): PNode = # a real field access; proc calls have already been transformed var x = getConstExpr(m, n.sons[0]) if x == nil or x.kind notin {nkObjConstr, nkPar}: return var field = n.sons[1].sym for i in countup(ord(x.kind == nkObjConstr), sonsLen(x) - 1): var it = x.sons[i] if it.kind != nkExprColonExpr: # lookup per index: result = x.sons[field.position] if result.kind == nkExprColonExpr: result = result.sons[1] return if it.sons[0].sym.name.id == field.name.id: result = x.sons[i].sons[1] return localError(n.info, errFieldXNotFound, field.name.s) proc foldConStrStr(m: PSym, n: PNode): PNode = result = newNodeIT(nkStrLit, n.info, n.typ) result.strVal = "" for i in countup(1, sonsLen(n) - 1): let a = getConstExpr(m, n.sons[i]) if a == nil: return nil result.strVal.add(getStrOrChar(a)) proc newSymNodeTypeDesc*(s: PSym; info: TLineInfo): PNode = result = newSymNode(s, info) result.typ = newType(tyTypeDesc, s.owner) result.typ.addSonSkipIntLit(s.typ) proc getConstExpr(m: PSym, n: PNode): PNode = result = nil case n.kind of nkSym: var s = n.sym case s.kind of skEnumField: result = newIntNodeT(s.position, n) of skConst: case s.magic of mIsMainModule: result = newIntNodeT(ord(sfMainModule in m.flags), n) of mCompileDate: result = newStrNodeT(times.getDateStr(), n) of mCompileTime: result = newStrNodeT(times.getClockStr(), n) of mCpuEndian: result = newIntNodeT(ord(CPU[targetCPU].endian), n) of mHostOS: result = newStrNodeT(toLowerAscii(platform.OS[targetOS].name), n) of mHostCPU: result = newStrNodeT(platform.CPU[targetCPU].name.toLowerAscii, n) of mAppType: result = getAppType(n) of mNaN: result = newFloatNodeT(NaN, n) of mInf: result = newFloatNodeT(Inf, n) of mNegInf: result = newFloatNodeT(NegInf, n) of mIntDefine: if isDefined(s.name): result = newIntNodeT(lookupSymbol(s.name).parseInt, n) of mStrDefine: if isDefined(s.name): result = newStrNodeT(lookupSymbol(s.name), n) else: if sfFakeConst notin s.flags: result = copyTree(s.ast) of {skProc, skMethod}: result = n of skType: result = newSymNodeTypeDesc(s, n.info) of skGenericParam: if s.typ.kind == tyStatic: if s.typ.n != nil: result = s.typ.n result.typ = s.typ.sons[0] else: result = newSymNodeTypeDesc(s, n.info) else: discard of nkCharLit..nkNilLit: result = copyNode(n) of nkIfExpr: result = getConstIfExpr(m, n) of nkCallKinds: if n.sons[0].kind != nkSym: return var s = n.sons[0].sym if s.kind != skProc: return try: case s.magic of mNone: # If it has no sideEffect, it should be evaluated. But not here. return of mSizeOf: var a = n.sons[1] if computeSize(a.typ) < 0: localError(a.info, errCannotEvalXBecauseIncompletelyDefined, "sizeof") result = nil elif skipTypes(a.typ, typedescInst).kind in IntegralTypes+NilableTypes+{tySet}: #{tyArray,tyObject,tyTuple}: result = newIntNodeT(getSize(a.typ), n) else: result = nil # XXX: size computation for complex types is still wrong of mLow: result = newIntNodeT(firstOrd(n.sons[1].typ), n) of mHigh: if skipTypes(n.sons[1].typ, abstractVar).kind notin {tySequence, tyString, tyCString, tyOpenArray, tyVarargs}: result = newIntNodeT(lastOrd(skipTypes(n[1].typ, abstractVar)), n) else: var a = getArrayConstr(m, n.sons[1]) if a.kind == nkBracket: # we can optimize it away: result = newIntNodeT(sonsLen(a)-1, n) of mLengthOpenArray: var a = getArrayConstr(m, n.sons[1]) if a.kind == nkBracket: # we can optimize it away! This fixes the bug ``len(134)``. result = newIntNodeT(sonsLen(a), n) else: result = magicCall(m, n) of mLengthArray: # It doesn't matter if the argument is const or not for mLengthArray. # This fixes bug #544. result = newIntNodeT(lengthOrd(n.sons[1].typ), n) of mAstToStr: result = newStrNodeT(renderTree(n[1], {renderNoComments}), n) of mConStrStr: result = foldConStrStr(m, n) of mIs: let a = getConstExpr(m, n[1]) if a != nil and a.kind == nkSym and a.sym.kind == skType: result = evalIs(n, a) else: result = magicCall(m, n) except OverflowError: localError(n.info, errOverOrUnderflow) except DivByZeroError: localError(n.info, errConstantDivisionByZero) of nkAddr: var a = getConstExpr(m, n.sons[0]) if a != nil: result = n n.sons[0] = a of nkBracket: result = copyTree(n) for i in countup(0, sonsLen(n) - 1): var a = getConstExpr(m, n.sons[i]) if a == nil: return nil result.sons[i] = a incl(result.flags, nfAllConst) of nkRange: var a = getConstExpr(m, n.sons[0]) if a == nil: return var b = getConstExpr(m, n.sons[1]) if b == nil: return result = copyNode(n) addSon(result, a) addSon(result, b) of nkCurly: result = copyTree(n) for i in countup(0, sonsLen(n) - 1): var a = getConstExpr(m, n.sons[i]) if a == nil: return nil result.sons[i] = a incl(result.flags, nfAllConst) of nkObjConstr: result = copyTree(n) for i in countup(1, sonsLen(n) - 1): var a = getConstExpr(m, n.sons[i].sons[1]) if a == nil: return nil result.sons[i].sons[1] = a incl(result.flags, nfAllConst) of nkPar: # tuple constructor result = copyTree(n) if (sonsLen(n) > 0) and (n.sons[0].kind == nkExprColonExpr): for i in countup(0, sonsLen(n) - 1): var a = getConstExpr(m, n.sons[i].sons[1]) if a == nil: return nil result.sons[i].sons[1] = a else: for i in countup(0, sonsLen(n) - 1): var a = getConstExpr(m, n.sons[i]) if a == nil: return nil result.sons[i] = a incl(result.flags, nfAllConst) of nkChckRangeF, nkChckRange64, nkChckRange: var a = getConstExpr(m, n.sons[0]) if a == nil: return if leValueConv(n.sons[1], a) and leValueConv(a, n.sons[2]): result = a # a <= x and x <= b result.typ = n.typ else: localError(n.info, errGenerated, `%`( msgKindToString(errIllegalConvFromXtoY), [typeToString(n.sons[0].typ), typeToString(n.typ)])) of nkStringToCString, nkCStringToString: var a = getConstExpr(m, n.sons[0]) if a == nil: return result = a result.typ = n.typ of nkHiddenStdConv, nkHiddenSubConv, nkConv: var a = getConstExpr(m, n.sons[1]) if a == nil: return result = foldConv(n, a, check=n.kind == nkHiddenStdConv) of nkCast: var a = getConstExpr(m, n.sons[1]) if a == nil: return if n.typ.kind in NilableTypes: # we allow compile-time 'cast' for pointer types: result = a result.typ = n.typ of nkBracketExpr: result = foldArrayAccess(m, n) of nkDotExpr: result = foldFieldAccess(m, n) else: discard