106093806Santirez /* hyperloglog.c - Redis HyperLogLog probabilistic cardinality approximation.
206093806Santirez * This file implements the algorithm and the exported Redis commands.
306093806Santirez *
406093806Santirez * Copyright (c) 2014, Salvatore Sanfilippo <antirez at gmail dot com>
506093806Santirez * All rights reserved.
606093806Santirez *
706093806Santirez * Redistribution and use in source and binary forms, with or without
806093806Santirez * modification, are permitted provided that the following conditions are met:
906093806Santirez *
1006093806Santirez * * Redistributions of source code must retain the above copyright notice,
1106093806Santirez * this list of conditions and the following disclaimer.
1206093806Santirez * * Redistributions in binary form must reproduce the above copyright
1306093806Santirez * notice, this list of conditions and the following disclaimer in the
1406093806Santirez * documentation and/or other materials provided with the distribution.
1506093806Santirez * * Neither the name of Redis nor the names of its contributors may be used
1606093806Santirez * to endorse or promote products derived from this software without
1706093806Santirez * specific prior written permission.
1806093806Santirez *
1906093806Santirez * THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS"
2006093806Santirez * AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
2106093806Santirez * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
2206093806Santirez * ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE
2306093806Santirez * LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
2406093806Santirez * CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
2506093806Santirez * SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
2606093806Santirez * INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
2706093806Santirez * CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
2806093806Santirez * ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
2906093806Santirez * POSSIBILITY OF SUCH DAMAGE.
3006093806Santirez */
3106093806Santirez
32cef054e8Santirez #include "server.h"
334ab162a5Santirez
34156929eeSantirez #include <stdint.h>
35ded86076Santirez #include <math.h>
3606093806Santirez
3706093806Santirez /* The Redis HyperLogLog implementation is based on the following ideas:
3806093806Santirez *
3906093806Santirez * * The use of a 64 bit hash function as proposed in [1], in order to don't
4006093806Santirez * limited to cardinalities up to 10^9, at the cost of just 1 additional
4106093806Santirez * bit per register.
4206093806Santirez * * The use of 16384 6-bit registers for a great level of accuracy, using
4306093806Santirez * a total of 12k per key.
4406093806Santirez * * The use of the Redis string data type. No new type is introduced.
4506093806Santirez * * No attempt is made to compress the data structure as in [1]. Also the
4606093806Santirez * algorithm used is the original HyperLogLog Algorithm as in [2], with
4706093806Santirez * the only difference that a 64 bit hash function is used, so no correction
4806093806Santirez * is performed for values near 2^32 as in [1].
4906093806Santirez *
5006093806Santirez * [1] Heule, Nunkesser, Hall: HyperLogLog in Practice: Algorithmic
5106093806Santirez * Engineering of a State of The Art Cardinality Estimation Algorithm.
5206093806Santirez *
5306093806Santirez * [2] P. Flajolet, Éric Fusy, O. Gandouet, and F. Meunier. Hyperloglog: The
5406093806Santirez * analysis of a near-optimal cardinality estimation algorithm.
55307a1899Santirez *
56da2fbcf9Santirez * Redis uses two representations:
57da2fbcf9Santirez *
58da2fbcf9Santirez * 1) A "dense" representation where every entry is represented by
59da2fbcf9Santirez * a 6-bit integer.
60da2fbcf9Santirez * 2) A "sparse" representation using run length compression suitable
61da2fbcf9Santirez * for representing HyperLogLogs with many registers set to 0 in
62da2fbcf9Santirez * a memory efficient way.
63da2fbcf9Santirez *
64d55474e5Santirez *
65d55474e5Santirez * HLL header
66d55474e5Santirez * ===
67d55474e5Santirez *
68d55474e5Santirez * Both the dense and sparse representation have a 16 byte header as follows:
69d55474e5Santirez *
70d55474e5Santirez * +------+---+-----+----------+
71d55474e5Santirez * | HYLL | E | N/U | Cardin. |
72d55474e5Santirez * +------+---+-----+----------+
73d55474e5Santirez *
74d55474e5Santirez * The first 4 bytes are a magic string set to the bytes "HYLL".
75d55474e5Santirez * "E" is one byte encoding, currently set to HLL_DENSE or
76d55474e5Santirez * HLL_SPARSE. N/U are three not used bytes.
77d55474e5Santirez *
78d55474e5Santirez * The "Cardin." field is a 64 bit integer stored in little endian format
79d55474e5Santirez * with the latest cardinality computed that can be reused if the data
80d55474e5Santirez * structure was not modified since the last computation (this is useful
81d55474e5Santirez * because there are high probabilities that HLLADD operations don't
82d55474e5Santirez * modify the actual data structure and hence the approximated cardinality).
83d55474e5Santirez *
84d55474e5Santirez * When the most significant bit in the most significant byte of the cached
85d55474e5Santirez * cardinality is set, it means that the data structure was modified and
86d55474e5Santirez * we can't reuse the cached value that must be recomputed.
87d55474e5Santirez *
88da2fbcf9Santirez * Dense representation
89da2fbcf9Santirez * ===
90da2fbcf9Santirez *
91da2fbcf9Santirez * The dense representation used by Redis is the following:
92307a1899Santirez *
93d55474e5Santirez * +--------+--------+--------+------// //--+
94d55474e5Santirez * |11000000|22221111|33333322|55444444 .... |
95d55474e5Santirez * +--------+--------+--------+------// //--+
96307a1899Santirez *
97307a1899Santirez * The 6 bits counters are encoded one after the other starting from the
98307a1899Santirez * LSB to the MSB, and using the next bytes as needed.
99307a1899Santirez *
100da2fbcf9Santirez * Sparse representation
101da2fbcf9Santirez * ===
102da2fbcf9Santirez *
1039c037ba8Santirez * The sparse representation encodes registers using a run length
1049c037ba8Santirez * encoding composed of three opcodes, two using one byte, and one using
105da2fbcf9Santirez * of two bytes. The opcodes are called ZERO, XZERO and VAL.
106da2fbcf9Santirez *
107da2fbcf9Santirez * ZERO opcode is represented as 00xxxxxx. The 6-bit integer represented
108da2fbcf9Santirez * by the six bits 'xxxxxx', plus 1, means that there are N registers set
109da2fbcf9Santirez * to 0. This opcode can represent from 1 to 64 contiguous registers set
110da2fbcf9Santirez * to the value of 0.
111da2fbcf9Santirez *
112da2fbcf9Santirez * XZERO opcode is represented by two bytes 01xxxxxx yyyyyyyy. The 14-bit
113da2fbcf9Santirez * integer represented by the bits 'xxxxxx' as most significant bits and
114da2fbcf9Santirez * 'yyyyyyyy' as least significant bits, plus 1, means that there are N
115c756936bSantirez * registers set to 0. This opcode can represent from 0 to 16384 contiguous
116da2fbcf9Santirez * registers set to the value of 0.
117da2fbcf9Santirez *
1189c037ba8Santirez * VAL opcode is represented as 1vvvvvxx. It contains a 5-bit integer
1199c037ba8Santirez * representing the value of a register, and a 2-bit integer representing
1209c037ba8Santirez * the number of contiguous registers set to that value 'vvvvv'.
1219c037ba8Santirez * To obtain the value and run length, the integers vvvvv and xx must be
1229c037ba8Santirez * incremented by one. This opcode can represent values from 1 to 32,
1239c037ba8Santirez * repeated from 1 to 4 times.
124da2fbcf9Santirez *
125da2fbcf9Santirez * The sparse representation can't represent registers with a value greater
1269c037ba8Santirez * than 32, however it is very unlikely that we find such a register in an
127da2fbcf9Santirez * HLL with a cardinality where the sparse representation is still more
128da2fbcf9Santirez * memory efficient than the dense representation. When this happens the
129da2fbcf9Santirez * HLL is converted to the dense representation.
130da2fbcf9Santirez *
131da2fbcf9Santirez * The sparse representation is purely positional. For example a sparse
132da2fbcf9Santirez * representation of an empty HLL is just: XZERO:16384.
133da2fbcf9Santirez *
134da2fbcf9Santirez * An HLL having only 3 non-zero registers at position 1000, 1020, 1021
135da2fbcf9Santirez * respectively set to 2, 3, 3, is represented by the following three
136da2fbcf9Santirez * opcodes:
137da2fbcf9Santirez *
138da2fbcf9Santirez * XZERO:1000 (Registers 0-999 are set to 0)
139da2fbcf9Santirez * VAL:2,1 (1 register set to value 2, that is register 1000)
140da2fbcf9Santirez * ZERO:19 (Registers 1001-1019 set to 0)
141da2fbcf9Santirez * VAL:3,2 (2 registers set to value 3, that is registers 1020,1021)
142da2fbcf9Santirez * XZERO:15362 (Registers 1022-16383 set to 0)
143da2fbcf9Santirez *
144da2fbcf9Santirez * In the example the sparse representation used just 7 bytes instead
145da2fbcf9Santirez * of 12k in order to represent the HLL registers. In general for low
146da2fbcf9Santirez * cardinality there is a big win in terms of space efficiency, traded
147da2fbcf9Santirez * with CPU time since the sparse representation is slower to access:
148da2fbcf9Santirez *
1499c037ba8Santirez * The following table shows average cardinality vs bytes used, 100
1509c037ba8Santirez * samples per cardinality (when the set was not representable because
1519c037ba8Santirez * of registers with too big value, the dense representation size was used
1529c037ba8Santirez * as a sample).
153da2fbcf9Santirez *
1549c037ba8Santirez * 100 267
1559c037ba8Santirez * 200 485
1569c037ba8Santirez * 300 678
1579c037ba8Santirez * 400 859
1589c037ba8Santirez * 500 1033
1599c037ba8Santirez * 600 1205
1609c037ba8Santirez * 700 1375
1619c037ba8Santirez * 800 1544
1629c037ba8Santirez * 900 1713
1639c037ba8Santirez * 1000 1882
1649c037ba8Santirez * 2000 3480
1659c037ba8Santirez * 3000 4879
1669c037ba8Santirez * 4000 6089
1679c037ba8Santirez * 5000 7138
1689c037ba8Santirez * 6000 8042
1699c037ba8Santirez * 7000 8823
1709c037ba8Santirez * 8000 9500
1719c037ba8Santirez * 9000 10088
1729c037ba8Santirez * 10000 10591
173da2fbcf9Santirez *
1749c037ba8Santirez * The dense representation uses 12288 bytes, so there is a big win up to
1759c037ba8Santirez * a cardinality of ~2000-3000. For bigger cardinalities the constant times
1769c037ba8Santirez * involved in updating the sparse representation is not justified by the
1779c037ba8Santirez * memory savings. The exact maximum length of the sparse representation
1789c037ba8Santirez * when this implementation switches to the dense representation is
179402110f9Santirez * configured via the define server.hll_sparse_max_bytes.
180da2fbcf9Santirez */
18106093806Santirez
182d55474e5Santirez struct hllhdr {
183d55474e5Santirez char magic[4]; /* "HYLL" */
184d55474e5Santirez uint8_t encoding; /* HLL_DENSE or HLL_SPARSE. */
185d55474e5Santirez uint8_t notused[3]; /* Reserved for future use, must be zero. */
186d55474e5Santirez uint8_t card[8]; /* Cached cardinality, little endian. */
187d55474e5Santirez uint8_t registers[]; /* Data bytes. */
188d55474e5Santirez };
189d55474e5Santirez
190d55474e5Santirez /* The cached cardinality MSB is used to signal validity of the cached value. */
191ba52cd06SMike Trinkala #define HLL_INVALIDATE_CACHE(hdr) (hdr)->card[7] |= (1<<7)
192ba52cd06SMike Trinkala #define HLL_VALID_CACHE(hdr) (((hdr)->card[7] & (1<<7)) == 0)
193d55474e5Santirez
194d55474e5Santirez #define HLL_P 14 /* The greater is P, the smaller the error. */
195d55474e5Santirez #define HLL_REGISTERS (1<<HLL_P) /* With P=14, 16384 registers. */
196d55474e5Santirez #define HLL_P_MASK (HLL_REGISTERS-1) /* Mask to index register. */
197d55474e5Santirez #define HLL_BITS 6 /* Enough to count up to 63 leading zeroes. */
198d55474e5Santirez #define HLL_REGISTER_MAX ((1<<HLL_BITS)-1)
199d55474e5Santirez #define HLL_HDR_SIZE sizeof(struct hllhdr)
200d55474e5Santirez #define HLL_DENSE_SIZE (HLL_HDR_SIZE+((HLL_REGISTERS*HLL_BITS+7)/8))
2010feb2aabSantirez #define HLL_DENSE 0 /* Dense encoding. */
2020feb2aabSantirez #define HLL_SPARSE 1 /* Sparse encoding. */
2030feb2aabSantirez #define HLL_RAW 255 /* Only used internally, never exposed. */
204d55474e5Santirez #define HLL_MAX_ENCODING 1
20506093806Santirez
2068e8f8189Santirez static char *invalid_hll_err = "-INVALIDOBJ Corrupted HLL object detected\r\n";
207848d0461Santirez
20806093806Santirez /* =========================== Low level bit macros ========================= */
20906093806Santirez
210da2fbcf9Santirez /* Macros to access the dense representation.
211da2fbcf9Santirez *
212da2fbcf9Santirez * We need to get and set 6 bit counters in an array of 8 bit bytes.
21306093806Santirez * We use macros to make sure the code is inlined since speed is critical
21406093806Santirez * especially in order to compute the approximated cardinality in
21506093806Santirez * HLLCOUNT where we need to access all the registers at once.
216e73839e7Santirez * For the same reason we also want to avoid conditionals in this code path.
21706093806Santirez *
21806093806Santirez * +--------+--------+--------+------//
2194628ac00Santirez * |11000000|22221111|33333322|55444444
22006093806Santirez * +--------+--------+--------+------//
22106093806Santirez *
2224628ac00Santirez * Note: in the above representation the most significant bit (MSB)
2234628ac00Santirez * of every byte is on the left. We start using bits from the LSB to MSB,
2244628ac00Santirez * and so forth passing to the next byte.
22506093806Santirez *
2264628ac00Santirez * Example, we want to access to counter at pos = 1 ("111111" in the
2274628ac00Santirez * illustration above).
2284628ac00Santirez *
2294628ac00Santirez * The index of the first byte b0 containing our data is:
2304628ac00Santirez *
2314628ac00Santirez * b0 = 6 * pos / 8 = 0
23206093806Santirez *
23306093806Santirez * +--------+
2344628ac00Santirez * |11000000| <- Our byte at b0
23506093806Santirez * +--------+
23606093806Santirez *
2374628ac00Santirez * The position of the first bit (counting from the LSB = 0) in the byte
2384628ac00Santirez * is given by:
2394628ac00Santirez *
2404628ac00Santirez * fb = 6 * pos % 8 -> 6
2414628ac00Santirez *
2424628ac00Santirez * Right shift b0 of 'fb' bits.
24306093806Santirez *
24406093806Santirez * +--------+
2454628ac00Santirez * |11000000| <- Initial value of b0
2464628ac00Santirez * |00000011| <- After right shift of 6 pos.
24706093806Santirez * +--------+
24806093806Santirez *
2494628ac00Santirez * Left shift b1 of bits 8-fb bits (2 bits)
25006093806Santirez *
25106093806Santirez * +--------+
2524628ac00Santirez * |22221111| <- Initial value of b1
2534628ac00Santirez * |22111100| <- After left shift of 2 bits.
25406093806Santirez * +--------+
25506093806Santirez *
2564628ac00Santirez * OR the two bits, and finally AND with 111111 (63 in decimal) to
2574628ac00Santirez * clean the higher order bits we are not interested in:
2584628ac00Santirez *
2594628ac00Santirez * +--------+
2604628ac00Santirez * |00000011| <- b0 right shifted
2614628ac00Santirez * |22111100| <- b1 left shifted
2624628ac00Santirez * |22111111| <- b0 OR b1
2634628ac00Santirez * | 111111| <- (b0 OR b1) AND 63, our value.
2644628ac00Santirez * +--------+
2654628ac00Santirez *
2664628ac00Santirez * We can try with a different example, like pos = 0. In this case
2674628ac00Santirez * the 6-bit counter is actually contained in a single byte.
2684628ac00Santirez *
2694628ac00Santirez * b0 = 6 * pos / 8 = 0
2704628ac00Santirez *
2714628ac00Santirez * +--------+
2724628ac00Santirez * |11000000| <- Our byte at b0
2734628ac00Santirez * +--------+
2744628ac00Santirez *
2754628ac00Santirez * fb = 6 * pos % 8 = 0
2764628ac00Santirez *
2774628ac00Santirez * So we right shift of 0 bits (no shift in practice) and
2784628ac00Santirez * left shift the next byte of 8 bits, even if we don't use it,
2794628ac00Santirez * but this has the effect of clearing the bits so the result
2804628ac00Santirez * will not be affacted after the OR.
28106093806Santirez *
28206093806Santirez * -------------------------------------------------------------------------
28306093806Santirez *
28406093806Santirez * Setting the register is a bit more complex, let's assume that 'val'
28506093806Santirez * is the value we want to set, already in the right range.
28606093806Santirez *
28706093806Santirez * We need two steps, in one we need to clear the bits, and in the other
28806093806Santirez * we need to bitwise-OR the new bits.
28906093806Santirez *
2904628ac00Santirez * Let's try with 'pos' = 1, so our first byte at 'b' is 0,
291e73839e7Santirez *
2924628ac00Santirez * "fb" is 6 in this case.
29306093806Santirez *
29406093806Santirez * +--------+
2954628ac00Santirez * |11000000| <- Our byte at b0
29606093806Santirez * +--------+
29706093806Santirez *
298e73839e7Santirez * To create a AND-mask to clear the bits about this position, we just
2994628ac00Santirez * initialize the mask with the value 63, left shift it of "fs" bits,
3004628ac00Santirez * and finally invert the result.
30106093806Santirez *
30206093806Santirez * +--------+
3034628ac00Santirez * |00111111| <- "mask" starts at 63
3044628ac00Santirez * |11000000| <- "mask" after left shift of "ls" bits.
3054628ac00Santirez * |00111111| <- "mask" after invert.
30606093806Santirez * +--------+
30706093806Santirez *
30806093806Santirez * Now we can bitwise-AND the byte at "b" with the mask, and bitwise-OR
3094628ac00Santirez * it with "val" left-shifted of "ls" bits to set the new bits.
31006093806Santirez *
3114628ac00Santirez * Now let's focus on the next byte b1:
31206093806Santirez *
31306093806Santirez * +--------+
3144628ac00Santirez * |22221111| <- Initial value of b1
31506093806Santirez * +--------+
31606093806Santirez *
3174628ac00Santirez * To build the AND mask we start again with the 63 value, right shift
3184628ac00Santirez * it by 8-fb bits, and invert it.
31906093806Santirez *
32006093806Santirez * +--------+
3214628ac00Santirez * |00111111| <- "mask" set at 2&6-1
3224628ac00Santirez * |00001111| <- "mask" after the right shift by 8-fb = 2 bits
3234628ac00Santirez * |11110000| <- "mask" after bitwise not.
32406093806Santirez * +--------+
32506093806Santirez *
32606093806Santirez * Now we can mask it with b+1 to clear the old bits, and bitwise-OR
32706093806Santirez * with "val" left-shifted by "rs" bits to set the new value.
32806093806Santirez */
32906093806Santirez
33006093806Santirez /* Note: if we access the last counter, we will also access the b+1 byte
33106093806Santirez * that is out of the array, but sds strings always have an implicit null
33206093806Santirez * term, so the byte exists, and we can skip the conditional (or the need
33306093806Santirez * to allocate 1 byte more explicitly). */
33406093806Santirez
33506093806Santirez /* Store the value of the register at position 'regnum' into variable 'target'.
33606093806Santirez * 'p' is an array of unsigned bytes. */
3371efc1e05Santirez #define HLL_DENSE_GET_REGISTER(target,p,regnum) do { \
3381c88c594Santirez uint8_t *_p = (uint8_t*) p; \
339d55474e5Santirez unsigned long _byte = regnum*HLL_BITS/8; \
340d55474e5Santirez unsigned long _fb = regnum*HLL_BITS&7; \
3414628ac00Santirez unsigned long _fb8 = 8 - _fb; \
3424628ac00Santirez unsigned long b0 = _p[_byte]; \
3434628ac00Santirez unsigned long b1 = _p[_byte+1]; \
344d55474e5Santirez target = ((b0 >> _fb) | (b1 << _fb8)) & HLL_REGISTER_MAX; \
34506093806Santirez } while(0)
34606093806Santirez
34706093806Santirez /* Set the value of the register at position 'regnum' to 'val'.
34806093806Santirez * 'p' is an array of unsigned bytes. */
3491efc1e05Santirez #define HLL_DENSE_SET_REGISTER(p,regnum,val) do { \
3501c88c594Santirez uint8_t *_p = (uint8_t*) p; \
351d55474e5Santirez unsigned long _byte = regnum*HLL_BITS/8; \
352d55474e5Santirez unsigned long _fb = regnum*HLL_BITS&7; \
3534628ac00Santirez unsigned long _fb8 = 8 - _fb; \
3544628ac00Santirez unsigned long _v = val; \
355d55474e5Santirez _p[_byte] &= ~(HLL_REGISTER_MAX << _fb); \
3564628ac00Santirez _p[_byte] |= _v << _fb; \
357d55474e5Santirez _p[_byte+1] &= ~(HLL_REGISTER_MAX >> _fb8); \
3584628ac00Santirez _p[_byte+1] |= _v >> _fb8; \
35906093806Santirez } while(0)
36006093806Santirez
361da2fbcf9Santirez /* Macros to access the sparse representation.
362da2fbcf9Santirez * The macros parameter is expected to be an uint8_t pointer. */
363c756936bSantirez #define HLL_SPARSE_XZERO_BIT 0x40 /* 01xxxxxx */
364c756936bSantirez #define HLL_SPARSE_VAL_BIT 0x80 /* 1vvvvvxx */
365837ca390Santirez #define HLL_SPARSE_IS_ZERO(p) (((*(p)) & 0xc0) == 0) /* 00xxxxxx */
366837ca390Santirez #define HLL_SPARSE_IS_XZERO(p) (((*(p)) & 0xc0) == HLL_SPARSE_XZERO_BIT)
367837ca390Santirez #define HLL_SPARSE_IS_VAL(p) ((*(p)) & HLL_SPARSE_VAL_BIT)
368837ca390Santirez #define HLL_SPARSE_ZERO_LEN(p) (((*(p)) & 0x3f)+1)
369837ca390Santirez #define HLL_SPARSE_XZERO_LEN(p) (((((*(p)) & 0x3f) << 8) | (*((p)+1)))+1)
370837ca390Santirez #define HLL_SPARSE_VAL_VALUE(p) ((((*(p)) >> 2) & 0x1f)+1)
371837ca390Santirez #define HLL_SPARSE_VAL_LEN(p) (((*(p)) & 0x3)+1)
372c756936bSantirez #define HLL_SPARSE_VAL_MAX_VALUE 32
373c756936bSantirez #define HLL_SPARSE_VAL_MAX_LEN 4
374c756936bSantirez #define HLL_SPARSE_ZERO_MAX_LEN 64
375c756936bSantirez #define HLL_SPARSE_XZERO_MAX_LEN 16384
376c756936bSantirez #define HLL_SPARSE_VAL_SET(p,val,len) do { \
377c756936bSantirez *(p) = (((val)-1)<<2|((len)-1))|HLL_SPARSE_VAL_BIT; \
378c756936bSantirez } while(0)
379c756936bSantirez #define HLL_SPARSE_ZERO_SET(p,len) do { \
380c756936bSantirez *(p) = (len)-1; \
381c756936bSantirez } while(0)
382c756936bSantirez #define HLL_SPARSE_XZERO_SET(p,len) do { \
383c756936bSantirez int _l = (len)-1; \
384c756936bSantirez *(p) = (_l>>8) | HLL_SPARSE_XZERO_BIT; \
385837ca390Santirez *((p)+1) = (_l&0xff); \
386c756936bSantirez } while(0)
387da2fbcf9Santirez
38806093806Santirez /* ========================= HyperLogLog algorithm ========================= */
38906093806Santirez
390aaf6db45Santirez /* Our hash function is MurmurHash2, 64 bit version.
391aaf6db45Santirez * It was modified for Redis in order to provide the same result in
392aaf6db45Santirez * big and little endian archs (endian neutral). */
MurmurHash64A(const void * key,int len,unsigned int seed)393156929eeSantirez uint64_t MurmurHash64A (const void * key, int len, unsigned int seed) {
394156929eeSantirez const uint64_t m = 0xc6a4a7935bd1e995;
395156929eeSantirez const int r = 47;
396156929eeSantirez uint64_t h = seed ^ (len * m);
397aaf6db45Santirez const uint8_t *data = (const uint8_t *)key;
398aaf6db45Santirez const uint8_t *end = data + (len-(len&7));
399156929eeSantirez
400156929eeSantirez while(data != end) {
401aaf6db45Santirez uint64_t k;
402aaf6db45Santirez
403aaf6db45Santirez #if (BYTE_ORDER == LITTLE_ENDIAN)
404aaf6db45Santirez k = *((uint64_t*)data);
405aaf6db45Santirez #else
406aaf6db45Santirez k = (uint64_t) data[0];
407aaf6db45Santirez k |= (uint64_t) data[1] << 8;
408aaf6db45Santirez k |= (uint64_t) data[2] << 16;
409aaf6db45Santirez k |= (uint64_t) data[3] << 24;
410aaf6db45Santirez k |= (uint64_t) data[4] << 32;
411aaf6db45Santirez k |= (uint64_t) data[5] << 40;
412aaf6db45Santirez k |= (uint64_t) data[6] << 48;
413aaf6db45Santirez k |= (uint64_t) data[7] << 56;
414aaf6db45Santirez #endif
415aaf6db45Santirez
416156929eeSantirez k *= m;
417156929eeSantirez k ^= k >> r;
418156929eeSantirez k *= m;
419156929eeSantirez h ^= k;
420156929eeSantirez h *= m;
421aaf6db45Santirez data += 8;
422156929eeSantirez }
423156929eeSantirez
424156929eeSantirez switch(len & 7) {
425aaf6db45Santirez case 7: h ^= (uint64_t)data[6] << 48;
426aaf6db45Santirez case 6: h ^= (uint64_t)data[5] << 40;
427aaf6db45Santirez case 5: h ^= (uint64_t)data[4] << 32;
428aaf6db45Santirez case 4: h ^= (uint64_t)data[3] << 24;
429aaf6db45Santirez case 3: h ^= (uint64_t)data[2] << 16;
430aaf6db45Santirez case 2: h ^= (uint64_t)data[1] << 8;
431aaf6db45Santirez case 1: h ^= (uint64_t)data[0];
432156929eeSantirez h *= m;
433156929eeSantirez };
434156929eeSantirez
435156929eeSantirez h ^= h >> r;
436156929eeSantirez h *= m;
437156929eeSantirez h ^= h >> r;
438156929eeSantirez return h;
439156929eeSantirez }
440156929eeSantirez
4411efc1e05Santirez /* Given a string element to add to the HyperLogLog, returns the length
4421efc1e05Santirez * of the pattern 000..1 of the element hash. As a side effect 'regp' is
4431efc1e05Santirez * set to the register index this element hashes to. */
hllPatLen(unsigned char * ele,size_t elesize,long * regp)444e9cd51c7Santirez int hllPatLen(unsigned char *ele, size_t elesize, long *regp) {
4455660ff1cSantirez uint64_t hash, bit, index;
4461efc1e05Santirez int count;
4475660ff1cSantirez
448d55474e5Santirez /* Count the number of zeroes starting from bit HLL_REGISTERS
4495660ff1cSantirez * (that is a power of two corresponding to the first bit we don't use
450f90a4af3Santirez * as index). The max run can be 64-P+1 bits.
451f90a4af3Santirez *
452f90a4af3Santirez * Note that the final "1" ending the sequence of zeroes must be
453f90a4af3Santirez * included in the count, so if we find "001" the count is 3, and
454f90a4af3Santirez * the smallest count possible is no zeroes at all, just a 1 bit
455f90a4af3Santirez * at the first position, that is a count of 1.
4565660ff1cSantirez *
4575660ff1cSantirez * This may sound like inefficient, but actually in the average case
4585660ff1cSantirez * there are high probabilities to find a 1 after a few iterations. */
459433ce7f8Santirez hash = MurmurHash64A(ele,elesize,0xadc83b19ULL);
4601efc1e05Santirez index = hash & HLL_P_MASK; /* Register index. */
461349c9781Santirez hash |= ((uint64_t)1<<63); /* Make sure the loop terminates. */
462d55474e5Santirez bit = HLL_REGISTERS; /* First bit not used to address the register. */
463349c9781Santirez count = 1; /* Initialized to 1 since we count the "00000...1" pattern. */
4645660ff1cSantirez while((hash & bit) == 0) {
4655660ff1cSantirez count++;
4665660ff1cSantirez bit <<= 1;
4675660ff1cSantirez }
4688ea5b46dSantirez *regp = (int) index;
4691efc1e05Santirez return count;
4701efc1e05Santirez }
4711efc1e05Santirez
4728ea5b46dSantirez /* ================== Dense representation implementation ================== */
4738ea5b46dSantirez
4748ea5b46dSantirez /* "Add" the element in the dense hyperloglog data structure.
4751efc1e05Santirez * Actually nothing is added, but the max 0 pattern counter of the subset
4761efc1e05Santirez * the element belongs to is incremented if needed.
4771efc1e05Santirez *
4781efc1e05Santirez * 'registers' is expected to have room for HLL_REGISTERS plus an
4791efc1e05Santirez * additional byte on the right. This requirement is met by sds strings
4801efc1e05Santirez * automatically since they are implicitly null terminated.
4811efc1e05Santirez *
4821efc1e05Santirez * The function always succeed, however if as a result of the operation
4831efc1e05Santirez * the approximated cardinality changed, 1 is returned. Otherwise 0
4841efc1e05Santirez * is returned. */
hllDenseAdd(uint8_t * registers,unsigned char * ele,size_t elesize)4858ea5b46dSantirez int hllDenseAdd(uint8_t *registers, unsigned char *ele, size_t elesize) {
4861efc1e05Santirez uint8_t oldcount, count;
487e9cd51c7Santirez long index;
4885660ff1cSantirez
489156929eeSantirez /* Update the register if this element produced a longer run of zeroes. */
4901efc1e05Santirez count = hllPatLen(ele,elesize,&index);
4911efc1e05Santirez HLL_DENSE_GET_REGISTER(oldcount,registers,index);
4925660ff1cSantirez if (count > oldcount) {
4931efc1e05Santirez HLL_DENSE_SET_REGISTER(registers,index,count);
4945660ff1cSantirez return 1;
4955660ff1cSantirez } else {
4965660ff1cSantirez return 0;
4975660ff1cSantirez }
4985660ff1cSantirez }
4995660ff1cSantirez
5008ea5b46dSantirez /* Compute SUM(2^-reg) in the dense representation.
5018ea5b46dSantirez * PE is an array with a pre-computer table of values 2^-reg indexed by reg.
5028ea5b46dSantirez * As a side effect the integer pointed by 'ezp' is set to the number
5038ea5b46dSantirez * of zero registers. */
hllDenseSum(uint8_t * registers,double * PE,int * ezp)5048ea5b46dSantirez double hllDenseSum(uint8_t *registers, double *PE, int *ezp) {
505ec1ee662Santirez double E = 0;
5068ea5b46dSantirez int j, ez = 0;
507ded86076Santirez
5088ea5b46dSantirez /* Redis default is to use 16384 registers 6 bits each. The code works
5093ed947fbSantirez * with other values by modifying the defines, but for our target value
5103ed947fbSantirez * we take a faster path with unrolled loops. */
511d55474e5Santirez if (HLL_REGISTERS == 16384 && HLL_BITS == 6) {
5123ed947fbSantirez uint8_t *r = registers;
5133ed947fbSantirez unsigned long r0, r1, r2, r3, r4, r5, r6, r7, r8, r9,
5143ed947fbSantirez r10, r11, r12, r13, r14, r15;
5153ed947fbSantirez for (j = 0; j < 1024; j++) {
5163ed947fbSantirez /* Handle 16 registers per iteration. */
5173ed947fbSantirez r0 = r[0] & 63; if (r0 == 0) ez++;
5184628ac00Santirez r1 = (r[0] >> 6 | r[1] << 2) & 63; if (r1 == 0) ez++;
5194628ac00Santirez r2 = (r[1] >> 4 | r[2] << 4) & 63; if (r2 == 0) ez++;
5204628ac00Santirez r3 = (r[2] >> 2) & 63; if (r3 == 0) ez++;
5215317a582Santirez r4 = r[3] & 63; if (r4 == 0) ez++;
5224628ac00Santirez r5 = (r[3] >> 6 | r[4] << 2) & 63; if (r5 == 0) ez++;
5234628ac00Santirez r6 = (r[4] >> 4 | r[5] << 4) & 63; if (r6 == 0) ez++;
5244628ac00Santirez r7 = (r[5] >> 2) & 63; if (r7 == 0) ez++;
5255317a582Santirez r8 = r[6] & 63; if (r8 == 0) ez++;
5264628ac00Santirez r9 = (r[6] >> 6 | r[7] << 2) & 63; if (r9 == 0) ez++;
5274628ac00Santirez r10 = (r[7] >> 4 | r[8] << 4) & 63; if (r10 == 0) ez++;
5284628ac00Santirez r11 = (r[8] >> 2) & 63; if (r11 == 0) ez++;
5295317a582Santirez r12 = r[9] & 63; if (r12 == 0) ez++;
5304628ac00Santirez r13 = (r[9] >> 6 | r[10] << 2) & 63; if (r13 == 0) ez++;
5314628ac00Santirez r14 = (r[10] >> 4 | r[11] << 4) & 63; if (r14 == 0) ez++;
5324628ac00Santirez r15 = (r[11] >> 2) & 63; if (r15 == 0) ez++;
5333ed947fbSantirez
5343ed947fbSantirez /* Additional parens will allow the compiler to optimize the
5353ed947fbSantirez * code more with a loss of precision that is not very relevant
5363ed947fbSantirez * here (floating point math is not commutative!). */
5373ed947fbSantirez E += (PE[r0] + PE[r1]) + (PE[r2] + PE[r3]) + (PE[r4] + PE[r5]) +
5383ed947fbSantirez (PE[r6] + PE[r7]) + (PE[r8] + PE[r9]) + (PE[r10] + PE[r11]) +
5393ed947fbSantirez (PE[r12] + PE[r13]) + (PE[r14] + PE[r15]);
5403ed947fbSantirez r += 12;
5413ed947fbSantirez }
5423ed947fbSantirez } else {
543d55474e5Santirez for (j = 0; j < HLL_REGISTERS; j++) {
54428dce36fSantirez unsigned long reg;
54528dce36fSantirez
5461efc1e05Santirez HLL_DENSE_GET_REGISTER(reg,registers,j);
547ded86076Santirez if (reg == 0) {
548ded86076Santirez ez++;
549192a2132Santirez /* Increment E at the end of the loop. */
550ded86076Santirez } else {
551ac8fbe88Santirez E += PE[reg]; /* Precomputed 2^(-reg[j]). */
552ded86076Santirez }
553ded86076Santirez }
554192a2132Santirez E += ez; /* Add 2^0 'ez' times. */
5553ed947fbSantirez }
5568ea5b46dSantirez *ezp = ez;
5578ea5b46dSantirez return E;
5588ea5b46dSantirez }
5598ea5b46dSantirez
5608ea5b46dSantirez /* ================== Sparse representation implementation ================= */
5618ea5b46dSantirez
5621fc04a62Santirez /* Convert the HLL with sparse representation given as input in its dense
5631fc04a62Santirez * representation. Both representations are represented by SDS strings, and
564b7571b74Santirez * the input representation is freed as a side effect.
565b7571b74Santirez *
56640eb548aSantirez * The function returns C_OK if the sparse representation was valid,
56740eb548aSantirez * otherwise C_ERR is returned if the representation was corrupted. */
hllSparseToDense(robj * o)568b7571b74Santirez int hllSparseToDense(robj *o) {
569e8e717e1Santirez sds sparse = o->ptr, dense;
5701fc04a62Santirez struct hllhdr *hdr, *oldhdr = (struct hllhdr*)sparse;
5711fc04a62Santirez int idx = 0, runlen, regval;
5721fc04a62Santirez uint8_t *p = (uint8_t*)sparse, *end = p+sdslen(sparse);
5731fc04a62Santirez
574e8e717e1Santirez /* If the representation is already the right one return ASAP. */
575e8e717e1Santirez hdr = (struct hllhdr*) sparse;
57640eb548aSantirez if (hdr->encoding == HLL_DENSE) return C_OK;
577e8e717e1Santirez
5781fc04a62Santirez /* Create a string of the right size filled with zero bytes.
5791fc04a62Santirez * Note that the cached cardinality is set to 0 as a side effect
5801fc04a62Santirez * that is exactly the cardinality of an empty HLL. */
5811fc04a62Santirez dense = sdsnewlen(NULL,HLL_DENSE_SIZE);
5821fc04a62Santirez hdr = (struct hllhdr*) dense;
5831fc04a62Santirez *hdr = *oldhdr; /* This will copy the magic and cached cardinality. */
5841fc04a62Santirez hdr->encoding = HLL_DENSE;
5851fc04a62Santirez
5861fc04a62Santirez /* Now read the sparse representation and set non-zero registers
5871fc04a62Santirez * accordingly. */
5881fc04a62Santirez p += HLL_HDR_SIZE;
5891fc04a62Santirez while(p < end) {
5901fc04a62Santirez if (HLL_SPARSE_IS_ZERO(p)) {
5911fc04a62Santirez runlen = HLL_SPARSE_ZERO_LEN(p);
5921fc04a62Santirez idx += runlen;
593b5659cb0Santirez p++;
5941fc04a62Santirez } else if (HLL_SPARSE_IS_XZERO(p)) {
5951fc04a62Santirez runlen = HLL_SPARSE_XZERO_LEN(p);
5961fc04a62Santirez idx += runlen;
597b5659cb0Santirez p += 2;
5981fc04a62Santirez } else {
5991fc04a62Santirez runlen = HLL_SPARSE_VAL_LEN(p);
6001fc04a62Santirez regval = HLL_SPARSE_VAL_VALUE(p);
6011fc04a62Santirez while(runlen--) {
6021fc04a62Santirez HLL_DENSE_SET_REGISTER(hdr->registers,idx,regval);
6031fc04a62Santirez idx++;
6041fc04a62Santirez }
605b5659cb0Santirez p++;
6061fc04a62Santirez }
6071fc04a62Santirez }
6081fc04a62Santirez
609b7571b74Santirez /* If the sparse representation was valid, we expect to find idx
610b7571b74Santirez * set to HLL_REGISTERS. */
611b7571b74Santirez if (idx != HLL_REGISTERS) {
612b7571b74Santirez sdsfree(dense);
61340eb548aSantirez return C_ERR;
614b7571b74Santirez }
615b7571b74Santirez
616e8e717e1Santirez /* Free the old representation and set the new one. */
617e8e717e1Santirez sdsfree(o->ptr);
618e8e717e1Santirez o->ptr = dense;
61940eb548aSantirez return C_OK;
620c756936bSantirez }
621c756936bSantirez
622c756936bSantirez /* "Add" the element in the sparse hyperloglog data structure.
623c756936bSantirez * Actually nothing is added, but the max 0 pattern counter of the subset
624c756936bSantirez * the element belongs to is incremented if needed.
625c756936bSantirez *
626c756936bSantirez * The object 'o' is the String object holding the HLL. The function requires
627c756936bSantirez * a reference to the object in order to be able to enlarge the string if
628c756936bSantirez * needed.
629c756936bSantirez *
630c756936bSantirez * On success, the function returns 1 if the cardinality changed, or 0
631c756936bSantirez * if the register for this element was not updated.
6322067644aSantirez * On error (if the representation is invalid) -1 is returned.
633c756936bSantirez *
634c756936bSantirez * As a side effect the function may promote the HLL representation from
635c756936bSantirez * sparse to dense: this happens when a register requires to be set to a value
636c756936bSantirez * not representable with the sparse representation, or when the resulting
637402110f9Santirez * size would be greater than server.hll_sparse_max_bytes. */
hllSparseAdd(robj * o,unsigned char * ele,size_t elesize)638c756936bSantirez int hllSparseAdd(robj *o, unsigned char *ele, size_t elesize) {
639c756936bSantirez struct hllhdr *hdr;
640c756936bSantirez uint8_t oldcount, count, *sparse, *end, *p, *prev, *next;
641e9cd51c7Santirez long index, first, span;
642e9cd51c7Santirez long is_zero = 0, is_xzero = 0, is_val = 0, runlen = 0;
643c756936bSantirez
644c756936bSantirez /* Update the register if this element produced a longer run of zeroes. */
645c756936bSantirez count = hllPatLen(ele,elesize,&index);
646c756936bSantirez
647c756936bSantirez /* If the count is too big to be representable by the sparse representation
648c756936bSantirez * switch to dense representation. */
649c756936bSantirez if (count > HLL_SPARSE_VAL_MAX_VALUE) goto promote;
650c756936bSantirez
651c756936bSantirez /* When updating a sparse representation, sometimes we may need to
652c756936bSantirez * enlarge the buffer for up to 3 bytes in the worst case (XZERO split
653c756936bSantirez * into XZERO-VAL-XZERO). Make sure there is enough space right now
654c756936bSantirez * so that the pointers we take during the execution of the function
655c756936bSantirez * will be valid all the time. */
656c756936bSantirez o->ptr = sdsMakeRoomFor(o->ptr,3);
657c756936bSantirez
658c756936bSantirez /* Step 1: we need to locate the opcode we need to modify to check
659c756936bSantirez * if a value update is actually needed. */
660c756936bSantirez sparse = p = ((uint8_t*)o->ptr) + HLL_HDR_SIZE;
661c756936bSantirez end = p + sdslen(o->ptr) - HLL_HDR_SIZE;
662c756936bSantirez
663c756936bSantirez first = 0;
664c756936bSantirez prev = NULL; /* Points to previos opcode at the end of the loop. */
665c756936bSantirez next = NULL; /* Points to the next opcode at the end of the loop. */
6662067644aSantirez span = 0;
667c756936bSantirez while(p < end) {
668e9cd51c7Santirez long oplen;
669db40da0aSantirez
670e9cd51c7Santirez /* Set span to the number of registers covered by this opcode.
671e9cd51c7Santirez *
672e9cd51c7Santirez * This is the most performance critical loop of the sparse
673e9cd51c7Santirez * representation. Sorting the conditionals from the most to the
674e9cd51c7Santirez * least frequent opcode in many-bytes sparse HLLs is faster. */
675e9cd51c7Santirez oplen = 1;
676db40da0aSantirez if (HLL_SPARSE_IS_ZERO(p)) {
677db40da0aSantirez span = HLL_SPARSE_ZERO_LEN(p);
678e9cd51c7Santirez } else if (HLL_SPARSE_IS_VAL(p)) {
679e9cd51c7Santirez span = HLL_SPARSE_VAL_LEN(p);
680e9cd51c7Santirez } else { /* XZERO. */
681db40da0aSantirez span = HLL_SPARSE_XZERO_LEN(p);
682db40da0aSantirez oplen = 2;
683db40da0aSantirez }
684c756936bSantirez /* Break if this opcode covers the register as 'index'. */
685142d133cSantirez if (index <= first+span-1) break;
686c756936bSantirez prev = p;
687db40da0aSantirez p += oplen;
688c756936bSantirez first += span;
689c756936bSantirez }
6902067644aSantirez if (span == 0) return -1; /* Invalid format. */
691c756936bSantirez
692c756936bSantirez next = HLL_SPARSE_IS_XZERO(p) ? p+2 : p+1;
693c756936bSantirez if (next >= end) next = NULL;
694c756936bSantirez
695c756936bSantirez /* Cache current opcode type to avoid using the macro again and
696c756936bSantirez * again for something that will not change.
697c756936bSantirez * Also cache the run-length of the opcode. */
698c756936bSantirez if (HLL_SPARSE_IS_ZERO(p)) {
699c756936bSantirez is_zero = 1;
700c756936bSantirez runlen = HLL_SPARSE_ZERO_LEN(p);
701c756936bSantirez } else if (HLL_SPARSE_IS_XZERO(p)) {
702c756936bSantirez is_xzero = 1;
703c756936bSantirez runlen = HLL_SPARSE_XZERO_LEN(p);
704c756936bSantirez } else {
705c756936bSantirez is_val = 1;
706c756936bSantirez runlen = HLL_SPARSE_VAL_LEN(p);
707c756936bSantirez }
708c756936bSantirez
709c756936bSantirez /* Step 2: After the loop:
710c756936bSantirez *
711c756936bSantirez * 'first' stores to the index of the first register covered
712c756936bSantirez * by the current opcode, which is pointed by 'p'.
713c756936bSantirez *
714c756936bSantirez * 'next' ad 'prev' store respectively the next and previous opcode,
715c756936bSantirez * or NULL if the opcode at 'p' is respectively the last or first.
716c756936bSantirez *
717c756936bSantirez * 'span' is set to the number of registers covered by the current
718c756936bSantirez * opcode.
719c756936bSantirez *
720c756936bSantirez * There are different cases in order to update the data structure
721c756936bSantirez * in place without generating it from scratch:
722c756936bSantirez *
723c756936bSantirez * A) If it is a VAL opcode already set to a value >= our 'count'
724c756936bSantirez * no update is needed, regardless of the VAL run-length field.
725c756936bSantirez * In this case PFADD returns 0 since no changes are performed.
726c756936bSantirez *
727c756936bSantirez * B) If it is a VAL opcode with len = 1 (representing only our
728c756936bSantirez * register) and the value is less than 'count', we just update it
729c756936bSantirez * since this is a trivial case. */
730c756936bSantirez if (is_val) {
731c756936bSantirez oldcount = HLL_SPARSE_VAL_VALUE(p);
732c756936bSantirez /* Case A. */
733c756936bSantirez if (oldcount >= count) return 0;
734c756936bSantirez
735c756936bSantirez /* Case B. */
736c756936bSantirez if (runlen == 1) {
737c756936bSantirez HLL_SPARSE_VAL_SET(p,count,1);
738c756936bSantirez goto updated;
739c756936bSantirez }
740c756936bSantirez }
741c756936bSantirez
742c756936bSantirez /* C) Another trivial to handle case is a ZERO opcode with a len of 1.
743c756936bSantirez * We can just replace it with a VAL opcode with our value and len of 1. */
744c756936bSantirez if (is_zero && runlen == 1) {
745c756936bSantirez HLL_SPARSE_VAL_SET(p,count,1);
746c756936bSantirez goto updated;
747c756936bSantirez }
748c756936bSantirez
749c756936bSantirez /* D) General case.
750c756936bSantirez *
751c756936bSantirez * The other cases are more complex: our register requires to be updated
752c756936bSantirez * and is either currently represented by a VAL opcode with len > 1,
753c756936bSantirez * by a ZERO opcode with len > 1, or by an XZERO opcode.
754c756936bSantirez *
755c756936bSantirez * In those cases the original opcode must be split into muliple
756c756936bSantirez * opcodes. The worst case is an XZERO split in the middle resuling into
757c756936bSantirez * XZERO - VAL - XZERO, so the resulting sequence max length is
758c756936bSantirez * 5 bytes.
759c756936bSantirez *
760c756936bSantirez * We perform the split writing the new sequence into the 'new' buffer
761c756936bSantirez * with 'newlen' as length. Later the new sequence is inserted in place
762c756936bSantirez * of the old one, possibly moving what is on the right a few bytes
763c756936bSantirez * if the new sequence is longer than the older one. */
764c756936bSantirez uint8_t seq[5], *n = seq;
765c756936bSantirez int last = first+span-1; /* Last register covered by the sequence. */
766c756936bSantirez int len;
767c756936bSantirez
768c756936bSantirez if (is_zero || is_xzero) {
769c756936bSantirez /* Handle splitting of ZERO / XZERO. */
770c756936bSantirez if (index != first) {
771c756936bSantirez len = index-first;
772c756936bSantirez if (len > HLL_SPARSE_ZERO_MAX_LEN) {
773c756936bSantirez HLL_SPARSE_XZERO_SET(n,len);
774c756936bSantirez n += 2;
775c756936bSantirez } else {
776c756936bSantirez HLL_SPARSE_ZERO_SET(n,len);
777c756936bSantirez n++;
778c756936bSantirez }
779c756936bSantirez }
780c756936bSantirez HLL_SPARSE_VAL_SET(n,count,1);
781c756936bSantirez n++;
782c756936bSantirez if (index != last) {
783c756936bSantirez len = last-index;
784c756936bSantirez if (len > HLL_SPARSE_ZERO_MAX_LEN) {
785c756936bSantirez HLL_SPARSE_XZERO_SET(n,len);
786c756936bSantirez n += 2;
787c756936bSantirez } else {
788c756936bSantirez HLL_SPARSE_ZERO_SET(n,len);
789c756936bSantirez n++;
790c756936bSantirez }
791c756936bSantirez }
792c756936bSantirez } else {
793c756936bSantirez /* Handle splitting of VAL. */
794c756936bSantirez int curval = HLL_SPARSE_VAL_VALUE(p);
795c756936bSantirez
796c756936bSantirez if (index != first) {
797c756936bSantirez len = index-first;
798c756936bSantirez HLL_SPARSE_VAL_SET(n,curval,len);
799c756936bSantirez n++;
800c756936bSantirez }
801c756936bSantirez HLL_SPARSE_VAL_SET(n,count,1);
802c756936bSantirez n++;
803c756936bSantirez if (index != last) {
804c756936bSantirez len = last-index;
805c756936bSantirez HLL_SPARSE_VAL_SET(n,curval,len);
806c756936bSantirez n++;
807c756936bSantirez }
808c756936bSantirez }
809c756936bSantirez
810c756936bSantirez /* Step 3: substitute the new sequence with the old one.
811c756936bSantirez *
812c756936bSantirez * Note that we already allocated space on the sds string
813c756936bSantirez * calling sdsMakeRoomFor(). */
8143c3c1656Santirez int seqlen = n-seq;
815c756936bSantirez int oldlen = is_xzero ? 2 : 1;
816c756936bSantirez int deltalen = seqlen-oldlen;
8171fc04a62Santirez
818402110f9Santirez if (deltalen > 0 &&
819402110f9Santirez sdslen(o->ptr)+deltalen > server.hll_sparse_max_bytes) goto promote;
82082c31f75Santirez if (deltalen && next) memmove(next+deltalen,next,end-next);
821c756936bSantirez sdsIncrLen(o->ptr,deltalen);
822c756936bSantirez memcpy(p,seq,seqlen);
8235532b530Santirez end += deltalen;
824c756936bSantirez
825c756936bSantirez updated:
826c756936bSantirez /* Step 4: Merge adjacent values if possible.
827c756936bSantirez *
828c756936bSantirez * The representation was updated, however the resulting representation
8295532b530Santirez * may not be optimal: adjacent VAL opcodes can sometimes be merged into
8305532b530Santirez * a single one. */
8315532b530Santirez p = prev ? prev : sparse;
8325532b530Santirez int scanlen = 5; /* Scan up to 5 upcodes starting from prev. */
8335532b530Santirez while (p < end && scanlen--) {
8345532b530Santirez if (HLL_SPARSE_IS_XZERO(p)) {
8355532b530Santirez p += 2;
8365532b530Santirez continue;
8375532b530Santirez } else if (HLL_SPARSE_IS_ZERO(p)) {
8385532b530Santirez p++;
8395532b530Santirez continue;
8405532b530Santirez }
8415532b530Santirez /* We need two adjacent VAL opcodes to try a merge, having
8424e0a99baSantirez * the same value, and a len that fits the VAL opcode max len. */
8435532b530Santirez if (p+1 < end && HLL_SPARSE_IS_VAL(p+1)) {
8445532b530Santirez int v1 = HLL_SPARSE_VAL_VALUE(p);
8455532b530Santirez int v2 = HLL_SPARSE_VAL_VALUE(p+1);
8465532b530Santirez if (v1 == v2) {
8475532b530Santirez int len = HLL_SPARSE_VAL_LEN(p)+HLL_SPARSE_VAL_LEN(p+1);
8485532b530Santirez if (len <= HLL_SPARSE_VAL_MAX_LEN) {
8495532b530Santirez HLL_SPARSE_VAL_SET(p+1,v1,len);
8505532b530Santirez memmove(p,p+1,end-p);
8515532b530Santirez sdsIncrLen(o->ptr,-1);
8525532b530Santirez end--;
8535532b530Santirez /* After a merge we reiterate without incrementing 'p'
8545532b530Santirez * in order to try to merge the just merged value with
8555532b530Santirez * a value on its right. */
8565532b530Santirez continue;
8575532b530Santirez }
8585532b530Santirez }
8595532b530Santirez }
8605532b530Santirez p++;
8615532b530Santirez }
8625532b530Santirez
8635532b530Santirez /* Invalidate the cached cardinality. */
864c756936bSantirez hdr = o->ptr;
865c756936bSantirez HLL_INVALIDATE_CACHE(hdr);
866c756936bSantirez return 1;
867c756936bSantirez
868c756936bSantirez promote: /* Promote to dense representation. */
86940eb548aSantirez if (hllSparseToDense(o) == C_ERR) return -1; /* Corrupted HLL. */
870c756936bSantirez hdr = o->ptr;
871ba0afb45Santirez
872ba0afb45Santirez /* We need to call hllDenseAdd() to perform the operation after the
873ba0afb45Santirez * conversion. However the result must be 1, since if we need to
874ba0afb45Santirez * convert from sparse to dense a register requires to be updated.
875ba0afb45Santirez *
876ba0afb45Santirez * Note that this in turn means that PFADD will make sure the command
877ba0afb45Santirez * is propagated to slaves / AOF, so if there is a sparse -> dense
878ba0afb45Santirez * convertion, it will be performed in all the slaves as well. */
879ba0afb45Santirez int dense_retval = hllDenseAdd(hdr->registers, ele, elesize);
8802d9e3eb1Santirez serverAssert(dense_retval == 1);
881ba0afb45Santirez return dense_retval;
882c756936bSantirez }
883c756936bSantirez
884c756936bSantirez /* Compute SUM(2^-reg) in the sparse representation.
885c756936bSantirez * PE is an array with a pre-computer table of values 2^-reg indexed by reg.
886c756936bSantirez * As a side effect the integer pointed by 'ezp' is set to the number
887c756936bSantirez * of zero registers. */
hllSparseSum(uint8_t * sparse,int sparselen,double * PE,int * ezp,int * invalid)888681bf746Santirez double hllSparseSum(uint8_t *sparse, int sparselen, double *PE, int *ezp, int *invalid) {
889c756936bSantirez double E = 0;
890c756936bSantirez int ez = 0, idx = 0, runlen, regval;
891c756936bSantirez uint8_t *end = sparse+sparselen, *p = sparse;
892c756936bSantirez
893c756936bSantirez while(p < end) {
894c756936bSantirez if (HLL_SPARSE_IS_ZERO(p)) {
895c756936bSantirez runlen = HLL_SPARSE_ZERO_LEN(p);
896c756936bSantirez idx += runlen;
897c756936bSantirez ez += runlen;
898192a2132Santirez /* Increment E at the end of the loop. */
899b5659cb0Santirez p++;
900c756936bSantirez } else if (HLL_SPARSE_IS_XZERO(p)) {
901c756936bSantirez runlen = HLL_SPARSE_XZERO_LEN(p);
902c756936bSantirez idx += runlen;
903c756936bSantirez ez += runlen;
904192a2132Santirez /* Increment E at the end of the loop. */
905b5659cb0Santirez p += 2;
906c756936bSantirez } else {
907c756936bSantirez runlen = HLL_SPARSE_VAL_LEN(p);
908c756936bSantirez regval = HLL_SPARSE_VAL_VALUE(p);
909c756936bSantirez idx += runlen;
910c756936bSantirez E += PE[regval]*runlen;
911b5659cb0Santirez p++;
912c756936bSantirez }
913c756936bSantirez }
914681bf746Santirez if (idx != HLL_REGISTERS && invalid) *invalid = 1;
915192a2132Santirez E += ez; /* Add 2^0 'ez' times. */
916c756936bSantirez *ezp = ez;
917c756936bSantirez return E;
918c756936bSantirez }
919c756936bSantirez
9208ea5b46dSantirez /* ========================= HyperLogLog Count ==============================
9218ea5b46dSantirez * This is the core of the algorithm where the approximated count is computed.
9228ea5b46dSantirez * The function uses the lower level hllDenseSum() and hllSparseSum() functions
9238ea5b46dSantirez * as helpers to compute the SUM(2^-reg) part of the computation, which is
9248ea5b46dSantirez * representation-specific, while all the rest is common. */
9258ea5b46dSantirez
9260feb2aabSantirez /* Implements the SUM operation for uint8_t data type which is only used
9270feb2aabSantirez * internally as speedup for PFCOUNT with multiple keys. */
hllRawSum(uint8_t * registers,double * PE,int * ezp)9280feb2aabSantirez double hllRawSum(uint8_t *registers, double *PE, int *ezp) {
9290feb2aabSantirez double E = 0;
9300feb2aabSantirez int j, ez = 0;
9315eb7ac0cSantirez uint64_t *word = (uint64_t*) registers;
9325eb7ac0cSantirez uint8_t *bytes;
9330feb2aabSantirez
9345eb7ac0cSantirez for (j = 0; j < HLL_REGISTERS/8; j++) {
9355eb7ac0cSantirez if (*word == 0) {
9365eb7ac0cSantirez ez += 8;
9370feb2aabSantirez } else {
9385eb7ac0cSantirez bytes = (uint8_t*) word;
9395eb7ac0cSantirez if (bytes[0]) E += PE[bytes[0]]; else ez++;
9405eb7ac0cSantirez if (bytes[1]) E += PE[bytes[1]]; else ez++;
9415eb7ac0cSantirez if (bytes[2]) E += PE[bytes[2]]; else ez++;
9425eb7ac0cSantirez if (bytes[3]) E += PE[bytes[3]]; else ez++;
9435eb7ac0cSantirez if (bytes[4]) E += PE[bytes[4]]; else ez++;
9445eb7ac0cSantirez if (bytes[5]) E += PE[bytes[5]]; else ez++;
9455eb7ac0cSantirez if (bytes[6]) E += PE[bytes[6]]; else ez++;
9465eb7ac0cSantirez if (bytes[7]) E += PE[bytes[7]]; else ez++;
9470feb2aabSantirez }
9485eb7ac0cSantirez word++;
9490feb2aabSantirez }
950192a2132Santirez E += ez; /* 2^(-reg[j]) is 1 when m is 0, add it 'ez' times for every
951192a2132Santirez zero register in the HLL. */
9520feb2aabSantirez *ezp = ez;
9530feb2aabSantirez return E;
9540feb2aabSantirez }
9550feb2aabSantirez
956ba52cd06SMike Trinkala /* Return the approximated cardinality of the set based on the harmonic
957c756936bSantirez * mean of the registers values. 'hdr' points to the start of the SDS
958681bf746Santirez * representing the String object holding the HLL representation.
959681bf746Santirez *
960681bf746Santirez * If the sparse representation of the HLL object is not valid, the integer
9610feb2aabSantirez * pointed by 'invalid' is set to non-zero, otherwise it is left untouched.
9620feb2aabSantirez *
9630feb2aabSantirez * hllCount() supports a special internal-only encoding of HLL_RAW, that
9640feb2aabSantirez * is, hdr->registers will point to an uint8_t array of HLL_REGISTERS element.
9650feb2aabSantirez * This is useful in order to speedup PFCOUNT when called against multiple
9660feb2aabSantirez * keys (no need to work with 6-bit integers encoding). */
hllCount(struct hllhdr * hdr,int * invalid)967681bf746Santirez uint64_t hllCount(struct hllhdr *hdr, int *invalid) {
9688ea5b46dSantirez double m = HLL_REGISTERS;
969681bf746Santirez double E, alpha = 0.7213/(1+1.079/m);
970681bf746Santirez int j, ez; /* Number of registers equal to 0. */
9718ea5b46dSantirez
9728ea5b46dSantirez /* We precompute 2^(-reg[j]) in a small table in order to
9738ea5b46dSantirez * speedup the computation of SUM(2^-register[0..i]). */
9748ea5b46dSantirez static int initialized = 0;
9758ea5b46dSantirez static double PE[64];
9768ea5b46dSantirez if (!initialized) {
9778ea5b46dSantirez PE[0] = 1; /* 2^(-reg[j]) is 1 when m is 0. */
9788ea5b46dSantirez for (j = 1; j < 64; j++) {
9798ea5b46dSantirez /* 2^(-reg[j]) is the same as 1/2^reg[j]. */
9808ea5b46dSantirez PE[j] = 1.0/(1ULL << j);
9818ea5b46dSantirez }
9828ea5b46dSantirez initialized = 1;
9838ea5b46dSantirez }
9848ea5b46dSantirez
9858ea5b46dSantirez /* Compute SUM(2^-register[0..i]). */
9868ea5b46dSantirez if (hdr->encoding == HLL_DENSE) {
9878ea5b46dSantirez E = hllDenseSum(hdr->registers,PE,&ez);
9880feb2aabSantirez } else if (hdr->encoding == HLL_SPARSE) {
989681bf746Santirez E = hllSparseSum(hdr->registers,
990681bf746Santirez sdslen((sds)hdr)-HLL_HDR_SIZE,PE,&ez,invalid);
9910feb2aabSantirez } else if (hdr->encoding == HLL_RAW) {
9920feb2aabSantirez E = hllRawSum(hdr->registers,PE,&ez);
9930feb2aabSantirez } else {
994*32f80e2fSantirez serverPanic("Unknown HyperLogLog encoding in hllCount()");
9958ea5b46dSantirez }
9968ea5b46dSantirez
997ded86076Santirez /* Muliply the inverse of E for alpha_m * m^2 to have the raw estimate. */
998ded86076Santirez E = (1/E)*alpha*m*m;
999ded86076Santirez
1000ec1ee662Santirez /* Use the LINEARCOUNTING algorithm for small cardinalities.
1001ec1ee662Santirez * For larger values but up to 72000 HyperLogLog raw approximation is
1002ec1ee662Santirez * used since linear counting error starts to increase. However HyperLogLog
1003ec1ee662Santirez * shows a strong bias in the range 2.5*16384 - 72000, so we try to
1004ec1ee662Santirez * compensate for it. */
1005ec1ee662Santirez if (E < m*2.5 && ez != 0) {
1006ded86076Santirez E = m*log(m/ez); /* LINEARCOUNTING() */
1007ec1ee662Santirez } else if (m == 16384 && E < 72000) {
1008ec1ee662Santirez /* We did polynomial regression of the bias for this range, this
1009ec1ee662Santirez * way we can compute the bias for a given cardinality and correct
1010ec1ee662Santirez * according to it. Only apply the correction for P=14 that's what
1011ec1ee662Santirez * we use and the value the correction was verified with. */
1012ec1ee662Santirez double bias = 5.9119*1.0e-18*(E*E*E*E)
1013ec1ee662Santirez -1.4253*1.0e-12*(E*E*E)+
1014ec1ee662Santirez 1.2940*1.0e-7*(E*E)
1015ec1ee662Santirez -5.2921*1.0e-3*E+
1016ec1ee662Santirez 83.3216;
1017ec1ee662Santirez E -= E*(bias/100);
1018ded86076Santirez }
1019ded86076Santirez /* We don't apply the correction for E > 1/30 of 2^32 since we use
1020ded86076Santirez * a 64 bit function and 6 bit counters. To apply the correction for
1021ded86076Santirez * 1/30 of 2^64 is not needed since it would require a huge set
1022ded86076Santirez * to approach such a value. */
1023ded86076Santirez return (uint64_t) E;
1024ded86076Santirez }
1025ded86076Santirez
1026a9e057e0Santirez /* Call hllDenseAdd() or hllSparseAdd() according to the HLL encoding. */
hllAdd(robj * o,unsigned char * ele,size_t elesize)1027a9e057e0Santirez int hllAdd(robj *o, unsigned char *ele, size_t elesize) {
1028a9e057e0Santirez struct hllhdr *hdr = o->ptr;
1029a9e057e0Santirez switch(hdr->encoding) {
1030a9e057e0Santirez case HLL_DENSE: return hllDenseAdd(hdr->registers,ele,elesize);
1031a9e057e0Santirez case HLL_SPARSE: return hllSparseAdd(o,ele,elesize);
1032a9e057e0Santirez default: return -1; /* Invalid representation. */
1033a9e057e0Santirez }
1034a9e057e0Santirez }
1035a9e057e0Santirez
1036fcd2155bSantirez /* Merge by computing MAX(registers[i],hll[i]) the HyperLogLog 'hll'
1037fcd2155bSantirez * with an array of uint8_t HLL_REGISTERS registers pointed by 'max'.
1038fcd2155bSantirez *
1039fcd2155bSantirez * The hll object must be already validated via isHLLObjectOrReply()
1040fcd2155bSantirez * or in some other way.
1041fcd2155bSantirez *
104240eb548aSantirez * If the HyperLogLog is sparse and is found to be invalid, C_ERR
1043fcd2155bSantirez * is returned, otherwise the function always succeeds. */
hllMerge(uint8_t * max,robj * hll)1044fcd2155bSantirez int hllMerge(uint8_t *max, robj *hll) {
1045fcd2155bSantirez struct hllhdr *hdr = hll->ptr;
1046fcd2155bSantirez int i;
1047fcd2155bSantirez
1048fcd2155bSantirez if (hdr->encoding == HLL_DENSE) {
1049fcd2155bSantirez uint8_t val;
1050fcd2155bSantirez
1051fcd2155bSantirez for (i = 0; i < HLL_REGISTERS; i++) {
1052fcd2155bSantirez HLL_DENSE_GET_REGISTER(val,hdr->registers,i);
1053fcd2155bSantirez if (val > max[i]) max[i] = val;
1054fcd2155bSantirez }
1055fcd2155bSantirez } else {
1056fcd2155bSantirez uint8_t *p = hll->ptr, *end = p + sdslen(hll->ptr);
1057fcd2155bSantirez long runlen, regval;
1058fcd2155bSantirez
1059fcd2155bSantirez p += HLL_HDR_SIZE;
1060fcd2155bSantirez i = 0;
1061fcd2155bSantirez while(p < end) {
1062fcd2155bSantirez if (HLL_SPARSE_IS_ZERO(p)) {
1063fcd2155bSantirez runlen = HLL_SPARSE_ZERO_LEN(p);
1064fcd2155bSantirez i += runlen;
1065fcd2155bSantirez p++;
1066fcd2155bSantirez } else if (HLL_SPARSE_IS_XZERO(p)) {
1067fcd2155bSantirez runlen = HLL_SPARSE_XZERO_LEN(p);
1068fcd2155bSantirez i += runlen;
1069fcd2155bSantirez p += 2;
1070fcd2155bSantirez } else {
1071fcd2155bSantirez runlen = HLL_SPARSE_VAL_LEN(p);
1072fcd2155bSantirez regval = HLL_SPARSE_VAL_VALUE(p);
1073fcd2155bSantirez while(runlen--) {
1074fcd2155bSantirez if (regval > max[i]) max[i] = regval;
1075fcd2155bSantirez i++;
1076fcd2155bSantirez }
1077fcd2155bSantirez p++;
1078fcd2155bSantirez }
1079fcd2155bSantirez }
108040eb548aSantirez if (i != HLL_REGISTERS) return C_ERR;
1081fcd2155bSantirez }
108240eb548aSantirez return C_OK;
1083fcd2155bSantirez }
1084fcd2155bSantirez
108506093806Santirez /* ========================== HyperLogLog commands ========================== */
108606093806Santirez
1087a79386b1Santirez /* Create an HLL object. We always create the HLL using sparse encoding.
1088a79386b1Santirez * This will be upgraded to the dense representation as needed. */
createHLLObject(void)1089096b5e92Santirez robj *createHLLObject(void) {
1090096b5e92Santirez robj *o;
1091a79386b1Santirez struct hllhdr *hdr;
1092a79386b1Santirez sds s;
1093a79386b1Santirez uint8_t *p;
1094a79386b1Santirez int sparselen = HLL_HDR_SIZE +
10951ccb6615Santirez (((HLL_REGISTERS+(HLL_SPARSE_XZERO_MAX_LEN-1)) /
10961ccb6615Santirez HLL_SPARSE_XZERO_MAX_LEN)*2);
1097a79386b1Santirez int aux;
1098096b5e92Santirez
1099a79386b1Santirez /* Populate the sparse representation with as many XZERO opcodes as
1100a79386b1Santirez * needed to represent all the registers. */
1101f5c03044Santirez aux = HLL_REGISTERS;
1102a79386b1Santirez s = sdsnewlen(NULL,sparselen);
1103a79386b1Santirez p = (uint8_t*)s + HLL_HDR_SIZE;
1104a79386b1Santirez while(aux) {
1105f5c03044Santirez int xzero = HLL_SPARSE_XZERO_MAX_LEN;
1106a79386b1Santirez if (xzero > aux) xzero = aux;
1107a79386b1Santirez HLL_SPARSE_XZERO_SET(p,xzero);
1108a79386b1Santirez p += 2;
1109a79386b1Santirez aux -= xzero;
1110a79386b1Santirez }
11112d9e3eb1Santirez serverAssert((p-(uint8_t*)s) == sparselen);
1112a79386b1Santirez
1113a79386b1Santirez /* Create the actual object. */
111414ff5724Santirez o = createObject(OBJ_STRING,s);
1115a79386b1Santirez hdr = o->ptr;
1116a79386b1Santirez memcpy(hdr->magic,"HYLL",4);
1117a79386b1Santirez hdr->encoding = HLL_SPARSE;
1118096b5e92Santirez return o;
1119096b5e92Santirez }
1120096b5e92Santirez
1121d55474e5Santirez /* Check if the object is a String with a valid HLL representation.
112240eb548aSantirez * Return C_OK if this is true, otherwise reply to the client
112340eb548aSantirez * with an error and return C_ERR. */
isHLLObjectOrReply(client * c,robj * o)1124554bd0e7Santirez int isHLLObjectOrReply(client *c, robj *o) {
1125d55474e5Santirez struct hllhdr *hdr;
1126d55474e5Santirez
1127ce637b2fSantirez /* Key exists, check type */
112814ff5724Santirez if (checkType(c,o,OBJ_STRING))
112940eb548aSantirez return C_ERR; /* Error already sent. */
1130ce637b2fSantirez
1131d55474e5Santirez if (stringObjectLen(o) < sizeof(*hdr)) goto invalid;
1132d55474e5Santirez hdr = o->ptr;
1133d55474e5Santirez
1134d55474e5Santirez /* Magic should be "HYLL". */
1135d55474e5Santirez if (hdr->magic[0] != 'H' || hdr->magic[1] != 'Y' ||
1136d55474e5Santirez hdr->magic[2] != 'L' || hdr->magic[3] != 'L') goto invalid;
1137d55474e5Santirez
1138d55474e5Santirez if (hdr->encoding > HLL_MAX_ENCODING) goto invalid;
1139d55474e5Santirez
1140d55474e5Santirez /* Dense representation string length should match exactly. */
1141d55474e5Santirez if (hdr->encoding == HLL_DENSE &&
1142d55474e5Santirez stringObjectLen(o) != HLL_DENSE_SIZE) goto invalid;
1143d55474e5Santirez
1144d55474e5Santirez /* All tests passed. */
114540eb548aSantirez return C_OK;
1146d55474e5Santirez
1147d55474e5Santirez invalid:
1148d2ca4bb6Santirez addReplySds(c,
1149d2ca4bb6Santirez sdsnew("-WRONGTYPE Key is not a valid "
1150d2ca4bb6Santirez "HyperLogLog string value.\r\n"));
115140eb548aSantirez return C_ERR;
1152ce637b2fSantirez }
1153ce637b2fSantirez
11545afcca34Santirez /* PFADD var ele ele ele ... ele => :0 or :1 */
pfaddCommand(client * c)1155554bd0e7Santirez void pfaddCommand(client *c) {
1156156929eeSantirez robj *o = lookupKeyWrite(c->db,c->argv[1]);
1157d55474e5Santirez struct hllhdr *hdr;
1158156929eeSantirez int updated = 0, j;
1159156929eeSantirez
1160156929eeSantirez if (o == NULL) {
1161156929eeSantirez /* Create the key with a string value of the exact length to
1162156929eeSantirez * hold our HLL data structure. sdsnewlen() when NULL is passed
1163156929eeSantirez * is guaranteed to return bytes initialized to zero. */
1164096b5e92Santirez o = createHLLObject();
1165156929eeSantirez dbAdd(c->db,c->argv[1],o);
11668aeb0c19Santirez updated++;
1167156929eeSantirez } else {
116840eb548aSantirez if (isHLLObjectOrReply(c,o) != C_OK) return;
1169543ede03Santirez o = dbUnshareStringValue(c->db,c->argv[1],o);
1170156929eeSantirez }
1171156929eeSantirez /* Perform the low level ADD operation for every element. */
1172156929eeSantirez for (j = 2; j < c->argc; j++) {
1173a9e057e0Santirez int retval = hllAdd(o, (unsigned char*)c->argv[j]->ptr,
1174a9e057e0Santirez sdslen(c->argv[j]->ptr));
1175a9e057e0Santirez switch(retval) {
1176a9e057e0Santirez case 1:
1177156929eeSantirez updated++;
1178a9e057e0Santirez break;
1179a9e057e0Santirez case -1:
11808e8f8189Santirez addReplySds(c,sdsnew(invalid_hll_err));
1181a9e057e0Santirez return;
1182156929eeSantirez }
1183156929eeSantirez }
1184a9e057e0Santirez hdr = o->ptr;
1185156929eeSantirez if (updated) {
1186156929eeSantirez signalModifiedKey(c->db,c->argv[1]);
1187*32f80e2fSantirez notifyKeyspaceEvent(NOTIFY_STRING,"pfadd",c->argv[1],c->db->id);
1188156929eeSantirez server.dirty++;
1189d55474e5Santirez HLL_INVALIDATE_CACHE(hdr);
1190156929eeSantirez }
1191156929eeSantirez addReply(c, updated ? shared.cone : shared.czero);
1192156929eeSantirez }
1193156929eeSantirez
11945afcca34Santirez /* PFCOUNT var -> approximated cardinality of set. */
pfcountCommand(client * c)1195554bd0e7Santirez void pfcountCommand(client *c) {
11960feb2aabSantirez robj *o;
1197d55474e5Santirez struct hllhdr *hdr;
1198307a1899Santirez uint64_t card;
1199ded86076Santirez
12000feb2aabSantirez /* Case 1: multi-key keys, cardinality of the union.
12010feb2aabSantirez *
12020feb2aabSantirez * When multiple keys are specified, PFCOUNT actually computes
12030feb2aabSantirez * the cardinality of the merge of the N HLLs specified. */
12040feb2aabSantirez if (c->argc > 2) {
12050feb2aabSantirez uint8_t max[HLL_HDR_SIZE+HLL_REGISTERS], *registers;
12060feb2aabSantirez int j;
12070feb2aabSantirez
12080feb2aabSantirez /* Compute an HLL with M[i] = MAX(M[i]_j). */
12090feb2aabSantirez memset(max,0,sizeof(max));
12100feb2aabSantirez hdr = (struct hllhdr*) max;
12110feb2aabSantirez hdr->encoding = HLL_RAW; /* Special internal-only encoding. */
12120feb2aabSantirez registers = max + HLL_HDR_SIZE;
12130feb2aabSantirez for (j = 1; j < c->argc; j++) {
12140feb2aabSantirez /* Check type and size. */
12150feb2aabSantirez robj *o = lookupKeyRead(c->db,c->argv[j]);
12160feb2aabSantirez if (o == NULL) continue; /* Assume empty HLL for non existing var.*/
121740eb548aSantirez if (isHLLObjectOrReply(c,o) != C_OK) return;
12180feb2aabSantirez
12190feb2aabSantirez /* Merge with this HLL with our 'max' HHL by setting max[i]
12200feb2aabSantirez * to MAX(max[i],hll[i]). */
122140eb548aSantirez if (hllMerge(registers,o) == C_ERR) {
12220feb2aabSantirez addReplySds(c,sdsnew(invalid_hll_err));
12230feb2aabSantirez return;
12240feb2aabSantirez }
12250feb2aabSantirez }
12260feb2aabSantirez
12270feb2aabSantirez /* Compute cardinality of the resulting set. */
12280feb2aabSantirez addReplyLongLong(c,hllCount(hdr,NULL));
12290feb2aabSantirez return;
12300feb2aabSantirez }
12310feb2aabSantirez
12320feb2aabSantirez /* Case 2: cardinality of the single HLL.
12330feb2aabSantirez *
12340feb2aabSantirez * The user specified a single key. Either return the cached value
12350feb2aabSantirez * or compute one and update the cache. */
123606e76bc3Santirez o = lookupKeyWrite(c->db,c->argv[1]);
1237ded86076Santirez if (o == NULL) {
1238ded86076Santirez /* No key? Cardinality is zero since no element was added, otherwise
12393ed947fbSantirez * we would have a key as HLLADD creates it as a side effect. */
1240ded86076Santirez addReply(c,shared.czero);
1241ded86076Santirez } else {
124240eb548aSantirez if (isHLLObjectOrReply(c,o) != C_OK) return;
1243d5be696dSantirez o = dbUnshareStringValue(c->db,c->argv[1],o);
1244307a1899Santirez
1245307a1899Santirez /* Check if the cached cardinality is valid. */
1246d55474e5Santirez hdr = o->ptr;
1247d55474e5Santirez if (HLL_VALID_CACHE(hdr)) {
1248307a1899Santirez /* Just return the cached value. */
1249d55474e5Santirez card = (uint64_t)hdr->card[0];
1250d55474e5Santirez card |= (uint64_t)hdr->card[1] << 8;
1251d55474e5Santirez card |= (uint64_t)hdr->card[2] << 16;
1252d55474e5Santirez card |= (uint64_t)hdr->card[3] << 24;
1253d55474e5Santirez card |= (uint64_t)hdr->card[4] << 32;
1254d55474e5Santirez card |= (uint64_t)hdr->card[5] << 40;
1255d55474e5Santirez card |= (uint64_t)hdr->card[6] << 48;
1256d55474e5Santirez card |= (uint64_t)hdr->card[7] << 56;
1257307a1899Santirez } else {
1258681bf746Santirez int invalid = 0;
1259307a1899Santirez /* Recompute it and update the cached value. */
1260681bf746Santirez card = hllCount(hdr,&invalid);
1261681bf746Santirez if (invalid) {
12628e8f8189Santirez addReplySds(c,sdsnew(invalid_hll_err));
1263681bf746Santirez return;
1264681bf746Santirez }
1265d55474e5Santirez hdr->card[0] = card & 0xff;
1266d55474e5Santirez hdr->card[1] = (card >> 8) & 0xff;
1267d55474e5Santirez hdr->card[2] = (card >> 16) & 0xff;
1268d55474e5Santirez hdr->card[3] = (card >> 24) & 0xff;
1269d55474e5Santirez hdr->card[4] = (card >> 32) & 0xff;
1270d55474e5Santirez hdr->card[5] = (card >> 40) & 0xff;
1271d55474e5Santirez hdr->card[6] = (card >> 48) & 0xff;
1272d55474e5Santirez hdr->card[7] = (card >> 56) & 0xff;
12734ab45183Santirez /* This is not considered a read-only command even if the
12744ab45183Santirez * data structure is not modified, since the cached value
12754ab45183Santirez * may be modified and given that the HLL is a Redis string
12764ab45183Santirez * we need to propagate the change. */
12774ab45183Santirez signalModifiedKey(c->db,c->argv[1]);
12784ab45183Santirez server.dirty++;
1279307a1899Santirez }
1280307a1899Santirez addReplyLongLong(c,card);
1281ded86076Santirez }
1282ded86076Santirez }
1283ded86076Santirez
12845afcca34Santirez /* PFMERGE dest src1 src2 src3 ... srcN => OK */
pfmergeCommand(client * c)1285554bd0e7Santirez void pfmergeCommand(client *c) {
1286d55474e5Santirez uint8_t max[HLL_REGISTERS];
1287d55474e5Santirez struct hllhdr *hdr;
1288fcd2155bSantirez int j;
1289f2277475Santirez
1290f2277475Santirez /* Compute an HLL with M[i] = MAX(M[i]_j).
1291f2277475Santirez * We we the maximum into the max array of registers. We'll write
1292f2277475Santirez * it to the target variable later. */
1293f2277475Santirez memset(max,0,sizeof(max));
1294f2277475Santirez for (j = 1; j < c->argc; j++) {
1295f2277475Santirez /* Check type and size. */
1296f2277475Santirez robj *o = lookupKeyRead(c->db,c->argv[j]);
1297f2277475Santirez if (o == NULL) continue; /* Assume empty HLL for non existing var. */
129840eb548aSantirez if (isHLLObjectOrReply(c,o) != C_OK) return;
1299f2277475Santirez
1300f1b76081Santirez /* Merge with this HLL with our 'max' HHL by setting max[i]
1301f1b76081Santirez * to MAX(max[i],hll[i]). */
130240eb548aSantirez if (hllMerge(max,o) == C_ERR) {
13038e8f8189Santirez addReplySds(c,sdsnew(invalid_hll_err));
130481ceef7dSantirez return;
130581ceef7dSantirez }
130681ceef7dSantirez }
1307f2277475Santirez
1308f2277475Santirez /* Create / unshare the destination key's value if needed. */
130981ceef7dSantirez robj *o = lookupKeyWrite(c->db,c->argv[1]);
1310f2277475Santirez if (o == NULL) {
1311f2277475Santirez /* Create the key with a string value of the exact length to
1312f2277475Santirez * hold our HLL data structure. sdsnewlen() when NULL is passed
1313f2277475Santirez * is guaranteed to return bytes initialized to zero. */
1314096b5e92Santirez o = createHLLObject();
1315f2277475Santirez dbAdd(c->db,c->argv[1],o);
1316f2277475Santirez } else {
1317f2277475Santirez /* If key exists we are sure it's of the right type/size
1318f2277475Santirez * since we checked when merging the different HLLs, so we
1319f2277475Santirez * don't check again. */
1320f2277475Santirez o = dbUnshareStringValue(c->db,c->argv[1],o);
1321f2277475Santirez }
1322f2277475Santirez
132381ceef7dSantirez /* Only support dense objects as destination. */
132440eb548aSantirez if (hllSparseToDense(o) == C_ERR) {
13258e8f8189Santirez addReplySds(c,sdsnew(invalid_hll_err));
132681ceef7dSantirez return;
132781ceef7dSantirez }
132881ceef7dSantirez
1329f2277475Santirez /* Write the resulting HLL to the destination HLL registers and
1330f2277475Santirez * invalidate the cached value. */
1331d55474e5Santirez hdr = o->ptr;
1332d55474e5Santirez for (j = 0; j < HLL_REGISTERS; j++) {
13331efc1e05Santirez HLL_DENSE_SET_REGISTER(hdr->registers,j,max[j]);
1334f2277475Santirez }
1335d55474e5Santirez HLL_INVALIDATE_CACHE(hdr);
1336f2277475Santirez
1337f2277475Santirez signalModifiedKey(c->db,c->argv[1]);
1338fcd2155bSantirez /* We generate an PFADD event for PFMERGE for semantical simplicity
1339f2277475Santirez * since in theory this is a mass-add of elements. */
1340*32f80e2fSantirez notifyKeyspaceEvent(NOTIFY_STRING,"pfadd",c->argv[1],c->db->id);
1341f2277475Santirez server.dirty++;
1342f2277475Santirez addReply(c,shared.ok);
1343f2277475Santirez }
1344f2277475Santirez
1345aaaed66cSantirez /* ========================== Testing / Debugging ========================== */
1346aaaed66cSantirez
1347aaaed66cSantirez /* PFSELFTEST
1348aaaed66cSantirez * This command performs a self-test of the HLL registers implementation.
1349be9860d0Santirez * Something that is not easy to test from within the outside. */
1350d55474e5Santirez #define HLL_TEST_CYCLES 1000
pfselftestCommand(client * c)1351554bd0e7Santirez void pfselftestCommand(client *c) {
1352edca2b14Santirez unsigned int j, i;
1353d55474e5Santirez sds bitcounters = sdsnewlen(NULL,HLL_DENSE_SIZE);
1354d541f65dSantirez struct hllhdr *hdr = (struct hllhdr*) bitcounters, *hdr2;
1355d541f65dSantirez robj *o = NULL;
1356d55474e5Santirez uint8_t bytecounters[HLL_REGISTERS];
1357552eb540Santirez
1358be9860d0Santirez /* Test 1: access registers.
1359be9860d0Santirez * The test is conceived to test that the different counters of our data
1360be9860d0Santirez * structure are accessible and that setting their values both result in
1361be9860d0Santirez * the correct value to be retained and not affect adjacent values. */
1362d55474e5Santirez for (j = 0; j < HLL_TEST_CYCLES; j++) {
1363552eb540Santirez /* Set the HLL counters and an array of unsigned byes of the
1364552eb540Santirez * same size to the same set of random values. */
1365d55474e5Santirez for (i = 0; i < HLL_REGISTERS; i++) {
1366d55474e5Santirez unsigned int r = rand() & HLL_REGISTER_MAX;
1367552eb540Santirez
1368552eb540Santirez bytecounters[i] = r;
13698ea5b46dSantirez HLL_DENSE_SET_REGISTER(hdr->registers,i,r);
1370552eb540Santirez }
1371552eb540Santirez /* Check that we are able to retrieve the same values. */
1372d55474e5Santirez for (i = 0; i < HLL_REGISTERS; i++) {
1373552eb540Santirez unsigned int val;
1374552eb540Santirez
13758ea5b46dSantirez HLL_DENSE_GET_REGISTER(val,hdr->registers,i);
1376552eb540Santirez if (val != bytecounters[i]) {
1377552eb540Santirez addReplyErrorFormat(c,
1378552eb540Santirez "TESTFAILED Register %d should be %d but is %d",
1379552eb540Santirez i, (int) bytecounters[i], (int) val);
1380552eb540Santirez goto cleanup;
1381552eb540Santirez }
1382552eb540Santirez }
1383552eb540Santirez }
1384552eb540Santirez
1385be9860d0Santirez /* Test 2: approximation error.
1386d541f65dSantirez * The test adds unique elements and check that the estimated value
1387be9860d0Santirez * is always reasonable bounds.
1388be9860d0Santirez *
13890adf4482Santirez * We check that the error is smaller than a few times than the expected
1390be9860d0Santirez * standard error, to make it very unlikely for the test to fail because
1391d541f65dSantirez * of a "bad" run.
1392d541f65dSantirez *
1393d541f65dSantirez * The test is performed with both dense and sparse HLLs at the same
1394d541f65dSantirez * time also verifying that the computed cardinality is the same. */
13958ea5b46dSantirez memset(hdr->registers,0,HLL_DENSE_SIZE-HLL_HDR_SIZE);
1396d541f65dSantirez o = createHLLObject();
1397d55474e5Santirez double relerr = 1.04/sqrt(HLL_REGISTERS);
1398d541f65dSantirez int64_t checkpoint = 1;
1399be9860d0Santirez uint64_t seed = (uint64_t)rand() | (uint64_t)rand() << 32;
1400be9860d0Santirez uint64_t ele;
1401be9860d0Santirez for (j = 1; j <= 10000000; j++) {
1402be9860d0Santirez ele = j ^ seed;
14038ea5b46dSantirez hllDenseAdd(hdr->registers,(unsigned char*)&ele,sizeof(ele));
1404d541f65dSantirez hllAdd(o,(unsigned char*)&ele,sizeof(ele));
1405d541f65dSantirez
1406d541f65dSantirez /* Make sure that for small cardinalities we use sparse
1407d541f65dSantirez * encoding. */
1408402110f9Santirez if (j == checkpoint && j < server.hll_sparse_max_bytes/2) {
1409d541f65dSantirez hdr2 = o->ptr;
1410d541f65dSantirez if (hdr2->encoding != HLL_SPARSE) {
1411d541f65dSantirez addReplyError(c, "TESTFAILED sparse encoding not used");
1412d541f65dSantirez goto cleanup;
1413d541f65dSantirez }
1414d541f65dSantirez }
1415d541f65dSantirez
1416d541f65dSantirez /* Check that dense and sparse representations agree. */
1417d541f65dSantirez if (j == checkpoint && hllCount(hdr,NULL) != hllCount(o->ptr,NULL)) {
1418d541f65dSantirez addReplyError(c, "TESTFAILED dense/sparse disagree");
1419d541f65dSantirez goto cleanup;
1420d541f65dSantirez }
1421d541f65dSantirez
1422d541f65dSantirez /* Check error. */
1423be9860d0Santirez if (j == checkpoint) {
1424681bf746Santirez int64_t abserr = checkpoint - (int64_t)hllCount(hdr,NULL);
14250adf4482Santirez uint64_t maxerr = ceil(relerr*6*checkpoint);
14260adf4482Santirez
14270adf4482Santirez /* Adjust the max error we expect for cardinality 10
14280adf4482Santirez * since from time to time it is statistically likely to get
14290adf4482Santirez * much higher error due to collision, resulting into a false
14300adf4482Santirez * positive. */
14310adf4482Santirez if (j == 10) maxerr = 1;
14320adf4482Santirez
1433be9860d0Santirez if (abserr < 0) abserr = -abserr;
1434edca2b14Santirez if (abserr > (int64_t)maxerr) {
1435be9860d0Santirez addReplyErrorFormat(c,
1436be9860d0Santirez "TESTFAILED Too big error. card:%llu abserr:%llu",
1437be9860d0Santirez (unsigned long long) checkpoint,
1438be9860d0Santirez (unsigned long long) abserr);
1439be9860d0Santirez goto cleanup;
1440be9860d0Santirez }
1441be9860d0Santirez checkpoint *= 10;
1442be9860d0Santirez }
1443be9860d0Santirez }
1444be9860d0Santirez
1445552eb540Santirez /* Success! */
1446552eb540Santirez addReply(c,shared.ok);
1447552eb540Santirez
1448552eb540Santirez cleanup:
1449552eb540Santirez sdsfree(bitcounters);
1450d541f65dSantirez if (o) decrRefCount(o);
1451552eb540Santirez }
1452aaaed66cSantirez
1453261da523Santirez /* PFDEBUG <subcommand> <key> ... args ...
1454261da523Santirez * Different debugging related operations about the HLL implementation. */
pfdebugCommand(client * c)1455554bd0e7Santirez void pfdebugCommand(client *c) {
1456261da523Santirez char *cmd = c->argv[1]->ptr;
1457d55474e5Santirez struct hllhdr *hdr;
1458261da523Santirez robj *o;
1459aaaed66cSantirez int j;
1460aaaed66cSantirez
146106e76bc3Santirez o = lookupKeyWrite(c->db,c->argv[2]);
1462aaaed66cSantirez if (o == NULL) {
1463aaaed66cSantirez addReplyError(c,"The specified key does not exist");
1464aaaed66cSantirez return;
1465261da523Santirez }
146640eb548aSantirez if (isHLLObjectOrReply(c,o) != C_OK) return;
1467261da523Santirez o = dbUnshareStringValue(c->db,c->argv[2],o);
1468d55474e5Santirez hdr = o->ptr;
1469261da523Santirez
1470261da523Santirez /* PFDEBUG GETREG <key> */
1471261da523Santirez if (!strcasecmp(cmd,"getreg")) {
1472261da523Santirez if (c->argc != 3) goto arityerr;
1473261da523Santirez
14743bc35f9cSantirez if (hdr->encoding == HLL_SPARSE) {
147540eb548aSantirez if (hllSparseToDense(o) == C_ERR) {
14768e8f8189Santirez addReplySds(c,sdsnew(invalid_hll_err));
1477b7571b74Santirez return;
1478b7571b74Santirez }
14793bc35f9cSantirez server.dirty++; /* Force propagation on encoding change. */
14803bc35f9cSantirez }
14811ee18db9Santirez
1482b7571b74Santirez hdr = o->ptr;
14831ee18db9Santirez addReplyMultiBulkLen(c,HLL_REGISTERS);
1484d55474e5Santirez for (j = 0; j < HLL_REGISTERS; j++) {
1485aaaed66cSantirez uint8_t val;
1486aaaed66cSantirez
14871efc1e05Santirez HLL_DENSE_GET_REGISTER(val,hdr->registers,j);
1488aaaed66cSantirez addReplyLongLong(c,val);
1489aaaed66cSantirez }
1490f9dc3cb0Santirez }
1491f9dc3cb0Santirez /* PFDEBUG DECODE <key> */
1492f9dc3cb0Santirez else if (!strcasecmp(cmd,"decode")) {
1493f9dc3cb0Santirez if (c->argc != 3) goto arityerr;
1494f9dc3cb0Santirez
1495f9dc3cb0Santirez uint8_t *p = o->ptr, *end = p+sdslen(o->ptr);
1496f9dc3cb0Santirez sds decoded = sdsempty();
1497f9dc3cb0Santirez
1498f9dc3cb0Santirez if (hdr->encoding != HLL_SPARSE) {
1499f9dc3cb0Santirez addReplyError(c,"HLL encoding is not sparse");
1500f9dc3cb0Santirez return;
1501f9dc3cb0Santirez }
1502f9dc3cb0Santirez
1503f9dc3cb0Santirez p += HLL_HDR_SIZE;
1504f9dc3cb0Santirez while(p < end) {
1505f9dc3cb0Santirez int runlen, regval;
1506f9dc3cb0Santirez
1507f9dc3cb0Santirez if (HLL_SPARSE_IS_ZERO(p)) {
1508f9dc3cb0Santirez runlen = HLL_SPARSE_ZERO_LEN(p);
1509f9dc3cb0Santirez p++;
1510f9dc3cb0Santirez decoded = sdscatprintf(decoded,"z:%d ",runlen);
1511f9dc3cb0Santirez } else if (HLL_SPARSE_IS_XZERO(p)) {
1512f9dc3cb0Santirez runlen = HLL_SPARSE_XZERO_LEN(p);
1513f9dc3cb0Santirez p += 2;
1514f9dc3cb0Santirez decoded = sdscatprintf(decoded,"Z:%d ",runlen);
1515f9dc3cb0Santirez } else {
1516f9dc3cb0Santirez runlen = HLL_SPARSE_VAL_LEN(p);
1517f9dc3cb0Santirez regval = HLL_SPARSE_VAL_VALUE(p);
1518f9dc3cb0Santirez p++;
1519f9dc3cb0Santirez decoded = sdscatprintf(decoded,"v:%d,%d ",regval,runlen);
1520f9dc3cb0Santirez }
1521f9dc3cb0Santirez }
1522f9dc3cb0Santirez decoded = sdstrim(decoded," ");
1523f9dc3cb0Santirez addReplyBulkCBuffer(c,decoded,sdslen(decoded));
1524f9dc3cb0Santirez sdsfree(decoded);
1525dde8dff7Santirez }
1526dde8dff7Santirez /* PFDEBUG ENCODING <key> */
1527dde8dff7Santirez else if (!strcasecmp(cmd,"encoding")) {
1528dde8dff7Santirez char *encodingstr[2] = {"dense","sparse"};
1529dde8dff7Santirez if (c->argc != 3) goto arityerr;
1530dde8dff7Santirez
1531dde8dff7Santirez addReplyStatus(c,encodingstr[hdr->encoding]);
15320bbdaca6Santirez }
15330bbdaca6Santirez /* PFDEBUG TODENSE <key> */
15340bbdaca6Santirez else if (!strcasecmp(cmd,"todense")) {
15350bbdaca6Santirez int conv = 0;
15360bbdaca6Santirez if (c->argc != 3) goto arityerr;
15370bbdaca6Santirez
15380bbdaca6Santirez if (hdr->encoding == HLL_SPARSE) {
153940eb548aSantirez if (hllSparseToDense(o) == C_ERR) {
15408e8f8189Santirez addReplySds(c,sdsnew(invalid_hll_err));
15410bbdaca6Santirez return;
15420bbdaca6Santirez }
15430bbdaca6Santirez conv = 1;
15440bbdaca6Santirez server.dirty++; /* Force propagation on encoding change. */
15450bbdaca6Santirez }
15460bbdaca6Santirez addReply(c,conv ? shared.cone : shared.czero);
1547261da523Santirez } else {
1548261da523Santirez addReplyErrorFormat(c,"Unknown PFDEBUG subcommand '%s'", cmd);
1549aaaed66cSantirez }
1550261da523Santirez return;
1551261da523Santirez
1552261da523Santirez arityerr:
1553261da523Santirez addReplyErrorFormat(c,
1554261da523Santirez "Wrong number of arguments for the '%s' subcommand",cmd);
1555aaaed66cSantirez }
1556261da523Santirez
1557