# # # Nim's Runtime Library # (c) Copyright 2017 Nim Authors # # See the file "copying.txt", included in this # distribution, for details about the copyright. # ## This module implements a series of low level methods for bit manipulation. ## By default, this module use compiler intrinsics to improve performance ## on supported compilers: ``GCC``, ``LLVM_GCC``, ``CLANG``, ``VCC``, ``ICC``. ## ## The module will fallback to pure nim procs incase the backend is not supported. ## You can also use the flag `noIntrinsicsBitOpts` to disable compiler intrinsics. ## ## This module is also compatible with other backends: ``Javascript``, ``Nimscript`` ## as well as the ``compiletime VM``. ## ## As a result of using optimized function/intrinsics some functions can return ## undefined results if the input is invalid. You can use the flag `noUndefinedBitOpts` ## to force predictable behaviour for all input, causing a small performance hit. ## ## At this time only `fastLog2`, `firstSetBit, `countLeadingZeroBits`, `countTrailingZeroBits` ## may return undefined and/or platform dependant value if given invalid input. const useBuiltins = not defined(noIntrinsicsBitOpts) const noUndefined = defined(noUndefinedBitOpts) const useGCC_builtins = (defined(gcc) or defined(llvm_gcc) or defined(clang)) and useBuiltins const useICC_builtins = defined(icc) and useBuiltins const useVCC_builtins = defined(vcc) and useBuiltins const arch64 = sizeof(int) == 8 # #### Pure Nim version #### proc firstSetBit_nim(x: uint32): int {.inline, nosideeffect.} = ## Returns the 1-based index of the least significant set bit of x, or if x is zero, returns zero. # https://graphics.stanford.edu/%7Eseander/bithacks.html#ZerosOnRightMultLookup const lookup: array[32, uint8] = [0'u8, 1, 28, 2, 29, 14, 24, 3, 30, 22, 20, 15, 25, 17, 4, 8, 31, 27, 13, 23, 21, 19, 16, 7, 26, 12, 18, 6, 11, 5, 10, 9] var v = x.uint32 var k = not v + 1 # get two's complement # cast[uint32](-cast[int32](v)) result = 1 + lookup[uint32((v and k) * 0x077CB531'u32) shr 27].int proc firstSetBit_nim(x: uint64): int {.inline, nosideeffect.} = ## Returns the 1-based index of the least significant set bit of x, or if x is zero, returns zero. # https://graphics.stanford.edu/%7Eseander/bithacks.html#ZerosOnRightMultLookup var v = uint64(x) var k = uint32(v and 0xFFFFFFFF'u32) if k == 0: k = uint32(v shr 32'u32) and 0xFFFFFFFF'u32 result = 32 result += firstSetBit_nim(k) proc fastlog2_nim(x: uint32): int {.inline, nosideeffect.} = ## Quickly find the log base 2 of a 32-bit or less integer. # https://graphics.stanford.edu/%7Eseander/bithacks.html#IntegerLogDeBruijn # https://stackoverflow.com/questions/11376288/fast-computing-of-log2-for-64-bit-integers const lookup: array[32, uint8] = [0'u8, 9, 1, 10, 13, 21, 2, 29, 11, 14, 16, 18, 22, 25, 3, 30, 8, 12, 20, 28, 15, 17, 24, 7, 19, 27, 23, 6, 26, 5, 4, 31] var v = x.uint32 v = v or v shr 1 # first round down to one less than a power of 2 v = v or v shr 2 v = v or v shr 4 v = v or v shr 8 v = v or v shr 16 result = lookup[uint32(v * 0x07C4ACDD'u32) shr 27].int proc fastlog2_nim(x: uint64): int {.inline, nosideeffect.} = ## Quickly find the log base 2 of a 64-bit integer. # https://graphics.stanford.edu/%7Eseander/bithacks.html#IntegerLogDeBruijn # https://stackoverflow.com/questions/11376288/fast-computing-of-log2-for-64-bit-integers const lookup: array[64, uint8] = [0'u8, 58, 1, 59, 47, 53, 2, 60, 39, 48, 27, 54, 33, 42, 3, 61, 51, 37, 40, 49, 18, 28, 20, 55, 30, 34, 11, 43, 14, 22, 4, 62, 57, 46, 52, 38, 26, 32, 41, 50, 36, 17, 19, 29, 10, 13, 21, 56, 45, 25, 31, 35, 16, 9, 12, 44, 24, 15, 8, 23, 7, 6, 5, 63] var v = x.uint64 v = v or v shr 1 # first round down to on
# from issue #7632
# imported and used in tstrformat

import strformat

proc fails*(a: static[int]): string =
  &"formatted {a:2}"

proc fails2*[N: static[int]](a: int): string =
  &"formatted {a:2}"

proc works*(a: int): string =
  &"formatted {a:2}"

proc fails0*(a: int or uint): string =
  &"formatted {a:2}"
if x == 0: return 0 when sizeof(x) <= 4: result = firstSetBit_nim(x.uint32) else: result = firstSetBit_nim(x.uint64) else: when noUndefined and not useGCC_builtins: if x == 0: return 0 when useGCC_builtins: when sizeof(x) <= 4: result = builtin_ffs(cast[cint](x.cuint)).int else: result = builtin_ffsll(cast[clonglong](x.culonglong)).int elif useVCC_builtins: when sizeof(x) <= 4: result = 1 + vcc_scan_impl(bitScanForward, x.culong) elif arch64: result = 1 + vcc_scan_impl(bitScanForward64, x.uint64) else: result = firstSetBit_nim(x.uint64) elif useICC_builtins: when sizeof(x) <= 4: result = 1 + icc_scan_impl(bitScanForward, x.uint32) elif arch64: result = 1 + icc_scan_impl(bitScanForward64, x.uint64) else: result = firstSetBit_nim(x.uint64) else: when sizeof(x) <= 4: result = firstSetBit_nim(x.uint32) else: result = firstSetBit_nim(x.uint64) proc fastLog2*(x: SomeInteger): int {.inline, nosideeffect.} = ## Quickly find the log base 2 of an integer. ## If `x` is zero, when ``noUndefinedBitOpts`` is set, result is -1, ## otherwise result is undefined. when noUndefined: if x == 0: return -1 when nimvm: when sizeof(x) <= 4: result = fastlog2_nim(x.uint32) else: result = fastlog2_nim(x.uint64) else: when useGCC_builtins: when sizeof(x) <= 4: result = 31 - builtin_clz(x.uint32).int else: result = 63 - builtin_clzll(x.uint64).int elif useVCC_builtins: when sizeof(x) <= 4: result = vcc_scan_impl(bitScanReverse, x.culong) elif arch64: result = vcc_scan_impl(bitScanReverse64, x.uint64) else: result = fastlog2_nim(x.uint64) elif useICC_builtins: when sizeof(x) <= 4: result = icc_scan_impl(bitScanReverse, x.uint32) elif arch64: result = icc_scan_impl(bitScanReverse64, x.uint64) else: result = fastlog2_nim(x.uint64) else: when sizeof(x) <= 4: result = fastlog2_nim(x.uint32) else: result = fastlog2_nim(x.uint64) proc countLeadingZeroBits*(x: SomeInteger): int {.inline, nosideeffect.} = ## Returns the number of leading zero bits in integer. ## If `x` is zero, when ``noUndefinedBitOpts`` is set, result is 0, ## otherwise result is undefined. when noUndefined: if x == 0: return 0 when nimvm: when sizeof(x) <= 4: result = sizeof(x)*8 - 1 - fastlog2_nim(x.uint32) else: result = sizeof(x)*8 - 1 - fastlog2_nim(x.uint64) else: when useGCC_builtins: when sizeof(x) <= 4: result = builtin_clz(x.uint32).int - (32 - sizeof(x)*8) else: result = builtin_clzll(x.uint64).int else: when sizeof(x) <= 4: result = sizeof(x)*8 - 1 - fastlog2_nim(x.uint32) else: result = sizeof(x)*8 - 1 - fastlog2_nim(x.uint64) proc countTrailingZeroBits*(x: SomeInteger): int {.inline, nosideeffect.} = ## Returns the number of trailing zeros in integer. ## If `x` is zero, when ``noUndefinedBitOpts`` is set, result is 0, ## otherwise result is undefined. when noUndefined: if x == 0: return 0 when nimvm: result = firstSetBit(x) - 1 else: when useGCC_builtins: when sizeof(x) <= 4: result = builtin_ctz(x.uint32).int else: result = builtin_ctzll(x.uint64).int else: result = firstSetBit(x) - 1 proc rotateLeftBits*(value: uint8; amount: range[0..8]): uint8 {.inline, noSideEffect.} = ## Left-rotate bits in a 8-bits value. # using this form instead of the one below should handle any value # out of range as well as negative values. # result = (value shl amount) or (value shr (8 - amount)) # taken from: https://en.wikipedia.org/wiki/Circular_shift#Implementing_circular_shifts let amount = amount and 7 result = (value shl amount) or (value shr ( (-amount) and 7)) proc rotateLeftBits*(value: uint16; amount: range[0..16]): uint16 {.inline, noSideEffect.} = ## Left-rotate bits in a 16-bits value. let amount = amount and 15 result = (value shl amount) or (value shr ( (-amount) and 15)) proc rotateLeftBits*(value: uint32; amount: range[0..32]): uint32 {.inline, noSideEffect.} = ## Left-rotate bits in a 32-bits value. let amount = amount and 31 result = (value shl amount) or (value shr ( (-amount) and 31)) proc rotateLeftBits*(value: uint64; amount: range[0..64]): uint64 {.inline, noSideEffect.} = ## Left-rotate bits in a 64-bits value. let amount = amount and 63 result = (value shl amount) or (value shr ( (-amount) and 63)) proc rotateRightBits*(value: uint8; amount: range[0..8]): uint8 {.inline, noSideEffect.} = ## Right-rotate bits in a 8-bits value. let amount = amount and 7 result = (value shr amount) or (value shl ( (-amount) and 7)) proc rotateRightBits*(value: uint16; amount: range[0..16]): uint16 {.inline, noSideEffect.} = ## Right-rotate bits in a 16-bits value. let amount = amount and 15 result = (value shr amount) or (value shl ( (-amount) and 15)) proc rotateRightBits*(value: uint32; amount: range[0..32]): uint32 {.inline, noSideEffect.} = ## Right-rotate bits in a 32-bits value. let amount = amount and 31 result = (value shr amount) or (value shl ( (-amount) and 31)) proc rotateRightBits*(value: uint64; amount: range[0..64]): uint64 {.inline, noSideEffect.} = ## Right-rotate bits in a 64-bits value. let amount = amount and 63 result = (value shr amount) or (value shl ( (-amount) and 63))