sign and verify and follow
This commit is contained in:
parent
9017d953be
commit
13bda9e6ae
8 changed files with 52 additions and 27 deletions
24
app/DB.hs
24
app/DB.hs
|
@ -1,11 +1,22 @@
|
||||||
|
|
||||||
|
-- needed because of a compiler bug with OverloadedRecordDot:
|
||||||
|
-- <https://play.haskell.org/saved/Xq0ZFrQi>
|
||||||
|
{-# language FieldSelectors #-}
|
||||||
|
|
||||||
-- | Database interaction
|
-- | Database interaction
|
||||||
module DB where
|
module DB
|
||||||
|
( module DB
|
||||||
|
, DB.Int64
|
||||||
|
)
|
||||||
|
where
|
||||||
|
|
||||||
import Data.Text qualified as T
|
import Data.Text qualified as T
|
||||||
import Database.Sqlite.Easy qualified as DB
|
import Database.Sqlite.Easy qualified as DB
|
||||||
import Fedi
|
import Fedi
|
||||||
import GHC.Stack (HasCallStack)
|
import GHC.Stack (HasCallStack)
|
||||||
import Text.RawString.QQ
|
import Text.RawString.QQ
|
||||||
|
import Control.Monad.IO.Class (liftIO)
|
||||||
|
import Data.Typeable
|
||||||
|
|
||||||
-----------------------
|
-----------------------
|
||||||
|
|
||||||
|
@ -16,7 +27,8 @@ data DB
|
||||||
{ getNotes :: IO [Note]
|
{ getNotes :: IO [Note]
|
||||||
, getNote :: DB.Int64 -> IO (Maybe Note)
|
, getNote :: DB.Int64 -> IO (Maybe Note)
|
||||||
, insertNote :: NoteEntry -> IO (DB.Int64, Note)
|
, insertNote :: NoteEntry -> IO (DB.Int64, Note)
|
||||||
, insertFollower :: FollowerEntry -> IO DB.Int64
|
, insertFollower ::
|
||||||
|
forall a. Typeable a => FollowerEntry -> (DB.Int64 -> IO a) -> IO a
|
||||||
, deleteFollower :: FollowerEntry -> IO DB.Int64
|
, deleteFollower :: FollowerEntry -> IO DB.Int64
|
||||||
, getFollowers :: IO [Follower]
|
, getFollowers :: IO [Follower]
|
||||||
}
|
}
|
||||||
|
@ -61,7 +73,9 @@ mkDB connstr details = do
|
||||||
, insertNote =
|
, insertNote =
|
||||||
\note -> DB.withPool pool (insertNoteToDb (actorUrl details) note)
|
\note -> DB.withPool pool (insertNoteToDb (actorUrl details) note)
|
||||||
, insertFollower =
|
, insertFollower =
|
||||||
\follower -> DB.withPool pool (insertFollowerToDb follower)
|
\follower handle -> DB.withPool pool $ DB.transaction do
|
||||||
|
id' <- insertFollowerToDb follower
|
||||||
|
liftIO $ handle id'
|
||||||
, deleteFollower =
|
, deleteFollower =
|
||||||
\follower -> DB.withPool pool (deleteFollowerFromDb follower)
|
\follower -> DB.withPool pool (deleteFollowerFromDb follower)
|
||||||
, getFollowers =
|
, getFollowers =
|
||||||
|
@ -233,8 +247,8 @@ deleteFollowerSQL :: FollowerEntry -> (DB.SQL, [DB.SQLData])
|
||||||
deleteFollowerSQL follower =
|
deleteFollowerSQL follower =
|
||||||
( [r|
|
( [r|
|
||||||
DELETE FROM follower
|
DELETE FROM follower
|
||||||
WHERE followId = ? AND actor = ?
|
WHERE follow_id = ? AND actor = ?
|
||||||
RETURNING followId
|
RETURNING follow_id
|
||||||
|]
|
|]
|
||||||
,
|
,
|
||||||
[ DB.SQLText follower.followId
|
[ DB.SQLText follower.followId
|
||||||
|
|
|
@ -4,7 +4,6 @@ import DB
|
||||||
import Data.Aeson qualified as A
|
import Data.Aeson qualified as A
|
||||||
import Data.Functor ((<&>))
|
import Data.Functor ((<&>))
|
||||||
import Data.SecureMem (secureMemFromByteString)
|
import Data.SecureMem (secureMemFromByteString)
|
||||||
import Data.String (fromString)
|
|
||||||
import Data.Text qualified as T
|
import Data.Text qualified as T
|
||||||
import Data.Text.Encoding qualified as T
|
import Data.Text.Encoding qualified as T
|
||||||
import Data.Text.IO qualified as T
|
import Data.Text.IO qualified as T
|
||||||
|
|
|
@ -1,11 +1,9 @@
|
||||||
module Routes where
|
module Routes where
|
||||||
|
|
||||||
import Control.Monad.IO.Class (liftIO)
|
|
||||||
import DB
|
import DB
|
||||||
import Data.Aeson qualified as A
|
import Data.Aeson qualified as A
|
||||||
import Data.Functor ((<&>))
|
import Data.Functor ((<&>))
|
||||||
import Data.Maybe (maybeToList)
|
import Data.Maybe (maybeToList)
|
||||||
import Data.String (fromString)
|
|
||||||
import Fedi qualified as Fedi
|
import Fedi qualified as Fedi
|
||||||
import Html
|
import Html
|
||||||
import Lucid qualified as H
|
import Lucid qualified as H
|
||||||
|
@ -140,20 +138,26 @@ handleInbox db detailsFile activity = do
|
||||||
Just id'' -> do
|
Just id'' -> do
|
||||||
if object == Fedi.LLink (Fedi.Link $ Fedi.actorUrl details)
|
if object == Fedi.LLink (Fedi.Link $ Fedi.actorUrl details)
|
||||||
then do
|
then do
|
||||||
liftIO do
|
let
|
||||||
insertId <- db.insertFollower FollowerEntry
|
followerEntry = ( FollowerEntry
|
||||||
{ actorId = fromString actor.unwrap
|
{ actorId = fromString actor.unwrap
|
||||||
, followId = fromString id''.unwrap
|
, followId = fromString id''.unwrap
|
||||||
}
|
}
|
||||||
(result :: A.Value) <- Fedi.sendPost
|
|
||||||
details
|
|
||||||
(id''.unwrap <> "/inbox")
|
|
||||||
( Fedi.makeAccept
|
|
||||||
follow
|
|
||||||
(Fedi.actorUrl details <> "/accepts/follows/" <> show insertId)
|
|
||||||
)
|
)
|
||||||
print result
|
callback =
|
||||||
pure $ Fedi.jsonLD "{}"
|
( \(insertId :: DB.Int64) -> do
|
||||||
|
(result :: A.Value) <- Fedi.sendPost
|
||||||
|
details
|
||||||
|
(actor.unwrap <> "/inbox")
|
||||||
|
( Fedi.makeAccept
|
||||||
|
follow
|
||||||
|
(Fedi.actorUrl details <> "/accepts/follows/" <> show insertId)
|
||||||
|
)
|
||||||
|
print result
|
||||||
|
pure $ Fedi.jsonLD "{}"
|
||||||
|
)
|
||||||
|
liftIO do
|
||||||
|
insertFollower db followerEntry callback
|
||||||
else Twain.next
|
else Twain.next
|
||||||
Nothing ->
|
Nothing ->
|
||||||
Twain.next
|
Twain.next
|
||||||
|
|
|
@ -61,6 +61,7 @@ library
|
||||||
, crypton
|
, crypton
|
||||||
, crypton-x509
|
, crypton-x509
|
||||||
, cryptostore
|
, cryptostore
|
||||||
|
, raw-strings-qq
|
||||||
, case-insensitive
|
, case-insensitive
|
||||||
, http-types
|
, http-types
|
||||||
|
|
||||||
|
|
|
@ -13,8 +13,14 @@ import Data.ByteString.Base64 qualified as Base64
|
||||||
import Data.Base64.Types qualified as Base64
|
import Data.Base64.Types qualified as Base64
|
||||||
import Data.Text qualified as T
|
import Data.Text qualified as T
|
||||||
|
|
||||||
|
-- import Debug.Trace
|
||||||
|
|
||||||
verifyPub :: MonadThrow m => ByteString -> ByteString -> ByteString -> m Bool
|
verifyPub :: MonadThrow m => ByteString -> ByteString -> ByteString -> m Bool
|
||||||
verifyPub pubkeypem sig message = do
|
verifyPub pubkeypem sig message = do
|
||||||
|
-- traceShowM ("pubkeypem", pubkeypem)
|
||||||
|
-- traceShowM ("sig", sig)
|
||||||
|
-- traceShowM ("mssage", message)
|
||||||
|
|
||||||
pubkey <-
|
pubkey <-
|
||||||
case Crypto.readPubKeyFileFromMemory pubkeypem of
|
case Crypto.readPubKeyFileFromMemory pubkeypem of
|
||||||
[Crypto.PubKeyRSA pubkey'] -> pure pubkey'
|
[Crypto.PubKeyRSA pubkey'] -> pure pubkey'
|
||||||
|
|
|
@ -33,7 +33,7 @@ checkSignatureAndParseBody :: Twain.ResponderM AnyActivity
|
||||||
checkSignatureAndParseBody = do
|
checkSignatureAndParseBody = do
|
||||||
-- get info
|
-- get info
|
||||||
request <- Twain.request
|
request <- Twain.request
|
||||||
liftIO $ print ("headers", 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" >>=
|
||||||
|
@ -58,7 +58,7 @@ makeSignatureString request (map (T.encodeUtf8 . T.toLower) -> headers) = do
|
||||||
let
|
let
|
||||||
requestHeaders = Wai.requestHeaders request
|
requestHeaders = Wai.requestHeaders request
|
||||||
method = T.encodeUtf8 $ T.toLower $ T.decodeUtf8 $ Wai.requestMethod request
|
method = T.encodeUtf8 $ T.toLower $ T.decodeUtf8 $ Wai.requestMethod request
|
||||||
path = T.encodeUtf8 (T.intercalate "/" $ Wai.pathInfo request)
|
path = "/" <> T.encodeUtf8 (T.intercalate "/" $ Wai.pathInfo request)
|
||||||
<> HTTP.renderQuery True (Wai.queryString request)
|
<> HTTP.renderQuery True (Wai.queryString request)
|
||||||
requestTarget = method <> " " <> path
|
requestTarget = method <> " " <> path
|
||||||
let
|
let
|
||||||
|
@ -115,8 +115,7 @@ 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 <-
|
||||||
( decodeBase64
|
( fromString
|
||||||
. fromString
|
|
||||||
) <$> lookup' Signature components
|
) <$> lookup' Signature components
|
||||||
P.eof
|
P.eof
|
||||||
pure SignatureHeader{..}
|
pure SignatureHeader{..}
|
||||||
|
|
|
@ -29,6 +29,8 @@ signSignature details host requestTarget body = do
|
||||||
components = []
|
components = []
|
||||||
signatureString = makeSignatureString host requestTarget date digest
|
signatureString = makeSignatureString host requestTarget date digest
|
||||||
|
|
||||||
|
-- BS.putStr $ signatureString <> "\n"
|
||||||
|
|
||||||
signed <- sign details.privatePem signatureString
|
signed <- sign details.privatePem signatureString
|
||||||
|
|
||||||
let
|
let
|
||||||
|
|
|
@ -270,8 +270,8 @@ instance (A.FromJSON a) => A.FromJSON (TypeActivity a) where
|
||||||
atype <- A.parseJSON object
|
atype <- A.parseJSON object
|
||||||
flip (A.withObject "TypeActivity") object \value -> do
|
flip (A.withObject "TypeActivity") object \value -> do
|
||||||
actor <- value A..: "actor"
|
actor <- value A..: "actor"
|
||||||
target <- value A..: "target"
|
target <- value A..:? "target"
|
||||||
origin <- value A..: "origin"
|
origin <- value A..:? "origin"
|
||||||
pure TypeActivity {..}
|
pure TypeActivity {..}
|
||||||
|
|
||||||
-- type Announce = Object (TypeActivity TypeAnnounce)
|
-- type Announce = Object (TypeActivity TypeAnnounce)
|
||||||
|
|
Loading…
Add table
Reference in a new issue