GCC Code Coverage Report


Directory: src/gate/
File: src/gate/encode/blockciphers.c
Date: 2025-09-14 13:10:38
Exec Total Coverage
Lines: 365 387 94.3%
Functions: 35 35 100.0%
Branches: 146 222 65.8%

Line Branch Exec Source
1 /* GATE PROJECT LICENSE:
2 +----------------------------------------------------------------------------+
3 | Copyright(c) 2018-2025, Stefan Meislinger <sm@opengate.at> |
4 | All rights reserved. |
5 | |
6 | Redistribution and use in source and binary forms, with or without |
7 | modification, are permitted provided that the following conditions are met:|
8 | |
9 | 1. Redistributions of source code must retain the above copyright notice, |
10 | this list of conditions and the following disclaimer. |
11 | 2. Redistributions in binary form must reproduce the above copyright |
12 | notice, this list of conditions and the following disclaimer in the |
13 | documentation and/or other materials provided with the distribution. |
14 | |
15 | THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS"|
16 | AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE |
17 | IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE |
18 | ARE DISCLAIMED.IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE |
19 | LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR |
20 | CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF |
21 | SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS |
22 | INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN |
23 | CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) |
24 | ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF |
25 | THE POSSIBILITY OF SUCH DAMAGE. |
26 +----------------------------------------------------------------------------+
27 */
28
29 #include <gate/encode/blockciphers.h>
30 #include <gate/results.h>
31
32 /* P init values */
33 static gate_uint32_t const blowfish_init_p[18] =
34 {
35 0x243f6a88, 0x85a308d3, 0x13198a2e, 0x03707344, 0xa4093822, 0x299f31d0, 0x082efa98, 0xec4e6c89,
36 0x452821e6, 0x38d01377, 0xbe5466cf, 0x34e90c6c, 0xc0ac29b7, 0xc97c50dd, 0x3f84d5b5, 0xb5470917,
37 0x9216d5d9, 0x8979fb1b
38 };
39
40 /* S init values */
41 static gate_uint32_t const blowfish_init_s[4][256] =
42 {
43 {
44 0xd1310ba6, 0x98dfb5ac, 0x2ffd72db, 0xd01adfb7, 0xb8e1afed, 0x6a267e96, 0xba7c9045, 0xf12c7f99,
45 0x24a19947, 0xb3916cf7, 0x0801f2e2, 0x858efc16, 0x636920d8, 0x71574e69, 0xa458fea3, 0xf4933d7e,
46 0x0d95748f, 0x728eb658, 0x718bcd58, 0x82154aee, 0x7b54a41d, 0xc25a59b5, 0x9c30d539, 0x2af26013,
47 0xc5d1b023, 0x286085f0, 0xca417918, 0xb8db38ef, 0x8e79dcb0, 0x603a180e, 0x6c9e0e8b, 0xb01e8a3e,
48 0xd71577c1, 0xbd314b27, 0x78af2fda, 0x55605c60, 0xe65525f3, 0xaa55ab94, 0x57489862, 0x63e81440,
49 0x55ca396a, 0x2aab10b6, 0xb4cc5c34, 0x1141e8ce, 0xa15486af, 0x7c72e993, 0xb3ee1411, 0x636fbc2a,
50 0x2ba9c55d, 0x741831f6, 0xce5c3e16, 0x9b87931e, 0xafd6ba33, 0x6c24cf5c, 0x7a325381, 0x28958677,
51 0x3b8f4898, 0x6b4bb9af, 0xc4bfe81b, 0x66282193, 0x61d809cc, 0xfb21a991, 0x487cac60, 0x5dec8032,
52 0xef845d5d, 0xe98575b1, 0xdc262302, 0xeb651b88, 0x23893e81, 0xd396acc5, 0x0f6d6ff3, 0x83f44239,
53 0x2e0b4482, 0xa4842004, 0x69c8f04a, 0x9e1f9b5e, 0x21c66842, 0xf6e96c9a, 0x670c9c61, 0xabd388f0,
54 0x6a51a0d2, 0xd8542f68, 0x960fa728, 0xab5133a3, 0x6eef0b6c, 0x137a3be4, 0xba3bf050, 0x7efb2a98,
55 0xa1f1651d, 0x39af0176, 0x66ca593e, 0x82430e88, 0x8cee8619, 0x456f9fb4, 0x7d84a5c3, 0x3b8b5ebe,
56 0xe06f75d8, 0x85c12073, 0x401a449f, 0x56c16aa6, 0x4ed3aa62, 0x363f7706, 0x1bfedf72, 0x429b023d,
57 0x37d0d724, 0xd00a1248, 0xdb0fead3, 0x49f1c09b, 0x075372c9, 0x80991b7b, 0x25d479d8, 0xf6e8def7,
58 0xe3fe501a, 0xb6794c3b, 0x976ce0bd, 0x04c006ba, 0xc1a94fb6, 0x409f60c4, 0x5e5c9ec2, 0x196a2463,
59 0x68fb6faf, 0x3e6c53b5, 0x1339b2eb, 0x3b52ec6f, 0x6dfc511f, 0x9b30952c, 0xcc814544, 0xaf5ebd09,
60 0xbee3d004, 0xde334afd, 0x660f2807, 0x192e4bb3, 0xc0cba857, 0x45c8740f, 0xd20b5f39, 0xb9d3fbdb,
61 0x5579c0bd, 0x1a60320a, 0xd6a100c6, 0x402c7279, 0x679f25fe, 0xfb1fa3cc, 0x8ea5e9f8, 0xdb3222f8,
62 0x3c7516df, 0xfd616b15, 0x2f501ec8, 0xad0552ab, 0x323db5fa, 0xfd238760, 0x53317b48, 0x3e00df82,
63 0x9e5c57bb, 0xca6f8ca0, 0x1a87562e, 0xdf1769db, 0xd542a8f6, 0x287effc3, 0xac6732c6, 0x8c4f5573,
64 0x695b27b0, 0xbbca58c8, 0xe1ffa35d, 0xb8f011a0, 0x10fa3d98, 0xfd2183b8, 0x4afcb56c, 0x2dd1d35b,
65 0x9a53e479, 0xb6f84565, 0xd28e49bc, 0x4bfb9790, 0xe1ddf2da, 0xa4cb7e33, 0x62fb1341, 0xcee4c6e8,
66 0xef20cada, 0x36774c01, 0xd07e9efe, 0x2bf11fb4, 0x95dbda4d, 0xae909198, 0xeaad8e71, 0x6b93d5a0,
67 0xd08ed1d0, 0xafc725e0, 0x8e3c5b2f, 0x8e7594b7, 0x8ff6e2fb, 0xf2122b64, 0x8888b812, 0x900df01c,
68 0x4fad5ea0, 0x688fc31c, 0xd1cff191, 0xb3a8c1ad, 0x2f2f2218, 0xbe0e1777, 0xea752dfe, 0x8b021fa1,
69 0xe5a0cc0f, 0xb56f74e8, 0x18acf3d6, 0xce89e299, 0xb4a84fe0, 0xfd13e0b7, 0x7cc43b81, 0xd2ada8d9,
70 0x165fa266, 0x80957705, 0x93cc7314, 0x211a1477, 0xe6ad2065, 0x77b5fa86, 0xc75442f5, 0xfb9d35cf,
71 0xebcdaf0c, 0x7b3e89a0, 0xd6411bd3, 0xae1e7e49, 0x00250e2d, 0x2071b35e, 0x226800bb, 0x57b8e0af,
72 0x2464369b, 0xf009b91e, 0x5563911d, 0x59dfa6aa, 0x78c14389, 0xd95a537f, 0x207d5ba2, 0x02e5b9c5,
73 0x83260376, 0x6295cfa9, 0x11c81968, 0x4e734a41, 0xb3472dca, 0x7b14a94a, 0x1b510052, 0x9a532915,
74 0xd60f573f, 0xbc9bc6e4, 0x2b60a476, 0x81e67400, 0x08ba6fb5, 0x571be91f, 0xf296ec6b, 0x2a0dd915,
75 0xb6636521, 0xe7b9f9b6, 0xff34052e, 0xc5855664, 0x53b02d5d, 0xa99f8fa1, 0x08ba4799, 0x6e85076a
76 },
77 {
78 0x4b7a70e9, 0xb5b32944, 0xdb75092e, 0xc4192623, 0xad6ea6b0, 0x49a7df7d, 0x9cee60b8, 0x8fedb266,
79 0xecaa8c71, 0x699a17ff, 0x5664526c, 0xc2b19ee1, 0x193602a5, 0x75094c29, 0xa0591340, 0xe4183a3e,
80 0x3f54989a, 0x5b429d65, 0x6b8fe4d6, 0x99f73fd6, 0xa1d29c07, 0xefe830f5, 0x4d2d38e6, 0xf0255dc1,
81 0x4cdd2086, 0x8470eb26, 0x6382e9c6, 0x021ecc5e, 0x09686b3f, 0x3ebaefc9, 0x3c971814, 0x6b6a70a1,
82 0x687f3584, 0x52a0e286, 0xb79c5305, 0xaa500737, 0x3e07841c, 0x7fdeae5c, 0x8e7d44ec, 0x5716f2b8,
83 0xb03ada37, 0xf0500c0d, 0xf01c1f04, 0x0200b3ff, 0xae0cf51a, 0x3cb574b2, 0x25837a58, 0xdc0921bd,
84 0xd19113f9, 0x7ca92ff6, 0x94324773, 0x22f54701, 0x3ae5e581, 0x37c2dadc, 0xc8b57634, 0x9af3dda7,
85 0xa9446146, 0x0fd0030e, 0xecc8c73e, 0xa4751e41, 0xe238cd99, 0x3bea0e2f, 0x3280bba1, 0x183eb331,
86 0x4e548b38, 0x4f6db908, 0x6f420d03, 0xf60a04bf, 0x2cb81290, 0x24977c79, 0x5679b072, 0xbcaf89af,
87 0xde9a771f, 0xd9930810, 0xb38bae12, 0xdccf3f2e, 0x5512721f, 0x2e6b7124, 0x501adde6, 0x9f84cd87,
88 0x7a584718, 0x7408da17, 0xbc9f9abc, 0xe94b7d8c, 0xec7aec3a, 0xdb851dfa, 0x63094366, 0xc464c3d2,
89 0xef1c1847, 0x3215d908, 0xdd433b37, 0x24c2ba16, 0x12a14d43, 0x2a65c451, 0x50940002, 0x133ae4dd,
90 0x71dff89e, 0x10314e55, 0x81ac77d6, 0x5f11199b, 0x043556f1, 0xd7a3c76b, 0x3c11183b, 0x5924a509,
91 0xf28fe6ed, 0x97f1fbfa, 0x9ebabf2c, 0x1e153c6e, 0x86e34570, 0xeae96fb1, 0x860e5e0a, 0x5a3e2ab3,
92 0x771fe71c, 0x4e3d06fa, 0x2965dcb9, 0x99e71d0f, 0x803e89d6, 0x5266c825, 0x2e4cc978, 0x9c10b36a,
93 0xc6150eba, 0x94e2ea78, 0xa5fc3c53, 0x1e0a2df4, 0xf2f74ea7, 0x361d2b3d, 0x1939260f, 0x19c27960,
94 0x5223a708, 0xf71312b6, 0xebadfe6e, 0xeac31f66, 0xe3bc4595, 0xa67bc883, 0xb17f37d1, 0x018cff28,
95 0xc332ddef, 0xbe6c5aa5, 0x65582185, 0x68ab9802, 0xeecea50f, 0xdb2f953b, 0x2aef7dad, 0x5b6e2f84,
96 0x1521b628, 0x29076170, 0xecdd4775, 0x619f1510, 0x13cca830, 0xeb61bd96, 0x0334fe1e, 0xaa0363cf,
97 0xb5735c90, 0x4c70a239, 0xd59e9e0b, 0xcbaade14, 0xeecc86bc, 0x60622ca7, 0x9cab5cab, 0xb2f3846e,
98 0x648b1eaf, 0x19bdf0ca, 0xa02369b9, 0x655abb50, 0x40685a32, 0x3c2ab4b3, 0x319ee9d5, 0xc021b8f7,
99 0x9b540b19, 0x875fa099, 0x95f7997e, 0x623d7da8, 0xf837889a, 0x97e32d77, 0x11ed935f, 0x16681281,
100 0x0e358829, 0xc7e61fd6, 0x96dedfa1, 0x7858ba99, 0x57f584a5, 0x1b227263, 0x9b83c3ff, 0x1ac24696,
101 0xcdb30aeb, 0x532e3054, 0x8fd948e4, 0x6dbc3128, 0x58ebf2ef, 0x34c6ffea, 0xfe28ed61, 0xee7c3c73,
102 0x5d4a14d9, 0xe864b7e3, 0x42105d14, 0x203e13e0, 0x45eee2b6, 0xa3aaabea, 0xdb6c4f15, 0xfacb4fd0,
103 0xc742f442, 0xef6abbb5, 0x654f3b1d, 0x41cd2105, 0xd81e799e, 0x86854dc7, 0xe44b476a, 0x3d816250,
104 0xcf62a1f2, 0x5b8d2646, 0xfc8883a0, 0xc1c7b6a3, 0x7f1524c3, 0x69cb7492, 0x47848a0b, 0x5692b285,
105 0x095bbf00, 0xad19489d, 0x1462b174, 0x23820e00, 0x58428d2a, 0x0c55f5ea, 0x1dadf43e, 0x233f7061,
106 0x3372f092, 0x8d937e41, 0xd65fecf1, 0x6c223bdb, 0x7cde3759, 0xcbee7460, 0x4085f2a7, 0xce77326e,
107 0xa6078084, 0x19f8509e, 0xe8efd855, 0x61d99735, 0xa969a7aa, 0xc50c06c2, 0x5a04abfc, 0x800bcadc,
108 0x9e447a2e, 0xc3453484, 0xfdd56705, 0x0e1e9ec9, 0xdb73dbd3, 0x105588cd, 0x675fda79, 0xe3674340,
109 0xc5c43465, 0x713e38d8, 0x3d28f89e, 0xf16dff20, 0x153e21e7, 0x8fb03d4a, 0xe6e39f2b, 0xdb83adf7
110 },
111 {
112 0xe93d5a68, 0x948140f7, 0xf64c261c, 0x94692934, 0x411520f7, 0x7602d4f7, 0xbcf46b2e, 0xd4a20068,
113 0xd4082471, 0x3320f46a, 0x43b7d4b7, 0x500061af, 0x1e39f62e, 0x97244546, 0x14214f74, 0xbf8b8840,
114 0x4d95fc1d, 0x96b591af, 0x70f4ddd3, 0x66a02f45, 0xbfbc09ec, 0x03bd9785, 0x7fac6dd0, 0x31cb8504,
115 0x96eb27b3, 0x55fd3941, 0xda2547e6, 0xabca0a9a, 0x28507825, 0x530429f4, 0x0a2c86da, 0xe9b66dfb,
116 0x68dc1462, 0xd7486900, 0x680ec0a4, 0x27a18dee, 0x4f3ffea2, 0xe887ad8c, 0xb58ce006, 0x7af4d6b6,
117 0xaace1e7c, 0xd3375fec, 0xce78a399, 0x406b2a42, 0x20fe9e35, 0xd9f385b9, 0xee39d7ab, 0x3b124e8b,
118 0x1dc9faf7, 0x4b6d1856, 0x26a36631, 0xeae397b2, 0x3a6efa74, 0xdd5b4332, 0x6841e7f7, 0xca7820fb,
119 0xfb0af54e, 0xd8feb397, 0x454056ac, 0xba489527, 0x55533a3a, 0x20838d87, 0xfe6ba9b7, 0xd096954b,
120 0x55a867bc, 0xa1159a58, 0xcca92963, 0x99e1db33, 0xa62a4a56, 0x3f3125f9, 0x5ef47e1c, 0x9029317c,
121 0xfdf8e802, 0x04272f70, 0x80bb155c, 0x05282ce3, 0x95c11548, 0xe4c66d22, 0x48c1133f, 0xc70f86dc,
122 0x07f9c9ee, 0x41041f0f, 0x404779a4, 0x5d886e17, 0x325f51eb, 0xd59bc0d1, 0xf2bcc18f, 0x41113564,
123 0x257b7834, 0x602a9c60, 0xdff8e8a3, 0x1f636c1b, 0x0e12b4c2, 0x02e1329e, 0xaf664fd1, 0xcad18115,
124 0x6b2395e0, 0x333e92e1, 0x3b240b62, 0xeebeb922, 0x85b2a20e, 0xe6ba0d99, 0xde720c8c, 0x2da2f728,
125 0xd0127845, 0x95b794fd, 0x647d0862, 0xe7ccf5f0, 0x5449a36f, 0x877d48fa, 0xc39dfd27, 0xf33e8d1e,
126 0x0a476341, 0x992eff74, 0x3a6f6eab, 0xf4f8fd37, 0xa812dc60, 0xa1ebddf8, 0x991be14c, 0xdb6e6b0d,
127 0xc67b5510, 0x6d672c37, 0x2765d43b, 0xdcd0e804, 0xf1290dc7, 0xcc00ffa3, 0xb5390f92, 0x690fed0b,
128 0x667b9ffb, 0xcedb7d9c, 0xa091cf0b, 0xd9155ea3, 0xbb132f88, 0x515bad24, 0x7b9479bf, 0x763bd6eb,
129 0x37392eb3, 0xcc115979, 0x8026e297, 0xf42e312d, 0x6842ada7, 0xc66a2b3b, 0x12754ccc, 0x782ef11c,
130 0x6a124237, 0xb79251e7, 0x06a1bbe6, 0x4bfb6350, 0x1a6b1018, 0x11caedfa, 0x3d25bdd8, 0xe2e1c3c9,
131 0x44421659, 0x0a121386, 0xd90cec6e, 0xd5abea2a, 0x64af674e, 0xda86a85f, 0xbebfe988, 0x64e4c3fe,
132 0x9dbc8057, 0xf0f7c086, 0x60787bf8, 0x6003604d, 0xd1fd8346, 0xf6381fb0, 0x7745ae04, 0xd736fccc,
133 0x83426b33, 0xf01eab71, 0xb0804187, 0x3c005e5f, 0x77a057be, 0xbde8ae24, 0x55464299, 0xbf582e61,
134 0x4e58f48f, 0xf2ddfda2, 0xf474ef38, 0x8789bdc2, 0x5366f9c3, 0xc8b38e74, 0xb475f255, 0x46fcd9b9,
135 0x7aeb2661, 0x8b1ddf84, 0x846a0e79, 0x915f95e2, 0x466e598e, 0x20b45770, 0x8cd55591, 0xc902de4c,
136 0xb90bace1, 0xbb8205d0, 0x11a86248, 0x7574a99e, 0xb77f19b6, 0xe0a9dc09, 0x662d09a1, 0xc4324633,
137 0xe85a1f02, 0x09f0be8c, 0x4a99a025, 0x1d6efe10, 0x1ab93d1d, 0x0ba5a4df, 0xa186f20f, 0x2868f169,
138 0xdcb7da83, 0x573906fe, 0xa1e2ce9b, 0x4fcd7f52, 0x50115e01, 0xa70683fa, 0xa002b5c4, 0x0de6d027,
139 0x9af88c27, 0x773f8641, 0xc3604c06, 0x61a806b5, 0xf0177a28, 0xc0f586e0, 0x006058aa, 0x30dc7d62,
140 0x11e69ed7, 0x2338ea63, 0x53c2dd94, 0xc2c21634, 0xbbcbee56, 0x90bcb6de, 0xebfc7da1, 0xce591d76,
141 0x6f05e409, 0x4b7c0188, 0x39720a3d, 0x7c927c24, 0x86e3725f, 0x724d9db9, 0x1ac15bb4, 0xd39eb8fc,
142 0xed545578, 0x08fca5b5, 0xd83d7cd3, 0x4dad0fc4, 0x1e50ef5e, 0xb161e6f8, 0xa28514d9, 0x6c51133c,
143 0x6fd5c7e7, 0x56e14ec4, 0x362abfce, 0xddc6c837, 0xd79a3234, 0x92638212, 0x670efa8e, 0x406000e0
144 },
145 {
146 0x3a39ce37, 0xd3faf5cf, 0xabc27737, 0x5ac52d1b, 0x5cb0679e, 0x4fa33742, 0xd3822740, 0x99bc9bbe,
147 0xd5118e9d, 0xbf0f7315, 0xd62d1c7e, 0xc700c47b, 0xb78c1b6b, 0x21a19045, 0xb26eb1be, 0x6a366eb4,
148 0x5748ab2f, 0xbc946e79, 0xc6a376d2, 0x6549c2c8, 0x530ff8ee, 0x468dde7d, 0xd5730a1d, 0x4cd04dc6,
149 0x2939bbdb, 0xa9ba4650, 0xac9526e8, 0xbe5ee304, 0xa1fad5f0, 0x6a2d519a, 0x63ef8ce2, 0x9a86ee22,
150 0xc089c2b8, 0x43242ef6, 0xa51e03aa, 0x9cf2d0a4, 0x83c061ba, 0x9be96a4d, 0x8fe51550, 0xba645bd6,
151 0x2826a2f9, 0xa73a3ae1, 0x4ba99586, 0xef5562e9, 0xc72fefd3, 0xf752f7da, 0x3f046f69, 0x77fa0a59,
152 0x80e4a915, 0x87b08601, 0x9b09e6ad, 0x3b3ee593, 0xe990fd5a, 0x9e34d797, 0x2cf0b7d9, 0x022b8b51,
153 0x96d5ac3a, 0x017da67d, 0xd1cf3ed6, 0x7c7d2d28, 0x1f9f25cf, 0xadf2b89b, 0x5ad6b472, 0x5a88f54c,
154 0xe029ac71, 0xe019a5e6, 0x47b0acfd, 0xed93fa9b, 0xe8d3c48d, 0x283b57cc, 0xf8d56629, 0x79132e28,
155 0x785f0191, 0xed756055, 0xf7960e44, 0xe3d35e8c, 0x15056dd4, 0x88f46dba, 0x03a16125, 0x0564f0bd,
156 0xc3eb9e15, 0x3c9057a2, 0x97271aec, 0xa93a072a, 0x1b3f6d9b, 0x1e6321f5, 0xf59c66fb, 0x26dcf319,
157 0x7533d928, 0xb155fdf5, 0x03563482, 0x8aba3cbb, 0x28517711, 0xc20ad9f8, 0xabcc5167, 0xccad925f,
158 0x4de81751, 0x3830dc8e, 0x379d5862, 0x9320f991, 0xea7a90c2, 0xfb3e7bce, 0x5121ce64, 0x774fbe32,
159 0xa8b6e37e, 0xc3293d46, 0x48de5369, 0x6413e680, 0xa2ae0810, 0xdd6db224, 0x69852dfd, 0x09072166,
160 0xb39a460a, 0x6445c0dd, 0x586cdecf, 0x1c20c8ae, 0x5bbef7dd, 0x1b588d40, 0xccd2017f, 0x6bb4e3bb,
161 0xdda26a7e, 0x3a59ff45, 0x3e350a44, 0xbcb4cdd5, 0x72eacea8, 0xfa6484bb, 0x8d6612ae, 0xbf3c6f47,
162 0xd29be463, 0x542f5d9e, 0xaec2771b, 0xf64e6370, 0x740e0d8d, 0xe75b1357, 0xf8721671, 0xaf537d5d,
163 0x4040cb08, 0x4eb4e2cc, 0x34d2466a, 0x0115af84, 0xe1b00428, 0x95983a1d, 0x06b89fb4, 0xce6ea048,
164 0x6f3f3b82, 0x3520ab82, 0x011a1d4b, 0x277227f8, 0x611560b1, 0xe7933fdc, 0xbb3a792b, 0x344525bd,
165 0xa08839e1, 0x51ce794b, 0x2f32c9b7, 0xa01fbac9, 0xe01cc87e, 0xbcc7d1f6, 0xcf0111c3, 0xa1e8aac7,
166 0x1a908749, 0xd44fbd9a, 0xd0dadecb, 0xd50ada38, 0x0339c32a, 0xc6913667, 0x8df9317c, 0xe0b12b4f,
167 0xf79e59b7, 0x43f5bb3a, 0xf2d519ff, 0x27d9459c, 0xbf97222c, 0x15e6fc2a, 0x0f91fc71, 0x9b941525,
168 0xfae59361, 0xceb69ceb, 0xc2a86459, 0x12baa8d1, 0xb6c1075e, 0xe3056a0c, 0x10d25065, 0xcb03a442,
169 0xe0ec6e0e, 0x1698db3b, 0x4c98a0be, 0x3278e964, 0x9f1f9532, 0xe0d392df, 0xd3a0342b, 0x8971f21e,
170 0x1b0a7441, 0x4ba3348c, 0xc5be7120, 0xc37632d8, 0xdf359f8d, 0x9b992f2e, 0xe60b6f47, 0x0fe3f11d,
171 0xe54cda54, 0x1edad891, 0xce6279cf, 0xcd3e7e6f, 0x1618b166, 0xfd2c1d05, 0x848fd2c5, 0xf6fb2299,
172 0xf523f357, 0xa6327623, 0x93a83531, 0x56cccd02, 0xacf08162, 0x5a75ebb5, 0x6e163697, 0x88d273cc,
173 0xde966292, 0x81b949d0, 0x4c50901b, 0x71c65614, 0xe6c6c7bd, 0x327a140a, 0x45e1d006, 0xc3f27b9a,
174 0xc9aa53fd, 0x62a80f00, 0xbb25bfe2, 0x35bdd2f6, 0x71126905, 0xb2040222, 0xb6cbcf7c, 0xcd769c2b,
175 0x53113ec0, 0x1640e3d3, 0x38abbd60, 0x2547adf0, 0xba38209c, 0xf746ce76, 0x77afa1c5, 0x20756060,
176 0x85cbfe4e, 0x8ae88dd8, 0x7aaaf9b0, 0x4cf9aa7e, 0x1948c25c, 0x02fb8a8c, 0x01c36ae4, 0xd6ebe1f9,
177 0x90d4f869, 0xa65cdea0, 0x3f09252d, 0xc208e69f, 0xb74e6132, 0xce77e25b, 0x578fdfe3, 0x3ac372e6
178 }
179 };
180
181 76050 static void save_uint32(gate_uint32_t value, unsigned char dst[4])
182 {
183 76050 dst[0] = (unsigned char)((value >> 24) & 0x0ff);
184 76050 dst[1] = (unsigned char)((value >> 16) & 0x0ff);
185 76050 dst[2] = (unsigned char)((value >> 8) & 0x0ff);
186 76050 dst[3] = (unsigned char)((value) & 0x0ff);
187 76050 }
188 17072 static gate_uint32_t load_uint32(unsigned char const src[4])
189 {
190 17072 gate_uint32_t ret =
191 17072 (((gate_uint32_t)src[0]) << 24)
192 17072 | (((gate_uint32_t)src[1]) << 16)
193 17072 | (((gate_uint32_t)src[2]) << 8)
194 17072 | (((gate_uint32_t)src[3]))
195 ;
196 17072 return ret;
197 }
198
199 67456 static gate_uint32_t feistel(gate_blowfish_t const* bf, gate_uint32_t value)
200 {
201 unsigned char ndx[4];
202 gate_uint32_t result;
203 67456 save_uint32(value, ndx);
204 67456 result = ((bf->S[0][ndx[0]] + bf->S[1][ndx[1]]) ^ bf->S[2][ndx[2]]) + bf->S[3][ndx[3]];
205 67456 return result;
206 }
207
208 24 static void block_xor(unsigned char const srcblock_l[4], unsigned char const srcblock_r[4],
209 unsigned char const xorblock_l[4], unsigned char const xorblock_r[4],
210 unsigned char dstblock_l[4], unsigned char dstblock_r[4])
211 {
212 24 gate_uint32_t l = load_uint32(srcblock_l);
213 24 gate_uint32_t r = load_uint32(srcblock_r);
214 24 gate_uint32_t xl = load_uint32(xorblock_l);
215 24 gate_uint32_t xr = load_uint32(xorblock_r);
216 24 save_uint32(l ^ xl, dstblock_l);
217 24 save_uint32(r ^ xr, dstblock_r);
218 24 }
219
220 4192 static void block_encrypt(gate_blowfish_t const* bf,
221 unsigned char const srcblock_l[4], unsigned char const srcblock_r[4],
222 unsigned char* dstblock_l, unsigned char* dstblock_r)
223 {
224 4192 gate_uint32_t l = load_uint32(srcblock_l);
225 4192 gate_uint32_t r = load_uint32(srcblock_r);
226 unsigned int n;
227
228
2/2
✓ Branch 0 taken 33536 times.
✓ Branch 1 taken 4192 times.
37728 for (n = 0; n < 16; n += 2)
229 {
230 33536 l ^= bf->P[n];
231 33536 r ^= feistel(bf, l);
232 33536 r ^= bf->P[n + 1];
233 33536 l ^= feistel(bf, r);
234 }
235 4192 l ^= bf->P[16];
236 4192 r ^= bf->P[17];
237 /* swap l,r */
238 4192 save_uint32(l, &dstblock_r[0]);
239 4192 save_uint32(r, &dstblock_l[0]);
240 4192 }
241 4168 static void block_encrypt2(gate_blowfish_t const* bf, gate_blowfish_block_t const* src, gate_blowfish_block_t* dst)
242 {
243 4168 block_encrypt(bf, src->L, src->R, dst->L, dst->R);
244 4168 }
245
246 24 static void block_decrypt(gate_blowfish_t const* bf,
247 unsigned char const* srcblock_l, unsigned char const* srcblock_r,
248 unsigned char* dstblock_l, unsigned char* dstblock_r)
249 {
250 24 gate_uint32_t l = load_uint32(&srcblock_l[0]);
251 24 gate_uint32_t r = load_uint32(&srcblock_r[0]);
252 unsigned int n;
253
254
2/2
✓ Branch 0 taken 192 times.
✓ Branch 1 taken 24 times.
216 for (n = 16; n > 0; n -= 2)
255 {
256 192 l ^= bf->P[n + 1];
257 192 r ^= feistel(bf, l);
258 192 r ^= bf->P[n];
259 192 l ^= feistel(bf, r);
260 }
261 24 l ^= bf->P[1];
262 24 r ^= bf->P[0];
263
264 /* swap l, r */
265 24 save_uint32(l, &dstblock_r[0]);
266 24 save_uint32(r, &dstblock_l[0]);
267 24 }
268
269 8 gate_result_t gate_blowfish_init(gate_blowfish_t* bf, void const* key, gate_size_t keylength)
270 {
271 unsigned i, j, k;
272 8 unsigned char const* ptrkey = (unsigned char const*)key;
273 gate_uint32_t xorvalue;
274 8 gate_blowfish_block_t block = { { 0, 0, 0, 0 }, { 0, 0, 0, 0 } };
275
276
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 8 times.
8 if (bf == NULL)
277 {
278 return GATE_RESULT_NULLPOINTER;
279 }
280
281
2/4
✓ Branch 0 taken 8 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 8 times.
8 if ((keylength > 0) && (key == NULL))
282 {
283 return GATE_RESULT_NULLPOINTER;
284 }
285
286 /*initialize object P boxes*/
287
2/2
✓ Branch 0 taken 144 times.
✓ Branch 1 taken 8 times.
152 for (i = 0; i < 18; ++i)
288 {
289 144 bf->P[i] = blowfish_init_p[i];
290 }
291 /*initialize object S boxes*/
292
2/2
✓ Branch 0 taken 32 times.
✓ Branch 1 taken 8 times.
40 for (i = 0; i < 4; ++i)
293 {
294
2/2
✓ Branch 0 taken 8192 times.
✓ Branch 1 taken 32 times.
8224 for (j = 0; j < 256; ++j)
295 {
296 8192 bf->S[i][j] = blowfish_init_s[i][j];
297 }
298 }
299
300 /* XOR P with key */
301 8 k = 0;
302
1/2
✓ Branch 0 taken 8 times.
✗ Branch 1 not taken.
8 if (keylength > 0)
303 {
304
2/2
✓ Branch 0 taken 144 times.
✓ Branch 1 taken 8 times.
152 for (i = 0; i < 18; ++i)
305 {
306 144 xorvalue = 0;
307
2/2
✓ Branch 0 taken 576 times.
✓ Branch 1 taken 144 times.
720 for (j = 0; j < 4; ++j)
308 {
309 576 xorvalue = (xorvalue << 8) | (gate_uint32_t)(ptrkey[k]);
310 576 ++k;
311
2/2
✓ Branch 0 taken 16 times.
✓ Branch 1 taken 560 times.
576 if (k >= keylength)
312 {
313 16 k = 0;
314 }
315 }
316 144 bf->P[i] ^= xorvalue;
317 }
318 }
319
320 8 i = 0;
321
2/2
✓ Branch 0 taken 72 times.
✓ Branch 1 taken 8 times.
80 while (i < 18)
322 {
323 72 block_encrypt2(bf, &block, &block);
324 72 bf->P[i] = load_uint32(&block.L[0]);
325 72 ++i;
326 72 bf->P[i] = load_uint32(&block.R[0]);
327 72 ++i;
328 }
329
330
2/2
✓ Branch 0 taken 32 times.
✓ Branch 1 taken 8 times.
40 for (i = 0; i < 4; ++i)
331 {
332 32 k = 0;
333
2/2
✓ Branch 0 taken 4096 times.
✓ Branch 1 taken 32 times.
4128 while (k < 256)
334 {
335 4096 block_encrypt2(bf, &block, &block);
336 4096 bf->S[i][k] = load_uint32(&block.L[0]);
337 4096 ++k;
338 4096 bf->S[i][k] = load_uint32(&block.R[0]);
339 4096 ++k;
340 }
341 }
342
343 8 return GATE_RESULT_OK;
344 }
345
346 9 gate_result_t gate_blowfish_block_init(gate_blowfish_block_t* block, gate_uint32_t l, gate_uint32_t r)
347 {
348
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 9 times.
9 if (block == NULL)
349 {
350 return GATE_RESULT_INVALIDARG;
351 }
352 9 save_uint32(l, block->L);
353 9 save_uint32(r, block->R);
354 9 return GATE_RESULT_OK;
355 }
356
357 40 static void block_load(gate_blowfish_block_t* block, unsigned char const* ptr)
358 {
359 40 gate_mem_copy(&block->L[0], &ptr[0], 4);
360 40 gate_mem_copy(&block->R[0], &ptr[4], 4);
361 40 }
362
363 4 gate_result_t gate_blowfish_block_load(gate_blowfish_block_t* block, void const* buffer, gate_size_t bufferlen)
364 {
365 4 unsigned char const* ptr = (unsigned char const*)buffer;
366
3/6
✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 4 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✓ Branch 5 taken 4 times.
4 if ((block == NULL) || (buffer == NULL) || (bufferlen != 8))
367 {
368 return GATE_RESULT_INVALIDARG;
369 }
370 4 block_load(block, ptr);
371 4 return GATE_RESULT_OK;
372 }
373
374
375 7 gate_result_t gate_blowfish_encrypt(gate_blowfish_t* bf, void const* src, void* dst, gate_size_t length)
376 {
377 7 unsigned char const* ptrsrc = (unsigned char const*)src;
378 7 unsigned char* ptrdst = (unsigned char*)dst;
379 unsigned n;
380
4/8
✓ Branch 0 taken 7 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 7 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 7 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 7 times.
7 if ((bf == NULL) || (src == NULL) || (dst == NULL) || ((length % 8) != 0))
381 {
382 return GATE_RESULT_INVALIDARG;
383 }
384
2/2
✓ Branch 0 taken 12 times.
✓ Branch 1 taken 7 times.
19 for (n = 0; n < length; n += 8)
385 {
386 12 block_encrypt(bf, &ptrsrc[n], &ptrsrc[n + 4], &ptrdst[n], &ptrdst[n + 4]);
387 }
388 7 return GATE_RESULT_OK;
389 }
390
391 1 gate_result_t gate_blowfish_encrypt_stream(gate_blowfish_t* bf, gate_stream_t* instream, gate_stream_t* outstream)
392 {
393 1 gate_result_t result = GATE_RESULT_OK;
394 char buffer[8];
395 gate_size_t buffer_used;
396
1/2
✓ Branch 0 taken 7 times.
✗ Branch 1 not taken.
7 while (GATE_SUCCEEDED(result))
397 {
398 7 result = gate_stream_read_block(instream, buffer, sizeof(buffer), &buffer_used);
399
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 7 times.
7 GATE_BREAK_IF_FAILED(result);
400
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 6 times.
7 if (buffer_used == 0)
401 {
402 /* end of stream reached */
403 1 break;
404 }
405
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 if (buffer_used < sizeof(buffer))
406 {
407 gate_mem_clear(&buffer[buffer_used], sizeof(buffer) - buffer_used);
408 }
409 6 result = gate_blowfish_encrypt(bf, buffer, buffer, sizeof(buffer));
410
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 GATE_BREAK_IF_FAILED(result);
411 6 result = gate_stream_write_block(outstream, buffer, sizeof(buffer), &buffer_used);
412
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 GATE_BREAK_IF_FAILED(result);
413 }
414 1 return result;
415 }
416
417 7 gate_result_t gate_blowfish_decrypt(gate_blowfish_t* bf, void const* src, void* dst, gate_size_t length)
418 {
419 7 unsigned char const* ptrsrc = (unsigned char const*)src;
420 7 unsigned char* ptrdst = (unsigned char*)dst;
421 unsigned n;
422
4/8
✓ Branch 0 taken 7 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 7 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 7 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 7 times.
7 if ((bf == NULL) || (src == NULL) || (dst == NULL) || ((length % 8) != 0))
423 {
424 return GATE_RESULT_INVALIDARG;
425 }
426
2/2
✓ Branch 0 taken 12 times.
✓ Branch 1 taken 7 times.
19 for (n = 0; n < length; n += 8)
427 {
428 12 block_decrypt(bf, &ptrsrc[n], &ptrsrc[n + 4], &ptrdst[n], &ptrdst[n + 4]);
429 }
430 7 return GATE_RESULT_OK;
431 }
432
433 1 gate_result_t gate_blowfish_decrypt_stream(gate_blowfish_t* bf, gate_stream_t* instream, gate_stream_t* outstream)
434 {
435 1 gate_result_t result = GATE_RESULT_OK;
436 char buffer[8];
437 gate_size_t buffer_used;
438
1/2
✓ Branch 0 taken 7 times.
✗ Branch 1 not taken.
7 while (GATE_SUCCEEDED(result))
439 {
440 7 result = gate_stream_read_block(instream, buffer, sizeof(buffer), &buffer_used);
441
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 7 times.
7 GATE_BREAK_IF_FAILED(result);
442
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 6 times.
7 if (buffer_used == 0)
443 {
444 /* end of stream reached */
445 1 break;
446 }
447
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 if (buffer_used < sizeof(buffer))
448 {
449 gate_mem_clear(&buffer[buffer_used], sizeof(buffer) - buffer_used);
450 }
451 6 result = gate_blowfish_decrypt(bf, buffer, buffer, sizeof(buffer));
452
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 GATE_BREAK_IF_FAILED(result);
453 6 result = gate_stream_write_block(outstream, buffer, sizeof(buffer), &buffer_used);
454
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 GATE_BREAK_IF_FAILED(result);
455 }
456 1 return result;
457 }
458
459
460 7 gate_result_t gate_blowfish_encrypt_cbc(gate_blowfish_t* bf, void const* src, void* dst, gate_size_t length, gate_blowfish_block_t* block)
461 {
462 7 unsigned char const* ptrsrc = (unsigned char const*)src;
463 7 unsigned char* ptrdst = (unsigned char*)dst;
464 unsigned n;
465
4/8
✓ Branch 0 taken 7 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 7 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 7 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 7 times.
7 if ((bf == NULL) || (src == NULL) || (dst == NULL) || ((length % 8) != 0))
466 {
467 return GATE_RESULT_INVALIDARG;
468 }
469
2/2
✓ Branch 0 taken 12 times.
✓ Branch 1 taken 7 times.
19 for (n = 0; n < length; n += 8)
470 {
471 12 block_xor(&ptrsrc[n], &ptrsrc[n + 4], &block->L[0], &block->R[0], &ptrdst[n], &ptrdst[n + 4]);
472 12 block_encrypt(bf, &ptrdst[n], &ptrdst[n + 4], &ptrdst[n], &ptrdst[n + 4]);
473 12 block_load(block, &ptrdst[n]);
474 }
475 7 return GATE_RESULT_OK;
476 }
477
478 1 gate_result_t gate_blowfish_encrypt_cbc_stream(gate_blowfish_t* bf, gate_stream_t* instream, gate_stream_t* outstream, gate_blowfish_block_t* block)
479 {
480 1 gate_result_t result = GATE_RESULT_OK;
481 char buffer[8];
482 gate_size_t buffer_used;
483
1/2
✓ Branch 0 taken 7 times.
✗ Branch 1 not taken.
7 while (GATE_SUCCEEDED(result))
484 {
485 7 result = gate_stream_read_block(instream, buffer, sizeof(buffer), &buffer_used);
486
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 7 times.
7 GATE_BREAK_IF_FAILED(result);
487
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 6 times.
7 if (buffer_used == 0)
488 {
489 /* end of stream reached */
490 1 break;
491 }
492
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 if (buffer_used < sizeof(buffer))
493 {
494 gate_mem_clear(&buffer[buffer_used], sizeof(buffer) - buffer_used);
495 }
496 6 result = gate_blowfish_encrypt_cbc(bf, buffer, buffer, sizeof(buffer), block);
497
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 GATE_BREAK_IF_FAILED(result);
498 6 result = gate_stream_write_block(outstream, buffer, sizeof(buffer), &buffer_used);
499
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 GATE_BREAK_IF_FAILED(result);
500 }
501 1 return result;
502 }
503
504 7 gate_result_t gate_blowfish_decrypt_cbc(gate_blowfish_t* bf, void const* src, void* dst, gate_size_t length, gate_blowfish_block_t* block)
505 {
506 7 unsigned char const* ptrsrc = (unsigned char const*)src;
507 7 unsigned char* ptrdst = (unsigned char*)dst;
508 unsigned n;
509 gate_blowfish_block_t tmp;
510
4/8
✓ Branch 0 taken 7 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 7 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 7 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 7 times.
7 if ((bf == NULL) || (src == NULL) || (dst == NULL) || ((length % 8) != 0))
511 {
512 return GATE_RESULT_INVALIDARG;
513 }
514
2/2
✓ Branch 0 taken 12 times.
✓ Branch 1 taken 7 times.
19 for (n = 0; n < length; n += 8)
515 {
516 12 block_load(&tmp, &ptrsrc[n]); /* backup future cbc block */
517 12 block_decrypt(bf, &ptrsrc[n], &ptrsrc[n + 4], &ptrdst[n], &ptrdst[n + 4]);
518 12 block_xor(&ptrdst[n], &ptrdst[n + 4], &block->L[0], &block->R[0], &ptrdst[n], &ptrdst[n + 4]);
519 12 block_load(block, (unsigned char const*)&tmp);
520 //cbfish_block_clone(&tmp, block); /* restore next cbc block */
521 }
522 7 return GATE_RESULT_OK;
523 }
524
525 1 gate_result_t gate_blowfish_decrypt_cbc_stream(gate_blowfish_t* bf, gate_stream_t* instream, gate_stream_t* outstream, gate_blowfish_block_t* block)
526 {
527 1 gate_result_t result = GATE_RESULT_OK;
528 char buffer[8];
529 gate_size_t buffer_used;
530
1/2
✓ Branch 0 taken 7 times.
✗ Branch 1 not taken.
7 while (GATE_SUCCEEDED(result))
531 {
532 7 result = gate_stream_read_block(instream, buffer, sizeof(buffer), &buffer_used);
533
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 7 times.
7 GATE_BREAK_IF_FAILED(result);
534
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 6 times.
7 if (buffer_used == 0)
535 {
536 /* end of stream reached */
537 1 break;
538 }
539
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 if (buffer_used < sizeof(buffer))
540 {
541 gate_mem_clear(&buffer[buffer_used], sizeof(buffer) - buffer_used);
542 }
543 6 result = gate_blowfish_decrypt_cbc(bf, buffer, buffer, sizeof(buffer), block);
544
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 GATE_BREAK_IF_FAILED(result);
545 6 result = gate_stream_write_block(outstream, buffer, sizeof(buffer), &buffer_used);
546
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 GATE_BREAK_IF_FAILED(result);
547 }
548 1 return result;
549 }
550
551
552
553 #define XTEA_DELTA 0x9e3779b9
554 #define XTEA_ROUNDS 32
555
556
557 /* based on code from: https://en.wikipedia.org/wiki/XTEA */
558
559 12 static void xtea_encipher(unsigned int num_rounds, gate_uint32_t v[2], gate_uint32_t const key[4])
560 {
561 unsigned int i;
562 12 gate_uint32_t v0 = v[0];
563 12 gate_uint32_t v1 = v[1];
564 12 gate_uint32_t sum = 0;
565
2/2
✓ Branch 0 taken 384 times.
✓ Branch 1 taken 12 times.
396 for (i = 0; i != num_rounds; ++i)
566 {
567 384 v0 += (((v1 << 4) ^ (v1 >> 5)) + v1) ^ (sum + key[sum & 3]);
568 384 sum += XTEA_DELTA;
569 384 v1 += (((v0 << 4) ^ (v0 >> 5)) + v0) ^ (sum + key[(sum >> 11) & 3]);
570 }
571 12 v[0] = v0;
572 12 v[1] = v1;
573 12 }
574
575 12 static void xtea_decipher(unsigned int num_rounds, gate_uint32_t v[2], gate_uint32_t const key[4])
576 {
577 unsigned int i;
578 12 gate_uint32_t v0 = v[0];
579 12 gate_uint32_t v1 = v[1];
580 12 gate_uint32_t sum = XTEA_DELTA * num_rounds;
581
2/2
✓ Branch 0 taken 384 times.
✓ Branch 1 taken 12 times.
396 for (i = 0; i != num_rounds; ++i)
582 {
583 384 v1 -= (((v0 << 4) ^ (v0 >> 5)) + v0) ^ (sum + key[(sum >> 11) & 3]);
584 384 sum -= XTEA_DELTA;
585 384 v0 -= (((v1 << 4) ^ (v1 >> 5)) + v1) ^ (sum + key[sum & 3]);
586 }
587 12 v[0] = v0;
588 12 v[1] = v1;
589 12 }
590
591 12 gate_result_t gate_xtea_block_encrypt(gate_uint32_t* blocks, gate_size_t blocks_count, gate_uint32_t const key[4])
592 {
593
2/2
✓ Branch 0 taken 12 times.
✓ Branch 1 taken 12 times.
24 while (blocks_count > 1)
594 {
595 12 xtea_encipher(XTEA_ROUNDS, blocks, key);
596 12 blocks += 2;
597 12 blocks_count -= 2;
598 }
599 12 return GATE_RESULT_OK;
600 }
601 12 gate_result_t gate_xtea_block_decrypt(gate_uint32_t* blocks, gate_size_t blocks_count, gate_uint32_t const key[4])
602 {
603
2/2
✓ Branch 0 taken 12 times.
✓ Branch 1 taken 12 times.
24 while (blocks_count > 1)
604 {
605 12 xtea_decipher(XTEA_ROUNDS, blocks, key);
606 12 blocks += 2;
607 12 blocks_count -= 2;
608 }
609 12 return GATE_RESULT_OK;
610 }
611
612 7 gate_result_t gate_xtea_encrypt(unsigned char* data, gate_size_t data_length, unsigned char const key[16])
613 {
614 7 gate_size_t const cnt = data_length / 8;
615 gate_size_t n;
616 gate_uint32_t tmp[2];
617 gate_uint32_t k[4];
618
619 7 k[0] = load_uint32(&key[0]);
620 7 k[1] = load_uint32(&key[4]);
621 7 k[2] = load_uint32(&key[8]);
622 7 k[3] = load_uint32(&key[12]);
623
624
2/4
✓ Branch 0 taken 7 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 7 times.
7 if (!data || ((data_length % 8) != 0))
625 {
626 return GATE_RESULT_INVALIDINPUT;
627 }
628
2/2
✓ Branch 0 taken 12 times.
✓ Branch 1 taken 7 times.
19 for (n = 0; n != cnt; ++n)
629 {
630 12 tmp[0] = load_uint32(&data[n * 8]);
631 12 tmp[1] = load_uint32(&data[n * 8 + 4]);
632 12 gate_xtea_block_encrypt(tmp, 2, k);
633 12 save_uint32(tmp[0], &data[n * 8]);
634 12 save_uint32(tmp[1], &data[n * 8 + 4]);
635 }
636 7 return GATE_RESULT_OK;
637 }
638 7 gate_result_t gate_xtea_decrypt(unsigned char* data, gate_size_t data_length, unsigned char const key[16])
639 {
640 7 gate_size_t const cnt = data_length / 8;
641 gate_size_t n;
642 gate_uint32_t tmp[2];
643 gate_uint32_t k[4];
644
645 7 k[0] = load_uint32(&key[0]);
646 7 k[1] = load_uint32(&key[4]);
647 7 k[2] = load_uint32(&key[8]);
648 7 k[3] = load_uint32(&key[12]);
649
650
2/4
✓ Branch 0 taken 7 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 7 times.
7 if (!data || ((data_length % 8) != 0))
651 {
652 return GATE_RESULT_INVALIDINPUT;
653 }
654
2/2
✓ Branch 0 taken 12 times.
✓ Branch 1 taken 7 times.
19 for (n = 0; n != cnt; ++n)
655 {
656 12 tmp[0] = load_uint32(&data[n * 8]);
657 12 tmp[1] = load_uint32(&data[n * 8 + 4]);
658 12 gate_xtea_block_decrypt(tmp, 2, k);
659 12 save_uint32(tmp[0], &data[n * 8]);
660 12 save_uint32(tmp[1], &data[n * 8 + 4]);
661 }
662 7 return GATE_RESULT_OK;
663 }
664
665 1 gate_result_t gate_xtea_encrypt_stream(gate_stream_t* instream, gate_stream_t* outstream, unsigned char const key[16])
666 {
667 1 gate_result_t result = GATE_RESULT_OK;
668 char buffer[8];
669 gate_size_t buffer_used;
670
1/2
✓ Branch 0 taken 7 times.
✗ Branch 1 not taken.
7 while (GATE_SUCCEEDED(result))
671 {
672 7 result = gate_stream_read_block(instream, buffer, sizeof(buffer), &buffer_used);
673
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 7 times.
7 GATE_BREAK_IF_FAILED(result);
674
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 6 times.
7 if (buffer_used == 0)
675 {
676 /* end of stream reached */
677 1 break;
678 }
679
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 if (buffer_used < sizeof(buffer))
680 {
681 gate_mem_clear(&buffer[buffer_used], sizeof(buffer) - buffer_used);
682 }
683 6 result = gate_xtea_encrypt((unsigned char*)buffer, sizeof(buffer), key);
684
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 GATE_BREAK_IF_FAILED(result);
685 6 result = gate_stream_write_block(outstream, buffer, sizeof(buffer), &buffer_used);
686
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 GATE_BREAK_IF_FAILED(result);
687 }
688 1 return result;
689 }
690
691 1 gate_result_t gate_xtea_decrypt_stream(gate_stream_t* instream, gate_stream_t* outstream, unsigned char const key[16])
692 {
693 1 gate_result_t result = GATE_RESULT_OK;
694 char buffer[8];
695 gate_size_t buffer_used;
696
1/2
✓ Branch 0 taken 7 times.
✗ Branch 1 not taken.
7 while (GATE_SUCCEEDED(result))
697 {
698 7 result = gate_stream_read_block(instream, buffer, sizeof(buffer), &buffer_used);
699
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 7 times.
7 GATE_BREAK_IF_FAILED(result);
700
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 6 times.
7 if (buffer_used == 0)
701 {
702 /* end of stream reached */
703 1 break;
704 }
705
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 if (buffer_used < sizeof(buffer))
706 {
707 gate_mem_clear(&buffer[buffer_used], sizeof(buffer) - buffer_used);
708 }
709 6 result = gate_xtea_decrypt((unsigned char*)buffer, sizeof(buffer), key);
710
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 GATE_BREAK_IF_FAILED(result);
711 6 result = gate_stream_write_block(outstream, buffer, sizeof(buffer), &buffer_used);
712
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 GATE_BREAK_IF_FAILED(result);
713 }
714 1 return result;
715 }
716
717
718
719
720 /* based on https://en.wikipedia.org/wiki/XXTEA */
721 #define MX (((z >> 5 ^ y << 2) + (y >> 3 ^ z << 4)) ^ ((sum ^ y) + (key[(p & 3) ^ e] ^ z)))
722
723 12 static void btea_encrypt(gate_uint32_t* v, gate_size_t n, gate_uint32_t const key[4])
724 {
725 gate_uint32_t y, z, sum;
726 gate_size_t p, rounds, e;
727 12 rounds = 6 + 52 / n;
728 12 sum = 0;
729 12 z = v[n - 1];
730 do
731 {
732 384 sum += XTEA_DELTA;
733 384 e = (sum >> 2) & 3;
734
2/2
✓ Branch 0 taken 384 times.
✓ Branch 1 taken 384 times.
768 for (p = 0; p < n - 1; p++)
735 {
736 384 y = v[p + 1];
737 384 z = v[p] += MX;
738 }
739 384 y = v[0];
740 384 z = v[n - 1] += MX;
741
2/2
✓ Branch 0 taken 372 times.
✓ Branch 1 taken 12 times.
384 } while (--rounds);
742 12 }
743 12 static void btea_decrypt(gate_uint32_t* v, gate_size_t n, gate_uint32_t const key[4])
744 {
745 gate_uint32_t y, z, sum;
746 gate_size_t p, rounds, e;
747 {
748 12 rounds = 6 + 52 / n;
749 12 sum = (gate_uint32_t)rounds * (gate_uint32_t)XTEA_DELTA;
750 12 y = v[0];
751 do
752 {
753 384 e = (sum >> 2) & 3;
754
2/2
✓ Branch 0 taken 384 times.
✓ Branch 1 taken 384 times.
768 for (p = n - 1; p > 0; p--)
755 {
756 384 z = v[p - 1];
757 384 y = v[p] -= MX;
758 }
759 384 z = v[n - 1];
760 384 y = v[0] -= MX;
761 384 sum -= XTEA_DELTA;
762
2/2
✓ Branch 0 taken 372 times.
✓ Branch 1 taken 12 times.
384 } while (--rounds);
763 }
764
765 12 }
766
767
768 12 gate_result_t gate_xxtea_block_encrypt(gate_uint32_t* blocks, gate_size_t blocks_count, gate_uint32_t const key[4])
769 {
770
2/4
✓ Branch 0 taken 12 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 12 times.
12 if (!blocks || (blocks_count < 2))
771 {
772 return GATE_RESULT_INVALIDINPUT;
773 }
774 12 btea_encrypt(blocks, blocks_count, key);
775 12 return GATE_RESULT_OK;
776 }
777 12 gate_result_t gate_xxtea_block_decrypt(gate_uint32_t* blocks, gate_size_t blocks_count, gate_uint32_t const key[4])
778 {
779
2/4
✓ Branch 0 taken 12 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 12 times.
12 if (!blocks || (blocks_count < 2))
780 {
781 return GATE_RESULT_INVALIDINPUT;
782 }
783 12 btea_decrypt(blocks, blocks_count, key);
784 12 return GATE_RESULT_OK;
785 }
786 7 gate_result_t gate_xxtea_encrypt(unsigned char* data, gate_size_t data_length, unsigned char const key[16])
787 {
788 7 gate_size_t const cnt = data_length / 8;
789 gate_size_t n;
790 gate_uint32_t tmp[2];
791 gate_uint32_t k[4];
792
793 7 k[0] = load_uint32(&key[0]);
794 7 k[1] = load_uint32(&key[4]);
795 7 k[2] = load_uint32(&key[8]);
796 7 k[3] = load_uint32(&key[12]);
797
798
2/4
✓ Branch 0 taken 7 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 7 times.
7 if (!data || ((data_length % 8) != 0))
799 {
800 return GATE_RESULT_INVALIDINPUT;
801 }
802
2/2
✓ Branch 0 taken 12 times.
✓ Branch 1 taken 7 times.
19 for (n = 0; n != cnt; ++n)
803 {
804 12 tmp[0] = load_uint32(&data[n * 8]);
805 12 tmp[1] = load_uint32(&data[n * 8 + 4]);
806 12 gate_xxtea_block_encrypt(tmp, 2, k);
807 12 save_uint32(tmp[0], &data[n * 8]);
808 12 save_uint32(tmp[1], &data[n * 8 + 4]);
809 }
810 7 return GATE_RESULT_OK;
811 }
812 7 gate_result_t gate_xxtea_decrypt(unsigned char* data, gate_size_t data_length, unsigned char const key[16])
813 {
814 7 gate_size_t const cnt = data_length / 8;
815 gate_size_t n;
816 gate_uint32_t tmp[2];
817 gate_uint32_t k[4];
818
819 7 k[0] = load_uint32(&key[0]);
820 7 k[1] = load_uint32(&key[4]);
821 7 k[2] = load_uint32(&key[8]);
822 7 k[3] = load_uint32(&key[12]);
823
824
2/4
✓ Branch 0 taken 7 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 7 times.
7 if (!data || ((data_length % 8) != 0))
825 {
826 return GATE_RESULT_INVALIDINPUT;
827 }
828
2/2
✓ Branch 0 taken 12 times.
✓ Branch 1 taken 7 times.
19 for (n = 0; n != cnt; ++n)
829 {
830 12 tmp[0] = load_uint32(&data[n * 8]);
831 12 tmp[1] = load_uint32(&data[n * 8 + 4]);
832 12 gate_xxtea_block_decrypt(tmp, 2, k);
833 12 save_uint32(tmp[0], &data[n * 8]);
834 12 save_uint32(tmp[1], &data[n * 8 + 4]);
835 }
836 7 return GATE_RESULT_OK;
837 }
838
839 1 gate_result_t gate_xxtea_encrypt_stream(gate_stream_t* instream, gate_stream_t* outstream, unsigned char const key[16])
840 {
841 1 gate_result_t result = GATE_RESULT_OK;
842 char buffer[8];
843 gate_size_t buffer_used;
844
1/2
✓ Branch 0 taken 7 times.
✗ Branch 1 not taken.
7 while (GATE_SUCCEEDED(result))
845 {
846 7 result = gate_stream_read_block(instream, buffer, sizeof(buffer), &buffer_used);
847
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 7 times.
7 GATE_BREAK_IF_FAILED(result);
848
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 6 times.
7 if (buffer_used == 0)
849 {
850 /* end of stream reached */
851 1 break;
852 }
853
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 if (buffer_used < sizeof(buffer))
854 {
855 gate_mem_clear(&buffer[buffer_used], sizeof(buffer) - buffer_used);
856 }
857 6 result = gate_xxtea_encrypt((unsigned char*)buffer, sizeof(buffer), key);
858
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 GATE_BREAK_IF_FAILED(result);
859 6 result = gate_stream_write_block(outstream, buffer, sizeof(buffer), &buffer_used);
860
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 GATE_BREAK_IF_FAILED(result);
861 }
862 1 return result;
863 }
864
865 1 gate_result_t gate_xxtea_decrypt_stream(gate_stream_t* instream, gate_stream_t* outstream, unsigned char const key[16])
866 {
867 1 gate_result_t result = GATE_RESULT_OK;
868 char buffer[8];
869 gate_size_t buffer_used;
870
1/2
✓ Branch 0 taken 7 times.
✗ Branch 1 not taken.
7 while (GATE_SUCCEEDED(result))
871 {
872 7 result = gate_stream_read_block(instream, buffer, sizeof(buffer), &buffer_used);
873
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 7 times.
7 GATE_BREAK_IF_FAILED(result);
874
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 6 times.
7 if (buffer_used == 0)
875 {
876 /* end of stream reached */
877 1 break;
878 }
879
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 if (buffer_used < sizeof(buffer))
880 {
881 gate_mem_clear(&buffer[buffer_used], sizeof(buffer) - buffer_used);
882 }
883 6 result = gate_xxtea_decrypt((unsigned char*)buffer, sizeof(buffer), key);
884
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 GATE_BREAK_IF_FAILED(result);
885 6 result = gate_stream_write_block(outstream, buffer, sizeof(buffer), &buffer_used);
886
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 GATE_BREAK_IF_FAILED(result);
887 }
888 1 return result;
889 }
890