Skip to content

Commit

Permalink
feat: Add new group chats savedata support.
Browse files Browse the repository at this point in the history
  • Loading branch information
iphydf committed Dec 23, 2023
1 parent b92867f commit b221d11
Show file tree
Hide file tree
Showing 19 changed files with 392 additions and 108 deletions.
62 changes: 31 additions & 31 deletions .cirrus.yml
Original file line number Diff line number Diff line change
Expand Up @@ -11,34 +11,34 @@ bazel-opt_task:
--config=ci
//hs-toxcore/...

android-aarch64_task:
container:
image: toktoknet/ghc-android:8.10.7.aarch64
cpu: 2
memory: 6G
build_script:
- android/build.sh

android-arm_task:
container:
image: toktoknet/ghc-android:8.10.7.arm
cpu: 2
memory: 6G
build_script:
- android/build.sh

android-i686_task:
container:
image: toktoknet/ghc-android:8.10.7.i686
cpu: 2
memory: 6G
build_script:
- android/build.sh

android-x86_64_task:
container:
image: toktoknet/ghc-android:8.10.7.x86_64
cpu: 2
memory: 6G
build_script:
- android/build.sh
#android-aarch64_task:
# container:
# image: toktoknet/ghc-android:8.10.7.aarch64
# cpu: 2
# memory: 6G
# build_script:
# - android/build.sh
#
#android-arm_task:
# container:
# image: toktoknet/ghc-android:8.10.7.arm
# cpu: 2
# memory: 6G
# build_script:
# - android/build.sh
#
#android-i686_task:
# container:
# image: toktoknet/ghc-android:8.10.7.i686
# cpu: 2
# memory: 6G
# build_script:
# - android/build.sh
#
#android-x86_64_task:
# container:
# image: toktoknet/ghc-android:8.10.7.x86_64
# cpu: 2
# memory: 6G
# build_script:
# - android/build.sh
10 changes: 4 additions & 6 deletions BUILD.bazel
Original file line number Diff line number Diff line change
Expand Up @@ -7,14 +7,14 @@ project(custom_cirrus = True)
haskell_library(
name = "hs-toxcore",
srcs = glob(["src/**/*.*hs"]),
compiler_flags = [
"-j4",
],
ghcopts = ["-j4"],
src_strip_prefix = "src",
version = "0.2.12",
visibility = ["//visibility:public"],
deps = [
"//hs-msgpack-arbitrary",
"//hs-msgpack-binary",
"//hs-msgpack-types",
"//third_party/haskell:MonadRandom",
"//third_party/haskell:QuickCheck",
"//third_party/haskell:base",
Expand All @@ -39,9 +39,7 @@ haskell_library(
hspec_test(
name = "testsuite",
size = "small",
compiler_flags = [
"-j4",
],
ghcopts = ["-j4"],
deps = [
":hs-toxcore",
"//hs-msgpack-binary",
Expand Down
12 changes: 1 addition & 11 deletions src/Network/Tox/Binary.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,26 +2,16 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StrictData #-}
module Network.Tox.Binary
( typeName
, encode
( encode
, decode
) where

import Data.Binary (Binary)
import Data.ByteString (ByteString)
import Data.Kind (Type)
import Data.Typeable (Typeable)
import qualified Data.Typeable as Typeable

import qualified Network.Tox.Encoding as Encoding


typeName :: Typeable (a :: Type) => proxy a -> String
typeName (_ :: proxy a) =
show . Typeable.typeOf $ (undefined :: a)



--------------------------------------------------------------------------------
--
-- :: decode
Expand Down
54 changes: 30 additions & 24 deletions src/Network/Tox/Crypto/Key.lhs
Original file line number Diff line number Diff line change
Expand Up @@ -11,29 +11,32 @@
{-# LANGUAGE StrictData #-}
module Network.Tox.Crypto.Key where
import Control.Monad ((>=>))
import Control.Monad.Validate (MonadValidate, refute)
import qualified Crypto.Saltine.Class as Sodium (IsEncoding, decode,
encode)
import qualified Crypto.Saltine.Core.Box as Sodium (CombinedKey, Nonce,
PublicKey, SecretKey)
import qualified Crypto.Saltine.Internal.Box as Sodium (box_beforenmbytes,
box_noncebytes,
box_publickeybytes,
box_secretkeybytes)
import Data.Binary (Binary)
import qualified Data.Binary as Binary (get, put)
import qualified Data.Binary.Get as Binary (getByteString, runGet)
import qualified Data.Binary.Put as Binary (putByteString)
import qualified Data.ByteString as ByteString
import qualified Data.ByteString.Base16 as Base16
import qualified Data.ByteString.Lazy as LazyByteString
import Data.MessagePack (DecodeError, MessagePack (..))
import Data.Proxy (Proxy (..))
import Data.Typeable (Typeable)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import qualified Test.QuickCheck.Arbitrary as Arbitrary
import Text.Read (readPrec)
import Control.Monad ((>=>))
import Control.Monad.Validate (MonadValidate, refute)
import qualified Crypto.Saltine.Class as Sodium (IsEncoding, decode,
encode)
import qualified Crypto.Saltine.Core.Box as Sodium (CombinedKey, Nonce,
PublicKey, SecretKey)
import qualified Crypto.Saltine.Core.Sign as Sodium (Signature)
import qualified Crypto.Saltine.Internal.Box as Sodium (box_beforenmbytes,
box_noncebytes,
box_publickeybytes,
box_secretkeybytes)
import qualified Crypto.Saltine.Internal.Sign as Sodium (sign_bytes)
import Data.Binary (Binary)
import qualified Data.Binary as Binary (get, put)
import qualified Data.Binary.Get as Binary (getByteString, runGet)
import qualified Data.Binary.Put as Binary (putByteString)
import qualified Data.ByteString as ByteString
import qualified Data.ByteString.Base16 as Base16
import qualified Data.ByteString.Lazy as LazyByteString
import Data.MessagePack (DecodeError, MessagePack (..))
import Data.Proxy (Proxy (..))
import Data.String (fromString)
import Data.Typeable (Typeable)
import qualified Test.QuickCheck.Arbitrary as Arbitrary
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import Text.Read (readPrec)
{-------------------------------------------------------------------------------
Expand Down Expand Up @@ -78,11 +81,13 @@ instance CryptoNumber Sodium.PublicKey where { encodedByteSize _ = Sodium.box_
instance CryptoNumber Sodium.SecretKey where { encodedByteSize _ = Sodium.box_secretkeybytes }
instance CryptoNumber Sodium.CombinedKey where { encodedByteSize _ = Sodium.box_beforenmbytes }
instance CryptoNumber Sodium.Nonce where { encodedByteSize _ = Sodium.box_noncebytes }
instance CryptoNumber Sodium.Signature where { encodedByteSize _ = Sodium.sign_bytes }
deriving instance Typeable Sodium.PublicKey
deriving instance Typeable Sodium.SecretKey
deriving instance Typeable Sodium.CombinedKey
deriving instance Typeable Sodium.Nonce
deriving instance Typeable Sodium.Signature
newtype Key a = Key { unKey :: a }
deriving (Eq, Ord, Typeable)
Expand All @@ -91,6 +96,7 @@ type PublicKey = Key Sodium.PublicKey
type SecretKey = Key Sodium.SecretKey
type CombinedKey = Key Sodium.CombinedKey
type Nonce = Key Sodium.Nonce
type Signature = Key Sodium.Signature
instance Sodium.IsEncoding a => Sodium.IsEncoding (Key a) where
encode = Sodium.encode . unKey
Expand All @@ -117,7 +123,7 @@ decode :: (CryptoNumber a, MonadValidate DecodeError m) => ByteString.ByteString
decode bytes =
case Sodium.decode bytes of
Just key -> return $ Key key
Nothing -> refute "unable to decode ByteString to Key"
Nothing -> refute $ fromString $ "unable to decode ByteString to Key: " <> show (ByteString.length bytes)
instance CryptoNumber a => Binary (Key a) where
Expand Down
2 changes: 1 addition & 1 deletion src/Network/Tox/DHT/ClientList.lhs
Original file line number Diff line number Diff line change
Expand Up @@ -11,8 +11,8 @@ import Data.Map (Map)
import qualified Data.Map as Map
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary,
arbitrarySizedNatural)
import Test.QuickCheck.Gen (Gen)
import qualified Test.QuickCheck.Gen as Gen
import Test.QuickCheck.Gen (Gen)
import Network.Tox.Crypto.Key (PublicKey)
import Network.Tox.DHT.ClientNode (ClientNode)
Expand Down
2 changes: 1 addition & 1 deletion src/Network/Tox/DHT/KBuckets.lhs
Original file line number Diff line number Diff line change
Expand Up @@ -21,8 +21,8 @@ import Data.Ord (comparing)
import Data.Traversable (mapAccumR)
import Data.Word (Word8)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import Test.QuickCheck.Gen (Gen)
import qualified Test.QuickCheck.Gen as Gen
import Test.QuickCheck.Gen (Gen)
import Network.Tox.Crypto.Key (PublicKey)
import Network.Tox.DHT.ClientList (ClientList)
Expand Down
2 changes: 1 addition & 1 deletion src/Network/Tox/DHT/Operation.lhs
Original file line number Diff line number Diff line change
Expand Up @@ -33,10 +33,10 @@ import System.Random (StdGen, mkStdGen)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import Network.Tox.Crypto.Key (PublicKey)
import qualified Network.Tox.Crypto.KeyPair as KeyPair
import Network.Tox.Crypto.Keyed (Keyed)
import Network.Tox.Crypto.KeyedT (KeyedT)
import qualified Network.Tox.Crypto.KeyedT as KeyedT
import qualified Network.Tox.Crypto.KeyPair as KeyPair
import Network.Tox.DHT.ClientList (ClientList)
import qualified Network.Tox.DHT.ClientList as ClientList
import Network.Tox.DHT.ClientNode (ClientNode)
Expand Down
32 changes: 15 additions & 17 deletions src/Network/Tox/SaveData.lhs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,6 @@ module Network.Tox.SaveData
, Section (..)
, NospamKeys (..)
, Friends (..)
, Bytes (..)
) where
\end{code}

Expand All @@ -36,9 +35,13 @@ import Data.MessagePack (MessagePack)
import Data.Word (Word16, Word32, Word8)
import GHC.Generics (Generic)
import Network.Tox.Crypto.Key (PublicKey, SecretKey)
import Network.Tox.Crypto.KeyPair (KeyPair (..))
import qualified Network.Tox.Crypto.KeyPair as KeyPair
import Network.Tox.SaveData.Bytes (Bytes)
import Network.Tox.SaveData.Conferences (Conferences)
import Network.Tox.SaveData.DHT (DHT)
import Network.Tox.SaveData.Friend (Friend)
import Network.Tox.SaveData.Groups (Groups)
import Network.Tox.SaveData.Nodes (Nodes)
import qualified Network.Tox.SaveData.Util as Util
import Test.QuickCheck.Arbitrary (Arbitrary (..),
Expand Down Expand Up @@ -124,6 +127,7 @@ Section types:
Name & 0x04 \\
StatusMessage & 0x05 \\
Status & 0x06 \\
Groups & 0x07 \\
TcpRelays & 0x0A \\
PathNodes & 0x0B \\
Conferences & 0x14 \\
Expand All @@ -147,6 +151,7 @@ getSections = go
0x04 -> load SectionName
0x05 -> load SectionStatusMessage
0x06 -> load SectionStatus
0x07 -> load SectionGroups
0x0A -> load SectionTcpRelays
0x0B -> load SectionPathNodes
0x14 -> load SectionConferences
Expand All @@ -169,6 +174,7 @@ putSections = mapM_ go
SectionName x -> (0x04, put x)
SectionStatusMessage x -> (0x05, put x)
SectionStatus x -> (0x06, put x)
SectionGroups x -> (0x07, put x)
SectionTcpRelays x -> (0x0A, put x)
SectionPathNodes x -> (0x0B, put x)
SectionConferences x -> (0x14, put x)
Expand Down Expand Up @@ -270,6 +276,7 @@ data Section
| SectionName Bytes
| SectionStatusMessage Bytes
| SectionStatus Word8
| SectionGroups Groups
| SectionTcpRelays Nodes
| SectionPathNodes Nodes
| SectionConferences Conferences
Expand All @@ -286,6 +293,7 @@ instance Arbitrary Section where
, SectionName <$> arbitrary
, SectionStatusMessage <$> arbitrary
, SectionStatus <$> arbitrary
, SectionGroups <$> arbitrary
, SectionTcpRelays <$> arbitrary
, SectionPathNodes <$> arbitrary
, SectionConferences <$> arbitrary
Expand Down Expand Up @@ -313,10 +321,12 @@ instance Binary NospamKeys where
put secretKey
instance Arbitrary NospamKeys where
arbitrary = NospamKeys
<$> arbitrary
<*> arbitrary
<*> arbitrary
arbitrary = do
KeyPair sk pk <- KeyPair.fromSecretKey <$> arbitrary
NospamKeys
<$> arbitrary
<*> pure pk
<*> pure sk
shrink = genericShrink
newtype Friends = Friends [Friend]
Expand All @@ -332,16 +342,4 @@ instance Arbitrary Friends where
arbitrary = Friends <$> arbitrary
shrink = genericShrink
newtype Bytes = Bytes LBS.ByteString
deriving (Eq, Show, Read, Generic)
instance MessagePack Bytes
instance Binary Bytes where
get = Bytes <$> Get.getRemainingLazyByteString
put (Bytes bs) = Put.putLazyByteString bs
instance Arbitrary Bytes where
arbitrary = Bytes . LBS.pack <$> arbitrary
\end{code}
32 changes: 32 additions & 0 deletions src/Network/Tox/SaveData/Bytes.lhs
Original file line number Diff line number Diff line change
@@ -0,0 +1,32 @@
\subsection{Bytes}

Arbitrary byte array.

\begin{code}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE StrictData #-}
module Network.Tox.SaveData.Bytes
( Bytes (..)
) where
import Data.Binary (Binary (..))
import qualified Data.Binary.Get as Get
import qualified Data.Binary.Put as Put
import qualified Data.ByteString.Lazy as LBS
import Data.MessagePack (MessagePack)
import GHC.Generics (Generic)
import Test.QuickCheck.Arbitrary (Arbitrary (..))
newtype Bytes = Bytes LBS.ByteString
deriving (Eq, Show, Read, Generic)
instance MessagePack Bytes
instance Binary Bytes where
get = Bytes <$> Get.getRemainingLazyByteString
put (Bytes bs) = Put.putLazyByteString bs
instance Arbitrary Bytes where
arbitrary = Bytes . LBS.pack <$> arbitrary
\end{code}
Loading

0 comments on commit b221d11

Please sign in to comment.