summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Crypto/Tox.hs13
1 files changed, 8 insertions, 5 deletions
diff --git a/src/Crypto/Tox.hs b/src/Crypto/Tox.hs
index 4fc87f7c..ad246d4e 100644
--- a/src/Crypto/Tox.hs
+++ b/src/Crypto/Tox.hs
@@ -10,6 +10,7 @@
10{-# LANGUAGE TypeOperators #-} 10{-# LANGUAGE TypeOperators #-}
11{-# LANGUAGE MagicHash, UnboxedTuples, BangPatterns #-} 11{-# LANGUAGE MagicHash, UnboxedTuples, BangPatterns #-}
12{-# LANGUAGE NamedFieldPuns #-} 12{-# LANGUAGE NamedFieldPuns #-}
13{-# LANGUAGE PatternSynonyms #-}
13module Crypto.Tox 14module Crypto.Tox
14 ( PublicKey 15 ( PublicKey
15 , publicKey 16 , publicKey
@@ -24,7 +25,7 @@ module Crypto.Tox
24 , newSecretsCache 25 , newSecretsCache
25 , Encrypted 26 , Encrypted
26 , Encrypted8(..) 27 , Encrypted8(..)
27 , type (∘)(..) 28 , type (∘), uncomposed, pattern Composed -- type (∘)(..)
28 , Asymm(..) 29 , Asymm(..)
29 , getAsymm 30 , getAsymm
30 , getAliasedAsymm 31 , getAliasedAsymm
@@ -108,6 +109,7 @@ import qualified Data.MinMaxPSQ as MM
108import Data.Time.Clock.POSIX 109import Data.Time.Clock.POSIX
109import Data.Hashable 110import Data.Hashable
110import System.IO.Unsafe (unsafeDupablePerformIO) 111import System.IO.Unsafe (unsafeDupablePerformIO)
112import Data.Functor.Compose
111 113
112-- | A 16-byte mac and an arbitrary-length encrypted stream. 114-- | A 16-byte mac and an arbitrary-length encrypted stream.
113newtype Encrypted a = Encrypted ByteString 115newtype Encrypted a = Encrypted ByteString
@@ -116,9 +118,11 @@ newtype Encrypted a = Encrypted ByteString
116newtype Encrypted8 a = E8 (Encrypted (a,Nonce8)) 118newtype Encrypted8 a = E8 (Encrypted (a,Nonce8))
117 deriving (Serialize, Show) 119 deriving (Serialize, Show)
118 120
119newtype (f ∘ g) x = Composed { uncomposed :: f (g x) } 121-- Simulating: newtype (f ∘ g) x = Composed { uncomposed :: f (g x) }
120 122pattern Composed x = Compose x
121infixr ∘ 123uncomposed = getCompose
124type f ∘ g = f `Compose` g
125infixr 9 ∘
122 126
123newtype Auth = Auth Poly1305.Auth deriving (Eq, ByteArrayAccess) 127newtype Auth = Auth Poly1305.Auth deriving (Eq, ByteArrayAccess)
124instance Ord Auth where 128instance Ord Auth where
@@ -498,7 +502,6 @@ data Asymm a = Asymm
498 } 502 }
499 deriving (Functor,Foldable,Traversable, Show, Eq, Ord) 503 deriving (Functor,Foldable,Traversable, Show, Eq, Ord)
500 504
501
502instance Sized a => Sized (Asymm a) where 505instance Sized a => Sized (Asymm a) where
503 size = case size of 506 size = case size of
504 ConstSize a -> ConstSize $ a + 24 + 32 507 ConstSize a -> ConstSize $ a + 24 + 32