1
Fork 0
mirror of https://github.com/redstrate/Physis.git synced 2025-04-20 11:47:46 +00:00

Reformat code

This commit is contained in:
Joshua Goins 2022-08-16 11:52:07 -04:00
parent c7184cb36f
commit d9e79e563a
27 changed files with 1037 additions and 815 deletions

View file

@ -1,10 +1,11 @@
use std::env;
use criterion::{criterion_group, criterion_main, Criterion};
use physis::sqpack::calculate_hash;
use std::env;
fn reload_repos() {
let game_dir = env::var("FFXIV_GAME_DIR").unwrap();
let mut gamedata = physis::gamedata::GameData::from_existing(format!("{}/game", game_dir).as_str()).unwrap();
let mut gamedata =
physis::gamedata::GameData::from_existing(format!("{}/game", game_dir).as_str()).unwrap();
gamedata.reload_repositories();
}
@ -15,7 +16,8 @@ fn bench_calculate_hash() {
fn fetch_data() {
let game_dir = env::var("FFXIV_GAME_DIR").unwrap();
let mut gamedata = physis::gamedata::GameData::from_existing(format!("{}/game", game_dir).as_str()).unwrap();
let mut gamedata =
physis::gamedata::GameData::from_existing(format!("{}/game", game_dir).as_str()).unwrap();
gamedata.reload_repositories();

View file

@ -1,5 +1,5 @@
use std::io::{Cursor, Write};
use crate::blowfish_constants::{BLOWFISH_P, BLOWFISH_S};
use std::io::{Cursor, Write};
const ROUNDS: usize = 16;
const KEYBITS: u32 = 64u32 >> 3;
@ -69,7 +69,8 @@ impl Blowfish {
let l_bytes: [u8; 4] = padded_data[i..i + 4].try_into().ok()?;
let r_bytes: [u8; 4] = padded_data[i + 4..i + 8].try_into().ok()?;
let (l, r) = self.encrypt_pair(u32::from_le_bytes(l_bytes), u32::from_le_bytes(r_bytes));
let (l, r) =
self.encrypt_pair(u32::from_le_bytes(l_bytes), u32::from_le_bytes(r_bytes));
cursor.write_all(u32::to_le_bytes(l).as_slice()).ok()?;
cursor.write_all(u32::to_le_bytes(r).as_slice()).ok()?;
@ -102,7 +103,8 @@ impl Blowfish {
let l_bytes: [u8; 4] = padded_data[i..i + 4].try_into().ok()?;
let r_bytes: [u8; 4] = padded_data[i + 4..i + 8].try_into().ok()?;
let (l, r) = self.decrypt_pair(u32::from_le_bytes(l_bytes), u32::from_le_bytes(r_bytes));
let (l, r) =
self.decrypt_pair(u32::from_le_bytes(l_bytes), u32::from_le_bytes(r_bytes));
cursor.write_all(u32::to_le_bytes(l).as_slice()).ok()?;
cursor.write_all(u32::to_le_bytes(r).as_slice()).ok()?;

View file

@ -1,188 +1,164 @@
pub const BLOWFISH_P: [u32; 18] = [
0x243f6a88, 0x85a308d3, 0x13198a2e, 0x03707344, 0xa4093822, 0x299f31d0,
0x082efa98, 0xec4e6c89, 0x452821e6, 0x38d01377, 0xbe5466cf, 0x34e90c6c,
0xc0ac29b7, 0xc97c50dd, 0x3f84d5b5, 0xb5470917, 0x9216d5d9, 0x8979fb1b
0x243f6a88, 0x85a308d3, 0x13198a2e, 0x03707344, 0xa4093822, 0x299f31d0, 0x082efa98, 0xec4e6c89,
0x452821e6, 0x38d01377, 0xbe5466cf, 0x34e90c6c, 0xc0ac29b7, 0xc97c50dd, 0x3f84d5b5, 0xb5470917,
0x9216d5d9, 0x8979fb1b,
];
pub const BLOWFISH_S: [[u32; 256]; 4] =
[[
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
pub const BLOWFISH_S: [[u32; 256]; 4] = [
[
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
]
];
[
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,
],
];

View file

@ -1,12 +1,12 @@
use crate::patch::{apply_patch, PatchError};
use std::fs;
use std::path::PathBuf;
use crate::patch::{apply_patch, PatchError};
/// Boot data for FFXIV.
pub struct BootData {
path : String,
path: String,
pub version : String,
pub version: String,
}
fn is_valid(path: &str) -> bool {
@ -36,7 +36,7 @@ impl BootData {
match is_valid(directory) {
true => Some(BootData {
path: directory.parse().unwrap(),
version: fs::read_to_string(format!("{directory}/ffxivboot.ver")).unwrap()
version: fs::read_to_string(format!("{directory}/ffxivboot.ver")).unwrap(),
}),
false => {
println!("Boot data is not valid!");
@ -45,7 +45,7 @@ impl BootData {
}
}
pub fn apply_patch(&self, patch_path : &str) -> Result<(), PatchError> {
pub fn apply_patch(&self, patch_path: &str) -> Result<(), PatchError> {
apply_patch(&self.path, patch_path)
}
}

View file

@ -33,7 +33,7 @@ pub fn get_language_code(lang: &Language) -> &'static str {
Language::French => "fr",
Language::ChineseSimplified => "chs",
Language::ChineseTraditional => "cht",
Language::Korean => "ko"
Language::Korean => "ko",
}
}
@ -41,6 +41,5 @@ pub fn get_language_code(lang: &Language) -> &'static str {
#[brw(repr = i16)]
#[derive(Debug, PartialEq)]
pub enum Region {
Global = -1
// TODO: find patch codes for other regions :-)
Global = -1, // TODO: find patch codes for other regions :-)
}

View file

@ -1,11 +1,11 @@
use std::ptr::null_mut;
use libz_sys::*;
use std::ptr::null_mut;
// This module's functions are licensed under MIT from https://github.com/rust-lang/flate2-rs
mod flate2_zallocation {
use std::alloc::{self, Layout};
use std::ffi::c_void;
use std::ptr::null_mut;
use std::alloc::{self, Layout};
const ALIGN: usize = std::mem::align_of::<usize>();
@ -81,7 +81,12 @@ pub fn no_header_decompress(in_data: &mut [u8], out_data: &mut [u8]) -> bool {
reserved: 0,
};
let ret = inflateInit2_(&mut strm, -15, zlibVersion(), core::mem::size_of::<z_stream>() as i32);
let ret = inflateInit2_(
&mut strm,
-15,
zlibVersion(),
core::mem::size_of::<z_stream>() as i32,
);
if ret != Z_OK {
return false;
}

View file

@ -1,11 +1,11 @@
use std::io::{Cursor, Read, Seek, SeekFrom};
use binrw::BinRead;
use binrw::binrw;
use crate::gamedata::MemoryBuffer;
use crate::model::ModelFileHeader;
use std::io::Write;
use binrw::BinWrite;
use crate::sqpack::read_data_block;
use binrw::binrw;
use binrw::BinRead;
use binrw::BinWrite;
use std::io::Write;
use std::io::{Cursor, Read, Seek, SeekFrom};
#[binrw]
#[brw(repr = i32)]
@ -39,7 +39,14 @@ struct TextureLodBlock {
}
#[binrw]
pub struct ModelMemorySizes<T: 'static + binrw::BinRead<Args=()> + binrw::BinWrite<Args=()> + Default + std::ops::AddAssign + Copy> {
pub struct ModelMemorySizes<
T: 'static
+ binrw::BinRead<Args = ()>
+ binrw::BinWrite<Args = ()>
+ Default
+ std::ops::AddAssign
+ Copy,
> {
pub stack_size: T,
pub runtime_size: T,
@ -48,7 +55,15 @@ pub struct ModelMemorySizes<T: 'static + binrw::BinRead<Args=()> + binrw::BinWri
pub index_buffer_size: [T; 3],
}
impl<T: 'static + binrw::BinRead<Args=()> + binrw::BinWrite<Args=()> + Default + std::ops::AddAssign + Copy> ModelMemorySizes<T> {
impl<
T: 'static
+ binrw::BinRead<Args = ()>
+ binrw::BinWrite<Args = ()>
+ Default
+ std::ops::AddAssign
+ Copy,
> ModelMemorySizes<T>
{
pub fn total(&self) -> T {
let mut total: T = T::default();
@ -127,21 +142,26 @@ pub struct Block {
#[br(map = | _ : i32 | if x < 32000 { CompressionMode::Compressed{ compressed_length : x, decompressed_length : y} } else { CompressionMode::Uncompressed { file_size : y } } )]
pub enum CompressionMode {
// we manually map here, because for this case the enum value is also a raw value we want to extract :-)
Compressed { compressed_length: i32, decompressed_length: i32 },
Uncompressed { file_size: i32 },
Compressed {
compressed_length: i32,
decompressed_length: i32,
},
Uncompressed {
file_size: i32,
},
}
#[binrw::binread]
#[derive(Debug)]
pub struct BlockHeader {
#[br(pad_after = 4)]
pub size : u32,
pub size: u32,
#[br(temp)]
x : i32,
x: i32,
#[br(temp)]
y : i32,
y: i32,
#[br(args { x, y })]
#[br(restore_position)]
@ -155,19 +175,14 @@ pub struct DatFile {
// from https://users.rust-lang.org/t/how-best-to-convert-u8-to-u16/57551/4
fn to_u8_slice(slice: &mut [u16]) -> &mut [u8] {
let byte_len = 2 * slice.len();
unsafe {
std::slice::from_raw_parts_mut(
slice.as_mut_ptr().cast::<u8>(),
byte_len,
)
}
unsafe { std::slice::from_raw_parts_mut(slice.as_mut_ptr().cast::<u8>(), byte_len) }
}
impl DatFile {
/// Creates a new reference to an existing dat file.
pub fn from_existing(path: &str) -> Option<DatFile> {
Some(DatFile {
file: std::fs::File::open(path).ok()?
file: std::fs::File::open(path).ok()?,
})
}
@ -178,22 +193,22 @@ impl DatFile {
pub fn read_from_offset(&mut self, offset: u32) -> Option<MemoryBuffer> {
let offset = (offset * 0x80) as u64;
self.file.seek(SeekFrom::Start(offset))
self.file
.seek(SeekFrom::Start(offset))
.expect("Unable to find offset in file.");
let file_info = FileInfo::read(&mut self.file)
.expect("Failed to parse file info.");
let file_info = FileInfo::read(&mut self.file).expect("Failed to parse file info.");
match file_info.file_type {
FileType::Empty => None,
FileType::Standard => self.read_standard_file(offset, &file_info),
FileType::Model => self.read_model_file(offset, &file_info),
FileType::Texture => self.read_texture_file(offset, &file_info)
FileType::Texture => self.read_texture_file(offset, &file_info),
}
}
/// Reads a standard file block.
fn read_standard_file(&mut self, offset : u64, file_info : &FileInfo) -> Option<MemoryBuffer> {
fn read_standard_file(&mut self, offset: u64, file_info: &FileInfo) -> Option<MemoryBuffer> {
let standard_file_info = file_info.standard_info.as_ref().unwrap();
let mut blocks: Vec<Block> = Vec::with_capacity(standard_file_info.num_blocks as usize);
@ -207,15 +222,20 @@ impl DatFile {
let starting_position = offset + (file_info.size as u64);
for i in 0..standard_file_info.num_blocks {
data.append(&mut read_data_block(&mut self.file, starting_position + (blocks[i as usize].offset as u64))
.expect("Failed to read data block."));
data.append(
&mut read_data_block(
&mut self.file,
starting_position + (blocks[i as usize].offset as u64),
)
.expect("Failed to read data block."),
);
}
Some(data)
}
/// Reads a model file block.
fn read_model_file(&mut self, offset : u64, file_info : &FileInfo) -> Option<MemoryBuffer> {
fn read_model_file(&mut self, offset: u64, file_info: &FileInfo) -> Option<MemoryBuffer> {
let mut buffer = Cursor::new(Vec::new());
let model_file_info = file_info.model_info.as_ref().unwrap();
@ -240,7 +260,11 @@ impl DatFile {
// start writing at 0x44
buffer.seek(SeekFrom::Start(0x44)).ok()?;
self.file.seek(SeekFrom::Start(base_offset + (model_file_info.offset.stack_size as u64))).ok()?;
self.file
.seek(SeekFrom::Start(
base_offset + (model_file_info.offset.stack_size as u64),
))
.ok()?;
// read from stack blocks
let mut read_model_blocks = |offset: u64, size: usize| -> Option<u64> {
@ -249,57 +273,93 @@ impl DatFile {
for _ in 0..size {
let last_pos = &self.file.stream_position().unwrap();
let data = read_data_block(&self.file, *last_pos)
.expect("Unable to read block data.");
let data =
read_data_block(&self.file, *last_pos).expect("Unable to read block data.");
// write to buffer
buffer.write_all(data.as_slice()).ok()?;
self.file.seek(SeekFrom::Start(last_pos + (compressed_block_sizes[current_block as usize] as u64))).ok()?;
self.file
.seek(SeekFrom::Start(
last_pos + (compressed_block_sizes[current_block as usize] as u64),
))
.ok()?;
current_block += 1;
}
Some(buffer.position() - stack_start)
};
let stack_size = read_model_blocks(model_file_info.offset.stack_size as u64, model_file_info.num.stack_size as usize).unwrap() as u32;
let runtime_size = read_model_blocks(model_file_info.offset.runtime_size as u64, model_file_info.num.runtime_size as usize).unwrap() as u32;
let stack_size = read_model_blocks(
model_file_info.offset.stack_size as u64,
model_file_info.num.stack_size as usize,
)
.unwrap() as u32;
let runtime_size = read_model_blocks(
model_file_info.offset.runtime_size as u64,
model_file_info.num.runtime_size as usize,
)
.unwrap() as u32;
let mut process_model_data = |i: usize, size: u32, offset: u32, offsets: &mut [u32; 3], data_sizes: &mut [u32; 3]| {
if size != 0 {
let current_vertex_offset = buffer.position() as u32;
if i == 0 || current_vertex_offset != offsets[i - 1] {
offsets[i] = current_vertex_offset;
} else {
offsets[i] = 0;
let mut process_model_data =
|i: usize,
size: u32,
offset: u32,
offsets: &mut [u32; 3],
data_sizes: &mut [u32; 3]| {
if size != 0 {
let current_vertex_offset = buffer.position() as u32;
if i == 0 || current_vertex_offset != offsets[i - 1] {
offsets[i] = current_vertex_offset;
} else {
offsets[i] = 0;
}
self.file
.seek(SeekFrom::Start(base_offset + (offset as u64)))
.ok();
for _ in 0..size {
let last_pos = self.file.stream_position().unwrap();
let data = read_data_block(&self.file, last_pos)
.expect("Unable to read raw model block!");
buffer
.write_all(data.as_slice())
.expect("Unable to write to memory buffer!");
data_sizes[i] += data.len() as u32;
self.file
.seek(SeekFrom::Start(
last_pos + (compressed_block_sizes[current_block] as u64),
))
.expect("Unable to seek properly.");
current_block += 1;
}
}
self.file.seek(SeekFrom::Start(base_offset + (offset as u64))).ok();
for _ in 0..size {
let last_pos = self.file.stream_position().unwrap();
let data = read_data_block(&self.file, last_pos)
.expect("Unable to read raw model block!");
buffer.write_all(data.as_slice()).expect("Unable to write to memory buffer!");
data_sizes[i] += data.len() as u32;
self.file.seek(SeekFrom::Start(last_pos + (compressed_block_sizes[current_block] as u64)))
.expect("Unable to seek properly.");
current_block += 1;
}
}
};
};
// process all 3 lods
for i in 0..3 {
// process vertices
process_model_data(i, model_file_info.num.vertex_buffer_size[i] as u32, model_file_info.offset.vertex_buffer_size[i], &mut vertex_data_offsets, &mut vertex_data_sizes);
process_model_data(
i,
model_file_info.num.vertex_buffer_size[i] as u32,
model_file_info.offset.vertex_buffer_size[i],
&mut vertex_data_offsets,
&mut vertex_data_sizes,
);
// TODO: process edges
// process indices
process_model_data(i, model_file_info.num.index_buffer_size[i] as u32, model_file_info.offset.index_buffer_size[i], &mut index_data_offsets, &mut index_data_sizes);
process_model_data(
i,
model_file_info.num.index_buffer_size[i] as u32,
model_file_info.offset.index_buffer_size[i],
&mut index_data_offsets,
&mut index_data_sizes,
);
}
let header = ModelFileHeader {
@ -325,7 +385,7 @@ impl DatFile {
}
/// Reads a texture file block.
fn read_texture_file(&mut self, offset : u64, file_info : &FileInfo) -> Option<MemoryBuffer> {
fn read_texture_file(&mut self, offset: u64, file_info: &FileInfo) -> Option<MemoryBuffer> {
let mut data: Vec<u8> = Vec::with_capacity(file_info.file_size as usize);
let texture_file_info = file_info.texture_info.as_ref().unwrap();
@ -335,7 +395,9 @@ impl DatFile {
if mipmap_size != 0 {
let original_pos = self.file.stream_position().ok()?;
self.file.seek(SeekFrom::Start(offset + file_info.size as u64)).ok()?;
self.file
.seek(SeekFrom::Start(offset + file_info.size as u64))
.ok()?;
let mut header = vec![0u8; texture_file_info.lods[0].compressed_offset as usize];
self.file.read_exact(&mut header).ok()?;
@ -346,7 +408,10 @@ impl DatFile {
}
for i in 0..texture_file_info.num_blocks {
let mut running_block_total = (texture_file_info.lods[i as usize].compressed_offset as u64) + offset + (file_info.size as u64);
let mut running_block_total = (texture_file_info.lods[i as usize].compressed_offset
as u64)
+ offset
+ (file_info.size as u64);
for _ in 0..texture_file_info.lods[i as usize].block_count {
let original_pos = self.file.stream_position().ok()?;

View file

@ -1,4 +1,4 @@
use crate::race::{Gender, get_race_id, Race, Subrace};
use crate::race::{get_race_id, Gender, Race, Subrace};
#[repr(u8)]
#[derive(Debug, PartialEq)]
@ -35,7 +35,7 @@ pub fn get_slot_abbreviation(slot: Slot) -> &'static str {
Slot::Earring => "ear",
Slot::Neck => "nek",
Slot::Rings => "rir",
Slot::Wrists => "wrs"
Slot::Wrists => "wrs",
}
}
@ -52,7 +52,7 @@ pub fn get_slot_from_id(id: i32) -> Option<Slot> {
10 => Some(Slot::Neck),
12 => Some(Slot::Rings),
11 => Some(Slot::Wrists),
_ => None
_ => None,
}
}
@ -69,25 +69,35 @@ pub fn get_slot_from_abbreviation(abrev: &str) -> Option<Slot> {
"nek" => Some(Slot::Neck),
"rir" => Some(Slot::Rings),
"wrs" => Some(Slot::Wrists),
_ => None
_ => None,
}
}
/// Builds a game path to the equipment specified.
pub fn build_equipment_path(model_id: i32, race: Race, subrace: Subrace, gender: Gender, slot: Slot) -> String {
format!("chara/equipment/e{:04}/model/c{:04}e{:04}_{}.mdl",
model_id,
get_race_id(race, subrace, gender).unwrap(),
model_id,
get_slot_abbreviation(slot))
pub fn build_equipment_path(
model_id: i32,
race: Race,
subrace: Subrace,
gender: Gender,
slot: Slot,
) -> String {
format!(
"chara/equipment/e{:04}/model/c{:04}e{:04}_{}.mdl",
model_id,
get_race_id(race, subrace, gender).unwrap(),
model_id,
get_slot_abbreviation(slot)
)
}
pub fn deconstruct_equipment_path(path : &str) -> Option<(i32, Slot)> {
pub fn deconstruct_equipment_path(path: &str) -> Option<(i32, Slot)> {
let model_id = &path[6..10];
let slot_name = &path[11..14];
Some((model_id.parse().ok()?, get_slot_from_abbreviation(slot_name)?))
Some((
model_id.parse().ok()?,
get_slot_from_abbreviation(slot_name)?,
))
}
#[cfg(test)]
@ -96,6 +106,9 @@ mod tests {
#[test]
fn test_equipment_path() {
assert_eq!(build_equipment_path(0, Race::Hyur, Subrace::Midlander, Gender::Male, Slot::Body), "chara/equipment/e0000/model/c0101e0000_top.mdl");
assert_eq!(
build_equipment_path(0, Race::Hyur, Subrace::Midlander, Gender::Male, Slot::Body),
"chara/equipment/e0000/model/c0101e0000_top.mdl"
);
}
}

View file

@ -1,45 +1,45 @@
use std::io::{Cursor, Seek, SeekFrom};
use crate::gamedata::MemoryBuffer;
use binrw::{binread, Endian, ReadOptions};
use crate::common::Language;
use binrw::BinRead;
use crate::exh::{ColumnDataType, ExcelColumnDefinition, ExcelDataPagination, EXH};
use crate::gamedata::MemoryBuffer;
use binrw::BinRead;
use binrw::{binread, Endian, ReadOptions};
use std::io::{Cursor, Seek, SeekFrom};
#[binread]
#[br(magic = b"EXDF")]
#[br(big)]
struct EXDHeader {
version : u16,
version: u16,
#[br(pad_before = 2)]
#[br(pad_after = 20)]
index_size : u32
index_size: u32,
}
#[binread]
#[br(big)]
struct ExcelDataOffset {
row_id : u32,
pub offset : u32
row_id: u32,
pub offset: u32,
}
#[binread]
#[br(big)]
struct ExcelDataRowHeader {
data_size : u32,
row_count : u16
data_size: u32,
row_count: u16,
}
#[binread]
#[br(big)]
pub struct EXD {
header : EXDHeader,
header: EXDHeader,
#[br(count = header.index_size / core::mem::size_of::<ExcelDataOffset>() as u32)]
data_offsets : Vec<ExcelDataOffset>,
data_offsets: Vec<ExcelDataOffset>,
#[br(ignore)]
pub rows : Vec<ExcelRow>
pub rows: Vec<ExcelRow>,
}
#[derive(Debug)]
@ -54,35 +54,54 @@ pub enum ColumnData {
UInt32(u32),
Float32(f32),
Int64(i64),
UInt64(u64)
UInt64(u64),
}
pub struct ExcelRow {
pub data : Vec<ColumnData>
pub data: Vec<ColumnData>,
}
impl EXD {
fn read_data_raw<Z : BinRead>(cursor: &mut Cursor<&MemoryBuffer>) -> Option<Z> where <Z as BinRead>::Args: Default {
Some(Z::read_options(cursor, &ReadOptions::new(Endian::Big) , <Z as BinRead>::Args::default()).unwrap())
fn read_data_raw<Z: BinRead>(cursor: &mut Cursor<&MemoryBuffer>) -> Option<Z>
where
<Z as BinRead>::Args: Default,
{
Some(
Z::read_options(
cursor,
&ReadOptions::new(Endian::Big),
<Z as BinRead>::Args::default(),
)
.unwrap(),
)
}
fn read_column(cursor: &mut Cursor<&MemoryBuffer>, exh: &EXH, offset : u32, column : &ExcelColumnDefinition) -> Option<ColumnData> {
let mut read_packed_bool = | shift : i32 | -> bool {
fn read_column(
cursor: &mut Cursor<&MemoryBuffer>,
exh: &EXH,
offset: u32,
column: &ExcelColumnDefinition,
) -> Option<ColumnData> {
let mut read_packed_bool = |shift: i32| -> bool {
let bit = 1 << shift;
let bool_data : i32 = Self::read_data_raw(cursor).unwrap();
let bool_data: i32 = Self::read_data_raw(cursor).unwrap();
(bool_data & bit) == bit
};
match column.data_type {
ColumnDataType::String => {
let string_offset : u32 = Self::read_data_raw(cursor).unwrap();
let string_offset: u32 = Self::read_data_raw(cursor).unwrap();
cursor.seek(SeekFrom::Start((offset + exh.header.data_offset as u32 + string_offset).into())).ok()?;
cursor
.seek(SeekFrom::Start(
(offset + exh.header.data_offset as u32 + string_offset).into(),
))
.ok()?;
let mut string = String::new();
let mut byte : u8 = Self::read_data_raw(cursor).unwrap();
let mut byte: u8 = Self::read_data_raw(cursor).unwrap();
while byte != 0 {
string.push(byte as char);
byte = Self::read_data_raw(cursor).unwrap();
@ -92,65 +111,39 @@ impl EXD {
}
ColumnDataType::Bool => {
// FIXME: i believe Bool is int8?
let bool_data : i32 = Self::read_data_raw(cursor).unwrap();
let bool_data: i32 = Self::read_data_raw(cursor).unwrap();
Some(ColumnData::Bool(bool_data == 1))
}
ColumnDataType::Int8 => {
Some(ColumnData::Int8(Self::read_data_raw(cursor).unwrap()))
}
ColumnDataType::UInt8 => {
Some(ColumnData::UInt8(Self::read_data_raw(cursor).unwrap()))
}
ColumnDataType::Int16 => {
Some(ColumnData::Int16(Self::read_data_raw(cursor).unwrap()))
}
ColumnDataType::Int8 => Some(ColumnData::Int8(Self::read_data_raw(cursor).unwrap())),
ColumnDataType::UInt8 => Some(ColumnData::UInt8(Self::read_data_raw(cursor).unwrap())),
ColumnDataType::Int16 => Some(ColumnData::Int16(Self::read_data_raw(cursor).unwrap())),
ColumnDataType::UInt16 => {
Some(ColumnData::UInt16(Self::read_data_raw(cursor).unwrap()))
}
ColumnDataType::Int32 => {
Some(ColumnData::Int32(Self::read_data_raw(cursor).unwrap()))
}
ColumnDataType::Int32 => Some(ColumnData::Int32(Self::read_data_raw(cursor).unwrap())),
ColumnDataType::UInt32 => {
Some(ColumnData::UInt32(Self::read_data_raw(cursor).unwrap()))
}
ColumnDataType::Float32 => {
Some(ColumnData::Float32(Self::read_data_raw(cursor).unwrap()))
}
ColumnDataType::Int64 => {
Some(ColumnData::Int64(Self::read_data_raw(cursor).unwrap()))
}
ColumnDataType::Int64 => Some(ColumnData::Int64(Self::read_data_raw(cursor).unwrap())),
ColumnDataType::UInt64 => {
Some(ColumnData::UInt64(Self::read_data_raw(cursor).unwrap()))
}
ColumnDataType::PackedBool0 => {
Some(ColumnData::Bool(read_packed_bool(0)))
}
ColumnDataType::PackedBool1 => {
Some(ColumnData::Bool(read_packed_bool(1)))
}
ColumnDataType::PackedBool2 => {
Some(ColumnData::Bool(read_packed_bool(2)))
}
ColumnDataType::PackedBool3 => {
Some(ColumnData::Bool(read_packed_bool(3)))
}
ColumnDataType::PackedBool4 => {
Some(ColumnData::Bool(read_packed_bool(4)))
}
ColumnDataType::PackedBool5 => {
Some(ColumnData::Bool(read_packed_bool(5)))
}
ColumnDataType::PackedBool6 => {
Some(ColumnData::Bool(read_packed_bool(6)))
}
ColumnDataType::PackedBool7 => {
Some(ColumnData::Bool(read_packed_bool(7)))
}
ColumnDataType::PackedBool0 => Some(ColumnData::Bool(read_packed_bool(0))),
ColumnDataType::PackedBool1 => Some(ColumnData::Bool(read_packed_bool(1))),
ColumnDataType::PackedBool2 => Some(ColumnData::Bool(read_packed_bool(2))),
ColumnDataType::PackedBool3 => Some(ColumnData::Bool(read_packed_bool(3))),
ColumnDataType::PackedBool4 => Some(ColumnData::Bool(read_packed_bool(4))),
ColumnDataType::PackedBool5 => Some(ColumnData::Bool(read_packed_bool(5))),
ColumnDataType::PackedBool6 => Some(ColumnData::Bool(read_packed_bool(6))),
ColumnDataType::PackedBool7 => Some(ColumnData::Bool(read_packed_bool(7))),
}
}
pub fn from_existing(exh : &EXH, buffer : &MemoryBuffer) -> Option<EXD> {
pub fn from_existing(exh: &EXH, buffer: &MemoryBuffer) -> Option<EXD> {
let mut cursor = Cursor::new(buffer);
let mut exd = EXD::read(&mut cursor).ok()?;
@ -163,13 +156,19 @@ impl EXD {
let header_offset = offset.offset + 6;
let mut read_row = | offset : u32 | -> Option<ExcelRow> {
let mut subrow = ExcelRow { data : Vec::with_capacity(exh.column_definitions.len()) };
let mut read_row = |offset: u32| -> Option<ExcelRow> {
let mut subrow = ExcelRow {
data: Vec::with_capacity(exh.column_definitions.len()),
};
for column in &exh.column_definitions {
cursor.seek(SeekFrom::Start((offset + column.offset as u32).into())).ok()?;
cursor
.seek(SeekFrom::Start((offset + column.offset as u32).into()))
.ok()?;
subrow.data.push(Self::read_column(&mut cursor, exh, offset, column).unwrap());
subrow
.data
.push(Self::read_column(&mut cursor, exh, offset, column).unwrap());
}
Some(subrow)
@ -177,7 +176,8 @@ impl EXD {
if row_header.row_count > 1 {
for i in 0..row_header.row_count {
let subrow_offset = header_offset + (i * exh.header.data_offset + 2 * (i + 1)) as u32;
let subrow_offset =
header_offset + (i * exh.header.data_offset + 2 * (i + 1)) as u32;
exd.rows.push(read_row(subrow_offset).unwrap());
}
@ -191,7 +191,11 @@ impl EXD {
Some(exd)
}
pub fn calculate_filename(name : &str, language : Language, page : &ExcelDataPagination) -> String {
pub fn calculate_filename(
name: &str,
language: Language,
page: &ExcelDataPagination,
) -> String {
use crate::common::get_language_code;
return match language {
@ -201,6 +205,6 @@ impl EXD {
lang => {
format!("{name}_{}_{}.exd", page.start_id, get_language_code(&lang))
}
}
};
}
}

View file

@ -1,23 +1,23 @@
use std::io::Cursor;
use crate::common::Language;
use crate::gamedata::MemoryBuffer;
use binrw::binread;
use crate::common::Language;
use binrw::BinRead;
use std::io::Cursor;
#[binread]
#[br(magic = b"EXHF")]
#[br(big)]
pub struct EXHHeader {
version : u16,
version: u16,
pub(crate) data_offset : u16,
column_count : u16,
page_count : u16,
language_count : u16,
pub(crate) data_offset: u16,
column_count: u16,
page_count: u16,
language_count: u16,
#[br(pad_before = 6)]
#[br(pad_after = 8)]
pub(crate) row_count : u32
#[br(pad_after = 8)]
pub(crate) row_count: u32,
}
#[binread]
@ -48,34 +48,34 @@ pub enum ColumnDataType {
#[binread]
#[br(big)]
pub struct ExcelColumnDefinition {
pub data_type : ColumnDataType,
pub offset : u16,
pub data_type: ColumnDataType,
pub offset: u16,
}
#[binread]
#[br(big)]
pub struct ExcelDataPagination {
pub start_id : u32,
row_count : u32,
pub start_id: u32,
row_count: u32,
}
#[binread]
#[br(big)]
pub struct EXH {
pub header : EXHHeader,
pub header: EXHHeader,
#[br(count = header.column_count)]
pub column_definitions : Vec<ExcelColumnDefinition>,
pub column_definitions: Vec<ExcelColumnDefinition>,
#[br(count = header.page_count)]
pub pages : Vec<ExcelDataPagination>,
pub pages: Vec<ExcelDataPagination>,
#[br(count = header.language_count)]
languages : Vec<Language>
languages: Vec<Language>,
}
impl EXH {
pub fn from_existing(buffer : &MemoryBuffer) -> Option<EXH> {
pub fn from_existing(buffer: &MemoryBuffer) -> Option<EXH> {
EXH::read(&mut Cursor::new(&buffer)).ok()
}
}

View file

@ -1,6 +1,6 @@
use crate::gamedata::MemoryBuffer;
use std::collections::HashMap;
use std::io::{BufRead, BufReader, Cursor};
use crate::gamedata::MemoryBuffer;
/// Represents an Excel List.
pub struct EXL {
@ -13,7 +13,7 @@ pub struct EXL {
impl EXL {
/// Initializes `EXL` from an existing list.
pub fn from_existing(buffer : &MemoryBuffer) -> Option<EXL> {
pub fn from_existing(buffer: &MemoryBuffer) -> Option<EXL> {
let mut exl = Self {
version: 0,
entries: HashMap::new(),
@ -62,9 +62,9 @@ impl EXL {
#[cfg(test)]
mod tests {
use super::*;
use std::fs::read;
use std::path::PathBuf;
use super::*;
fn common_setup() -> EXL {
let mut d = PathBuf::from(env!("CARGO_MANIFEST_DIR"));

View file

@ -1,8 +1,8 @@
use crate::gamedata::MemoryBuffer;
use binrw::binrw;
use binrw::BinRead;
use std::fs::read;
use std::io::Cursor;
use binrw::binrw;
use crate::gamedata::MemoryBuffer;
use binrw::BinRead;
#[binrw]
#[brw(magic = b"FileInfo")]
@ -11,21 +11,21 @@ pub struct FileInfo {
#[brw(pad_before = 16)]
#[br(ignore)]
#[bw(calc = 1024)]
unknown : i32,
unknown: i32,
#[br(temp)]
#[bw(calc = (entries.len() * 96) as i32)]
entries_size : i32,
entries_size: i32,
#[brw(pad_before = 992)]
#[br(count = entries_size / 96)]
entries : Vec<FIINEntry>
entries: Vec<FIINEntry>,
}
#[binrw]
#[derive(Debug)]
pub struct FIINEntry {
file_size : i32,
file_size: i32,
#[brw(pad_before = 4)]
#[br(count = 64)]
@ -36,12 +36,12 @@ pub struct FIINEntry {
#[br(count = 24)]
#[bw(pad_size_to = 24)]
sha1 : Vec<u8>
sha1: Vec<u8>,
}
impl FileInfo {
/// Parses an existing FIIN file.
pub fn from_existing(buffer : &MemoryBuffer) -> Option<FileInfo> {
pub fn from_existing(buffer: &MemoryBuffer) -> Option<FileInfo> {
let mut cursor = Cursor::new(buffer);
FileInfo::read(&mut cursor).ok()
}
@ -51,7 +51,7 @@ impl FileInfo {
/// hashes.
///
/// The new FileInfo structure can then be serialized back into retail-compatible form.
pub fn new(file_names : Vec<&str>) -> Option<FileInfo> {
pub fn new(file_names: Vec<&str>) -> Option<FileInfo> {
let mut entries = vec![];
for name in file_names {
@ -60,12 +60,10 @@ impl FileInfo {
entries.push(FIINEntry {
file_size: file.len() as i32,
file_name: name.to_string(),
sha1: sha1_smol::Sha1::from(file).digest().bytes().to_vec()
sha1: sha1_smol::Sha1::from(file).digest().bytes().to_vec(),
});
}
Some(FileInfo {
entries
})
Some(FileInfo { entries })
}
}

View file

@ -1,6 +1,3 @@
use std::fs;
use std::fs::DirEntry;
use std::path::PathBuf;
use crate::common::Language;
use crate::dat::DatFile;
use crate::exd::EXD;
@ -8,8 +5,11 @@ use crate::exh::EXH;
use crate::exl::EXL;
use crate::index::IndexFile;
use crate::patch::{apply_patch, PatchError};
use crate::repository::{Category, Repository, string_to_category};
use crate::repository::{string_to_category, Category, Repository};
use crate::sqpack::calculate_hash;
use std::fs;
use std::fs::DirEntry;
use std::path::PathBuf;
/// Framework for operating on game data.
pub struct GameData {
@ -83,7 +83,8 @@ impl GameData {
.collect();
for repository_path in repository_paths {
self.repositories.push(Repository::from_existing(repository_path.path().to_str().unwrap()).unwrap());
self.repositories
.push(Repository::from_existing(repository_path.path().to_str().unwrap()).unwrap());
}
self.repositories.sort();
@ -92,23 +93,29 @@ impl GameData {
fn get_index_file(&self, path: &str) -> Option<IndexFile> {
let (repository, category) = self.parse_repository_category(path).unwrap();
let index_path : PathBuf = [self.game_directory.clone(),
let index_path: PathBuf = [
self.game_directory.clone(),
"sqpack".to_string(),
repository.name.clone(),
repository.index_filename(category)]
.iter().collect();
repository.index_filename(category),
]
.iter()
.collect();
IndexFile::from_existing(index_path.to_str()?)
}
fn get_dat_file(&self, path: &str, data_file_id : u32) -> Option<DatFile> {
fn get_dat_file(&self, path: &str, data_file_id: u32) -> Option<DatFile> {
let (repository, category) = self.parse_repository_category(path).unwrap();
let dat_path : PathBuf = [self.game_directory.clone(),
let dat_path: PathBuf = [
self.game_directory.clone(),
"sqpack".to_string(),
repository.name.clone(),
repository.dat_filename(category, data_file_id)]
.iter().collect();
repository.dat_filename(category, data_file_id),
]
.iter()
.collect();
DatFile::from_existing(dat_path.to_str()?)
}
@ -129,7 +136,8 @@ impl GameData {
pub fn exists(&self, path: &str) -> bool {
let hash = calculate_hash(path);
let index_file = self.get_index_file(path)
let index_file = self
.get_index_file(path)
.expect("Failed to find index file.");
index_file.entries.iter().any(|s| s.hash == hash)
@ -161,7 +169,7 @@ impl GameData {
dat_file.read_from_offset(entry.bitfield.offset())
}
None => None
None => None,
}
}
@ -183,7 +191,7 @@ impl GameData {
Some((&self.repositories[0], string_to_category(tokens[0])?))
}
pub fn read_excel_sheet_header(&self, name : &str) -> Option<EXH> {
pub fn read_excel_sheet_header(&self, name: &str) -> Option<EXH> {
let root_exl_file = self.extract("exd/root.exl")?;
let root_exl = EXL::from_existing(&root_exl_file)?;
@ -194,30 +202,39 @@ impl GameData {
let path = format!("exd/{new_filename}.exh");
return EXH::from_existing(&self.extract(&path)?)
return EXH::from_existing(&self.extract(&path)?);
}
}
None
}
pub fn read_excel_sheet(&self, name : &str, exh : &EXH, language : Language, page : usize) -> Option<EXD> {
let exd_path = format!("exd/{}", EXD::calculate_filename(name, language, &exh.pages[page]));
pub fn read_excel_sheet(
&self,
name: &str,
exh: &EXH,
language: Language,
page: usize,
) -> Option<EXD> {
let exd_path = format!(
"exd/{}",
EXD::calculate_filename(name, language, &exh.pages[page])
);
let exd_file = self.extract(&exd_path).unwrap();
EXD::from_existing(exh, &exd_file)
}
pub fn apply_patch(&self, patch_path : &str) -> Result<(), PatchError> {
pub fn apply_patch(&self, patch_path: &str) -> Result<(), PatchError> {
apply_patch(&self.game_directory, patch_path)
}
}
#[cfg(test)]
mod tests {
use crate::repository::Category::EXD;
use super::*;
use crate::repository::Category::EXD;
fn common_setup_data() -> GameData {
let mut d = PathBuf::from(env!("CARGO_MANIFEST_DIR"));
@ -243,8 +260,12 @@ mod tests {
let mut data = common_setup_data();
data.reload_repositories();
assert_eq!(data.parse_repository_category("exd/root.exl").unwrap(),
(&data.repositories[0], EXD));
assert!(data.parse_repository_category("what/some_font.dat").is_none());
assert_eq!(
data.parse_repository_category("exd/root.exl").unwrap(),
(&data.repositories[0], EXD)
);
assert!(data
.parse_repository_category("what/some_font.dat")
.is_none());
}
}

View file

@ -1,7 +1,7 @@
use std::io::SeekFrom;
use binrw::binrw;
use binrw::BinRead;
use bitfield_struct::bitfield;
use std::io::SeekFrom;
#[binrw]
#[brw(repr = u8)]

View file

@ -24,14 +24,14 @@ const BOOT_COMPONENT_FILES: [&str; 18] = [
"icudt.dll",
"libcef.dll",
"license.txt",
"locales/reserved.txt"
"locales/reserved.txt",
];
const GAME_COMPONENT_FILES: [&str; 1] = ["ffxivgame.ver"];
#[repr(C)]
struct Unshield {
_private: [u8; 0]
_private: [u8; 0],
}
#[link(name = "unshield")]
@ -39,16 +39,16 @@ extern "C" {
fn unshield_open(filename: *const c_char) -> *mut Unshield;
fn unshield_close(unshield: *mut Unshield);
fn unshield_set_log_level(level : i32);
fn unshield_set_log_level(level: i32);
fn unshield_file_count(unshield: *mut Unshield) -> i32;
fn unshield_file_name(unshield: *mut Unshield, index : i32) -> *const c_char;
fn unshield_file_save(unshield: *mut Unshield, index : i32, filename: *const c_char) -> bool;
fn unshield_file_name(unshield: *mut Unshield, index: i32) -> *const c_char;
fn unshield_file_save(unshield: *mut Unshield, index: i32, filename: *const c_char) -> bool;
}
pub enum InstallError {
IOFailure,
FFIFailure
FFIFailure,
}
impl From<std::io::Error> for InstallError {
@ -64,7 +64,7 @@ impl From<NulError> for InstallError {
}
/// Installs the game from the provided retail installer.
pub fn install_game(installer_path : &str, game_directory : &str) -> Result<(), InstallError> {
pub fn install_game(installer_path: &str, game_directory: &str) -> Result<(), InstallError> {
let installer_file = fs::read(installer_path).unwrap();
let mut last_position = 0;
@ -72,7 +72,9 @@ pub fn install_game(installer_path : &str, game_directory : &str) -> Result<(),
for filename in FILES_TO_EXTRACT {
let needle = format!("Disk1\\{}", filename);
let position = installer_file.windows(needle.len()).position(|window| window == needle.as_str().as_bytes());
let position = installer_file
.windows(needle.len())
.position(|window| window == needle.as_str().as_bytes());
if position == None {
break;
}
@ -126,8 +128,9 @@ pub fn install_game(installer_path : &str, game_directory : &str) -> Result<(),
}
}
unsafe { unshield_close(unshield); }
unsafe {
unshield_close(unshield);
}
Ok(())
}

View file

@ -15,8 +15,8 @@ pub mod sqpack;
/// Reading and writing SqPack index files.
pub mod index;
mod dat;
mod compression;
mod dat;
pub mod model;
/// All of the races in Eorzea in a nice enum package.

View file

@ -1,15 +1,15 @@
use std::io::{Cursor, Seek, SeekFrom};
use binrw::binread;
use crate::gamedata::MemoryBuffer;
use binrw::binread;
use binrw::BinRead;
use std::io::{Cursor, Seek, SeekFrom};
#[binread]
pub struct ChatLogHeader {
content_size : u32,
file_size : u32,
content_size: u32,
file_size: u32,
#[br(count = file_size - content_size)]
offset_entries : Vec<u32>
offset_entries: Vec<u32>,
}
#[binread]
@ -45,24 +45,24 @@ enum EventChannel {
#[binread]
#[derive(Debug)]
pub struct ChatLogEntry {
timestamp : u32,
filter : EventFilter,
channel : EventChannel,
timestamp: u32,
filter: EventFilter,
channel: EventChannel,
#[br(temp)]
garbage : u32,
garbage: u32,
#[br(ignore)]
message : String
message: String,
}
#[derive(Debug)]
pub struct ChatLog {
entries : Vec<ChatLogEntry>
entries: Vec<ChatLogEntry>,
}
impl ChatLog {
pub fn from_existing(buffer : &MemoryBuffer) -> Option<ChatLog> {
pub fn from_existing(buffer: &MemoryBuffer) -> Option<ChatLog> {
let mut cursor = Cursor::new(buffer);
let header = ChatLogHeader::read(&mut cursor).expect("Cannot parse header.");
@ -80,15 +80,16 @@ impl ChatLog {
let mut entry = ChatLogEntry::read(&mut cursor).expect("Unable to parse log message.");
// TODO: handle the coloring properly, in some way
entry.message = String::from_utf8_lossy(&*buffer[cursor.position() as usize..new_last_offset as usize].to_vec()).to_string();
entry.message = String::from_utf8_lossy(
&*buffer[cursor.position() as usize..new_last_offset as usize].to_vec(),
)
.to_string();
cursor.seek(SeekFrom::Start(new_last_offset)).ok()?;
entries.push(entry);
}
Some(ChatLog {
entries
})
Some(ChatLog { entries })
}
}

View file

@ -1,5 +1,6 @@
/// Creates a enum list of combined race identifiers. For example, (Hyur, Midlander, Male) becomes a new variant called HyurMidlanderMale.
#[macro_export(crate)] macro_rules! define_race_enum {
#[macro_export(crate)]
macro_rules! define_race_enum {
(
pub enum $name:ident {
$(

View file

@ -1,9 +1,9 @@
use std::io::{Cursor, Seek, SeekFrom};
use binrw::binrw;
use crate::gamedata::MemoryBuffer;
use binrw::BinRead;
use binrw::binread;
use binrw::binrw;
use binrw::BinRead;
use half::f16;
use std::io::{Cursor, Seek, SeekFrom};
#[binrw]
#[derive(Debug)]
@ -43,7 +43,7 @@ enum ModelFlags1 {
LightingReflectionEnabled = 0x08,
WavingAnimationDisabled = 0x04,
LightShadowDisabled = 0x02,
ShadowDisabled = 0x01
ShadowDisabled = 0x01,
}
#[binread]
@ -58,196 +58,193 @@ enum ModelFlags2 {
ShadowMaskEnabled = 0x08,
ForceLodRangeEnabled = 0x04,
EdgeGeometryEnabled = 0x02,
Unknown3 = 0x01
Unknown3 = 0x01,
}
#[binread]
#[derive(Debug)]
pub struct ModelHeader {
#[br(pad_after = 2)]
string_count : u16,
string_size : u32,
string_count: u16,
string_size: u32,
#[br(count = string_size)]
strings : Vec<u8>,
strings: Vec<u8>,
radius : f32,
radius: f32,
mesh_count : u16,
attribute_count : u16,
submesh_count : u16,
material_count : u16,
bone_count : u16,
bone_table_count : u16,
shape_count : u16,
shape_mesh_count : u16,
shape_value_count : u16,
mesh_count: u16,
attribute_count: u16,
submesh_count: u16,
material_count: u16,
bone_count: u16,
bone_table_count: u16,
shape_count: u16,
shape_mesh_count: u16,
shape_value_count: u16,
lod_count : u8,
lod_count: u8,
flags1 : ModelFlags1,
flags1: ModelFlags1,
element_id_count : u16,
terrain_shadow_mesh_count : u8,
element_id_count: u16,
terrain_shadow_mesh_count: u8,
#[br(err_context("radius = {}", radius))]
flags2 : ModelFlags2,
flags2: ModelFlags2,
model_clip_out_of_distance : f32,
shadow_clip_out_of_distance : f32,
model_clip_out_of_distance: f32,
shadow_clip_out_of_distance: f32,
#[br(pad_before = 2)]
#[br(pad_after = 2)]
terrain_shadow_submesh_count : u16,
terrain_shadow_submesh_count: u16,
bg_change_material_index : u8,
bg_change_material_index: u8,
#[br(pad_after = 12)]
bg_crest_change_material_index : u8,
bg_crest_change_material_index: u8,
}
#[binread]
#[derive(Debug)]
struct MeshLod {
mesh_index : u16,
mesh_count : u16,
mesh_index: u16,
mesh_count: u16,
model_lod_range : f32,
texture_lod_range : f32,
model_lod_range: f32,
texture_lod_range: f32,
water_mesh_index : u16,
water_mesh_count : u16,
water_mesh_index: u16,
water_mesh_count: u16,
shadow_mesh_index : u16,
shadow_mesh_count : u16,
shadow_mesh_index: u16,
shadow_mesh_count: u16,
terrain_shadow_mesh_count : u16,
terrain_shadow_mesh_index : u16,
terrain_shadow_mesh_count: u16,
terrain_shadow_mesh_index: u16,
vertical_fog_mesh_index : u16,
vertical_fog_mesh_count : u16,
vertical_fog_mesh_index: u16,
vertical_fog_mesh_count: u16,
// unused on win32 according to lumina devs
edge_geometry_size : u32,
edge_geometry_data_offset : u32,
edge_geometry_size: u32,
edge_geometry_data_offset: u32,
#[br(pad_after = 4)]
polygon_count : u32,
polygon_count: u32,
vertex_buffer_size : u32,
index_buffer_size : u32,
vertex_data_offset : u32,
index_data_offset : u32
vertex_buffer_size: u32,
index_buffer_size: u32,
vertex_data_offset: u32,
index_data_offset: u32,
}
#[binread]
#[derive(Debug)]
struct Mesh {
#[br(pad_after = 2)]
vertex_count : u16,
index_count : u32,
vertex_count: u16,
index_count: u32,
material_index : u16,
submesh_index : u16,
submesh_count : u16,
material_index: u16,
submesh_index: u16,
submesh_count: u16,
bone_table_index : u16,
start_index : u32,
bone_table_index: u16,
start_index: u32,
vertex_buffer_offsets : [u32; 3],
vertex_buffer_strides : [u8; 3],
vertex_buffer_offsets: [u32; 3],
vertex_buffer_strides: [u8; 3],
vertex_stream_count : u8
vertex_stream_count: u8,
}
#[binread]
#[derive(Debug)]
struct Submesh {
index_offset : i32,
index_count : i32,
index_offset: i32,
index_count: i32,
attribute_index_mask : u32,
attribute_index_mask: u32,
bone_start_index : u16,
bone_count : u16
bone_start_index: u16,
bone_count: u16,
}
#[binread]
#[derive(Debug)]
struct BoneTable {
bone_indices : [u16; 64],
bone_indices: [u16; 64],
#[br(pad_after = 3)]
bone_count : u8
bone_count: u8,
}
#[binread]
#[derive(Debug)]
struct BoundingBox {
min : [f32; 4],
max : [f32; 4]
min: [f32; 4],
max: [f32; 4],
}
#[binread]
#[derive(Debug)]
struct ModelData {
header : ModelHeader,
header: ModelHeader,
#[br(count = header.element_id_count)]
element_ids : Vec<ElementId>,
element_ids: Vec<ElementId>,
#[br(count = 3)]
lods : Vec<MeshLod>,
lods: Vec<MeshLod>,
#[br(count = header.mesh_count)]
meshes : Vec<Mesh>,
meshes: Vec<Mesh>,
#[br(count = header.attribute_count)]
attribute_name_offsets : Vec<u32>,
attribute_name_offsets: Vec<u32>,
// TODO: implement terrain shadow meshes
#[br(count = header.submesh_count)]
submeshes : Vec<Submesh>,
submeshes: Vec<Submesh>,
// TODO: implement terrain shadow submeshes
#[br(count = header.material_count)]
material_name_offsets : Vec<u32>,
material_name_offsets: Vec<u32>,
#[br(count = header.bone_count)]
bone_name_offsets : Vec<u32>,
bone_name_offsets: Vec<u32>,
#[br(count = header.bone_table_count)]
bone_tables : Vec<BoneTable>,
bone_tables: Vec<BoneTable>,
// TODO: implement shapes
#[br(temp)]
submesh_bone_map_size : u32,
submesh_bone_map_size: u32,
#[br(count = submesh_bone_map_size / 2, err_context("lods = {:#?}", lods))]
submesh_bone_map : Vec<u16>,
submesh_bone_map: Vec<u16>,
#[br(temp)]
padding_amount : u8,
padding_amount: u8,
#[br(pad_before = padding_amount)]
bounding_box : BoundingBox,
model_bounding_box : BoundingBox,
water_bounding_box : BoundingBox,
vertical_fog_bounding_box : BoundingBox,
bounding_box: BoundingBox,
model_bounding_box: BoundingBox,
water_bounding_box: BoundingBox,
vertical_fog_bounding_box: BoundingBox,
#[br(count = header.bone_count)]
bone_bounding_boxes : Vec<BoundingBox>
bone_bounding_boxes: Vec<BoundingBox>,
}
#[binread]
#[derive(Debug)]
struct ElementId {
element_id : u32,
parent_bone_name : u32,
translate : [f32; 3],
rotate : [f32; 3]
element_id: u32,
parent_bone_name: u32,
translate: [f32; 3],
rotate: [f32; 3],
}
#[binread]
@ -260,7 +257,7 @@ enum VertexType {
UInt = 5,
ByteFloat4 = 8,
Half2 = 13,
Half4 = 14
Half4 = 14,
}
#[binread]
@ -280,50 +277,54 @@ enum VertexUsage {
#[binread]
#[derive(Copy, Clone, Debug)]
struct VertexElement {
stream : u8,
offset : u8,
vertex_type : VertexType,
vertex_usage : VertexUsage,
stream: u8,
offset: u8,
vertex_type: VertexType,
vertex_usage: VertexUsage,
#[br(pad_after = 3)]
usage_index: u8
usage_index: u8,
}
#[derive(Clone)]
#[repr(C)]
pub struct Vertex {
pub position : [f32; 3],
pub position: [f32; 3],
pub uv: [f32; 2],
pub normal: [f32; 3],
pub bone_weight: [f32; 4],
pub bone_id : [u8; 4]
pub bone_id: [u8; 4],
}
pub struct Part {
pub vertices : Vec<Vertex>,
pub indices : Vec<u16>
pub vertices: Vec<Vertex>,
pub indices: Vec<u16>,
}
pub struct Lod {
pub parts : Vec<Part>
pub parts: Vec<Part>,
}
pub struct MDL {
pub lods : Vec<Lod>,
pub affected_bone_names : Vec<String>
pub lods: Vec<Lod>,
pub affected_bone_names: Vec<String>,
}
impl MDL {
pub fn from_existing(buffer : &MemoryBuffer) -> Option<MDL> {
pub fn from_existing(buffer: &MemoryBuffer) -> Option<MDL> {
let mut cursor = Cursor::new(buffer);
let model_file_header = ModelFileHeader::read(&mut cursor).unwrap();
#[derive(Clone)]
struct VertexDeclaration {
elements : Vec<VertexElement>
elements: Vec<VertexElement>,
}
let mut vertex_declarations: Vec<VertexDeclaration> = vec![VertexDeclaration{ elements : vec![] }; model_file_header.vertex_declaration_count as usize];
let mut vertex_declarations: Vec<VertexDeclaration> =
vec![
VertexDeclaration { elements: vec![] };
model_file_header.vertex_declaration_count as usize
];
for declaration in &mut vertex_declarations {
let mut element = VertexElement::read(&mut cursor).unwrap();
@ -335,7 +336,7 @@ impl MDL {
if element.stream == 255 {
break;
}
};
}
let to_seek = 17 * 8 - (declaration.elements.len() + 1) * 8;
cursor.seek(SeekFrom::Current(to_seek as i64)).ok()?;
@ -363,7 +364,9 @@ impl MDL {
for i in 0..model.header.lod_count {
let mut parts = vec![];
for j in model.lods[i as usize].mesh_index..model.lods[i as usize].mesh_index + model.lods[i as usize].mesh_count {
for j in model.lods[i as usize].mesh_index
..model.lods[i as usize].mesh_index + model.lods[i as usize].mesh_count
{
let declaration = &vertex_declarations[j as usize];
let vertex_count = model.meshes[j as usize].vertex_count;
@ -372,37 +375,58 @@ impl MDL {
uv: [0.0; 2],
normal: [0.0; 3],
bone_weight: [0.0; 4],
bone_id: [0u8; 4]
bone_id: [0u8; 4],
};
let mut vertices: Vec<Vertex> = vec![default_vertex; vertex_count as usize];
for k in 0..vertex_count {
for element in &declaration.elements {
cursor.seek(SeekFrom::Start((model.lods[i as usize].vertex_data_offset +
model.meshes[j as usize].vertex_buffer_offsets[element.stream as usize] +
element.offset as u32 +
model.meshes[i as usize].vertex_buffer_strides[element.stream as usize] as u32 * k as u32) as u64)).ok()?;
cursor
.seek(SeekFrom::Start(
(model.lods[i as usize].vertex_data_offset
+ model.meshes[j as usize].vertex_buffer_offsets
[element.stream as usize]
+ element.offset as u32
+ model.meshes[i as usize].vertex_buffer_strides
[element.stream as usize]
as u32
* k as u32) as u64,
))
.ok()?;
match element.vertex_usage {
VertexUsage::Position => {
vertices[k as usize].position = <[f32; 3]>::read(&mut cursor).unwrap();
vertices[k as usize].position =
<[f32; 3]>::read(&mut cursor).unwrap();
}
VertexUsage::BlendWeights => {
vertices[k as usize].bone_weight = <[f32; 4]>::read(&mut cursor).unwrap();
vertices[k as usize].bone_weight =
<[f32; 4]>::read(&mut cursor).unwrap();
}
VertexUsage::BlendIndices => {
vertices[k as usize].bone_id = <[u8; 4]>::read(&mut cursor).unwrap();
vertices[k as usize].bone_id =
<[u8; 4]>::read(&mut cursor).unwrap();
}
VertexUsage::Normal => {
// TODO: normals are assumed to be half4
vertices[k as usize].normal[0] = f16::from_bits(<u16 as BinRead>::read(&mut cursor).unwrap()).to_f32();
vertices[k as usize].normal[1] = f16::from_bits(<u16 as BinRead>::read(&mut cursor).unwrap()).to_f32();
vertices[k as usize].normal[2] = f16::from_bits(<u16 as BinRead>::read(&mut cursor).unwrap()).to_f32();
vertices[k as usize].normal[0] =
f16::from_bits(<u16 as BinRead>::read(&mut cursor).unwrap())
.to_f32();
vertices[k as usize].normal[1] =
f16::from_bits(<u16 as BinRead>::read(&mut cursor).unwrap())
.to_f32();
vertices[k as usize].normal[2] =
f16::from_bits(<u16 as BinRead>::read(&mut cursor).unwrap())
.to_f32();
}
VertexUsage::UV => {
vertices[k as usize].uv[0] = f16::from_bits(<u16 as BinRead>::read(&mut cursor).unwrap()).to_f32();
vertices[k as usize].uv[1] = f16::from_bits(<u16 as BinRead>::read(&mut cursor).unwrap()).to_f32();
vertices[k as usize].uv[0] =
f16::from_bits(<u16 as BinRead>::read(&mut cursor).unwrap())
.to_f32();
vertices[k as usize].uv[1] =
f16::from_bits(<u16 as BinRead>::read(&mut cursor).unwrap())
.to_f32();
}
VertexUsage::Tangent2 => {}
VertexUsage::Tangent1 => {}
@ -411,28 +435,30 @@ impl MDL {
}
}
cursor.seek(SeekFrom::Start((model_file_header.index_offsets[i as usize] + (model.meshes[j as usize].start_index * 2)) as u64)).ok()?;
cursor
.seek(SeekFrom::Start(
(model_file_header.index_offsets[i as usize]
+ (model.meshes[j as usize].start_index * 2))
as u64,
))
.ok()?;
// TODO: optimize!
let mut indices : Vec<u16> = Vec::with_capacity(model.meshes[j as usize].index_count as usize);
let mut indices: Vec<u16> =
Vec::with_capacity(model.meshes[j as usize].index_count as usize);
for _ in 0..model.meshes[j as usize].index_count {
indices.push(<u16 as BinRead>::read(&mut cursor).unwrap());
}
parts.push(Part {
vertices,
indices
});
parts.push(Part { vertices, indices });
}
lods.push(Lod {
parts
});
lods.push(Lod { parts });
}
Some(MDL {
lods,
affected_bone_names
affected_bone_names,
})
}
}

View file

@ -1,6 +1,6 @@
use std::io::Cursor;
use crate::gamedata::MemoryBuffer;
use binrw::{binread, BinRead};
use std::io::Cursor;
#[binread]
#[derive(Debug)]
@ -13,7 +13,7 @@ struct MaterialFileHeader {
texture_count: u8,
uv_set_count: u8,
color_set_count: u8,
additional_data_size: u8
additional_data_size: u8,
}
#[binread]
@ -23,7 +23,7 @@ struct MaterialHeader {
shader_key_count: u16,
constant_count: u16,
#[br(pad_after = 4)]
sampler_count: u16
sampler_count: u16,
}
#[binread]
@ -31,28 +31,28 @@ struct MaterialHeader {
struct ColorSet {
name_offset: u16,
#[br(pad_after = 1)]
index: u8
index: u8,
}
#[binread]
#[derive(Debug)]
struct ColorSetInfo {
#[br(count = 256)]
data: Vec<u16>
data: Vec<u16>,
}
#[binread]
#[derive(Debug)]
struct ColorSetDyeInfo {
#[br(count = 16)]
data: Vec<u16>
data: Vec<u16>,
}
#[binread]
#[derive(Debug)]
struct ShaderKey {
category: u32,
value: u32
value: u32,
}
#[binread]
@ -60,7 +60,7 @@ struct ShaderKey {
struct Constant {
constant_id: u32,
value_offset: u16,
value_size: u16
value_size: u16,
}
#[binread]
@ -105,12 +105,12 @@ struct MaterialData {
#[br(count = header.sampler_count)]
samplers: Vec<Sampler>,
#[br(count = header.shader_value_list_size / 4)]
shader_values: Vec<f32>
shader_values: Vec<f32>,
}
#[derive(Debug)]
pub struct Material {
pub texture_paths: Vec<String>
pub texture_paths: Vec<String>,
}
impl Material {
@ -136,8 +136,6 @@ impl Material {
offset += 1;
}
Some(Material {
texture_paths
})
Some(Material { texture_paths })
}
}

View file

@ -1,13 +1,13 @@
use crate::common::Region;
use crate::sqpack::read_data_block_patch;
use binrw::binread;
use binrw::binrw;
use binrw::BinRead;
use core::cmp::min;
use std::fs;
use std::fs::{File, OpenOptions};
use std::io::{Seek, SeekFrom, Write};
use binrw::BinRead;
use binrw::binread;
use binrw::binrw;
use crate::sqpack::read_data_block_patch;
use core::cmp::min;
use std::path::PathBuf;
use crate::common::Region;
#[binread]
#[derive(Debug)]
@ -17,7 +17,7 @@ struct PatchHeader {
#[br(pad_before = 1)]
#[br(pad_after = 4)]
#[br(assert(magic == b"ZIPATCH"))]
magic : Vec<u8>
magic: Vec<u8>,
}
#[derive(BinRead, Debug)]
@ -26,26 +26,35 @@ struct PatchChunk {
size: u32,
chunk_type: ChunkType,
#[br(if(chunk_type != ChunkType::EndOfFile))]
crc32: u32
crc32: u32,
}
#[derive(BinRead, PartialEq, Debug)]
enum ChunkType {
#[br(magic = b"FHDR")] FileHeader(
#[br(magic = b"FHDR")]
FileHeader(
#[br(pad_before = 2)]
#[br(pad_after = 1)]
FileHeaderChunk),
#[br(magic = b"APLY")] ApplyOption(ApplyOptionChunk),
#[br(magic = b"ADIR")] AddDirectory(DirectoryChunk),
#[br(magic = b"DELD")] DeleteDirectory(DirectoryChunk),
#[br(magic = b"SQPK")] Sqpk(SqpkChunk),
#[br(magic = b"EOF_")] EndOfFile,
FileHeaderChunk,
),
#[br(magic = b"APLY")]
ApplyOption(ApplyOptionChunk),
#[br(magic = b"ADIR")]
AddDirectory(DirectoryChunk),
#[br(magic = b"DELD")]
DeleteDirectory(DirectoryChunk),
#[br(magic = b"SQPK")]
Sqpk(SqpkChunk),
#[br(magic = b"EOF_")]
EndOfFile,
}
#[derive(BinRead, PartialEq, Debug)]
enum FileHeaderChunk {
#[br(magic = 2u8)] Version2(FileHeaderChunk2),
#[br(magic = 3u8)] Version3(FileHeaderChunk3)
#[br(magic = 2u8)]
Version2(FileHeaderChunk2),
#[br(magic = 3u8)]
Version3(FileHeaderChunk3),
}
#[derive(BinRead, PartialEq, Debug)]
@ -56,7 +65,7 @@ struct FileHeaderChunk2 {
name: String,
#[br(pad_before = 8)]
depot_hash: u32
depot_hash: u32,
}
#[derive(BinRead, PartialEq, Debug)]
@ -68,19 +77,19 @@ struct FileHeaderChunk3 {
entry_files: u32,
add_directories : u32,
delete_directories : u32,
delete_data_size : u32,
delete_data_size_2 : u32,
minor_version : u32,
repository_name : u32,
commands : u32,
add_directories: u32,
delete_directories: u32,
delete_data_size: u32,
delete_data_size_2: u32,
minor_version: u32,
repository_name: u32,
commands: u32,
sqpk_add_commands: u32,
sqpk_delete_commands: u32,
sqpk_expand_commands: u32,
sqpk_header_commands: u32,
#[br(pad_after = 0xB8)]
sqpk_file_commands: u32
sqpk_file_commands: u32,
}
#[binread]
@ -115,39 +124,49 @@ struct DirectoryChunk {
#[binread]
#[derive(PartialEq, Debug)]
enum SqpkOperation {
#[br(magic = b'A')] AddData(SqpkAddData),
#[br(magic = b'D')] DeleteData(SqpkDeleteData),
#[br(magic = b'E')] ExpandData(SqpkDeleteData),
#[br(magic = b'F')] FileOperation(SqpkFileOperationData),
#[br(magic = b'H')] HeaderUpdate(SqpkHeaderUpdateData),
#[br(magic = b'I')] IndexAddDelete(SqpkIndexData),
#[br(magic = b'X')] PatchInfo(SqpkPatchInfo),
#[br(magic = b'T')] TargetInfo(SqpkTargetInfo),
#[br(magic = b'A')]
AddData(SqpkAddData),
#[br(magic = b'D')]
DeleteData(SqpkDeleteData),
#[br(magic = b'E')]
ExpandData(SqpkDeleteData),
#[br(magic = b'F')]
FileOperation(SqpkFileOperationData),
#[br(magic = b'H')]
HeaderUpdate(SqpkHeaderUpdateData),
#[br(magic = b'I')]
IndexAddDelete(SqpkIndexData),
#[br(magic = b'X')]
PatchInfo(SqpkPatchInfo),
#[br(magic = b'T')]
TargetInfo(SqpkTargetInfo),
}
#[derive(BinRead, PartialEq, Debug)]
enum SqpkIndexCommand {
#[br(magic = b'A')] Add,
#[br(magic = b'D')] Delete
#[br(magic = b'A')]
Add,
#[br(magic = b'D')]
Delete,
}
#[derive(BinRead, PartialEq, Debug)]
#[br(big)]
struct SqpkIndexData {
command : SqpkIndexCommand,
command: SqpkIndexCommand,
#[br(map = | x: u8 | x != 0)]
#[br(pad_after = 1)]
is_synonym : bool,
is_synonym: bool,
main_id : u16,
sub_id : u16,
file_id : u32,
main_id: u16,
sub_id: u16,
file_id: u32,
file_hash : u64,
file_hash: u64,
block_offset : u32,
block_number : u32
block_offset: u32,
block_number: u32,
}
#[derive(BinRead, PartialEq, Debug)]
@ -157,78 +176,86 @@ struct SqpkPatchInfo {
version: u8,
#[br(big)]
install_size : u64
install_size: u64,
}
#[binread]
#[derive(PartialEq, Debug)]
enum SqpkFileOperation {
#[br(magic = b'A')] AddFile,
#[br(magic = b'R')] RemoveAll,
#[br(magic = b'D')] DeleteFile
#[br(magic = b'A')]
AddFile,
#[br(magic = b'R')]
RemoveAll,
#[br(magic = b'D')]
DeleteFile,
}
#[derive(BinRead, PartialEq, Debug)]
#[br(big)]
struct SqpkAddData {
#[br(pad_before = 3)]
main_id : u16,
sub_id : u16,
file_id : u32,
main_id: u16,
sub_id: u16,
file_id: u32,
#[br(map = | x : i32 | x << 7 )]
block_offset : i32,
block_offset: i32,
#[br(map = | x : i32 | x << 7 )]
block_number : i32,
block_number: i32,
#[br(map = | x : i32 | x << 7 )]
block_delete_number : i32,
block_delete_number: i32,
#[br(count = block_number)]
block_data : Vec<u8>
block_data: Vec<u8>,
}
#[derive(BinRead, PartialEq, Debug)]
#[br(big)]
struct SqpkDeleteData {
#[br(pad_before = 3)]
main_id : u16,
sub_id : u16,
file_id : u32,
main_id: u16,
sub_id: u16,
file_id: u32,
#[br(map = | x : i32 | x << 7 )]
block_offset : i32,
block_offset: i32,
#[br(pad_after = 4)]
block_number : i32
block_number: i32,
}
#[binread]
#[derive(PartialEq, Debug)]
enum TargetFileKind {
#[br(magic=b'D')] Dat,
#[br(magic=b'I')] Index
#[br(magic = b'D')]
Dat,
#[br(magic = b'I')]
Index,
}
#[binread]
#[derive(PartialEq, Debug)]
enum TargetHeaderKind {
#[br(magic=b'V')] Version,
#[br(magic=b'I')] Index,
#[br(magic=b'D')] Data
#[br(magic = b'V')]
Version,
#[br(magic = b'I')]
Index,
#[br(magic = b'D')]
Data,
}
#[derive(BinRead, PartialEq, Debug)]
#[br(big)]
struct SqpkHeaderUpdateData {
file_kind : TargetFileKind,
header_kind : TargetHeaderKind,
file_kind: TargetFileKind,
header_kind: TargetHeaderKind,
#[br(pad_before = 1)]
main_id : u16,
sub_id : u16,
file_id : u32,
main_id: u16,
sub_id: u16,
file_id: u32,
#[br(count = 1024)]
header_data : Vec<u8>
header_data: Vec<u8>,
}
#[binread]
@ -238,11 +265,11 @@ struct SqpkFileOperationData {
#[br(pad_after = 2)]
operation: SqpkFileOperation,
offset : i64,
file_size : u64,
offset: i64,
file_size: u64,
#[br(temp)]
path_length : u32,
expansion_id : u32,
path_length: u32,
expansion_id: u32,
#[br(count = path_length)]
#[br(map = | x: Vec < u8 > | String::from_utf8(x[..x.len() - 1].to_vec()).unwrap())]
@ -262,7 +289,7 @@ fn get_platform_string(id: &PlatformId) -> &'static str {
match &id {
PlatformId::Windows => "win32",
PlatformId::PS3 => "ps3", // TODO: lol are these even correct? i have no idea
PlatformId::PS4 => "ps4"
PlatformId::PS4 => "ps4",
}
}
@ -270,28 +297,28 @@ fn get_platform_string(id: &PlatformId) -> &'static str {
#[br(big)]
struct SqpkTargetInfo {
#[br(pad_before = 3)]
platform : PlatformId,
region : Region,
platform: PlatformId,
region: Region,
#[br(map = | x : i16 | x == 1)]
is_debug : bool,
version : u16,
is_debug: bool,
version: u16,
#[br(little)]
deleted_data_size : u64,
deleted_data_size: u64,
#[br(little)]
#[br(pad_after = 96)]
seek_count : u64
seek_count: u64,
}
#[derive(BinRead, PartialEq, Debug)]
#[br(big)]
struct SqpkChunk {
size: u32,
operation : SqpkOperation
operation: SqpkOperation,
}
const WIPE_BUFFER: [u8; 1 << 16] = [0; 1 << 16];
fn wipe(mut file : &File, length : i32) -> Result<(), PatchError> {
fn wipe(mut file: &File, length: i32) -> Result<(), PatchError> {
let mut length = length;
while length > 0 {
let num_bytes = min(WIPE_BUFFER.len() as i32, length);
@ -302,47 +329,51 @@ fn wipe(mut file : &File, length : i32) -> Result<(), PatchError> {
Ok(())
}
fn wipe_from_offset(mut file : &File, length : i32, offset : i32) -> Result<(), PatchError> {
fn wipe_from_offset(mut file: &File, length: i32, offset: i32) -> Result<(), PatchError> {
file.seek(SeekFrom::Start(offset as u64))?;
wipe(file, length)
}
fn write_empty_file_block_at(mut file : &File, offset : i32, block_number : i32) -> Result<(), PatchError> {
fn write_empty_file_block_at(
mut file: &File,
offset: i32,
block_number: i32,
) -> Result<(), PatchError> {
wipe_from_offset(file, block_number << 7, offset)?;
file.seek(SeekFrom::Start(offset as u64))?;
let block_size : i32 = 1 << 7;
let block_size: i32 = 1 << 7;
file.write_all(block_size.to_le_bytes().as_slice())?;
let unknown : i32 = 0;
let unknown: i32 = 0;
file.write_all(unknown.to_le_bytes().as_slice())?;
let file_size : i32 = 0;
let file_size: i32 = 0;
file.write_all(file_size.to_le_bytes().as_slice())?;
let num_blocks : i32 = block_number - 1;
let num_blocks: i32 = block_number - 1;
file.write_all(num_blocks.to_le_bytes().as_slice())?;
let used_blocks : i32 = 0;
let used_blocks: i32 = 0;
file.write_all(used_blocks.to_le_bytes().as_slice())?;
Ok(())
}
fn get_expansion_folder(sub_id : u16) -> String {
fn get_expansion_folder(sub_id: u16) -> String {
let expansion_id = sub_id >> 8;
match expansion_id {
0 => "ffxiv".to_string(),
n => format!("ex{}", n)
n => format!("ex{}", n),
}
}
#[derive(Debug)]
pub enum PatchError {
InvalidPatchFile,
ParseError
ParseError,
}
impl From<std::io::Error> for PatchError {
@ -358,32 +389,49 @@ impl From<binrw::Error> for PatchError {
}
/// Applies a boot or a game patch to the specified _data_dir_.
pub(crate) fn apply_patch(data_dir : &str, patch_path : &str) -> Result<(), PatchError> {
pub(crate) fn apply_patch(data_dir: &str, patch_path: &str) -> Result<(), PatchError> {
let mut file = File::open(patch_path)?;
PatchHeader::read(&mut file)?;
let mut target_info : Option<SqpkTargetInfo> = None;
let mut target_info: Option<SqpkTargetInfo> = None;
let get_dat_path = |target_info : &SqpkTargetInfo, main_id : u16, sub_id : u16, file_id : u32| -> String {
let filename = format!("{:02x}{:04x}.{}.dat{}", main_id, sub_id, get_platform_string(&target_info.platform), file_id);
let path : PathBuf = [data_dir, "sqpack", &get_expansion_folder(sub_id), &filename].iter().collect();
let get_dat_path =
|target_info: &SqpkTargetInfo, main_id: u16, sub_id: u16, file_id: u32| -> String {
let filename = format!(
"{:02x}{:04x}.{}.dat{}",
main_id,
sub_id,
get_platform_string(&target_info.platform),
file_id
);
let path: PathBuf = [data_dir, "sqpack", &get_expansion_folder(sub_id), &filename]
.iter()
.collect();
path.to_str().unwrap().to_string()
};
path.to_str().unwrap().to_string()
};
let get_index_path = |target_info : &SqpkTargetInfo, main_id : u16, sub_id : u16, file_id : u32| -> String {
let mut filename = format!("{:02x}{:04x}.{}.index", main_id, sub_id, get_platform_string(&target_info.platform));
let get_index_path =
|target_info: &SqpkTargetInfo, main_id: u16, sub_id: u16, file_id: u32| -> String {
let mut filename = format!(
"{:02x}{:04x}.{}.index",
main_id,
sub_id,
get_platform_string(&target_info.platform)
);
// index files have no special ending if it's file_id == 0
if file_id != 0 {
filename += &*format!("{}", file_id);
}
// index files have no special ending if it's file_id == 0
if file_id != 0 {
filename += &*format!("{}", file_id);
}
let path : PathBuf = [data_dir, "sqpack", &get_expansion_folder(sub_id), &filename].iter().collect();
let path: PathBuf = [data_dir, "sqpack", &get_expansion_folder(sub_id), &filename]
.iter()
.collect();
path.to_str().unwrap().to_string()
};
path.to_str().unwrap().to_string()
};
loop {
let chunk = PatchChunk::read(&mut file)?;
@ -392,15 +440,18 @@ pub(crate) fn apply_patch(data_dir : &str, patch_path : &str) -> Result<(), Patc
ChunkType::Sqpk(pchunk) => {
match pchunk.operation {
SqpkOperation::AddData(add) => {
let filename = get_dat_path(target_info.as_ref().unwrap(), add.main_id, add.sub_id, add.file_id);
let filename = get_dat_path(
target_info.as_ref().unwrap(),
add.main_id,
add.sub_id,
add.file_id,
);
let (left, _) = filename.rsplit_once('/').unwrap();
fs::create_dir_all(left)?;
let mut new_file = OpenOptions::new()
.write(true)
.create(true)
.open(filename)?;
let mut new_file =
OpenOptions::new().write(true).create(true).open(filename)?;
new_file.seek(SeekFrom::Start(add.block_offset as u64))?;
@ -409,36 +460,59 @@ pub(crate) fn apply_patch(data_dir : &str, patch_path : &str) -> Result<(), Patc
wipe(&new_file, add.block_delete_number)?;
}
SqpkOperation::DeleteData(delete) => {
let filename = get_dat_path(target_info.as_ref().unwrap(), delete.main_id, delete.sub_id, delete.file_id);
let filename = get_dat_path(
target_info.as_ref().unwrap(),
delete.main_id,
delete.sub_id,
delete.file_id,
);
let new_file = OpenOptions::new()
.write(true)
.create(true)
.open(filename)?;
let new_file =
OpenOptions::new().write(true).create(true).open(filename)?;
write_empty_file_block_at(&new_file, delete.block_offset, delete.block_number)?;
write_empty_file_block_at(
&new_file,
delete.block_offset,
delete.block_number,
)?;
}
SqpkOperation::ExpandData(expand) => {
let filename = get_dat_path(target_info.as_ref().unwrap(), expand.main_id, expand.sub_id, expand.file_id);
let filename = get_dat_path(
target_info.as_ref().unwrap(),
expand.main_id,
expand.sub_id,
expand.file_id,
);
let (left, _) = filename.rsplit_once('/').unwrap();
fs::create_dir_all(left)?;
let new_file = OpenOptions::new()
.write(true)
.create(true)
.open(filename)?;
let new_file =
OpenOptions::new().write(true).create(true).open(filename)?;
write_empty_file_block_at(&new_file, expand.block_offset, expand.block_number)?;
write_empty_file_block_at(
&new_file,
expand.block_offset,
expand.block_number,
)?;
}
SqpkOperation::HeaderUpdate(header) => {
let file_path = match header.file_kind {
TargetFileKind::Dat => get_dat_path(target_info.as_ref().unwrap(), header.main_id, header.sub_id, header.file_id),
TargetFileKind::Index => get_index_path(target_info.as_ref().unwrap(), header.main_id, header.sub_id, header.file_id)
TargetFileKind::Dat => get_dat_path(
target_info.as_ref().unwrap(),
header.main_id,
header.sub_id,
header.file_id,
),
TargetFileKind::Index => get_index_path(
target_info.as_ref().unwrap(),
header.main_id,
header.sub_id,
header.file_id,
),
};
let (left, _) = file_path.rsplit_once('/')
.ok_or(PatchError::ParseError)?;
let (left, _) = file_path.rsplit_once('/').ok_or(PatchError::ParseError)?;
fs::create_dir_all(left)?;
let mut new_file = OpenOptions::new()
@ -474,10 +548,8 @@ pub(crate) fn apply_patch(data_dir : &str, patch_path : &str) -> Result<(), Patc
file.seek(SeekFrom::Current(4))?;
// now apply the file!
let mut new_file = OpenOptions::new()
.write(true)
.create(true)
.open(new_path)?;
let mut new_file =
OpenOptions::new().write(true).create(true).open(new_path)?;
new_file.seek(SeekFrom::Start(fop.offset as u64))?;
new_file.write_all(&data)?;
@ -495,18 +567,18 @@ pub(crate) fn apply_patch(data_dir : &str, patch_path : &str) -> Result<(), Patc
SqpkOperation::IndexAddDelete(_) => todo!(),
SqpkOperation::PatchInfo(patch_info) => {
println!("Got patch info: {:#?}", patch_info);
},
}
SqpkOperation::TargetInfo(new_target_info) => {
target_info = Some(new_target_info);
}
}
},
}
ChunkType::FileHeader(header) => {
println!("Got file header: {:#?}", header);
},
}
ChunkType::ApplyOption(option) => {
println!("apply option: {:#?}", option);
},
}
ChunkType::AddDirectory(_) => todo!(),
ChunkType::DeleteDirectory(_) => todo!(),
ChunkType::EndOfFile => {

View file

@ -44,14 +44,14 @@ pub enum Race {
}
mod internal_race {
use crate::race::Race;
use crate::race::Subrace;
use crate::race::Gender;
use crate::race::Race::*;
use crate::race::Subrace::*;
use crate::race::Gender::*;
use paste::paste;
use crate::define_race_enum;
use crate::race::Gender;
use crate::race::Gender::*;
use crate::race::Race;
use crate::race::Race::*;
use crate::race::Subrace;
use crate::race::Subrace::*;
use paste::paste;
define_race_enum! {
pub enum RaceTest {
@ -92,12 +92,14 @@ pub fn get_race_id(race: Race, subrace: Subrace, gender: Gender) -> Option<i32>
#[cfg(test)]
mod tests {
use crate::race::internal_race::{convert_to_internal, RaceTest};
use super::*;
use crate::race::internal_race::{convert_to_internal, RaceTest};
#[test]
fn test_convert_to_internal() {
assert_eq!(convert_to_internal(Race::Hyur, Subrace::Midlander, Gender::Female).unwrap(),
RaceTest::HyurMidlanderFemale);
assert_eq!(
convert_to_internal(Race::Hyur, Subrace::Midlander, Gender::Female).unwrap(),
RaceTest::HyurMidlanderFemale
);
}
}

View file

@ -1,8 +1,8 @@
use crate::repository::RepositoryType::{Base, Expansion};
use std::cmp::Ordering;
use std::cmp::Ordering::{Greater, Less};
use std::fs;
use std::path::{Path, PathBuf};
use crate::repository::RepositoryType::{Base, Expansion};
/// The type of repository, discerning game data from expansion data.
#[derive(Debug, PartialEq, Copy, Clone)]
@ -13,7 +13,7 @@ pub enum RepositoryType {
/// An expansion directory, like "ex1".
Expansion {
/// The expansion number starting at 1.
number: i32
number: i32,
},
}
@ -46,7 +46,7 @@ impl Ord for Repository {
let super_number = number;
match other.repo_type {
Base => Greater,
Expansion { number } => super_number.cmp(&number)
Expansion { number } => super_number.cmp(&number),
}
}
}
@ -118,7 +118,7 @@ pub fn string_to_category(string: &str) -> Option<Category> {
"music" => Some(Music),
"sqpack_test" => Some(SqPackTest),
"debug" => Some(Debug),
_ => None
_ => None,
}
}
@ -137,7 +137,7 @@ impl Repository {
Base
} else {
Expansion {
number: name[2..3].parse().unwrap()
number: name[2..3].parse().unwrap(),
}
};
@ -169,14 +169,19 @@ impl Repository {
fn expansion(&self) -> i32 {
match self.repo_type {
Base => 0,
Expansion { number } => number
Expansion { number } => number,
}
}
/// Calculate an index filename for a specific category, like _"0a0000.win32.index"_.
pub fn index_filename(&self, category: Category) -> String {
format!("{:02x}{:02}{:02}.{}.index",
category as i32, self.expansion(), 0, "win32")
format!(
"{:02x}{:02}{:02}.{}.index",
category as i32,
self.expansion(),
0,
"win32"
)
}
/// Calculate a dat filename given a category and a data file id, returns something like _"0a0000.win32.dat0"_.
@ -185,7 +190,9 @@ impl Repository {
let chunk = 0;
let platform = "win32";
format!("{:02x}{expansion:02}{chunk:02}.{platform}.dat{data_file_id}",
category as u32)
format!(
"{:02x}{expansion:02}{chunk:02}.{platform}.dat{data_file_id}",
category as u32
)
}
}

View file

@ -1,6 +1,6 @@
use crate::gamedata::MemoryBuffer;
use hard_xml::XmlRead;
use glam::Mat4;
use hard_xml::XmlRead;
#[derive(Debug)]
pub struct Bone {
@ -9,24 +9,24 @@ pub struct Bone {
pub position: [f32; 3],
pub rotation: [f32; 4],
pub scale: [f32; 3]
pub scale: [f32; 3],
}
#[derive(Debug)]
pub struct Skeleton {
pub bones : Vec<Bone>
pub bones: Vec<Bone>,
}
impl Skeleton {
/// Parses a Havok XML packfile generated by the Havok SDK.
pub fn from_packfile(buffer : &MemoryBuffer) -> Option<Skeleton> {
pub fn from_packfile(buffer: &MemoryBuffer) -> Option<Skeleton> {
#[derive(XmlRead, Debug)]
#[xml(tag = "hkpackfile")]
struct HkPackfile {
#[xml(child = "hksection")]
sections: Vec<HkSection>,
#[xml(attr = "toplevelobject")]
top_level_object : String
top_level_object: String,
}
#[derive(XmlRead, Debug)]
@ -36,7 +36,7 @@ impl Skeleton {
name: String,
#[xml(child = "hkobject")]
objects: Vec<HkObject>
objects: Vec<HkObject>,
}
#[derive(XmlRead, Debug)]
@ -49,33 +49,35 @@ impl Skeleton {
class: Option<String>,
#[xml(child = "hkparam")]
params: Vec<HkParam>
params: Vec<HkParam>,
}
#[derive(XmlRead, Debug)]
#[xml(tag = "hkparam")]
struct HkParam {
#[xml(attr = "name")]
name : String,
name: String,
#[xml(attr = "className")]
class_name : Option<String>,
class_name: Option<String>,
#[xml(attr = "variant")]
variant : Option<String>,
variant: Option<String>,
#[xml(child = "hkobject")]
objects : Vec<HkObject>,
objects: Vec<HkObject>,
#[xml(text)]
content : String
content: String,
}
let pak = HkPackfile::from_str(std::str::from_utf8(buffer).unwrap())
.expect("Failed to parse sidecar file!");
// find the root level object
let root_level_object = pak.sections[0].objects.iter()
let root_level_object = pak.sections[0]
.objects
.iter()
.find(|s| s.name.as_ref() == Some(&pak.top_level_object))
.expect("Cannot locate root level object.");
@ -87,7 +89,7 @@ impl Skeleton {
}
/// Parses the TexTools skeleton format, as a nice alternative to packfiles.
pub fn from_skel(buffer : &MemoryBuffer) -> Option<Skeleton> {
pub fn from_skel(buffer: &MemoryBuffer) -> Option<Skeleton> {
let mut string_repr = String::from_utf8(buffer.to_vec()).unwrap();
// for some reason, textools does NOT write valid JSON.
@ -104,17 +106,15 @@ impl Skeleton {
#[derive(Debug, Deserialize)]
#[serde(rename_all = "PascalCase")]
struct BoneObject {
bone_name : String,
bone_number : i32,
bone_parent : i32,
pose_matrix : [f32; 16]
bone_name: String,
bone_number: i32,
bone_parent: i32,
pose_matrix: [f32; 16],
}
let json_bones : Vec<BoneObject> = serde_json::from_str(&string_repr).unwrap();
let json_bones: Vec<BoneObject> = serde_json::from_str(&string_repr).unwrap();
let mut skeleton = Skeleton {
bones: vec![]
};
let mut skeleton = Skeleton { bones: vec![] };
for bone in &json_bones {
let pose_matrix = Mat4::from_cols_array(&bone.pose_matrix);
@ -126,7 +126,7 @@ impl Skeleton {
parent_index: bone.bone_parent,
position: translation.to_array(),
rotation: rotation.to_array(),
scale: scale.to_array()
scale: scale.to_array(),
});
}

View file

@ -1,8 +1,8 @@
use std::io::{Read, Seek, SeekFrom};
use crc::{Crc, CRC_32_JAMCRC};
use crate::compression::no_header_decompress;
use crate::dat::{BlockHeader, CompressionMode};
use binrw::BinRead;
use crc::{Crc, CRC_32_JAMCRC};
use std::io::{Read, Seek, SeekFrom};
const JAMCRC: Crc<u32> = Crc::<u32>::new(&CRC_32_JAMCRC);
@ -20,13 +20,16 @@ pub fn calculate_hash(path: &str) -> u64 {
(directory_crc as u64) << 32 | (filename_crc as u64)
}
pub fn read_data_block<T : Read + Seek>(mut buf : T, starting_position: u64) -> Option<Vec<u8>> {
pub fn read_data_block<T: Read + Seek>(mut buf: T, starting_position: u64) -> Option<Vec<u8>> {
buf.seek(SeekFrom::Start(starting_position)).ok()?;
let block_header = BlockHeader::read(&mut buf).unwrap();
match block_header.compression {
CompressionMode::Compressed { compressed_length, decompressed_length } => {
CompressionMode::Compressed {
compressed_length,
decompressed_length,
} => {
let mut compressed_data: Vec<u8> = vec![0; compressed_length as usize];
buf.read_exact(&mut compressed_data).ok()?;
@ -47,12 +50,16 @@ pub fn read_data_block<T : Read + Seek>(mut buf : T, starting_position: u64) ->
}
/// A fixed version of read_data_block accounting for differing compressed block sizes in ZiPatch files.
pub fn read_data_block_patch<T : Read + Seek>(mut buf : T) -> Option<Vec<u8>> {
pub fn read_data_block_patch<T: Read + Seek>(mut buf: T) -> Option<Vec<u8>> {
let block_header = BlockHeader::read(&mut buf).unwrap();
match block_header.compression {
CompressionMode::Compressed { compressed_length, decompressed_length } => {
let compressed_length : usize = ((compressed_length as usize + 143) & 0xFFFFFF80) - (block_header.size as usize);
CompressionMode::Compressed {
compressed_length,
decompressed_length,
} => {
let compressed_length: usize =
((compressed_length as usize + 143) & 0xFFFFFF80) - (block_header.size as usize);
let mut compressed_data: Vec<u8> = vec![0; compressed_length as usize];
buf.read_exact(&mut compressed_data).ok()?;
@ -65,12 +72,15 @@ pub fn read_data_block_patch<T : Read + Seek>(mut buf : T) -> Option<Vec<u8>> {
Some(decompressed_data)
}
CompressionMode::Uncompressed { file_size } => {
let new_file_size : usize = (file_size as usize + 143) & 0xFFFFFF80;
let new_file_size: usize = (file_size as usize + 143) & 0xFFFFFF80;
let mut local_data: Vec<u8> = vec![0; file_size as usize];
buf.read_exact(&mut local_data).ok()?;
buf.seek(SeekFrom::Current((new_file_size as usize - block_header.size as usize - file_size as usize) as i64)).ok()?;
buf.seek(SeekFrom::Current(
(new_file_size as usize - block_header.size as usize - file_size as usize) as i64,
))
.ok()?;
Some(local_data)
}

View file

@ -1,9 +1,9 @@
use std::cmp::min;
use std::io::{Cursor, Read, Seek, SeekFrom};
use binrw::binread;
use crate::gamedata::MemoryBuffer;
use binrw::binread;
use binrw::BinRead;
use bitflags::bitflags;
use std::cmp::min;
use std::io::{Cursor, Read, Seek, SeekFrom};
use texpresso::Format;
// Attributes and Format are adapted from Lumina (https://github.com/NotAdam/Lumina/blob/master/src/Lumina/Data/Files/TexFile.cs)
@ -43,28 +43,28 @@ bitflags! {
enum TextureFormat {
B8G8R8A8 = 0x1450,
BC1 = 0x3420,
BC5 = 0x3431
BC5 = 0x3431,
}
#[binread]
#[derive(Debug)]
struct TexHeader {
attribute : TextureAttribute,
attribute: TextureAttribute,
format: TextureFormat,
width : u16,
height : u16,
depth : u16,
mip_levels : u16,
width: u16,
height: u16,
depth: u16,
mip_levels: u16,
lod_offsets : [u32; 3],
offset_to_surface : [u32; 13]
lod_offsets: [u32; 3],
offset_to_surface: [u32; 13],
}
pub struct Texture {
pub width: u32,
pub height: u32,
pub rgba: Vec<u8>
pub rgba: Vec<u8>,
}
impl Texture {
@ -79,14 +79,18 @@ impl Texture {
for i in 0..size - 1 {
texture_data_size[i] = header.offset_to_surface[i + 1] - header.offset_to_surface[i];
}
texture_data_size[size - 1] = (buffer.len() - header.offset_to_surface[size - 1] as usize) as u32;
texture_data_size[size - 1] =
(buffer.len() - header.offset_to_surface[size - 1] as usize) as u32;
cursor.seek(SeekFrom::Start(header.offset_to_surface[0] as u64)).ok()?;
cursor
.seek(SeekFrom::Start(header.offset_to_surface[0] as u64))
.ok()?;
let mut src = vec![0u8; texture_data_size.iter().sum::<u32>() as usize];
cursor.read_exact(src.as_mut_slice()).ok()?;
let mut dst : Vec<u8> = vec![0u8; (header.width as usize * header.height as usize * 4) as usize];
let mut dst: Vec<u8> =
vec![0u8; (header.width as usize * header.height as usize * 4) as usize];
match header.format {
TextureFormat::B8G8R8A8 => {
@ -94,18 +98,28 @@ impl Texture {
}
TextureFormat::BC1 => {
let format = Format::Bc1;
format.decompress(&src, header.width as usize, header.height as usize, dst.as_mut_slice());
format.decompress(
&src,
header.width as usize,
header.height as usize,
dst.as_mut_slice(),
);
}
TextureFormat::BC5 => {
let format = Format::Bc3;
format.decompress(&src, header.width as usize, header.height as usize, dst.as_mut_slice());
format.decompress(
&src,
header.width as usize,
header.height as usize,
dst.as_mut_slice(),
);
}
}
Some(Texture {
width: header.width as u32,
height: header.height as u32,
rgba: dst
rgba: dst,
})
}
}

View file

@ -1,12 +1,14 @@
use std::env;
use physis::index;
use std::env;
#[test]
#[cfg_attr(not(feature = "retail_game_testing"), ignore)]
fn test_index_read() {
let game_dir = env::var("FFXIV_GAME_DIR").unwrap();
index::IndexFile::from_existing(format!("{}/game/sqpack/ffxiv/000000.win32.index", game_dir).as_str());
index::IndexFile::from_existing(
format!("{}/game/sqpack/ffxiv/000000.win32.index", game_dir).as_str(),
);
}
#[test]
@ -14,7 +16,8 @@ fn test_index_read() {
fn test_gamedata_extract() {
let game_dir = env::var("FFXIV_GAME_DIR").unwrap();
let mut gamedata = physis::gamedata::GameData::from_existing(format!("{}/game", game_dir).as_str()).unwrap();
let mut gamedata =
physis::gamedata::GameData::from_existing(format!("{}/game", game_dir).as_str()).unwrap();
gamedata.reload_repositories();