not yet working but progress
This commit is contained in:
parent
2a3b0f9434
commit
e741ba9251
3 changed files with 36 additions and 15 deletions
|
@ -52,6 +52,7 @@ library
|
||||||
, wai
|
, wai
|
||||||
, exceptions
|
, exceptions
|
||||||
, req
|
, req
|
||||||
|
, modern-uri
|
||||||
, base64
|
, base64
|
||||||
, crypton
|
, crypton
|
||||||
, crypton-x509
|
, crypton-x509
|
||||||
|
|
|
@ -3,10 +3,12 @@
|
||||||
module Fedi.Requests where
|
module Fedi.Requests where
|
||||||
|
|
||||||
import Data.Aeson qualified as A
|
import Data.Aeson qualified as A
|
||||||
|
import Fedi.Helpers
|
||||||
import Fedi.UserDetails
|
import Fedi.UserDetails
|
||||||
import Fedi.Crypto
|
import Fedi.Crypto
|
||||||
import Network.HTTP.Req qualified as Req
|
import Network.HTTP.Req qualified as Req
|
||||||
import Data.ByteString.Lazy qualified as BSL
|
import Data.ByteString.Lazy qualified as BSL
|
||||||
|
import Text.URI qualified as URI
|
||||||
|
|
||||||
sendPost
|
sendPost
|
||||||
:: (A.FromJSON output, A.ToJSON input)
|
:: (A.FromJSON output, A.ToJSON input)
|
||||||
|
@ -17,15 +19,19 @@ sendPost
|
||||||
sendPost details url payload = do
|
sendPost details url payload = do
|
||||||
let encoded = BSL.toStrict $ A.encode payload
|
let encoded = BSL.toStrict $ A.encode payload
|
||||||
signed <- sign details encoded
|
signed <- sign details encoded
|
||||||
|
uri <- URI.mkURI $ fromString url
|
||||||
|
(url', scheme) <- maybe (throw "couldn't parse uri") pure (Req.useHttpsURI uri)
|
||||||
|
print ("url", url')
|
||||||
|
|
||||||
Req.runReq Req.defaultHttpConfig do
|
Req.runReq Req.defaultHttpConfig do
|
||||||
r <-
|
r <-
|
||||||
Req.req
|
Req.req
|
||||||
Req.POST
|
Req.POST
|
||||||
(Req.https $ fromString url)
|
url'
|
||||||
(Req.ReqBodyBs encoded)
|
(Req.ReqBodyBs encoded)
|
||||||
Req.jsonResponse
|
Req.jsonResponse
|
||||||
( Req.header "ContentType" "application/activity+json"
|
( scheme
|
||||||
|
<> Req.header "ContentType" "application/activity+json"
|
||||||
<> Req.header "Digest" signed.signedDigest
|
<> Req.header "Digest" signed.signedDigest
|
||||||
<> Req.header "Signature" signed.signedMessage
|
<> Req.header "Signature" signed.signedMessage
|
||||||
)
|
)
|
||||||
|
@ -33,13 +39,18 @@ sendPost details url payload = do
|
||||||
|
|
||||||
sendGet :: (A.FromJSON a) => String -> IO a
|
sendGet :: (A.FromJSON a) => String -> IO a
|
||||||
sendGet url = do
|
sendGet url = do
|
||||||
|
uri <- URI.mkURI $ fromString url
|
||||||
|
(url', scheme) <- maybe (throw "couldn't parse uri") pure (Req.useHttpsURI uri)
|
||||||
|
print ("url", url')
|
||||||
|
|
||||||
Req.runReq Req.defaultHttpConfig do
|
Req.runReq Req.defaultHttpConfig do
|
||||||
r <-
|
r <-
|
||||||
Req.req
|
Req.req
|
||||||
Req.GET
|
Req.GET
|
||||||
(Req.https $ fromString url)
|
url'
|
||||||
Req.NoReqBody
|
Req.NoReqBody
|
||||||
Req.jsonResponse
|
Req.jsonResponse
|
||||||
( Req.header "ContentType" "application/activity+json"
|
( scheme
|
||||||
|
<> Req.header "ContentType" "application/activity+json"
|
||||||
)
|
)
|
||||||
pure $ Req.responseBody r
|
pure $ Req.responseBody r
|
||||||
|
|
|
@ -12,10 +12,10 @@ import Web.Twain.Types qualified as Twain
|
||||||
import Data.Text qualified as T
|
import Data.Text qualified as T
|
||||||
import Network.Wai qualified as Wai
|
import Network.Wai qualified as Wai
|
||||||
import Control.Monad.IO.Class (liftIO)
|
import Control.Monad.IO.Class (liftIO)
|
||||||
import Control.Monad.Catch (catch)
|
import Control.Monad.Catch (catch, displayException, SomeException)
|
||||||
import Text.ParserCombinators.ReadP qualified as P
|
import Text.ParserCombinators.ReadP qualified as P
|
||||||
import Data.Text.Encoding qualified as T
|
import Data.Text.Encoding qualified as T
|
||||||
import Data.Text.Encoding.Base64 qualified as Base64
|
import Data.ByteString.Base64 qualified as Base64
|
||||||
import Data.ByteString.Lazy qualified as BSL
|
import Data.ByteString.Lazy qualified as BSL
|
||||||
import Fedi.Crypto
|
import Fedi.Crypto
|
||||||
|
|
||||||
|
@ -32,16 +32,18 @@ handleInbox handle = do
|
||||||
activity <- checkSignatureAndParseBody
|
activity <- checkSignatureAndParseBody
|
||||||
response <- handle activity
|
response <- handle activity
|
||||||
Twain.send response
|
Twain.send response
|
||||||
handler `catch` \(Error e) -> do
|
handler `catch` \(e :: SomeException) -> do
|
||||||
liftIO $ print e
|
liftIO $ putStrLn (displayException e)
|
||||||
Twain.send $ Twain.status Twain.status500 $ Twain.text (T.pack e)
|
Twain.send $
|
||||||
|
Twain.status Twain.status500 $
|
||||||
|
Twain.text "Internal Server Error 500"
|
||||||
|
|
||||||
-- | Check the signature of the sender and parse the body of the request.
|
-- | Check the signature of the sender and parse the body of the request.
|
||||||
checkSignatureAndParseBody :: Twain.ResponderM AnyActivity
|
checkSignatureAndParseBody :: Twain.ResponderM AnyActivity
|
||||||
checkSignatureAndParseBody = do
|
checkSignatureAndParseBody = do
|
||||||
-- get info
|
-- get info
|
||||||
request <- Twain.request
|
request <- Twain.request
|
||||||
liftIO $ print $ Twain.requestHeaders request
|
liftIO $ print ("headers", Twain.requestHeaders request)
|
||||||
body <- liftIO (Wai.strictRequestBody request)
|
body <- liftIO (Wai.strictRequestBody request)
|
||||||
sigheader <- parseSignature =<< Twain.header "Signature"
|
sigheader <- parseSignature =<< Twain.header "Signature"
|
||||||
digest <- Twain.header "Digest" >>=
|
digest <- Twain.header "Digest" >>=
|
||||||
|
@ -82,20 +84,23 @@ data SignatureHeader
|
||||||
headers :: [T.Text]
|
headers :: [T.Text]
|
||||||
, -- | Contains the signature
|
, -- | Contains the signature
|
||||||
signature :: ByteString
|
signature :: ByteString
|
||||||
|
, components :: [(Component, String)]
|
||||||
}
|
}
|
||||||
|
deriving Show
|
||||||
|
|
||||||
data Component
|
data Component
|
||||||
= KeyId
|
= KeyId
|
||||||
| Headers
|
| Headers
|
||||||
| Signature
|
| Signature
|
||||||
deriving Eq
|
| Other String
|
||||||
|
deriving (Eq, Show)
|
||||||
|
|
||||||
parseSignature :: MonadThrow m => Maybe T.Text -> m SignatureHeader
|
parseSignature :: MonadThrow m => Maybe T.Text -> m SignatureHeader
|
||||||
parseSignature minput = do
|
parseSignature minput = do
|
||||||
input <- maybe (throw "no signature.") (pure . T.unpack) minput
|
input <- maybe (throw "no signature.") (pure . T.unpack) minput
|
||||||
case P.readP_to_S parser input of
|
case P.readP_to_S parser input of
|
||||||
[(sig, "")] -> pure sig
|
[(sig, "")] -> pure sig
|
||||||
_ -> throw "error parsing signature."
|
xs -> throw $ "error parsing signature: " <> show xs
|
||||||
where
|
where
|
||||||
lookup' a b =
|
lookup' a b =
|
||||||
maybe (fail "error parsing signature") pure $ lookup a b
|
maybe (fail "error parsing signature") pure $ lookup a b
|
||||||
|
@ -104,9 +109,8 @@ parseSignature minput = do
|
||||||
keyId <- lookup' KeyId components
|
keyId <- lookup' KeyId components
|
||||||
headers <- T.split (==' ') . T.pack <$> lookup' Headers components
|
headers <- T.split (==' ') . T.pack <$> lookup' Headers components
|
||||||
signature <-
|
signature <-
|
||||||
( T.encodeUtf8
|
( Base64.decodeBase64Lenient
|
||||||
. Base64.decodeBase64Lenient
|
. fromString
|
||||||
. T.pack
|
|
||||||
) <$> lookup' Signature components
|
) <$> lookup' Signature components
|
||||||
pure SignatureHeader{..}
|
pure SignatureHeader{..}
|
||||||
component = P.choice
|
component = P.choice
|
||||||
|
@ -122,4 +126,9 @@ parseSignature minput = do
|
||||||
_ <- P.string "signature="
|
_ <- P.string "signature="
|
||||||
url <- P.between (P.char '\"') (P.char '\"') (P.munch1 (/= '\"'))
|
url <- P.between (P.char '\"') (P.char '\"') (P.munch1 (/= '\"'))
|
||||||
pure (Signature, url)
|
pure (Signature, url)
|
||||||
|
, do
|
||||||
|
key <- P.munch1 (/= '=')
|
||||||
|
_ <- P.char '='
|
||||||
|
value <- P.between (P.char '\"') (P.char '\"') (P.munch1 (/= '\"'))
|
||||||
|
pure (Other key, value)
|
||||||
]
|
]
|
||||||
|
|
Loading…
Add table
Reference in a new issue