summaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
-rw-r--r--CHANGELOG1
-rw-r--r--HTTP/Server.hs10
-rw-r--r--Tunables.hs17
3 files changed, 23 insertions, 5 deletions
diff --git a/CHANGELOG b/CHANGELOG
index 1859882..e2a8be4 100644
--- a/CHANGELOG
+++ b/CHANGELOG
@@ -4,6 +4,7 @@ keysafe (0.20160820) UNRELEASED; urgency=medium
* Removed embedded copy of secret-sharing library, since finite-field
only supports prime fields. This caused shares to be twice the size of
the input value.
+ * Reduced object size to 32kb due to share size doubling.
-- Joey Hess <id@joeyh.name> Mon, 22 Aug 2016 13:56:16 -0400
diff --git a/HTTP/Server.hs b/HTTP/Server.hs
index cce91cd..a26cd5e 100644
--- a/HTTP/Server.hs
+++ b/HTTP/Server.hs
@@ -10,6 +10,7 @@ module HTTP.Server (runServer) where
import HTTP
import Types
import Types.Storage
+import Tunables
import Storage.Local
import Serialization ()
import Servant
@@ -65,9 +66,12 @@ getObject st i _pow = do
putObject :: ServerState -> StorableObjectIdent -> Maybe ProofOfWork -> StorableObject -> Handler (ProofOfWorkRequirement StoreResult)
putObject st i _pow o = do
- r <- liftIO $ storeShare serverStorage i (Share dummyShareNum o)
- liftIO $ requestObscure st
- return (Result r)
+ if validObjectsize o
+ then do
+ r <- liftIO $ storeShare serverStorage i (Share dummyShareNum o)
+ liftIO $ requestObscure st
+ return (Result r)
+ else throwError err413 -- Request Entity Too Large
countObjects :: ServerState -> Maybe ProofOfWork -> Handler (ProofOfWorkRequirement CountResult)
countObjects _st _pow = liftIO $ Result <$> countShares serverStorage
diff --git a/Tunables.hs b/Tunables.hs
index ce7aa6e..3fa700a 100644
--- a/Tunables.hs
+++ b/Tunables.hs
@@ -7,8 +7,10 @@
module Tunables where
+import Types
import Cost
import qualified Crypto.Argon2 as Argon2
+import qualified Data.ByteString as B
-- | To determine the tunables used for a key name the expensive hash of the
-- name is calculated, using a particular configuration, and if the
@@ -38,6 +40,8 @@ data Tunables = Tunables
-- ^ a StorableObject is exactly this many bytes in size
-- (must be a multiple of AES block size 16, and cannot be smaller
-- than 256 bytes)
+ , shareOverhead :: Int
+ -- ^ Share encoding overhead as a multiple of the objectSize
, nameGenerationTunable :: NameGenerationTunable
, keyEncryptionKeyTunable :: KeyEncryptionKeyTunable
, encryptionTunable :: EncryptionTunable
@@ -82,7 +86,8 @@ data EncryptionTunable = UseAES256
defaultTunables :: Tunables
defaultTunables = Tunables
{ shareParams = ShareParams { totalObjects = 3, neededObjects = 2 }
- , objectSize = 1024*64 -- 64 kb
+ , objectSize = 1024*32 -- 32 kb
+ , shareOverhead = 2
-- The nameGenerationHash was benchmarked at 661 seconds CPU time
-- on a 2 core Intel(R) Core(TM) i5-4210Y CPU @ 1.50GHz.
-- Since cost is measured per core, we double that.
@@ -114,7 +119,8 @@ defaultTunables = Tunables
testModeTunables :: Tunables
testModeTunables = Tunables
{ shareParams = ShareParams { totalObjects = 3, neededObjects = 2 }
- , objectSize = 1024*64
+ , objectSize = 1024*32
+ , shareOverhead = 2
, nameGenerationTunable = NameGenerationTunable
{ nameGenerationHash = weakargon2 (CPUCost (Seconds (2*600)))
}
@@ -127,3 +133,10 @@ testModeTunables = Tunables
}
where
weakargon2 c = UseArgon2 c Argon2.defaultHashOptions
+
+validObjectsize :: StorableObject -> Bool
+validObjectsize o = any (sz ==) knownsizes
+ where
+ sz = B.length (fromStorableObject o)
+ knownsizes = map (\t -> objectSize t * shareOverhead t)
+ (map snd knownTunings)