summaryrefslogtreecommitdiff
path: root/src/Data
diff options
context:
space:
mode:
Diffstat (limited to 'src/Data')
-rw-r--r--src/Data/Tox/Msg.hs27
1 files changed, 25 insertions, 2 deletions
diff --git a/src/Data/Tox/Msg.hs b/src/Data/Tox/Msg.hs
index d42b092b..e8c26a56 100644
--- a/src/Data/Tox/Msg.hs
+++ b/src/Data/Tox/Msg.hs
@@ -10,6 +10,9 @@
10{-# LANGUAGE TypeFamilies #-} 10{-# LANGUAGE TypeFamilies #-}
11module Data.Tox.Msg where 11module Data.Tox.Msg where
12 12
13import Crypto.Error
14import qualified Crypto.PubKey.Ed25519 as Ed25519
15import Data.ByteArray as BA
13import Data.ByteString as B 16import Data.ByteString as B
14import Data.Dependent.Sum 17import Data.Dependent.Sum
15import Data.Functor.Contravariant 18import Data.Functor.Contravariant
@@ -234,8 +237,28 @@ lossyness m = case msgbyte m of
234 | otherwise -> Lossless 237 | otherwise -> Lossless
235 238
236 239
237newtype ChatID = ChatID Nonce32 240newtype ChatID = ChatID Ed25519.PublicKey
238 deriving (Eq,Show,Serialize,Sized) 241 deriving Eq
242
243instance Sized ChatID where size = ConstSize 32
244
245instance Serialize ChatID where
246 get = do
247 bs <- getBytes 32
248 case Ed25519.publicKey bs of
249 CryptoPassed ed -> return $ ChatID ed
250 CryptoFailed e -> fail (show e)
251 put (ChatID ed) = putByteString $ BA.convert ed
252
253instance Read ChatID where
254 readsPrec _ s
255 | Right bs <- parseToken32 s
256 , CryptoPassed ed <- Ed25519.publicKey bs
257 = [ (ChatID ed, Prelude.drop 43 s) ]
258 | otherwise = []
259
260instance Show ChatID where
261 show (ChatID ed) = showToken32 ed
239 262
240data InviteType = GroupInvite { groupName :: Text } 263data InviteType = GroupInvite { groupName :: Text }
241 | AccptedInvite 264 | AccptedInvite