module Test.Cargohold.API.Federation where
import API.Cargohold
import qualified Codec.MIME.Type as MIME
import Control.Lens hiding ((.=))
import Crypto.Random (getRandomBytes)
import Data.ByteString.Builder
import Data.String.Conversions
import SetupHelpers
import Test.Cargohold.API.Util
import Testlib.Prelude
testGetAssetAvailablePublic :: (HasCallStack) => App ()
testGetAssetAvailablePublic :: HasCallStack => App ()
testGetAssetAvailablePublic = HasCallStack => Bool -> App ()
Bool -> App ()
getAssetAvailable Bool
True
testGetAssetAvailablePrivate :: (HasCallStack) => App ()
testGetAssetAvailablePrivate :: HasCallStack => App ()
testGetAssetAvailablePrivate = HasCallStack => Bool -> App ()
Bool -> App ()
getAssetAvailable Bool
False
getAssetAvailable :: (HasCallStack) => Bool -> App ()
getAssetAvailable :: HasCallStack => Bool -> App ()
getAssetAvailable Bool
isPublicAsset = do
let bdy :: (MIMEType, ByteString)
bdy = (MIMEType
applicationOctetStream, String -> ByteString
forall a b. ConvertibleStrings a b => a -> b
cs String
"Hello World")
settings :: Value
settings = [Pair] -> Value
object [String
"public" String -> Bool -> Pair
forall a. ToJSON a => String -> a -> Pair
.= Bool
isPublicAsset, String
"retention" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"volatile"]
Value
uid1 <- Domain -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser Domain
OwnDomain CreateUser
forall a. Default a => a
def
Value
uid2 <- Domain -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser Domain
OtherDomain CreateUser
forall a. Default a => a
def
Response
r1 <- Value -> Value -> (MIMEType, ByteString) -> App Response
forall user settings.
(HasCallStack, MakesValue user, MakesValue settings) =>
user -> settings -> (MIMEType, ByteString) -> App Response
uploadSimple Value
uid1 Value
settings (MIMEType, ByteString)
bdy
Response
r1.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
201
Value
ast <- App Value -> (Value -> App Value) -> Maybe Value -> App Value
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> App Value
forall a. HasCallStack => String -> a
error String
"No JSON in the response") Value -> App Value
forall a. a -> App a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Response
r1.jsonBody
Either String ()
tok <-
if Bool
isPublicAsset
then Either String () -> App (Either String ())
forall a. a -> App a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> App (Either String ()))
-> Either String () -> App (Either String ())
forall a b. (a -> b) -> a -> b
$ () -> Either String ()
forall a b. b -> Either a b
Right ()
else String -> Either String ()
forall a b. a -> Either a b
Left (String -> Either String ())
-> App String -> App (Either String ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Value
ast Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"token" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString)
Response
res <- Value -> Maybe Value -> Either String () -> App Response
forall user loc tok.
(HasCallStack, MakesValue user, IsAssetLocation loc,
IsAssetToken tok) =>
user -> loc -> tok -> App Response
downloadAsset' Value
uid2 Response
r1.jsonBody Either String ()
tok
Response
res.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200
testGetAssetNotAvailable :: (HasCallStack) => App ()
testGetAssetNotAvailable :: HasCallStack => App ()
testGetAssetNotAvailable = do
Value
uid <- Domain -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser Domain
OwnDomain CreateUser
forall a. Default a => a
def
String
userId <- Value
uid Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"id" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
String
token <- App String
HasCallStack => App String
randomToken
String
assetId <- App String
HasCallStack => App String
randomId
String
otherDomain <- Domain -> App Value
forall a. (MakesValue a, HasCallStack) => a -> App Value
make Domain
OtherDomain App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
let key :: String
key = String
"3-2-" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
assetId
ga :: Value
ga = [Pair] -> Value
object [String
"user" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
userId, String
"token" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
token, String
"key" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
key, String
"domain" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
otherDomain]
Response
r <- Value -> Value -> Value -> App Response
forall user loc tok.
(HasCallStack, MakesValue user, IsAssetLocation loc,
IsAssetToken tok) =>
user -> loc -> tok -> App Response
downloadAsset' Value
uid Value
ga Value
ga
Response
r.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
404
Response
r.jsonBody Maybe Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"message" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"Asset not found"
testGetAssetWrongToken :: (HasCallStack) => App ()
testGetAssetWrongToken :: HasCallStack => App ()
testGetAssetWrongToken = do
let bdy :: (MIMEType, ByteString)
bdy = (MIMEType
applicationOctetStream, String -> ByteString
forall a b. ConvertibleStrings a b => a -> b
cs String
"Hello World")
settings :: Value
settings = [Pair] -> Value
object [String
"public" String -> Bool -> Pair
forall a. ToJSON a => String -> a -> Pair
.= Bool
False, String
"retention" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"volatile"]
Value
uid1 <- Domain -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser Domain
OwnDomain CreateUser
forall a. Default a => a
def
Value
uid2 <- Domain -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser Domain
OtherDomain CreateUser
forall a. Default a => a
def
String
userId2 <- Value
uid2 Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"id" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
String
domain <- Value
uid1 Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"qualified_id" App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
Response
r1 <- Value -> Value -> (MIMEType, ByteString) -> App Response
forall user settings.
(HasCallStack, MakesValue user, MakesValue settings) =>
user -> settings -> (MIMEType, ByteString) -> App Response
uploadSimple Value
uid1 Value
settings (MIMEType, ByteString)
bdy
Response
r1.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
201
String
key <- Response
r1.jsonBody Maybe Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"key" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
String
tok <- App String
HasCallStack => App String
randomToken
let ga :: Value
ga =
[Pair] -> Value
object
[ String
"user" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
userId2,
String
"token" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
tok,
String
"key" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
key,
String
"domain" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
domain
]
Response
r2 <- Value -> Value -> Value -> App Response
forall user loc tok.
(HasCallStack, MakesValue user, IsAssetLocation loc,
IsAssetToken tok) =>
user -> loc -> tok -> App Response
downloadAsset' Value
uid2 Value
ga Value
ga
Response
r2.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
404
Response
r2.jsonBody Maybe Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"message" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"Asset not found"
testLargeAsset :: (HasCallStack) => App ()
testLargeAsset :: HasCallStack => App ()
testLargeAsset = do
let settings :: Value
settings = [Pair] -> Value
object [String
"public" String -> Bool -> Pair
forall a. ToJSON a => String -> a -> Pair
.= Bool
False, String
"retention" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"volatile"]
Value
uid <- Domain -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser Domain
OwnDomain CreateUser
forall a. Default a => a
def
String
domain <- Value
uid Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"qualified_id" App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
Value
uid2 <- Domain -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser Domain
OtherDomain CreateUser
forall a. Default a => a
def
String
userId2 <- Value
uid2 Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"id" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
let size :: Int
size = Int
1024 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
1024
ByteString
bs :: ByteString <- IO ByteString -> App ByteString
forall a. IO a -> App a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> App ByteString)
-> IO ByteString -> App ByteString
forall a b. (a -> b) -> a -> b
$ Int -> IO ByteString
forall byteArray. ByteArray byteArray => Int -> IO byteArray
forall (m :: * -> *) byteArray.
(MonadRandom m, ByteArray byteArray) =>
Int -> m byteArray
getRandomBytes Int
size
let body :: ByteString
body = Builder -> ByteString
toLazyByteString (Builder -> ByteString) -> Builder -> ByteString
forall a b. (a -> b) -> a -> b
$ Value -> Type -> ByteString -> Builder
buildMultipartBody' Value
settings Type
applicationOctetStream' (ByteString -> ByteString
forall a b. ConvertibleStrings a b => a -> b
cs ByteString
bs)
Response
r1 <- Value -> ByteString -> App Response
forall user.
(HasCallStack, MakesValue user) =>
user -> ByteString -> App Response
uploadRaw Value
uid ByteString
body
Response
r1.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
201
String
tok <- Response
r1.jsonBody Maybe Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"token" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
String
key <- Response
r1.jsonBody Maybe Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"key" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
let ga :: Value
ga =
[Pair] -> Value
object
[ String
"user" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
userId2,
String
"key" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
key,
String
"domain" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
domain,
String
"token" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
tok
]
Response
r2 <- Value -> Value -> Value -> App Response
forall user loc tok.
(HasCallStack, MakesValue user, IsAssetLocation loc,
IsAssetToken tok) =>
user -> loc -> tok -> App Response
downloadAsset' Value
uid2 Value
ga Value
ga
Response
r2.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200
testStreamAsset :: (HasCallStack) => App ()
testStreamAsset :: HasCallStack => App ()
testStreamAsset = do
Value
uid <- Domain -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser Domain
OwnDomain CreateUser
forall a. Default a => a
def
Value
uid2 <- Domain -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser Domain
OtherDomain CreateUser
forall a. Default a => a
def
String
userId <- Value
uid Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"id" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
String
domain <- Value
uid Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"qualified_id" App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
Response
r1 <- Value -> Value -> (MIMEType, ByteString) -> App Response
forall user settings.
(HasCallStack, MakesValue user, MakesValue settings) =>
user -> settings -> (MIMEType, ByteString) -> App Response
uploadSimple Value
uid Value
settings (MIMEType, ByteString)
forall a. ConvertibleStrings String a => (MIMEType, a)
bdy
Response
r1.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
201
String
tok <- Response
r1.jsonBody Maybe Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"token" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
String
key <- Response
r1.jsonBody Maybe Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"key" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
let ga :: Value
ga = [Pair] -> Value
object [String
"user" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
userId, String
"token" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
tok, String
"key" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
key, String
"domain" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
domain]
Response
r2 <- Value -> Value -> Value -> App Response
forall user loc tok.
(HasCallStack, MakesValue user, IsAssetLocation loc,
IsAssetToken tok) =>
user -> loc -> tok -> App Response
downloadAsset' Value
uid2 Value
ga Value
ga
Response
r2.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
200
forall a b. ConvertibleStrings a b => a -> b
cs @_ @String Response
r2.body String -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` ((MIMEType, String) -> String
forall a b. (a, b) -> b
snd (MIMEType, String)
forall a. ConvertibleStrings String a => (MIMEType, a)
bdy :: String)
where
bdy :: (ConvertibleStrings String a) => (MIME.MIMEType, a)
bdy :: forall a. ConvertibleStrings String a => (MIMEType, a)
bdy = (MIMEType
applicationOctetStream, String -> a
forall a b. ConvertibleStrings a b => a -> b
cs String
"Hello World")
settings :: Value
settings = [Pair] -> Value
object [String
"public" String -> Bool -> Pair
forall a. ToJSON a => String -> a -> Pair
.= Bool
False, String
"retention" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"volatile"]
testStreamAssetNotAvailable :: (HasCallStack) => App ()
testStreamAssetNotAvailable :: HasCallStack => App ()
testStreamAssetNotAvailable = do
Value
uid <- Domain -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser Domain
OwnDomain CreateUser
forall a. Default a => a
def
Value
uid2 <- Domain -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser Domain
OtherDomain CreateUser
forall a. Default a => a
def
String
userId <- Value
uid2 Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"id" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
String
domain <- Value
uid Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"qualified_id" App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
String
token <- App String
HasCallStack => App String
randomToken
String
assetId <- App String
HasCallStack => App String
randomId
let key :: String
key = String
"3-2-" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
assetId
ga :: Value
ga = [Pair] -> Value
object [String
"user" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
userId, String
"token" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
token, String
"key" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
key, String
"domain" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
domain]
Response
r <- Value -> Value -> Value -> App Response
forall user loc tok.
(HasCallStack, MakesValue user, IsAssetLocation loc,
IsAssetToken tok) =>
user -> loc -> tok -> App Response
downloadAsset' Value
uid2 Value
ga Value
ga
Response
r.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
404
Response
r.jsonBody Maybe Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"message" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"Asset not found"
testStreamAssetWrongToken :: (HasCallStack) => App ()
testStreamAssetWrongToken :: HasCallStack => App ()
testStreamAssetWrongToken = do
Value
uid <- Domain -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser Domain
OwnDomain CreateUser
forall a. Default a => a
def
Value
uid2 <- Domain -> CreateUser -> App Value
forall domain.
(HasCallStack, MakesValue domain) =>
domain -> CreateUser -> App Value
randomUser Domain
OtherDomain CreateUser
forall a. Default a => a
def
String
userId2 <- Value
uid2 Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"id" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
String
domain <- Value
uid Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"qualified_id" App Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"domain" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
Response
r1 <- Value -> Value -> (MIMEType, ByteString) -> App Response
forall user settings.
(HasCallStack, MakesValue user, MakesValue settings) =>
user -> settings -> (MIMEType, ByteString) -> App Response
uploadSimple Value
uid Value
settings (MIMEType, ByteString)
forall a. ConvertibleStrings String a => (MIMEType, a)
bdy
Response
r1.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
201
String
tok <- App String
HasCallStack => App String
randomToken
String
key <- Response
r1.jsonBody Maybe Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"key" App Value -> (App Value -> App String) -> App String
forall a b. a -> (a -> b) -> b
& App Value -> App String
forall a. (HasCallStack, MakesValue a) => a -> App String
asString
let ga :: Value
ga = [Pair] -> Value
object [String
"user" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
userId2, String
"token" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
tok, String
"key" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
key, String
"domain" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
domain]
Response
r2 <- Value -> Value -> Value -> App Response
forall user loc tok.
(HasCallStack, MakesValue user, IsAssetLocation loc,
IsAssetToken tok) =>
user -> loc -> tok -> App Response
downloadAsset' Value
uid2 Value
ga Value
ga
Response
r2.status Int -> Int -> App ()
forall a. (MakesValue a, HasCallStack) => a -> Int -> App ()
`shouldMatchInt` Int
404
Response
r2.jsonBody Maybe Value -> String -> App Value
forall a. (HasCallStack, MakesValue a) => a -> String -> App Value
%. String
"message" App Value -> String -> App ()
forall a b.
(MakesValue a, MakesValue b, HasCallStack) =>
a -> b -> App ()
`shouldMatch` String
"Asset not found"
where
bdy :: (ConvertibleStrings String a) => (MIME.MIMEType, a)
bdy :: forall a. ConvertibleStrings String a => (MIMEType, a)
bdy = (MIMEType
applicationOctetStream, String -> a
forall a b. ConvertibleStrings a b => a -> b
cs String
"Hello World")
settings :: Value
settings = [Pair] -> Value
object [String
"public" String -> Bool -> Pair
forall a. ToJSON a => String -> a -> Pair
.= Bool
False, String
"retention" String -> String -> Pair
forall a. ToJSON a => String -> a -> Pair
.= String
"volatile"]