mirror of
https://github.com/Airsequel/AirGQL.git
synced 2025-08-12 09:46:57 +03:00
Split off introspection tests into their own file
This commit is contained in:
parent
c5fbeee8bd
commit
346a0e017c
4 changed files with 854 additions and 884 deletions
|
@ -151,7 +151,7 @@ makeField field = do
|
|||
pure $ Out.Field field.description ty $ HashMap.fromList args
|
||||
|
||||
|
||||
-- | Create a resolver by calling which always returns a constant value.
|
||||
-- | Create a resolver which always returns a constant value.
|
||||
makeConstField :: IType.Field -> Type.Value -> Result (Out.Resolver IO)
|
||||
makeConstField field value = do
|
||||
gqlField <- makeField field
|
||||
|
|
1024
tests/Spec.hs
1024
tests/Spec.hs
File diff suppressed because it is too large
Load diff
656
tests/Tests/IntrospectionSpec.hs
Normal file
656
tests/Tests/IntrospectionSpec.hs
Normal file
|
@ -0,0 +1,656 @@
|
|||
{-# LANGUAGE QuasiQuotes #-}
|
||||
{-# LANGUAGE NoMonomorphismRestriction #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-local-signatures #-}
|
||||
|
||||
module Tests.IntrospectionSpec (main) where
|
||||
|
||||
import Protolude (
|
||||
Either (Right),
|
||||
Maybe (Nothing),
|
||||
Monoid (mempty),
|
||||
Text,
|
||||
readFile,
|
||||
void,
|
||||
($),
|
||||
)
|
||||
|
||||
import Data.Aeson qualified as Ae
|
||||
import Database.SQLite.Simple qualified as SS
|
||||
import Database.SQLite.Simple.QQ (sql)
|
||||
import Language.GraphQL.JSON (graphql)
|
||||
import Language.GraphQL.TH (gql)
|
||||
import System.Directory (makeAbsolute)
|
||||
import System.FilePath ((</>))
|
||||
import Test.Hspec (Spec, describe, it, shouldBe)
|
||||
|
||||
import AirGQL.GraphQL (getDerivedSchema)
|
||||
import AirGQL.Lib (AccessMode (WriteOnly), getEnrichedTables)
|
||||
import AirGQL.Raw (raw)
|
||||
import AirGQL.Types.SchemaConf (SchemaConf (accessMode), defaultSchemaConf)
|
||||
import AirGQL.Utils (withRetryConn)
|
||||
import Tests.Utils (dbPath, fixtureDbId, rmSpaces, testRoot, withTestDbConn)
|
||||
|
||||
|
||||
main :: Spec
|
||||
main = void $ do
|
||||
describe "Query" $ do
|
||||
it "supports a minimal introspection query" $ do
|
||||
let
|
||||
introspectionQuery :: Text
|
||||
introspectionQuery =
|
||||
[gql|
|
||||
query IntrospectionQuery {
|
||||
__schema {
|
||||
queryType { name }
|
||||
}
|
||||
}
|
||||
|]
|
||||
|
||||
expected =
|
||||
rmSpaces
|
||||
[raw|
|
||||
{
|
||||
"data": {
|
||||
"__schema": {
|
||||
"queryType": {
|
||||
"name": "Query"
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
|]
|
||||
|
||||
conn <- SS.open dbPath
|
||||
Right tables <- getEnrichedTables conn
|
||||
schema <- getDerivedSchema defaultSchemaConf conn fixtureDbId tables
|
||||
|
||||
Right result <- graphql schema Nothing mempty introspectionQuery
|
||||
|
||||
Ae.encode result `shouldBe` expected
|
||||
|
||||
it "supports an optional filter argument" $ do
|
||||
let
|
||||
introspectionQuery :: Text
|
||||
introspectionQuery =
|
||||
[gql|
|
||||
query IntrospectionQuery {
|
||||
__schema {
|
||||
queryType {
|
||||
name
|
||||
fields {
|
||||
name
|
||||
args {
|
||||
name
|
||||
type {
|
||||
name
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
|]
|
||||
expected =
|
||||
rmSpaces
|
||||
[raw|{
|
||||
"data": {
|
||||
"__schema": {
|
||||
"queryType": {
|
||||
"name": "Query",
|
||||
"fields": [
|
||||
{
|
||||
"name": "users",
|
||||
"args": [
|
||||
{ "name": "filter",
|
||||
"type": { "name": "users_filter" }
|
||||
},
|
||||
{ "name": "order_by",
|
||||
"type": { "name": null }
|
||||
},
|
||||
{ "name": "limit",
|
||||
"type": { "name": "Int" }
|
||||
},
|
||||
{ "name": "offset",
|
||||
"type": { "name": "Int" }
|
||||
}
|
||||
]
|
||||
},
|
||||
{
|
||||
"name": "songs",
|
||||
"args": [
|
||||
{ "name": "filter",
|
||||
"type": { "name": "songs_filter" }
|
||||
},
|
||||
{ "name": "order_by",
|
||||
"type": { "name": null }
|
||||
},
|
||||
{ "name": "limit",
|
||||
"type": { "name": "Int" }
|
||||
},
|
||||
{ "name": "offset",
|
||||
"type": { "name": "Int" }
|
||||
}
|
||||
]
|
||||
}
|
||||
]
|
||||
}
|
||||
}
|
||||
}
|
||||
}|]
|
||||
|
||||
conn <- SS.open dbPath
|
||||
Right tables <- getEnrichedTables conn
|
||||
schema <- getDerivedSchema defaultSchemaConf conn fixtureDbId tables
|
||||
|
||||
Right result <- graphql schema Nothing mempty introspectionQuery
|
||||
|
||||
Ae.encode result `shouldBe` expected
|
||||
|
||||
it "doesn't allow writeonly tokens to read data" $ do
|
||||
let
|
||||
introspectionQuery :: Text
|
||||
introspectionQuery =
|
||||
[gql|
|
||||
query IntrospectionQuery {
|
||||
__schema {
|
||||
queryType { name }
|
||||
}
|
||||
}
|
||||
|]
|
||||
|
||||
expected =
|
||||
rmSpaces
|
||||
[raw|
|
||||
{
|
||||
"data": null,
|
||||
"errors": [{
|
||||
"locations": [{ "column":3, "line":2 }],
|
||||
"message": "user error (Cannot read field using writeonly access code)",
|
||||
"path": ["__schema"]
|
||||
}]
|
||||
}
|
||||
|]
|
||||
|
||||
schema <- withRetryConn dbPath $ \conn -> do
|
||||
Right tables <- getEnrichedTables conn
|
||||
getDerivedSchema
|
||||
defaultSchemaConf{accessMode = WriteOnly}
|
||||
conn
|
||||
fixtureDbId
|
||||
tables
|
||||
|
||||
Right response <-
|
||||
graphql schema Nothing mempty introspectionQuery
|
||||
|
||||
Ae.encode response `shouldBe` expected
|
||||
|
||||
describe "Mutation" $ do
|
||||
it "supports introspection queries" $ do
|
||||
let
|
||||
introspectionQuery :: Text
|
||||
introspectionQuery =
|
||||
[gql|
|
||||
query IntrospectionQuery {
|
||||
__schema {
|
||||
mutationType {
|
||||
name
|
||||
fields {
|
||||
name
|
||||
args {
|
||||
name
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
|]
|
||||
expected =
|
||||
rmSpaces
|
||||
[raw|
|
||||
{
|
||||
"data": {
|
||||
"__schema": {
|
||||
"mutationType": {
|
||||
"name": "Mutation",
|
||||
"fields": [
|
||||
{
|
||||
"name": "insert_users",
|
||||
"args": [ { "name": "objects" }, { "name": "on_conflict" } ]
|
||||
},
|
||||
{
|
||||
"name": "update_users",
|
||||
"args": [
|
||||
{ "name": "filter" },
|
||||
{ "name": "set" }
|
||||
]
|
||||
},
|
||||
{
|
||||
"name": "delete_users",
|
||||
"args": [ { "name": "filter" } ]
|
||||
},
|
||||
{
|
||||
"name": "insert_songs",
|
||||
"args": [ { "name": "objects" }, { "name": "on_conflict" } ]
|
||||
},
|
||||
{
|
||||
"name": "update_songs",
|
||||
"args": [
|
||||
{ "name": "filter" },
|
||||
{ "name": "set" }
|
||||
]
|
||||
},
|
||||
{
|
||||
"name": "delete_songs",
|
||||
"args": [ { "name": "filter" } ]
|
||||
}
|
||||
]
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
|]
|
||||
|
||||
conn <- SS.open dbPath
|
||||
Right tables <- getEnrichedTables conn
|
||||
schema <- getDerivedSchema defaultSchemaConf conn fixtureDbId tables
|
||||
|
||||
Right result <- graphql schema Nothing mempty introspectionQuery
|
||||
|
||||
Ae.encode result `shouldBe` expected
|
||||
|
||||
it "supports __typename on root query" $ do
|
||||
let
|
||||
introspectionQuery =
|
||||
[gql|
|
||||
query TypeName {
|
||||
__typename
|
||||
}
|
||||
|]
|
||||
|
||||
expected =
|
||||
rmSpaces
|
||||
[raw|
|
||||
{
|
||||
"data": {
|
||||
"__typename" : "Query"
|
||||
}
|
||||
}
|
||||
|]
|
||||
|
||||
conn <- SS.open dbPath
|
||||
Right tables <- getEnrichedTables conn
|
||||
schema <- getDerivedSchema defaultSchemaConf conn fixtureDbId tables
|
||||
|
||||
Right result <- graphql schema Nothing mempty introspectionQuery
|
||||
|
||||
Ae.encode result `shouldBe` expected
|
||||
|
||||
it "returns fields for {query,mutation,subscription}Type" $ do
|
||||
let
|
||||
introspectionQuery =
|
||||
[gql|
|
||||
query {
|
||||
__schema {
|
||||
queryType { fields { name } }
|
||||
mutationType { fields { name } }
|
||||
subscriptionType { fields { name } }
|
||||
}
|
||||
}
|
||||
|]
|
||||
|
||||
expected =
|
||||
rmSpaces
|
||||
[raw|
|
||||
{
|
||||
"data": {
|
||||
"__schema": {
|
||||
"queryType": {
|
||||
"fields": [
|
||||
{ "name": "users" },
|
||||
{ "name": "songs" }
|
||||
]
|
||||
},
|
||||
"subscriptionType": null,
|
||||
"mutationType": {
|
||||
"fields": [
|
||||
{ "name": "insert_users" },
|
||||
{ "name": "update_users" },
|
||||
{ "name": "delete_users" },
|
||||
{ "name": "insert_songs" },
|
||||
{ "name": "update_songs" },
|
||||
{ "name": "delete_songs" }
|
||||
]
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
|]
|
||||
|
||||
conn <- SS.open dbPath
|
||||
Right tables <- getEnrichedTables conn
|
||||
schema <- getDerivedSchema defaultSchemaConf conn fixtureDbId tables
|
||||
|
||||
Right result <- graphql schema Nothing mempty introspectionQuery
|
||||
|
||||
Ae.encode result `shouldBe` expected
|
||||
|
||||
it "supports __typename fields" $ do
|
||||
let
|
||||
introspectionQuery =
|
||||
[gql|
|
||||
query UsersTypeName {
|
||||
users {
|
||||
__typename
|
||||
}
|
||||
}
|
||||
|]
|
||||
|
||||
expected =
|
||||
rmSpaces
|
||||
[raw|
|
||||
{
|
||||
"data": {
|
||||
"users": [
|
||||
{ "__typename" : "users_row" }
|
||||
]
|
||||
}
|
||||
}
|
||||
|]
|
||||
|
||||
conn <- SS.open dbPath
|
||||
SS.execute_
|
||||
conn
|
||||
[sql|
|
||||
insert into users (name, email, created_utc)
|
||||
values ('John', 'john@example.com', '2022-01-01T00:00Z')
|
||||
|]
|
||||
Right tables <- getEnrichedTables conn
|
||||
schema <- getDerivedSchema defaultSchemaConf conn fixtureDbId tables
|
||||
|
||||
Right result <- graphql schema Nothing mempty introspectionQuery
|
||||
|
||||
Ae.encode result `shouldBe` expected
|
||||
|
||||
it "returns types" $ do
|
||||
let
|
||||
introspectionQuery =
|
||||
[gql|
|
||||
query {
|
||||
__schema {
|
||||
types {
|
||||
kind
|
||||
name
|
||||
}
|
||||
}
|
||||
}
|
||||
|]
|
||||
expected =
|
||||
rmSpaces
|
||||
[raw|
|
||||
{
|
||||
"data": {
|
||||
"__schema": {
|
||||
"types": [
|
||||
{ "kind": "OBJECT", "name": "users_row" },
|
||||
{ "kind": "OBJECT", "name": "users_mutation_response" },
|
||||
{ "kind": "INPUT_OBJECT", "name": "users_insert_input" },
|
||||
{ "kind": "ENUM", "name": "users_column" },
|
||||
{ "kind": "INPUT_OBJECT", "name": "users_upsert_on_conflict" },
|
||||
{ "kind": "INPUT_OBJECT", "name": "users_set_input" },
|
||||
{ "kind": "INPUT_OBJECT", "name": "users_filter" },
|
||||
{ "kind": "INPUT_OBJECT", "name": "users_order_by" },
|
||||
|
||||
{ "kind": "OBJECT", "name": "songs_row" },
|
||||
{ "kind": "OBJECT", "name": "songs_mutation_response" },
|
||||
{ "kind": "INPUT_OBJECT", "name": "songs_insert_input" },
|
||||
{ "kind": "ENUM", "name": "songs_column" },
|
||||
{ "kind": "INPUT_OBJECT", "name": "songs_upsert_on_conflict" },
|
||||
{ "kind": "INPUT_OBJECT", "name": "songs_set_input" },
|
||||
{ "kind": "INPUT_OBJECT", "name": "songs_filter" },
|
||||
{ "kind": "INPUT_OBJECT", "name": "songs_order_by" },
|
||||
|
||||
{ "kind": "INPUT_OBJECT", "name": "IntComparison" },
|
||||
{ "kind": "INPUT_OBJECT", "name": "FloatComparison" },
|
||||
{ "kind": "INPUT_OBJECT", "name": "StringComparison" },
|
||||
{ "kind": "INPUT_OBJECT", "name": "BooleanComparison" },
|
||||
|
||||
{ "kind": "ENUM", "name": "OrderingTerm" },
|
||||
|
||||
{ "kind": "OBJECT", "name": "Query" },
|
||||
{ "kind": "OBJECT", "name": "Mutation" },
|
||||
{ "kind": "SCALAR", "name": "Boolean" },
|
||||
{ "kind": "SCALAR", "name": "Int" },
|
||||
{ "kind": "SCALAR", "name": "Float" },
|
||||
{ "kind": "SCALAR", "name": "String" },
|
||||
{ "kind": "SCALAR", "name": "ID" },
|
||||
{ "kind": "SCALAR", "name": "Upload" },
|
||||
{ "kind": "OBJECT", "name": "__Schema" },
|
||||
{ "kind": "OBJECT", "name": "__Type" },
|
||||
{ "kind": "ENUM", "name": "__TypeKind" },
|
||||
{ "kind": "OBJECT", "name": "__Field" },
|
||||
{ "kind": "OBJECT", "name": "__InputValue" },
|
||||
{ "kind": "OBJECT", "name": "__EnumValue" },
|
||||
{ "kind": "OBJECT", "name": "__Directive" },
|
||||
{ "kind": "ENUM", "name": "__DirectiveLocation" }
|
||||
]
|
||||
}
|
||||
}
|
||||
}
|
||||
|]
|
||||
|
||||
conn <- SS.open dbPath
|
||||
Right tables <- getEnrichedTables conn
|
||||
schema <- getDerivedSchema defaultSchemaConf conn fixtureDbId tables
|
||||
|
||||
Right result <- graphql schema Nothing mempty introspectionQuery
|
||||
|
||||
Ae.encode result `shouldBe` expected
|
||||
|
||||
it "returns directives on __schema" $ do
|
||||
let
|
||||
introspectionQuery :: Text =
|
||||
[gql|
|
||||
query UsersTypeName {
|
||||
__schema {
|
||||
directives {
|
||||
name
|
||||
description
|
||||
locations
|
||||
args {
|
||||
name
|
||||
description
|
||||
defaultValue
|
||||
type { ...TypeRef }
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
|
||||
fragment TypeRef on __Type {
|
||||
kind
|
||||
name
|
||||
ofType {
|
||||
kind
|
||||
name
|
||||
ofType {
|
||||
kind
|
||||
name
|
||||
ofType {
|
||||
kind
|
||||
name
|
||||
ofType {
|
||||
kind
|
||||
name
|
||||
ofType {
|
||||
kind
|
||||
name
|
||||
ofType {
|
||||
kind
|
||||
name
|
||||
ofType {
|
||||
kind
|
||||
name
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
|]
|
||||
expected =
|
||||
rmSpaces
|
||||
[raw|
|
||||
{
|
||||
"data": {
|
||||
"__schema": {
|
||||
"directives": [
|
||||
{
|
||||
"name": "skip",
|
||||
"args": [
|
||||
{
|
||||
"name": "if",
|
||||
"defaultValue": null,
|
||||
"type": {
|
||||
"kind": "NON_NULL",
|
||||
"name": null,
|
||||
"ofType": {
|
||||
"kind":"SCALAR",
|
||||
"name":"Boolean",
|
||||
"ofType":null
|
||||
}
|
||||
},
|
||||
"description": "Skipped when true."
|
||||
}
|
||||
],
|
||||
"locations": [
|
||||
"INLINE_FRAGMENT",
|
||||
"FRAGMENT_SPREAD",
|
||||
"FIELD"
|
||||
],
|
||||
"description": "Directs the executor to skip this field or fragment when the `if` argument is true."
|
||||
},
|
||||
{
|
||||
"name": "include",
|
||||
"args": [
|
||||
{
|
||||
"name": "if",
|
||||
"defaultValue": null,
|
||||
"type": {
|
||||
"kind": "NON_NULL",
|
||||
"name": null,
|
||||
"ofType": {
|
||||
"kind":"SCALAR",
|
||||
"name":"Boolean",
|
||||
"ofType":null
|
||||
}
|
||||
},
|
||||
"description": "Included when true."
|
||||
}
|
||||
],
|
||||
"locations": [
|
||||
"INLINE_FRAGMENT",
|
||||
"FRAGMENT_SPREAD",
|
||||
"FIELD"
|
||||
],
|
||||
"description":
|
||||
"Directs the executor to include this field or fragment only when the `if` argument is true."
|
||||
},
|
||||
{
|
||||
"name": "deprecated",
|
||||
"args": [
|
||||
{
|
||||
"name": "reason",
|
||||
"defaultValue": "\"No longer supported\"",
|
||||
"type": {
|
||||
"kind": "SCALAR",
|
||||
"name": "String",
|
||||
"ofType": null
|
||||
},
|
||||
"description":
|
||||
"Explains why this element was deprecated, usually also including a suggestion for how to access supported similar data. Formatted using the Markdown syntax (as specified by [CommonMark](https://commonmark.org/)."
|
||||
}
|
||||
],
|
||||
"locations": [
|
||||
"ENUM_VALUE",
|
||||
"FIELD_DEFINITION"
|
||||
],
|
||||
"description":
|
||||
"Marks an element of a GraphQL schema as no longer supported."
|
||||
}
|
||||
]
|
||||
}
|
||||
}
|
||||
}
|
||||
|]
|
||||
|
||||
conn <- SS.open dbPath
|
||||
Right tables <- getEnrichedTables conn
|
||||
schema <- getDerivedSchema defaultSchemaConf conn fixtureDbId tables
|
||||
|
||||
Right result <- graphql schema Nothing mempty introspectionQuery
|
||||
|
||||
Ae.encode result `shouldBe` expected
|
||||
|
||||
it "supports a full introspection query" $ do
|
||||
gqlFile <- makeAbsolute $ testRoot </> "introspection_query.gql"
|
||||
introspectionQuery <- readFile gqlFile
|
||||
|
||||
jsonFile <- makeAbsolute $ testRoot </> "introspection_result.json"
|
||||
expected <- readFile jsonFile
|
||||
|
||||
conn <- SS.open dbPath
|
||||
Right tables <- getEnrichedTables conn
|
||||
schema <- getDerivedSchema defaultSchemaConf conn fixtureDbId tables
|
||||
|
||||
Right result <- graphql schema Nothing mempty introspectionQuery
|
||||
|
||||
Ae.encode result `shouldBe` rmSpaces expected
|
||||
|
||||
it "doesn't allow writeonly tokens to return data" $ do
|
||||
let dbName = "no-writeonly-return.db"
|
||||
withTestDbConn dbName $ \conn -> do
|
||||
SS.execute_
|
||||
conn
|
||||
[sql|
|
||||
CREATE TABLE items (
|
||||
id INTEGER PRIMARY KEY
|
||||
)
|
||||
|]
|
||||
|
||||
let
|
||||
query :: Text
|
||||
query =
|
||||
[gql|
|
||||
mutation items {
|
||||
update_items(filter: { id: { eq: 0 }}, set: { id: 0 }) {
|
||||
returning { id }
|
||||
}
|
||||
}
|
||||
|]
|
||||
|
||||
expected =
|
||||
rmSpaces
|
||||
[raw|
|
||||
{
|
||||
"data": null,
|
||||
"errors": [{
|
||||
"locations": [{ "column":3, "line":2 }],
|
||||
"message": "Cannot query field \"update_items\" on type \"Mutation\"."
|
||||
}]
|
||||
}
|
||||
|]
|
||||
|
||||
schema <- withRetryConn dbPath $ \conn -> do
|
||||
Right tables <- getEnrichedTables conn
|
||||
getDerivedSchema
|
||||
defaultSchemaConf{accessMode = WriteOnly}
|
||||
conn
|
||||
fixtureDbId
|
||||
tables
|
||||
|
||||
Right response <-
|
||||
graphql schema Nothing mempty query
|
||||
|
||||
Ae.encode response `shouldBe` expected
|
|
@ -1,17 +1,32 @@
|
|||
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
|
||||
|
||||
{-# HLINT ignore "Replace case with maybe" #-}
|
||||
|
||||
module Tests.Utils (
|
||||
testRoot,
|
||||
withDataDbConn,
|
||||
withTestDbConn,
|
||||
rmSpaces,
|
||||
dbPath,
|
||||
fixtureDbId,
|
||||
shouldSaveDbs,
|
||||
) where
|
||||
|
||||
import Protolude (
|
||||
Bool (True),
|
||||
FilePath,
|
||||
IO,
|
||||
Maybe (Just, Nothing),
|
||||
Text,
|
||||
encodeUtf8,
|
||||
pure,
|
||||
($),
|
||||
(&),
|
||||
(<>),
|
||||
)
|
||||
|
||||
import Data.Aeson qualified as Ae
|
||||
import Data.ByteString.Lazy qualified as BL
|
||||
import Database.SQLite.Simple qualified as SS
|
||||
import System.Directory (createDirectoryIfMissing, removePathForcibly)
|
||||
import System.FilePath ((</>))
|
||||
|
@ -23,9 +38,31 @@ testRoot :: FilePath
|
|||
testRoot = "../../airgql/tests"
|
||||
|
||||
|
||||
dbPath :: FilePath
|
||||
dbPath = testRoot </> "fixture.db"
|
||||
|
||||
|
||||
-- Although airsequel tries its best to be separate from Airsequel proper,
|
||||
-- it looks like a bunch of functions still take database ids as arguments,
|
||||
-- even though this concept doesn't exist in airgql. Example usages include:
|
||||
-- - including the ID in error messages
|
||||
-- - generating an url where the user can access a file when it's cell needs
|
||||
-- to be converted to graphql
|
||||
--
|
||||
-- I don't think any of the usages matter when testing,
|
||||
-- so we use a dummy id instead.
|
||||
fixtureDbId :: Text
|
||||
fixtureDbId = "fixtures-db"
|
||||
|
||||
|
||||
-- | Save test databases after running tests for later inspection
|
||||
shouldSaveDbs :: Bool
|
||||
shouldSaveDbs = True
|
||||
|
||||
|
||||
-- | Get a connection to a database in the test database directory
|
||||
withTestDbConn :: Bool -> FilePath -> (SS.Connection -> IO a) -> IO a
|
||||
withTestDbConn shouldSaveDbs testDbPath callback = do
|
||||
withTestDbConn :: FilePath -> (SS.Connection -> IO a) -> IO a
|
||||
withTestDbConn testDbPath callback = do
|
||||
removeIfExists $ testRoot </> testDbPath
|
||||
withRetryConn
|
||||
(if shouldSaveDbs then testRoot </> testDbPath else ":memory:")
|
||||
|
@ -39,3 +76,18 @@ withDataDbConn testDbDir callback = do
|
|||
removePathForcibly fullPath
|
||||
createDirectoryIfMissing True fullPath
|
||||
withRetryConn (fullPath </> "main.sqlite") callback
|
||||
|
||||
|
||||
rmSpaces :: Text -> BL.ByteString
|
||||
rmSpaces text =
|
||||
let
|
||||
value :: Maybe Ae.Value =
|
||||
text
|
||||
& encodeUtf8
|
||||
& pure
|
||||
& BL.fromChunks
|
||||
& Ae.decode
|
||||
in
|
||||
case value of
|
||||
Just val -> Ae.encode val
|
||||
Nothing -> "ERROR: Failed to decode JSON"
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue