serveGet invalidation
This commit is contained in:
parent
80d2ffc79a
commit
2228d56db3
3 changed files with 23 additions and 17 deletions
|
@ -164,8 +164,8 @@ testGet = do
|
||||||
res <- liftIO $ clientGet (mkClientEnv mgr burl)
|
res <- liftIO $ clientGet (mkClientEnv mgr burl)
|
||||||
(P2P.ProtocolVersion 3)
|
(P2P.ProtocolVersion 3)
|
||||||
(B64Key (fromJust $ deserializeKey ("SHA256E-s1048576000--e3b67ce72aa2571c799d6419e3e36828461ac1c78f8ef300c7f9c8ae671c517f" :: String)))
|
(B64Key (fromJust $ deserializeKey ("SHA256E-s1048576000--e3b67ce72aa2571c799d6419e3e36828461ac1c78f8ef300c7f9c8ae671c517f" :: String)))
|
||||||
(B64UUID (toUUID ("cu" :: String)))
|
|
||||||
(B64UUID (toUUID ("f11773f0-11e1-45b2-9805-06db16768efe" :: String)))
|
(B64UUID (toUUID ("f11773f0-11e1-45b2-9805-06db16768efe" :: String)))
|
||||||
|
(B64UUID (toUUID ("cu" :: String)))
|
||||||
[]
|
[]
|
||||||
Nothing
|
Nothing
|
||||||
Nothing
|
Nothing
|
||||||
|
|
36
P2P/Http.hs
36
P2P/Http.hs
|
@ -12,6 +12,7 @@
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
{-# LANGUAGE TypeApplications #-}
|
{-# LANGUAGE TypeApplications #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
{-# LANGUAGE BangPatterns #-}
|
||||||
|
|
||||||
module P2P.Http (
|
module P2P.Http (
|
||||||
module P2P.Http,
|
module P2P.Http,
|
||||||
|
@ -188,38 +189,45 @@ serveGet st su apiver (B64Key k) cu bypass baf startat sec auth = do
|
||||||
void $ liftIO $ forkIO $ waitfinal endv finalv conn annexworker
|
void $ liftIO $ forkIO $ waitfinal endv finalv conn annexworker
|
||||||
(Len len, bs) <- liftIO $ atomically $ takeTMVar bsv
|
(Len len, bs) <- liftIO $ atomically $ takeTMVar bsv
|
||||||
bv <- liftIO $ newMVar (L.toChunks bs)
|
bv <- liftIO $ newMVar (L.toChunks bs)
|
||||||
|
szv <- liftIO $ newMVar 0
|
||||||
let streamer = S.SourceT $ \s -> s =<< return
|
let streamer = S.SourceT $ \s -> s =<< return
|
||||||
(stream (bv, endv, validityv, finalv))
|
(stream (bv, szv, len, endv, validityv, finalv))
|
||||||
return $ addHeader len streamer
|
return $ addHeader len streamer
|
||||||
where
|
where
|
||||||
stream (bv, endv, validityv, finalv) =
|
stream (bv, szv, len, endv, validityv, finalv) =
|
||||||
S.fromActionStep B.null $
|
S.fromActionStep B.null $
|
||||||
modifyMVar bv $ nextchunk $
|
modifyMVar bv $ nextchunk szv $
|
||||||
checkvalidity (endv, validityv, finalv)
|
checkvalidity szv len endv validityv finalv
|
||||||
|
|
||||||
nextchunk atend (b:bs)
|
nextchunk szv atend (b:bs)
|
||||||
| not (B.null b) = return (bs, b)
|
| not (B.null b) = do
|
||||||
| otherwise = nextchunk atend bs
|
modifyMVar szv $ \sz ->
|
||||||
nextchunk atend [] = do
|
let !sz' = sz + fromIntegral (B.length b)
|
||||||
|
in return (sz', ())
|
||||||
|
return (bs, b)
|
||||||
|
| otherwise = nextchunk szv atend bs
|
||||||
|
nextchunk _szv atend [] = do
|
||||||
endbit <- atend
|
endbit <- atend
|
||||||
return ([], endbit)
|
return ([], endbit)
|
||||||
|
|
||||||
checkvalidity (endv, validityv, finalv) =
|
checkvalidity szv len endv validityv finalv =
|
||||||
ifM (atomically $ isEmptyTMVar endv)
|
ifM (atomically $ isEmptyTMVar endv)
|
||||||
( do
|
( do
|
||||||
atomically $ putTMVar endv ()
|
atomically $ putTMVar endv ()
|
||||||
validity <- atomically $ takeTMVar validityv
|
validity <- atomically $ takeTMVar validityv
|
||||||
|
sz <- takeMVar szv
|
||||||
atomically $ putTMVar finalv ()
|
atomically $ putTMVar finalv ()
|
||||||
-- When the key's content is invalid,
|
-- When the key's content is invalid,
|
||||||
-- indicate that to the client by padding
|
-- indicate that to the client by padding
|
||||||
-- the response, so it is not the same
|
-- the response if necessary, so it is not
|
||||||
-- length indicated by the DataLengthHeader.
|
-- the same length indicated by the
|
||||||
|
-- DataLengthHeader.
|
||||||
return $ case validity of
|
return $ case validity of
|
||||||
Nothing -> mempty
|
Nothing -> mempty
|
||||||
Just Valid -> mempty
|
Just Valid -> mempty
|
||||||
Just Invalid -> "XXXXXXX"
|
Just Invalid
|
||||||
-- FIXME: need to count bytes and emit
|
| sz == len -> "X"
|
||||||
-- something to make it invalid
|
| otherwise -> mempty
|
||||||
, pure mempty
|
, pure mempty
|
||||||
)
|
)
|
||||||
|
|
||||||
|
|
|
@ -31,8 +31,6 @@ Planned schedule of work:
|
||||||
* http server and client are working, remaining
|
* http server and client are working, remaining
|
||||||
server API endpoints need wiring up and testing.
|
server API endpoints need wiring up and testing.
|
||||||
|
|
||||||
* serveGet needs to handle invalidation
|
|
||||||
|
|
||||||
* I have a file `servant.hs` in the httpproto branch that works through some
|
* I have a file `servant.hs` in the httpproto branch that works through some
|
||||||
of the bytestring streaming issues.
|
of the bytestring streaming issues.
|
||||||
|
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue