{-# LANGUAGE OverloadedStrings #-} {- Copyright 2016 Joey Hess - - Licensed under the GNU AGPL version 3 or higher. -} module HTTP.Server (runServer) where import HTTP import HTTP.ProofOfWork import HTTP.RateLimit import Types import Types.Storage import Tunables import Storage.Local import Serialization () import Servant import Network.Wai import Network.Wai.Handler.Warp import Control.Monad.IO.Class import Control.Concurrent import Control.Concurrent.STM import Data.String import qualified Data.ByteString as B data ServerState = ServerState { obscurerRequest :: TMVar () , storageDirectory :: Maybe LocalStorageDirectory , rateLimiter :: RateLimiter } newServerState :: Maybe LocalStorageDirectory -> IO ServerState newServerState d = ServerState <$> newEmptyTMVarIO <*> pure d <*> newRateLimiter runServer :: Maybe LocalStorageDirectory -> String -> Port -> IO () runServer d bindaddress port = do st <- newServerState d _ <- forkIO $ obscurerThread st runSettings settings (app st) where settings = setHost host $ setPort port $ defaultSettings host = fromString bindaddress serverStorage :: ServerState -> Storage serverStorage st = localStorage (storageDir $ storageDirectory st) "server" app :: ServerState -> Application app st = serve userAPI (server st) userAPI :: Proxy HttpAPI userAPI = Proxy server :: ServerState -> Server HttpAPI server st = motd :<|> getObject st :<|> putObject st :<|> countObjects st motd :: Handler Motd motd = return $ Motd "Hello World!" getObject :: ServerState -> StorableObjectIdent -> Maybe ProofOfWork -> Handler (POWGuarded StorableObject) getObject st i pow = rateLimit (rateLimiter st) pow i $ do r <- liftIO $ retrieveShare (serverStorage st) dummyShareNum i liftIO $ requestObscure st case r of RetrieveSuccess (Share _n o) -> return o RetrieveFailure _ -> throwError err404 putObject :: ServerState -> StorableObjectIdent -> Maybe ProofOfWork -> StorableObject -> Handler (POWGuarded StoreResult) putObject st i pow o = rateLimit (rateLimiter st) pow i $ do if validObjectsize o then do r <- liftIO $ storeShare (serverStorage st) i (Share dummyShareNum o) liftIO $ requestObscure st return r else return $ StoreFailure "invalid object size" validObjectsize :: StorableObject -> Bool validObjectsize o = any (sz ==) knownObjectSizes where sz = B.length (fromStorableObject o) countObjects :: ServerState -> Maybe ProofOfWork -> Handler (POWGuarded CountResult) countObjects st pow = rateLimit (rateLimiter st) pow NoPOWIdent $ liftIO $ countShares $ serverStorage st -- | 1 is a dummy value; the server does not know the actual share numbers. dummyShareNum :: ShareNum dummyShareNum = 1 -- | This thread handles obscuring the shares after put and get operations. -- Since obscuring can be an expensive process when there are many shares, -- the thread runs a maximum of once per half-hour. obscurerThread :: ServerState -> IO () obscurerThread st = do _ <- obscureShares (serverStorage st) putStrLn "obscured shares" threadDelay (1000000*60*30) _ <- atomically $ takeTMVar (obscurerRequest st) obscurerThread st requestObscure :: ServerState -> IO () requestObscure st = do _ <- atomically $ tryPutTMVar (obscurerRequest st) () return ()