{-# LANGUAGE TemplateHaskell #-}
module Hasura.RQL.Types.QueryCollection
( CollectionName (..),
CollectionDef (..),
cdQueries,
CreateCollection (..),
ccName,
ccDefinition,
ccComment,
RenameCollection (..),
rcName,
rcNewName,
AddQueryToCollection (..),
DropQueryFromCollection (..),
DropCollection (..),
GQLQuery (..),
GQLQueryWithText (..),
QueryName (..),
ListedQuery (..),
getGQLQuery,
getGQLQueryText,
QueryCollections,
collectionQueries,
)
where
import Control.Lens
import Data.Aeson
import Data.Aeson.TH
import Data.Text.Extended
import Data.Text.NonEmpty
import Database.PG.Query qualified as Q
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
import Language.GraphQL.Draft.Syntax qualified as G
newtype CollectionName = CollectionName {CollectionName -> NonEmptyText
unCollectionName :: NonEmptyText}
deriving
( Int -> CollectionName -> ShowS
[CollectionName] -> ShowS
CollectionName -> String
(Int -> CollectionName -> ShowS)
-> (CollectionName -> String)
-> ([CollectionName] -> ShowS)
-> Show CollectionName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CollectionName] -> ShowS
$cshowList :: [CollectionName] -> ShowS
show :: CollectionName -> String
$cshow :: CollectionName -> String
showsPrec :: Int -> CollectionName -> ShowS
$cshowsPrec :: Int -> CollectionName -> ShowS
Show,
CollectionName -> CollectionName -> Bool
(CollectionName -> CollectionName -> Bool)
-> (CollectionName -> CollectionName -> Bool) -> Eq CollectionName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CollectionName -> CollectionName -> Bool
$c/= :: CollectionName -> CollectionName -> Bool
== :: CollectionName -> CollectionName -> Bool
$c== :: CollectionName -> CollectionName -> Bool
Eq,
Eq CollectionName
Eq CollectionName
-> (CollectionName -> CollectionName -> Ordering)
-> (CollectionName -> CollectionName -> Bool)
-> (CollectionName -> CollectionName -> Bool)
-> (CollectionName -> CollectionName -> Bool)
-> (CollectionName -> CollectionName -> Bool)
-> (CollectionName -> CollectionName -> CollectionName)
-> (CollectionName -> CollectionName -> CollectionName)
-> Ord CollectionName
CollectionName -> CollectionName -> Bool
CollectionName -> CollectionName -> Ordering
CollectionName -> CollectionName -> CollectionName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CollectionName -> CollectionName -> CollectionName
$cmin :: CollectionName -> CollectionName -> CollectionName
max :: CollectionName -> CollectionName -> CollectionName
$cmax :: CollectionName -> CollectionName -> CollectionName
>= :: CollectionName -> CollectionName -> Bool
$c>= :: CollectionName -> CollectionName -> Bool
> :: CollectionName -> CollectionName -> Bool
$c> :: CollectionName -> CollectionName -> Bool
<= :: CollectionName -> CollectionName -> Bool
$c<= :: CollectionName -> CollectionName -> Bool
< :: CollectionName -> CollectionName -> Bool
$c< :: CollectionName -> CollectionName -> Bool
compare :: CollectionName -> CollectionName -> Ordering
$ccompare :: CollectionName -> CollectionName -> Ordering
$cp1Ord :: Eq CollectionName
Ord,
Int -> CollectionName -> Int
CollectionName -> Int
(Int -> CollectionName -> Int)
-> (CollectionName -> Int) -> Hashable CollectionName
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: CollectionName -> Int
$chash :: CollectionName -> Int
hashWithSalt :: Int -> CollectionName -> Int
$chashWithSalt :: Int -> CollectionName -> Int
Hashable,
[CollectionName] -> Value
[CollectionName] -> Encoding
CollectionName -> Value
CollectionName -> Encoding
(CollectionName -> Value)
-> (CollectionName -> Encoding)
-> ([CollectionName] -> Value)
-> ([CollectionName] -> Encoding)
-> ToJSON CollectionName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CollectionName] -> Encoding
$ctoEncodingList :: [CollectionName] -> Encoding
toJSONList :: [CollectionName] -> Value
$ctoJSONList :: [CollectionName] -> Value
toEncoding :: CollectionName -> Encoding
$ctoEncoding :: CollectionName -> Encoding
toJSON :: CollectionName -> Value
$ctoJSON :: CollectionName -> Value
ToJSON,
ToJSONKeyFunction [CollectionName]
ToJSONKeyFunction CollectionName
ToJSONKeyFunction CollectionName
-> ToJSONKeyFunction [CollectionName] -> ToJSONKey CollectionName
forall a.
ToJSONKeyFunction a -> ToJSONKeyFunction [a] -> ToJSONKey a
toJSONKeyList :: ToJSONKeyFunction [CollectionName]
$ctoJSONKeyList :: ToJSONKeyFunction [CollectionName]
toJSONKey :: ToJSONKeyFunction CollectionName
$ctoJSONKey :: ToJSONKeyFunction CollectionName
ToJSONKey,
Value -> Parser [CollectionName]
Value -> Parser CollectionName
(Value -> Parser CollectionName)
-> (Value -> Parser [CollectionName]) -> FromJSON CollectionName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CollectionName]
$cparseJSONList :: Value -> Parser [CollectionName]
parseJSON :: Value -> Parser CollectionName
$cparseJSON :: Value -> Parser CollectionName
FromJSON,
Maybe ByteString -> Either Text CollectionName
(Maybe ByteString -> Either Text CollectionName)
-> FromCol CollectionName
forall a. (Maybe ByteString -> Either Text a) -> FromCol a
fromCol :: Maybe ByteString -> Either Text CollectionName
$cfromCol :: Maybe ByteString -> Either Text CollectionName
Q.FromCol,
CollectionName -> PrepArg
(CollectionName -> PrepArg) -> ToPrepArg CollectionName
forall a. (a -> PrepArg) -> ToPrepArg a
toPrepVal :: CollectionName -> PrepArg
$ctoPrepVal :: CollectionName -> PrepArg
Q.ToPrepArg,
CollectionName -> Text
(CollectionName -> Text) -> ToTxt CollectionName
forall a. (a -> Text) -> ToTxt a
toTxt :: CollectionName -> Text
$ctoTxt :: CollectionName -> Text
ToTxt,
(forall x. CollectionName -> Rep CollectionName x)
-> (forall x. Rep CollectionName x -> CollectionName)
-> Generic CollectionName
forall x. Rep CollectionName x -> CollectionName
forall x. CollectionName -> Rep CollectionName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CollectionName x -> CollectionName
$cfrom :: forall x. CollectionName -> Rep CollectionName x
Generic
)
newtype QueryName = QueryName {QueryName -> NonEmptyText
unQueryName :: NonEmptyText}
deriving (Int -> QueryName -> ShowS
[QueryName] -> ShowS
QueryName -> String
(Int -> QueryName -> ShowS)
-> (QueryName -> String)
-> ([QueryName] -> ShowS)
-> Show QueryName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QueryName] -> ShowS
$cshowList :: [QueryName] -> ShowS
show :: QueryName -> String
$cshow :: QueryName -> String
showsPrec :: Int -> QueryName -> ShowS
$cshowsPrec :: Int -> QueryName -> ShowS
Show, QueryName -> QueryName -> Bool
(QueryName -> QueryName -> Bool)
-> (QueryName -> QueryName -> Bool) -> Eq QueryName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryName -> QueryName -> Bool
$c/= :: QueryName -> QueryName -> Bool
== :: QueryName -> QueryName -> Bool
$c== :: QueryName -> QueryName -> Bool
Eq, Eq QueryName
Eq QueryName
-> (QueryName -> QueryName -> Ordering)
-> (QueryName -> QueryName -> Bool)
-> (QueryName -> QueryName -> Bool)
-> (QueryName -> QueryName -> Bool)
-> (QueryName -> QueryName -> Bool)
-> (QueryName -> QueryName -> QueryName)
-> (QueryName -> QueryName -> QueryName)
-> Ord QueryName
QueryName -> QueryName -> Bool
QueryName -> QueryName -> Ordering
QueryName -> QueryName -> QueryName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: QueryName -> QueryName -> QueryName
$cmin :: QueryName -> QueryName -> QueryName
max :: QueryName -> QueryName -> QueryName
$cmax :: QueryName -> QueryName -> QueryName
>= :: QueryName -> QueryName -> Bool
$c>= :: QueryName -> QueryName -> Bool
> :: QueryName -> QueryName -> Bool
$c> :: QueryName -> QueryName -> Bool
<= :: QueryName -> QueryName -> Bool
$c<= :: QueryName -> QueryName -> Bool
< :: QueryName -> QueryName -> Bool
$c< :: QueryName -> QueryName -> Bool
compare :: QueryName -> QueryName -> Ordering
$ccompare :: QueryName -> QueryName -> Ordering
$cp1Ord :: Eq QueryName
Ord, QueryName -> ()
(QueryName -> ()) -> NFData QueryName
forall a. (a -> ()) -> NFData a
rnf :: QueryName -> ()
$crnf :: QueryName -> ()
NFData, Int -> QueryName -> Int
QueryName -> Int
(Int -> QueryName -> Int)
-> (QueryName -> Int) -> Hashable QueryName
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: QueryName -> Int
$chash :: QueryName -> Int
hashWithSalt :: Int -> QueryName -> Int
$chashWithSalt :: Int -> QueryName -> Int
Hashable, [QueryName] -> Value
[QueryName] -> Encoding
QueryName -> Value
QueryName -> Encoding
(QueryName -> Value)
-> (QueryName -> Encoding)
-> ([QueryName] -> Value)
-> ([QueryName] -> Encoding)
-> ToJSON QueryName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [QueryName] -> Encoding
$ctoEncodingList :: [QueryName] -> Encoding
toJSONList :: [QueryName] -> Value
$ctoJSONList :: [QueryName] -> Value
toEncoding :: QueryName -> Encoding
$ctoEncoding :: QueryName -> Encoding
toJSON :: QueryName -> Value
$ctoJSON :: QueryName -> Value
ToJSON, ToJSONKeyFunction [QueryName]
ToJSONKeyFunction QueryName
ToJSONKeyFunction QueryName
-> ToJSONKeyFunction [QueryName] -> ToJSONKey QueryName
forall a.
ToJSONKeyFunction a -> ToJSONKeyFunction [a] -> ToJSONKey a
toJSONKeyList :: ToJSONKeyFunction [QueryName]
$ctoJSONKeyList :: ToJSONKeyFunction [QueryName]
toJSONKey :: ToJSONKeyFunction QueryName
$ctoJSONKey :: ToJSONKeyFunction QueryName
ToJSONKey, Value -> Parser [QueryName]
Value -> Parser QueryName
(Value -> Parser QueryName)
-> (Value -> Parser [QueryName]) -> FromJSON QueryName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [QueryName]
$cparseJSONList :: Value -> Parser [QueryName]
parseJSON :: Value -> Parser QueryName
$cparseJSON :: Value -> Parser QueryName
FromJSON, QueryName -> Text
(QueryName -> Text) -> ToTxt QueryName
forall a. (a -> Text) -> ToTxt a
toTxt :: QueryName -> Text
$ctoTxt :: QueryName -> Text
ToTxt, (forall x. QueryName -> Rep QueryName x)
-> (forall x. Rep QueryName x -> QueryName) -> Generic QueryName
forall x. Rep QueryName x -> QueryName
forall x. QueryName -> Rep QueryName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep QueryName x -> QueryName
$cfrom :: forall x. QueryName -> Rep QueryName x
Generic, Eq QueryName
Eq QueryName
-> (Accesses -> QueryName -> QueryName -> Bool)
-> Cacheable QueryName
Accesses -> QueryName -> QueryName -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> QueryName -> QueryName -> Bool
$cunchanged :: Accesses -> QueryName -> QueryName -> Bool
$cp1Cacheable :: Eq QueryName
Cacheable)
newtype GQLQuery = GQLQuery {GQLQuery -> ExecutableDocument Name
unGQLQuery :: G.ExecutableDocument G.Name}
deriving (Int -> GQLQuery -> ShowS
[GQLQuery] -> ShowS
GQLQuery -> String
(Int -> GQLQuery -> ShowS)
-> (GQLQuery -> String) -> ([GQLQuery] -> ShowS) -> Show GQLQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GQLQuery] -> ShowS
$cshowList :: [GQLQuery] -> ShowS
show :: GQLQuery -> String
$cshow :: GQLQuery -> String
showsPrec :: Int -> GQLQuery -> ShowS
$cshowsPrec :: Int -> GQLQuery -> ShowS
Show, GQLQuery -> GQLQuery -> Bool
(GQLQuery -> GQLQuery -> Bool)
-> (GQLQuery -> GQLQuery -> Bool) -> Eq GQLQuery
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GQLQuery -> GQLQuery -> Bool
$c/= :: GQLQuery -> GQLQuery -> Bool
== :: GQLQuery -> GQLQuery -> Bool
$c== :: GQLQuery -> GQLQuery -> Bool
Eq, Eq GQLQuery
Eq GQLQuery
-> (GQLQuery -> GQLQuery -> Ordering)
-> (GQLQuery -> GQLQuery -> Bool)
-> (GQLQuery -> GQLQuery -> Bool)
-> (GQLQuery -> GQLQuery -> Bool)
-> (GQLQuery -> GQLQuery -> Bool)
-> (GQLQuery -> GQLQuery -> GQLQuery)
-> (GQLQuery -> GQLQuery -> GQLQuery)
-> Ord GQLQuery
GQLQuery -> GQLQuery -> Bool
GQLQuery -> GQLQuery -> Ordering
GQLQuery -> GQLQuery -> GQLQuery
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GQLQuery -> GQLQuery -> GQLQuery
$cmin :: GQLQuery -> GQLQuery -> GQLQuery
max :: GQLQuery -> GQLQuery -> GQLQuery
$cmax :: GQLQuery -> GQLQuery -> GQLQuery
>= :: GQLQuery -> GQLQuery -> Bool
$c>= :: GQLQuery -> GQLQuery -> Bool
> :: GQLQuery -> GQLQuery -> Bool
$c> :: GQLQuery -> GQLQuery -> Bool
<= :: GQLQuery -> GQLQuery -> Bool
$c<= :: GQLQuery -> GQLQuery -> Bool
< :: GQLQuery -> GQLQuery -> Bool
$c< :: GQLQuery -> GQLQuery -> Bool
compare :: GQLQuery -> GQLQuery -> Ordering
$ccompare :: GQLQuery -> GQLQuery -> Ordering
$cp1Ord :: Eq GQLQuery
Ord, GQLQuery -> ()
(GQLQuery -> ()) -> NFData GQLQuery
forall a. (a -> ()) -> NFData a
rnf :: GQLQuery -> ()
$crnf :: GQLQuery -> ()
NFData, Int -> GQLQuery -> Int
GQLQuery -> Int
(Int -> GQLQuery -> Int) -> (GQLQuery -> Int) -> Hashable GQLQuery
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: GQLQuery -> Int
$chash :: GQLQuery -> Int
hashWithSalt :: Int -> GQLQuery -> Int
$chashWithSalt :: Int -> GQLQuery -> Int
Hashable, [GQLQuery] -> Value
[GQLQuery] -> Encoding
GQLQuery -> Value
GQLQuery -> Encoding
(GQLQuery -> Value)
-> (GQLQuery -> Encoding)
-> ([GQLQuery] -> Value)
-> ([GQLQuery] -> Encoding)
-> ToJSON GQLQuery
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [GQLQuery] -> Encoding
$ctoEncodingList :: [GQLQuery] -> Encoding
toJSONList :: [GQLQuery] -> Value
$ctoJSONList :: [GQLQuery] -> Value
toEncoding :: GQLQuery -> Encoding
$ctoEncoding :: GQLQuery -> Encoding
toJSON :: GQLQuery -> Value
$ctoJSON :: GQLQuery -> Value
ToJSON, Value -> Parser [GQLQuery]
Value -> Parser GQLQuery
(Value -> Parser GQLQuery)
-> (Value -> Parser [GQLQuery]) -> FromJSON GQLQuery
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [GQLQuery]
$cparseJSONList :: Value -> Parser [GQLQuery]
parseJSON :: Value -> Parser GQLQuery
$cparseJSON :: Value -> Parser GQLQuery
FromJSON, Eq GQLQuery
Eq GQLQuery
-> (Accesses -> GQLQuery -> GQLQuery -> Bool) -> Cacheable GQLQuery
Accesses -> GQLQuery -> GQLQuery -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> GQLQuery -> GQLQuery -> Bool
$cunchanged :: Accesses -> GQLQuery -> GQLQuery -> Bool
$cp1Cacheable :: Eq GQLQuery
Cacheable)
newtype GQLQueryWithText
= GQLQueryWithText (Text, GQLQuery)
deriving (Int -> GQLQueryWithText -> ShowS
[GQLQueryWithText] -> ShowS
GQLQueryWithText -> String
(Int -> GQLQueryWithText -> ShowS)
-> (GQLQueryWithText -> String)
-> ([GQLQueryWithText] -> ShowS)
-> Show GQLQueryWithText
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GQLQueryWithText] -> ShowS
$cshowList :: [GQLQueryWithText] -> ShowS
show :: GQLQueryWithText -> String
$cshow :: GQLQueryWithText -> String
showsPrec :: Int -> GQLQueryWithText -> ShowS
$cshowsPrec :: Int -> GQLQueryWithText -> ShowS
Show, GQLQueryWithText -> GQLQueryWithText -> Bool
(GQLQueryWithText -> GQLQueryWithText -> Bool)
-> (GQLQueryWithText -> GQLQueryWithText -> Bool)
-> Eq GQLQueryWithText
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GQLQueryWithText -> GQLQueryWithText -> Bool
$c/= :: GQLQueryWithText -> GQLQueryWithText -> Bool
== :: GQLQueryWithText -> GQLQueryWithText -> Bool
$c== :: GQLQueryWithText -> GQLQueryWithText -> Bool
Eq, Eq GQLQueryWithText
Eq GQLQueryWithText
-> (GQLQueryWithText -> GQLQueryWithText -> Ordering)
-> (GQLQueryWithText -> GQLQueryWithText -> Bool)
-> (GQLQueryWithText -> GQLQueryWithText -> Bool)
-> (GQLQueryWithText -> GQLQueryWithText -> Bool)
-> (GQLQueryWithText -> GQLQueryWithText -> Bool)
-> (GQLQueryWithText -> GQLQueryWithText -> GQLQueryWithText)
-> (GQLQueryWithText -> GQLQueryWithText -> GQLQueryWithText)
-> Ord GQLQueryWithText
GQLQueryWithText -> GQLQueryWithText -> Bool
GQLQueryWithText -> GQLQueryWithText -> Ordering
GQLQueryWithText -> GQLQueryWithText -> GQLQueryWithText
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GQLQueryWithText -> GQLQueryWithText -> GQLQueryWithText
$cmin :: GQLQueryWithText -> GQLQueryWithText -> GQLQueryWithText
max :: GQLQueryWithText -> GQLQueryWithText -> GQLQueryWithText
$cmax :: GQLQueryWithText -> GQLQueryWithText -> GQLQueryWithText
>= :: GQLQueryWithText -> GQLQueryWithText -> Bool
$c>= :: GQLQueryWithText -> GQLQueryWithText -> Bool
> :: GQLQueryWithText -> GQLQueryWithText -> Bool
$c> :: GQLQueryWithText -> GQLQueryWithText -> Bool
<= :: GQLQueryWithText -> GQLQueryWithText -> Bool
$c<= :: GQLQueryWithText -> GQLQueryWithText -> Bool
< :: GQLQueryWithText -> GQLQueryWithText -> Bool
$c< :: GQLQueryWithText -> GQLQueryWithText -> Bool
compare :: GQLQueryWithText -> GQLQueryWithText -> Ordering
$ccompare :: GQLQueryWithText -> GQLQueryWithText -> Ordering
$cp1Ord :: Eq GQLQueryWithText
Ord, GQLQueryWithText -> ()
(GQLQueryWithText -> ()) -> NFData GQLQueryWithText
forall a. (a -> ()) -> NFData a
rnf :: GQLQueryWithText -> ()
$crnf :: GQLQueryWithText -> ()
NFData, (forall x. GQLQueryWithText -> Rep GQLQueryWithText x)
-> (forall x. Rep GQLQueryWithText x -> GQLQueryWithText)
-> Generic GQLQueryWithText
forall x. Rep GQLQueryWithText x -> GQLQueryWithText
forall x. GQLQueryWithText -> Rep GQLQueryWithText x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GQLQueryWithText x -> GQLQueryWithText
$cfrom :: forall x. GQLQueryWithText -> Rep GQLQueryWithText x
Generic, Eq GQLQueryWithText
Eq GQLQueryWithText
-> (Accesses -> GQLQueryWithText -> GQLQueryWithText -> Bool)
-> Cacheable GQLQueryWithText
Accesses -> GQLQueryWithText -> GQLQueryWithText -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> GQLQueryWithText -> GQLQueryWithText -> Bool
$cunchanged :: Accesses -> GQLQueryWithText -> GQLQueryWithText -> Bool
$cp1Cacheable :: Eq GQLQueryWithText
Cacheable, Int -> GQLQueryWithText -> Int
GQLQueryWithText -> Int
(Int -> GQLQueryWithText -> Int)
-> (GQLQueryWithText -> Int) -> Hashable GQLQueryWithText
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: GQLQueryWithText -> Int
$chash :: GQLQueryWithText -> Int
hashWithSalt :: Int -> GQLQueryWithText -> Int
$chashWithSalt :: Int -> GQLQueryWithText -> Int
Hashable)
instance FromJSON GQLQueryWithText where
parseJSON :: Value -> Parser GQLQueryWithText
parseJSON v :: Value
v@(String Text
t) = (Text, GQLQuery) -> GQLQueryWithText
GQLQueryWithText ((Text, GQLQuery) -> GQLQueryWithText)
-> (GQLQuery -> (Text, GQLQuery)) -> GQLQuery -> GQLQueryWithText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text
t,) (GQLQuery -> GQLQueryWithText)
-> Parser GQLQuery -> Parser GQLQueryWithText
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser GQLQuery
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
parseJSON Value
_ = String -> Parser GQLQueryWithText
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"expecting String for GraphQL query"
instance ToJSON GQLQueryWithText where
toJSON :: GQLQueryWithText -> Value
toJSON (GQLQueryWithText (Text
t, GQLQuery
_)) = Text -> Value
String Text
t
getGQLQuery :: GQLQueryWithText -> GQLQuery
getGQLQuery :: GQLQueryWithText -> GQLQuery
getGQLQuery (GQLQueryWithText (Text, GQLQuery)
v) = (Text, GQLQuery) -> GQLQuery
forall a b. (a, b) -> b
snd (Text, GQLQuery)
v
getGQLQueryText :: GQLQueryWithText -> Text
getGQLQueryText :: GQLQueryWithText -> Text
getGQLQueryText (GQLQueryWithText (Text, GQLQuery)
v) = (Text, GQLQuery) -> Text
forall a b. (a, b) -> a
fst (Text, GQLQuery)
v
data ListedQuery = ListedQuery
{ ListedQuery -> QueryName
_lqName :: QueryName,
ListedQuery -> GQLQueryWithText
_lqQuery :: GQLQueryWithText
}
deriving (Int -> ListedQuery -> ShowS
[ListedQuery] -> ShowS
ListedQuery -> String
(Int -> ListedQuery -> ShowS)
-> (ListedQuery -> String)
-> ([ListedQuery] -> ShowS)
-> Show ListedQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListedQuery] -> ShowS
$cshowList :: [ListedQuery] -> ShowS
show :: ListedQuery -> String
$cshow :: ListedQuery -> String
showsPrec :: Int -> ListedQuery -> ShowS
$cshowsPrec :: Int -> ListedQuery -> ShowS
Show, ListedQuery -> ListedQuery -> Bool
(ListedQuery -> ListedQuery -> Bool)
-> (ListedQuery -> ListedQuery -> Bool) -> Eq ListedQuery
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListedQuery -> ListedQuery -> Bool
$c/= :: ListedQuery -> ListedQuery -> Bool
== :: ListedQuery -> ListedQuery -> Bool
$c== :: ListedQuery -> ListedQuery -> Bool
Eq, (forall x. ListedQuery -> Rep ListedQuery x)
-> (forall x. Rep ListedQuery x -> ListedQuery)
-> Generic ListedQuery
forall x. Rep ListedQuery x -> ListedQuery
forall x. ListedQuery -> Rep ListedQuery x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListedQuery x -> ListedQuery
$cfrom :: forall x. ListedQuery -> Rep ListedQuery x
Generic)
instance NFData ListedQuery
instance Cacheable ListedQuery
instance Hashable ListedQuery
$(deriveJSON hasuraJSON ''ListedQuery)
newtype CollectionDef = CollectionDef
{CollectionDef -> [ListedQuery]
_cdQueries :: [ListedQuery]}
deriving (Int -> CollectionDef -> ShowS
[CollectionDef] -> ShowS
CollectionDef -> String
(Int -> CollectionDef -> ShowS)
-> (CollectionDef -> String)
-> ([CollectionDef] -> ShowS)
-> Show CollectionDef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CollectionDef] -> ShowS
$cshowList :: [CollectionDef] -> ShowS
show :: CollectionDef -> String
$cshow :: CollectionDef -> String
showsPrec :: Int -> CollectionDef -> ShowS
$cshowsPrec :: Int -> CollectionDef -> ShowS
Show, CollectionDef -> CollectionDef -> Bool
(CollectionDef -> CollectionDef -> Bool)
-> (CollectionDef -> CollectionDef -> Bool) -> Eq CollectionDef
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CollectionDef -> CollectionDef -> Bool
$c/= :: CollectionDef -> CollectionDef -> Bool
== :: CollectionDef -> CollectionDef -> Bool
$c== :: CollectionDef -> CollectionDef -> Bool
Eq, (forall x. CollectionDef -> Rep CollectionDef x)
-> (forall x. Rep CollectionDef x -> CollectionDef)
-> Generic CollectionDef
forall x. Rep CollectionDef x -> CollectionDef
forall x. CollectionDef -> Rep CollectionDef x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CollectionDef x -> CollectionDef
$cfrom :: forall x. CollectionDef -> Rep CollectionDef x
Generic, CollectionDef -> ()
(CollectionDef -> ()) -> NFData CollectionDef
forall a. (a -> ()) -> NFData a
rnf :: CollectionDef -> ()
$crnf :: CollectionDef -> ()
NFData, Eq CollectionDef
Eq CollectionDef
-> (Accesses -> CollectionDef -> CollectionDef -> Bool)
-> Cacheable CollectionDef
Accesses -> CollectionDef -> CollectionDef -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> CollectionDef -> CollectionDef -> Bool
$cunchanged :: Accesses -> CollectionDef -> CollectionDef -> Bool
$cp1Cacheable :: Eq CollectionDef
Cacheable)
$(deriveJSON hasuraJSON ''CollectionDef)
$(makeLenses ''CollectionDef)
data CreateCollection = CreateCollection
{ CreateCollection -> CollectionName
_ccName :: CollectionName,
CreateCollection -> CollectionDef
_ccDefinition :: CollectionDef,
:: Maybe Text
}
deriving (Int -> CreateCollection -> ShowS
[CreateCollection] -> ShowS
CreateCollection -> String
(Int -> CreateCollection -> ShowS)
-> (CreateCollection -> String)
-> ([CreateCollection] -> ShowS)
-> Show CreateCollection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateCollection] -> ShowS
$cshowList :: [CreateCollection] -> ShowS
show :: CreateCollection -> String
$cshow :: CreateCollection -> String
showsPrec :: Int -> CreateCollection -> ShowS
$cshowsPrec :: Int -> CreateCollection -> ShowS
Show, CreateCollection -> CreateCollection -> Bool
(CreateCollection -> CreateCollection -> Bool)
-> (CreateCollection -> CreateCollection -> Bool)
-> Eq CreateCollection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateCollection -> CreateCollection -> Bool
$c/= :: CreateCollection -> CreateCollection -> Bool
== :: CreateCollection -> CreateCollection -> Bool
$c== :: CreateCollection -> CreateCollection -> Bool
Eq, (forall x. CreateCollection -> Rep CreateCollection x)
-> (forall x. Rep CreateCollection x -> CreateCollection)
-> Generic CreateCollection
forall x. Rep CreateCollection x -> CreateCollection
forall x. CreateCollection -> Rep CreateCollection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateCollection x -> CreateCollection
$cfrom :: forall x. CreateCollection -> Rep CreateCollection x
Generic)
$(deriveJSON hasuraJSON ''CreateCollection)
$()
collectionQueries :: CreateCollection -> [G.ExecutableDocument G.Name]
collectionQueries :: CreateCollection -> [ExecutableDocument Name]
collectionQueries = (ListedQuery -> ExecutableDocument Name)
-> [ListedQuery] -> [ExecutableDocument Name]
forall a b. (a -> b) -> [a] -> [b]
map (GQLQuery -> ExecutableDocument Name
unGQLQuery (GQLQuery -> ExecutableDocument Name)
-> (ListedQuery -> GQLQuery)
-> ListedQuery
-> ExecutableDocument Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GQLQueryWithText -> GQLQuery
getGQLQuery (GQLQueryWithText -> GQLQuery)
-> (ListedQuery -> GQLQueryWithText) -> ListedQuery -> GQLQuery
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ListedQuery -> GQLQueryWithText
_lqQuery) ([ListedQuery] -> [ExecutableDocument Name])
-> (CreateCollection -> [ListedQuery])
-> CreateCollection
-> [ExecutableDocument Name]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CollectionDef -> [ListedQuery]
_cdQueries (CollectionDef -> [ListedQuery])
-> (CreateCollection -> CollectionDef)
-> CreateCollection
-> [ListedQuery]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CreateCollection -> CollectionDef
_ccDefinition
data RenameCollection = RenameCollection
{ RenameCollection -> CollectionName
_rcName :: CollectionName,
RenameCollection -> CollectionName
_rcNewName :: CollectionName
}
deriving (Int -> RenameCollection -> ShowS
[RenameCollection] -> ShowS
RenameCollection -> String
(Int -> RenameCollection -> ShowS)
-> (RenameCollection -> String)
-> ([RenameCollection] -> ShowS)
-> Show RenameCollection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RenameCollection] -> ShowS
$cshowList :: [RenameCollection] -> ShowS
show :: RenameCollection -> String
$cshow :: RenameCollection -> String
showsPrec :: Int -> RenameCollection -> ShowS
$cshowsPrec :: Int -> RenameCollection -> ShowS
Show, RenameCollection -> RenameCollection -> Bool
(RenameCollection -> RenameCollection -> Bool)
-> (RenameCollection -> RenameCollection -> Bool)
-> Eq RenameCollection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RenameCollection -> RenameCollection -> Bool
$c/= :: RenameCollection -> RenameCollection -> Bool
== :: RenameCollection -> RenameCollection -> Bool
$c== :: RenameCollection -> RenameCollection -> Bool
Eq, (forall x. RenameCollection -> Rep RenameCollection x)
-> (forall x. Rep RenameCollection x -> RenameCollection)
-> Generic RenameCollection
forall x. Rep RenameCollection x -> RenameCollection
forall x. RenameCollection -> Rep RenameCollection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RenameCollection x -> RenameCollection
$cfrom :: forall x. RenameCollection -> Rep RenameCollection x
Generic)
$(deriveJSON hasuraJSON ''RenameCollection)
$(makeLenses ''RenameCollection)
data DropCollection = DropCollection
{ DropCollection -> CollectionName
_dcCollection :: CollectionName,
DropCollection -> Bool
_dcCascade :: Bool
}
deriving (Int -> DropCollection -> ShowS
[DropCollection] -> ShowS
DropCollection -> String
(Int -> DropCollection -> ShowS)
-> (DropCollection -> String)
-> ([DropCollection] -> ShowS)
-> Show DropCollection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DropCollection] -> ShowS
$cshowList :: [DropCollection] -> ShowS
show :: DropCollection -> String
$cshow :: DropCollection -> String
showsPrec :: Int -> DropCollection -> ShowS
$cshowsPrec :: Int -> DropCollection -> ShowS
Show, DropCollection -> DropCollection -> Bool
(DropCollection -> DropCollection -> Bool)
-> (DropCollection -> DropCollection -> Bool) -> Eq DropCollection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DropCollection -> DropCollection -> Bool
$c/= :: DropCollection -> DropCollection -> Bool
== :: DropCollection -> DropCollection -> Bool
$c== :: DropCollection -> DropCollection -> Bool
Eq)
$(deriveJSON hasuraJSON ''DropCollection)
data AddQueryToCollection = AddQueryToCollection
{ AddQueryToCollection -> CollectionName
_aqtcCollectionName :: CollectionName,
AddQueryToCollection -> QueryName
_aqtcQueryName :: QueryName,
AddQueryToCollection -> GQLQueryWithText
_aqtcQuery :: GQLQueryWithText
}
deriving (Int -> AddQueryToCollection -> ShowS
[AddQueryToCollection] -> ShowS
AddQueryToCollection -> String
(Int -> AddQueryToCollection -> ShowS)
-> (AddQueryToCollection -> String)
-> ([AddQueryToCollection] -> ShowS)
-> Show AddQueryToCollection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddQueryToCollection] -> ShowS
$cshowList :: [AddQueryToCollection] -> ShowS
show :: AddQueryToCollection -> String
$cshow :: AddQueryToCollection -> String
showsPrec :: Int -> AddQueryToCollection -> ShowS
$cshowsPrec :: Int -> AddQueryToCollection -> ShowS
Show, AddQueryToCollection -> AddQueryToCollection -> Bool
(AddQueryToCollection -> AddQueryToCollection -> Bool)
-> (AddQueryToCollection -> AddQueryToCollection -> Bool)
-> Eq AddQueryToCollection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddQueryToCollection -> AddQueryToCollection -> Bool
$c/= :: AddQueryToCollection -> AddQueryToCollection -> Bool
== :: AddQueryToCollection -> AddQueryToCollection -> Bool
$c== :: AddQueryToCollection -> AddQueryToCollection -> Bool
Eq)
$(deriveJSON hasuraJSON ''AddQueryToCollection)
data DropQueryFromCollection = DropQueryFromCollection
{ DropQueryFromCollection -> CollectionName
_dqfcCollectionName :: CollectionName,
DropQueryFromCollection -> QueryName
_dqfcQueryName :: QueryName
}
deriving (Int -> DropQueryFromCollection -> ShowS
[DropQueryFromCollection] -> ShowS
DropQueryFromCollection -> String
(Int -> DropQueryFromCollection -> ShowS)
-> (DropQueryFromCollection -> String)
-> ([DropQueryFromCollection] -> ShowS)
-> Show DropQueryFromCollection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DropQueryFromCollection] -> ShowS
$cshowList :: [DropQueryFromCollection] -> ShowS
show :: DropQueryFromCollection -> String
$cshow :: DropQueryFromCollection -> String
showsPrec :: Int -> DropQueryFromCollection -> ShowS
$cshowsPrec :: Int -> DropQueryFromCollection -> ShowS
Show, DropQueryFromCollection -> DropQueryFromCollection -> Bool
(DropQueryFromCollection -> DropQueryFromCollection -> Bool)
-> (DropQueryFromCollection -> DropQueryFromCollection -> Bool)
-> Eq DropQueryFromCollection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DropQueryFromCollection -> DropQueryFromCollection -> Bool
$c/= :: DropQueryFromCollection -> DropQueryFromCollection -> Bool
== :: DropQueryFromCollection -> DropQueryFromCollection -> Bool
$c== :: DropQueryFromCollection -> DropQueryFromCollection -> Bool
Eq)
$(deriveJSON hasuraJSON ''DropQueryFromCollection)
type QueryCollections = InsOrdHashMap CollectionName CreateCollection