Turn nonce into a non-effect constant using FFI

This commit is contained in:
Emi Simpson 2022-11-06 11:58:15 -05:00
parent 111bebf0de
commit 69f66e7908
Signed by: Emi
GPG Key ID: A12F2C2FFDC3D847
3 changed files with 8 additions and 10 deletions

View File

@ -2,7 +2,7 @@ module Aviary.Logic where
import Prelude import Prelude
import AviaryFormat.Format (Format, Image, Index, parseIndex) as Format import AviaryFormat.Format (Format, Image, Index, parseIndex) as Format
import Aviary.FFI (arrayBufferToBlob) import Aviary.FFI (arrayBufferToBlob, nonce)
import Aviary.Model (formatToMime, GalleryError(..), Image, ImageData(..), ImageError(..), Model(..)) import Aviary.Model (formatToMime, GalleryError(..), Image, ImageData(..), ImageError(..), Model(..))
import Control.Monad.Error.Class (try) import Control.Monad.Error.Class (try)
@ -16,11 +16,10 @@ import Data.Either (Either(..), note)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Newtype (unwrap) import Data.Newtype (unwrap)
import Data.ArrayBuffer.ArrayBuffer (byteLength) import Data.ArrayBuffer.ArrayBuffer (byteLength)
import Data.ArrayBuffer.Builder (DataBuff, execPut, putDataBuff, putInt8) import Data.ArrayBuffer.Builder (DataBuff, execPut, putDataBuff)
import Data.ArrayBuffer.DataView (whole) import Data.ArrayBuffer.DataView (whole)
import Data.ArrayBuffer.Types (ArrayBuffer) import Data.ArrayBuffer.Types (ArrayBuffer)
import Data.Filterable (partitionMap) import Data.Filterable (partitionMap)
import Data.Foldable (traverse_)
import Data.String (drop) import Data.String (drop)
import Parsing (runParserT) import Parsing (runParserT)
import Web.File.Url (createObjectURL) import Web.File.Url (createObjectURL)
@ -34,9 +33,6 @@ import Crypto.Subtle.Key.Import (aes)
import Crypto.Subtle.Key.Import (importKey) as SC import Crypto.Subtle.Key.Import (importKey) as SC
import Crypto.Subtle.Key.Types (CryptoKey, decrypt, raw) import Crypto.Subtle.Key.Types (CryptoKey, decrypt, raw)
nonceE :: Effect ArrayBuffer
nonceE = execPut $ traverse_ putInt8 [0xd0, 0xc3, 0x75, 0x56, 0x58, 0xc1, 0x7e, 0x5f, 0xd6, 0xcc, 0xb6, 0x76]
databuffToBuffer :: DataBuff -> Effect ArrayBuffer databuffToBuffer :: DataBuff -> Effect ArrayBuffer
databuffToBuffer = execPut <<< putDataBuff databuffToBuffer = execPut <<< putDataBuff
@ -49,7 +45,6 @@ importKey key =
decryptBlob :: CryptoKey -> ArrayBuffer -> ArrayBuffer -> Aff ArrayBuffer decryptBlob :: CryptoKey -> ArrayBuffer -> ArrayBuffer -> Aff ArrayBuffer
decryptBlob key cyphertext nonce = decryptBlob key cyphertext nonce =
-- nonce <- makeAff (\_ -> nonceE)
Alg.decrypt (Alg.aesGCM nonce Nothing (Just t128)) key cyphertext Alg.decrypt (Alg.aesGCM nonce Nothing (Just t128)) key cyphertext
convertImageFromProtobuf :: Format.Image -> Either GalleryError Image convertImageFromProtobuf :: Format.Image -> Either GalleryError Image
@ -103,8 +98,7 @@ fetch_gallery_from_page_info = do
keyB64 <- drop 1 <$> Location.hash location keyB64 <- drop 1 <$> Location.hash location
server <- Location.origin location server <- Location.origin location
fileId <- drop 1 <$> Location.pathname location fileId <- drop 1 <$> Location.pathname location
nonce <- nonceE pure {keyB64, server, fileId}
pure {keyB64, server, fileId, nonce}
case decodeKey urlInfo.keyB64 of case decodeKey urlInfo.keyB64 of
Nothing -> pure $ GError MalformedKey Nothing -> pure $ GError MalformedKey
Just keyBuffer -> do Just keyBuffer -> do
@ -113,7 +107,7 @@ fetch_gallery_from_page_info = do
case status of case status of
200 -> do 200 -> do
encryptedIndex <- arrayBuffer encryptedIndex <- arrayBuffer
serializedIndex <- try $ decryptBlob cryptoKey encryptedIndex urlInfo.nonce serializedIndex <- try $ decryptBlob cryptoKey encryptedIndex nonce
case serializedIndex of case serializedIndex of
Left _ -> pure $ GError DecryptFailed Left _ -> pure $ GError DecryptFailed
Right serializedIndex' -> do Right serializedIndex' -> do

View File

@ -3,3 +3,5 @@ export function arrayBufferToBlob(mime) {
return new Blob([data], {type: mime}) return new Blob([data], {type: mime})
} }
} }
export const nonce = new Uint8Array([0xd0, 0xc3, 0x75, 0x56, 0x58, 0xc1, 0x7e, 0x5f, 0xd6, 0xcc, 0xb6, 0x76]).buffer

View File

@ -6,3 +6,5 @@ import Web.File.Blob (Blob)
-- mimeType :: String -- mimeType :: String
-- blobData :: ArrayBuffer -- blobData :: ArrayBuffer
foreign import arrayBufferToBlob :: String -> ArrayBuffer -> Blob foreign import arrayBufferToBlob :: String -> ArrayBuffer -> Blob
foreign import nonce :: ArrayBuffer