try adding followers and message signatures

This commit is contained in:
me 2024-12-17 10:46:59 +02:00
parent c596417dcc
commit 396bbb7969
16 changed files with 531 additions and 226 deletions

109
app/DB.hs
View file

@ -15,8 +15,9 @@ data DB
= DB = DB
{ getNotes :: IO [Note] { getNotes :: IO [Note]
, getNote :: DB.Int64 -> IO (Maybe Note) , getNote :: DB.Int64 -> IO (Maybe Note)
, insertNote :: NoteEntry -> IO ObjectId , insertNote :: NoteEntry -> IO (DB.Int64, Note)
, insertFollower :: FollowerEntry -> IO DB.Int64 , insertFollower :: FollowerEntry -> IO DB.Int64
, getFollowers :: IO [Follower]
} }
-- * Data types -- * Data types
@ -35,6 +36,13 @@ data FollowerEntry
, actorId :: T.Text , actorId :: T.Text
} }
data Follower
= Follower
{ myid :: T.Text
, followId :: T.Text
, actorId :: T.Text
}
----------------------- -----------------------
-- * Handler smart constructor -- * Handler smart constructor
@ -46,13 +54,15 @@ mkDB connstr details = do
pure pure
DB DB
{ getNotes = { getNotes =
DB.withPool pool (getNotesFromDb $ actorUrl details) DB.withPool pool getNotesFromDb
, getNote = , getNote =
\noteid -> DB.withPool pool (getNoteFromDb noteid $ actorUrl details) \noteid -> DB.withPool pool (getNoteFromDb noteid)
, 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 -> DB.withPool pool (insertFollowerToDb follower)
, getFollowers =
DB.withPool pool (getFollowersFromDb $ actorUrl details)
} }
----------------------- -----------------------
@ -110,18 +120,18 @@ migrateDown = \case
-- * Database actions -- * Database actions
getNotesFromDb :: Url -> DB.SQLite [Note] getNotesFromDb :: DB.SQLite [Note]
getNotesFromDb url = getNotesFromDb =
map decodeNoteRow <$> uncurry DB.runWith (getNotesSQL url) map (snd . decodeNoteRow) <$> uncurry DB.runWith getNotesSQL
getNoteFromDb :: DB.Int64 -> Url -> DB.SQLite (Maybe Note) getNoteFromDb :: DB.Int64 -> DB.SQLite (Maybe Note)
getNoteFromDb noteid url = do getNoteFromDb noteid = do
n <- map decodeNoteRow <$> uncurry DB.runWith (getNoteSQL noteid url) n <- map (snd . decodeNoteRow) <$> uncurry DB.runWith (getNoteSQL noteid)
pure (listToMaybe n) pure (listToMaybe n)
insertNoteToDb :: Url -> NoteEntry -> DB.SQLite ObjectId insertNoteToDb :: Url -> NoteEntry -> DB.SQLite (DB.Int64, Note)
insertNoteToDb actor note = do insertNoteToDb actor note = do
[n] <- map decodeNoteIdRow <$> uncurry DB.runWith (insertNoteSQL actor note) [n] <- map decodeNoteRow <$> uncurry DB.runWith (insertNoteSQL actor note)
pure n pure n
insertFollowerToDb :: FollowerEntry -> DB.SQLite DB.Int64 insertFollowerToDb :: FollowerEntry -> DB.SQLite DB.Int64
@ -129,13 +139,18 @@ insertFollowerToDb follower = do
[n] <- map decodeIntRow <$> uncurry DB.runWith (insertFollowerSQL follower) [n] <- map decodeIntRow <$> uncurry DB.runWith (insertFollowerSQL follower)
pure n pure n
getFollowersFromDb :: Url -> DB.SQLite [Follower]
getFollowersFromDb url =
map decodeFollowerRow <$> uncurry DB.runWith (getFollowersSQL url)
-- ** SQL -- ** SQL
getNotesSQL :: Url -> (DB.SQL, [DB.SQLData]) getNotesSQL :: (DB.SQL, [DB.SQLData])
getNotesSQL url = getNotesSQL =
( [r| ( [r|
SELECT SELECT
? || '/notes/' || id, id,
actor || '/notes/' || id,
published, published,
actor, actor,
content, content,
@ -146,14 +161,15 @@ getNotesSQL url =
WHERE inReplyTo IS NULL WHERE inReplyTo IS NULL
ORDER BY published DESC ORDER BY published DESC
|] |]
, [DB.SQLText $ T.pack url] , []
) )
getNoteSQL :: DB.Int64 -> Url -> (DB.SQL, [DB.SQLData]) getNoteSQL :: DB.Int64 -> (DB.SQL, [DB.SQLData])
getNoteSQL noteid url = getNoteSQL noteid =
( [r| ( [r|
SELECT SELECT
? || '/notes/' || id, id as nid,
actor || '/notes/' || id,
published, published,
actor, actor,
content, content,
@ -164,7 +180,7 @@ getNoteSQL noteid url =
WHERE note.id = ? WHERE note.id = ?
ORDER BY published DESC ORDER BY published DESC
|] |]
, [DB.SQLText $ T.pack url, DB.SQLInteger noteid] , [DB.SQLInteger noteid]
) )
insertNoteSQL :: Url -> NoteEntry -> (DB.SQL, [DB.SQLData]) insertNoteSQL :: Url -> NoteEntry -> (DB.SQL, [DB.SQLData])
@ -172,7 +188,16 @@ insertNoteSQL actor note =
( [r| ( [r|
INSERT INTO note(actor, inReplyTo, content, name, url) INSERT INTO note(actor, inReplyTo, content, name, url)
VALUES (?, ?, ?, ?, ?) VALUES (?, ?, ?, ?, ?)
RETURNING cast(id as text) RETURNING
id as nid,
actor || '/notes/' || id,
published,
actor,
content,
name,
inReplyTo,
url
|] |]
, ,
[ DB.SQLText (T.pack actor) [ DB.SQLText (T.pack actor)
@ -196,13 +221,25 @@ insertFollowerSQL follower =
] ]
) )
getFollowersSQL :: Url -> (DB.SQL, [DB.SQLData])
getFollowersSQL url =
( [r|
SELECT
? || '/followers/' || id,
follow_id,
actor
FROM follower
|]
, [DB.SQLText $ T.pack url]
)
----------------------- -----------------------
-- ** Decode row -- ** Decode row
decodeNoteRow :: [DB.SQLData] -> Note decodeNoteRow :: [DB.SQLData] -> (DB.Int64, Note)
decodeNoteRow = \case decodeNoteRow = \case
[ DB.SQLText noteid [ DB.SQLInteger noteid
, DB.SQLText noteidurl
, DB.SQLText published , DB.SQLText published
, DB.SQLText actor , DB.SQLText actor
, DB.SQLText content , DB.SQLText content
@ -212,9 +249,9 @@ decodeNoteRow = \case
] -> ] ->
let let
emptyNote = emptyUserNote $ T.unpack actor emptyNote = emptyUserNote $ T.unpack actor
in in (noteid,
emptyNote emptyNote
{ id = Just $ ObjectId $ T.unpack noteid { id = Just $ ObjectId $ T.unpack noteidurl
, published = Just $ read (T.unpack published) , published = Just $ read (T.unpack published)
, attributedTo = Just $ LLink $ Link $ T.unpack actor , attributedTo = Just $ LLink $ Link $ T.unpack actor
, inReplyTo = LLink . Link <$> inReplyTo , inReplyTo = LLink . Link <$> inReplyTo
@ -225,26 +262,34 @@ decodeNoteRow = \case
emptyNote.otype emptyNote.otype
{ likes = { likes =
emptyNote.otype.likes emptyNote.otype.likes
{ id = Just $ ObjectId $ T.unpack noteid <> "/likes" { id = Just $ ObjectId $ T.unpack noteidurl <> "/likes"
} }
, shares = , shares =
emptyNote.otype.shares emptyNote.otype.shares
{ id = Just $ ObjectId $ T.unpack noteid <> "/shares" { id = Just $ ObjectId $ T.unpack noteidurl <> "/shares"
} }
} }
} })
row -> error $ "Couldn't decode row as Note: " <> show row row -> error $ "Couldn't decode row as Note: " <> show row
decodeNoteIdRow :: [DB.SQLData] -> ObjectId
decodeNoteIdRow = \case
[DB.SQLText noteid] -> ObjectId $ T.unpack noteid
row -> error $ "Couldn't decode row as NoteId: " <> show row
decodeIntRow :: [DB.SQLData] -> DB.Int64 decodeIntRow :: [DB.SQLData] -> DB.Int64
decodeIntRow = \case decodeIntRow = \case
[DB.SQLInteger fid] -> fid [DB.SQLInteger fid] -> fid
row -> error $ "Couldn't decode row as NoteId: " <> show row row -> error $ "Couldn't decode row as NoteId: " <> show row
decodeFollowerRow :: [DB.SQLData] -> Follower
decodeFollowerRow = \case
[ DB.SQLText myid
, DB.SQLText follower_id
, DB.SQLText actor
] ->
Follower
{ myid = myid
, followId = follower_id
, actorId = actor
}
row -> error $ "Couldn't decode row as Follower: " <> show row
nullableString :: DB.SQLData -> Maybe (Maybe String) nullableString :: DB.SQLData -> Maybe (Maybe String)
nullableString = \case nullableString = \case
DB.SQLText text -> Just (Just $ T.unpack text) DB.SQLText text -> Just (Just $ T.unpack text)

View file

@ -12,6 +12,7 @@ import Database.Sqlite.Easy qualified as Sqlite
import Network.Wai.Handler.Warp (Port, run) import Network.Wai.Handler.Warp (Port, run)
import Network.Wai.Middleware.HttpAuth (basicAuth) import Network.Wai.Middleware.HttpAuth (basicAuth)
import Network.Wai.Middleware.RequestLogger qualified as Logger import Network.Wai.Middleware.RequestLogger qualified as Logger
import Network.Wai.Middleware.RequestSizeLimit qualified as Limit
import Network.Wai.Middleware.Routed qualified as Wai import Network.Wai.Middleware.Routed qualified as Wai
import Routes import Routes
import System.Environment (getArgs, lookupEnv) import System.Environment (getArgs, lookupEnv)
@ -113,7 +114,11 @@ runServer port authMiddleware app = do
, "(ctrl-c to quit)" , "(ctrl-c to quit)"
] ]
auth <- Wai.routedMiddleware matchAdmin <$> pure authMiddleware auth <- Wai.routedMiddleware matchAdmin <$> pure authMiddleware
run port (Logger.logStdoutDev $ auth app) run port $
( Logger.logStdoutDev
. Limit.requestSizeLimitMiddleware Limit.defaultRequestSizeLimitSettings
. auth
) app
matchAdmin :: [T.Text] -> Bool matchAdmin :: [T.Text] -> Bool
matchAdmin = any (== "admin") matchAdmin = any (== "admin")

View file

@ -11,16 +11,8 @@ import Html
import Lucid qualified as H import Lucid qualified as H
import System.IO.Unsafe (unsafePerformIO) import System.IO.Unsafe (unsafePerformIO)
import Web.Twain qualified as Twain import Web.Twain qualified as Twain
import Network.HTTP.Req import Data.Text qualified as T
( runReq import Control.Concurrent.Async qualified as Async
, defaultHttpConfig
, req
, POST(POST)
, ReqBodyJson(ReqBodyJson)
, jsonResponse
, responseBody
, https
)
routes :: DB -> FilePath -> [Twain.Middleware] routes :: DB -> FilePath -> [Twain.Middleware]
routes db detailsFile = routes db detailsFile =
@ -102,7 +94,7 @@ routes db detailsFile =
url <- Twain.param "url" url <- Twain.param "url"
details <- liftIO $ fetchUserDetails detailsFile details <- liftIO $ fetchUserDetails detailsFile
noteid <- (noteid, note) <-
liftIO $ liftIO $
db.insertNote db.insertNote
NoteEntry NoteEntry
@ -112,7 +104,9 @@ routes db detailsFile =
, url = if trim url == "" then Nothing else Just url , url = if trim url == "" then Nothing else Just url
} }
Twain.send $ Twain.redirect302 (fromString ("/" <> details.username <> "/notes/" <> noteid.unwrap)) liftIO $ sendFollowers details db (Fedi.ActivityCreate $ noteToCreate note)
Twain.send $ Twain.redirect302 (fromString ("/" <> details.username <> "/notes/" <> show noteid))
] ]
trim :: String -> String trim :: String -> String
@ -144,7 +138,8 @@ handleInbox db detailsFile activity = do
{ actorId = fromString actor.unwrap { actorId = fromString actor.unwrap
, followId = fromString id''.unwrap , followId = fromString id''.unwrap
} }
(result :: A.Value) <- sendRequest (result :: A.Value) <- Fedi.sendPost
details
(id''.unwrap <> "/inbox") (id''.unwrap <> "/inbox")
( Fedi.makeAccept ( Fedi.makeAccept
follow follow
@ -159,14 +154,10 @@ handleInbox db detailsFile activity = do
liftIO (print activity) liftIO (print activity)
Twain.next Twain.next
sendRequest :: (A.ToJSON input, A.FromJSON output) => Fedi.Url -> input -> IO output sendFollowers :: Fedi.UserDetails -> DB -> Fedi.AnyActivity -> IO ()
sendRequest url payload = do sendFollowers details db message = do
runReq defaultHttpConfig do followers <- db.getFollowers
r <- Fedi.for_ followers \follower -> do
req Async.async $ do
POST result <- Fedi.sendPost @A.Value details (T.unpack follower.actorId <> "/inbox") message
(https $ fromString url) print (follower.actorId, A.encode result)
(ReqBodyJson payload)
jsonResponse
mempty
pure $ responseBody r

View file

@ -1 +1,3 @@
packages: *.cabal packages: *.cabal
constraints: cryptostore +use_crypton

View file

@ -17,10 +17,13 @@ library
import: warnings import: warnings
exposed-modules: exposed-modules:
Fedi Fedi
Fedi.Requests
Fedi.Helpers Fedi.Helpers
Fedi.Types Fedi.Types
Fedi.Types.Helpers
Fedi.UserDetails Fedi.UserDetails
Fedi.Webfinger Fedi.Webfinger
Fedi.Crypto
Fedi.Routes Fedi.Routes
Fedi.Routes.Helpers Fedi.Routes.Helpers
@ -46,6 +49,13 @@ library
, twain , twain
, mime-types , mime-types
, time , time
, wai
, exceptions
, req
, base64
, crypton
, crypton-x509
, cryptostore
hs-source-dirs: src hs-source-dirs: src
default-language: GHC2021 default-language: GHC2021
@ -84,7 +94,6 @@ executable fedi
, raw-strings-qq , raw-strings-qq
, securemem , securemem
, lucid2 , lucid2
, req
hs-source-dirs: app hs-source-dirs: app
default-language: GHC2021 default-language: GHC2021

View file

@ -1,7 +1,10 @@
module Fedi (module Export) where module Fedi (module Export) where
import Fedi.Crypto as Export
import Fedi.Helpers as Export import Fedi.Helpers as Export
import Fedi.Routes as Export import Fedi.Routes as Export
import Fedi.Types as Export import Fedi.Types as Export
import Fedi.Types.Helpers as Export
import Fedi.UserDetails as Export import Fedi.UserDetails as Export
import Fedi.Webfinger as Export import Fedi.Webfinger as Export
import Fedi.Requests as Export

75
src/Fedi/Crypto.hs Normal file
View file

@ -0,0 +1,75 @@
{-# language RecordWildCards #-}
module Fedi.Crypto where
import Crypto.Hash qualified as Crypto
import Crypto.PubKey.RSA.PSS qualified as Crypto
import Crypto.Store.X509 qualified as Crypto
import Crypto.Store.PKCS8 qualified as Crypto
import Data.X509 qualified as Crypto
import Fedi.Helpers
import Fedi.UserDetails
import Data.ByteString.Base64 qualified as Base64
import Data.Base64.Types qualified as Base64
verifyPub :: ByteString -> ByteString -> ByteString -> Bool
verifyPub pubkeypem sig message =
let
pubkey = case Crypto.readPubKeyFileFromMemory pubkeypem of
[Crypto.PubKeyRSA pubkey'] -> pubkey'
_ -> error "failed to read pubkey pem"
in
Crypto.verify (Crypto.defaultPSSParams Crypto.SHA256) pubkey message sig
verifyDigest :: ByteString -> ByteString -> ByteString -> Bool
verifyDigest pubkeypem sig digest' =
let
pubkey = case Crypto.readPubKeyFileFromMemory pubkeypem of
[Crypto.PubKeyRSA pubkey'] -> pubkey'
_ -> error "failed to read pubkey pem"
digest = Crypto.hash digest'
in
Crypto.verifyDigest (Crypto.defaultPSSParams Crypto.SHA256) pubkey digest sig
sign :: UserDetails -> ByteString -> IO Signed
sign details message = do
-- get private key
privkeypem <- Crypto.readKeyFile details.privatePem
let
privateKey = case privkeypem of
[Crypto.Unprotected (Crypto.PrivKeyRSA privkey)] -> privkey
_ -> error $ "error reading local private key from '" <> details.privatePem <> "'."
-- sign message
signedMessage <- either (error . show) id <$>
Crypto.sign Nothing (Crypto.defaultPSSParams Crypto.SHA256) privateKey message
-- sign digest
let
digest :: Crypto.Digest Crypto.SHA256
digest = Crypto.hash message
signedDigest <- either (error . show) id <$>
Crypto.signDigest Nothing (Crypto.defaultPSSParams Crypto.SHA256) privateKey digest
-- return
pure Signed{..}
data Signed
= Signed
{ signedMessage :: ByteString
, signedDigest :: ByteString
}
deriving Show
ppSigned :: Signed -> String
ppSigned signed =
unlines
[ "Signature"
, "{ signedMessage = " <> encodeBase64 signed.signedMessage
, ", signedDigest = " <> encodeBase64 signed.signedDigest
, "}"
]
encodeBase64 :: ByteString -> String
encodeBase64 = show . Base64.extractBase64 . Base64.encodeBase64

View file

@ -1,168 +1,17 @@
module Fedi.Helpers where module Fedi.Helpers
( module Export
)
where
import Data.Text qualified as T
import Fedi.Types
import Fedi.UserDetails import Fedi.UserDetails
import Data.Foldable as Export
-- | An empty activitypub Object. import Data.Maybe as Export (fromMaybe, listToMaybe, maybeToList)
emptyObject :: Object () import Data.String as Export (fromString)
emptyObject = import Data.Text as Export (Text)
Object import Data.ByteString as Export (ByteString)
{ id = Nothing import Data.Time as Export (UTCTime)
, otype = () import Data.Traversable as Export
, content = Nothing import GHC.Generics as Export (Generic)
, published = Nothing import Control.Monad as Export
, replies = Nothing import Data.Functor as Export
, attachment = Nothing import Data.Function as Export
, attributedTo = Nothing
, tag = Nothing
, to = Nothing
, cc = Nothing
, inReplyTo = Nothing
, url = Nothing
, name = Nothing
, icon = Nothing
, image = Nothing
, preview = Nothing
, summary = Nothing
, updated = Nothing
, mediaType = Nothing
}
-- | Create an activitypub Actor.
makeActor :: UserDetails -> Actor
makeActor details =
let
actor = actorUrl details
in
ActorPerson $
emptyObject
{ id = Just $ ObjectId actor
, otype =
TypePerson
{ preferredUsername = details.username
, inbox = Link $ actor <> "/inbox"
, outbox = Link $ actor <> "/outbox"
, following = Link $ actor <> "/following"
, followers = Link $ actor <> "/followers"
, publicKey =
PublicKey
{ pkid = actor <> "#main-key"
, owner = actor
, publicKeyPem = details.publicPem
}
}
, url = Nothing -- details.url
, name = Just $ StringName details.name
, icon = Just $ makeImage details.icon
, image = Just $ makeImage details.image
, summary = Just $ T.pack details.summary
}
makeCreateNote :: Note -> Create
makeCreateNote note =
emptyObject
{ id = (\oid -> ObjectId $ oid.unwrap <> "/create") <$> note.id
, otype =
TypeActivity
{ actor = maybe (Link "") getAttributedTo note.attributedTo
, atype = TypeCreate note
, target = Nothing
, origin = Nothing
}
}
-- | Create an user's empty 'Note'.
emptyUserNote :: Url -> Note
emptyUserNote actor =
emptyObject
{ otype = emptyTypeNote
, attributedTo = Just (LLink $ Link actor)
, to = Just [Link "https://www.w3.org/ns/activitystreams#Public"]
, cc = Just [Link $ actor <> "/followers"]
}
-- | An empty 'Note'.
emptyTypeNote :: TypeNote
emptyTypeNote =
TypeNote
{ likes = emptyUnorderedCollection
, shares = emptyUnorderedCollection
, replies = emptyUnorderedCollection
, sensitive = False
}
-- | Create an activitypub Image.
makeImage :: Url -> Image
makeImage link =
emptyObject
{ otype = TypeImage
, mediaType = Just ("image/png" :: MediaType)
, url = Just link
}
-- | An empty 'Collection'.
emptyUnorderedCollection :: Collection a
emptyUnorderedCollection =
emptyObject
{ otype =
CollectionType
{ ctype =
UnorderedCollectionType
{ items = []
}
, first = Nothing
, last = Nothing
, current = Nothing
}
}
-- | An empty 'OrderedCollection'.
emptyOrderedCollection :: OrderedCollection a
emptyOrderedCollection =
emptyObject
{ otype =
CollectionType
{ ctype =
OrderedCollectionType
{ orderedItems = []
}
, first = Nothing
, last = Nothing
, current = Nothing
}
}
-- | Create an empty 'OrderedCollectionPage'.
emptyOrderedCollectionPage :: Url -> OrderedCollectionPage a
emptyOrderedCollectionPage url =
emptyObject
{ otype =
CollectionType
{ ctype =
OrderedCollectionPageType
{ partOf = url
, prev = Nothing
, next = Nothing
, porderedItems = []
}
, first = Nothing
, last = Nothing
, current = Nothing
}
}
makeAccept :: Follow -> Url -> Accept
makeAccept theirFollow myfollowId =
emptyObject
{ id = Just $ ObjectId myfollowId
, otype =
TypeActivity
{ actor = theirFollow.otype.actor
, atype = TypeAccept
{ object = ActivityFollow theirFollow
}
, target = Nothing
, origin = Nothing
}
}

45
src/Fedi/Requests.hs Normal file
View file

@ -0,0 +1,45 @@
{-# language DataKinds #-}
module Fedi.Requests where
import Data.Aeson qualified as A
import Fedi.UserDetails
import Fedi.Crypto
import Network.HTTP.Req qualified as Req
import Data.ByteString.Lazy qualified as BSL
sendPost
:: (A.FromJSON output, A.ToJSON input)
=> UserDetails
-> String
-> input
-> IO output
sendPost details url payload = do
let encoded = BSL.toStrict $ A.encode payload
signed <- sign details encoded
Req.runReq Req.defaultHttpConfig do
r <-
Req.req
Req.POST
(Req.https $ fromString url)
(Req.ReqBodyBs encoded)
Req.jsonResponse
( Req.header "ContentType" "application/activity+json"
<> Req.header "Digest" signed.signedDigest
<> Req.header "Signature" signed.signedMessage
)
pure $ Req.responseBody r
sendGet :: (A.FromJSON a) => String -> IO a
sendGet url = do
Req.runReq Req.defaultHttpConfig do
r <-
Req.req
Req.GET
(Req.https $ fromString url)
Req.NoReqBody
Req.jsonResponse
( Req.header "ContentType" "application/activity+json"
)
pure $ Req.responseBody r

View file

@ -3,6 +3,7 @@ module Fedi.Routes.Follow where
import Data.Aeson qualified as A import Data.Aeson qualified as A
import Fedi.Helpers import Fedi.Helpers
import Fedi.Types import Fedi.Types
import Fedi.Types.Helpers
import Fedi.UserDetails import Fedi.UserDetails
import Fedi.Routes.Helpers import Fedi.Routes.Helpers
import Web.Twain qualified as Twain import Web.Twain qualified as Twain

View file

@ -1,8 +1,10 @@
module Fedi.Routes.Helpers where module Fedi.Routes.Helpers where
import Data.Aeson qualified as A
import Data.ByteString qualified as BS import Data.ByteString qualified as BS
import Data.ByteString.Lazy qualified as BSL import Data.ByteString.Lazy qualified as BSL
import Web.Twain qualified as Twain import Web.Twain qualified as Twain
import Control.Monad.Catch (throwM)
jsonLD :: BSL.ByteString -> Twain.Response jsonLD :: BSL.ByteString -> Twain.Response
jsonLD = jsonLD =
@ -19,3 +21,9 @@ checkContentTypeAccept request =
&& ("profile=\"https://www.w3.org/ns/activitystreams\"" `BS.isInfixOf` bs) && ("profile=\"https://www.w3.org/ns/activitystreams\"" `BS.isInfixOf` bs)
) )
Nothing -> False Nothing -> False
parseJson :: (A.FromJSON a) => BSL.ByteString -> Twain.ResponderM a
parseJson body = do
case A.eitherDecode body of
Left msg -> throwM $ Twain.HttpError Twain.status400 msg
Right a -> pure a

View file

@ -1,9 +1,20 @@
module Fedi.Routes.Inbox where module Fedi.Routes.Inbox where
import Fedi.Requests
import Fedi.Types import Fedi.Types
import Fedi.UserDetails import Fedi.UserDetails
import Fedi.Routes.Helpers
import Fedi.Helpers
import Web.Twain qualified as Twain import Web.Twain qualified as Twain
import Web.Twain.Types qualified as Twain import Web.Twain.Types qualified as Twain
import Data.Text qualified as T
import Network.Wai qualified as Wai
import Control.Monad.IO.Class (liftIO)
import Text.ParserCombinators.ReadP qualified as P
import Data.Text.Encoding qualified as T
import Data.Text.Encoding.Base64 qualified as Base64
import Data.ByteString.Lazy qualified as BSL
import Fedi.Crypto
-- * Inbox -- * Inbox
@ -13,7 +24,93 @@ matchInbox details =
handleInbox :: (AnyActivity -> Twain.ResponderM Twain.Response) -> Twain.ResponderM b handleInbox :: (AnyActivity -> Twain.ResponderM Twain.Response) -> Twain.ResponderM b
handleInbox handle = do handleInbox handle = do
activity <- Twain.fromBody activity <- checkSignatureAndParseBody
-- sig <- Twain.header "Signature"
response <- handle activity response <- handle activity
Twain.send response Twain.send response
-- | Check the signature of the sender and parse the body of the request.
checkSignatureAndParseBody :: Twain.ResponderM AnyActivity
checkSignatureAndParseBody = do
-- get info
request <- Twain.request
body <- liftIO (Wai.strictRequestBody request)
sigheader <- parseSignature <$> Twain.header "Signature"
digest <-
maybe (error "missing header Digest") T.encodeUtf8 <$> Twain.header "Digest"
(person :: Person) <- liftIO $ sendGet sigheader.keyId
let personPkid = person.otype.publicKey.pkid
let personPublicKey = pemToBS person.otype.publicKey.publicKeyPem
-- check
liftIO $
checkSignature personPkid personPublicKey sigheader digest (BSL.toStrict body)
-- parse the body and return it
parseJson body
checkSignature
:: Url -> ByteString -> SignatureHeader -> ByteString -> ByteString -> IO ()
checkSignature personPkid personPublicKey sigheader digest body = do
-- check
unless (personPkid == sigheader.keyId) $
error "public key mismatch with signature."
unless (verifyPub personPublicKey sigheader.signature body) $
error "signature verification failed."
unless (verifyDigest personPublicKey digest body) $
error "digest verification failed."
-- todo: check date
data SignatureHeader
= SignatureHeader
{ -- | Where to get the public key for this actor
keyId :: Url
, -- | Which headers have been sent
headers :: [T.Text]
, -- | Contains the signature
signature :: ByteString
}
data Component
= KeyId
| Headers
| Signature
deriving Eq
parseSignature :: Maybe T.Text -> SignatureHeader
parseSignature minput =
let
input = maybe (error "no signature.") T.unpack minput
in case P.readP_to_S parser input of
[(sig, "")] -> sig
_ -> error "error parsing signature."
where
lookup' a b =
fromMaybe (error "error parsing signature") $ lookup a b
parser = do
components <- component `P.sepBy` P.char ','
pure SignatureHeader
{ keyId = lookup' KeyId components
, headers = T.split (==' ') . T.pack $ lookup' Headers components
, signature =
( T.encodeUtf8
. Base64.decodeBase64Lenient
. T.pack
. lookup' Signature
) components
}
component = P.choice
[ do
_ <- P.string "keyId="
url <- P.between (P.char '\"') (P.char '\"') (P.munch1 (/= '\"'))
pure (KeyId, url)
, do
_ <- P.string "headers="
url <- P.between (P.char '\"') (P.char '\"') (P.munch1 (/= '\"'))
pure (Headers, url)
, do
_ <- P.string "signature="
url <- P.between (P.char '\"') (P.char '\"') (P.munch1 (/= '\"'))
pure (Signature, url)
]

View file

@ -3,6 +3,7 @@ module Fedi.Routes.Outbox where
import Data.Aeson qualified as A import Data.Aeson qualified as A
import Fedi.Helpers import Fedi.Helpers
import Fedi.Types import Fedi.Types
import Fedi.Types.Helpers
import Fedi.UserDetails import Fedi.UserDetails
import Fedi.Routes.Helpers import Fedi.Routes.Helpers
import Web.Twain qualified as Twain import Web.Twain qualified as Twain

View file

@ -4,6 +4,7 @@ import Data.Aeson qualified as A
import Fedi.Helpers import Fedi.Helpers
import Fedi.UserDetails import Fedi.UserDetails
import Fedi.Webfinger import Fedi.Webfinger
import Fedi.Types.Helpers
import Fedi.Routes.Helpers import Fedi.Routes.Helpers
import Web.Twain qualified as Twain import Web.Twain qualified as Twain
import Web.Twain.Types qualified as Twain import Web.Twain.Types qualified as Twain

168
src/Fedi/Types/Helpers.hs Normal file
View file

@ -0,0 +1,168 @@
module Fedi.Types.Helpers where
import Data.Text qualified as T
import Fedi.Types
import Fedi.UserDetails
-- | An empty activitypub Object.
emptyObject :: Object ()
emptyObject =
Object
{ id = Nothing
, otype = ()
, content = Nothing
, published = Nothing
, replies = Nothing
, attachment = Nothing
, attributedTo = Nothing
, tag = Nothing
, to = Nothing
, cc = Nothing
, inReplyTo = Nothing
, url = Nothing
, name = Nothing
, icon = Nothing
, image = Nothing
, preview = Nothing
, summary = Nothing
, updated = Nothing
, mediaType = Nothing
}
-- | Create an activitypub Actor.
makeActor :: UserDetails -> Actor
makeActor details =
let
actor = actorUrl details
in
ActorPerson $
emptyObject
{ id = Just $ ObjectId actor
, otype =
TypePerson
{ preferredUsername = details.username
, inbox = Link $ actor <> "/inbox"
, outbox = Link $ actor <> "/outbox"
, following = Link $ actor <> "/following"
, followers = Link $ actor <> "/followers"
, publicKey =
PublicKey
{ pkid = actor <> "#main-key"
, owner = actor
, publicKeyPem = details.publicPem
}
}
, url = Nothing -- details.url
, name = Just $ StringName details.name
, icon = Just $ makeImage details.icon
, image = Just $ makeImage details.image
, summary = Just $ T.pack details.summary
}
makeCreateNote :: Note -> Create
makeCreateNote note =
emptyObject
{ id = (\oid -> ObjectId $ oid.unwrap <> "/create") <$> note.id
, otype =
TypeActivity
{ actor = maybe (Link "") getAttributedTo note.attributedTo
, atype = TypeCreate note
, target = Nothing
, origin = Nothing
}
}
-- | Create an user's empty 'Note'.
emptyUserNote :: Url -> Note
emptyUserNote actor =
emptyObject
{ otype = emptyTypeNote
, attributedTo = Just (LLink $ Link actor)
, to = Just [Link "https://www.w3.org/ns/activitystreams#Public"]
, cc = Just [Link $ actor <> "/followers"]
}
-- | An empty 'Note'.
emptyTypeNote :: TypeNote
emptyTypeNote =
TypeNote
{ likes = emptyUnorderedCollection
, shares = emptyUnorderedCollection
, replies = emptyUnorderedCollection
, sensitive = False
}
-- | Create an activitypub Image.
makeImage :: Url -> Image
makeImage link =
emptyObject
{ otype = TypeImage
, mediaType = Just ("image/png" :: MediaType)
, url = Just link
}
-- | An empty 'Collection'.
emptyUnorderedCollection :: Collection a
emptyUnorderedCollection =
emptyObject
{ otype =
CollectionType
{ ctype =
UnorderedCollectionType
{ items = []
}
, first = Nothing
, last = Nothing
, current = Nothing
}
}
-- | An empty 'OrderedCollection'.
emptyOrderedCollection :: OrderedCollection a
emptyOrderedCollection =
emptyObject
{ otype =
CollectionType
{ ctype =
OrderedCollectionType
{ orderedItems = []
}
, first = Nothing
, last = Nothing
, current = Nothing
}
}
-- | Create an empty 'OrderedCollectionPage'.
emptyOrderedCollectionPage :: Url -> OrderedCollectionPage a
emptyOrderedCollectionPage url =
emptyObject
{ otype =
CollectionType
{ ctype =
OrderedCollectionPageType
{ partOf = url
, prev = Nothing
, next = Nothing
, porderedItems = []
}
, first = Nothing
, last = Nothing
, current = Nothing
}
}
makeAccept :: Follow -> Url -> Accept
makeAccept theirFollow myfollowId =
emptyObject
{ id = Just $ ObjectId myfollowId
, otype =
TypeActivity
{ actor = theirFollow.otype.actor
, atype = TypeAccept
{ object = ActivityFollow theirFollow
}
, target = Nothing
, origin = Nothing
}
}

View file

@ -8,7 +8,9 @@ import Data.Foldable as Export
import Data.Maybe as Export (fromMaybe, listToMaybe, maybeToList) import Data.Maybe as Export (fromMaybe, listToMaybe, maybeToList)
import Data.String as Export (fromString) import Data.String as Export (fromString)
import Data.Text as Export (Text) import Data.Text as Export (Text)
import Data.ByteString as Export (ByteString)
import Data.Text qualified as T import Data.Text qualified as T
import Data.Text.Encoding qualified as T
import Data.Time as Export (UTCTime) import Data.Time as Export (UTCTime)
import Data.Traversable as Export import Data.Traversable as Export
import GHC.Generics as Export (Generic) import GHC.Generics as Export (Generic)
@ -23,6 +25,9 @@ newtype Pem = Pem T.Text
deriving (Show, Eq) deriving (Show, Eq)
deriving (A.FromJSON) via T.Text deriving (A.FromJSON) via T.Text
pemToBS :: Pem -> ByteString
pemToBS (Pem txt) = T.encodeUtf8 txt
instance A.ToJSON Pem where instance A.ToJSON Pem where
toJSON (Pem pem) = A.String pem toJSON (Pem pem) = A.String pem