chronojump r469 - in trunk: . build/data chronojump_server chronojump_server/bin glade sqlite_diagrams src src/gui src/sqlite



Author: xaviblas
Date: Thu Mar  5 16:29:43 2009
New Revision: 469
URL: http://svn.gnome.org/viewvc/chronojump?rev=469&view=rev

Log:
	0.8.2.6
	evaluator code ended with encryption. Only pending the confiable flag:
	-added BCryp.cs to allow encryption of evaluatorServerUniqueID
	-added code to Sevaluator table;
	-done upload or insert evaluator data

	finished evaluator win:
	-ended fillDialog
	-fixed crash on accept (bad sql)
	-fixed crash on cancel, or delete, or accept (on closing window)
	-accept is shown while no date of birth (done?)
	-unchecked button_accept if needed on start

	dialogMessage again as modal because there where problems (unclickable) 
	when is called from evaluator window until evaluator win is closed

	improved chrash message on start



Added:
   trunk/chronojump_server/BCrypt.cs   (contents, props changed)
Modified:
   trunk/Makefile
   trunk/build/data/chronojump.prg
   trunk/build/data/chronojump_mini.prg
   trunk/build/data/version.txt
   trunk/changelog.txt
   trunk/chronojump_server/ChronojumpServer.cs
   trunk/chronojump_server/bin/chronojumpServer.dll
   trunk/chronojump_server/chronojumpServerCSharp.cs
   trunk/glade/chronojump.glade
   trunk/sqlite_diagrams/chronojump_sqlite.dia
   trunk/src/chronojump.cs
   trunk/src/gui/chronojump.cs
   trunk/src/gui/evaluator.cs
   trunk/src/server.cs
   trunk/src/serverEvaluator.cs
   trunk/src/sqlite/server.cs
   trunk/version.txt

Modified: trunk/Makefile
==============================================================================
--- trunk/Makefile	(original)
+++ trunk/Makefile	Thu Mar  5 16:29:43 2009
@@ -114,7 +114,7 @@
 
 #--------Dependences of CHRONOJUMP_SERVER
 
-CHRONOJUMP_SERVER_DEP = chronojump_server/chronojumpServerCSharp.cs src/sqlite/*.cs src/util.cs src/person.cs src/event.cs src/jump.cs src/run.cs src/pulse.cs src/reactionTime.cs src/session.cs src/eventType.cs src/jumpType.cs src/runType.cs src/pulseType.cs src/sport.cs src/constants.cs src/log.cs src/serverPing.cs src/serverEvaluator.cs
+CHRONOJUMP_SERVER_DEP = chronojump_server/chronojumpServerCSharp.cs src/sqlite/*.cs src/util.cs src/person.cs src/event.cs src/jump.cs src/run.cs src/pulse.cs src/reactionTime.cs src/session.cs src/eventType.cs src/jumpType.cs src/runType.cs src/pulseType.cs src/sport.cs src/constants.cs src/log.cs src/serverPing.cs src/serverEvaluator.cs chronojump_server/BCrypt.cs 
 
 
 #--------Makefiles

Modified: trunk/build/data/chronojump.prg
==============================================================================
Binary files. No diff available.

Modified: trunk/build/data/chronojump_mini.prg
==============================================================================
Binary files. No diff available.

Modified: trunk/build/data/version.txt
==============================================================================
--- trunk/build/data/version.txt	(original)
+++ trunk/build/data/version.txt	Thu Mar  5 16:29:43 2009
@@ -1 +1 @@
-0.8.2.5
+0.8.2.6

Modified: trunk/changelog.txt
==============================================================================
--- trunk/changelog.txt	(original)
+++ trunk/changelog.txt	Thu Mar  5 16:29:43 2009
@@ -11,11 +11,24 @@
 
 do the ping gets real IP
 
-evaluator win TODO:
--unchecked button_accept if needed on start
--fix crash on cancel, or delete, or accept (on closing window)
--fix crash on accept (bad sql)
--accept is shown while no date of birth
+5 mar 2009
+	0.8.2.6
+	evaluator code ended with encryption. Only pending the confiable flag:
+	-added BCryp.cs to allow encryption of evaluatorServerUniqueID
+	-added code to Sevaluator table;
+	-done upload or insert evaluator data
+
+	finished evaluator win:
+	-ended fillDialog
+	-fixed crash on accept (bad sql)
+	-fixed crash on cancel, or delete, or accept (on closing window)
+	-accept is shown while no date of birth (done?)
+	-unchecked button_accept if needed on start
+
+	dialogMessage again as modal because there where problems (unclickable) 
+	when is called from evaluator window until evaluator win is closed
+
+	improved chrash message on start
 
 3 mar 2009
 	0.8.2.5

Added: trunk/chronojump_server/BCrypt.cs
==============================================================================
--- (empty file)
+++ trunk/chronojump_server/BCrypt.cs	Thu Mar  5 16:29:43 2009
@@ -0,0 +1,760 @@
+// Copyright (c) 2006 Damien Miller <djm mindrot org>
+// Copyright (c) 2007 Derek Slager
+//
+// Permission to use, copy, modify, and distribute this software for any
+// purpose with or without fee is hereby granted, provided that the above
+// copyright notice and this permission notice appear in all copies.
+//
+// THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES
+// WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF
+// MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR
+// ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES
+// WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN
+// ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF
+// OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
+
+using System;
+using System.Collections.Generic;
+using System.Globalization;
+using System.Security.Cryptography;
+using System.Text;
+
+[assembly: System.Reflection.AssemblyVersion("0.1")]
+
+
+//http://derekslager.com/blog/posts/2007/10/bcrypt-dotnet-strong-password-hashing-for-dotnet-and-mono.ashx
+
+/// <summary>BCrypt implements OpenBSD-style Blowfish password hashing
+/// using the scheme described in "A Future-Adaptable Password Scheme"
+/// by Niels Provos and David Mazieres.</summary>
+/// <remarks>
+/// <para>This password hashing system tries to thwart offline
+/// password cracking using a computationally-intensive hashing
+/// algorithm, based on Bruce Schneier's Blowfish cipher. The work
+/// factor of the algorithm is parametized, so it can be increased as
+/// computers get faster.</para>
+/// <para>To hash a password for the first time, call the
+/// <c>HashPassword</c> method with a random salt, like this:</para>
+/// <code>
+/// string hashed = BCrypt.HashPassword(plainPassword, BCrypt.GenerateSalt());
+/// </code>
+/// <para>To check whether a plaintext password matches one that has
+/// been hashed previously, use the <c>CheckPassword</c> method:</para>
+/// <code>
+/// if (BCrypt.CheckPassword(candidatePassword, storedHash)) {
+///     Console.WriteLine("It matches");
+/// } else {
+///     Console.WriteLine("It does not match");
+/// }
+/// </code>
+/// <para>The <c>GenerateSalt</c> method takes an optional parameter
+/// (logRounds) that determines the computational complexity of the
+/// hashing:</para>
+/// <code>
+/// string strongSalt = BCrypt.GenerateSalt(10);
+/// string strongerSalt = BCrypt.GenerateSalt(12);
+/// </code>
+/// <para>
+/// The amount of work increases exponentially (2**log_rounds), so
+/// each increment is twice as much work. The default log_rounds is
+/// 10, and the valid range is 4 to 31.
+/// </para>
+/// </remarks>
+public class BCrypt {
+
+    private const int GENSALT_DEFAULT_LOG2_ROUNDS = 10;
+    private const int BCRYPT_SALT_LEN = 16;
+
+    // Blowfish parameters.
+    private const int BLOWFISH_NUM_ROUNDS = 16;
+
+    // Initial contents of key schedule.
+    private static readonly uint[] p_orig = {
+        0x243f6a88, 0x85a308d3, 0x13198a2e, 0x03707344,
+        0xa4093822, 0x299f31d0, 0x082efa98, 0xec4e6c89,
+        0x452821e6, 0x38d01377, 0xbe5466cf, 0x34e90c6c,
+        0xc0ac29b7, 0xc97c50dd, 0x3f84d5b5, 0xb5470917,
+        0x9216d5d9, 0x8979fb1b
+    };
+
+    private static readonly uint[] s_orig = {
+        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
+    };
+
+    // bcrypt IV: "OrpheanBeholderScryDoubt".
+    private static readonly uint[] bf_crypt_ciphertext = {
+        0x4f727068, 0x65616e42, 0x65686f6c,
+        0x64657253, 0x63727944, 0x6f756274
+    };
+
+    // Table for Base64 encoding.
+    private static readonly char[] base64_code = {
+        '.', '/', 'A', 'B', 'C', 'D', 'E', 'F', 'G', 'H', 'I', 'J',
+        'K', 'L', 'M', 'N', 'O', 'P', 'Q', 'R', 'S', 'T', 'U', 'V',
+        'W', 'X', 'Y', 'Z', 'a', 'b', 'c', 'd', 'e', 'f', 'g', 'h',
+        'i', 'j', 'k', 'l', 'm', 'n', 'o', 'p', 'q', 'r', 's', 't',
+        'u', 'v', 'w', 'x', 'y', 'z', '0', '1', '2', '3', '4', '5',
+        '6', '7', '8', '9'
+    };
+
+    // Table for Base64 decoding.
+    private static readonly int[] index_64 = {
+        -1, -1, -1, -1, -1, -1, -1, -1, -1, -1,
+        -1, -1, -1, -1, -1, -1, -1, -1, -1, -1,
+        -1, -1, -1, -1, -1, -1, -1, -1, -1, -1,
+        -1, -1, -1, -1, -1, -1, -1, -1, -1, -1,
+        -1, -1, -1, -1, -1, -1, 0, 1, 54, 55,
+        56, 57, 58, 59, 60, 61, 62, 63, -1, -1,
+        -1, -1, -1, -1, -1, 2, 3, 4, 5, 6,
+        7, 8, 9, 10, 11, 12, 13, 14, 15, 16,
+        17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27,
+        -1, -1, -1, -1, -1, -1, 28, 29, 30,
+        31, 32, 33, 34, 35, 36, 37, 38, 39, 40,
+        41, 42, 43, 44, 45, 46, 47, 48, 49, 50,
+        51, 52, 53, -1, -1, -1, -1, -1
+    };
+
+    // Expanded Blowfish key.
+    private uint[] p;
+    private uint[] s;
+
+    /// <summary>Encode a byte array using bcrypt's slightly-modified
+    /// Base64 encoding scheme. Note that this is _not_ compatible
+    /// with the standard MIME-Base64 encoding.</summary>
+    /// <param name="d">The byte array to encode</param>
+    /// <param name="length">The number of bytes to encode</param>
+    /// <returns>A Base64-encoded string</returns>
+    private static string EncodeBase64(byte[] d, int length) {
+
+        if (length <= 0 || length > d.Length) {
+            throw new ArgumentOutOfRangeException("length", length, null);
+        }
+
+        StringBuilder rs = new StringBuilder(length * 2);
+
+        for (int offset = 0, c1, c2; offset < length; ) {
+            c1 = d[offset++] & 0xff;
+            rs.Append(base64_code[(c1 >> 2) & 0x3f]);
+            c1 = (c1 & 0x03) << 4;
+            if (offset >= length) {
+                rs.Append(base64_code[c1 & 0x3f]);
+                break;
+            }
+            c2 = d[offset++] & 0xff;
+            c1 |= (c2 >> 4) & 0x0f;
+            rs.Append(base64_code[c1 & 0x3f]);
+            c1 = (c2 & 0x0f) << 2;
+            if (offset >= length) {
+                rs.Append(base64_code[c1 & 0x3f]);
+                break;
+            }
+            c2 = d[offset++] & 0xff;
+            c1 |= (c2 >> 6) & 0x03;
+            rs.Append(base64_code[c1 & 0x3f]);
+            rs.Append(base64_code[c2 & 0x3f]);
+        }
+
+        return rs.ToString();
+    }
+
+    /// <summary>Look up the 3 bits base64-encoded by the specified
+    /// character, range-checking against the conversion
+    /// table.</summary>
+    /// <param name="c">The Base64-encoded value</param>
+    /// <returns>The decoded value of <c>x</c></returns>
+    private static int Char64(char c) {
+        int i = (int)c;
+        return (i < 0 || i > index_64.Length) ? -1 : index_64[i];
+    }
+
+    /// <summary>Decode a string encoded using BCrypt's Base64 scheme to a
+    /// byte array. Note that this is _not_ compatible with the standard
+    /// MIME-Base64 encoding.</summary>
+    /// <param name="s">The string to decode</param>
+    /// <param name="maximumLength">The maximum number of bytes to decode</param>
+    /// <returns>An array containing the decoded bytes</returns>
+    private static byte[] DecodeBase64(string s, int maximumLength) {
+
+        List<byte> bytes = new List<byte>(Math.Min(maximumLength, s.Length));
+
+        if (maximumLength <= 0) {
+            throw new ArgumentOutOfRangeException("maximumLength", maximumLength, null);
+        }
+
+        for (int offset = 0, slen = s.Length, length = 0; offset < slen - 1 && length < maximumLength; ) {
+            int c1 = Char64(s[offset++]);
+            int c2 = Char64(s[offset++]);
+            if (c1 == -1 || c2 == -1) {
+                break;
+            }
+
+            bytes.Add((byte)((c1 << 2) | ((c2 & 0x30) >> 4)));
+            if (++length >= maximumLength || offset >= s.Length) {
+                break;
+            }
+
+            int c3 = Char64(s[offset++]);
+            if (c3 == -1) {
+                break;
+            }
+
+            bytes.Add((byte)(((c2 & 0x0f) << 4) | ((c3 & 0x3c) >> 2)));
+            if (++length >= maximumLength || offset >= s.Length) {
+                break;
+            }
+
+            int c4 = Char64(s[offset++]);
+            bytes.Add((byte)(((c3 & 0x03) << 6) | c4));
+
+            ++length;
+        }
+
+        return bytes.ToArray();
+    }
+
+    /// <summary>
+    /// Blowfish encipher a single 64-bit block encoded as two 32-bit
+    /// halves.
+    /// </summary>
+    /// <param name="block">An array containing the two 32-bit half
+    /// blocks.</param>
+    /// <param name="offset">The position in the array of the
+    /// blocks.</param>
+    private void Encipher(uint[] block, int offset) {
+
+        uint i, n, l = block[offset], r = block[offset + 1];
+
+        l ^= this.p[0];
+        for (i = 0; i <= BLOWFISH_NUM_ROUNDS - 2;) {
+            // Feistel substitution on left word
+            n = this.s[(l >> 24) & 0xff];
+            n += this.s[0x100 | ((l >> 16) & 0xff)];
+            n ^= this.s[0x200 | ((l >> 8) & 0xff)];
+            n += this.s[0x300 | (l & 0xff)];
+            r ^= n ^ this.p[++i];
+
+            // Feistel substitution on right word
+            n = this.s[(r >> 24) & 0xff];
+            n += this.s[0x100 | ((r >> 16) & 0xff)];
+            n ^= this.s[0x200 | ((r >> 8) & 0xff)];
+            n += this.s[0x300 | (r & 0xff)];
+            l ^= n ^ this.p[++i];
+        }
+        block[offset] = r ^ this.p[BLOWFISH_NUM_ROUNDS + 1];
+        block[offset + 1] = l;
+    }
+
+    /// <summary>
+    /// Cycically extract a word of key material.
+    /// </summary>
+    /// <param name="data">The string to extract the data
+    /// from.</param>
+    /// <param name="offset">The current offset into data.</param>
+    /// <returns>The next work of material from data.</returns>
+    private static uint StreamToWord(byte[] data, ref int offset) {
+
+        uint word = 0;
+
+        for (int i = 0; i < 4; i++) {
+            word = (word << 8) | data[offset];
+            offset = (offset + 1) % data.Length;
+        }
+
+        return word;
+    }
+
+    /// <summary>
+    /// Initialize the Blowfish key schedule.
+    /// </summary>
+    private void InitKey() {
+        this.p = new uint[p_orig.Length];
+        p_orig.CopyTo(this.p, 0);
+        this.s = new uint[s_orig.Length];
+        s_orig.CopyTo(this.s, 0);
+    }
+
+    /// <summary>
+    /// Key the Blowfish cipher.
+    /// </summary>
+    /// <param name="key">An array containing the key.</param>
+    private void Key(byte[] key) {
+
+        uint[] lr = { 0, 0 };
+        int plen = this.p.Length, slen = this.s.Length;
+
+        int offset = 0;
+        for (int i = 0; i < plen; i++) {
+            this.p[i] = this.p[i] ^ StreamToWord(key, ref offset);
+        }
+
+        for (int i = 0; i < plen; i += 2) {
+            Encipher(lr, 0);
+            this.p[i] = lr[0];
+            this.p[i + 1] = lr[1];
+        }
+
+        for (int i = 0; i < slen; i += 2) {
+            Encipher(lr, 0);
+            this.s[i] = lr[0];
+            this.s[i + 1] = lr[1];
+        }
+    }
+
+    /// <summary>
+    /// Perform the "enhanced key schedule" step described by Provos
+    /// and Mazieres in "A Future-Adaptable Password Scheme"
+    /// (http://www.openbsd.org/papers/bcrypt-paper.ps).
+    /// </summary>
+    /// <param name="data">Salt information.</param>
+    /// <param name="key">Password information.</param>
+    private void EksKey(byte[] data, byte[] key) {
+
+        uint[] lr = { 0, 0 };
+        int plen = this.p.Length, slen = this.s.Length;
+
+        int keyOffset = 0;
+        for (int i = 0; i < plen; i++) {
+            this.p[i] = this.p[i] ^ StreamToWord(key, ref keyOffset);
+        }
+
+        int dataOffset = 0;
+        for (int i = 0; i < plen; i += 2) {
+            lr[0] ^= StreamToWord(data, ref dataOffset);
+            lr[1] ^= StreamToWord(data, ref dataOffset);
+            Encipher(lr, 0);
+            this.p[i] = lr[0];
+            this.p[i + 1] = lr[1];
+        }
+
+        for (int i = 0; i < slen; i += 2) {
+            lr[0] ^= StreamToWord(data, ref dataOffset);
+            lr[1] ^= StreamToWord(data, ref dataOffset);
+            Encipher(lr, 0);
+            this.s[i] = lr[0];
+            this.s[i + 1] = lr[1];
+        }
+    }
+
+    /// <summary>
+    /// Perform the central password hashing step in the bcrypt
+    /// scheme.
+    /// </summary>
+    /// <param name="password">The password to hash.</param>
+    /// <param name="salt">The binary salt to hash with the
+    /// password.</param>
+    /// <param name="logRounds">The binary logarithm of the number of
+    /// rounds of hashing to apply.</param>
+    /// <returns>An array containing the binary hashed password.</returns>
+    private byte[] CryptRaw(byte[] password, byte[] salt, int logRounds) {
+
+        uint[] cdata = new uint[bf_crypt_ciphertext.Length];
+        bf_crypt_ciphertext.CopyTo(cdata, 0);
+
+        int clen = cdata.Length;
+        byte[] ret;
+
+        if (logRounds < 4 || logRounds > 31) {
+            throw new ArgumentOutOfRangeException("logRounds", logRounds, null);
+        }
+
+        int rounds = 1 << logRounds;
+        if (salt.Length != BCRYPT_SALT_LEN) {
+            throw new ArgumentException("Invalid salt length.", "salt");
+        }
+
+        InitKey();
+        EksKey(salt, password);
+
+        for (int i = 0; i < rounds; i++) {
+            Key(password);
+            Key(salt);
+        }
+
+        for (int i = 0; i < 64; i++) {
+            for (int j = 0; j < (clen >> 1); j++) {
+                Encipher(cdata, j << 1);
+            }
+        }
+
+        ret = new byte[clen * 4];
+        for (int i = 0, j = 0; i < clen; i++) {
+            ret[j++] = (byte)((cdata[i] >> 24) & 0xff);
+            ret[j++] = (byte)((cdata[i] >> 16) & 0xff);
+            ret[j++] = (byte)((cdata[i] >> 8) & 0xff);
+            ret[j++] = (byte)(cdata[i] & 0xff);
+        }
+
+        return ret;
+    }
+
+    /// <summary>
+    /// Hash a password using the OpenBSD bcrypt scheme.
+    /// </summary>
+    /// <param name="password">The password to hash.</param>
+    /// <param name="salt">The salt to hash with (perhaps generated
+    /// using <c>BCrypt.GenerateSalt</c>).</param>
+    /// <returns>The hashed password.</returns>
+    public static string HashPassword(string password, string salt) {
+        if (password == null) {
+            throw new ArgumentNullException("password");
+        }
+        if (salt == null) {
+            throw new ArgumentNullException("salt");
+        }
+
+        char minor = (char)0;
+
+        if (salt[0] != '$' || salt[1] != '2') {
+            throw new ArgumentException("Invalid salt version");
+        }
+
+        int offset;
+        if (salt[1] != '$') {
+            minor = salt[2];
+            if (minor != 'a' || salt[3] != '$') {
+                throw new ArgumentException("Invalid salt revision");
+            }
+            offset = 4;
+        } else {
+            offset = 3;
+        }
+
+        // Extract number of rounds
+        if (salt[offset + 2] > '$') {
+            throw new ArgumentException("Missing salt rounds");
+        }
+
+        int rounds = Int32.Parse(salt.Substring(offset, 2), NumberFormatInfo.InvariantInfo);
+
+        byte[] passwordBytes = Encoding.UTF8.GetBytes(password + (minor >= 'a' ? "\0" : String.Empty));
+        byte[] saltBytes = DecodeBase64(salt.Substring(offset + 3, 22),
+                                        BCRYPT_SALT_LEN);
+
+        BCrypt bcrypt = new BCrypt();
+
+        byte[] hashed = bcrypt.CryptRaw(passwordBytes, saltBytes, rounds);
+
+        StringBuilder rs = new StringBuilder();
+
+        rs.Append("$2");
+        if (minor >= 'a') {
+            rs.Append(minor);
+        }
+        rs.Append('$');
+        if (rounds < 10) {
+            rs.Append('0');
+        }
+        rs.Append(rounds);
+        rs.Append('$');
+        rs.Append(EncodeBase64(saltBytes, saltBytes.Length));
+        rs.Append(EncodeBase64(hashed,
+                               (bf_crypt_ciphertext.Length * 4) - 1));
+
+        return rs.ToString();
+    }
+
+    /// <summary>
+    /// Generate a salt for use with the BCrypt.HashPassword() method.
+    /// </summary>
+    /// <param name="logRounds">The log2 of the number of rounds of
+    /// hashing to apply. The work factor therefore increases as (2 **
+    /// logRounds).</param>
+    /// <returns>An encoded salt value.</returns>
+    public static string GenerateSalt(int logRounds) {
+
+        byte[] randomBytes = new byte[BCRYPT_SALT_LEN];
+
+        RandomNumberGenerator.Create().GetBytes(randomBytes);
+
+        StringBuilder rs = new StringBuilder((randomBytes.Length * 2) + 8);
+
+        rs.Append("$2a$");
+        if (logRounds < 10) {
+            rs.Append('0');
+        }
+        rs.Append(logRounds);
+        rs.Append('$');
+        rs.Append(EncodeBase64(randomBytes, randomBytes.Length));
+
+        return rs.ToString();
+    }
+
+    /// <summary>
+    /// Generate a salt for use with the <c>BCrypt.HashPassword()</c>
+    /// method, selecting a reasonable default for the number of hashing
+    /// rounds to apply.
+    /// </summary>
+    /// <returns>An encoded salt value.</returns>
+    public static string GenerateSalt() {
+        return GenerateSalt(GENSALT_DEFAULT_LOG2_ROUNDS);
+    }
+
+    /// <summary>
+    /// Check that a plaintext password matches a previously hashed
+    /// one.
+    /// </summary>
+    /// <param name="plaintext">The plaintext password to verify.</param>
+    /// <param name="hashed">The previously hashed password.</param>
+    /// <returns><c>true</c> if the passwords, <c>false</c>
+    /// otherwise.</returns>
+    public static bool CheckPassword(string plaintext, string hashed) {
+        return StringComparer.Ordinal.Compare(hashed, HashPassword(plaintext, hashed)) == 0;
+    }
+
+}
+

Modified: trunk/chronojump_server/ChronojumpServer.cs
==============================================================================
--- trunk/chronojump_server/ChronojumpServer.cs	(original)
+++ trunk/chronojump_server/ChronojumpServer.cs	Thu Mar  5 16:29:43 2009
@@ -52,6 +52,8 @@
     
     private System.Threading.SendOrPostCallback UploadEvaluatorOperationCompleted;
     
+    private System.Threading.SendOrPostCallback EditEvaluatorOperationCompleted;
+    
     private System.Threading.SendOrPostCallback UploadJumpOperationCompleted;
     
     private System.Threading.SendOrPostCallback UploadJumpRjOperationCompleted;
@@ -100,6 +102,8 @@
     
     private event UploadEvaluatorCompletedEventHandler UploadEvaluatorCompleted;
     
+    private event EditEvaluatorCompletedEventHandler EditEvaluatorCompleted;
+    
     private event UploadJumpCompletedEventHandler UploadJumpCompleted;
     
     private event UploadJumpRjCompletedEventHandler UploadJumpRjCompleted;
@@ -682,38 +686,35 @@
     }
     
     /// <remarks>
-///Upload a evaluator
+///Upload an evaluator
 ///</remarks>
     [System.Web.Services.Protocols.SoapDocumentMethodAttribute("http://server.chronojump.org/UploadEvaluator";, RequestNamespace="http://server.chronojump.org/";, ResponseNamespace="http://server.chronojump.org/";, ParameterStyle=System.Web.Services.Protocols.SoapParameterStyle.Wrapped, Use=System.Web.Services.Description.SoapBindingUse.Literal)]
-    public int UploadEvaluator(ServerEvaluator myEval, int evalSID) {
+    public string UploadEvaluator(ServerEvaluator myEval) {
         object[] results = this.Invoke("UploadEvaluator", new object[] {
-                    myEval,
-                    evalSID});
-        return ((int)(results[0]));
+                    myEval});
+        return ((string)(results[0]));
     }
     
-    public System.IAsyncResult BeginUploadEvaluator(ServerEvaluator myEval, int evalSID, System.AsyncCallback callback, object asyncState) {
+    public System.IAsyncResult BeginUploadEvaluator(ServerEvaluator myEval, System.AsyncCallback callback, object asyncState) {
         return this.BeginInvoke("UploadEvaluator", new object[] {
-                    myEval,
-                    evalSID}, callback, asyncState);
+                    myEval}, callback, asyncState);
     }
     
-    public int EndUploadEvaluator(System.IAsyncResult asyncResult) {
+    public string EndUploadEvaluator(System.IAsyncResult asyncResult) {
         object[] results = this.EndInvoke(asyncResult);
-        return ((int)(results[0]));
+        return ((string)(results[0]));
     }
     
-    public void UploadEvaluatorAsync(ServerEvaluator myEval, int evalSID) {
-        this.UploadEvaluatorAsync(myEval, evalSID, null);
+    public void UploadEvaluatorAsync(ServerEvaluator myEval) {
+        this.UploadEvaluatorAsync(myEval, null);
     }
     
-    public void UploadEvaluatorAsync(ServerEvaluator myEval, int evalSID, object userState) {
+    public void UploadEvaluatorAsync(ServerEvaluator myEval, object userState) {
         if ((this.UploadEvaluatorOperationCompleted == null)) {
             this.UploadEvaluatorOperationCompleted = new System.Threading.SendOrPostCallback(this.OnUploadEvaluatorCompleted);
         }
         this.InvokeAsync("UploadEvaluator", new object[] {
-                    myEval,
-                    evalSID}, this.UploadEvaluatorOperationCompleted, userState);
+                    myEval}, this.UploadEvaluatorOperationCompleted, userState);
     }
     
     private void OnUploadEvaluatorCompleted(object arg) {
@@ -724,6 +725,48 @@
     }
     
     /// <remarks>
+///Edit an evaluator
+///</remarks>
+    [System.Web.Services.Protocols.SoapDocumentMethodAttribute("http://server.chronojump.org/EditEvaluator";, RequestNamespace="http://server.chronojump.org/";, ResponseNamespace="http://server.chronojump.org/";, ParameterStyle=System.Web.Services.Protocols.SoapParameterStyle.Wrapped, Use=System.Web.Services.Description.SoapBindingUse.Literal)]
+    public bool EditEvaluator(ServerEvaluator clientEval, int evalSID) {
+        object[] results = this.Invoke("EditEvaluator", new object[] {
+                    clientEval,
+                    evalSID});
+        return ((bool)(results[0]));
+    }
+    
+    public System.IAsyncResult BeginEditEvaluator(ServerEvaluator clientEval, int evalSID, System.AsyncCallback callback, object asyncState) {
+        return this.BeginInvoke("EditEvaluator", new object[] {
+                    clientEval,
+                    evalSID}, callback, asyncState);
+    }
+    
+    public bool EndEditEvaluator(System.IAsyncResult asyncResult) {
+        object[] results = this.EndInvoke(asyncResult);
+        return ((bool)(results[0]));
+    }
+    
+    public void EditEvaluatorAsync(ServerEvaluator clientEval, int evalSID) {
+        this.EditEvaluatorAsync(clientEval, evalSID, null);
+    }
+    
+    public void EditEvaluatorAsync(ServerEvaluator clientEval, int evalSID, object userState) {
+        if ((this.EditEvaluatorOperationCompleted == null)) {
+            this.EditEvaluatorOperationCompleted = new System.Threading.SendOrPostCallback(this.OnEditEvaluatorCompleted);
+        }
+        this.InvokeAsync("EditEvaluator", new object[] {
+                    clientEval,
+                    evalSID}, this.EditEvaluatorOperationCompleted, userState);
+    }
+    
+    private void OnEditEvaluatorCompleted(object arg) {
+        if ((this.EditEvaluatorCompleted != null)) {
+            System.Web.Services.Protocols.InvokeCompletedEventArgs invokeArgs = ((System.Web.Services.Protocols.InvokeCompletedEventArgs)(arg));
+            this.EditEvaluatorCompleted(this, new EditEvaluatorCompletedEventArgs(invokeArgs.Results, invokeArgs.Error, invokeArgs.Cancelled, invokeArgs.UserState));
+        }
+    }
+    
+    /// <remarks>
 ///Upload a jump
 ///</remarks>
     [System.Web.Services.Protocols.SoapDocumentMethodAttribute("http://server.chronojump.org/UploadJump";, RequestNamespace="http://server.chronojump.org/";, ResponseNamespace="http://server.chronojump.org/";, ParameterStyle=System.Web.Services.Protocols.SoapParameterStyle.Wrapped, Use=System.Web.Services.Description.SoapBindingUse.Literal)]
@@ -996,7 +1039,6 @@
         }
     }
 }
-
 /*
 /// <remarks/>
 [System.CodeDom.Compiler.GeneratedCodeAttribute("System.Xml", "2.0.50727.42")]
@@ -1241,6 +1283,9 @@
     public int UniqueID;
     
     /// <remarks/>
+    public string Code;
+    
+    /// <remarks/>
     public string Name;
     
     /// <remarks/>
@@ -1414,7 +1459,6 @@
     public string TimesString;
 }
 */
-
 public class ConnectDatabaseCompletedEventArgs : System.ComponentModel.AsyncCompletedEventArgs {
     
     private object[] results;
@@ -1690,16 +1734,35 @@
         this.results = results;
     }
     
-    public int Result {
+    public string Result {
         get {
             this.RaiseExceptionIfNecessary();
-            return ((int)(this.results[0]));
+            return ((string)(this.results[0]));
         }
     }
 }
 
 public delegate void UploadEvaluatorCompletedEventHandler(object sender, UploadEvaluatorCompletedEventArgs args);
 
+public class EditEvaluatorCompletedEventArgs : System.ComponentModel.AsyncCompletedEventArgs {
+    
+    private object[] results;
+    
+    internal EditEvaluatorCompletedEventArgs(object[] results, System.Exception exception, bool cancelled, object userState) : 
+            base(exception, cancelled, userState) {
+        this.results = results;
+    }
+    
+    public bool Result {
+        get {
+            this.RaiseExceptionIfNecessary();
+            return ((bool)(this.results[0]));
+        }
+    }
+}
+
+public delegate void EditEvaluatorCompletedEventHandler(object sender, EditEvaluatorCompletedEventArgs args);
+
 public class UploadJumpCompletedEventArgs : System.ComponentModel.AsyncCompletedEventArgs {
     
     private object[] results;

Modified: trunk/chronojump_server/bin/chronojumpServer.dll
==============================================================================
Binary files. No diff available.

Modified: trunk/chronojump_server/chronojumpServerCSharp.cs
==============================================================================
--- trunk/chronojump_server/chronojumpServerCSharp.cs	(original)
+++ trunk/chronojump_server/chronojumpServerCSharp.cs	Thu Mar  5 16:29:43 2009
@@ -258,18 +258,46 @@
 		return SqlitePreferences.Select("versionAvailable");
 	}
 
-	[WebMethod(Description="Upload a evaluator")]
-	public int UploadEvaluator(ServerEvaluator myEval, int evalSID)
+	[WebMethod(Description="Upload an evaluator")]
+	public string UploadEvaluator(ServerEvaluator myEval)
 	{
-		Console.WriteLine("eval string: " + myEval.ToString());
-		int id = 0;
+		Console.WriteLine("upload. eval string: " + myEval.ToString());
 
-		if(evalSID == Constants.ServerUndefinedID) 
-			id = myEval.InsertAtDB(false); //do insertion
-		else
-			id = myEval.Update(false); //do update
-		
-		return id;
+		string idCode;
+		Random rnd = new Random();  
+		string password = myEval.Name + rnd.Next().ToString();
+		string hashed = BCrypt.HashPassword(password, BCrypt.GenerateSalt(10));
+
+		//insert the password in the server and the hash in the client
+		myEval.Code = password;
+
+		int id = myEval.InsertAtDB(false); //do insertion
+
+		return id.ToString() + ":" + hashed;
+	}
+
+	[WebMethod(Description="Edit an evaluator")]
+	public bool EditEvaluator(ServerEvaluator clientEval, int evalSID)
+	{
+		Console.WriteLine("edit. eval string: " + clientEval.ToString());
+
+		ServerEvaluator serverEval = SqliteServer.SelectEvaluator(evalSID);
+
+		//serveEval.Code is password
+		//clientEval.Code is hash
+		bool matches = BCrypt.CheckPassword(serverEval.Code, clientEval.Code);
+		if(matches) {
+			//put the uniqueID that corresponds in server
+			clientEval.UniqueID = evalSID;
+
+			//put the pass code instead of the client password hash
+			clientEval.Code = serverEval.Code;
+
+			clientEval.Update(false); //do update
+			return true;
+		}
+			
+		return false;
 	}
 
 

Modified: trunk/glade/chronojump.glade
==============================================================================
--- trunk/glade/chronojump.glade	(original)
+++ trunk/glade/chronojump.glade	Thu Mar  5 16:29:43 2009
@@ -13939,7 +13939,7 @@
   <property name="title" translatable="yes">Message</property>
   <property name="type">GTK_WINDOW_TOPLEVEL</property>
   <property name="window_position">GTK_WIN_POS_CENTER_ALWAYS</property>
-  <property name="modal">False</property>
+  <property name="modal">True</property>
   <property name="resizable">False</property>
   <property name="destroy_with_parent">False</property>
   <property name="decorated">True</property>
@@ -26337,7 +26337,7 @@
   <property name="decorated">True</property>
   <property name="skip_taskbar_hint">False</property>
   <property name="skip_pager_hint">False</property>
-  <property name="type_hint">GDK_WINDOW_TYPE_HINT_DIALOG</property>
+  <property name="type_hint">GDK_WINDOW_TYPE_HINT_NORMAL</property>
   <property name="gravity">GDK_GRAVITY_NORTH_WEST</property>
   <property name="focus_on_map">True</property>
   <property name="urgency_hint">False</property>

Modified: trunk/sqlite_diagrams/chronojump_sqlite.dia
==============================================================================
Binary files. No diff available.

Modified: trunk/src/chronojump.cs
==============================================================================
--- trunk/src/chronojump.cs	(original)
+++ trunk/src/chronojump.cs	Thu Mar  5 16:29:43 2009
@@ -112,7 +112,6 @@
 	protected void sqliteThings () {
 		bool crashedBefore = checkIfChronojumpExitAbnormally();
 		
-
 		/* SERVER COMMUNICATION TESTS */
 		//try {
 
@@ -257,7 +256,7 @@
 		}
 
 		string versionAvailableKnown = SqlitePreferences.Select("versionAvailable");
-		if( versionAvailable != Constants.ServerOffline && versionAvailable != progVersion ) {
+		if( versionAvailableKnown.Length > 0 && versionAvailable != Constants.ServerOffline && versionAvailable != progVersion ) {
 			//versionAvailable is higher than client version
 			if(versionAvailable != versionAvailableKnown) {
 				//is the first time we know about this new version
@@ -273,7 +272,7 @@
 
 		//if chronojump chrashed before
 		if(crashedBefore) {
-			if( versionAvailableKnown != progVersion ) 
+			if( versionAvailableKnown.Length > 0 && versionAvailableKnown != progVersion ) 
 				messageToShowOnBoot += "\n" + Catalog.GetString("Chronojump crashed before.") + "\n" +
 				       Catalog.GetString("Please, update to new version: ") + versionAvailableKnown + "\n";
 			else
@@ -484,8 +483,9 @@
 
 
 		messageChrashedBefore = "\n" +
-			string.Format(Catalog.GetString("Chronojump {0} crashed before. Please, report it at forums:"), progVersion) + 
-			"\nhttp://chronojump.org\n\n"; + Catalog.GetString("Include also this file:") + "\n\n" +
+			string.Format(Catalog.GetString("Chronojump {0} crashed before. If this problem persist, please, report it at forums:"), progVersion) + 
+			"\nhttp://chronojump.org\n\n"; + Catalog.GetString("Remember to describe on Chronojump software forum how crash happened.") +
+		       "\n" + Catalog.GetString("Optionally, you can include this file:") + "\n\n" +
 			Log.GetLast() +
 			//windowsTextLog +
 			"\n\n" +	

Modified: trunk/src/gui/chronojump.cs
==============================================================================
--- trunk/src/gui/chronojump.cs	(original)
+++ trunk/src/gui/chronojump.cs	Thu Mar  5 16:29:43 2009
@@ -952,7 +952,21 @@
 	
 	private void on_menuitem_server_evaluator_data (object o, EventArgs args) {
 		ServerEvaluator myEval = SqliteServer.SelectEvaluator(1);
-		evalWin = new EvaluatorWindow(myEval);
+		//evalWin = new EvaluatorWindow(myEval);
+		evalWin = EvaluatorWindow.Show(myEval);
+		evalWin.FakeButtonAccept.Clicked += new EventHandler(on_evaluator_done);
+	}
+
+	private void on_evaluator_done (object o, EventArgs args) {
+		string versionAvailable = Server.Ping(false, "", ""); //false: don't do insertion
+		if(versionAvailable != Constants.ServerOffline) { //false: don't do insertion
+			ConfirmWindow confirmWin = ConfirmWindow.Show(Catalog.GetString("Do you want to upload evaluator data now?"), "");
+			confirmWin.Button_accept.Clicked += new EventHandler(on_evaluator_upload_accepted);
+		}
+	}
+
+	private void on_evaluator_upload_accepted (object o, EventArgs args) {
+		Server.ServerUploadEvaluator();
 	}
 
 	/* 

Modified: trunk/src/gui/evaluator.cs
==============================================================================
--- trunk/src/gui/evaluator.cs	(original)
+++ trunk/src/gui/evaluator.cs	Thu Mar  5 16:29:43 2009
@@ -91,6 +91,9 @@
 	ServerEvaluator eval;
 
 	bool creating; //true if no record found before. False if updating
+	
+	//allows to upload data (from gui/chronojump.cs) after has been inserted in sql
+	public Gtk.Button fakeButtonAccept;
 
 	static EvaluatorWindow EvaluatorWindowBox;
 	
@@ -104,14 +107,17 @@
 		//put an icon to window
 		UtilGtk.IconWindow(evaluator_window);
 		
+		fakeButtonAccept = new Gtk.Button();
+
 		this.eval = eval;
-		if(eval.Name == "")
+		if(eval.UniqueID == -1)
 			creating = true;
 		
 		createComboContinents();
 		createComboCountries();
 		
 		putNonStandardIcons();	
+		
 
 		entry_cp_other.Sensitive = false;
 	}
@@ -287,7 +293,8 @@
 		if(
 				entry_name.Text.Length > 0 &&
 				entry_email.Text.Length > 0 &&
-				label_date.Text != Constants.UndefinedDefault &&
+				label_date.Text.Length >0  && 
+				label_date.Text != Catalog.GetString(Constants.UndefinedDefault) &&
 				UtilGtk.ComboGetActive(combo_countries) != Catalog.GetString(Constants.CountryUndefined) &&
 				! radio_cp_undef.Active &&
 				! (radio_cp_other.Active && entry_cp_other.Text.Length == 0) &&
@@ -301,7 +308,9 @@
 	}
 
 	private void on_button_confiable_clicked(object o, EventArgs args) {
-		Console.WriteLine("Confiable info");
+		new DialogMessage(Constants.MessageTypes.INFO, 
+				"Currently we are creating confiable parameters.\n" + 
+				"In nearly future maybe your data can be confiable");
 	}
 	
 	private void on_button_cp1_zoom_clicked(object o, EventArgs args) {
@@ -341,67 +350,74 @@
 		entry_name.Text = eval.Name;
 		entry_email.Text = eval.Email;
 
-		DateTime dateTime = Util.DateAsDateTime(eval.DateBorn);
-		if(dateTime == DateTime.MinValue)
+		Console.Write(creating.ToString());
+		if(creating)
 			label_date.Text = Catalog.GetString(Constants.UndefinedDefault);
-		else
-			label_date.Text = dateTime.ToLongDateString();
-
-		//country stuff
-		if(eval.CountryID != Constants.CountryUndefinedID) {
-			string [] countryString = SqliteCountry.Select(eval.CountryID);
-			combo_continents.Active = UtilGtk.ComboMakeActive(continentsTranslated, 
-					Catalog.GetString(countryString[3]));
-			combo_countries.Active = UtilGtk.ComboMakeActive(countriesTranslated, 
-					Catalog.GetString(countryString[1]));
+		else {
+			dateTime = Util.DateAsDateTime(eval.DateBorn);
+			if(dateTime == DateTime.MinValue)
+				label_date.Text = Catalog.GetString(Constants.UndefinedDefault);
+			else
+				label_date.Text = dateTime.ToLongDateString();
 		}
 
-		label_confiable.Text = eval.Confiable.ToString();
+		if(! creating) {		
+			//country stuff
+			if(eval.CountryID != Constants.CountryUndefinedID) {
+				string [] countryString = SqliteCountry.Select(eval.CountryID);
+				combo_continents.Active = UtilGtk.ComboMakeActive(continentsTranslated, 
+						Catalog.GetString(countryString[3]));
+				combo_countries.Active = UtilGtk.ComboMakeActive(countriesTranslated, 
+						Catalog.GetString(countryString[1]));
+			}
 
-		TextBuffer tb = new TextBuffer (new TextTagTable());
-		tb.Text = eval.Comments;
-		textview_comments.Buffer = tb;
-
-		switch(eval.Chronometer) {
-			case "": 
-			case Constants.UndefinedDefault: 
-				radio_cp_undef.Active = true;
-			break;
-			case Constants.ChronometerCp1: 
-				radio_cp1.Active = true;
-			break;
-			case Constants.ChronometerCp2: 
-				radio_cp2.Active = true;
-			break;
-			case Constants.ChronometerCp3: 
-				radio_cp3.Active = true;
-			break;
-			default:
-				radio_cp_other.Active = true;
-				entry_cp_other.Text = eval.Chronometer;
-			break;
-		}
+			label_confiable.Text = eval.Confiable.ToString();
 
-		switch(eval.Device) {
-			case "": 
-			case Constants.UndefinedDefault: 
-				radio_device_undef.Active = true;
-			break;
-			case Constants.DeviceContactSteel: 
-				radio_contact_steel.Active = true;
-			break;
-			case Constants.DeviceContactCircuit: 
-				radio_contact_modular.Active = true;
-			break;
-			case Constants.DeviceInfrared: 
-				radio_infrared.Active = true;
-			break;
-			default:
-				radio_device_other.Active = true;
-				entry_device_other.Text = eval.Device;
-			break;
+			TextBuffer tb = new TextBuffer (new TextTagTable());
+			tb.Text = eval.Comments;
+			textview_comments.Buffer = tb;
+
+			switch(eval.Chronometer) {
+				case "": 
+				case Constants.UndefinedDefault: 
+					radio_cp_undef.Active = true;
+					break;
+				case Constants.ChronometerCp1: 
+					radio_cp1.Active = true;
+					break;
+				case Constants.ChronometerCp2: 
+					radio_cp2.Active = true;
+					break;
+				case Constants.ChronometerCp3: 
+					radio_cp3.Active = true;
+					break;
+				default:
+					radio_cp_other.Active = true;
+					entry_cp_other.Text = eval.Chronometer;
+					break;
+			}
+
+			switch(eval.Device) {
+				case "": 
+				case Constants.UndefinedDefault: 
+					radio_device_undef.Active = true;
+					break;
+				case Constants.DeviceContactSteel: 
+					radio_contact_steel.Active = true;
+					break;
+				case Constants.DeviceContactCircuit: 
+					radio_contact_modular.Active = true;
+					break;
+				case Constants.DeviceInfrared: 
+					radio_infrared.Active = true;
+					break;
+				default:
+					radio_device_other.Active = true;
+					entry_device_other.Text = eval.Device;
+					break;
+			}
 		}
-		
+
 		//show or hide button_accept
 		on_entries_required_changed(new object(), new EventArgs());
 	}
@@ -410,25 +426,28 @@
 	protected void on_button_cancel_clicked (object o, EventArgs args)
 	{
 		EvaluatorWindowBox.evaluator_window.Hide();
-		//EvaluatorWindowBox = null;
+		EvaluatorWindowBox = null;
 	}
 	
 	protected void on_delete_event (object o, DeleteEventArgs args)
 	{
 		EvaluatorWindowBox.evaluator_window.Hide();
-		//EvaluatorWindowBox = null;
+		EvaluatorWindowBox = null;
 	}
 
 	protected void on_button_accept_clicked (object o, EventArgs args)
 	{
-		//eval.UniqueID = 1;
 		eval.Name = entry_name.Text.ToString();
 		eval.Email = entry_email.Text.ToString();
-		eval.DateBorn = label_date.Text.ToString();
+		
+		string dateFull = dateTime.Day.ToString() + "/" + dateTime.Month.ToString() + "/" +
+			dateTime.Year.ToString();
+		eval.DateBorn = dateFull;
 
 		eval.CountryID = Convert.ToInt32(
 				Util.FindOnArray(':', 2, 0, UtilGtk.ComboGetActive(combo_countries), countries));
 
+		eval.Comments = textview_comments.Buffer.Text;
 
 		if(radio_cp_undef.Active)
 			eval.Chronometer = Constants.UndefinedDefault;
@@ -459,17 +478,18 @@
 		else
 			eval.Update(false);
 
+		fakeButtonAccept.Click();
+
 		EvaluatorWindowBox.evaluator_window.Hide();
-		//EvaluatorWindowBox = null;
+		EvaluatorWindowBox = null;
 	}
 
-/*	
-	public Button Button_accept 
+	public Button FakeButtonAccept 
 	{
-		set { button_accept = value; }
-		get { return button_accept; }
+		set { fakeButtonAccept = value; }
+		get { return fakeButtonAccept; }
 	}
-*/
+
 
 	~EvaluatorWindow() {}
 	

Modified: trunk/src/server.cs
==============================================================================
--- trunk/src/server.cs	(original)
+++ trunk/src/server.cs	Thu Mar  5 16:29:43 2009
@@ -567,24 +567,28 @@
 			ChronojumpServer myServer = new ChronojumpServer();
 			Log.WriteLine(myServer.ConnectDatabase());
 			
-			//get Data, TODO: do it in a gui/window
-			//ServerEvaluator myEval = new ServerEvaluator("myName", "myEmail", "myDateBorn", 
-			//		Constants.CountryUndefinedID, "myChronometer", "myDevice", false);
 			ServerEvaluator myEval = SqliteServer.SelectEvaluator(1);
 
+			bool success = false;
 			int evalSID = Convert.ToInt32(SqlitePreferences.Select("evaluatorServerID"));
-			/*
-			 * upload to server, will insert if:
-			 * if(evalSID == Constants.ServerUndefinedID) 
-			 * otherwise will update
-			 */
-			myEval.UniqueID = myServer.UploadEvaluator(myEval, evalSID);
+			if(evalSID == Constants.ServerUndefinedID) {
+				string idCode = myServer.UploadEvaluator(myEval);
+				myEval.Code = Util.FetchName(idCode);
 
-			//update evaluatorServerID locally
-			if(evalSID == Constants.ServerUndefinedID) 
-				SqlitePreferences.Update("evaluatorServerID", myEval.UniqueID.ToString(), false);
+				myEval.Update(false);
 
-			new DialogMessage(Constants.MessageTypes.INFO, "Uploaded with ID: " + myEval.UniqueID);
+				evalSID = Util.FetchID(idCode);
+				SqlitePreferences.Update("evaluatorServerID", evalSID.ToString(), false);
+				success = true;
+			} else 
+				success = myServer.EditEvaluator(myEval, evalSID);
+				
+			if(success)
+				new DialogMessage(Constants.MessageTypes.INFO, 
+						string.Format(Catalog.GetString("Successfully Uploaded evaluator with ID: {0}"), evalSID));
+			else
+				new DialogMessage(Constants.MessageTypes.WARNING, 
+						string.Format(Catalog.GetString("Evaluator {0} has not been correctly uploaded. Maybe codes doesn't match."), evalSID));
 			
 			Log.WriteLine(myServer.DisConnectDatabase());
 		} catch {

Modified: trunk/src/serverEvaluator.cs
==============================================================================
--- trunk/src/serverEvaluator.cs	(original)
+++ trunk/src/serverEvaluator.cs	Thu Mar  5 16:29:43 2009
@@ -27,6 +27,7 @@
 public partial class ServerEvaluator
 {
 	private int uniqueID;
+	private string code;
 	private string name;
 	private string email;
 	private string dateBorn;
@@ -41,7 +42,8 @@
 	public ServerEvaluator() {
 	}
 
-	public ServerEvaluator(string name, string email, string dateBorn, int countryID, string chronometer, string device, string comments, bool confiable) {
+	public ServerEvaluator(string code, string name, string email, string dateBorn, int countryID, string chronometer, string device, string comments, bool confiable) {
+		this.code = code;
 		this.name = name;
 		this.email = email;
 		this.dateBorn = dateBorn;
@@ -53,12 +55,13 @@
 	}
 
 	public int InsertAtDB(bool dbconOpened){
-		int myID = SqliteServer.InsertEvaluator(dbconOpened, name, email, dateBorn, countryID, chronometer, device, comments, confiable);
+		int myID = SqliteServer.InsertEvaluator(dbconOpened, code, name, email, dateBorn, countryID, chronometer, device, comments, confiable);
 		return myID;
 	}	
 
 	public int Update (bool dbconOpened){
-		SqliteServer.UpdateEvaluator(dbconOpened, uniqueID, name, email, dateBorn, countryID, chronometer, device, comments, confiable);
+		//confiable will not get updated
+		SqliteServer.UpdateEvaluator(dbconOpened, uniqueID, code, name, email, dateBorn, countryID, chronometer, device, comments, confiable);
 		return uniqueID;
 	}	
 
@@ -77,6 +80,11 @@
 	//"Private, internal, and protected members do not get serialized.  
 	//If the accessor is not specific, it is private by default (and will not get serialized)."
 	
+	public string Code {
+		get { return code; }
+		set { code = value; }
+	}
+
 	public string Name {
 		get { return name; }
 		set { name = value; }

Modified: trunk/src/sqlite/server.cs
==============================================================================
--- trunk/src/sqlite/server.cs	(original)
+++ trunk/src/sqlite/server.cs	Thu Mar  5 16:29:43 2009
@@ -51,6 +51,7 @@
 		dbcmd.CommandText = 
 			"CREATE TABLE " + Constants.ServerEvaluatorTable + " ( " +
 			"uniqueID INTEGER PRIMARY KEY, " +
+			"code TEXT, " +
 			"name TEXT, " +
 			"email TEXT, " +
 			"dateborn TEXT, " +
@@ -89,7 +90,7 @@
 		return myReturn;
 	}
 
-	public static int InsertEvaluator(bool dbconOpened, string name, string email, string dateBorn, 
+	public static int InsertEvaluator(bool dbconOpened, string code, string name, string email, string dateBorn, 
 			int countryID, string chronometer, string device, string comments, bool confiable)
 	{
 		if(! dbconOpened)
@@ -98,8 +99,9 @@
 		string uniqueID = "NULL";
 
 		string myString = "INSERT INTO " + Constants.ServerEvaluatorTable + 
-			" (uniqueID, name, email, dateBorn, countryID, chronometer, device, comments, confiable) VALUES (" + 
-			uniqueID + ", '" + name + "', '" + 
+			" (uniqueID, code, name, email, dateBorn, countryID, chronometer, device, comments, confiable) VALUES (" + 
+			uniqueID + ", '" + 
+			code + "', '" + name + "', '" + 
 			email + "', '" + dateBorn + "', " +
 			countryID + ", '" + chronometer + "', '" + 
 			device + "', '" + comments + "', " +
@@ -120,13 +122,14 @@
 		return myReturn;
 	}
 	
-	public static void UpdateEvaluator(bool dbconOpened, int uniqueID, string name, string email, string dateBorn, 
+	public static void UpdateEvaluator(bool dbconOpened, int uniqueID, string code, string name, string email, string dateBorn, 
 			int countryID, string chronometer, string device, string comments, bool confiable)
 	{
 		if(! dbconOpened)
 			dbcon.Open();
 		dbcmd.CommandText = "UPDATE " + Constants.ServerEvaluatorTable + " " +
-			" SET name = '" + name +
+			" SET code = '" + code +
+			"' , name = '" + name +
 			"' , email = '" + email +
 			"' , dateBorn = '" + dateBorn +
 			"' , countryID = " + countryID +
@@ -134,7 +137,7 @@
 			"', device = '" + device +
 			"', comments = '" + comments +
 			//"', confiable = " + Util.BoolToInt(confiable) + //security: update cannot change confiable
-			" WHERE uniqueID == " + uniqueID;
+			"' WHERE uniqueID == " + uniqueID;
 		Log.WriteLine(dbcmd.CommandText.ToString());
 		dbcmd.ExecuteNonQuery();
 
@@ -155,16 +158,21 @@
 		reader = dbcmd.ExecuteReader();
 	
 		ServerEvaluator myEval = new ServerEvaluator();
+
+		//will return a -1 on uniqueID to know that evaluator data is not in the database		
+		myEval.UniqueID = -1; 
+
 		while(reader.Read()) {
 			myEval.UniqueID = Convert.ToInt32(reader[0].ToString()); 
-			myEval.Name = reader[1].ToString(); 
-			myEval.Email = reader[2].ToString(); 
-			myEval.DateBorn = reader[3].ToString();
-			myEval.CountryID = Convert.ToInt32(reader[4].ToString());
-			myEval.Chronometer = reader[5].ToString();
-			myEval.Device = reader[6].ToString();
-			myEval.Comments = reader[7].ToString();
-			myEval.Confiable = Util.IntToBool(Convert.ToInt32(reader[8].ToString())); 
+			myEval.Code = reader[1].ToString(); 
+			myEval.Name = reader[2].ToString(); 
+			myEval.Email = reader[3].ToString(); 
+			myEval.DateBorn = reader[4].ToString();
+			myEval.CountryID = Convert.ToInt32(reader[5].ToString());
+			myEval.Chronometer = reader[6].ToString();
+			myEval.Device = reader[7].ToString();
+			myEval.Comments = reader[8].ToString();
+			myEval.Confiable = Util.IntToBool(Convert.ToInt32(reader[9].ToString())); 
 		}
 
 		dbcon.Close();

Modified: trunk/version.txt
==============================================================================
--- trunk/version.txt	(original)
+++ trunk/version.txt	Thu Mar  5 16:29:43 2009
@@ -1 +1 @@
-0.8.2.5
+0.8.2.6



[Date Prev][Date Next]   [Thread Prev][Thread Next]   [Thread Index] [Date Index] [Author Index]