module Network.TLS.Record.Writing
( encodeRecord
, encodeRecord13
, sendBytes
) where
import Network.TLS.Cap
import Network.TLS.Cipher
import Network.TLS.Context.Internal
import Network.TLS.Hooks
import Network.TLS.Imports
import Network.TLS.Packet
import Network.TLS.Parameters
import Network.TLS.Record
import Network.TLS.State
import Network.TLS.Struct
import Control.Concurrent.MVar
import Control.Monad.State.Strict
import qualified Data.ByteString as B
encodeRecord :: Context -> Record Plaintext -> IO (Either TLSError ByteString)
encodeRecord :: Context -> Record Plaintext -> IO (Either TLSError ByteString)
encodeRecord Context
ctx = Context -> RecordM ByteString -> IO (Either TLSError ByteString)
forall a. Context -> RecordM a -> IO (Either TLSError a)
prepareRecord Context
ctx (RecordM ByteString -> IO (Either TLSError ByteString))
-> (Record Plaintext -> RecordM ByteString)
-> Record Plaintext
-> IO (Either TLSError ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Record Plaintext -> RecordM ByteString
encodeRecordM
prepareRecord :: Context -> RecordM a -> IO (Either TLSError a)
prepareRecord :: Context -> RecordM a -> IO (Either TLSError a)
prepareRecord Context
ctx RecordM a
f = do
Version
ver <- Context -> TLSSt Version -> IO Version
forall a. Context -> TLSSt a -> IO a
usingState_ Context
ctx (Version -> TLSSt Version
getVersionWithDefault (Version -> TLSSt Version) -> Version -> TLSSt Version
forall a b. (a -> b) -> a -> b
$ [Version] -> Version
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Version] -> Version) -> [Version] -> Version
forall a b. (a -> b) -> a -> b
$ Supported -> [Version]
supportedVersions (Supported -> [Version]) -> Supported -> [Version]
forall a b. (a -> b) -> a -> b
$ Context -> Supported
ctxSupported Context
ctx)
RecordState
txState <- MVar RecordState -> IO RecordState
forall a. MVar a -> IO a
readMVar (MVar RecordState -> IO RecordState)
-> MVar RecordState -> IO RecordState
forall a b. (a -> b) -> a -> b
$ Context -> MVar RecordState
ctxTxState Context
ctx
let sz :: Int
sz = case RecordState -> Maybe Cipher
stCipher RecordState
txState of
Maybe Cipher
Nothing -> Int
0
Just Cipher
cipher -> if BulkFunctions -> Bool
hasRecordIV (BulkFunctions -> Bool) -> BulkFunctions -> Bool
forall a b. (a -> b) -> a -> b
$ Bulk -> BulkFunctions
bulkF (Bulk -> BulkFunctions) -> Bulk -> BulkFunctions
forall a b. (a -> b) -> a -> b
$ Cipher -> Bulk
cipherBulk Cipher
cipher
then Bulk -> Int
bulkIVSize (Bulk -> Int) -> Bulk -> Int
forall a b. (a -> b) -> a -> b
$ Cipher -> Bulk
cipherBulk Cipher
cipher
else Int
0
if Version -> Bool
hasExplicitBlockIV Version
ver Bool -> Bool -> Bool
&& Int
sz Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then do ByteString
newIV <- Context -> Int -> IO ByteString
getStateRNG Context
ctx Int
sz
Context -> RecordM a -> IO (Either TLSError a)
forall a. Context -> RecordM a -> IO (Either TLSError a)
runTxState Context
ctx ((RecordState -> RecordState) -> RecordM ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (ByteString -> RecordState -> RecordState
setRecordIV ByteString
newIV) RecordM () -> RecordM a -> RecordM a
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> RecordM a
f)
else Context -> RecordM a -> IO (Either TLSError a)
forall a. Context -> RecordM a -> IO (Either TLSError a)
runTxState Context
ctx RecordM a
f
encodeRecordM :: Record Plaintext -> RecordM ByteString
encodeRecordM :: Record Plaintext -> RecordM ByteString
encodeRecordM Record Plaintext
record = do
Record Ciphertext
erecord <- Record Plaintext -> RecordM (Record Ciphertext)
engageRecord Record Plaintext
record
let (Header
hdr, ByteString
content) = Record Ciphertext -> (Header, ByteString)
forall a. Record a -> (Header, ByteString)
recordToRaw Record Ciphertext
erecord
ByteString -> RecordM ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> RecordM ByteString)
-> ByteString -> RecordM ByteString
forall a b. (a -> b) -> a -> b
$ [ByteString] -> ByteString
B.concat [ Header -> ByteString
encodeHeader Header
hdr, ByteString
content ]
encodeRecord13 :: Context -> Record Plaintext -> IO (Either TLSError ByteString)
encodeRecord13 :: Context -> Record Plaintext -> IO (Either TLSError ByteString)
encodeRecord13 Context
ctx = Context -> RecordM ByteString -> IO (Either TLSError ByteString)
forall a. Context -> RecordM a -> IO (Either TLSError a)
prepareRecord13 Context
ctx (RecordM ByteString -> IO (Either TLSError ByteString))
-> (Record Plaintext -> RecordM ByteString)
-> Record Plaintext
-> IO (Either TLSError ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Record Plaintext -> RecordM ByteString
encodeRecordM
prepareRecord13 :: Context -> RecordM a -> IO (Either TLSError a)
prepareRecord13 :: Context -> RecordM a -> IO (Either TLSError a)
prepareRecord13 = Context -> RecordM a -> IO (Either TLSError a)
forall a. Context -> RecordM a -> IO (Either TLSError a)
runTxState
sendBytes :: Context -> ByteString -> IO ()
sendBytes :: Context -> ByteString -> IO ()
sendBytes Context
ctx ByteString
dataToSend = do
Context -> (Logging -> IO ()) -> IO ()
withLog Context
ctx ((Logging -> IO ()) -> IO ()) -> (Logging -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Logging
logging -> Logging -> ByteString -> IO ()
loggingIOSent Logging
logging ByteString
dataToSend
Context -> ByteString -> IO ()
contextSend Context
ctx ByteString
dataToSend