module AirGQL.Types.Types (
FileFormat (..),
FilenameField (..),
GQLPost (..),
GQLResponse (..),
gqlResponseToObject,
MetadataPair (..),
RawJsonMime,
Database (..),
UsageError (..),
)
where
import Protolude (
Eq,
Generic,
Maybe (Nothing),
Monoid (mempty),
Show,
Text,
)
import Protolude qualified as P
import Data.Aeson (
FromJSON,
KeyValue ((.=)),
Object,
ToJSON (toJSON),
Value (Object),
object,
)
import Database.SQLite.Simple qualified as SS
import Servant.Docs (ToSample (toSamples), singleSample)
data RawJsonMime
data FileFormat
= SQLiteFile
| CSVFile
| PlainTextFile
| DisallowedFile Text
deriving (Int -> FileFormat -> ShowS
[FileFormat] -> ShowS
FileFormat -> String
(Int -> FileFormat -> ShowS)
-> (FileFormat -> String)
-> ([FileFormat] -> ShowS)
-> Show FileFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FileFormat -> ShowS
showsPrec :: Int -> FileFormat -> ShowS
$cshow :: FileFormat -> String
show :: FileFormat -> String
$cshowList :: [FileFormat] -> ShowS
showList :: [FileFormat] -> ShowS
Show, FileFormat -> FileFormat -> Bool
(FileFormat -> FileFormat -> Bool)
-> (FileFormat -> FileFormat -> Bool) -> Eq FileFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FileFormat -> FileFormat -> Bool
== :: FileFormat -> FileFormat -> Bool
$c/= :: FileFormat -> FileFormat -> Bool
/= :: FileFormat -> FileFormat -> Bool
Eq)
data GQLPost = GQLPost
{ GQLPost -> Text
query :: Text
, GQLPost -> Maybe Text
operationName :: Maybe Text
, GQLPost -> Maybe Object
variables :: Maybe Object
}
deriving (GQLPost -> GQLPost -> Bool
(GQLPost -> GQLPost -> Bool)
-> (GQLPost -> GQLPost -> Bool) -> Eq GQLPost
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GQLPost -> GQLPost -> Bool
== :: GQLPost -> GQLPost -> Bool
$c/= :: GQLPost -> GQLPost -> Bool
/= :: GQLPost -> GQLPost -> Bool
Eq, Int -> GQLPost -> ShowS
[GQLPost] -> ShowS
GQLPost -> String
(Int -> GQLPost -> ShowS)
-> (GQLPost -> String) -> ([GQLPost] -> ShowS) -> Show GQLPost
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GQLPost -> ShowS
showsPrec :: Int -> GQLPost -> ShowS
$cshow :: GQLPost -> String
show :: GQLPost -> String
$cshowList :: [GQLPost] -> ShowS
showList :: [GQLPost] -> ShowS
Show, (forall x. GQLPost -> Rep GQLPost x)
-> (forall x. Rep GQLPost x -> GQLPost) -> Generic GQLPost
forall x. Rep GQLPost x -> GQLPost
forall x. GQLPost -> Rep GQLPost x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GQLPost -> Rep GQLPost x
from :: forall x. GQLPost -> Rep GQLPost x
$cto :: forall x. Rep GQLPost x -> GQLPost
to :: forall x. Rep GQLPost x -> GQLPost
Generic)
instance ToJSON GQLPost
instance FromJSON GQLPost
instance ToSample GQLPost where
toSamples :: Proxy GQLPost -> [(Text, GQLPost)]
toSamples Proxy GQLPost
_ =
GQLPost -> [(Text, GQLPost)]
forall a. a -> [(Text, a)]
singleSample
GQLPost
{ $sel:query:GQLPost :: Text
query = Text
"{ users { name, email } }"
, $sel:variables:GQLPost :: Maybe Object
variables = Maybe Object
forall a. Maybe a
Nothing
, $sel:operationName:GQLPost :: Maybe Text
operationName = Maybe Text
forall a. Maybe a
Nothing
}
data GQLResponse = GQLResponse
{ GQLResponse -> Maybe Value
data_ :: Maybe Value
, GQLResponse -> Maybe [Value]
errors :: Maybe [Value]
}
deriving (GQLResponse -> GQLResponse -> Bool
(GQLResponse -> GQLResponse -> Bool)
-> (GQLResponse -> GQLResponse -> Bool) -> Eq GQLResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GQLResponse -> GQLResponse -> Bool
== :: GQLResponse -> GQLResponse -> Bool
$c/= :: GQLResponse -> GQLResponse -> Bool
/= :: GQLResponse -> GQLResponse -> Bool
Eq, Int -> GQLResponse -> ShowS
[GQLResponse] -> ShowS
GQLResponse -> String
(Int -> GQLResponse -> ShowS)
-> (GQLResponse -> String)
-> ([GQLResponse] -> ShowS)
-> Show GQLResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GQLResponse -> ShowS
showsPrec :: Int -> GQLResponse -> ShowS
$cshow :: GQLResponse -> String
show :: GQLResponse -> String
$cshowList :: [GQLResponse] -> ShowS
showList :: [GQLResponse] -> ShowS
Show, (forall x. GQLResponse -> Rep GQLResponse x)
-> (forall x. Rep GQLResponse x -> GQLResponse)
-> Generic GQLResponse
forall x. Rep GQLResponse x -> GQLResponse
forall x. GQLResponse -> Rep GQLResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GQLResponse -> Rep GQLResponse x
from :: forall x. GQLResponse -> Rep GQLResponse x
$cto :: forall x. Rep GQLResponse x -> GQLResponse
to :: forall x. Rep GQLResponse x -> GQLResponse
Generic)
instance ToJSON GQLResponse where
toJSON :: GQLResponse -> Value
toJSON GQLResponse{Maybe Value
$sel:data_:GQLResponse :: GQLResponse -> Maybe Value
data_ :: Maybe Value
data_, Maybe [Value]
$sel:errors:GQLResponse :: GQLResponse -> Maybe [Value]
errors :: Maybe [Value]
errors} =
[Pair] -> Value
object
[ Key
"data" Key -> Maybe Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Maybe Value
data_
, Key
"errors" Key -> Maybe [Value] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Maybe [Value]
errors
]
newtype FilenameField = FilenameField Text
deriving ((forall x. FilenameField -> Rep FilenameField x)
-> (forall x. Rep FilenameField x -> FilenameField)
-> Generic FilenameField
forall x. Rep FilenameField x -> FilenameField
forall x. FilenameField -> Rep FilenameField x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FilenameField -> Rep FilenameField x
from :: forall x. FilenameField -> Rep FilenameField x
$cto :: forall x. Rep FilenameField x -> FilenameField
to :: forall x. Rep FilenameField x -> FilenameField
Generic, Int -> FilenameField -> ShowS
[FilenameField] -> ShowS
FilenameField -> String
(Int -> FilenameField -> ShowS)
-> (FilenameField -> String)
-> ([FilenameField] -> ShowS)
-> Show FilenameField
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FilenameField -> ShowS
showsPrec :: Int -> FilenameField -> ShowS
$cshow :: FilenameField -> String
show :: FilenameField -> String
$cshowList :: [FilenameField] -> ShowS
showList :: [FilenameField] -> ShowS
Show)
instance SS.FromRow FilenameField
data MetadataPair = MetadataPair
{ MetadataPair -> Text
attribute :: Text
, MetadataPair -> Text
value :: Text
}
deriving (MetadataPair -> MetadataPair -> Bool
(MetadataPair -> MetadataPair -> Bool)
-> (MetadataPair -> MetadataPair -> Bool) -> Eq MetadataPair
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MetadataPair -> MetadataPair -> Bool
== :: MetadataPair -> MetadataPair -> Bool
$c/= :: MetadataPair -> MetadataPair -> Bool
/= :: MetadataPair -> MetadataPair -> Bool
Eq, Int -> MetadataPair -> ShowS
[MetadataPair] -> ShowS
MetadataPair -> String
(Int -> MetadataPair -> ShowS)
-> (MetadataPair -> String)
-> ([MetadataPair] -> ShowS)
-> Show MetadataPair
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MetadataPair -> ShowS
showsPrec :: Int -> MetadataPair -> ShowS
$cshow :: MetadataPair -> String
show :: MetadataPair -> String
$cshowList :: [MetadataPair] -> ShowS
showList :: [MetadataPair] -> ShowS
Show, (forall x. MetadataPair -> Rep MetadataPair x)
-> (forall x. Rep MetadataPair x -> MetadataPair)
-> Generic MetadataPair
forall x. Rep MetadataPair x -> MetadataPair
forall x. MetadataPair -> Rep MetadataPair x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MetadataPair -> Rep MetadataPair x
from :: forall x. MetadataPair -> Rep MetadataPair x
$cto :: forall x. Rep MetadataPair x -> MetadataPair
to :: forall x. Rep MetadataPair x -> MetadataPair
Generic)
instance SS.FromRow MetadataPair
gqlResponseToObject :: GQLResponse -> Object
gqlResponseToObject :: GQLResponse -> Object
gqlResponseToObject GQLResponse
gqlRes =
case GQLResponse -> Value
forall a. ToJSON a => a -> Value
toJSON GQLResponse
gqlRes of
Object Object
obj -> Object
obj
Value
_ -> Object
forall a. Monoid a => a
mempty
data Database = Database
{ Database -> Text
id :: Text
, Database -> Text
name :: Text
, Database -> Maybe Text
environment :: Maybe Text
, Database -> Text
ownership_utc :: Text
}
deriving ((forall x. Database -> Rep Database x)
-> (forall x. Rep Database x -> Database) -> Generic Database
forall x. Rep Database x -> Database
forall x. Database -> Rep Database x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Database -> Rep Database x
from :: forall x. Database -> Rep Database x
$cto :: forall x. Rep Database x -> Database
to :: forall x. Rep Database x -> Database
Generic, Int -> Database -> ShowS
[Database] -> ShowS
Database -> String
(Int -> Database -> ShowS)
-> (Database -> String) -> ([Database] -> ShowS) -> Show Database
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Database -> ShowS
showsPrec :: Int -> Database -> ShowS
$cshow :: Database -> String
show :: Database -> String
$cshowList :: [Database] -> ShowS
showList :: [Database] -> ShowS
Show)
instance FromJSON Database
instance ToJSON Database
instance SS.FromRow Database
newtype UsageError = UsageError Text
deriving (UsageError -> UsageError -> Bool
(UsageError -> UsageError -> Bool)
-> (UsageError -> UsageError -> Bool) -> Eq UsageError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UsageError -> UsageError -> Bool
== :: UsageError -> UsageError -> Bool
$c/= :: UsageError -> UsageError -> Bool
/= :: UsageError -> UsageError -> Bool
Eq, Int -> UsageError -> ShowS
[UsageError] -> ShowS
UsageError -> String
(Int -> UsageError -> ShowS)
-> (UsageError -> String)
-> ([UsageError] -> ShowS)
-> Show UsageError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UsageError -> ShowS
showsPrec :: Int -> UsageError -> ShowS
$cshow :: UsageError -> String
show :: UsageError -> String
$cshowList :: [UsageError] -> ShowS
showList :: [UsageError] -> ShowS
Show)
instance P.Exception UsageError