This commit is contained in:
Dmitry Zuikov 2024-03-13 11:32:31 +03:00
parent 411b436d0a
commit 130444181f
3 changed files with 77 additions and 3 deletions

View File

@ -2,29 +2,52 @@
module HttpWorker where module HttpWorker where
import HBS2.Prelude import HBS2.Prelude
import HBS2.Hash
import HBS2.Actors.Peer import HBS2.Actors.Peer
import HBS2.Storage import HBS2.Storage
import HBS2.Data.Detect
import HBS2.Data.Types.Refs import HBS2.Data.Types.Refs
import HBS2.Merkle (AnnMetaData) import HBS2.Merkle
import HBS2.Peer.Proto import HBS2.Peer.Proto
import HBS2.Events import HBS2.Events
import HBS2.Storage.Operations.ByteString
import PeerTypes import PeerTypes
import PeerConfig import PeerConfig
import RefLog ( doRefLogBroadCast ) import RefLog ( doRefLogBroadCast )
import Data.Config.Suckless
import Data.ByteString.Lazy qualified as LBS import Data.ByteString.Lazy qualified as LBS
import Network.HTTP.Types.Status import Network.HTTP.Types.Status
import Network.Wai.Middleware.RequestLogger import Network.Wai.Middleware.RequestLogger
import Text.InterpolatedString.Perl6 (qc) import Text.InterpolatedString.Perl6 (qc)
import Web.Scotty import Web.Scotty
import Network.Wai (responseStream)
import Network.Wai.Internal (Response(..))
import Data.ByteString.Builder (byteString, Builder)
import Data.Either
import Codec.Serialise (deserialiseOrFail) import Codec.Serialise (deserialiseOrFail)
import Data.Aeson (object, (.=)) import Data.Aeson (object, (.=))
import Data.ByteString.Lazy.Char8 qualified as LBS8
import Control.Monad.Reader import Control.Monad.Reader
import Lens.Micro.Platform (view) import Lens.Micro.Platform (view)
import System.FilePath
import Control.Monad.Except
import Control.Monad.Trans.Cont
{- HLINT ignore "Functor law" -}
-- TODO: introduce-http-of-off-feature -- TODO: introduce-http-of-off-feature
extractMetadataHash :: Hash HbSync -> LBS.ByteString -> Maybe (Hash HbSync)
extractMetadataHash what blob =
case tryDetect what blob of
MerkleAnn (MTreeAnn {_mtaMeta = AnnHashRef h, _mtaCrypt = NullEncryption}) -> Just h
_ -> Nothing
httpWorker :: forall e s m . ( MyPeer e httpWorker :: forall e s m . ( MyPeer e
, MonadIO m , MonadIO m
, HasStorage m , HasStorage m
@ -53,6 +76,56 @@ httpWorker (PeerConfig syn) pmeta e = do
Just n -> do Just n -> do
json n json n
get "/tree/:hash" do
what <- param @String "hash" <&> fromString
void $ flip runContT pure do
callCC $ \exit -> do
mblob <- liftIO $ getBlock sto what
blob <- ContT $ maybe1 mblob (status status404)
mh <- ContT $ maybe1 (extractMetadataHash what blob) (status status404)
metabs <- lift (getBlock sto mh)
meta <- ContT (maybe1 metabs (status status404))
<&> LBS8.unpack
<&> fromRight mempty . parseTop
let tp = headDef "application/octet-stream"
[ show (pretty w)
| ListVal [SymbolVal "mime-type:", LitStrVal w] <- meta
]
let fn = headMay
[ show (pretty w)
| ListVal [SymbolVal "file-name:", LitStrVal w] <- meta
]
liftIO $ print $ pretty meta
case fn of
Just x | takeExtension x == ".html" -> pure ()
| otherwise -> lift $ do
addHeader "content-disposition" [qc|attachment; filename="{x}"|]
_ -> pure ()
lift $ addHeader "content-type" (fromString tp)
elbs <- lift $ runExceptT $ readFromMerkle sto (SimpleKey what)
case elbs of
Left{} -> lift $ status status404
Right lbs -> lift do
stream $ \write flush -> do
for_ (LBS.toChunks lbs) $ \chunk -> do
write $ byteString chunk
flush
get "/cat/:hash" do get "/cat/:hash" do
what <- param @String "hash" <&> fromString what <- param @String "hash" <&> fromString
blob <- liftIO $ getBlock sto what blob <- liftIO $ getBlock sto what

View File

@ -69,6 +69,7 @@ common common-deps
, warp , warp
, http-conduit , http-conduit
, http-types , http-types
, wai
, wai-extra , wai-extra
, unliftio , unliftio
, unliftio-core , unliftio-core

View File

@ -563,8 +563,8 @@ main = join . customExecParser (prefs showHelpOnError) $
magicLoadDefault magic magicLoadDefault magic
mime <- magicFile magic fn mime <- magicFile magic fn
pure [ "file-name:" <+> pretty (takeFileName fn) pure [ "file-name:" <+> dquotes (pretty $ takeFileName fn)
, "mime-type:" <+> pretty mime , "mime-type:" <+> dquotes (pretty mime)
] ]
let s = LBS8.pack $ show $ vcat meta let s = LBS8.pack $ show $ vcat meta